never executed always true always false
    1 {-# LANGUAGE KindSignatures #-}
    2 {-# LANGUAGE ConstraintKinds #-}
    3 {-# LANGUAGE MultiParamTypeClasses #-}
    4 -- | The 'TPipelineClass' and 'MonadUse' classes and associated types
    5 module GHC.Driver.Pipeline.Monad (
    6   TPipelineClass, MonadUse(..)
    7 
    8   , PipeEnv(..)
    9   , PipelineOutput(..)
   10   ) where
   11 
   12 import GHC.Prelude
   13 import Control.Monad.IO.Class
   14 import qualified Data.Kind as K
   15 import GHC.Driver.Phases
   16 import GHC.Utils.TmpFs
   17 
   18 -- The interface that the pipeline monad must implement.
   19 type TPipelineClass (f :: K.Type -> K.Type) (m :: K.Type -> K.Type)
   20   = (Functor m, MonadIO m, Applicative m, Monad m, MonadUse f m)
   21 
   22 -- | Lift a `f` action into an `m` action.
   23 class MonadUse f m where
   24   use :: f a -> m a
   25 
   26 -- PipeEnv: invariant information passed down through the pipeline
   27 data PipeEnv = PipeEnv {
   28        stop_phase   :: StopPhase,   -- ^ Stop just after this phase
   29        src_filename :: String,      -- ^ basename of original input source
   30        src_basename :: String,      -- ^ basename of original input source
   31        src_suffix   :: String,      -- ^ its extension
   32        output_spec  :: PipelineOutput -- ^ says where to put the pipeline output
   33   }
   34 
   35 
   36 data PipelineOutput
   37   = Temporary TempFileLifetime
   38         -- ^ Output should be to a temporary file: we're going to
   39         -- run more compilation steps on this output later.
   40   | Persistent
   41         -- ^ We want a persistent file, i.e. a file in the current directory
   42         -- derived from the input filename, but with the appropriate extension.
   43         -- eg. in "ghc -c Foo.hs" the output goes into ./Foo.o.
   44   | SpecificFile
   45         -- ^ The output must go into the specific outputFile in DynFlags.
   46         -- We don't store the filename in the constructor as it changes
   47         -- when doing -dynamic-too.
   48   | NoOutputFile
   49         -- ^ No output should be created, like in Interpreter or NoBackend.
   50     deriving Show