haskell-src-meta-0.2: Parse source to template-haskell abstract syntax.

Language.Haskell.Meta.QQ.ADo

Contents

Description

Applicative do. Phillipa Cowderoy's idea, some explanations due Edward Kmett

Pointful version of Language.Haskell.Meta.QQ.Idiom. Note the only expression which has the bound variables in scope is the last one.

This lets you work with applicatives without the order of fields in an data constructor becoming such a burden.

In a similar role as fail in do notation, if match failures can be expected, the result is an Applicative f => f (Maybe a), rather than Applicative f => f a, where a may be partially defined.

Synopsis

Documentation

ado :: QuasiQuoterSource

Usage:

 ghci> [$ado| a <- "foo"; b <- "bar"; (a,b) |]
 [('f','b'),('f','a'),('f','r'),('o','b'),('o','a'),('o','r'),('o','b'),('o','a'),('o','r')]
 ghci> [$ado| Just a <- [Just 1,Nothing,Just 2]; b <- "fo"; (a,b) |]
 [Just (1,'f'),Just (1,'o'),Nothing,Nothing,Just (2,'f'),Just (2,'o')]

ado' :: QuasiQuoterSource

Variant of ado that does not implicitly add a Maybe when patterns may fail:

 ghci> [$ado'| Just a <- [Just 1,Nothing,Just 2]; b <- "fo"; (a,b) |]
 [(1,'f'),(1,'o'),*** Exception: <interactive>:...

Desugaring

If you use patterns that may fail:

 foo :: Applicative f => f (Maybe T)
 foo = [$ado|
    x:xs <- foo bar baz
    Just y <- quux quaffle
    T x y |]

ado desugars to:

 foo = (\x y -> case (x,y) of
                    (x:xs,Just y) -> Just $ T x y
                    _ -> Nothing
        ) <$> foo bar baz <*> quux quaffle

While ado' desugars to the less safe:

 foo = (\(x:xs) (Just y) -> T x y) <$> foo bar baz <*> quux quaffle

If the simple patterns cannot fail, there is no Maybe for the ado quote, just like ado':

 newtype A = A Int
 foo :: Applicative f => f T
 foo = [$ado|
    ~(x:xs) <- foo bar baz
    A y <- quux quaffle
    T x y |]

Becomes:

 foo = (\ ~(x:xs) (A y) -> T x y) <$> foo bar baz <*> quux quaffle