{-# LANGUAGE CPP, DeriveFunctor, DerivingVia, RankNTypes #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}
module GHC.Driver.Monad (
GhcMonad(..),
Ghc(..),
GhcT(..), liftGhcT,
reflectGhc, reifyGhc,
getSessionDynFlags,
liftIO,
Session(..), withSession, modifySession, withTempSession,
logWarnings, printException,
WarnErrLogger, defaultWarnErrLogger
) where
import GHC.Prelude
import GHC.Utils.Monad
import GHC.Driver.Types
import GHC.Driver.Session
import GHC.Utils.Exception
import GHC.Utils.Error
import Control.Monad
import Control.Monad.Catch as MC
import Control.Monad.Trans.Reader
import Data.IORef
class (Functor m, ExceptionMonad m, HasDynFlags m) => GhcMonad m where
getSession :: m HscEnv
setSession :: HscEnv -> m ()
withSession :: GhcMonad m => (HscEnv -> m a) -> m a
withSession :: (HscEnv -> m a) -> m a
withSession HscEnv -> m a
f = m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
Evidence bound by a type signature of the constraint type GhcMonad m
getSession m HscEnv -> (HscEnv -> m a) -> m a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a superclass of: GhcMonad of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
>>= HscEnv -> m a
f
getSessionDynFlags :: GhcMonad m => m DynFlags
getSessionDynFlags :: m DynFlags
getSessionDynFlags = (HscEnv -> m DynFlags) -> m DynFlags
forall (m :: * -> *) a. GhcMonad m => (HscEnv -> m a) -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSession (DynFlags -> m DynFlags
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a superclass of: GhcMonad of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return (DynFlags -> m DynFlags)
-> (HscEnv -> DynFlags) -> HscEnv -> m DynFlags
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HscEnv -> DynFlags
hsc_dflags)
modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m ()
modifySession :: (HscEnv -> HscEnv) -> m ()
modifySession HscEnv -> HscEnv
f = do HscEnv
h <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
Evidence bound by a type signature of the constraint type GhcMonad m
getSession
HscEnv -> m ()
forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
Evidence bound by a type signature of the constraint type GhcMonad m
setSession (HscEnv -> m ()) -> HscEnv -> m ()
forall a b. (a -> b) -> a -> b
$! HscEnv -> HscEnv
f HscEnv
h
withSavedSession :: GhcMonad m => m a -> m a
withSavedSession :: m a -> m a
withSavedSession m a
m = do
HscEnv
saved_session <- m HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
Evidence bound by a type signature of the constraint type GhcMonad m
getSession
m a
m m a -> m () -> m a
forall (m :: * -> *) a b. MonadMask m => m a -> m b -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c3
Evidence bound by a superclass of: GhcMonad of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
`MC.finally` HscEnv -> m ()
forall (m :: * -> *). GhcMonad m => HscEnv -> m ()
Evidence bound by a type signature of the constraint type GhcMonad m
setSession HscEnv
saved_session
withTempSession :: GhcMonad m => (HscEnv -> HscEnv) -> m a -> m a
withTempSession :: (HscEnv -> HscEnv) -> m a -> m a
withTempSession HscEnv -> HscEnv
f m a
m =
m a -> m a
forall (m :: * -> *) a. GhcMonad m => m a -> m a
Evidence bound by a type signature of the constraint type GhcMonad m
withSavedSession (m a -> m a) -> m a -> m a
forall a b. (a -> b) -> a -> b
$ (HscEnv -> HscEnv) -> m ()
forall (m :: * -> *). GhcMonad m => (HscEnv -> HscEnv) -> m ()
Evidence bound by a type signature of the constraint type GhcMonad m
modifySession HscEnv -> HscEnv
f m () -> m a -> m a
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a superclass of: GhcMonad of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
>> m a
m
logWarnings :: GhcMonad m => WarningMessages -> m ()
logWarnings :: WarningMessages -> m ()
logWarnings WarningMessages
warns = do
DynFlags
dflags <- m DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
Evidence bound by a type signature of the constraint type GhcMonad m
getSessionDynFlags
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a superclass of: GhcMonad of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> WarningMessages -> IO ()
printOrThrowWarnings DynFlags
dflags WarningMessages
warns
newtype Ghc a = Ghc { Ghc a -> Session -> IO a
unGhc :: Session -> IO a }
deriving (a -> Ghc b -> Ghc a
(a -> b) -> Ghc a -> Ghc b
(forall a b. (a -> b) -> Ghc a -> Ghc b)
-> (forall a b. a -> Ghc b -> Ghc a) -> Functor Ghc
forall a b. a -> Ghc b -> Ghc a
forall a b. (a -> b) -> Ghc a -> Ghc b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Ghc b -> Ghc a
$c<$ :: forall a b. a -> Ghc b -> Ghc a
fmap :: (a -> b) -> Ghc a -> Ghc b
$cfmap :: forall a b. (a -> b) -> Ghc a -> Ghc b
External instance of the constraint type Functor IO
Functor)
deriving (Monad Ghc
e -> Ghc a
Monad Ghc
-> (forall e a. Exception e => e -> Ghc a) -> MonadThrow Ghc
forall e a. Exception e => e -> Ghc a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
throwM :: e -> Ghc a
$cthrowM :: forall e a. Exception e => e -> Ghc a
External instance of the constraint type MonadThrow IO
External instance of the constraint type MonadThrow IO
External instance of the constraint type forall (m :: * -> *) r. MonadThrow m => MonadThrow (ReaderT r m)
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a HsWrapper of the constraint type Exception e
Evidence bound by a HsWrapper of the constraint type Exception e
Instance of class: Monad of the constraint type Monad Ghc
Instance of class: Monad of the constraint type Monad Ghc
MonadThrow, MonadThrow Ghc
MonadThrow Ghc
-> (forall e a. Exception e => Ghc a -> (e -> Ghc a) -> Ghc a)
-> MonadCatch Ghc
Ghc a -> (e -> Ghc a) -> Ghc a
forall e a. Exception e => Ghc a -> (e -> Ghc a) -> Ghc a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
catch :: Ghc a -> (e -> Ghc a) -> Ghc a
$ccatch :: forall e a. Exception e => Ghc a -> (e -> Ghc a) -> Ghc a
External instance of the constraint type MonadCatch IO
External instance of the constraint type MonadCatch IO
External instance of the constraint type forall (m :: * -> *) r. MonadCatch m => MonadCatch (ReaderT r m)
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a HsWrapper of the constraint type Exception e
Evidence bound by a HsWrapper of the constraint type Exception e
Instance of class: MonadThrow of the constraint type MonadThrow Ghc
Instance of class: MonadThrow of the constraint type MonadThrow Ghc
MonadCatch, MonadCatch Ghc
MonadCatch Ghc
-> (forall b. ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b)
-> (forall b. ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b)
-> (forall a b c.
Ghc a -> (a -> ExitCase b -> Ghc c) -> (a -> Ghc b) -> Ghc (b, c))
-> MonadMask Ghc
Ghc a -> (a -> ExitCase b -> Ghc c) -> (a -> Ghc b) -> Ghc (b, c)
((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b
((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b
forall b. ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b
forall a b c.
Ghc a -> (a -> ExitCase b -> Ghc c) -> (a -> Ghc b) -> Ghc (b, c)
forall (m :: * -> *).
MonadCatch m
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall a b c.
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c))
-> MonadMask m
generalBracket :: Ghc a -> (a -> ExitCase b -> Ghc c) -> (a -> Ghc b) -> Ghc (b, c)
$cgeneralBracket :: forall a b c.
Ghc a -> (a -> ExitCase b -> Ghc c) -> (a -> Ghc b) -> Ghc (b, c)
uninterruptibleMask :: ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b
$cuninterruptibleMask :: forall b. ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b
mask :: ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b
$cmask :: forall b. ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b
External instance of the constraint type MonadMask IO
External instance of the constraint type MonadMask IO
External instance of the constraint type MonadMask IO
External instance of the constraint type MonadMask IO
External instance of the constraint type forall (m :: * -> *) r. MonadMask m => MonadMask (ReaderT r m)
Instance of class: MonadCatch of the constraint type MonadCatch Ghc
Instance of class: MonadCatch of the constraint type MonadCatch Ghc
MonadMask) via (ReaderT Session IO)
data Session = Session !(IORef HscEnv)
instance Applicative Ghc where
pure :: a -> Ghc a
pure a
a = (Session -> IO a) -> Ghc a
forall a. (Session -> IO a) -> Ghc a
Ghc ((Session -> IO a) -> Ghc a) -> (Session -> IO a) -> Ghc a
forall a b. (a -> b) -> a -> b
$ \Session
_ -> a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return a
a
Ghc (a -> b)
g <*> :: Ghc (a -> b) -> Ghc a -> Ghc b
<*> Ghc a
m = do a -> b
f <- Ghc (a -> b)
g; a
a <- Ghc a
m; b -> Ghc b
forall (m :: * -> *) a. Monad m => a -> m a
Instance of class: Monad of the constraint type Monad Ghc
return (a -> b
f a
a)
instance Monad Ghc where
Ghc a
m >>= :: Ghc a -> (a -> Ghc b) -> Ghc b
>>= a -> Ghc b
g = (Session -> IO b) -> Ghc b
forall a. (Session -> IO a) -> Ghc a
Ghc ((Session -> IO b) -> Ghc b) -> (Session -> IO b) -> Ghc b
forall a b. (a -> b) -> a -> b
$ \Session
s -> do a
a <- Ghc a -> Session -> IO a
forall a. Ghc a -> Session -> IO a
unGhc Ghc a
m Session
s; Ghc b -> Session -> IO b
forall a. Ghc a -> Session -> IO a
unGhc (a -> Ghc b
g a
a) Session
s
instance MonadIO Ghc where
liftIO :: IO a -> Ghc a
liftIO IO a
ioA = (Session -> IO a) -> Ghc a
forall a. (Session -> IO a) -> Ghc a
Ghc ((Session -> IO a) -> Ghc a) -> (Session -> IO a) -> Ghc a
forall a b. (a -> b) -> a -> b
$ \Session
_ -> IO a
ioA
instance MonadFix Ghc where
mfix :: (a -> Ghc a) -> Ghc a
mfix a -> Ghc a
f = (Session -> IO a) -> Ghc a
forall a. (Session -> IO a) -> Ghc a
Ghc ((Session -> IO a) -> Ghc a) -> (Session -> IO a) -> Ghc a
forall a b. (a -> b) -> a -> b
$ \Session
s -> (a -> IO a) -> IO a
forall (m :: * -> *) a. MonadFix m => (a -> m a) -> m a
External instance of the constraint type MonadFix IO
mfix (\a
x -> Ghc a -> Session -> IO a
forall a. Ghc a -> Session -> IO a
unGhc (a -> Ghc a
f a
x) Session
s)
instance HasDynFlags Ghc where
getDynFlags :: Ghc DynFlags
getDynFlags = Ghc DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
Instance of class: GhcMonad of the constraint type GhcMonad Ghc
getSessionDynFlags
instance GhcMonad Ghc where
getSession :: Ghc HscEnv
getSession = (Session -> IO HscEnv) -> Ghc HscEnv
forall a. (Session -> IO a) -> Ghc a
Ghc ((Session -> IO HscEnv) -> Ghc HscEnv)
-> (Session -> IO HscEnv) -> Ghc HscEnv
forall a b. (a -> b) -> a -> b
$ \(Session IORef HscEnv
r) -> IORef HscEnv -> IO HscEnv
forall a. IORef a -> IO a
readIORef IORef HscEnv
r
setSession :: HscEnv -> Ghc ()
setSession HscEnv
s' = (Session -> IO ()) -> Ghc ()
forall a. (Session -> IO a) -> Ghc a
Ghc ((Session -> IO ()) -> Ghc ()) -> (Session -> IO ()) -> Ghc ()
forall a b. (a -> b) -> a -> b
$ \(Session IORef HscEnv
r) -> IORef HscEnv -> HscEnv -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef HscEnv
r HscEnv
s'
reflectGhc :: Ghc a -> Session -> IO a
reflectGhc :: Ghc a -> Session -> IO a
reflectGhc Ghc a
m = Ghc a -> Session -> IO a
forall a. Ghc a -> Session -> IO a
unGhc Ghc a
m
reifyGhc :: (Session -> IO a) -> Ghc a
reifyGhc :: (Session -> IO a) -> Ghc a
reifyGhc Session -> IO a
act = (Session -> IO a) -> Ghc a
forall a. (Session -> IO a) -> Ghc a
Ghc ((Session -> IO a) -> Ghc a) -> (Session -> IO a) -> Ghc a
forall a b. (a -> b) -> a -> b
$ Session -> IO a
act
newtype GhcT m a = GhcT { GhcT m a -> Session -> m a
unGhcT :: Session -> m a }
deriving (a -> GhcT m b -> GhcT m a
(a -> b) -> GhcT m a -> GhcT m b
(forall a b. (a -> b) -> GhcT m a -> GhcT m b)
-> (forall a b. a -> GhcT m b -> GhcT m a) -> Functor (GhcT m)
forall a b. a -> GhcT m b -> GhcT m a
forall a b. (a -> b) -> GhcT m a -> GhcT m b
forall (m :: * -> *) a b. Functor m => a -> GhcT m b -> GhcT m a
forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> GhcT m a -> GhcT m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> GhcT m b -> GhcT m a
$c<$ :: forall (m :: * -> *) a b. Functor m => a -> GhcT m b -> GhcT m a
fmap :: (a -> b) -> GhcT m a -> GhcT m b
$cfmap :: forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> GhcT m a -> GhcT m b
Evidence bound by a type signature of the constraint type Functor m
Functor)
deriving (Monad (GhcT m)
e -> GhcT m a
Monad (GhcT m)
-> (forall e a. Exception e => e -> GhcT m a)
-> MonadThrow (GhcT m)
forall e a. Exception e => e -> GhcT m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
forall {m :: * -> *}. MonadThrow m => Monad (GhcT m)
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> GhcT m a
throwM :: e -> GhcT m a
$cthrowM :: forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> GhcT m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a HsWrapper of the constraint type Exception e
Evidence bound by a HsWrapper of the constraint type Exception e
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a type signature of the constraint type MonadThrow m
Instance of class: Monad of the constraint type forall (m :: * -> *). Monad m => Monad (GhcT m)
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Evidence bound by a type signature of the constraint type MonadThrow m
Evidence bound by a type signature of the constraint type MonadThrow m
External instance of the constraint type forall (m :: * -> *) r. MonadThrow m => MonadThrow (ReaderT r m)
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
Instance of class: Monad of the constraint type forall (m :: * -> *). Monad m => Monad (GhcT m)
MonadThrow, MonadThrow (GhcT m)
MonadThrow (GhcT m)
-> (forall e a.
Exception e =>
GhcT m a -> (e -> GhcT m a) -> GhcT m a)
-> MonadCatch (GhcT m)
GhcT m a -> (e -> GhcT m a) -> GhcT m a
forall e a. Exception e => GhcT m a -> (e -> GhcT m a) -> GhcT m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
forall {m :: * -> *}. MonadCatch m => MonadThrow (GhcT m)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
GhcT m a -> (e -> GhcT m a) -> GhcT m a
catch :: GhcT m a -> (e -> GhcT m a) -> GhcT m a
$ccatch :: forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
GhcT m a -> (e -> GhcT m a) -> GhcT m a
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a HsWrapper of the constraint type Exception e
Evidence bound by a HsWrapper of the constraint type Exception e
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a type signature of the constraint type MonadCatch m
Instance of class: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => MonadThrow (GhcT m)
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
Evidence bound by a type signature of the constraint type MonadCatch m
Evidence bound by a type signature of the constraint type MonadCatch m
Instance of class: MonadThrow of the constraint type forall (m :: * -> *). MonadThrow m => MonadThrow (GhcT m)
External instance of the constraint type forall (m :: * -> *) r. MonadCatch m => MonadCatch (ReaderT r m)
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
MonadCatch, MonadCatch (GhcT m)
MonadCatch (GhcT m)
-> (forall b.
((forall a. GhcT m a -> GhcT m a) -> GhcT m b) -> GhcT m b)
-> (forall b.
((forall a. GhcT m a -> GhcT m a) -> GhcT m b) -> GhcT m b)
-> (forall a b c.
GhcT m a
-> (a -> ExitCase b -> GhcT m c)
-> (a -> GhcT m b)
-> GhcT m (b, c))
-> MonadMask (GhcT m)
GhcT m a
-> (a -> ExitCase b -> GhcT m c)
-> (a -> GhcT m b)
-> GhcT m (b, c)
((forall a. GhcT m a -> GhcT m a) -> GhcT m b) -> GhcT m b
((forall a. GhcT m a -> GhcT m a) -> GhcT m b) -> GhcT m b
forall b.
((forall a. GhcT m a -> GhcT m a) -> GhcT m b) -> GhcT m b
forall a b c.
GhcT m a
-> (a -> ExitCase b -> GhcT m c)
-> (a -> GhcT m b)
-> GhcT m (b, c)
forall (m :: * -> *).
MonadCatch m
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall a b c.
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c))
-> MonadMask m
forall {m :: * -> *}. MonadMask m => MonadCatch (GhcT m)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. GhcT m a -> GhcT m a) -> GhcT m b) -> GhcT m b
forall (m :: * -> *) a b c.
MonadMask m =>
GhcT m a
-> (a -> ExitCase b -> GhcT m c)
-> (a -> GhcT m b)
-> GhcT m (b, c)
generalBracket :: GhcT m a
-> (a -> ExitCase b -> GhcT m c)
-> (a -> GhcT m b)
-> GhcT m (b, c)
$cgeneralBracket :: forall (m :: * -> *) a b c.
MonadMask m =>
GhcT m a
-> (a -> ExitCase b -> GhcT m c)
-> (a -> GhcT m b)
-> GhcT m (b, c)
uninterruptibleMask :: ((forall a. GhcT m a -> GhcT m a) -> GhcT m b) -> GhcT m b
$cuninterruptibleMask :: forall (m :: * -> *) b.
MonadMask m =>
((forall a. GhcT m a -> GhcT m a) -> GhcT m b) -> GhcT m b
mask :: ((forall a. GhcT m a -> GhcT m a) -> GhcT m b) -> GhcT m b
$cmask :: forall (m :: * -> *) b.
MonadMask m =>
((forall a. GhcT m a -> GhcT m a) -> GhcT m b) -> GhcT m b
External instance of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
External instance of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
Instance of class: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadCatch (GhcT m)
External instance of the constraint type forall (m :: * -> *). MonadMask m => MonadCatch m
Evidence bound by a type signature of the constraint type MonadMask m
Evidence bound by a type signature of the constraint type MonadMask m
Instance of class: MonadCatch of the constraint type forall (m :: * -> *). MonadCatch m => MonadCatch (GhcT m)
External instance of the constraint type forall (m :: * -> *) r. MonadMask m => MonadMask (ReaderT r m)
MonadMask) via (ReaderT Session m)
liftGhcT :: m a -> GhcT m a
liftGhcT :: m a -> GhcT m a
liftGhcT m a
m = (Session -> m a) -> GhcT m a
forall (m :: * -> *) a. (Session -> m a) -> GhcT m a
GhcT ((Session -> m a) -> GhcT m a) -> (Session -> m a) -> GhcT m a
forall a b. (a -> b) -> a -> b
$ \Session
_ -> m a
m
instance Applicative m => Applicative (GhcT m) where
pure :: a -> GhcT m a
pure a
x = (Session -> m a) -> GhcT m a
forall (m :: * -> *) a. (Session -> m a) -> GhcT m a
GhcT ((Session -> m a) -> GhcT m a) -> (Session -> m a) -> GhcT m a
forall a b. (a -> b) -> a -> b
$ \Session
_ -> a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative m
pure a
x
GhcT m (a -> b)
g <*> :: GhcT m (a -> b) -> GhcT m a -> GhcT m b
<*> GhcT m a
m = (Session -> m b) -> GhcT m b
forall (m :: * -> *) a. (Session -> m a) -> GhcT m a
GhcT ((Session -> m b) -> GhcT m b) -> (Session -> m b) -> GhcT m b
forall a b. (a -> b) -> a -> b
$ \Session
s -> GhcT m (a -> b) -> Session -> m (a -> b)
forall (m :: * -> *) a. GhcT m a -> Session -> m a
unGhcT GhcT m (a -> b)
g Session
s m (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative m
<*> GhcT m a -> Session -> m a
forall (m :: * -> *) a. GhcT m a -> Session -> m a
unGhcT GhcT m a
m Session
s
instance Monad m => Monad (GhcT m) where
GhcT m a
m >>= :: GhcT m a -> (a -> GhcT m b) -> GhcT m b
>>= a -> GhcT m b
k = (Session -> m b) -> GhcT m b
forall (m :: * -> *) a. (Session -> m a) -> GhcT m a
GhcT ((Session -> m b) -> GhcT m b) -> (Session -> m b) -> GhcT m b
forall a b. (a -> b) -> a -> b
$ \Session
s -> do a
a <- GhcT m a -> Session -> m a
forall (m :: * -> *) a. GhcT m a -> Session -> m a
unGhcT GhcT m a
m Session
s; GhcT m b -> Session -> m b
forall (m :: * -> *) a. GhcT m a -> Session -> m a
unGhcT (a -> GhcT m b
k a
a) Session
s
instance MonadIO m => MonadIO (GhcT m) where
liftIO :: IO a -> GhcT m a
liftIO IO a
ioA = (Session -> m a) -> GhcT m a
forall (m :: * -> *) a. (Session -> m a) -> GhcT m a
GhcT ((Session -> m a) -> GhcT m a) -> (Session -> m a) -> GhcT m a
forall a b. (a -> b) -> a -> b
$ \Session
_ -> IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
Evidence bound by a type signature of the constraint type MonadIO m
liftIO IO a
ioA
instance MonadIO m => HasDynFlags (GhcT m) where
getDynFlags :: GhcT m DynFlags
getDynFlags = (Session -> m DynFlags) -> GhcT m DynFlags
forall (m :: * -> *) a. (Session -> m a) -> GhcT m a
GhcT ((Session -> m DynFlags) -> GhcT m DynFlags)
-> (Session -> m DynFlags) -> GhcT m DynFlags
forall a b. (a -> b) -> a -> b
$ \(Session IORef HscEnv
r) -> (HscEnv -> DynFlags) -> m HscEnv -> m DynFlags
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
External instance of the constraint type forall (m :: * -> *). MonadIO m => Monad m
Evidence bound by a type signature of the constraint type MonadIO m
liftM HscEnv -> DynFlags
hsc_dflags (IO HscEnv -> m HscEnv
forall (m :: * -> *) a. MonadIO m => IO a -> m a
Evidence bound by a type signature of the constraint type MonadIO m
liftIO (IO HscEnv -> m HscEnv) -> IO HscEnv -> m HscEnv
forall a b. (a -> b) -> a -> b
$ IORef HscEnv -> IO HscEnv
forall a. IORef a -> IO a
readIORef IORef HscEnv
r)
instance ExceptionMonad m => GhcMonad (GhcT m) where
getSession :: GhcT m HscEnv
getSession = (Session -> m HscEnv) -> GhcT m HscEnv
forall (m :: * -> *) a. (Session -> m a) -> GhcT m a
GhcT ((Session -> m HscEnv) -> GhcT m HscEnv)
-> (Session -> m HscEnv) -> GhcT m HscEnv
forall a b. (a -> b) -> a -> b
$ \(Session IORef HscEnv
r) -> IO HscEnv -> m HscEnv
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type ExceptionMonad m
liftIO (IO HscEnv -> m HscEnv) -> IO HscEnv -> m HscEnv
forall a b. (a -> b) -> a -> b
$ IORef HscEnv -> IO HscEnv
forall a. IORef a -> IO a
readIORef IORef HscEnv
r
setSession :: HscEnv -> GhcT m ()
setSession HscEnv
s' = (Session -> m ()) -> GhcT m ()
forall (m :: * -> *) a. (Session -> m a) -> GhcT m a
GhcT ((Session -> m ()) -> GhcT m ()) -> (Session -> m ()) -> GhcT m ()
forall a b. (a -> b) -> a -> b
$ \(Session IORef HscEnv
r) -> IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type ExceptionMonad m
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ IORef HscEnv -> HscEnv -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef HscEnv
r HscEnv
s'
printException :: GhcMonad m => SourceError -> m ()
printException :: SourceError -> m ()
printException SourceError
err = do
DynFlags
dflags <- m DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
Evidence bound by a type signature of the constraint type GhcMonad m
getSessionDynFlags
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a superclass of: GhcMonad of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DynFlags -> WarningMessages -> IO ()
printBagOfErrors DynFlags
dflags (SourceError -> WarningMessages
srcErrorMessages SourceError
err)
type WarnErrLogger = forall m. GhcMonad m => Maybe SourceError -> m ()
defaultWarnErrLogger :: WarnErrLogger
defaultWarnErrLogger :: Maybe SourceError -> m ()
defaultWarnErrLogger Maybe SourceError
Nothing = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadThrow m => Monad m
External instance of the constraint type forall (m :: * -> *). MonadCatch m => MonadThrow m
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a superclass of: GhcMonad of the constraint type forall (m :: * -> *). GhcMonad m => ExceptionMonad m
Evidence bound by a type signature of the constraint type GhcMonad m
return ()
defaultWarnErrLogger (Just SourceError
e) = SourceError -> m ()
forall (m :: * -> *). GhcMonad m => SourceError -> m ()
Evidence bound by a type signature of the constraint type GhcMonad m
printException SourceError
e