never executed always true always false
    1 -- | The home unit is the unit (i.e. compiled package) that contains the module
    2 -- we are compiling/typechecking.
    3 module GHC.Unit.Home
    4    ( GenHomeUnit (..)
    5    , HomeUnit
    6    , homeUnitId
    7    , homeUnitInstantiations
    8    , homeUnitInstanceOf
    9    , homeUnitInstanceOfMaybe
   10    , homeUnitAsUnit
   11    , homeUnitMap
   12    -- * Predicates
   13    , isHomeUnitIndefinite
   14    , isHomeUnitDefinite
   15    , isHomeUnitInstantiating
   16    , isHomeUnit
   17    , isHomeUnitId
   18    , isHomeUnitInstanceOf
   19    , isHomeModule
   20    , isHomeInstalledModule
   21    , notHomeModule
   22    , notHomeModuleMaybe
   23    , notHomeInstalledModule
   24    , notHomeInstalledModuleMaybe
   25    -- * Helpers
   26    , mkHomeModule
   27    , mkHomeInstalledModule
   28    , homeModuleInstantiation
   29    , homeModuleNameInstantiation
   30    )
   31 where
   32 
   33 import GHC.Prelude
   34 import GHC.Unit.Types
   35 import GHC.Unit.Module.Name
   36 import Data.Maybe
   37 
   38 -- | Information about the home unit (i.e., the until that will contain the
   39 -- modules we are compiling)
   40 --
   41 -- The unit identifier of the instantiating units is left open to allow
   42 -- switching from UnitKey (what is provided by the user) to UnitId (internal
   43 -- unit identifier) with `homeUnitMap`.
   44 --
   45 -- TODO: this isn't implemented yet. UnitKeys are still converted too early into
   46 -- UnitIds in GHC.Unit.State.readUnitDataBase
   47 data GenHomeUnit u
   48    = DefiniteHomeUnit UnitId (Maybe (u, GenInstantiations u))
   49       -- ^ Definite home unit (i.e. that we can compile).
   50       --
   51       -- Nothing:        not an instantiated unit
   52       -- Just (i,insts): made definite by instantiating "i" with "insts"
   53 
   54    | IndefiniteHomeUnit UnitId (GenInstantiations u)
   55       -- ^ Indefinite home unit (i.e. that we can only typecheck)
   56       --
   57       -- All the holes are instantiated with fake modules from the Hole unit.
   58       -- See Note [Representation of module/name variables] in "GHC.Unit"
   59 
   60 type HomeUnit = GenHomeUnit UnitId
   61 
   62 -- | Return home unit id
   63 homeUnitId :: GenHomeUnit u -> UnitId
   64 homeUnitId (DefiniteHomeUnit u _)   = u
   65 homeUnitId (IndefiniteHomeUnit u _) = u
   66 
   67 -- | Return home unit instantiations
   68 homeUnitInstantiations :: GenHomeUnit u -> GenInstantiations u
   69 homeUnitInstantiations (DefiniteHomeUnit   _ Nothing)       = []
   70 homeUnitInstantiations (DefiniteHomeUnit   _ (Just (_,is))) = is
   71 homeUnitInstantiations (IndefiniteHomeUnit _ is)            = is
   72 
   73 -- | Return the unit id of the unit that is instantiated by the home unit.
   74 --
   75 -- E.g. if home unit = q[A=p:B,...] we return q.
   76 --
   77 -- If the home unit is not an instance of another unit, we return its own unit
   78 -- id (it is an instance of itself if you will).
   79 homeUnitInstanceOf :: HomeUnit -> UnitId
   80 homeUnitInstanceOf h = fromMaybe (homeUnitId h) (homeUnitInstanceOfMaybe h)
   81 
   82 -- | Return the unit id of the unit that is instantiated by the home unit.
   83 --
   84 -- E.g. if home unit = q[A=p:B,...] we return (Just q).
   85 --
   86 -- If the home unit is not an instance of another unit, we return Nothing.
   87 homeUnitInstanceOfMaybe :: GenHomeUnit u -> Maybe u
   88 homeUnitInstanceOfMaybe (DefiniteHomeUnit   _ (Just (u,_))) = Just u
   89 homeUnitInstanceOfMaybe _                                   = Nothing
   90 
   91 -- | Return the home unit as a normal unit.
   92 --
   93 -- We infer from the home unit itself the kind of unit we create:
   94 --    1. If the home unit is definite, we must be compiling so we return a real
   95 --    unit. The definite home unit may be the result of a unit instantiation,
   96 --    say `p = q[A=r:X]`. In this case we could have returned a virtual unit
   97 --    `q[A=r:X]` but it's not what the clients of this function expect,
   98 --    especially because `p` is lost when we do this. The unit id of a virtual
   99 --    unit is made up internally so `unitId(q[A=r:X])` is not equal to `p`.
  100 --
  101 --    2. If the home unit is indefinite we can only create a virtual unit from
  102 --    it. It's ok because we must be only typechecking the home unit so we won't
  103 --    produce any code object that rely on the unit id of this virtual unit.
  104 homeUnitAsUnit :: HomeUnit -> Unit
  105 homeUnitAsUnit (DefiniteHomeUnit u _)    = RealUnit (Definite u)
  106 homeUnitAsUnit (IndefiniteHomeUnit u is) = mkVirtUnit u is
  107 
  108 -- | Map over the unit identifier for instantiating units
  109 homeUnitMap :: IsUnitId v => (u -> v) -> GenHomeUnit u -> GenHomeUnit v
  110 homeUnitMap _ (DefiniteHomeUnit u Nothing)       = DefiniteHomeUnit u Nothing
  111 homeUnitMap f (DefiniteHomeUnit u (Just (i,is))) = DefiniteHomeUnit u (Just (f i, mapInstantiations f is))
  112 homeUnitMap f (IndefiniteHomeUnit u is)          = IndefiniteHomeUnit u (mapInstantiations f is)
  113 
  114 ----------------------------
  115 -- Predicates
  116 ----------------------------
  117 
  118 -- | Test if we are type-checking an indefinite unit
  119 --
  120 -- (if it is not, we should never use on-the-fly renaming)
  121 isHomeUnitIndefinite :: GenHomeUnit u -> Bool
  122 isHomeUnitIndefinite (DefiniteHomeUnit {})   = False
  123 isHomeUnitIndefinite (IndefiniteHomeUnit {}) = True
  124 
  125 -- | Test if we are compiling a definite unit
  126 --
  127 -- (if it is, we should never use on-the-fly renaming)
  128 isHomeUnitDefinite :: GenHomeUnit u -> Bool
  129 isHomeUnitDefinite (DefiniteHomeUnit {})   = True
  130 isHomeUnitDefinite (IndefiniteHomeUnit {}) = False
  131 
  132 -- | Test if we are compiling by instantiating a definite unit
  133 isHomeUnitInstantiating :: GenHomeUnit u -> Bool
  134 isHomeUnitInstantiating u =
  135    isHomeUnitDefinite u && not (null (homeUnitInstantiations u))
  136 
  137 -- | Test if the unit is the home unit
  138 isHomeUnit :: HomeUnit -> Unit -> Bool
  139 isHomeUnit hu u = u == homeUnitAsUnit hu
  140 
  141 -- | Test if the unit-id is the home unit-id
  142 isHomeUnitId :: GenHomeUnit u -> UnitId -> Bool
  143 isHomeUnitId hu uid = uid == homeUnitId hu
  144 
  145 -- | Test if the home unit is an instance of the given unit-id
  146 isHomeUnitInstanceOf :: HomeUnit -> UnitId -> Bool
  147 isHomeUnitInstanceOf hu u = homeUnitInstanceOf hu == u
  148 
  149 -- | Test if the module comes from the home unit
  150 isHomeModule :: HomeUnit -> Module -> Bool
  151 isHomeModule hu m = isHomeUnit hu (moduleUnit m)
  152 
  153 -- | Test if the module comes from the home unit
  154 isHomeInstalledModule :: GenHomeUnit u -> InstalledModule -> Bool
  155 isHomeInstalledModule hu m = isHomeUnitId hu (moduleUnit m)
  156 
  157 
  158 -- | Test if a module doesn't come from the given home unit
  159 notHomeInstalledModule :: GenHomeUnit u -> InstalledModule -> Bool
  160 notHomeInstalledModule hu m = not (isHomeInstalledModule hu m)
  161 
  162 -- | Test if a module doesn't come from the given home unit
  163 notHomeInstalledModuleMaybe :: Maybe (GenHomeUnit u) -> InstalledModule -> Bool
  164 notHomeInstalledModuleMaybe mh m = fromMaybe True $ fmap (`notHomeInstalledModule` m) mh
  165 
  166 
  167 -- | Test if a module doesn't come from the given home unit
  168 notHomeModule :: HomeUnit -> Module -> Bool
  169 notHomeModule hu m = not (isHomeModule hu m)
  170 
  171 -- | Test if a module doesn't come from the given home unit
  172 notHomeModuleMaybe :: Maybe HomeUnit -> Module -> Bool
  173 notHomeModuleMaybe mh m = fromMaybe True $ fmap (`notHomeModule` m) mh
  174 
  175 ----------------------------
  176 -- helpers
  177 ----------------------------
  178 
  179 -- | Make a module in home unit
  180 mkHomeModule :: HomeUnit -> ModuleName -> Module
  181 mkHomeModule hu = mkModule (homeUnitAsUnit hu)
  182 
  183 -- | Make a module in home unit
  184 mkHomeInstalledModule :: GenHomeUnit u -> ModuleName -> InstalledModule
  185 mkHomeInstalledModule hu = mkModule (homeUnitId hu)
  186 
  187 -- | Return the module that is used to instantiate the given home module name.
  188 -- If the ModuleName doesn't refer to a signature, return the actual home
  189 -- module.
  190 --
  191 -- E.g., the instantiating module of @A@ in @p[A=q[]:B]@ is @q[]:B@.
  192 --       the instantiating module of @A@ in @p@ is @p:A@.
  193 homeModuleNameInstantiation :: HomeUnit -> ModuleName -> Module
  194 homeModuleNameInstantiation hu mod_name =
  195     case lookup mod_name (homeUnitInstantiations hu) of
  196         Nothing  -> mkHomeModule hu mod_name
  197         Just mod -> mod
  198 
  199 -- | Return the module that is used to instantiate the given home module.
  200 --
  201 -- If the given module isn't a module hole, return the actual home module.
  202 --
  203 -- E.g., the instantiating module of @p:A@ in @p[A=q[]:B]@ is @q[]:B@.
  204 --       the instantiating module of @r:A@ in @p[A=q[]:B]@ is @r:A@.
  205 --       the instantiating module of @p:A@ in @p@ is @p:A@.
  206 --       the instantiating module of @r:A@ in @p@ is @r:A@.
  207 homeModuleInstantiation :: HomeUnit -> Module -> Module
  208 homeModuleInstantiation hu mod
  209    | isHomeModule hu mod = homeModuleNameInstantiation hu (moduleName mod)
  210    | otherwise           = mod
  211