module StrQuote (str) where
import Language.Haskell.TH (Pat(LitP), Type(LitT), stringE, Lit(StringL), TyLit(StrTyLit))
import Language.Haskell.TH.Quote (QuasiQuoter(..))
str :: QuasiQuoter
str :: QuasiQuoter
str = QuasiQuoter
{ quoteExp :: String -> Q Exp
quoteExp = forall (m :: * -> *). Quote m => String -> m Exp
stringE
, quotePat :: String -> Q Pat
quotePat = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lit -> Pat
LitP forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Lit
StringL
, quoteType :: String -> Q Type
quoteType = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. TyLit -> Type
LitT forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> TyLit
StrTyLit
, quoteDec :: String -> Q [Dec]
quoteDec = forall a b. a -> b -> a
const (forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"str is for expressions")
}