cabal-debian-5.0.3: Create a Debianization for a Cabal package

Safe HaskellNone
LanguageHaskell2010

Debian.Debianize.BasicInfo

Contents

Description

The basic information required to load a Cabal or Debian package description.

Synopsis

Types

data Flags Source #

This record supplies enough information to locate and load a debianization or a cabal file from the IO monad.

Constructors

Flags 

Fields

  • _verbosity :: Int

    Run with progress messages at the given level of verboseness.

  • _dryRun :: Bool

    Don't write any files or create any directories, just explain what would have been done.

  • _upgrade :: Bool

    Carefully upgrade the packaging

  • _roundtrip :: Bool

    Normalize a debianization (field order, whitespace) by round-tripping it.

  • _validate :: Bool

    Fail if the debianization already present doesn't match the one we are going to generate closely enough that it is safe to debianize during the run of dpkg-buildpackage, when Setup configure is run. Specifically, the version number in the top changelog entry must match, and the sets of package names in the control file must match.

  • _compilerFlavor :: CompilerFlavor

    Which compiler should we generate library packages for? In theory a single deb could handle multiple compiler flavors, but the support tools are not ready for this as of right now (28 Jan 2015.)

  • _cabalFlagAssignments :: Set (FlagName, Bool)

    Flags to pass to Cabal function finalizePackageDescription, this can be used to control the flags in the cabal file. It can be supplied to the cabal-debian binary using the --flags option.

  • _buildEnv :: EnvSet

    Directory containing the build environment for which the debianization will be generated. This determines which compiler will be available, which in turn determines which basic libraries can be provided by the compiler. By default all the paths in EnvSet are "/".

Instances
Eq Flags Source # 
Instance details

Defined in Debian.Debianize.BasicInfo

Methods

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

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

Data Flags Source # 
Instance details

Defined in Debian.Debianize.BasicInfo

Methods

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

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

toConstr :: Flags -> Constr #

dataTypeOf :: Flags -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Flags Source # 
Instance details

Defined in Debian.Debianize.BasicInfo

Methods

compare :: Flags -> Flags -> Ordering #

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

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

(>) :: Flags -> Flags -> Bool #

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

max :: Flags -> Flags -> Flags #

min :: Flags -> Flags -> Flags #

Show Flags Source # 
Instance details

Defined in Debian.Debianize.BasicInfo

Methods

showsPrec :: Int -> Flags -> ShowS #

show :: Flags -> String #

showList :: [Flags] -> ShowS #

data EnvSet Source #

Constructors

EnvSet 

Fields

Instances
Eq EnvSet Source # 
Instance details

Defined in Debian.Debianize.BasicInfo

Methods

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

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

Data EnvSet Source # 
Instance details

Defined in Debian.Debianize.BasicInfo

Methods

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

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

toConstr :: EnvSet -> Constr #

dataTypeOf :: EnvSet -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EnvSet Source # 
Instance details

Defined in Debian.Debianize.BasicInfo

Show EnvSet Source # 
Instance details

Defined in Debian.Debianize.BasicInfo

data DebType Source #

A redundant data type, too lazy to expunge.

Constructors

Dev 
Prof 
Doc 
Instances
Eq DebType Source # 
Instance details

Defined in Debian.Debianize.BasicInfo

Methods

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

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

Data DebType Source # 
Instance details

Defined in Debian.Debianize.BasicInfo

Methods

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

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

toConstr :: DebType -> Constr #

dataTypeOf :: DebType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DebType Source # 
Instance details

Defined in Debian.Debianize.BasicInfo

Read DebType Source # 
Instance details

Defined in Debian.Debianize.BasicInfo

Show DebType Source # 
Instance details

Defined in Debian.Debianize.BasicInfo

Lenses

State Monad

flagOptions :: MonadIO m => [OptDescr (StateT Flags m ())] Source #

Command line options which build a function that modifies a state monad value of type Flags