{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
module Language.Haskell.TH.TestUtils
(
tryQ'
, tryQ
, tryQErr
, tryQErr'
) where
import Control.Monad ((>=>))
import qualified Control.Monad.Fail as Fail
#if MIN_VERSION_template_haskell(2,13,0)
import Control.Monad.IO.Class (MonadIO)
#endif
import qualified Control.Monad.Trans.Class as Trans
import Control.Monad.Trans.Except (ExceptT, catchE, runExceptT, throwE)
import Control.Monad.Trans.State (StateT, put, runStateT)
import Language.Haskell.TH (Exp, Q, appE, runQ)
#if MIN_VERSION_template_haskell(2,12,0)
import qualified Language.Haskell.TH as TH
#endif
import Language.Haskell.TH.Syntax (Quasi(..), lift)
newtype TryQ a = TryQ { unTryQ :: ExceptT () (StateT (Maybe String) Q) a }
deriving
( Functor
, Applicative
, Monad
#if MIN_VERSION_template_haskell(2,13,0)
, MonadIO
#endif
)
liftQ :: Q a -> TryQ a
liftQ = TryQ . Trans.lift . Trans.lift
instance Fail.MonadFail TryQ where
fail _ = TryQ $ throwE ()
instance Quasi TryQ where
qNewName name = liftQ $ qNewName name
qReport False msg = liftQ $ qReport False msg
qReport True msg = TryQ . Trans.lift . put $ Just msg
qRecover (TryQ handler) (TryQ action) = TryQ $ catchE action (const handler)
qLookupName b name = liftQ $ qLookupName b name
qReify name = liftQ $ qReify name
qReifyFixity name = liftQ $ qReifyFixity name
qReifyInstances name types = liftQ $ qReifyInstances name types
qReifyRoles name = liftQ $ qReifyRoles name
qReifyAnnotations ann = liftQ $ qReifyAnnotations ann
qReifyModule m = liftQ $ qReifyModule m
qReifyConStrictness name = liftQ $ qReifyConStrictness name
qLocation = liftQ qLocation
qRunIO m = liftQ $ qRunIO m
qAddDependentFile fp = liftQ $ qAddDependentFile fp
qAddTopDecls decs = liftQ $ qAddTopDecls decs
qAddModFinalizer q = liftQ $ qAddModFinalizer q
qGetQ = liftQ qGetQ
qPutQ x = liftQ $ qPutQ x
qIsExtEnabled ext = liftQ $ qIsExtEnabled ext
qExtsEnabled = liftQ qExtsEnabled
#if MIN_VERSION_template_haskell(2,13,0)
qAddCorePlugin s = liftQ $ qAddCorePlugin s
#endif
#if MIN_VERSION_template_haskell(2,14,0)
qAddTempFile s = liftQ $ qAddTempFile s
qAddForeignFilePath lang s = liftQ $ qAddForeignFilePath lang s
#elif MIN_VERSION_template_haskell(2,12,0)
qAddForeignFile lang s = liftQ $ qAddForeignFile lang s
#endif
#if MIN_VERSION_template_haskell(2,16,0)
qReifyType n = liftQ $ qReifyType n
#endif
tryQ' :: Q a -> Q (Either String a)
tryQ' = fmap cast . (`runStateT` Nothing) . runExceptT . unTryQ . runQ
where
cast (Left (), Nothing) = Left "Q monad failure"
cast (Left (), Just msg) = Left msg
cast (Right a, _) = Right a
tryQ :: Q Exp -> Q Exp
tryQ = tryQ' >=> either
(appE (typeAppString [| Left |]) . lift)
(appE (typeAppString [| Right |]) . pure)
tryQErr :: Q a -> Q Exp
tryQErr = tryQ' >=> either
(appE (typeAppString [| Just |]) . lift)
(const (typeAppString [| Nothing |]))
tryQErr' :: Q a -> Q Exp
tryQErr' = tryQ' >=> either
lift
(const $ fail "Q monad unexpectedly succeeded")
typeAppString :: Q Exp -> Q Exp
typeAppString expQ =
#if MIN_VERSION_template_haskell(2,12,0)
TH.appTypeE expQ [t| String |]
#else
expQ
#endif