On Mon, May 23, 2011 at 10:49:55AM -0700, Alexander Solla wrote:
> On Mon, May 23, 2011 at 9:20 AM, michael rice <nowg...@yahoo.com> wrote:
> 
> > What's the best way to end up with a list composed of only the Just values,
> > no Nothings?
> >
> > Michael
> >
> > ==========================
> >
> > import Control.Monad.State
> > import Data.Maybe
> >
> >
> > type GeneratorState = State Int
> >
> > tick :: GeneratorState (Maybe Int)
> > tick = do n <- get
> >           if ((n `mod` 7) == 0)
> >             then
> >               return Nothing
> >             else do
> >               put (n+1)
> >               return (Just n)
> >
> > {-
> > *Main> evalState (sequence $ replicate 9 tick) 1
> > [Just 1,Just 2,Just 3,Just 4,Just 5,Just 6,Nothing,Nothing,Nothing]
> > -}
> >
> >
> There's a library function for it, but also:
> 
> > filter ((/=) Nothing)
> 
> is readable enough.

Just a minor quibble: note that

> filter (not . isNothing)

is slightly preferable since it does not introduce a frivolous
equality constraint on the type wrapped by the Maybe.

-Brent

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to