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

Safe HaskellNone
LanguageHaskell2010

Debian.Debianize.CopyrightDescription

Contents

Description

Synopsis

Documentation

data CopyrightDescription Source #

Description of the machine readable debian/copyright file. A special case is used to represeent the old style free format file - if the value is equal to newCopyrightDescription except for the field _summaryComment, the text in _summaryComment is the copyright file.

Instances
Eq CopyrightDescription Source # 
Instance details

Defined in Debian.Debianize.CopyrightDescription

Data CopyrightDescription Source # 
Instance details

Defined in Debian.Debianize.CopyrightDescription

Methods

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

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

toConstr :: CopyrightDescription -> Constr #

dataTypeOf :: CopyrightDescription -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CopyrightDescription Source # 
Instance details

Defined in Debian.Debianize.CopyrightDescription

Show CopyrightDescription Source # 
Instance details

Defined in Debian.Debianize.CopyrightDescription

Pretty CopyrightDescription Source # 
Instance details

Defined in Debian.Debianize.CopyrightDescription

Default CopyrightDescription Source # 
Instance details

Defined in Debian.Debianize.CopyrightDescription

Pretty (PP (PackageDescription -> IO CopyrightDescription)) Source # 
Instance details

Defined in Debian.Debianize.Files

data FilesOrLicenseDescription Source #

Instances
Eq FilesOrLicenseDescription Source # 
Instance details

Defined in Debian.Debianize.CopyrightDescription

Data FilesOrLicenseDescription Source # 
Instance details

Defined in Debian.Debianize.CopyrightDescription

Methods

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

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

toConstr :: FilesOrLicenseDescription -> Constr #

dataTypeOf :: FilesOrLicenseDescription -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FilesOrLicenseDescription Source # 
Instance details

Defined in Debian.Debianize.CopyrightDescription

Show FilesOrLicenseDescription Source # 
Instance details

Defined in Debian.Debianize.CopyrightDescription

Lenses

Builders

readCopyrightDescription :: Text -> CopyrightDescription Source #

Read a CopyrightDescription from the text one might obtain from a debian/copyright file.

parseCopyrightDescription :: [Paragraph' Text] -> Maybe CopyrightDescription Source #

Try to parse a structured copyright file

defaultCopyrightDescription :: PackageDescription -> IO CopyrightDescription Source #

Infer a CopyrightDescription from a Cabal package description. This will try to read any copyright files listed in the cabal configuration. Inputs include the license field from the cabal file, the contents of the license files mentioned there, and the provided copyright0 value.