{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Language.Haskell.TH.TestUtils (
QState (..),
MockedMode (..),
QMode (..),
ReifyInfo (..),
loadNames,
unmockedState,
runTestQ,
runTestQErr,
tryTestQ,
) where
import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.Trans.Class (lift)
import qualified Control.Monad.Trans.Except as Except
import qualified Control.Monad.Trans.Reader as Reader
import qualified Control.Monad.Trans.State as State
import Data.Maybe (fromMaybe)
import Language.Haskell.TH (Name, Q, runIO, runQ)
import Language.Haskell.TH.Syntax (Quasi (..), mkNameU)
import Language.Haskell.TH.TestUtils.QMode
import Language.Haskell.TH.TestUtils.QState
runTestQ :: forall mode a. IsMockedMode mode => QState mode -> Q a -> TestQResult mode a
runTestQ :: forall (mode :: MockedMode) a.
IsMockedMode mode =>
QState mode -> Q a -> TestQResult mode a
runTestQ QState mode
state = (Either String a -> a)
-> TestQResult mode (Either String a) -> TestQResult mode a
fmapResult' (forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a. HasCallStack => String -> a
error forall a. a -> a
id) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (mode :: MockedMode) a.
IsMockedMode mode =>
QState mode -> Q a -> TestQResult mode (Either String a)
tryTestQ QState mode
state
where
fmapResult' :: (Either String a -> a)
-> TestQResult mode (Either String a) -> TestQResult mode a
fmapResult' = forall (mode :: MockedMode) a b.
IsMockedMode mode =>
(a -> b) -> TestQResult mode a -> TestQResult mode b
fmapResult @mode @(Either String a) @a
runTestQErr :: forall mode a. (IsMockedMode mode, Show a) => QState mode -> Q a -> TestQResult mode String
runTestQErr :: forall (mode :: MockedMode) a.
(IsMockedMode mode, Show a) =>
QState mode -> Q a -> TestQResult mode String
runTestQErr QState mode
state = (Either String a -> String)
-> TestQResult mode (Either String a) -> TestQResult mode String
fmapResult' (forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a. a -> a
id (forall a. HasCallStack => String -> a
error forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. Show a => a -> String
mkMsg)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (mode :: MockedMode) a.
IsMockedMode mode =>
QState mode -> Q a -> TestQResult mode (Either String a)
tryTestQ QState mode
state
where
fmapResult' :: (Either String a -> String)
-> TestQResult mode (Either String a) -> TestQResult mode String
fmapResult' = forall (mode :: MockedMode) a b.
IsMockedMode mode =>
(a -> b) -> TestQResult mode a -> TestQResult mode b
fmapResult @mode @(Either String a) @String
mkMsg :: a -> String
mkMsg a
a = String
"Unexpected success: " forall a. [a] -> [a] -> [a]
++ forall {a}. Show a => a -> String
show a
a
tryTestQ :: forall mode a. IsMockedMode mode => QState mode -> Q a -> TestQResult mode (Either String a)
tryTestQ :: forall (mode :: MockedMode) a.
IsMockedMode mode =>
QState mode -> Q a -> TestQResult mode (Either String a)
tryTestQ QState mode
state = forall (mode :: MockedMode) a.
IsMockedMode mode =>
Q a -> TestQResult mode a
runResult @mode forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestQ mode a -> Q (Either String a)
runTestQMonad forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Quasi m => Q a -> m a
runQ
where
runTestQMonad :: TestQ mode a -> Q (Either String a)
runTestQMonad =
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
Except.runExceptT
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
`State.evalStateT` InternalState
initialInternalState)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
`Reader.runReaderT` QState mode
state)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (mode :: MockedMode) a.
TestQ mode a
-> ReaderT
(QState mode) (StateT InternalState (ExceptT String Q)) a
unTestQ
initialInternalState :: InternalState
initialInternalState =
InternalState
{ lastErrorReport :: Maybe String
lastErrorReport = forall a. Maybe a
Nothing
, newNameCounter :: Int
newNameCounter = Int
0
}
data InternalState = InternalState
{ InternalState -> Maybe String
lastErrorReport :: Maybe String
, InternalState -> Int
newNameCounter :: Int
}
newtype TestQ (mode :: MockedMode) a = TestQ
{ forall (mode :: MockedMode) a.
TestQ mode a
-> ReaderT
(QState mode) (StateT InternalState (ExceptT String Q)) a
unTestQ ::
Reader.ReaderT
(QState mode)
( State.StateT
InternalState
( Except.ExceptT
String
Q
)
)
a
}
deriving (forall a b. a -> TestQ mode b -> TestQ mode a
forall a b. (a -> b) -> TestQ mode a -> TestQ mode b
forall (mode :: MockedMode) a b. a -> TestQ mode b -> TestQ mode a
forall (mode :: MockedMode) a b.
(a -> b) -> TestQ mode a -> TestQ mode b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> TestQ mode b -> TestQ mode a
$c<$ :: forall (mode :: MockedMode) a b. a -> TestQ mode b -> TestQ mode a
fmap :: forall a b. (a -> b) -> TestQ mode a -> TestQ mode b
$cfmap :: forall (mode :: MockedMode) a b.
(a -> b) -> TestQ mode a -> TestQ mode b
Functor, forall a. a -> TestQ mode a
forall a b. TestQ mode a -> TestQ mode b -> TestQ mode a
forall a b. TestQ mode a -> TestQ mode b -> TestQ mode b
forall a b. TestQ mode (a -> b) -> TestQ mode a -> TestQ mode b
forall a b c.
(a -> b -> c) -> TestQ mode a -> TestQ mode b -> TestQ mode c
forall (mode :: MockedMode). Functor (TestQ mode)
forall (mode :: MockedMode) a. a -> TestQ mode a
forall (mode :: MockedMode) a b.
TestQ mode a -> TestQ mode b -> TestQ mode a
forall (mode :: MockedMode) a b.
TestQ mode a -> TestQ mode b -> TestQ mode b
forall (mode :: MockedMode) a b.
TestQ mode (a -> b) -> TestQ mode a -> TestQ mode b
forall (mode :: MockedMode) a b c.
(a -> b -> c) -> TestQ mode a -> TestQ mode b -> TestQ mode c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
<* :: forall a b. TestQ mode a -> TestQ mode b -> TestQ mode a
$c<* :: forall (mode :: MockedMode) a b.
TestQ mode a -> TestQ mode b -> TestQ mode a
*> :: forall a b. TestQ mode a -> TestQ mode b -> TestQ mode b
$c*> :: forall (mode :: MockedMode) a b.
TestQ mode a -> TestQ mode b -> TestQ mode b
liftA2 :: forall a b c.
(a -> b -> c) -> TestQ mode a -> TestQ mode b -> TestQ mode c
$cliftA2 :: forall (mode :: MockedMode) a b c.
(a -> b -> c) -> TestQ mode a -> TestQ mode b -> TestQ mode c
<*> :: forall a b. TestQ mode (a -> b) -> TestQ mode a -> TestQ mode b
$c<*> :: forall (mode :: MockedMode) a b.
TestQ mode (a -> b) -> TestQ mode a -> TestQ mode b
pure :: forall a. a -> TestQ mode a
$cpure :: forall (mode :: MockedMode) a. a -> TestQ mode a
Applicative, forall a. a -> TestQ mode a
forall a b. TestQ mode a -> TestQ mode b -> TestQ mode b
forall a b. TestQ mode a -> (a -> TestQ mode b) -> TestQ mode b
forall (mode :: MockedMode). Applicative (TestQ mode)
forall (mode :: MockedMode) a. a -> TestQ mode a
forall (mode :: MockedMode) a b.
TestQ mode a -> TestQ mode b -> TestQ mode b
forall (mode :: MockedMode) a b.
TestQ mode a -> (a -> TestQ mode b) -> TestQ mode b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> TestQ mode a
$creturn :: forall (mode :: MockedMode) a. a -> TestQ mode a
>> :: forall a b. TestQ mode a -> TestQ mode b -> TestQ mode b
$c>> :: forall (mode :: MockedMode) a b.
TestQ mode a -> TestQ mode b -> TestQ mode b
>>= :: forall a b. TestQ mode a -> (a -> TestQ mode b) -> TestQ mode b
$c>>= :: forall (mode :: MockedMode) a b.
TestQ mode a -> (a -> TestQ mode b) -> TestQ mode b
Monad)
getState :: TestQ mode (QState mode)
getState :: forall (mode :: MockedMode). TestQ mode (QState mode)
getState = forall (mode :: MockedMode) a.
ReaderT (QState mode) (StateT InternalState (ExceptT String Q)) a
-> TestQ mode a
TestQ forall (m :: * -> *) r. Monad m => ReaderT r m r
Reader.ask
getMode :: TestQ mode (QMode mode)
getMode :: forall (mode :: MockedMode). TestQ mode (QMode mode)
getMode = forall (mode :: MockedMode). QState mode -> QMode mode
mode forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (mode :: MockedMode). TestQ mode (QState mode)
getState
lookupReifyInfo :: (ReifyInfo -> a) -> Name -> TestQ mode a
lookupReifyInfo :: forall a (mode :: MockedMode).
(ReifyInfo -> a) -> Name -> TestQ mode a
lookupReifyInfo ReifyInfo -> a
f Name
name = do
QState{[(Name, ReifyInfo)]
reifyInfo :: forall (mode :: MockedMode). QState mode -> [(Name, ReifyInfo)]
reifyInfo :: [(Name, ReifyInfo)]
reifyInfo} <- forall (mode :: MockedMode). TestQ mode (QState mode)
getState
case forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Name
name [(Name, ReifyInfo)]
reifyInfo of
Just ReifyInfo
info -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ReifyInfo -> a
f ReifyInfo
info
Maybe ReifyInfo
Nothing -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Cannot reify " forall a. [a] -> [a] -> [a]
++ forall {a}. Show a => a -> String
show Name
name forall a. [a] -> [a] -> [a]
++ String
" (did you mean to add it to reifyInfo?)"
getLastError :: TestQ mode (Maybe String)
getLastError :: forall (mode :: MockedMode). TestQ mode (Maybe String)
getLastError = forall (mode :: MockedMode) a.
ReaderT (QState mode) (StateT InternalState (ExceptT String Q)) a
-> TestQ mode a
TestQ forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s a. Monad m => (s -> a) -> StateT s m a
State.gets InternalState -> Maybe String
lastErrorReport
storeLastError :: String -> TestQ mode ()
storeLastError :: forall (mode :: MockedMode). String -> TestQ mode ()
storeLastError String
msg = forall (mode :: MockedMode) a.
ReaderT (QState mode) (StateT InternalState (ExceptT String Q)) a
-> TestQ mode a
TestQ forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s. Monad m => (s -> s) -> StateT s m ()
State.modify (\InternalState
state -> InternalState
state{lastErrorReport :: Maybe String
lastErrorReport = forall a. a -> Maybe a
Just String
msg})
getAndIncrementNewNameCounter :: TestQ mode Int
getAndIncrementNewNameCounter :: forall (mode :: MockedMode). TestQ mode Int
getAndIncrementNewNameCounter = forall (mode :: MockedMode) a.
ReaderT (QState mode) (StateT InternalState (ExceptT String Q)) a
-> TestQ mode a
TestQ forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
State.state forall a b. (a -> b) -> a -> b
$ \InternalState
state ->
let n :: Int
n = InternalState -> Int
newNameCounter InternalState
state
in (Int
n, InternalState
state{newNameCounter :: Int
newNameCounter = Int
n forall a. Num a => a -> a -> a
+ Int
1})
throwError :: String -> TestQ mode a
throwError :: forall (mode :: MockedMode) a. String -> TestQ mode a
throwError = forall (mode :: MockedMode) a.
ReaderT (QState mode) (StateT InternalState (ExceptT String Q)) a
-> TestQ mode a
TestQ forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a. Monad m => e -> ExceptT e m a
Except.throwE
catchError :: TestQ mode a -> (String -> TestQ mode a) -> TestQ mode a
catchError :: forall (mode :: MockedMode) a.
TestQ mode a -> (String -> TestQ mode a) -> TestQ mode a
catchError (TestQ ReaderT (QState mode) (StateT InternalState (ExceptT String Q)) a
action) String -> TestQ mode a
handler = forall (mode :: MockedMode) a.
ReaderT (QState mode) (StateT InternalState (ExceptT String Q)) a
-> TestQ mode a
TestQ forall a b. (a -> b) -> a -> b
$ forall {e} {r} {s} {a}.
Catch e (ReaderT r (StateT s (ExceptT e Q))) a
catchE' ReaderT (QState mode) (StateT InternalState (ExceptT String Q)) a
action (forall (mode :: MockedMode) a.
TestQ mode a
-> ReaderT
(QState mode) (StateT InternalState (ExceptT String Q)) a
unTestQ forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> TestQ mode a
handler)
where
catchE' :: Catch e (ReaderT r (StateT s (ExceptT e Q))) a
catchE' = forall e (m :: * -> *) a r. Catch e m a -> Catch e (ReaderT r m) a
Reader.liftCatch (forall e (m :: * -> *) a s.
Catch e m (a, s) -> Catch e (StateT s m) a
State.liftCatch forall (m :: * -> *) e a e'.
Monad m =>
ExceptT e m a -> (e -> ExceptT e' m a) -> ExceptT e' m a
Except.catchE)
liftQ :: Q a -> TestQ mode a
liftQ :: forall a (mode :: MockedMode). Q a -> TestQ mode a
liftQ = forall (mode :: MockedMode) a.
ReaderT (QState mode) (StateT InternalState (ExceptT String Q)) a
-> TestQ mode a
TestQ forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift
instance MonadIO (TestQ mode) where
liftIO :: forall a. IO a -> TestQ mode a
liftIO = forall a (mode :: MockedMode). Q a -> TestQ mode a
liftQ forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IO a -> Q a
runIO
instance MonadFail (TestQ mode) where
fail :: forall a. String -> TestQ mode a
fail String
msg = do
Maybe String
lastMessage <- forall (mode :: MockedMode). TestQ mode (Maybe String)
getLastError
forall (mode :: MockedMode) a. String -> TestQ mode a
throwError forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a -> a
fromMaybe String
msg Maybe String
lastMessage
use :: Override mode a -> TestQ mode a
use :: forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use Override{Q a
WhenMocked mode a
whenMocked :: forall (mode :: MockedMode) a. Override mode a -> WhenMocked mode a
whenAllowed :: forall (mode :: MockedMode) a. Override mode a -> Q a
whenMocked :: WhenMocked mode a
whenAllowed :: Q a
..} = do
QMode mode
mode <- forall (mode :: MockedMode). TestQ mode (QMode mode)
getMode
case (QMode mode
mode, WhenMocked mode a
whenMocked) of
(QMode mode
AllowQ, WhenMocked mode a
_) -> forall a (mode :: MockedMode). Q a -> TestQ mode a
liftQ Q a
whenAllowed
(QMode mode
_, DoInstead TestQ mode a
testQ) -> TestQ mode a
testQ
(QMode mode
_, Unsupported String
label) -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Cannot run '" forall a. [a] -> [a] -> [a]
++ String
label forall a. [a] -> [a] -> [a]
++ String
"' with TestQ"
data Override mode a = Override
{ forall (mode :: MockedMode) a. Override mode a -> Q a
whenAllowed :: Q a
, forall (mode :: MockedMode) a. Override mode a -> WhenMocked mode a
whenMocked :: WhenMocked mode a
}
data WhenMocked mode a
= DoInstead (TestQ mode a)
| Unsupported String
instance Quasi (TestQ mode) where
qRunIO :: forall a. IO a -> TestQ mode a
qRunIO IO a
io =
forall (mode :: MockedMode). TestQ mode (QMode mode)
getMode forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
QMode mode
MockQ -> forall a. HasCallStack => String -> a
error String
"IO actions not allowed"
QMode mode
_ -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO a
io
qRecover :: forall a. TestQ mode a -> TestQ mode a -> TestQ mode a
qRecover TestQ mode a
handler TestQ mode a
action = TestQ mode a
action forall (mode :: MockedMode) a.
TestQ mode a -> (String -> TestQ mode a) -> TestQ mode a
`catchError` forall a b. a -> b -> a
const TestQ mode a
handler
qReport :: Bool -> String -> TestQ mode ()
qReport Bool
False String
msg =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q ()
whenAllowed = forall (m :: * -> *). Quasi m => Bool -> String -> m ()
qReport Bool
False String
msg
, whenMocked :: WhenMocked mode ()
whenMocked = forall (mode :: MockedMode) a. TestQ mode a -> WhenMocked mode a
DoInstead forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return ()
}
qReport Bool
True String
msg = forall (mode :: MockedMode). String -> TestQ mode ()
storeLastError String
msg
qNewName :: String -> TestQ mode Name
qNewName String
name =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q Name
whenAllowed = forall (m :: * -> *). Quasi m => String -> m Name
qNewName String
name
, whenMocked :: WhenMocked mode Name
whenMocked = forall (mode :: MockedMode) a. TestQ mode a -> WhenMocked mode a
DoInstead forall a b. (a -> b) -> a -> b
$ String -> Uniq -> Name
mkNameU String
name forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (mode :: MockedMode). TestQ mode Int
getAndIncrementNewNameCounter
}
qLookupName :: Bool -> String -> TestQ mode (Maybe Name)
qLookupName Bool
b String
name =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q (Maybe Name)
whenAllowed = forall (m :: * -> *). Quasi m => Bool -> String -> m (Maybe Name)
qLookupName Bool
b String
name
, whenMocked :: WhenMocked mode (Maybe Name)
whenMocked = forall (mode :: MockedMode) a. TestQ mode a -> WhenMocked mode a
DoInstead forall a b. (a -> b) -> a -> b
$ do
QState{[(String, Name)]
knownNames :: forall (mode :: MockedMode). QState mode -> [(String, Name)]
knownNames :: [(String, Name)]
knownNames} <- forall (mode :: MockedMode). TestQ mode (QState mode)
getState
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
name [(String, Name)]
knownNames
}
qReify :: Name -> TestQ mode Info
qReify Name
name =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q Info
whenAllowed = forall (m :: * -> *). Quasi m => Name -> m Info
qReify Name
name
, whenMocked :: WhenMocked mode Info
whenMocked = forall (mode :: MockedMode) a. TestQ mode a -> WhenMocked mode a
DoInstead forall a b. (a -> b) -> a -> b
$ forall a (mode :: MockedMode).
(ReifyInfo -> a) -> Name -> TestQ mode a
lookupReifyInfo ReifyInfo -> Info
reifyInfoInfo Name
name
}
qReifyFixity :: Name -> TestQ mode (Maybe Fixity)
qReifyFixity Name
name =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q (Maybe Fixity)
whenAllowed = forall (m :: * -> *). Quasi m => Name -> m (Maybe Fixity)
qReifyFixity Name
name
, whenMocked :: WhenMocked mode (Maybe Fixity)
whenMocked = forall (mode :: MockedMode) a. TestQ mode a -> WhenMocked mode a
DoInstead forall a b. (a -> b) -> a -> b
$ forall a (mode :: MockedMode).
(ReifyInfo -> a) -> Name -> TestQ mode a
lookupReifyInfo ReifyInfo -> Maybe Fixity
reifyInfoFixity Name
name
}
qReifyRoles :: Name -> TestQ mode [Role]
qReifyRoles Name
name =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q [Role]
whenAllowed = forall (m :: * -> *). Quasi m => Name -> m [Role]
qReifyRoles Name
name
, whenMocked :: WhenMocked mode [Role]
whenMocked =
forall (mode :: MockedMode) a. TestQ mode a -> WhenMocked mode a
DoInstead forall a b. (a -> b) -> a -> b
$
forall a (mode :: MockedMode).
(ReifyInfo -> a) -> Name -> TestQ mode a
lookupReifyInfo ReifyInfo -> Maybe [Role]
reifyInfoRoles Name
name forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe [Role]
Nothing -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"No roles associated with " forall a. [a] -> [a] -> [a]
++ forall {a}. Show a => a -> String
show Name
name
Just [Role]
roles -> forall (m :: * -> *) a. Monad m => a -> m a
return [Role]
roles
}
qReifyType :: Name -> TestQ mode Type
qReifyType Name
name =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q Type
whenAllowed = forall (m :: * -> *). Quasi m => Name -> m Type
qReifyType Name
name
, whenMocked :: WhenMocked mode Type
whenMocked = forall (mode :: MockedMode) a. TestQ mode a -> WhenMocked mode a
DoInstead forall a b. (a -> b) -> a -> b
$ forall a (mode :: MockedMode).
(ReifyInfo -> a) -> Name -> TestQ mode a
lookupReifyInfo ReifyInfo -> Type
reifyInfoType Name
name
}
qReifyInstances :: Name -> [Type] -> TestQ mode [Dec]
qReifyInstances Name
name [Type]
types =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q [Dec]
whenAllowed = forall (m :: * -> *). Quasi m => Name -> [Type] -> m [Dec]
qReifyInstances Name
name [Type]
types
, whenMocked :: WhenMocked mode [Dec]
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qReifyInstances"
}
qReifyAnnotations :: forall a. Data a => AnnLookup -> TestQ mode [a]
qReifyAnnotations AnnLookup
annlookup =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q [a]
whenAllowed = forall (m :: * -> *) a. (Quasi m, Data a) => AnnLookup -> m [a]
qReifyAnnotations AnnLookup
annlookup
, whenMocked :: WhenMocked mode [a]
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qReifyAnnotations"
}
qReifyModule :: Module -> TestQ mode ModuleInfo
qReifyModule Module
mod' =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q ModuleInfo
whenAllowed = forall (m :: * -> *). Quasi m => Module -> m ModuleInfo
qReifyModule Module
mod'
, whenMocked :: WhenMocked mode ModuleInfo
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qReifyModule"
}
qReifyConStrictness :: Name -> TestQ mode [DecidedStrictness]
qReifyConStrictness Name
name =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q [DecidedStrictness]
whenAllowed = forall (m :: * -> *). Quasi m => Name -> m [DecidedStrictness]
qReifyConStrictness Name
name
, whenMocked :: WhenMocked mode [DecidedStrictness]
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qReifyConStrictness"
}
qLocation :: TestQ mode Loc
qLocation =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q Loc
whenAllowed = forall (m :: * -> *). Quasi m => m Loc
qLocation
, whenMocked :: WhenMocked mode Loc
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qLocation"
}
qAddDependentFile :: String -> TestQ mode ()
qAddDependentFile String
fp =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q ()
whenAllowed = forall (m :: * -> *). Quasi m => String -> m ()
qAddDependentFile String
fp
, whenMocked :: WhenMocked mode ()
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qAddDependentFile"
}
qAddTopDecls :: [Dec] -> TestQ mode ()
qAddTopDecls [Dec]
decls =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q ()
whenAllowed = forall (m :: * -> *). Quasi m => [Dec] -> m ()
qAddTopDecls [Dec]
decls
, whenMocked :: WhenMocked mode ()
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qAddTopDecls"
}
qAddModFinalizer :: Q () -> TestQ mode ()
qAddModFinalizer Q ()
q =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q ()
whenAllowed = forall (m :: * -> *). Quasi m => Q () -> m ()
qAddModFinalizer Q ()
q
, whenMocked :: WhenMocked mode ()
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qAddModFinalizer"
}
qGetQ :: forall a. Typeable a => TestQ mode (Maybe a)
qGetQ =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q (Maybe a)
whenAllowed = forall (m :: * -> *) a. (Quasi m, Typeable a) => m (Maybe a)
qGetQ
, whenMocked :: WhenMocked mode (Maybe a)
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qGetQ"
}
qPutQ :: forall a. Typeable a => a -> TestQ mode ()
qPutQ a
a =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q ()
whenAllowed = forall (m :: * -> *) a. (Quasi m, Typeable a) => a -> m ()
qPutQ a
a
, whenMocked :: WhenMocked mode ()
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qPutQ"
}
qIsExtEnabled :: Extension -> TestQ mode Bool
qIsExtEnabled Extension
ext =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q Bool
whenAllowed = forall (m :: * -> *). Quasi m => Extension -> m Bool
qIsExtEnabled Extension
ext
, whenMocked :: WhenMocked mode Bool
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qIsExtEnabled"
}
qExtsEnabled :: TestQ mode [Extension]
qExtsEnabled =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q [Extension]
whenAllowed = forall (m :: * -> *). Quasi m => m [Extension]
qExtsEnabled
, whenMocked :: WhenMocked mode [Extension]
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qExtsEnabled"
}
qAddCorePlugin :: String -> TestQ mode ()
qAddCorePlugin String
plugin =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q ()
whenAllowed = forall (m :: * -> *). Quasi m => String -> m ()
qAddCorePlugin String
plugin
, whenMocked :: WhenMocked mode ()
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qAddCorePlugin"
}
qAddTempFile :: String -> TestQ mode String
qAddTempFile String
suffix =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q String
whenAllowed = forall (m :: * -> *). Quasi m => String -> m String
qAddTempFile String
suffix
, whenMocked :: WhenMocked mode String
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qAddTempFile"
}
qAddForeignFilePath :: ForeignSrcLang -> String -> TestQ mode ()
qAddForeignFilePath ForeignSrcLang
lang String
fp =
forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use
Override
{ whenAllowed :: Q ()
whenAllowed = forall (m :: * -> *). Quasi m => ForeignSrcLang -> String -> m ()
qAddForeignFilePath ForeignSrcLang
lang String
fp
, whenMocked :: WhenMocked mode ()
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qAddForeignFilePath"
}
#if MIN_VERSION_template_haskell(2,18,0)
qPutDoc :: DocLoc -> String -> TestQ mode ()
qPutDoc DocLoc
loc String
doc = forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use Override
{ whenAllowed :: Q ()
whenAllowed = forall (m :: * -> *). Quasi m => DocLoc -> String -> m ()
qPutDoc DocLoc
loc String
doc
, whenMocked :: WhenMocked mode ()
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qPutDoc"
}
qGetDoc :: DocLoc -> TestQ mode (Maybe String)
qGetDoc DocLoc
loc = forall (mode :: MockedMode) a. Override mode a -> TestQ mode a
use Override
{ whenAllowed :: Q (Maybe String)
whenAllowed = forall (m :: * -> *). Quasi m => DocLoc -> m (Maybe String)
qGetDoc DocLoc
loc
, whenMocked :: WhenMocked mode (Maybe String)
whenMocked = forall (mode :: MockedMode) a. String -> WhenMocked mode a
Unsupported String
"qGetDoc"
}
#endif
#if MIN_VERSION_template_haskell(2,19,0)
qGetPackageRoot =
use
Override
{ whenAllowed = qGetPackageRoot
, whenMocked = Unsupported "qGetPackageRoot"
}
#endif