{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module GHC.Driver.Pipeline.Monad (
TPipelineClass, MonadUse(..)
, PipeEnv(..)
, PipelineOutput(..)
) where
import GHC.Prelude
import Control.Monad.IO.Class
import qualified Data.Kind as K
import GHC.Driver.Phases
import GHC.Utils.TmpFs
type TPipelineClass (f :: K.Type -> K.Type) (m :: K.Type -> K.Type)
= (Functor m, MonadIO m, Applicative m, Monad m, MonadUse f m)
class MonadUse f m where
use :: f a -> m a
data PipeEnv = PipeEnv {
PipeEnv -> StopPhase
stop_phase :: StopPhase,
PipeEnv -> String
src_filename :: String,
PipeEnv -> String
src_basename :: String,
PipeEnv -> String
src_suffix :: String,
PipeEnv -> Phase
start_phase :: Phase,
PipeEnv -> PipelineOutput
output_spec :: PipelineOutput
}
data PipelineOutput
= Temporary TempFileLifetime
| Persistent
| SpecificFile
| NoOutputFile
deriving Int -> PipelineOutput -> ShowS
[PipelineOutput] -> ShowS
PipelineOutput -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PipelineOutput] -> ShowS
$cshowList :: [PipelineOutput] -> ShowS
show :: PipelineOutput -> String
$cshow :: PipelineOutput -> String
showsPrec :: Int -> PipelineOutput -> ShowS
$cshowsPrec :: Int -> PipelineOutput -> ShowS
Show