never executed always true always false
    1 {-# LANGUAGE DerivingVia #-}
    2 
    3 module GHC.Driver.Env.Types
    4   ( Hsc(..)
    5   , HscEnv(..)
    6   ) where
    7 
    8 import GHC.Driver.Errors.Types ( GhcMessage )
    9 import {-# SOURCE #-} GHC.Driver.Hooks
   10 import GHC.Driver.Session ( DynFlags, ContainsDynFlags(..), HasDynFlags(..) )
   11 import GHC.Prelude
   12 import GHC.Runtime.Context
   13 import GHC.Runtime.Interpreter.Types ( Interp )
   14 import GHC.Types.Error ( Messages )
   15 import GHC.Types.Name.Cache
   16 import GHC.Types.Target
   17 import GHC.Types.TypeEnv
   18 import GHC.Unit.Finder.Types
   19 import GHC.Unit.Module.Graph
   20 import GHC.Unit.Env
   21 import GHC.Utils.Logger
   22 import GHC.Utils.TmpFs
   23 import {-# SOURCE #-} GHC.Driver.Plugins
   24 
   25 import Control.Monad.IO.Class
   26 import Control.Monad.Trans.Reader
   27 import Control.Monad.Trans.State
   28 import Data.IORef
   29 import GHC.Driver.Env.KnotVars
   30 
   31 -- | The Hsc monad: Passing an environment and diagnostic state
   32 newtype Hsc a = Hsc (HscEnv -> Messages GhcMessage -> IO (a, Messages GhcMessage))
   33     deriving (Functor, Applicative, Monad, MonadIO)
   34       via ReaderT HscEnv (StateT (Messages GhcMessage) IO)
   35 
   36 instance HasDynFlags Hsc where
   37     getDynFlags = Hsc $ \e w -> return (hsc_dflags e, w)
   38 
   39 instance ContainsDynFlags HscEnv where
   40     extractDynFlags h = hsc_dflags h
   41 
   42 instance HasLogger Hsc where
   43     getLogger = Hsc $ \e w -> return (hsc_logger e, w)
   44 
   45 
   46 -- | HscEnv is like 'GHC.Driver.Monad.Session', except that some of the fields are immutable.
   47 -- An HscEnv is used to compile a single module from plain Haskell source
   48 -- code (after preprocessing) to either C, assembly or C--. It's also used
   49 -- to store the dynamic linker state to allow for multiple linkers in the
   50 -- same address space.
   51 -- Things like the module graph don't change during a single compilation.
   52 --
   53 -- Historical note: \"hsc\" used to be the name of the compiler binary,
   54 -- when there was a separate driver and compiler.  To compile a single
   55 -- module, the driver would invoke hsc on the source code... so nowadays
   56 -- we think of hsc as the layer of the compiler that deals with compiling
   57 -- a single module.
   58 data HscEnv
   59   = HscEnv {
   60         hsc_dflags :: DynFlags,
   61                 -- ^ The dynamic flag settings
   62 
   63         hsc_targets :: [Target],
   64                 -- ^ The targets (or roots) of the current session
   65 
   66         hsc_mod_graph :: ModuleGraph,
   67                 -- ^ The module graph of the current session
   68 
   69         hsc_IC :: InteractiveContext,
   70                 -- ^ The context for evaluating interactive statements
   71 
   72         hsc_NC  :: {-# UNPACK #-} !NameCache,
   73                 -- ^ Global Name cache so that each Name gets a single Unique.
   74                 -- Also track the origin of the Names.
   75 
   76         hsc_FC   :: {-# UNPACK #-} !FinderCache,
   77                 -- ^ The cached result of performing finding in the file system
   78 
   79         hsc_type_env_vars :: KnotVars (IORef TypeEnv)
   80                 -- ^ Used for one-shot compilation only, to initialise
   81                 -- the 'IfGblEnv'. See 'GHC.Tc.Utils.tcg_type_env_var' for
   82                 -- 'GHC.Tc.Utils.TcGblEnv'.  See also Note [hsc_type_env_var hack]
   83 
   84         , hsc_interp :: Maybe Interp
   85                 -- ^ target code interpreter (if any) to use for TH and GHCi.
   86                 -- See Note [Target code interpreter]
   87 
   88         , hsc_plugins :: ![LoadedPlugin]
   89                 -- ^ plugins dynamically loaded after processing arguments. What
   90                 -- will be loaded here is directed by DynFlags.pluginModNames.
   91                 -- Arguments are loaded from DynFlags.pluginModNameOpts.
   92                 --
   93                 -- The purpose of this field is to cache the plugins so they
   94                 -- don't have to be loaded each time they are needed.  See
   95                 -- 'GHC.Runtime.Loader.initializePlugins'.
   96 
   97         , hsc_static_plugins :: ![StaticPlugin]
   98                 -- ^ static plugins which do not need dynamic loading. These plugins are
   99                 -- intended to be added by GHC API users directly to this list.
  100                 --
  101                 -- To add dynamically loaded plugins through the GHC API see
  102                 -- 'addPluginModuleName' instead.
  103 
  104         , hsc_unit_env :: UnitEnv
  105                 -- ^ Unit environment (unit state, home unit, etc.).
  106                 --
  107                 -- Initialized from the databases cached in 'hsc_unit_dbs' and
  108                 -- from the DynFlags.
  109 
  110         , hsc_logger :: !Logger
  111                 -- ^ Logger with its flags.
  112                 --
  113                 -- Don't forget to update the logger flags if the logging
  114                 -- related DynFlags change. Or better, use hscSetFlags setter
  115                 -- which does it.
  116 
  117         , hsc_hooks :: !Hooks
  118                 -- ^ Hooks
  119 
  120         , hsc_tmpfs :: !TmpFs
  121                 -- ^ Temporary files
  122  }