ghc-9.2.3: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Unit.Types

Description

Unit & Module types

This module is used to resolve the loops between Unit and Module types (Module references a Unit and vice-versa).

Synopsis

Modules

data GenModule unit Source #

A generic module is a pair of a unit identifier and a ModuleName.

Constructors

Module 

Fields

Instances

Instances details
Functor GenModule Source # 
Instance details

Defined in GHC.Unit.Types

Methods

fmap :: (a -> b) -> GenModule a -> GenModule b Source #

(<$) :: a -> GenModule b -> GenModule a Source #

Uniquable Module Source # 
Instance details

Defined in GHC.Unit.Types

Outputable InstalledModule Source # 
Instance details

Defined in GHC.Unit.Types

Outputable InstantiatedModule Source # 
Instance details

Defined in GHC.Unit.Types

Outputable Module Source # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Module -> SDoc Source #

Data unit => Data (GenModule unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenModule unit -> c (GenModule unit) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenModule unit) Source #

toConstr :: GenModule unit -> Constr Source #

dataTypeOf :: GenModule unit -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GenModule unit)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GenModule unit)) Source #

gmapT :: (forall b. Data b => b -> b) -> GenModule unit -> GenModule unit Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenModule unit -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenModule unit -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GenModule unit -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenModule unit -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenModule unit -> m (GenModule unit) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenModule unit -> m (GenModule unit) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenModule unit -> m (GenModule unit) Source #

NFData (GenModule a) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

rnf :: GenModule a -> () Source #

Binary a => Binary (GenModule a) Source # 
Instance details

Defined in GHC.Unit.Types

