never executed always true always false
    1 module GHC.Types.SourceFile
    2    ( HscSource(..)
    3    , hscSourceToIsBoot
    4    , isHsBootOrSig
    5    , isHsigFile
    6    , hscSourceString
    7    )
    8 where
    9 
   10 import GHC.Prelude
   11 import GHC.Utils.Binary
   12 import GHC.Unit.Types
   13 
   14 -- Note [HscSource types]
   15 -- ~~~~~~~~~~~~~~~~~~~~~~
   16 -- There are three types of source file for Haskell code:
   17 --
   18 --      * HsSrcFile is an ordinary hs file which contains code,
   19 --
   20 --      * HsBootFile is an hs-boot file, which is used to break
   21 --        recursive module imports (there will always be an
   22 --        HsSrcFile associated with it), and
   23 --
   24 --      * HsigFile is an hsig file, which contains only type
   25 --        signatures and is used to specify signatures for
   26 --        modules.
   27 --
   28 -- Syntactically, hs-boot files and hsig files are quite similar: they
   29 -- only include type signatures and must be associated with an
   30 -- actual HsSrcFile.  isHsBootOrSig allows us to abstract over code
   31 -- which is indifferent to which.  However, there are some important
   32 -- differences, mostly owing to the fact that hsigs are proper
   33 -- modules (you `import Sig` directly) whereas HsBootFiles are
   34 -- temporary placeholders (you `import {-# SOURCE #-} Mod).
   35 -- When we finish compiling the true implementation of an hs-boot,
   36 -- we replace the HomeModInfo with the real HsSrcFile.  An HsigFile, on the
   37 -- other hand, is never replaced (in particular, we *cannot* use the
   38 -- HomeModInfo of the original HsSrcFile backing the signature, since it
   39 -- will export too many symbols.)
   40 --
   41 -- Additionally, while HsSrcFile is the only Haskell file
   42 -- which has *code*, we do generate .o files for HsigFile, because
   43 -- this is how the recompilation checker figures out if a file
   44 -- needs to be recompiled.  These are fake object files which
   45 -- should NOT be linked against.
   46 
   47 data HscSource
   48    = HsSrcFile  -- ^ .hs file
   49    | HsBootFile -- ^ .hs-boot file
   50    | HsigFile   -- ^ .hsig file
   51    deriving (Eq, Ord, Show)
   52 
   53 -- | Tests if an 'HscSource' is a boot file, primarily for constructing elements
   54 -- of 'BuildModule'. We conflate signatures and modules because they are bound
   55 -- in the same namespace; only boot interfaces can be disambiguated with
   56 -- `import {-# SOURCE #-}`.
   57 hscSourceToIsBoot :: HscSource -> IsBootInterface
   58 hscSourceToIsBoot HsBootFile = IsBoot
   59 hscSourceToIsBoot _ = NotBoot
   60 
   61 instance Binary HscSource where
   62     put_ bh HsSrcFile = putByte bh 0
   63     put_ bh HsBootFile = putByte bh 1
   64     put_ bh HsigFile = putByte bh 2
   65     get bh = do
   66         h <- getByte bh
   67         case h of
   68             0 -> return HsSrcFile
   69             1 -> return HsBootFile
   70             _ -> return HsigFile
   71 
   72 hscSourceString :: HscSource -> String
   73 hscSourceString HsSrcFile   = ""
   74 hscSourceString HsBootFile  = "[boot]"
   75 hscSourceString HsigFile    = "[sig]"
   76 
   77 -- See Note [HscSource types]
   78 isHsBootOrSig :: HscSource -> Bool
   79 isHsBootOrSig HsBootFile = True
   80 isHsBootOrSig HsigFile   = True
   81 isHsBootOrSig _          = False
   82 
   83 isHsigFile :: HscSource -> Bool
   84 isHsigFile HsigFile = True
   85 isHsigFile _        = False