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

Safe HaskellNone
LanguageHaskell2010

Debian.Debianize

Contents

Description

QUICK START:

You can either run cabal-debian, or for more power and flexibility you can put a Debianize.hs script in the package's debian subdirectory.

To see what your debianization would produce, or how it differs from the debianization already present:

% cabal-debian -n

This is equivalent to the library call

% ghc -e 'System.Environment.withArgs ["-n"] $ Debian.Debianize.performDebianization Debian.Debianize.debianDefaults'

To actually create the debianization and then build the debs,

% ghc -e 'Debian.Debianize.performDebianization Debian.Debianize.debianDefaults'
% sudo dpkg-buildpackage

At this point you may need a script to achieve specific packaging goals. Put this this in debian/Debianize.hs:

import Control.Lens
import Data.Map as Map
import Data.Set as Set
import Debian.Relation (BinPkgName(BinPkgName), Relation(Rel))
import Debian.Debianize
main = performDebianization $ do
  debianDefaults
  (debInfo . binaryDebDescription (BinPkgName "cabal-debian") . relations . depends) %= (++ (rels "apt-file, debian-policy, debhelper, haskell-devscripts (>= 0.8.19)"))

Then to test it,

% runhaskell debian/Debianize.hs -n

and to run it for real:

% runhaskell debian/Debianize.hs
DESIGN OVERVIEW

The three phases of the operation of the system are Input -> Finalization -> Output.

Input
Module Debian.Debianize.Input - gather inputs using IO operations and customization functions, from the .cabal file, an existing debianization, and so on. This information results in a value of type Atoms. Modules Types, Lenses, Inputs.
Customize
Make modifications to the input values
Finalization
Module Debian.Debianize.Finalize - Fill in any information missing from Atoms that is required to build the debianization based on the inputs and our policy decisions.
Debianize
Module Debian.Debianize.Files - Compute the paths and files of the debianization from the Atoms value.
Output
Module Debian.Debianize.Output - Perform a variety of output operations on the debianzation - writing or updating the files in a debian directory, comparing two debianizations, validate a debianization (ensure two debianizations match in source and binary package names), or describe a debianization.

There is also a high level function to run a script that runs this entire pipeline when it finds from a script found in a debian/Debianize.hs file.

Synopsis

Collect information about desired debianization

State monads to carry the collected information, command line options

evalCabalT :: Monad m => CabalT m a -> CabalInfo -> m a Source #

evalDebianT :: Monad m => DebianT m a -> DebInfo -> m a Source #

Functions for maping Cabal name and version number to Debian name

mapCabal :: Monad m => PackageName -> DebBase -> CabalT m () Source #

Map all versions of Cabal package pname to Debian package dname. Not really a debian package name, but the name of a cabal package that maps to the debian package name we want. (Should this be a SrcPkgName?)

splitCabal :: Monad m => PackageName -> DebBase -> Version -> CabalT m () Source #

Map versions less than ver of Cabal Package pname to Debian package ltname

remapCabal :: Monad m => PackageName -> DebBase -> CabalT m () Source #

Replace any existing mapping of the cabal name pname with the debian name dname. (Use case: to change the debian package name so it differs from the package provided by ghc.)

Specific details about the particular packages and versions in the Debian repo

debianDefaults :: Monad m => CabalT m () Source #

Update the CabalInfo value in the CabalT state with some details about the debian repository - special cases for how some cabal packages are mapped to debian package names.

Functions to configure some useful packaging idioms - web server packages,

IO functions for reading debian or cabal packaging info

inputDebianizationFile :: MonadIO m => FilePath -> DebianT m () Source #

Try to input a file and if successful add it to the debianization's list of "intermediate" files, files which will simply be added to the final debianization without any understanding of their contents or purpose.

inputChangeLog :: MonadIO m => DebianT m () Source #

Look in several places for a debian changelog

inputCabalization :: forall m. MonadIO m => Flags -> m (Either String PackageDescription) Source #

Load a PackageDescription using the information in the Flags record - in particular, using the dependency environment in the EnvSet, find the newest available compiler of the requested compiler flavor and use that information load the configured PackageDescription.

Finish computing the debianization and output the result