Eq unit => Eq (GenModule unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

(==) :: GenModule unit -> GenModule unit -> Bool #

(/=) :: GenModule unit -> GenModule unit -> Bool #

Ord unit => Ord (GenModule unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

compare :: GenModule unit -> GenModule unit -> Ordering #

(<) :: GenModule unit -> GenModule unit -> Bool #

(<=) :: GenModule unit -> GenModule unit -> Bool #

(>) :: GenModule unit -> GenModule unit -> Bool #

(>=) :: GenModule unit -> GenModule unit -> Bool #

max :: GenModule unit -> GenModule unit -> GenModule unit #

min :: GenModule unit -> GenModule unit -> GenModule unit #

type Module = GenModule Unit Source #

A Module is a pair of a Unit and a ModuleName.

type InstalledModule = GenModule UnitId Source #

A InstalledModule is a Module whose unit is identified with an UnitId.

moduleFreeHoles :: GenModule (GenUnit u) -> UniqDSet ModuleName Source #

Calculate the free holes of a Module. If this set is non-empty, this module was defined in an indefinite library that had required signatures.

If a module has free holes, that means that substitutions can operate on it; if it has no free holes, substituting over a module has no effect.

Units

class IsUnitId u Source #

Class for types that are used as unit identifiers (UnitKey, UnitId, Unit)

We need this class because we create new unit ids for virtual units (see VirtUnit) and they have to to be made from units with different kinds of identifiers.

Minimal complete definition

unitFS

Instances

Instances details
IsUnitId UnitId Source # 
Instance details

Defined in GHC.Unit.Types

IsUnitId UnitKey Source # 
Instance details

Defined in GHC.Unit.Types

IsUnitId unit => IsUnitId (Definite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

unitFS :: Definite unit -> FastString Source #

IsUnitId u => IsUnitId (GenUnit u) Source # 
Instance details

Defined in GHC.Unit.Types

IsUnitId unit => IsUnitId (Indefinite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

unitFS :: Indefinite unit -> FastString Source #

data GenUnit uid Source #

A unit identifier identifies a (possibly partially) instantiated library. It is primarily used as part of Module, which in turn is used in Name, which is used to give names to entities when typechecking.

There are two possible forms for a Unit:

1) It can be a RealUnit, in which case we just have a DefUnitId that uniquely identifies some fully compiled, installed library we have on disk.

2) It can be an VirtUnit. When we are typechecking a library with missing holes, we may need to instantiate a library on the fly (in which case we don't have any on-disk representation.) In that case, you have an InstantiatedUnit, which explicitly records the instantiation, so that we can substitute over it.

Constructors

RealUnit !(Definite uid)

Installed definite unit (either a fully instantiated unit or a closed unit)

VirtUnit !(GenInstantiatedUnit uid)

Virtual unit instantiated on-the-fly. It may be definite if all the holes are instantiated but we don't have code objects for it.

HoleUnit

Fake hole unit

Instances

Instances details
Data Unit Source # 
Instance details

Defined in GHC.Unit.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Unit -> c Unit Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Unit Source #

toConstr :: Unit -> Constr Source #

dataTypeOf :: Unit -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Unit) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Unit) Source #

gmapT :: (forall b. Data b => b -> b) -> Unit -> Unit Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Unit -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Unit -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Unit -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Unit -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Unit -> m Unit Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Unit -> m Unit Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Unit -> m Unit Source #

Show Unit Source # 
Instance details

Defined in GHC.Unit.Types

NFData Unit Source # 
Instance details

Defined in GHC.Unit.Types

Methods

rnf :: Unit -> () Source #

Uniquable Module Source # 
Instance details

Defined in GHC.Unit.Types

Binary Unit Source # 
Instance details

Defined in GHC.Unit.Types

Outputable Module Source # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Module -> SDoc Source #

Outputable Unit Source # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Unit -> SDoc Source #

Ord Unit Source # 
Instance details

Defined in GHC.Unit.Types

Methods

compare :: Unit -> Unit -> Ordering #

(<) :: Unit -> Unit -> Bool #

(<=) :: Unit -> Unit -> Bool #

(>) :: Unit -> Unit -> Bool #

(>=) :: Unit -> Unit -> Bool #

max :: Unit -> Unit -> Unit #

min :: Unit -> Unit -> Unit #

IsUnitId u => Uniquable (GenUnit u) Source # 
Instance details

Defined in GHC.Unit.Types

IsUnitId u => IsUnitId (GenUnit u) Source # 
Instance details

Defined in GHC.Unit.Types

IsUnitId u => Eq (GenUnit u) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

(==) :: GenUnit u -> GenUnit u -> Bool #

(/=) :: GenUnit u -> GenUnit u -> Bool #

newtype UnitId Source #

A UnitId identifies a built library in a database and is used to generate unique symbols, etc. It's usually of the form:

pkgname-1.2:libname+hash

These UnitId are provided to us via the -this-unit-id flag.

The library in question may be definite or indefinite; if it is indefinite, none of the holes have been filled (we never install partially instantiated libraries as we can cheaply instantiate them on-the-fly, cf VirtUnit). Put another way, an installed unit id is either fully instantiated, or not instantiated at all.

Constructors

UnitId 

Fields

  • unitIdFS :: FastString

    The full hashed unit identifier, including the component id and the hash.

Instances

Instances details
Data Unit Source # 
Instance details

Defined in GHC.Unit.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Unit -> c Unit Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Unit Source #

toConstr :: Unit -> Constr Source #

dataTypeOf :: Unit -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Unit) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Unit) Source #

gmapT :: (forall b. Data b => b -> b) -> Unit -> Unit Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Unit -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Unit -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Unit -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Unit -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Unit -> m Unit Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Unit -> m Unit Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Unit -> m Unit Source #

Show Unit Source # 
Instance details

Defined in GHC.Unit.Types

NFData Unit Source # 
Instance details

Defined in GHC.Unit.Types

Methods

rnf :: Unit -> () Source #

Uniquable Module Source # 
Instance details

Defined in GHC.Unit.Types

Uniquable UnitId Source # 
Instance details

Defined in GHC.Unit.Types

IsUnitId UnitId Source # 
Instance details

Defined in GHC.Unit.Types

Binary InstantiatedUnit Source # 
Instance details

Defined in GHC.Unit.Types

Binary Unit Source # 
Instance details

Defined in GHC.Unit.Types

Binary UnitId Source # 
Instance details

Defined in GHC.Unit.Types

