applicative-quoters-0.1.0.1: Quasiquoters for idiom brackets and an applicative do-notation

Control.Applicative.QQ.ADo

Contents

Description

Applicative do. Philippa 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')]

Notice that the last statement is not of an applicative type, so when translating from monadic do, drop the final return:

 (do x <- [1,2,3]; return (x + 1)) == [$ado| x <- [1,2,3]; x + 1 |]

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

Caveats

Template Haskell is currently unable to reliably look up constructor names just from a string: if there is a type with the same name, it will return information for that instead. This means that the safe version of ado is prone to failure where types and values share names. It tries to make a "best guess" in the common case that type and constructor have the same name, but has nontrivial failure modes. In such cases, ado' should work fine: at a pinch, you can bind simple variables with it and case-match on them in your last statement.

See also: http://hackage.haskell.org/trac/ghc/ticket/4429