Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Is it possible to use a bracketing syntactic sugar for an applicative functor?

Tags:

In McBride and Paterson's 'Applicative programming with effects' they introduce some lovely syntactic sugar for lifting a pure function:

[| f x y z |]

for

f <$> x <*> y <*> z

and I recall someone somewhere else using li f w x y z il or il f v w x y z li, and I thought/hoped that might be because it could be defined using some existing language feature and cunning definition of li and il.

I can't find any reference to this beyond the paper, and assuming that [| and |] aren't likely to turn up in ghc any time soon, is it possible to implement li and il somehow? I can't think of a sensible type for them, so I assume I'd need Template Haskell or similar, but don't know nearly enough to accomplish this. [af| f x y ] would be fine, but I don't know whether it's possible before I start attempting it, and certainly need help if it is.

like image 929
AndrewC Avatar asked Aug 17 '12 23:08

AndrewC


2 Answers

I think this is what you are looking for. If I remember correctly there has also been a discussion on the haskell-cafe mailing list regarding this style of applicative applications.

like image 96
Jan Christiansen Avatar answered Sep 27 '22 16:09

Jan Christiansen


This is pretty easy to implement in Template Haskell by using the haskell-src-meta package to parse the Haskell expression in the quasi-quotation.

{-# LANGUAGE TemplateHaskell #-}

import Language.Haskell.TH
import Language.Haskell.TH.Quote
import Language.Haskell.Meta (parseExp)

import Control.Applicative ((<*>), (<$>))

af = QuasiQuoter
    { quoteExp  = parseAf
    , quotePat  = undefined
    , quoteType = undefined
    , quoteDec  = undefined
    }

parseAf :: String -> Q Exp
parseAf s = case parseExp s of
    Right ex -> applyExp ex
    Left err -> fail err

applyExp :: Exp -> Q Exp
applyExp (AppE f@(AppE _ _) a) = [|$(applyExp f) <*> $(return a)|]
applyExp (AppE f a) = [|$(return f) <$> $(return a)|]
applyExp _ = fail "invalid expression in af"

Note that due to how Template Haskell works, you can't use the quasiquoter from the same file where it's defined, so save the above to its own module.

Testing in GHCi

*Main> :set -XTemplateHaskell
*Main> :set -XQuasiQuotes
*Main> [af|(+) (Just 3) (Just 8)|]
Just 11
*Main> [af|(+) (Just 6) Nothing|]
Nothing
like image 40
shang Avatar answered Sep 27 '22 16:09

shang