version of findIndex that works with a monadic predicate

Hello. I need a function findIndexM, similar to findIndex from the standard module Data.List, but which works with a monadic predicate to test list elements. findIndex :: (a -> Bool) -> [a] -> Maybe Int findIndexM :: (Monad m, Num a) => (t -> m Bool) -> [t] -> m (Maybe a) findIndexM p xs = go 0 xs where go _ [] = return Nothing go n (x:xs) = do res <- p x if res then return (Just n) else go (n+1) xs How can this function be rewritten using combinators? Romildo

findIndexM = (liftM (findIndex id) .) . mapM On 26 Nov 2010, at 22:46, José Romildo Malaquias wrote:
Hello.
I need a function findIndexM, similar to findIndex from the standard module Data.List, but which works with a monadic predicate to test list elements.
findIndex :: (a -> Bool) -> [a] -> Maybe Int
findIndexM :: (Monad m, Num a) => (t -> m Bool) -> [t] -> m (Maybe a)
findIndexM p xs = go 0 xs where go _ [] = return Nothing go n (x:xs) = do res <- p x if res then return (Just n) else go (n+1) xs
How can this function be rewritten using combinators?
Romildo _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, 2010-11-27 at 02:23 +0300, Miguel Mitrofanov wrote:
findIndexM = (liftM (findIndex id) .) . mapM
Not quite. Compare: findIndexM (\x -> print x >> return True) [1,2,3] or findIndexM (\x -> if x == 2 then Nothing else Just True) [1,2,3] Possibly better: findIndexM p = foldr (\(n, y) x -> p y >>= \b -> if b then return $! Just $! n else x) (return $! Nothing) . zip (map fromIntegral [1..])) Regards
participants (3)
-
José Romildo Malaquias
-
Maciej Piechotka
-
Miguel Mitrofanov