Suppose there's a handy library for parsing things. It exports a function parseThing
along with some types and helpers:
module Text.Thing.Parser
( Thing ()
, parseThing
, ParseError
-- ...
) where
-- ...
data Thing = {- implementation -}
parseThing :: String -> Either ParseError Thing
parseThing = {- implementation -}
I decide to write a wrapper library which enables parsing things at the compile-time.
{-# LANGUAGE TemplateHaskell #-}
module Text.Thing.Parser.TH where
import Text.Thing.Parser
import Language.Haskell.TH
import Language.Haskell.TH.Quote
thingExpr :: String -> Q Exp
thingExpr src = do
case parseThing src of
Left err -> fail $ show err
Right thing -> [| thing |]
thing :: QuasiQuoter
thing = QuasiQuoter { quoteExp = thingExpr
, quoteDec = undefined
, quotePat = undefined
, quoteType = undefined
}
Compilation fails with No instance (Lift Thing)
error, but I cannot add the instance declaration, because Thing
is an abstract datatype I don't have access to: it is defined elsewhere and no constructors are exported. And since I'm new to Template Haskell, I can't come up with a solution other than lifting a local variable (if there is any).
So how do I define thingExpr
? Thanks.