never executed always true always false
    1 -- | This is the syntax for bkp files which are parsed in 'ghc --backpack'
    2 -- mode.  This syntax is used purely for testing purposes.
    3 
    4 module GHC.Driver.Backpack.Syntax (
    5     -- * Backpack abstract syntax
    6     HsUnitId(..),
    7     LHsUnitId,
    8     HsModuleSubst,
    9     LHsModuleSubst,
   10     HsModuleId(..),
   11     LHsModuleId,
   12     HsComponentId(..),
   13     LHsUnit, HsUnit(..),
   14     LHsUnitDecl, HsUnitDecl(..),
   15     IncludeDecl(..),
   16     LRenaming, Renaming(..),
   17     ) where
   18 
   19 import GHC.Prelude
   20 
   21 import GHC.Hs
   22 
   23 import GHC.Types.SrcLoc
   24 import GHC.Types.SourceFile
   25 
   26 import GHC.Unit.Module.Name
   27 import GHC.Unit.Types
   28 import GHC.Unit.Info
   29 
   30 import GHC.Utils.Outputable
   31 
   32 {-
   33 ************************************************************************
   34 *                                                                      *
   35                         User syntax
   36 *                                                                      *
   37 ************************************************************************
   38 -}
   39 
   40 data HsComponentId = HsComponentId {
   41     hsPackageName :: PackageName,
   42     hsComponentId :: UnitId
   43     }
   44 
   45 instance Outputable HsComponentId where
   46     ppr (HsComponentId _pn cid) = ppr cid -- todo debug with pn
   47 
   48 data HsUnitId n = HsUnitId (Located n) [LHsModuleSubst n]
   49 type LHsUnitId n = Located (HsUnitId n)
   50 
   51 type HsModuleSubst n = (Located ModuleName, LHsModuleId n)
   52 type LHsModuleSubst n = Located (HsModuleSubst n)
   53 
   54 data HsModuleId n = HsModuleVar (Located ModuleName)
   55                   | HsModuleId (LHsUnitId n) (Located ModuleName)
   56 type LHsModuleId n = Located (HsModuleId n)
   57 
   58 -- | Top level @unit@ declaration in a Backpack file.
   59 data HsUnit n = HsUnit {
   60         hsunitName :: Located n,
   61         hsunitBody :: [LHsUnitDecl n]
   62     }
   63 type LHsUnit n = Located (HsUnit n)
   64 
   65 -- | A declaration in a package, e.g. a module or signature definition,
   66 -- or an include.
   67 data HsUnitDecl n
   68     = DeclD   HscSource (Located ModuleName) (Maybe (Located HsModule))
   69     | IncludeD   (IncludeDecl n)
   70 type LHsUnitDecl n = Located (HsUnitDecl n)
   71 
   72 -- | An include of another unit
   73 data IncludeDecl n = IncludeDecl {
   74         idUnitId :: LHsUnitId n,
   75         idModRenaming :: Maybe [ LRenaming ],
   76         -- | Is this a @dependency signature@ include?  If so,
   77         -- we don't compile this include when we instantiate this
   78         -- unit (as there should not be any modules brought into
   79         -- scope.)
   80         idSignatureInclude :: Bool
   81     }
   82 
   83 -- | Rename a module from one name to another.  The identity renaming
   84 -- means that the module should be brought into scope.
   85 data Renaming = Renaming { renameFrom :: Located ModuleName
   86                          , renameTo :: Maybe (Located ModuleName) }
   87 type LRenaming = Located Renaming