never executed always true always false
    1 {-# LANGUAGE CPP #-}
    2 
    3 -- | Types used by the runtime interpreter
    4 module GHC.Runtime.Interpreter.Types
    5    ( Interp(..)
    6    , InterpInstance(..)
    7    , IServ(..)
    8    , IServInstance(..)
    9    , IServConfig(..)
   10    , IServState(..)
   11    )
   12 where
   13 
   14 import GHC.Prelude
   15 import GHC.Linker.Types
   16 
   17 import GHCi.RemoteTypes
   18 import GHCi.Message         ( Pipe )
   19 import GHC.Types.Unique.FM
   20 import GHC.Data.FastString ( FastString )
   21 import Foreign
   22 
   23 import Control.Concurrent
   24 import System.Process   ( ProcessHandle, CreateProcess )
   25 
   26 -- | Interpreter
   27 data Interp = Interp
   28   { interpInstance :: !InterpInstance
   29       -- ^ Interpreter instance (internal, external)
   30 
   31   , interpLoader   :: !Loader
   32       -- ^ Interpreter loader
   33   }
   34 
   35 
   36 data InterpInstance
   37    = ExternalInterp !IServConfig !IServ -- ^ External interpreter
   38 #if defined(HAVE_INTERNAL_INTERPRETER)
   39    | InternalInterp                     -- ^ Internal interpreter
   40 #endif
   41 
   42 -- | External interpreter
   43 --
   44 -- The external interpreter is spawned lazily (on first use) to avoid slowing
   45 -- down sessions that don't require it. The contents of the MVar reflects the
   46 -- state of the interpreter (running or not).
   47 newtype IServ = IServ (MVar IServState)
   48 
   49 -- | State of an external interpreter
   50 data IServState
   51    = IServPending                 -- ^ Not spawned yet
   52    | IServRunning !IServInstance  -- ^ Running
   53 
   54 -- | Configuration needed to spawn an external interpreter
   55 data IServConfig = IServConfig
   56   { iservConfProgram  :: !String   -- ^ External program to run
   57   , iservConfOpts     :: ![String] -- ^ Command-line options
   58   , iservConfProfiled :: !Bool     -- ^ Use Profiling way
   59   , iservConfDynamic  :: !Bool     -- ^ Use Dynamic way
   60   , iservConfHook     :: !(Maybe (CreateProcess -> IO ProcessHandle)) -- ^ Hook
   61   , iservConfTrace    :: IO ()     -- ^ Trace action executed after spawn
   62   }
   63 
   64 -- | External interpreter instance
   65 data IServInstance = IServInstance
   66   { iservPipe              :: !Pipe
   67   , iservProcess           :: !ProcessHandle
   68   , iservLookupSymbolCache :: !(UniqFM FastString (Ptr ()))
   69   , iservPendingFrees      :: ![HValueRef]
   70       -- ^ Values that need to be freed before the next command is sent.
   71       -- Threads can append values to this list asynchronously (by modifying the
   72       -- IServ state MVar).
   73   }
   74