runDebianizeScript :: [String] -> IO Bool Source #

Run the script in debian/Debianize.hs with the given command line arguments. Returns True if the script exists and succeeds. In this case it may be assumed that a debianization was created (or updated) in the debian subdirectory of the current directory. In this way we can include a script in a package to produce a customized debianization more sophisticated than the one that would be produced by the cabal-debian executable. An example is included in the debian subdirectory of this library.

performDebianization :: CabalT IO () -> IO () Source #

Perform whole debianization. You provide your customization, this function does everything else.

finishDebianization :: forall m. (MonadIO m, MonadFail m) => StateT CabalInfo m () Source #

Depending on the options in atoms, either validate, describe, or write the generated debianization.

writeDebianization :: (MonadIO m, MonadFail m) => DebianT m () Source #

Write the files of the debianization d to ./debian

describeDebianization :: (MonadIO m, MonadFail m) => DebianT m String Source #

Return a string describing the debianization - a list of file names and their contents in a somewhat human readable format.

compareDebianization :: DebInfo -> DebInfo -> [String] Source #

Compare the old and new debianizations, returning a string describing the differences.

validateDebianization :: DebInfo -> DebInfo -> () Source #

Make sure the new debianization matches the existing debianization in several ways - specifically, version number, and the names of the source and binary packages. Some debian packages come with a skeleton debianization that needs to be filled in, this can be used to make sure the debianization we produce is usable.

Utility functions

buildDebVersionMap :: IO DebMap Source #

Query versions of installed packages

dpkgFileMap :: IO (Map FilePath (Set BinPkgName)) Source #

Create a map from pathname to the names of the packages that contains that pathname using the contents of the debian package info directory varlibdpkginfo.

debOfFile :: FilePath -> ReaderT (Map FilePath (Set BinPkgName)) IO (Maybe BinPkgName) Source #

Given a path, return the name of the package that owns it.

withCurrentDirectory :: FilePath -> IO a -> IO a Source #

From Darcs.Utils - set the working directory and run an IO operation.

(.?=) :: Monad m => Lens' a (Maybe b) -> Maybe b -> StateT a m () Source #

Set b if it currently isNothing and the argument isJust, that is 1. Nothing happens if the argument isNothing 2. Nothing happens if the current value isJust

newtype DebBase Source #

The base of a debian binary package name, the string that appears between "libghc-" and "-dev".

Constructors

DebBase String 
Instances
Eq DebBase Source # 
Instance details

Defined in Debian.Debianize.VersionSplits

Methods

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

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

Data DebBase Source # 
Instance details

Defined in Debian.Debianize.VersionSplits

Methods

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

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

toConstr :: DebBase -> Constr #

dataTypeOf :: DebBase -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DebBase Source # 
Instance details

Defined in Debian.Debianize.VersionSplits

Read DebBase Source # 
Instance details

Defined in Debian.Debianize.VersionSplits

Show DebBase Source # 
Instance details

Defined in Debian.Debianize.VersionSplits

Interspersed VersionSplits DebBase Version Source # 
Instance details

Defined in Debian.Debianize.VersionSplits

Methods

leftmost :: VersionSplits -> DebBase Source #

pairs :: VersionSplits -> [(Version, DebBase)] Source #

foldTriples :: (DebBase -> Version -> DebBase -> r -> r) -> r -> VersionSplits -> r Source #

foldInverted :: (Maybe Version -> DebBase -> Maybe Version -> r -> r) -> r -> VersionSplits -> r Source #

foldArounds :: (DebBase -> DebBase -> r -> r) -> r -> VersionSplits -> r Source #

foldBetweens :: (Version -> r -> r) -> r -> VersionSplits -> r Source #

data License Source #

Constructors

Public_Domain

No license required for any purpose; the work is not subject to copyright in any jurisdiction.

Apache

Apache license 1.0, 2.0.

Artistic

Artistic license 1.0, 2.0.

BSD_2_Clause

Berkeley software distribution license, 2-clause version.

BSD_3_Clause

Berkeley software distribution license, 3-clause version.

BSD_4_Clause

Berkeley software distribution license, 4-clause version.

ISC

Internet Software Consortium, sometimes also known as the OpenBSD License.