Outputable InstalledModule Source # 
Instance details

Defined in GHC.Unit.Types

Outputable InstantiatedModule Source # 
Instance details

Defined in GHC.Unit.Types

Outputable InstantiatedUnit Source # 
Instance details

Defined in GHC.Unit.Types

Outputable Module Source # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Module -> SDoc Source #

Outputable Unit Source # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Unit -> SDoc Source #

Outputable UnitId Source # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: UnitId -> SDoc Source #

Eq UnitId Source # 
Instance details

Defined in GHC.Unit.Types

Methods

(==) :: UnitId -> UnitId -> Bool #

(/=) :: UnitId -> UnitId -> Bool #

Ord Unit Source # 
Instance details

Defined in GHC.Unit.Types

Methods

compare :: Unit -> Unit -> Ordering #

(<) :: Unit -> Unit -> Bool #

(<=) :: Unit -> Unit -> Bool #

(>) :: Unit -> Unit -> Bool #

(>=) :: Unit -> Unit -> Bool #

max :: Unit -> Unit -> Unit #

min :: Unit -> Unit -> Unit #

Ord UnitId Source # 
Instance details

Defined in GHC.Unit.Types

newtype UnitKey Source #

A unit key in the database

Constructors

UnitKey FastString 

Instances

Instances details
IsUnitId UnitKey Source # 
Instance details

Defined in GHC.Unit.Types

data GenInstantiatedUnit unit Source #

An instantiated unit.

It identifies an indefinite library (with holes) that has been instantiated.

This unit may be indefinite or not (i.e. with remaining holes or not). If it is definite, we don't know if it has already been compiled and installed in a database. Nevertheless, we have a mechanism called "improvement" to try to match a fully instantiated unit with existing compiled and installed units: see Note [VirtUnit to RealUnit improvement].

An indefinite unit identifier pretty-prints to something like p[H=H,A=aimpl:A>] (p is the IndefUnitId, and the brackets enclose the module substitution).

Constructors

InstantiatedUnit 

Fields

type IndefUnitId = Indefinite UnitId Source #

An IndefUnitId is an UnitId with the invariant that it only refers to an indefinite library; i.e., one that can be instantiated.

type DefUnitId = Definite UnitId Source #

A DefUnitId is an UnitId with the invariant that it only refers to a definite library; i.e., one we have generated code for.

mkInstantiatedUnit :: IsUnitId u => Indefinite u -> GenInstantiations u -> GenInstantiatedUnit u Source #

Create a new GenInstantiatedUnit given an explicit module substitution.

mkInstantiatedUnitHash :: IsUnitId u => Indefinite u -> [(ModuleName, GenModule (GenUnit u))] -> FastString Source #

Generate a uniquely identifying hash (internal unit-id) for an instantiated unit.

This is a one-way function. If the indefinite unit has not been instantiated at all, we return its unit-id.

This hash is completely internal to GHC and is not used for symbol names or file paths. It is different from the hash Cabal would produce for the same instantiated unit.

mkVirtUnit :: IsUnitId u => Indefinite u -> [(ModuleName, GenModule (GenUnit u))] -> GenUnit u Source #

Smart constructor for instantiated GenUnit

mapGenUnit :: IsUnitId v => (u -> v) -> GenUnit u -> GenUnit v Source #

Map over the unit type of a GenUnit

mapInstantiations :: IsUnitId v => (u -> v) -> GenInstantiations u -> GenInstantiations v Source #

Map over the unit identifier of unit instantiations.

unitFreeModuleHoles :: GenUnit u -> UniqDSet ModuleName Source #

Retrieve the set of free module holes of a Unit.

fsToUnit :: FastString -> Unit Source #

Create a new simple unit identifier from a FastString. Internally, this is primarily used to specify wired-in unit identifiers.

toUnitId :: Unit -> UnitId Source #

Return the UnitId of the Unit. For on-the-fly instantiated units, return the UnitId of the indefinite unit this unit is an instance of.

virtualUnitId :: InstantiatedUnit -> UnitId Source #

Return the virtual UnitId of an on-the-fly instantiated unit.

