Cabal-2.4.1.0: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Backpack

Contents

Description

This module defines the core data types for Backpack. For more details, see:

https://github.com/ezyang/ghc-proposals/blob/backpack/proposals/0000-backpack.rst

Synopsis

OpenUnitId

data OpenUnitId Source #

An OpenUnitId describes a (possibly partially) instantiated Backpack component, with a description of how the holes are filled in. Unlike OpenUnitId, the ModuleSubst is kept in a structured form that allows for substitution (which fills in holes.) This form of unit cannot be installed. It must first be converted to a UnitId.

In the absence of Backpack, there are no holes to fill, so any such component always has an empty module substitution; thus we can lossly represent it as an 'OpenUnitId uid'.

For a source component using Backpack, however, there is more structure as components may be parametrized over some signatures, and these "holes" may be partially or wholly filled.

OpenUnitId plays an important role when we are mix-in linking, and is recorded to the installed packaged database for indefinite packages; however, for compiled packages that are fully instantiated, we instantiate OpenUnitId into UnitId.

For more details see the Backpack spec https://github.com/ezyang/ghc-proposals/blob/backpack/proposals/0000-backpack.rst

Constructors

IndefFullUnitId ComponentId OpenModuleSubst

Identifies a component which may have some unfilled holes; specifying its ComponentId and its OpenModuleSubst. TODO: Invariant that OpenModuleSubst is non-empty? See also the Text instance.

DefiniteUnitId DefUnitId

Identifies a fully instantiated component, which has been compiled and abbreviated as a hash. The embedded UnitId MUST NOT be for an indefinite component; an OpenUnitId is guaranteed not to have any holes.

Instances
Eq OpenUnitId Source # 
Instance details

Defined in Distribution.Backpack

Data OpenUnitId Source # 
Instance details

Defined in Distribution.Backpack

Methods

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

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

toConstr :: OpenUnitId -> Constr #

dataTypeOf :: OpenUnitId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OpenUnitId Source # 
Instance details

Defined in Distribution.Backpack

Read OpenUnitId Source # 
Instance details

Defined in Distribution.Backpack

Show OpenUnitId Source # 
Instance details

Defined in Distribution.Backpack

Generic OpenUnitId Source # 
Instance details

Defined in Distribution.Backpack

Associated Types

type Rep OpenUnitId :: Type -> Type #

Binary OpenUnitId Source # 
Instance details

Defined in Distribution.Backpack

NFData OpenUnitId Source # 
Instance details

Defined in Distribution.Backpack

Methods

rnf :: OpenUnitId -> () #

Pretty OpenUnitId Source # 
Instance details

Defined in Distribution.Backpack

Parsec OpenUnitId Source #
>>> eitherParsec "foobar" :: Either String OpenUnitId
Right (DefiniteUnitId (DefUnitId {unDefUnitId = UnitId "foobar"}))
>>> eitherParsec "foo[Str=text-1.2.3:Data.Text.Text]" :: Either String OpenUnitId
Right (IndefFullUnitId (ComponentId "foo") (fromList [(ModuleName ["Str"],OpenModule (DefiniteUnitId (DefUnitId {unDefUnitId = UnitId "text-1.2.3"})) (ModuleName ["Data","Text","Text"]))]))
Instance details

Defined in Distribution.Backpack

Text OpenUnitId Source # 
Instance details

Defined in Distribution.Backpack

ModSubst OpenUnitId Source # 
Instance details

Defined in Distribution.Backpack.ModSubst

type Rep OpenUnitId Source # 
Instance details

Defined in Distribution.Backpack

openUnitIdFreeHoles :: OpenUnitId -> Set ModuleName Source #

Get the set of holes (ModuleVar) embedded in a UnitId.

mkOpenUnitId :: UnitId -> ComponentId -> OpenModuleSubst -> OpenUnitId Source #

Safe constructor from a UnitId. The only way to do this safely is if the instantiation is provided.

DefUnitId

data DefUnitId Source #

A UnitId for a definite package. The DefUnitId invariant says that a UnitId identified this way is definite; i.e., it has no unfilled holes.

Instances
Eq DefUnitId Source # 
Instance details

Defined in Distribution.Types.UnitId

Data DefUnitId Source # 
Instance details

Defined in Distribution.Types.UnitId

Methods

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

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

toConstr :: DefUnitId -> Constr #

dataTypeOf :: DefUnitId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DefUnitId Source # 
Instance details

Defined in Distribution.Types.UnitId

Read DefUnitId Source # 
Instance details

Defined in Distribution.Types.UnitId

Show DefUnitId Source # 
Instance details

Defined in Distribution.Types.UnitId

Generic DefUnitId Source # 
Instance details

Defined in Distribution.Types.UnitId

Associated Types

type Rep DefUnitId :: Type -> Type #

Binary DefUnitId Source # 
Instance details

Defined in Distribution.Types.UnitId

