module GHC.Driver.Pipeline.Monad (
CompPipeline(..), evalP
, PhasePlus(..)
, PipeEnv(..), PipeState(..), PipelineOutput(..)
, getPipeEnv, getPipeState, getPipeSession
, setDynFlags, setModLocation, setForeignOs, setIface
, pipeStateDynFlags, pipeStateModIface, setPlugins
) where
import GHC.Prelude
import GHC.Utils.Monad
import GHC.Utils.Outputable
import GHC.Utils.Logger
import GHC.Driver.Session
import GHC.Driver.Phases
import GHC.Driver.Env
import GHC.Driver.Plugins
import GHC.Utils.TmpFs (TempFileLifetime)
import GHC.Types.SourceFile
import GHC.Unit.Module
import GHC.Unit.Module.ModDetails
import GHC.Unit.Module.ModIface
import GHC.Unit.Module.Status
import Control.Monad
newtype CompPipeline a = P { unP :: PipeEnv -> PipeState -> IO (PipeState, a) }
deriving (Functor)
evalP :: CompPipeline a -> PipeEnv -> PipeState -> IO (PipeState, a)
evalP (P f) env st = f env st
instance Applicative CompPipeline where
pure a = P $ \_env state -> return (state, a)
(<*>) = ap
instance Monad CompPipeline where
P m >>= k = P $ \env state -> do (state',a) <- m env state
unP (k a) env state'
instance MonadIO CompPipeline where
liftIO m = P $ \_env state -> do a <- m; return (state, a)
data PhasePlus = RealPhase Phase
| HscOut HscSource ModuleName HscStatus
instance Outputable PhasePlus where
ppr (RealPhase p) = ppr p
ppr (HscOut {}) = text "HscOut"
data PipeEnv = PipeEnv {
stop_phase :: Phase,
src_filename :: String,
src_basename :: String,
src_suffix :: String,
output_spec :: PipelineOutput
}
data PipeState = PipeState {
hsc_env :: HscEnv,
maybe_loc :: Maybe ModLocation,
foreign_os :: [FilePath],
iface :: Maybe (ModIface, ModDetails)
}
pipeStateDynFlags :: PipeState -> DynFlags
pipeStateDynFlags = hsc_dflags . hsc_env
pipeStateModIface :: PipeState -> Maybe (ModIface, ModDetails)
pipeStateModIface = iface
data PipelineOutput
= Temporary TempFileLifetime
| Persistent
| SpecificFile
deriving Show
getPipeEnv :: CompPipeline PipeEnv
getPipeEnv = P $ \env state -> return (state, env)
getPipeState :: CompPipeline PipeState
getPipeState = P $ \_env state -> return (state, state)
getPipeSession :: CompPipeline HscEnv
getPipeSession = P $ \_env state -> return (state, hsc_env state)
instance HasDynFlags CompPipeline where
getDynFlags = P $ \_env state -> return (state, hsc_dflags (hsc_env state))
instance HasLogger CompPipeline where
getLogger = P $ \_env state -> return (state, hsc_logger (hsc_env state))
setDynFlags :: DynFlags -> CompPipeline ()
setDynFlags dflags = P $ \_env state ->
return (state{hsc_env= (hsc_env state){ hsc_dflags = dflags }}, ())
setPlugins :: [LoadedPlugin] -> [StaticPlugin] -> CompPipeline ()
setPlugins dyn static = P $ \_env state ->
let hsc_env' = (hsc_env state){ hsc_plugins = dyn, hsc_static_plugins = static }
in return (state{hsc_env = hsc_env'}, ())
setModLocation :: ModLocation -> CompPipeline ()
setModLocation loc = P $ \_env state ->
return (state{ maybe_loc = Just loc }, ())
setForeignOs :: [FilePath] -> CompPipeline ()
setForeignOs os = P $ \_env state ->
return (state{ foreign_os = os }, ())
setIface :: ModIface -> ModDetails -> CompPipeline ()
setIface iface details = P $ \_env state -> return (state{ iface = Just (iface, details) }, ())