Cabal-2.0.1.0: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Types.ModuleRenaming

Synopsis

Documentation

data ModuleRenaming Source #

Renaming applied to the modules provided by a package. The boolean indicates whether or not to also include all of the original names of modules. Thus, ModuleRenaming False [] is "don't expose any modules, and ModuleRenaming True [(Data.Bool, Bool)] is, "expose all modules, but also expose Data.Bool as Bool". If a renaming is omitted you get the DefaultRenaming.

(NB: This is a list not a map so that we can preserve order.)

Constructors

ModuleRenaming [(ModuleName, ModuleName)]

A module renaming/thinning; e.g., (A as B, C as C) brings B and C into scope.

DefaultRenaming

The default renaming, bringing all exported modules into scope.

HidingRenaming [ModuleName]

Hiding renaming, e.g., hiding (A, B), bringing all exported modules into scope except the hidden ones.

Instances

Eq ModuleRenaming # 
Data ModuleRenaming # 

Methods

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

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

toConstr :: ModuleRenaming -> Constr Source #

dataTypeOf :: ModuleRenaming -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord ModuleRenaming # 
Read ModuleRenaming # 
Show ModuleRenaming # 
Generic ModuleRenaming # 
Binary ModuleRenaming # 
Text ModuleRenaming # 
type Rep ModuleRenaming # 
type Rep ModuleRenaming = D1 * (MetaData "ModuleRenaming" "Distribution.Types.ModuleRenaming" "Cabal-2.0.1.0" False) ((:+:) * (C1 * (MetaCons "ModuleRenaming" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(ModuleName, ModuleName)]))) ((:+:) * (C1 * (MetaCons "DefaultRenaming" PrefixI False) (U1 *)) (C1 * (MetaCons "HidingRenaming" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ModuleName])))))

defaultRenaming :: ModuleRenaming Source #

The default renaming, if something is specified in build-depends only.

isDefaultRenaming :: ModuleRenaming -> Bool Source #

Tests if its the default renaming; we can use a more compact syntax in IncludeRenaming in this case.