never executed always true always false
    1 module GHC.Types.Target
    2    ( Target(..)
    3    , TargetId(..)
    4    , InputFileBuffer
    5    , pprTarget
    6    , pprTargetId
    7    )
    8 where
    9 
   10 import GHC.Prelude
   11 import GHC.Driver.Phases ( Phase )
   12 import GHC.Unit
   13 import GHC.Data.StringBuffer ( StringBuffer )
   14 import GHC.Utils.Outputable
   15 
   16 import Data.Time
   17 
   18 -- | A compilation target.
   19 --
   20 -- A target may be supplied with the actual text of the
   21 -- module.  If so, use this instead of the file contents (this
   22 -- is for use in an IDE where the file hasn't been saved by
   23 -- the user yet).
   24 --
   25 -- These fields are strict because Targets are long lived.
   26 data Target
   27   = Target {
   28       targetId           :: !TargetId, -- ^ module or filename
   29       targetAllowObjCode :: !Bool,     -- ^ object code allowed?
   30       targetUnitId       :: !UnitId,   -- ^ id of the unit this target is part of
   31       targetContents     :: !(Maybe (InputFileBuffer, UTCTime))
   32       -- ^ Optional in-memory buffer containing the source code GHC should
   33       -- use for this target instead of reading it from disk.
   34       --
   35       -- Since GHC version 8.10 modules which require preprocessors such as
   36       -- Literate Haskell or CPP to run are also supported.
   37       --
   38       -- If a corresponding source file does not exist on disk this will
   39       -- result in a 'SourceError' exception if @targetId = TargetModule _@
   40       -- is used. However together with @targetId = TargetFile _@ GHC will
   41       -- not complain about the file missing.
   42     }
   43 
   44 data TargetId
   45   = TargetModule !ModuleName
   46         -- ^ A module name: search for the file
   47   | TargetFile !FilePath !(Maybe Phase)
   48         -- ^ A filename: preprocess & parse it to find the module name.
   49         -- If specified, the Phase indicates how to compile this file
   50         -- (which phase to start from).  Nothing indicates the starting phase
   51         -- should be determined from the suffix of the filename.
   52   deriving Eq
   53 
   54 type InputFileBuffer = StringBuffer
   55 
   56 
   57 pprTarget :: Target -> SDoc
   58 pprTarget Target { targetId = id, targetAllowObjCode = obj } =
   59     (if obj then empty else char '*') <> pprTargetId id
   60 
   61 instance Outputable Target where
   62     ppr = pprTarget
   63 
   64 pprTargetId :: TargetId -> SDoc
   65 pprTargetId (TargetModule m) = ppr m
   66 pprTargetId (TargetFile f _) = text f
   67 
   68 instance Outputable TargetId where
   69     ppr = pprTargetId
   70