CC_BY

Creative Commons Attribution license 1.0, 2.0, 2.5, 3.0.

CC_BY_SA

Creative Commons Attribution Share Alike license 1.0, 2.0, 2.5, 3.0.

CC_BY_ND

Creative Commons Attribution No Derivatives license 1.0, 2.0, 2.5, 3.0.

CC_BY_NC

Creative Commons Attribution Non-Commercial license 1.0, 2.0, 2.5, 3.0.

CC_BY_NC_SA

Creative Commons Attribution Non-Commercial Share Alike license 1.0, 2.0, 2.5, 3.0.

CC_BY_NC_ND

Creative Commons Attribution Non-Commercial No Derivatives license 1.0, 2.0, 2.5, 3.0.

CC0

Creative Commons Zero 1.0 Universal. Omit Universal from the license version when forming the short name.

CDDL

Common Development and Distribution License 1.0.

CPL

IBM Common Public License.

EFL

The Eiffel Forum License 1.0, 2.0.

Expat

The Expat license.

GPL

GNU General Public License 1.0, 2.0, 3.0.

LGPL

GNU Lesser General Public License 2.1, 3.0, or GNU Library General Public License 2.0.

GFDL

GNU Free Documentation License 1.0, 1.1, 1.2, or 1.3. Use GFDL-NIV instead if there are no Front-Cover or Back-Cover Texts or Invariant Sections.

GFDL_NIV

GNU Free Documentation License, with no Front-Cover or Back-Cover Texts or Invariant Sections. Use the same version numbers as GFDL.

LPPL

LaTeX Project Public License 1.0, 1.1, 1.2, 1.3c.

MPL

Mozilla Public License 1.1.

Perl

erl license (use "GPL-1+ or Artistic-1" instead)

Python

Python license 2.0.

QPL

Q Public License 1.0.

W3C

W3C Software License For more information, consult the W3C Intellectual Rights FAQ.

Zlib

zlib/libpng license.

Zope

Zope Public License 1.0, 1.1, 2.0, 2.1.

OtherLicense String

Any other license name

Instances
Eq License Source # 
Instance details

Defined in Debian.Policy

Methods

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

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

Data License Source # 
Instance details

Defined in Debian.Policy

Methods

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

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

toConstr :: License -> Constr #

dataTypeOf :: License -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord License Source # 
Instance details

Defined in Debian.Policy

Read License Source # 
Instance details

Defined in Debian.Policy

Show License Source # 
Instance details

Defined in Debian.Policy

Pretty License Source # 
Instance details

Defined in Debian.Policy

Methods

pretty :: License -> Doc #

data Area Source #

Constructors

Main 
Contrib 
NonFree 
Instances
Eq Area Source # 
Instance details

Defined in Debian.Policy

Methods

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

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

Data Area Source # 
Instance details

Defined in Debian.Policy

Methods

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

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

toConstr :: Area -> Constr #

dataTypeOf :: Area -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Area Source # 
Instance details

Defined in Debian.Policy

Methods

compare :: Area -> Area -> Ordering #

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

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

(>) :: Area -> Area -> Bool #

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

max :: Area -> Area -> Area #

min :: Area -> Area -> Area #

Read Area Source # 
Instance details

Defined in Debian.Policy

Show Area Source # 
Instance details

Defined in Debian.Policy

Methods

showsPrec :: Int -> Area -> ShowS #

show :: Area -> String #

showList :: [Area] -> ShowS #

Pretty (PP Area) Source # 
Instance details

Defined in Debian.Policy

Methods

pretty :: PP Area -> Doc #

data MultiArch Source #

Constructors

MANo 
MASame 
MAForeign 
MAAllowed 
Instances
Eq MultiArch Source # 
Instance details

Defined in Debian.Policy

Data MultiArch Source # 
Instance details

Defined in Debian.Policy

Methods

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

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

toConstr :: MultiArch -> Constr #

dataTypeOf :: MultiArch -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MultiArch Source # 
Instance details

Defined in Debian.Policy

Read MultiArch Source # 
Instance details

Defined in Debian.Policy

Show MultiArch Source # 
Instance details

Defined in Debian.Policy

