[Haskell-cafe] version of findIndex that works with a monadic predicate

Miguel Mitrofanov miguelimo38 at yandex.ru
Sat Nov 27 00:23:06 CET 2010


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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 



More information about the Haskell-Cafe mailing list