stableUnitCmp :: Unit -> Unit -> Ordering Source #

Compares unit ids lexically, rather than by their Uniques

unitIsDefinite :: Unit -> Bool Source #

A Unit is definite if it has no free holes.

Unit Ids

Utils

newtype Definite unit Source #

A definite unit (i.e. without any free module hole)

Constructors

Definite 

Fields

Instances

Instances details
Functor Definite Source # 
Instance details

Defined in GHC.Unit.Types

Methods

fmap :: (a -> b) -> Definite a -> Definite b Source #

(<$) :: a -> Definite b -> Definite a Source #

Uniquable unit => Uniquable (Definite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Definite unit -> Unique Source #

IsUnitId unit => IsUnitId (Definite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

unitFS :: Definite unit -> FastString Source #

Binary unit => Binary (Definite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

put_ :: BinHandle -> Definite unit -> IO () Source #

put :: BinHandle -> Definite unit -> IO (Bin (Definite unit)) Source #

get :: BinHandle -> IO (Definite unit) Source #

Outputable unit => Outputable (Definite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Definite unit -> SDoc Source #

Eq unit => Eq (Definite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

(==) :: Definite unit -> Definite unit -> Bool #

(/=) :: Definite unit -> Definite unit -> Bool #

Ord unit => Ord (Definite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

compare :: Definite unit -> Definite unit -> Ordering #

(<) :: Definite unit -> Definite unit -> Bool #

(<=) :: Definite unit -> Definite unit -> Bool #

(>) :: Definite unit -> Definite unit -> Bool #

(>=) :: Definite unit -> Definite unit -> Bool #

max :: Definite unit -> Definite unit -> Definite unit #

min :: Definite unit -> Definite unit -> Definite unit #

newtype Indefinite unit Source #

Constructors

Indefinite 

Fields

Instances

Instances details
Functor Indefinite Source # 
Instance details

Defined in GHC.Unit.Types

Methods

fmap :: (a -> b) -> Indefinite a -> Indefinite b Source #

(<$) :: a -> Indefinite b -> Indefinite a Source #

Uniquable unit => Uniquable (Indefinite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Indefinite unit -> Unique Source #

IsUnitId unit => IsUnitId (Indefinite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

unitFS :: Indefinite unit -> FastString Source #

Binary unit => Binary (Indefinite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

put_ :: BinHandle -> Indefinite unit -> IO () Source #

put :: BinHandle -> Indefinite unit -> IO (Bin (Indefinite unit)) Source #

get :: BinHandle -> IO (Indefinite unit) Source #

Outputable unit => Outputable (Indefinite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Indefinite unit -> SDoc Source #

Eq unit => Eq (Indefinite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

(==) :: Indefinite unit -> Indefinite unit -> Bool #

(/=) :: Indefinite unit -> Indefinite unit -> Bool #

Ord unit => Ord (Indefinite unit) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

compare :: Indefinite unit -> Indefinite unit -> Ordering #

(<) :: Indefinite unit -> Indefinite unit -> Bool #

(<=) :: Indefinite unit -> Indefinite unit -> Bool #

(>) :: Indefinite unit -> Indefinite unit -> Bool #

(>=) :: Indefinite unit -> Indefinite unit -> Bool #

max :: Indefinite unit -> Indefinite unit -> Indefinite unit #

min :: Indefinite unit -> Indefinite unit -> Indefinite unit #

Wired-in units

mainUnitId :: UnitId Source #

This is the package Id for the current program. It is the default package Id if you don't specify a package name. We don't add this prefix to symbol names, since there can be only one main package per program.

Boot modules

data IsBootInterface Source #

Indicates whether a module name is referring to a boot interface (hs-boot file) or regular module (hs file). We need to treat boot modules specially when building compilation graphs, since they break cycles. Regular source files and signature files are treated equivalently.

Constructors

NotBoot 
IsBoot 

Instances

Instances details
Data IsBootInterface Source # 
Instance details

Defined in GHC.Unit.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IsBootInterface -> c IsBootInterface Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IsBootInterface Source #

toConstr :: IsBootInterface -> Constr Source #

dataTypeOf :: IsBootInterface -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IsBootInterface) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IsBootInterface) Source #

gmapT :: (forall b. Data b => b -> b) -> IsBootInterface -> IsBootInterface Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IsBootInterface -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IsBootInterface -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IsBootInterface -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IsBootInterface -> m IsBootInterface Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IsBootInterface -> m IsBootInterface Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IsBootInterface -> m IsBootInterface Source #

Show IsBootInterface Source # 
Instance details

Defined in GHC.Unit.Types

Binary IsBootInterface Source # 
Instance details

Defined in GHC.Unit.Types

Eq IsBootInterface Source # 
Instance details

Defined in GHC.Unit.Types

Ord IsBootInterface Source # 
Instance details

Defined in GHC.Unit.Types

data GenWithIsBoot mod Source #

This data type just pairs a value mod with an IsBootInterface flag. In practice, mod is usually a Module or ModuleName'.

Constructors

GWIB 

Instances

Instances details
Foldable GenWithIsBoot Source # 
Instance details

Defined in GHC.Unit.Types

Methods

fold :: Monoid m => GenWithIsBoot m -> m Source #

foldMap :: Monoid m => (a -> m) -> GenWithIsBoot a -> m Source #

foldMap' :: Monoid m => (a -> m) -> GenWithIsBoot a -> m Source #

foldr :: (a -> b -> b) -> b -> GenWithIsBoot a -> b Source #

foldr' :: (a -> b -> b) -> b -> GenWithIsBoot a -> b Source #

foldl :: (b -> a -> b) -> b -> GenWithIsBoot a -> b Source #

foldl' :: (b -> a -> b) -> b -> GenWithIsBoot a -> b Source #

foldr1 :: (a -> a -> a) -> GenWithIsBoot a -> a Source #

foldl1 :: (a -> a -> a) -> GenWithIsBoot a -> a Source #

toList :: GenWithIsBoot a -> [a] Source #

null :: GenWithIsBoot a -> Bool Source #

length :: GenWithIsBoot a -> Int Source #

elem :: Eq a => a -> GenWithIsBoot a -> Bool Source #

maximum :: Ord a => GenWithIsBoot a -> a Source #

minimum :: Ord a => GenWithIsBoot a -> a Source #

sum :: Num a => GenWithIsBoot a -> a Source #

product :: Num a => GenWithIsBoot a -> a Source #

Traversable GenWithIsBoot Source # 
Instance details

Defined in GHC.Unit.Types

Methods

traverse :: Applicative f => (a -> f b) -> GenWithIsBoot a -> f (GenWithIsBoot b) Source #

sequenceA :: Applicative f => GenWithIsBoot (f a) -> f (GenWithIsBoot a) Source #

mapM :: Monad m => (a -> m b) -> GenWithIsBoot a -> m (GenWithIsBoot b) Source #

sequence :: Monad m => GenWithIsBoot (m a) -> m (GenWithIsBoot a) Source #

Functor GenWithIsBoot Source # 
Instance details

Defined in GHC.Unit.Types

Methods

fmap :: (a -> b) -> GenWithIsBoot a -> GenWithIsBoot b Source #

(<$) :: a -> GenWithIsBoot b -> GenWithIsBoot a Source #

Show mod => Show (GenWithIsBoot mod) Source # 
Instance details

Defined in GHC.Unit.Types

Binary a => Binary (GenWithIsBoot a) Source # 
Instance details

Defined in GHC.Unit.Types

Outputable a => Outputable (GenWithIsBoot a) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: GenWithIsBoot a -> SDoc Source #

Eq mod => Eq (GenWithIsBoot mod) Source # 
Instance details

Defined in GHC.Unit.Types

Methods

(==) :: GenWithIsBoot mod -> GenWithIsBoot mod -> Bool #

(/=) :: GenWithIsBoot mod -> GenWithIsBoot mod -> Bool #

Ord mod => Ord (GenWithIsBoot mod) Source # 
Instance details

Defined in GHC.Unit.Types