{-# LANGUAGE ScopedTypeVariables, StandaloneDeriving, DeriveGeneric,
TupleSections, RecordWildCards, InstanceSigs, CPP #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module GHCi.TH
( startTH
, runModFinalizerRefs
, runTH
, GHCiQException(..)
) where
import Prelude
import GHCi.Message
import GHCi.RemoteTypes
import GHC.Serialized
import Control.Exception
import qualified Control.Monad.Fail as Fail
import Control.Monad.IO.Class (MonadIO (..))
import Data.Binary
import Data.Binary.Put
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as LB
import Data.Data
import Data.Dynamic
import Data.Either
import Data.IORef
import Data.Map (Map)
import qualified Data.Map as M
import Data.Maybe
import GHC.Desugar
import qualified Language.Haskell.TH as TH
import qualified Language.Haskell.TH.Syntax as TH
import Unsafe.Coerce
initQState :: Pipe -> QState
initQState :: Pipe -> QState
initQState Pipe
p = Map TypeRep Dynamic -> Maybe Loc -> Pipe -> QState
QState Map TypeRep Dynamic
forall k a. Map k a
M.empty Maybe Loc
forall a. Maybe a
Nothing Pipe
p
newtype GHCiQ a = GHCiQ { GHCiQ a -> QState -> IO (a, QState)
runGHCiQ :: QState -> IO (a, QState) }
data GHCiQException = GHCiQException QState String
deriving Int -> GHCiQException -> ShowS
[GHCiQException] -> ShowS
GHCiQException -> String
(Int -> GHCiQException -> ShowS)
-> (GHCiQException -> String)
-> ([GHCiQException] -> ShowS)
-> Show GHCiQException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GHCiQException] -> ShowS
$cshowList :: [GHCiQException] -> ShowS
show :: GHCiQException -> String
$cshow :: GHCiQException -> String
showsPrec :: Int -> GHCiQException -> ShowS
$cshowsPrec :: Int -> GHCiQException -> ShowS
Show
instance Exception GHCiQException
instance Functor GHCiQ where
fmap :: (a -> b) -> GHCiQ a -> GHCiQ b
fmap a -> b
f (GHCiQ QState -> IO (a, QState)
s) = (QState -> IO (b, QState)) -> GHCiQ b
forall a. (QState -> IO (a, QState)) -> GHCiQ a
GHCiQ ((QState -> IO (b, QState)) -> GHCiQ b)
-> (QState -> IO (b, QState)) -> GHCiQ b
forall a b. (a -> b) -> a -> b
$ ((a, QState) -> (b, QState)) -> IO (a, QState) -> IO (b, QState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(a
x,QState
s') -> (a -> b
f a
x,QState
s')) (IO (a, QState) -> IO (b, QState))
-> (QState -> IO (a, QState)) -> QState -> IO (b, QState)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QState -> IO (a, QState)
s
instance Applicative GHCiQ where
GHCiQ (a -> b)
f <*> :: GHCiQ (a -> b) -> GHCiQ a -> GHCiQ b
<*> GHCiQ a
a = (QState -> IO (b, QState)) -> GHCiQ b
forall a. (QState -> IO (a, QState)) -> GHCiQ a
GHCiQ ((QState -> IO (b, QState)) -> GHCiQ b)
-> (QState -> IO (b, QState)) -> GHCiQ b
forall a b. (a -> b) -> a -> b
$ \QState
s ->
do (a -> b
f',QState
s') <- GHCiQ (a -> b) -> QState -> IO (a -> b, QState)
forall a. GHCiQ a -> QState -> IO (a, QState)
runGHCiQ GHCiQ (a -> b)
f QState
s
(a
a',QState
s'') <- GHCiQ a -> QState -> IO (a, QState)
forall a. GHCiQ a -> QState -> IO (a, QState)
runGHCiQ GHCiQ a
a QState
s'
(b, QState) -> IO (b, QState)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> b
f' a
a', QState
s'')
pure :: a -> GHCiQ a
pure a
x = (QState -> IO (a, QState)) -> GHCiQ a
forall a. (QState -> IO (a, QState)) -> GHCiQ a
GHCiQ (\QState
s -> (a, QState) -> IO (a, QState)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
x,QState
s))
instance Monad GHCiQ where
GHCiQ a
m >>= :: GHCiQ a -> (a -> GHCiQ b) -> GHCiQ b
>>= a -> GHCiQ b
f = (QState -> IO (b, QState)) -> GHCiQ b
forall a. (QState -> IO (a, QState)) -> GHCiQ a
GHCiQ ((QState -> IO (b, QState)) -> GHCiQ b)
-> (QState -> IO (b, QState)) -> GHCiQ b
forall a b. (a -> b) -> a -> b
$ \QState
s ->
do (a
m', QState
s') <- GHCiQ a -> QState -> IO (a, QState)
forall a. GHCiQ a -> QState -> IO (a, QState)
runGHCiQ GHCiQ a
m QState
s
(b
a, QState
s'') <- GHCiQ b -> QState -> IO (b, QState)
forall a. GHCiQ a -> QState -> IO (a, QState)
runGHCiQ (a -> GHCiQ b
f a
m') QState
s'
(b, QState) -> IO (b, QState)
forall (m :: * -> *) a. Monad m => a -> m a
return (b
a, QState
s'')
#if !MIN_VERSION_base(4,13,0)
fail = Fail.fail
#endif
instance Fail.MonadFail GHCiQ where
fail :: String -> GHCiQ a
fail String
err = (QState -> IO (a, QState)) -> GHCiQ a
forall a. (QState -> IO (a, QState)) -> GHCiQ a
GHCiQ ((QState -> IO (a, QState)) -> GHCiQ a)
-> (QState -> IO (a, QState)) -> GHCiQ a
forall a b. (a -> b) -> a -> b
$ \QState
s -> GHCiQException -> IO (a, QState)
forall e a. Exception e => e -> IO a
throwIO (QState -> String -> GHCiQException
GHCiQException QState
s String
err)
getState :: GHCiQ QState
getState :: GHCiQ QState
getState = (QState -> IO (QState, QState)) -> GHCiQ QState
forall a. (QState -> IO (a, QState)) -> GHCiQ a
GHCiQ ((QState -> IO (QState, QState)) -> GHCiQ QState)
-> (QState -> IO (QState, QState)) -> GHCiQ QState
forall a b. (a -> b) -> a -> b
$ \QState
s -> (QState, QState) -> IO (QState, QState)
forall (m :: * -> *) a. Monad m => a -> m a
return (QState
s,QState
s)
noLoc :: TH.Loc
noLoc :: Loc
noLoc = String -> String -> String -> CharPos -> CharPos -> Loc
TH.Loc String
"<no file>" String
"<no package>" String
"<no module>" (Int
0,Int
0) (Int
0,Int
0)
ghcCmd :: Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd :: THMessage (THResult a) -> GHCiQ a
ghcCmd THMessage (THResult a)
m = (QState -> IO (a, QState)) -> GHCiQ a
forall a. (QState -> IO (a, QState)) -> GHCiQ a
GHCiQ ((QState -> IO (a, QState)) -> GHCiQ a)
-> (QState -> IO (a, QState)) -> GHCiQ a
forall a b. (a -> b) -> a -> b
$ \QState
s -> do
THResult a
r <- Pipe -> THMessage (THResult a) -> IO (THResult a)
forall a. Binary a => Pipe -> THMessage a -> IO a
remoteTHCall (QState -> Pipe
qsPipe QState
s) THMessage (THResult a)
m
case THResult a
r of
THException String
str -> GHCiQException -> IO (a, QState)
forall e a. Exception e => e -> IO a
throwIO (QState -> String -> GHCiQException
GHCiQException QState
s String
str)
THComplete a
res -> (a, QState) -> IO (a, QState)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
res, QState
s)
instance MonadIO GHCiQ where
liftIO :: IO a -> GHCiQ a
liftIO IO a
m = (QState -> IO (a, QState)) -> GHCiQ a
forall a. (QState -> IO (a, QState)) -> GHCiQ a
GHCiQ ((QState -> IO (a, QState)) -> GHCiQ a)
-> (QState -> IO (a, QState)) -> GHCiQ a
forall a b. (a -> b) -> a -> b
$ \QState
s -> (a -> (a, QState)) -> IO a -> IO (a, QState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (,QState
s) IO a
m
instance TH.Quasi GHCiQ where
qNewName :: String -> GHCiQ Name
qNewName String
str = THMessage (THResult Name) -> GHCiQ Name
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (String -> THMessage (THResult Name)
NewName String
str)
qReport :: Bool -> String -> GHCiQ ()
qReport Bool
isError String
msg = THMessage (THResult ()) -> GHCiQ ()
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (Bool -> String -> THMessage (THResult ())
Report Bool
isError String
msg)
qRecover :: GHCiQ a -> GHCiQ a -> GHCiQ a
qRecover (GHCiQ QState -> IO (a, QState)
h) GHCiQ a
a = (QState -> IO (a, QState)) -> GHCiQ a
forall a. (QState -> IO (a, QState)) -> GHCiQ a
GHCiQ ((QState -> IO (a, QState)) -> GHCiQ a)
-> (QState -> IO (a, QState)) -> GHCiQ a
forall a b. (a -> b) -> a -> b
$ \QState
s -> ((forall a. IO a -> IO a) -> IO (a, QState)) -> IO (a, QState)
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
mask (((forall a. IO a -> IO a) -> IO (a, QState)) -> IO (a, QState))
-> ((forall a. IO a -> IO a) -> IO (a, QState)) -> IO (a, QState)
forall a b. (a -> b) -> a -> b
$ \forall a. IO a -> IO a
unmask -> do
Pipe -> THMessage () -> IO ()
forall a. Binary a => Pipe -> THMessage a -> IO a
remoteTHCall (QState -> Pipe
qsPipe QState
s) THMessage ()
StartRecover
Either GHCiQException (a, QState)
e <- IO (a, QState) -> IO (Either GHCiQException (a, QState))
forall e a. Exception e => IO a -> IO (Either e a)
try (IO (a, QState) -> IO (Either GHCiQException (a, QState)))
-> IO (a, QState) -> IO (Either GHCiQException (a, QState))
forall a b. (a -> b) -> a -> b
$ IO (a, QState) -> IO (a, QState)
forall a. IO a -> IO a
unmask (IO (a, QState) -> IO (a, QState))
-> IO (a, QState) -> IO (a, QState)
forall a b. (a -> b) -> a -> b
$ GHCiQ a -> QState -> IO (a, QState)
forall a. GHCiQ a -> QState -> IO (a, QState)
runGHCiQ (GHCiQ a
a GHCiQ a -> GHCiQ () -> GHCiQ a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* THMessage (THResult ()) -> GHCiQ ()
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd THMessage (THResult ())
FailIfErrs) QState
s
Pipe -> THMessage () -> IO ()
forall a. Binary a => Pipe -> THMessage a -> IO a
remoteTHCall (QState -> Pipe
qsPipe QState
s) (Bool -> THMessage ()
EndRecover (Either GHCiQException (a, QState) -> Bool
forall a b. Either a b -> Bool
isLeft Either GHCiQException (a, QState)
e))
case Either GHCiQException (a, QState)
e of
Left GHCiQException{} -> QState -> IO (a, QState)
h QState
s
Right (a, QState)
r -> (a, QState) -> IO (a, QState)
forall (m :: * -> *) a. Monad m => a -> m a
return (a, QState)
r
qLookupName :: Bool -> String -> GHCiQ (Maybe Name)
qLookupName Bool
isType String
occ = THMessage (THResult (Maybe Name)) -> GHCiQ (Maybe Name)
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (Bool -> String -> THMessage (THResult (Maybe Name))
LookupName Bool
isType String
occ)
qReify :: Name -> GHCiQ Info
qReify Name
name = THMessage (THResult Info) -> GHCiQ Info
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (Name -> THMessage (THResult Info)
Reify Name
name)
qReifyFixity :: Name -> GHCiQ (Maybe Fixity)
qReifyFixity Name
name = THMessage (THResult (Maybe Fixity)) -> GHCiQ (Maybe Fixity)
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (Name -> THMessage (THResult (Maybe Fixity))
ReifyFixity Name
name)
qReifyType :: Name -> GHCiQ Type
qReifyType Name
name = THMessage (THResult Type) -> GHCiQ Type
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (Name -> THMessage (THResult Type)
ReifyType Name
name)
qReifyInstances :: Name -> [Type] -> GHCiQ [Dec]
qReifyInstances Name
name [Type]
tys = THMessage (THResult [Dec]) -> GHCiQ [Dec]
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (Name -> [Type] -> THMessage (THResult [Dec])
ReifyInstances Name
name [Type]
tys)
qReifyRoles :: Name -> GHCiQ [Role]
qReifyRoles Name
name = THMessage (THResult [Role]) -> GHCiQ [Role]
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (Name -> THMessage (THResult [Role])
ReifyRoles Name
name)
qReifyAnnotations :: forall a . Data a => TH.AnnLookup -> GHCiQ [a]
qReifyAnnotations :: AnnLookup -> GHCiQ [a]
qReifyAnnotations AnnLookup
lookup =
(ByteString -> a) -> [ByteString] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map ([Word8] -> a
forall a. Data a => [Word8] -> a
deserializeWithData ([Word8] -> a) -> (ByteString -> [Word8]) -> ByteString -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Word8]
B.unpack) ([ByteString] -> [a]) -> GHCiQ [ByteString] -> GHCiQ [a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
THMessage (THResult [ByteString]) -> GHCiQ [ByteString]
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (AnnLookup -> TypeRep -> THMessage (THResult [ByteString])
ReifyAnnotations AnnLookup
lookup TypeRep
typerep)
where typerep :: TypeRep
typerep = a -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf (a
forall a. HasCallStack => a
undefined :: a)
qReifyModule :: Module -> GHCiQ ModuleInfo
qReifyModule Module
m = THMessage (THResult ModuleInfo) -> GHCiQ ModuleInfo
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (Module -> THMessage (THResult ModuleInfo)
ReifyModule Module
m)
qReifyConStrictness :: Name -> GHCiQ [DecidedStrictness]
qReifyConStrictness Name
name = THMessage (THResult [DecidedStrictness])
-> GHCiQ [DecidedStrictness]
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (Name -> THMessage (THResult [DecidedStrictness])
ReifyConStrictness Name
name)
qLocation :: GHCiQ Loc
qLocation = Loc -> Maybe Loc -> Loc
forall a. a -> Maybe a -> a
fromMaybe Loc
noLoc (Maybe Loc -> Loc) -> (QState -> Maybe Loc) -> QState -> Loc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QState -> Maybe Loc
qsLocation (QState -> Loc) -> GHCiQ QState -> GHCiQ Loc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GHCiQ QState
getState
qAddDependentFile :: String -> GHCiQ ()
qAddDependentFile String
file = THMessage (THResult ()) -> GHCiQ ()
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (String -> THMessage (THResult ())
AddDependentFile String
file)
qAddTempFile :: String -> GHCiQ String
qAddTempFile String
suffix = THMessage (THResult String) -> GHCiQ String
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (String -> THMessage (THResult String)
AddTempFile String
suffix)
qAddTopDecls :: [Dec] -> GHCiQ ()
qAddTopDecls [Dec]
decls = THMessage (THResult ()) -> GHCiQ ()
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd ([Dec] -> THMessage (THResult ())
AddTopDecls [Dec]
decls)
qAddForeignFilePath :: ForeignSrcLang -> String -> GHCiQ ()
qAddForeignFilePath ForeignSrcLang
lang String
fp = THMessage (THResult ()) -> GHCiQ ()
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (ForeignSrcLang -> String -> THMessage (THResult ())
AddForeignFilePath ForeignSrcLang
lang String
fp)
qAddModFinalizer :: Q () -> GHCiQ ()
qAddModFinalizer Q ()
fin = (QState -> IO (RemoteRef (Q ()), QState))
-> GHCiQ (RemoteRef (Q ()))
forall a. (QState -> IO (a, QState)) -> GHCiQ a
GHCiQ (\QState
s -> Q () -> IO (RemoteRef (Q ()))
forall a. a -> IO (RemoteRef a)
mkRemoteRef Q ()
fin IO (RemoteRef (Q ()))
-> (RemoteRef (Q ()) -> IO (RemoteRef (Q ()), QState))
-> IO (RemoteRef (Q ()), QState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (RemoteRef (Q ()), QState) -> IO (RemoteRef (Q ()), QState)
forall (m :: * -> *) a. Monad m => a -> m a
return ((RemoteRef (Q ()), QState) -> IO (RemoteRef (Q ()), QState))
-> (RemoteRef (Q ()) -> (RemoteRef (Q ()), QState))
-> RemoteRef (Q ())
-> IO (RemoteRef (Q ()), QState)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (, QState
s)) GHCiQ (RemoteRef (Q ()))
-> (RemoteRef (Q ()) -> GHCiQ ()) -> GHCiQ ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
THMessage (THResult ()) -> GHCiQ ()
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (THMessage (THResult ()) -> GHCiQ ())
-> (RemoteRef (Q ()) -> THMessage (THResult ()))
-> RemoteRef (Q ())
-> GHCiQ ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RemoteRef (Q ()) -> THMessage (THResult ())
AddModFinalizer
qAddCorePlugin :: String -> GHCiQ ()
qAddCorePlugin String
str = THMessage (THResult ()) -> GHCiQ ()
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (String -> THMessage (THResult ())
AddCorePlugin String
str)
qGetQ :: GHCiQ (Maybe a)
qGetQ = (QState -> IO (Maybe a, QState)) -> GHCiQ (Maybe a)
forall a. (QState -> IO (a, QState)) -> GHCiQ a
GHCiQ ((QState -> IO (Maybe a, QState)) -> GHCiQ (Maybe a))
-> (QState -> IO (Maybe a, QState)) -> GHCiQ (Maybe a)
forall a b. (a -> b) -> a -> b
$ \QState
s ->
let lookup :: forall a. Typeable a => Map TypeRep Dynamic -> Maybe a
lookup :: Map TypeRep Dynamic -> Maybe a
lookup Map TypeRep Dynamic
m = Dynamic -> Maybe a
forall a. Typeable a => Dynamic -> Maybe a
fromDynamic (Dynamic -> Maybe a) -> Maybe Dynamic -> Maybe a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< TypeRep -> Map TypeRep Dynamic -> Maybe Dynamic
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (a -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf (a
forall a. HasCallStack => a
undefined::a)) Map TypeRep Dynamic
m
in (Maybe a, QState) -> IO (Maybe a, QState)
forall (m :: * -> *) a. Monad m => a -> m a
return (Map TypeRep Dynamic -> Maybe a
forall a. Typeable a => Map TypeRep Dynamic -> Maybe a
lookup (QState -> Map TypeRep Dynamic
qsMap QState
s), QState
s)
qPutQ :: a -> GHCiQ ()
qPutQ a
k = (QState -> IO ((), QState)) -> GHCiQ ()
forall a. (QState -> IO (a, QState)) -> GHCiQ a
GHCiQ ((QState -> IO ((), QState)) -> GHCiQ ())
-> (QState -> IO ((), QState)) -> GHCiQ ()
forall a b. (a -> b) -> a -> b
$ \QState
s ->
((), QState) -> IO ((), QState)
forall (m :: * -> *) a. Monad m => a -> m a
return ((), QState
s { qsMap :: Map TypeRep Dynamic
qsMap = TypeRep -> Dynamic -> Map TypeRep Dynamic -> Map TypeRep Dynamic
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (a -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf a
k) (a -> Dynamic
forall a. Typeable a => a -> Dynamic
toDyn a
k) (QState -> Map TypeRep Dynamic
qsMap QState
s) })
qIsExtEnabled :: Extension -> GHCiQ Bool
qIsExtEnabled Extension
x = THMessage (THResult Bool) -> GHCiQ Bool
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd (Extension -> THMessage (THResult Bool)
IsExtEnabled Extension
x)
qExtsEnabled :: GHCiQ [Extension]
qExtsEnabled = THMessage (THResult [Extension]) -> GHCiQ [Extension]
forall a. Binary a => THMessage (THResult a) -> GHCiQ a
ghcCmd THMessage (THResult [Extension])
ExtsEnabled
startTH :: IO (RemoteRef (IORef QState))
startTH :: IO (RemoteRef (IORef QState))
startTH = do
IORef QState
r <- QState -> IO (IORef QState)
forall a. a -> IO (IORef a)
newIORef (Pipe -> QState
initQState (String -> Pipe
forall a. HasCallStack => String -> a
error String
"startTH: no pipe"))
IORef QState -> IO (RemoteRef (IORef QState))
forall a. a -> IO (RemoteRef a)
mkRemoteRef IORef QState
r
runModFinalizerRefs :: Pipe -> RemoteRef (IORef QState)
-> [RemoteRef (TH.Q ())]
-> IO ()
runModFinalizerRefs :: Pipe -> RemoteRef (IORef QState) -> [RemoteRef (Q ())] -> IO ()
runModFinalizerRefs Pipe
pipe RemoteRef (IORef QState)
rstate [RemoteRef (Q ())]
qrefs = do
[Q ()]
qs <- (RemoteRef (Q ()) -> IO (Q ())) -> [RemoteRef (Q ())] -> IO [Q ()]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM RemoteRef (Q ()) -> IO (Q ())
forall a. RemoteRef a -> IO a
localRef [RemoteRef (Q ())]
qrefs
IORef QState
qstateref <- RemoteRef (IORef QState) -> IO (IORef QState)
forall a. RemoteRef a -> IO a
localRef RemoteRef (IORef QState)
rstate
QState
qstate <- IORef QState -> IO QState
forall a. IORef a -> IO a
readIORef IORef QState
qstateref
((), QState)
_ <- GHCiQ () -> QState -> IO ((), QState)
forall a. GHCiQ a -> QState -> IO (a, QState)
runGHCiQ (Q () -> GHCiQ ()
forall (m :: * -> *) a. Quasi m => Q a -> m a
TH.runQ (Q () -> GHCiQ ()) -> Q () -> GHCiQ ()
forall a b. (a -> b) -> a -> b
$ [Q ()] -> Q ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [Q ()]
qs) QState
qstate { qsPipe :: Pipe
qsPipe = Pipe
pipe }
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
runTH
:: Pipe
-> RemoteRef (IORef QState)
-> HValueRef
-> THResultType
-> Maybe TH.Loc
-> IO ByteString
runTH :: Pipe
-> RemoteRef (IORef QState)
-> HValueRef
-> THResultType
-> Maybe Loc
-> IO ByteString
runTH Pipe
pipe RemoteRef (IORef QState)
rstate HValueRef
rhv THResultType
ty Maybe Loc
mb_loc = do
HValue
hv <- HValueRef -> IO HValue
forall a. RemoteRef a -> IO a
localRef HValueRef
rhv
case THResultType
ty of
THResultType
THExp -> Pipe
-> RemoteRef (IORef QState) -> Maybe Loc -> Q Exp -> IO ByteString
forall a.
Binary a =>
Pipe
-> RemoteRef (IORef QState) -> Maybe Loc -> Q a -> IO ByteString
runTHQ Pipe
pipe RemoteRef (IORef QState)
rstate Maybe Loc
mb_loc (HValue -> Q Exp
forall a b. a -> b
unsafeCoerce HValue
hv :: TH.Q TH.Exp)
THResultType
THPat -> Pipe
-> RemoteRef (IORef QState) -> Maybe Loc -> Q Pat -> IO ByteString
forall a.
Binary a =>
Pipe
-> RemoteRef (IORef QState) -> Maybe Loc -> Q a -> IO ByteString
runTHQ Pipe
pipe RemoteRef (IORef QState)
rstate Maybe Loc
mb_loc (HValue -> Q Pat
forall a b. a -> b
unsafeCoerce HValue
hv :: TH.Q TH.Pat)
THResultType
THType -> Pipe
-> RemoteRef (IORef QState) -> Maybe Loc -> Q Type -> IO ByteString
forall a.
Binary a =>
Pipe
-> RemoteRef (IORef QState) -> Maybe Loc -> Q a -> IO ByteString
runTHQ Pipe
pipe RemoteRef (IORef QState)
rstate Maybe Loc
mb_loc (HValue -> Q Type
forall a b. a -> b
unsafeCoerce HValue
hv :: TH.Q TH.Type)
THResultType
THDec -> Pipe
-> RemoteRef (IORef QState)
-> Maybe Loc
-> Q [Dec]
-> IO ByteString
forall a.
Binary a =>
Pipe
-> RemoteRef (IORef QState) -> Maybe Loc -> Q a -> IO ByteString
runTHQ Pipe
pipe RemoteRef (IORef QState)
rstate Maybe Loc
mb_loc (HValue -> Q [Dec]
forall a b. a -> b
unsafeCoerce HValue
hv :: TH.Q [TH.Dec])
THResultType
THAnnWrapper -> do
AnnotationWrapper
hv <- HValue -> AnnotationWrapper
forall a b. a -> b
unsafeCoerce (HValue -> AnnotationWrapper) -> IO HValue -> IO AnnotationWrapper
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HValueRef -> IO HValue
forall a. RemoteRef a -> IO a
localRef HValueRef
rhv
case AnnotationWrapper
hv :: AnnotationWrapper of
AnnotationWrapper a
thing -> ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$!
ByteString -> ByteString
LB.toStrict (Put -> ByteString
runPut (Serialized -> Put
forall t. Binary t => t -> Put
put ((a -> [Word8]) -> a -> Serialized
forall a. Typeable a => (a -> [Word8]) -> a -> Serialized
toSerialized a -> [Word8]
forall a. Data a => a -> [Word8]
serializeWithData a
thing)))
runTHQ
:: Binary a => Pipe -> RemoteRef (IORef QState) -> Maybe TH.Loc -> TH.Q a
-> IO ByteString
runTHQ :: Pipe
-> RemoteRef (IORef QState) -> Maybe Loc -> Q a -> IO ByteString
runTHQ Pipe
pipe RemoteRef (IORef QState)
rstate Maybe Loc
mb_loc Q a
ghciq = do
IORef QState
qstateref <- RemoteRef (IORef QState) -> IO (IORef QState)
forall a. RemoteRef a -> IO a
localRef RemoteRef (IORef QState)
rstate
QState
qstate <- IORef QState -> IO QState
forall a. IORef a -> IO a
readIORef IORef QState
qstateref
let st :: QState
st = QState
qstate { qsLocation :: Maybe Loc
qsLocation = Maybe Loc
mb_loc, qsPipe :: Pipe
qsPipe = Pipe
pipe }
(a
r,QState
new_state) <- GHCiQ a -> QState -> IO (a, QState)
forall a. GHCiQ a -> QState -> IO (a, QState)
runGHCiQ (Q a -> GHCiQ a
forall (m :: * -> *) a. Quasi m => Q a -> m a
TH.runQ Q a
ghciq) QState
st
IORef QState -> QState -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef QState
qstateref QState
new_state
ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$! ByteString -> ByteString
LB.toStrict (Put -> ByteString
runPut (a -> Put
forall t. Binary t => t -> Put
put a
r))