module FFICXX.Generate.QQ.Verbatim where
import Language.Haskell.TH.Lib
( litE,
stringL,
)
import Language.Haskell.TH.Quote
( QuasiQuoter (..),
quoteDec,
quoteExp,
quotePat,
quoteType,
)
verbatim :: QuasiQuoter
verbatim :: QuasiQuoter
verbatim =
QuasiQuoter
{ quoteExp :: String -> Q Exp
quoteExp = forall (m :: * -> *). Quote m => Lit -> m Exp
litE forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Lit
stringL,
quotePat :: String -> Q Pat
quotePat = forall a. HasCallStack => a
undefined,
quoteType :: String -> Q Type
quoteType = forall a. HasCallStack => a
undefined,
quoteDec :: String -> Q [Dec]
quoteDec = forall a. HasCallStack => a
undefined
}