Pretty (PP MultiArch) Source # 
Instance details

Defined in Debian.Policy

Methods

pretty :: PP MultiArch -> Doc #

data Section Source #

Instances
Eq Section Source # 
Instance details

Defined in Debian.Policy

Methods

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

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

Data Section Source # 
Instance details

Defined in Debian.Policy

Methods

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

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

toConstr :: Section -> Constr #

dataTypeOf :: Section -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Section Source # 
Instance details

Defined in Debian.Policy

Read Section Source # 
Instance details

Defined in Debian.Policy

Show Section Source # 
Instance details

Defined in Debian.Policy

Pretty (PP Section) Source # 
Instance details

Defined in Debian.Policy

Methods

pretty :: PP Section -> Doc #

data PackageArchitectures Source #

The architectures for which a binary deb can be built.

Constructors

All

The package is architecture independenct

Any

The package can be built for any architecture

Names [String]

The list of suitable architectures

Instances
Eq PackageArchitectures Source # 
Instance details

Defined in Debian.Policy

Data PackageArchitectures Source # 
Instance details

Defined in Debian.Policy

Methods

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

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

toConstr :: PackageArchitectures -> Constr #

dataTypeOf :: PackageArchitectures -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PackageArchitectures Source # 
Instance details

Defined in Debian.Policy

Read PackageArchitectures Source # 
Instance details

Defined in Debian.Policy

Show PackageArchitectures Source # 
Instance details

Defined in Debian.Policy

Pretty (PP PackageArchitectures) Source # 
Instance details

Defined in Debian.Policy

data PackagePriority Source #

Instances
Eq PackagePriority Source # 
Instance details

Defined in Debian.Policy

Data PackagePriority Source # 
Instance details

Defined in Debian.Policy

Methods

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

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

toConstr :: PackagePriority -> Constr #

dataTypeOf :: PackagePriority -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PackagePriority Source # 
Instance details

Defined in Debian.Policy

Read PackagePriority Source # 
Instance details

Defined in Debian.Policy

Show PackagePriority Source # 
Instance details

Defined in Debian.Policy

Pretty (PP PackagePriority) Source # 
Instance details

Defined in Debian.Policy

data SourceFormat Source #

Constructors

Native3 
Quilt3 
Instances
Eq SourceFormat Source # 
Instance details

Defined in Debian.Policy

Data SourceFormat Source # 
Instance details

Defined in Debian.Policy

Methods

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

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

toConstr :: SourceFormat -> Constr #

dataTypeOf :: SourceFormat -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SourceFormat Source # 
Instance details

Defined in Debian.Policy

Show SourceFormat Source # 
Instance details

Defined in Debian.Policy

Pretty (PP SourceFormat) Source # 
Instance details

Defined in Debian.Policy

Methods

pretty :: PP SourceFormat -> Doc #

data StandardsVersion Source #

Instances
Eq StandardsVersion Source # 
Instance details

Defined in Debian.Policy

Data StandardsVersion Source # 
Instance details

Defined in Debian.Policy

Methods

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

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

toConstr :: StandardsVersion -> Constr #

dataTypeOf :: StandardsVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord StandardsVersion Source # 
Instance details

Defined in Debian.Policy

Show StandardsVersion Source # 
Instance details

Defined in Debian.Policy

Pretty (PP StandardsVersion) Source # 
Instance details

Defined in Debian.Policy

getDebhelperCompatLevel :: IO (Maybe Int) Source #

With the current state of CDBS, anything above 10 breaks, so for now we force this to 10.

getDebianStandardsVersion :: IO (Maybe StandardsVersion) Source #

Assumes debian-policy is installed

parseUploaders :: String -> Either String [NameAddr] Source #

Turn the uploaders field of a cabal package into a list of RFC2822 NameAddr values.

parseMaintainer :: String -> Either String NameAddr Source #

Parse a string containing a single NameAddr value.

fromCabalLicense :: License -> License Source #

Convert the Cabal license to a Debian license. I would welcome input on how to make this more correct.

toCabalLicense :: License -> License Source #

Convert a Debian license to a Cabal license. Additional cases and corrections welcome.

readLicense :: Text -> License Source #

I think we need an actual parser for license names.