module Control.Applicative.QQ.Idiom (i) where
import Control.Applicative ((<*>), pure)
import Control.Monad ((<=<))
import Language.Haskell.Meta (parseExp)
import Language.Haskell.TH.Lib
import Language.Haskell.TH.Quote
import Language.Haskell.TH.Syntax
i :: QuasiQuoter
i = QuasiQuoter { quoteExp = applicate <=< either fail return . parseExp,
quotePat = nonsense "pattern",
quoteType = nonsense "type",
quoteDec = nonsense "dec" }
where
nonsense context = fail $ "You can't use idiom brackets in " ++ context ++
" context, that doesn't even make sense."
applicate :: Exp -> ExpQ
applicate (AppE f x) =
[| $(applicate f) <*> $(return x) |]
applicate (InfixE (Just left) op (Just right)) =
[| pure $(return op) <*> $(return left) <*> $(return right) |]
applicate (UInfixE left op right) = case (left,right) of
(UInfixE{}, _) -> ambig
(_, UInfixE{}) -> ambig
(_, _) -> [| pure $(return op) <*> $(return left) <*> $(return right) |]
where
ambig = fail "Ambiguous infix expression in idiom bracket."
applicate x = [| pure $(return x) |]