NFData DefUnitId Source # 
Instance details

Defined in Distribution.Types.UnitId

Methods

rnf :: DefUnitId -> () #

Pretty DefUnitId Source # 
Instance details

Defined in Distribution.Types.UnitId

Methods

pretty :: DefUnitId -> Doc Source #

Parsec DefUnitId Source # 
Instance details

Defined in Distribution.Types.UnitId

Text DefUnitId Source # 
Instance details

Defined in Distribution.Types.UnitId

type Rep DefUnitId Source # 
Instance details

Defined in Distribution.Types.UnitId

type Rep DefUnitId = D1 (MetaData "DefUnitId" "Distribution.Types.UnitId" "Cabal-2.4.1.0-B0ZPupqxKZe72LoceK3cGA" True) (C1 (MetaCons "DefUnitId" PrefixI True) (S1 (MetaSel (Just "unDefUnitId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UnitId)))

mkDefUnitId :: ComponentId -> Map ModuleName Module -> DefUnitId Source #

Create a DefUnitId from a ComponentId and an instantiation with no holes.

OpenModule

data OpenModule Source #

Unlike a Module, an OpenModule is either an ordinary module from some unit, OR an OpenModuleVar, representing a hole that needs to be filled in. Substitutions are over module variables.

Instances
Eq OpenModule Source # 
Instance details

Defined in Distribution.Backpack

Data OpenModule Source # 
Instance details

Defined in Distribution.Backpack

Methods

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

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

toConstr :: OpenModule -> Constr #

dataTypeOf :: OpenModule -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OpenModule Source # 
Instance details

Defined in Distribution.Backpack

Read OpenModule Source # 
Instance details

Defined in Distribution.Backpack

Show OpenModule Source # 
Instance details

Defined in Distribution.Backpack

Generic OpenModule Source # 
Instance details

Defined in Distribution.Backpack

Associated Types

type Rep OpenModule :: Type -> Type #

Binary OpenModule Source # 
Instance details

Defined in Distribution.Backpack

NFData OpenModule Source # 
Instance details

Defined in Distribution.Backpack

Methods

rnf :: OpenModule -> () #

Pretty OpenModule Source # 
Instance details

Defined in Distribution.Backpack

Parsec OpenModule Source #
>>> eitherParsec "Includes2-0.1.0.0-inplace-mysql:Database.MySQL" :: Either String OpenModule
Right (OpenModule (DefiniteUnitId (DefUnitId {unDefUnitId = UnitId "Includes2-0.1.0.0-inplace-mysql"})) (ModuleName ["Database","MySQL"]))
Instance details

Defined in Distribution.Backpack

Text OpenModule Source # 
Instance details

Defined in Distribution.Backpack

ModSubst OpenModule Source # 
Instance details

Defined in Distribution.Backpack.ModSubst

type Rep OpenModule Source # 
Instance details

Defined in Distribution.Backpack

openModuleFreeHoles :: OpenModule -> Set ModuleName Source #

Get the set of holes (ModuleVar) embedded in a Module.

OpenModuleSubst

type OpenModuleSubst = Map ModuleName OpenModule Source #

An explicit substitution on modules.

NB: These substitutions are NOT idempotent, for example, a valid substitution is (A -> B, B -> A).

dispOpenModuleSubst :: OpenModuleSubst -> Doc Source #

Pretty-print the entries of a module substitution, suitable for embedding into a OpenUnitId or passing to GHC via --instantiate-with.

dispOpenModuleSubstEntry :: (ModuleName, OpenModule) -> Doc Source #

Pretty-print a single entry of a module substitution.

parseOpenModuleSubst :: ReadP r OpenModuleSubst Source #

Inverse to dispModSubst.

parseOpenModuleSubstEntry :: ReadP r (ModuleName, OpenModule) Source #

Inverse to dispModSubstEntry.

parsecOpenModuleSubst :: CabalParsing m => m OpenModuleSubst Source #

Inverse to dispModSubst.

Since: 2.2

parsecOpenModuleSubstEntry :: CabalParsing m => m (ModuleName, OpenModule) Source #

Inverse to dispModSubstEntry.

Since: 2.2

openModuleSubstFreeHoles :: OpenModuleSubst -> Set ModuleName Source #

Get the set of holes (ModuleVar) embedded in a OpenModuleSubst. This is NOT the domain of the substitution.

Conversions to UnitId

abstractUnitId :: OpenUnitId -> UnitId Source #

When typechecking, we don't demand that a freshly instantiated IndefFullUnitId be compiled; instead, we just depend on the installed indefinite unit installed at the ComponentId.

hashModuleSubst :: Map ModuleName Module -> Maybe String Source #

Take a module substitution and hash it into a string suitable for UnitId. Note that since this takes Module, not OpenModule, you are responsible for recursively converting OpenModule into Module. See also Distribution.Backpack.ReadyComponent.