[Haskell-cafe] [] vs [()]

Daryoush Mehrtash dmehrtash at gmail.com
Fri Oct 10 13:59:28 EDT 2008


I was in fact trying to figure out how "guard" worked in the "do".    The
interesting  (for a beginner) insight is that:

[()]  map f = [f]  --( just as any list with one element would have been
such as [1] map f = [f] )   where as

[] map f = []


so if your guard computes to [()]  (or any list of one element) the
following steps in the do  would continue.  Where as if it computes to an
empty list then following steps are not executed.


daryoush


On Fri, Oct 10, 2008 at 6:33 AM, Ryan Ingram <ryani.spam at gmail.com> wrote:

> (This is a literate haskell post, save into SMM.lhs and load in ghci!)
>
> Here's one place you might use [()] and []:
>
> > guard :: Bool -> [()]
> > guard True = [()]
> > guard False = []
>
> You can then use "guard" in monadic list computations to abort the
> computation on some branches:
>
> > sendmoney :: [[Int]]
> > sendmoney = do
> >    choice@[s,e,n,d,m,o,r,y] <- generate 8 [0..9]
> >    guard (s /= 0)
> >    guard (m /= 0)
> >    guard (val [s,e,n,d] + val [m,o,r,e] == val [m,o,n,e,y])
> >    return choice
>
> (evaluating this in ghci takes a little while, but it does succeed!
> You can easily optimize by noticing that m must be equal to 1 and
> therefore s must be 8 or 9.)
>
> Using guard in this way works because of the definition of bind on lists:
>
>    xs >>= f  =  concatMap f xs = concat (map f xs)
>
> Consider a simpler example:
>
> > simple = do
> >    x <- [1,2,3]
> >    guard (x /= 2)
> >    return x
>
> This is the same as
>     [1,2,3] >>= \x ->
>     guard (x /= 2) >>= \_ ->
>     return x
>
> = mapConcat (\x -> mapConcat (\_ -> return x) (guard (x /= 2))) [1,2,3]
> = concat
>     [ mapConcat (\_ -> return 1) (guard (1 /= 2))
>     , mapConcat (\_ -> return 2) (guard (2 /= 2))
>     , mapConcat (\_ -> return 3) (guard (3 /= 2))
>     ]
> = concat
>     [ mapConcat (\_ -> return 1) [()]
>     , mapConcat (\_ -> return 2) []
>     , mapConcat (\_ -> return 3) [()]
>     ]
> = concat
>     [ concat [ [1] ]
>     , concat []
>     , concat [ [3] ]
>     ]
> = concat [ [1], [], [3] ]
> = [1,3]
>
> Another fun example:
>
> > double :: [()]
> > double = [(), ()]
>
> > sixteen:: Int
> > sixteen = length $ do
> >    double
> >    double
> >    double
> >    double
>
> Helper code for "send more money" follows...
>
> > generate :: Int -> [a] -> [[a]]
> > generate 0 _ = return []
> > generate n as = do
> >    (x,xs) <- select as
> >    rest <- generate (n-1) xs
> >    return (x:rest)
>
> > select :: [a] -> [(a,[a])]
> > select [] = []
> > select [x] = return (x,[])
> > select (x:xs) = (x,xs) : [ (y, x:ys) | (y,ys) <- select xs ]
>
> > val xs = val' 0 xs where
> >    val' v [] = v
> >    val' v (x:xs) = val' (10*v + x) xs
>




Weblog:  http://perlustration.blogspot.com/
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20081010/cf968e0f/attachment.htm


More information about the Haskell-Cafe mailing list