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

Safe HaskellNone
LanguageHaskell2010

Debian.Policy

Contents

Description

Code pulled out of cabal-debian that straightforwardly implements parts of the Debian policy manual, or other bits of Linux standards.

Synopsis

Paths

Installed packages

getDebhelperCompatLevel :: IO (Maybe Int) Source #

The version number of the installed debhelper package is the highest acceptable value for compat in a debian/control file. If the package doesn't explicitly set an (acceptable) compat value we can use the value returned by this function, assuming debhelper is installed.

data StandardsVersion Source #

Instances

Eq StandardsVersion Source # 
Data StandardsVersion Source # 

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 # 
Show StandardsVersion Source # 
Pretty (PP StandardsVersion) Source # 

getDebianStandardsVersion :: IO (Maybe StandardsVersion) Source #

Assumes debian-policy is installed

Package fields

data SourceFormat Source #

Constructors

Native3 
Quilt3 

Instances

Eq SourceFormat Source # 
Data SourceFormat Source # 

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 # 
Show SourceFormat Source # 
Pretty (PP SourceFormat) Source # 

data PackagePriority Source #

Instances

Eq PackagePriority Source # 
Data PackagePriority Source # 

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 # 
Read PackagePriority Source # 
Show PackagePriority Source # 
Pretty (PP PackagePriority) Source # 

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 # 
Data PackageArchitectures Source # 

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 # 
Read PackageArchitectures Source # 
Show PackageArchitectures Source # 
Pretty (PP PackageArchitectures) Source # 

data Section Source #

Instances

Eq Section Source # 

Methods

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

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

Data Section Source # 

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 # 
Read Section Source # 
Show Section Source # 
Pretty (PP Section) Source # 

data MultiArch Source #

Constructors

MANo 
MASame 
MAForeign 
MAAllowed 

Instances

Eq MultiArch Source # 
Data MultiArch Source # 

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 # 
Read MultiArch Source # 
Show MultiArch Source # 
Pretty (PP MultiArch) Source # 

data Area Source #

Constructors

Main 
Contrib 
NonFree 

Instances

Eq Area Source # 

Methods

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

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

Data Area Source # 

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 # 

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 # 
Show Area Source # 

Methods

showsPrec :: Int -> Area -> ShowS #

show :: Area -> String #

showList :: [Area] -> ShowS #

Pretty (PP Area) Source # 

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.

maintainerOfLastResort :: NameAddr Source #

Maintainer is a mandatory field, so we need a value we can use when all else fails.

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 # 

Methods

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

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

Data License Source # 

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 # 
Read License Source # 
Show License Source # 
Pretty License Source # 

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.