{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
module Debian.Debianize.CopyrightDescription
( CopyrightDescription(..)
, FilesOrLicenseDescription(..)
, format
, upstreamName
, upstreamContact
, upstreamSource
, disclaimer
, summaryComment
, summaryLicense
, summaryCopyright
, filesAndLicenses
, filesPattern
, filesCopyright
, filesLicense
, filesLicenseText
, filesComment
, license
, licenseText
, comment
, readCopyrightDescription
, parseCopyrightDescription
, defaultCopyrightDescription
) where
import Data.Char (isSpace)
import Data.Default (Default(def))
import Data.Either (lefts, rights)
import Data.Generics (Data, Typeable)
import Control.Lens.TH (makeLenses)
import Data.List as List (dropWhileEnd, partition)
import Data.Maybe.Extended (isJust, catMaybes, fromJust, fromMaybe, listToMaybe, nothingIf)
import Data.Monoid ((<>), mempty)
import Data.Text as Text (Text, pack, strip, unpack, null, lines, unlines, dropWhileEnd)
import Debian.Control (Field'(Field), fieldValue, Paragraph'(Paragraph), Control'(Control, unControl), parseControl)
import Debian.Debianize.Prelude (readFileMaybe)
import Debian.Orphans ()
import Debian.Policy (License(..), readLicense, fromCabalLicense)
import Debian.Pretty (prettyText, ppText)
import Debug.Trace
import qualified Distribution.License as Cabal (License(UnknownLicense))
import qualified Distribution.Package as Cabal
import qualified Distribution.PackageDescription as Cabal (PackageDescription(licenseFiles, copyright, licenseRaw, package, maintainer))
#if MIN_VERSION_Cabal(3,2,0)
import qualified Distribution.Utils.ShortText as ST
#endif
#if MIN_VERSION_Cabal(3,6,0)
import qualified Distribution.Utils.Path as DUP
#endif
import Network.URI (URI, parseURI)
import Prelude hiding (init, init, log, log, unlines, readFile)
import Text.PrettyPrint.HughesPJClass (text)
import Distribution.Pretty (Pretty(pretty))
unPackageName :: Cabal.PackageName -> String
unPackageName :: PackageName -> String
unPackageName PackageName
p = PackageName -> String
Cabal.unPackageName PackageName
p
data CopyrightDescription
= CopyrightDescription
{ CopyrightDescription -> URI
_format :: URI
, CopyrightDescription -> Maybe Text
_upstreamName :: Maybe Text
, CopyrightDescription -> Maybe Text
_upstreamContact :: Maybe Text
, CopyrightDescription -> Maybe Text
_upstreamSource :: Maybe Text
, CopyrightDescription -> Maybe Text
_disclaimer :: Maybe Text
, :: Maybe Text
, CopyrightDescription -> Maybe (License, Maybe Text)
_summaryLicense :: Maybe (License, Maybe Text)
, CopyrightDescription -> Maybe Text
_summaryCopyright :: Maybe Text
, CopyrightDescription -> [FilesOrLicenseDescription]
_filesAndLicenses :: [FilesOrLicenseDescription]
} deriving (CopyrightDescription -> CopyrightDescription -> Bool
(CopyrightDescription -> CopyrightDescription -> Bool)
-> (CopyrightDescription -> CopyrightDescription -> Bool)
-> Eq CopyrightDescription
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyrightDescription -> CopyrightDescription -> Bool
$c/= :: CopyrightDescription -> CopyrightDescription -> Bool
== :: CopyrightDescription -> CopyrightDescription -> Bool
$c== :: CopyrightDescription -> CopyrightDescription -> Bool
Eq, Eq CopyrightDescription
Eq CopyrightDescription
-> (CopyrightDescription -> CopyrightDescription -> Ordering)
-> (CopyrightDescription -> CopyrightDescription -> Bool)
-> (CopyrightDescription -> CopyrightDescription -> Bool)
-> (CopyrightDescription -> CopyrightDescription -> Bool)
-> (CopyrightDescription -> CopyrightDescription -> Bool)
-> (CopyrightDescription
-> CopyrightDescription -> CopyrightDescription)
-> (CopyrightDescription
-> CopyrightDescription -> CopyrightDescription)
-> Ord CopyrightDescription
CopyrightDescription -> CopyrightDescription -> Bool
CopyrightDescription -> CopyrightDescription -> Ordering
CopyrightDescription
-> CopyrightDescription -> CopyrightDescription
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CopyrightDescription
-> CopyrightDescription -> CopyrightDescription
$cmin :: CopyrightDescription
-> CopyrightDescription -> CopyrightDescription
max :: CopyrightDescription
-> CopyrightDescription -> CopyrightDescription
$cmax :: CopyrightDescription
-> CopyrightDescription -> CopyrightDescription
>= :: CopyrightDescription -> CopyrightDescription -> Bool
$c>= :: CopyrightDescription -> CopyrightDescription -> Bool
> :: CopyrightDescription -> CopyrightDescription -> Bool
$c> :: CopyrightDescription -> CopyrightDescription -> Bool
<= :: CopyrightDescription -> CopyrightDescription -> Bool
$c<= :: CopyrightDescription -> CopyrightDescription -> Bool
< :: CopyrightDescription -> CopyrightDescription -> Bool
$c< :: CopyrightDescription -> CopyrightDescription -> Bool
compare :: CopyrightDescription -> CopyrightDescription -> Ordering
$ccompare :: CopyrightDescription -> CopyrightDescription -> Ordering
$cp1Ord :: Eq CopyrightDescription
Ord, Int -> CopyrightDescription -> ShowS
[CopyrightDescription] -> ShowS
CopyrightDescription -> String
(Int -> CopyrightDescription -> ShowS)
-> (CopyrightDescription -> String)
-> ([CopyrightDescription] -> ShowS)
-> Show CopyrightDescription
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CopyrightDescription] -> ShowS
$cshowList :: [CopyrightDescription] -> ShowS
show :: CopyrightDescription -> String
$cshow :: CopyrightDescription -> String
showsPrec :: Int -> CopyrightDescription -> ShowS
$cshowsPrec :: Int -> CopyrightDescription -> ShowS
Show, Typeable CopyrightDescription
DataType
Constr
Typeable CopyrightDescription
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CopyrightDescription
-> c CopyrightDescription)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CopyrightDescription)
-> (CopyrightDescription -> Constr)
-> (CopyrightDescription -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CopyrightDescription))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CopyrightDescription))
-> ((forall b. Data b => b -> b)
-> CopyrightDescription -> CopyrightDescription)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CopyrightDescription -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CopyrightDescription -> r)
-> (forall u.
(forall d. Data d => d -> u) -> CopyrightDescription -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CopyrightDescription -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CopyrightDescription -> m CopyrightDescription)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CopyrightDescription -> m CopyrightDescription)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CopyrightDescription -> m CopyrightDescription)
-> Data CopyrightDescription
CopyrightDescription -> DataType
CopyrightDescription -> Constr
(forall b. Data b => b -> b)
-> CopyrightDescription -> CopyrightDescription
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CopyrightDescription
-> c CopyrightDescription
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CopyrightDescription
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CopyrightDescription -> u
forall u.
(forall d. Data d => d -> u) -> CopyrightDescription -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CopyrightDescription -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CopyrightDescription -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CopyrightDescription -> m CopyrightDescription
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CopyrightDescription -> m CopyrightDescription
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CopyrightDescription
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CopyrightDescription
-> c CopyrightDescription
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CopyrightDescription)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CopyrightDescription)
$cCopyrightDescription :: Constr
$tCopyrightDescription :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> CopyrightDescription -> m CopyrightDescription
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CopyrightDescription -> m CopyrightDescription
gmapMp :: (forall d. Data d => d -> m d)
-> CopyrightDescription -> m CopyrightDescription
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CopyrightDescription -> m CopyrightDescription
gmapM :: (forall d. Data d => d -> m d)
-> CopyrightDescription -> m CopyrightDescription
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CopyrightDescription -> m CopyrightDescription
gmapQi :: Int -> (forall d. Data d => d -> u) -> CopyrightDescription -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> CopyrightDescription -> u
gmapQ :: (forall d. Data d => d -> u) -> CopyrightDescription -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> CopyrightDescription -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CopyrightDescription -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CopyrightDescription -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CopyrightDescription -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CopyrightDescription -> r
gmapT :: (forall b. Data b => b -> b)
-> CopyrightDescription -> CopyrightDescription
$cgmapT :: (forall b. Data b => b -> b)
-> CopyrightDescription -> CopyrightDescription
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CopyrightDescription)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CopyrightDescription)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c CopyrightDescription)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CopyrightDescription)
dataTypeOf :: CopyrightDescription -> DataType
$cdataTypeOf :: CopyrightDescription -> DataType
toConstr :: CopyrightDescription -> Constr
$ctoConstr :: CopyrightDescription -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CopyrightDescription
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CopyrightDescription
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CopyrightDescription
-> c CopyrightDescription
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> CopyrightDescription
-> c CopyrightDescription
$cp1Data :: Typeable CopyrightDescription
Data, Typeable)
data FilesOrLicenseDescription
= FilesDescription
{ FilesOrLicenseDescription -> String
_filesPattern :: FilePath
, FilesOrLicenseDescription -> Text
_filesCopyright :: Text
, FilesOrLicenseDescription -> License
_filesLicense :: License
, FilesOrLicenseDescription -> Maybe Text
_filesLicenseText :: Maybe Text
, :: Maybe Text
}
| LicenseDescription
{ FilesOrLicenseDescription -> License
_license :: License
, FilesOrLicenseDescription -> Maybe Text
_licenseText :: Maybe Text
, :: Maybe Text
} deriving (FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool
(FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool)
-> (FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool)
-> Eq FilesOrLicenseDescription
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool
$c/= :: FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool
== :: FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool
$c== :: FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool
Eq, Eq FilesOrLicenseDescription
Eq FilesOrLicenseDescription
-> (FilesOrLicenseDescription
-> FilesOrLicenseDescription -> Ordering)
-> (FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool)
-> (FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool)
-> (FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool)
-> (FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool)
-> (FilesOrLicenseDescription
-> FilesOrLicenseDescription -> FilesOrLicenseDescription)
-> (FilesOrLicenseDescription
-> FilesOrLicenseDescription -> FilesOrLicenseDescription)
-> Ord FilesOrLicenseDescription
FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool
FilesOrLicenseDescription -> FilesOrLicenseDescription -> Ordering
FilesOrLicenseDescription
-> FilesOrLicenseDescription -> FilesOrLicenseDescription
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FilesOrLicenseDescription
-> FilesOrLicenseDescription -> FilesOrLicenseDescription
$cmin :: FilesOrLicenseDescription
-> FilesOrLicenseDescription -> FilesOrLicenseDescription
max :: FilesOrLicenseDescription
-> FilesOrLicenseDescription -> FilesOrLicenseDescription
$cmax :: FilesOrLicenseDescription
-> FilesOrLicenseDescription -> FilesOrLicenseDescription
>= :: FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool
$c>= :: FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool
> :: FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool
$c> :: FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool
<= :: FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool
$c<= :: FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool
< :: FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool
$c< :: FilesOrLicenseDescription -> FilesOrLicenseDescription -> Bool
compare :: FilesOrLicenseDescription -> FilesOrLicenseDescription -> Ordering
$ccompare :: FilesOrLicenseDescription -> FilesOrLicenseDescription -> Ordering
$cp1Ord :: Eq FilesOrLicenseDescription
Ord, Int -> FilesOrLicenseDescription -> ShowS
[FilesOrLicenseDescription] -> ShowS
FilesOrLicenseDescription -> String
(Int -> FilesOrLicenseDescription -> ShowS)
-> (FilesOrLicenseDescription -> String)
-> ([FilesOrLicenseDescription] -> ShowS)
-> Show FilesOrLicenseDescription
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilesOrLicenseDescription] -> ShowS
$cshowList :: [FilesOrLicenseDescription] -> ShowS
show :: FilesOrLicenseDescription -> String
$cshow :: FilesOrLicenseDescription -> String
showsPrec :: Int -> FilesOrLicenseDescription -> ShowS
$cshowsPrec :: Int -> FilesOrLicenseDescription -> ShowS
Show, Typeable FilesOrLicenseDescription
DataType
Constr
Typeable FilesOrLicenseDescription
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FilesOrLicenseDescription
-> c FilesOrLicenseDescription)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FilesOrLicenseDescription)
-> (FilesOrLicenseDescription -> Constr)
-> (FilesOrLicenseDescription -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c FilesOrLicenseDescription))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FilesOrLicenseDescription))
-> ((forall b. Data b => b -> b)
-> FilesOrLicenseDescription -> FilesOrLicenseDescription)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FilesOrLicenseDescription
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FilesOrLicenseDescription
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> FilesOrLicenseDescription -> [u])
-> (forall u.
Int
-> (forall d. Data d => d -> u) -> FilesOrLicenseDescription -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FilesOrLicenseDescription -> m FilesOrLicenseDescription)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FilesOrLicenseDescription -> m FilesOrLicenseDescription)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FilesOrLicenseDescription -> m FilesOrLicenseDescription)
-> Data FilesOrLicenseDescription
FilesOrLicenseDescription -> DataType
FilesOrLicenseDescription -> Constr
(forall b. Data b => b -> b)
-> FilesOrLicenseDescription -> FilesOrLicenseDescription
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FilesOrLicenseDescription
-> c FilesOrLicenseDescription
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FilesOrLicenseDescription
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u) -> FilesOrLicenseDescription -> u
forall u.
(forall d. Data d => d -> u) -> FilesOrLicenseDescription -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FilesOrLicenseDescription
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FilesOrLicenseDescription
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FilesOrLicenseDescription -> m FilesOrLicenseDescription
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FilesOrLicenseDescription -> m FilesOrLicenseDescription
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FilesOrLicenseDescription
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FilesOrLicenseDescription
-> c FilesOrLicenseDescription
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c FilesOrLicenseDescription)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FilesOrLicenseDescription)
$cLicenseDescription :: Constr
$cFilesDescription :: Constr
$tFilesOrLicenseDescription :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> FilesOrLicenseDescription -> m FilesOrLicenseDescription
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FilesOrLicenseDescription -> m FilesOrLicenseDescription
gmapMp :: (forall d. Data d => d -> m d)
-> FilesOrLicenseDescription -> m FilesOrLicenseDescription
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FilesOrLicenseDescription -> m FilesOrLicenseDescription
gmapM :: (forall d. Data d => d -> m d)
-> FilesOrLicenseDescription -> m FilesOrLicenseDescription
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FilesOrLicenseDescription -> m FilesOrLicenseDescription
gmapQi :: Int
-> (forall d. Data d => d -> u) -> FilesOrLicenseDescription -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> FilesOrLicenseDescription -> u
gmapQ :: (forall d. Data d => d -> u) -> FilesOrLicenseDescription -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> FilesOrLicenseDescription -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FilesOrLicenseDescription
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FilesOrLicenseDescription
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FilesOrLicenseDescription
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FilesOrLicenseDescription
-> r
gmapT :: (forall b. Data b => b -> b)
-> FilesOrLicenseDescription -> FilesOrLicenseDescription
$cgmapT :: (forall b. Data b => b -> b)
-> FilesOrLicenseDescription -> FilesOrLicenseDescription
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FilesOrLicenseDescription)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FilesOrLicenseDescription)
dataCast1 :: (forall d. Data d => c (t d))
-> Maybe (c FilesOrLicenseDescription)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c FilesOrLicenseDescription)
dataTypeOf :: FilesOrLicenseDescription -> DataType
$cdataTypeOf :: FilesOrLicenseDescription -> DataType
toConstr :: FilesOrLicenseDescription -> Constr
$ctoConstr :: FilesOrLicenseDescription -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FilesOrLicenseDescription
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FilesOrLicenseDescription
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FilesOrLicenseDescription
-> c FilesOrLicenseDescription
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FilesOrLicenseDescription
-> c FilesOrLicenseDescription
$cp1Data :: Typeable FilesOrLicenseDescription
Data, Typeable)
instance Pretty CopyrightDescription where
pretty :: CopyrightDescription -> Doc
pretty x :: CopyrightDescription
x@(CopyrightDescription {_summaryComment :: CopyrightDescription -> Maybe Text
_summaryComment = Just Text
t}) | CopyrightDescription
x {_summaryComment :: Maybe Text
_summaryComment = Maybe Text
forall a. Maybe a
Nothing} CopyrightDescription -> CopyrightDescription -> Bool
forall a. Eq a => a -> a -> Bool
== CopyrightDescription
forall a. Default a => a
def = String -> Doc
text ((Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
List.dropWhileEnd Char -> Bool
isSpace (Text -> String
unpack Text
t) String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"\n")
pretty CopyrightDescription
x = Control' Text -> Doc
forall a. Pretty a => a -> Doc
pretty (Control' Text -> Doc)
-> (CopyrightDescription -> Control' Text)
-> CopyrightDescription
-> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CopyrightDescription -> Control' Text
toControlFile (CopyrightDescription -> Doc) -> CopyrightDescription -> Doc
forall a b. (a -> b) -> a -> b
$ CopyrightDescription
x
instance Default CopyrightDescription where
def :: CopyrightDescription
def = CopyrightDescription :: URI
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe (License, Maybe Text)
-> Maybe Text
-> [FilesOrLicenseDescription]
-> CopyrightDescription
CopyrightDescription
{ _format :: URI
_format = Maybe URI -> URI
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe URI -> URI) -> Maybe URI -> URI
forall a b. (a -> b) -> a -> b
$ String -> Maybe URI
parseURI String
"https://www.debian.org/doc/packaging-manuals/copyright-format/1.0/"
, _upstreamName :: Maybe Text
_upstreamName = Maybe Text
forall a. Maybe a
Nothing
, _upstreamContact :: Maybe Text
_upstreamContact = Maybe Text
forall a. Maybe a
Nothing
, _upstreamSource :: Maybe Text
_upstreamSource = Maybe Text
forall a. Maybe a
Nothing
, _disclaimer :: Maybe Text
_disclaimer = Maybe Text
forall a. Maybe a
Nothing
, _summaryComment :: Maybe Text
_summaryComment = Maybe Text
forall a. Maybe a
Nothing
, _summaryLicense :: Maybe (License, Maybe Text)
_summaryLicense = Maybe (License, Maybe Text)
forall a. Maybe a
Nothing
, _summaryCopyright :: Maybe Text
_summaryCopyright = Maybe Text
forall a. Maybe a
Nothing
, _filesAndLicenses :: [FilesOrLicenseDescription]
_filesAndLicenses = [] }
readCopyrightDescription :: Text -> CopyrightDescription
readCopyrightDescription :: Text -> CopyrightDescription
readCopyrightDescription Text
t =
case String -> Text -> Either ParseError (Control' Text)
forall a.
ControlFunctions a =>
String -> a -> Either ParseError (Control' a)
parseControl String
"debian/copyright" Text
t of
Left ParseError
_e -> CopyrightDescription
forall a. Default a => a
def { _summaryComment :: Maybe Text
_summaryComment = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t }
Right Control' Text
ctl -> case [Paragraph' Text] -> Maybe CopyrightDescription
parseCopyrightDescription (Control' Text -> [Paragraph' Text]
forall a. Control' a -> [Paragraph' a]
unControl Control' Text
ctl) of
Just CopyrightDescription
cpy -> CopyrightDescription
cpy
Maybe CopyrightDescription
Nothing -> CopyrightDescription
forall a. Default a => a
def { _summaryComment :: Maybe Text
_summaryComment = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t }
parseCopyrightDescription :: [Paragraph' Text] -> Maybe CopyrightDescription
parseCopyrightDescription :: [Paragraph' Text] -> Maybe CopyrightDescription
parseCopyrightDescription (Paragraph' Text
hd : [Paragraph' Text]
tl) =
let (Either (Paragraph' Text) URI
muri :: Either (Paragraph' Text) URI) = Either (Paragraph' Text) URI
-> (URI -> Either (Paragraph' Text) URI)
-> Maybe URI
-> Either (Paragraph' Text) URI
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Paragraph' Text -> Either (Paragraph' Text) URI
forall a b. a -> Either a b
Left Paragraph' Text
hd) URI -> Either (Paragraph' Text) URI
forall a b. b -> Either a b
Right (Maybe URI -> (Text -> Maybe URI) -> Maybe Text -> Maybe URI
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Maybe URI
forall a. Maybe a
Nothing (String -> Maybe URI
parseURI (String -> Maybe URI) -> (Text -> String) -> Text -> Maybe URI
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack) (String -> Paragraph' Text -> Maybe Text
forall a. ControlFunctions a => String -> Paragraph' a -> Maybe a
fieldValue String
"Format" Paragraph' Text
hd)) in
case (Either (Paragraph' Text) URI
muri, (Paragraph' Text
-> Either (Paragraph' Text) FilesOrLicenseDescription)
-> [Paragraph' Text]
-> [Either (Paragraph' Text) FilesOrLicenseDescription]
forall a b. (a -> b) -> [a] -> [b]
map Paragraph' Text
-> Either (Paragraph' Text) FilesOrLicenseDescription
parseFilesOrLicense [Paragraph' Text]
tl) of
(Right URI
uri, [Either (Paragraph' Text) FilesOrLicenseDescription]
fnls) | (Either (Paragraph' Text) FilesOrLicenseDescription -> Bool)
-> [Either (Paragraph' Text) FilesOrLicenseDescription] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((Paragraph' Text -> Bool)
-> (FilesOrLicenseDescription -> Bool)
-> Either (Paragraph' Text) FilesOrLicenseDescription
-> Bool
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Bool -> Paragraph' Text -> Bool
forall a b. a -> b -> a
const Bool
False) (Bool -> FilesOrLicenseDescription -> Bool
forall a b. a -> b -> a
const Bool
True)) [Either (Paragraph' Text) FilesOrLicenseDescription]
fnls ->
CopyrightDescription -> Maybe CopyrightDescription
forall a. a -> Maybe a
Just (CopyrightDescription -> Maybe CopyrightDescription)
-> CopyrightDescription -> Maybe CopyrightDescription
forall a b. (a -> b) -> a -> b
$ CopyrightDescription :: URI
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe (License, Maybe Text)
-> Maybe Text
-> [FilesOrLicenseDescription]
-> CopyrightDescription
CopyrightDescription
{ _format :: URI
_format = URI
uri
, _upstreamName :: Maybe Text
_upstreamName = String -> Paragraph' Text -> Maybe Text
forall a. ControlFunctions a => String -> Paragraph' a -> Maybe a
fieldValue String
"Upstream-Name" Paragraph' Text
hd
, _upstreamContact :: Maybe Text
_upstreamContact = String -> Paragraph' Text -> Maybe Text
forall a. ControlFunctions a => String -> Paragraph' a -> Maybe a
fieldValue String
"Upstream-Contact" Paragraph' Text
hd
, _upstreamSource :: Maybe Text
_upstreamSource = String -> Paragraph' Text -> Maybe Text
forall a. ControlFunctions a => String -> Paragraph' a -> Maybe a
fieldValue String
"Source" Paragraph' Text
hd
, _disclaimer :: Maybe Text
_disclaimer = String -> Paragraph' Text -> Maybe Text
forall a. ControlFunctions a => String -> Paragraph' a -> Maybe a
fieldValue String
"Disclaimer" Paragraph' Text
hd
, _summaryComment :: Maybe Text
_summaryComment = String -> Paragraph' Text -> Maybe Text
forall a. ControlFunctions a => String -> Paragraph' a -> Maybe a
fieldValue String
"Comment" Paragraph' Text
hd
, _summaryLicense :: Maybe (License, Maybe Text)
_summaryLicense = (Text -> (License, Maybe Text))
-> Maybe Text -> Maybe (License, Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> (License, Maybe Text)
readLicenseField (String -> Paragraph' Text -> Maybe Text
forall a. ControlFunctions a => String -> Paragraph' a -> Maybe a
fieldValue String
"License" Paragraph' Text
hd)
, _summaryCopyright :: Maybe Text
_summaryCopyright = Maybe Text
forall a. Maybe a
Nothing
, _filesAndLicenses :: [FilesOrLicenseDescription]
_filesAndLicenses = [Either (Paragraph' Text) FilesOrLicenseDescription]
-> [FilesOrLicenseDescription]
forall a b. [Either a b] -> [b]
rights [Either (Paragraph' Text) FilesOrLicenseDescription]
fnls
}
(Either (Paragraph' Text) URI
_, [Either (Paragraph' Text) FilesOrLicenseDescription]
fnls) -> String -> Maybe CopyrightDescription -> Maybe CopyrightDescription
forall a. String -> a -> a
trace (String
"Not a parsable copyright file: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [Paragraph' Text] -> String
forall a. Show a => a -> String
show ([Either (Paragraph' Text) URI] -> [Paragraph' Text]
forall a b. [Either a b] -> [a]
lefts [Either (Paragraph' Text) URI
muri] [Paragraph' Text] -> [Paragraph' Text] -> [Paragraph' Text]
forall a. [a] -> [a] -> [a]
++ [Either (Paragraph' Text) FilesOrLicenseDescription]
-> [Paragraph' Text]
forall a b. [Either a b] -> [a]
lefts [Either (Paragraph' Text) FilesOrLicenseDescription]
fnls)) Maybe CopyrightDescription
forall a. Maybe a
Nothing
parseCopyrightDescription [] = Maybe CopyrightDescription
forall a. Maybe a
Nothing
readLicenseField :: Text -> (License, Maybe Text)
readLicenseField :: Text -> (License, Maybe Text)
readLicenseField Text
v
| [Text] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Text]
lns Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1
= (Text -> License
readLicense Text
firstLine, Text -> Maybe Text
forall a. a -> Maybe a
Just Text
otherLines)
| Bool
otherwise
= (Text -> License
readLicense Text
v, Maybe Text
forall a. Maybe a
Nothing)
where
lns :: [Text]
lns = Text -> [Text]
Text.lines Text
v
firstLine :: Text
firstLine = [Text] -> Text
forall a. [a] -> a
head [Text]
lns
otherLines :: Text
otherLines = [Text] -> Text
Text.unlines ([Text] -> [Text]
forall a. [a] -> [a]
tail [Text]
lns)
parseFilesOrLicense :: Paragraph' Text -> Either (Paragraph' Text) (FilesOrLicenseDescription)
parseFilesOrLicense :: Paragraph' Text
-> Either (Paragraph' Text) FilesOrLicenseDescription
parseFilesOrLicense Paragraph' Text
p =
case (String -> Paragraph' Text -> Maybe Text
forall a. ControlFunctions a => String -> Paragraph' a -> Maybe a
fieldValue String
"Files" Paragraph' Text
p, String -> Paragraph' Text -> Maybe Text
forall a. ControlFunctions a => String -> Paragraph' a -> Maybe a
fieldValue String
"Copyright" Paragraph' Text
p, String -> Paragraph' Text -> Maybe Text
forall a. ControlFunctions a => String -> Paragraph' a -> Maybe a
fieldValue String
"License" Paragraph' Text
p) of
(Just Text
files,
Just Text
copyright,
Just Text
license) ->
let (License
l,Maybe Text
t) = Text -> (License, Maybe Text)
readLicenseField Text
license
in FilesOrLicenseDescription
-> Either (Paragraph' Text) FilesOrLicenseDescription
forall a b. b -> Either a b
Right (FilesOrLicenseDescription
-> Either (Paragraph' Text) FilesOrLicenseDescription)
-> FilesOrLicenseDescription
-> Either (Paragraph' Text) FilesOrLicenseDescription
forall a b. (a -> b) -> a -> b
$ FilesDescription :: String
-> Text
-> License
-> Maybe Text
-> Maybe Text
-> FilesOrLicenseDescription
FilesDescription
{ _filesPattern :: String
_filesPattern = Text -> String
unpack Text
files
, _filesCopyright :: Text
_filesCopyright = Text
copyright
, _filesLicense :: License
_filesLicense = License
l
, _filesLicenseText :: Maybe Text
_filesLicenseText = Maybe Text
t
, _filesComment :: Maybe Text
_filesComment = String -> Paragraph' Text -> Maybe Text
forall a. ControlFunctions a => String -> Paragraph' a -> Maybe a
fieldValue String
"Comment" Paragraph' Text
p }
(Maybe Text
Nothing,
Maybe Text
Nothing,
Just Text
license) ->
let (License
l,Maybe Text
t) = Text -> (License, Maybe Text)
readLicenseField Text
license
in FilesOrLicenseDescription
-> Either (Paragraph' Text) FilesOrLicenseDescription
forall a b. b -> Either a b
Right (FilesOrLicenseDescription
-> Either (Paragraph' Text) FilesOrLicenseDescription)
-> FilesOrLicenseDescription
-> Either (Paragraph' Text) FilesOrLicenseDescription
forall a b. (a -> b) -> a -> b
$ LicenseDescription :: License -> Maybe Text -> Maybe Text -> FilesOrLicenseDescription
LicenseDescription
{ _license :: License
_license = License
l
, _licenseText :: Maybe Text
_licenseText = Maybe Text
t
, _comment :: Maybe Text
_comment = String -> Paragraph' Text -> Maybe Text
forall a. ControlFunctions a => String -> Paragraph' a -> Maybe a
fieldValue String
"Comment" Paragraph' Text
p }
(Maybe Text, Maybe Text, Maybe Text)
_ -> Paragraph' Text
-> Either (Paragraph' Text) FilesOrLicenseDescription
forall a b. a -> Either a b
Left Paragraph' Text
p
toControlFile :: CopyrightDescription -> Control' Text
toControlFile :: CopyrightDescription -> Control' Text
toControlFile CopyrightDescription
d =
[Paragraph' Text] -> Control' Text
forall a. [Paragraph' a] -> Control' a
Control
( [Field' Text] -> Paragraph' Text
forall a. [Field' a] -> Paragraph' a
Paragraph
( [ (Text, Text) -> Field' Text
forall a. (a, a) -> Field' a
Field (Text
"Format", (Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> URI -> Text
forall a. Pretty (PP a) => a -> Text
ppText (CopyrightDescription -> URI
_format CopyrightDescription
d))) ] [Field' Text] -> [Field' Text] -> [Field' Text]
forall a. [a] -> [a] -> [a]
++
[Field' Text]
-> (Text -> [Field' Text]) -> Maybe Text -> [Field' Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
x -> [(Text, Text) -> Field' Text
forall a. (a, a) -> Field' a
Field (Text
"Upstream-Name", Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
x)]) (CopyrightDescription -> Maybe Text
_upstreamName CopyrightDescription
d) [Field' Text] -> [Field' Text] -> [Field' Text]
forall a. [a] -> [a] -> [a]
++
[Field' Text]
-> (Text -> [Field' Text]) -> Maybe Text -> [Field' Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
x -> [(Text, Text) -> Field' Text
forall a. (a, a) -> Field' a
Field (Text
"Upstream-Contact", Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
x)]) (CopyrightDescription -> Maybe Text
_upstreamContact CopyrightDescription
d) [Field' Text] -> [Field' Text] -> [Field' Text]
forall a. [a] -> [a] -> [a]
++
[Field' Text]
-> (Text -> [Field' Text]) -> Maybe Text -> [Field' Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
x -> [(Text, Text) -> Field' Text
forall a. (a, a) -> Field' a
Field (Text
"Source", Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
x)]) (CopyrightDescription -> Maybe Text
_upstreamSource CopyrightDescription
d) [Field' Text] -> [Field' Text] -> [Field' Text]
forall a. [a] -> [a] -> [a]
++
[Field' Text]
-> (Text -> [Field' Text]) -> Maybe Text -> [Field' Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
x -> [(Text, Text) -> Field' Text
forall a. (a, a) -> Field' a
Field (Text
"Disclaimer", Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
x)]) (CopyrightDescription -> Maybe Text
_disclaimer CopyrightDescription
d) [Field' Text] -> [Field' Text] -> [Field' Text]
forall a. [a] -> [a] -> [a]
++
[Field' Text]
-> ((License, Maybe Text) -> [Field' Text])
-> Maybe (License, Maybe Text)
-> [Field' Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\(License
x,Maybe Text
t) -> [License -> Maybe Text -> Field' Text
toLicenseField License
x Maybe Text
t]) (CopyrightDescription -> Maybe (License, Maybe Text)
_summaryLicense CopyrightDescription
d) [Field' Text] -> [Field' Text] -> [Field' Text]
forall a. [a] -> [a] -> [a]
++
[Field' Text]
-> (Text -> [Field' Text]) -> Maybe Text -> [Field' Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
x -> [(Text, Text) -> Field' Text
forall a. (a, a) -> Field' a
Field (Text
"Copyright", Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
x)]) (CopyrightDescription -> Maybe Text
_summaryCopyright CopyrightDescription
d) [Field' Text] -> [Field' Text] -> [Field' Text]
forall a. [a] -> [a] -> [a]
++
[Field' Text]
-> (Text -> [Field' Text]) -> Maybe Text -> [Field' Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
x -> [(Text, Text) -> Field' Text
forall a. (a, a) -> Field' a
Field (Text
"Comment", Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
x)]) (CopyrightDescription -> Maybe Text
_summaryComment CopyrightDescription
d)) Paragraph' Text -> [Paragraph' Text] -> [Paragraph' Text]
forall a. a -> [a] -> [a]
:
(FilesOrLicenseDescription -> Paragraph' Text)
-> [FilesOrLicenseDescription] -> [Paragraph' Text]
forall a b. (a -> b) -> [a] -> [b]
map FilesOrLicenseDescription -> Paragraph' Text
toParagraph (CopyrightDescription -> [FilesOrLicenseDescription]
_filesAndLicenses CopyrightDescription
d) )
toParagraph :: FilesOrLicenseDescription -> Paragraph' Text
toParagraph :: FilesOrLicenseDescription -> Paragraph' Text
toParagraph fd :: FilesOrLicenseDescription
fd@FilesDescription {} =
[Field' Text] -> Paragraph' Text
forall a. [Field' a] -> Paragraph' a
Paragraph ([Field' Text] -> Paragraph' Text)
-> [Field' Text] -> Paragraph' Text
forall a b. (a -> b) -> a -> b
$
[ (Text, Text) -> Field' Text
forall a. (a, a) -> Field' a
Field (Text
"Files", Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
pack (FilesOrLicenseDescription -> String
_filesPattern FilesOrLicenseDescription
fd))
, (Text, Text) -> Field' Text
forall a. (a, a) -> Field' a
Field (Text
"Copyright", Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FilesOrLicenseDescription -> Text
_filesCopyright FilesOrLicenseDescription
fd)
, License -> Maybe Text -> Field' Text
toLicenseField (FilesOrLicenseDescription -> License
_filesLicense FilesOrLicenseDescription
fd) (FilesOrLicenseDescription -> Maybe Text
_filesLicenseText FilesOrLicenseDescription
fd)
] [Field' Text] -> [Field' Text] -> [Field' Text]
forall a. [a] -> [a] -> [a]
++
[Field' Text]
-> (Text -> [Field' Text]) -> Maybe Text -> [Field' Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\ Text
t -> [(Text, Text) -> Field' Text
forall a. (a, a) -> Field' a
Field (Text
"Comment", Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t)]) (FilesOrLicenseDescription -> Maybe Text
_filesComment FilesOrLicenseDescription
fd)
toParagraph ld :: FilesOrLicenseDescription
ld@LicenseDescription {} =
[Field' Text] -> Paragraph' Text
forall a. [Field' a] -> Paragraph' a
Paragraph ([Field' Text] -> Paragraph' Text)
-> [Field' Text] -> Paragraph' Text
forall a b. (a -> b) -> a -> b
$
[ License -> Maybe Text -> Field' Text
toLicenseField (FilesOrLicenseDescription -> License
_license FilesOrLicenseDescription
ld) (FilesOrLicenseDescription -> Maybe Text
_licenseText FilesOrLicenseDescription
ld)
] [Field' Text] -> [Field' Text] -> [Field' Text]
forall a. [a] -> [a] -> [a]
++
[Field' Text]
-> (Text -> [Field' Text]) -> Maybe Text -> [Field' Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\ Text
t -> [(Text, Text) -> Field' Text
forall a. (a, a) -> Field' a
Field (Text
"Comment", Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t)]) (FilesOrLicenseDescription -> Maybe Text
_comment FilesOrLicenseDescription
ld)
toLicenseField :: License -> Maybe Text -> Field' Text
toLicenseField :: License -> Maybe Text -> Field' Text
toLicenseField License
l Maybe Text
t =
(Text, Text) -> Field' Text
forall a. (a, a) -> Field' a
Field (Text
"License", Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> License -> Text
forall a. Pretty a => a -> Text
prettyText License
l Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> (Text -> Text) -> Maybe Text -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
forall a. Monoid a => a
mempty (String -> Text
Text.pack String
"\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) Maybe Text
t)
sourceDefaultFilesDescription :: Maybe Text -> License -> FilesOrLicenseDescription
sourceDefaultFilesDescription :: Maybe Text -> License -> FilesOrLicenseDescription
sourceDefaultFilesDescription Maybe Text
copyrt License
license =
FilesDescription :: String
-> Text
-> License
-> Maybe Text
-> Maybe Text
-> FilesOrLicenseDescription
FilesDescription {
_filesPattern :: String
_filesPattern = String
"*"
, _filesCopyright :: Text
_filesCopyright = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"(No copyright field in cabal file)" Maybe Text
copyrt
, _filesLicense :: License
_filesLicense = License
license
, _filesLicenseText :: Maybe Text
_filesLicenseText = Maybe Text
forall a. Monoid a => a
mempty
, _filesComment :: Maybe Text
_filesComment = Maybe Text
forall a. Monoid a => a
mempty
}
debianDefaultFilesDescription :: License -> FilesOrLicenseDescription
debianDefaultFilesDescription :: License -> FilesOrLicenseDescription
debianDefaultFilesDescription License
license =
FilesDescription :: String
-> Text
-> License
-> Maybe Text
-> Maybe Text
-> FilesOrLicenseDescription
FilesDescription {
_filesPattern :: String
_filesPattern = String
"debian/*"
, _filesCopyright :: Text
_filesCopyright = Text
"held by the contributors mentioned in debian/changelog"
, _filesLicense :: License
_filesLicense = License
license
, _filesLicenseText :: Maybe Text
_filesLicenseText = Maybe Text
forall a. Monoid a => a
mempty
, _filesComment :: Maybe Text
_filesComment = Maybe Text
forall a. Monoid a => a
mempty
}
defaultLicenseDescriptions ::
License -> [(FilePath, Maybe Text)] -> [FilesOrLicenseDescription]
defaultLicenseDescriptions :: License -> [(String, Maybe Text)] -> [FilesOrLicenseDescription]
defaultLicenseDescriptions License
license = \case
[] -> []
[(String
_, Maybe Text
txt)] -> [License -> Maybe Text -> Maybe Text -> FilesOrLicenseDescription
LicenseDescription License
license Maybe Text
txt Maybe Text
forall a. Maybe a
Nothing]
[(String, Maybe Text)]
pairs -> ((String, Maybe Text) -> FilesOrLicenseDescription)
-> [(String, Maybe Text)] -> [FilesOrLicenseDescription]
forall a b. (a -> b) -> [a] -> [b]
map (String, Maybe Text) -> FilesOrLicenseDescription
mkLicenseDescription [(String, Maybe Text)]
pairs
where
mkLicenseDescription :: (String, Maybe Text) -> FilesOrLicenseDescription
mkLicenseDescription (String
path, Maybe Text
txt) =
LicenseDescription :: License -> Maybe Text -> Maybe Text -> FilesOrLicenseDescription
LicenseDescription {
_license :: License
_license = License -> License
fromCabalLicense (String -> License
Cabal.UnknownLicense String
path)
, _licenseText :: Maybe Text
_licenseText = Maybe Text
txt
, _comment :: Maybe Text
_comment = Maybe Text
forall a. Monoid a => a
mempty
}
defaultCopyrightDescription :: Cabal.PackageDescription -> IO CopyrightDescription
defaultCopyrightDescription :: PackageDescription -> IO CopyrightDescription
defaultCopyrightDescription PackageDescription
pkgDesc = do
#if MIN_VERSION_Cabal(3,6,0)
let (debianCopyrightPath, otherLicensePaths) = partition (== DUP.unsafeMakeSymbolicPath "debian/copyright") (Cabal.licenseFiles pkgDesc)
#else
let ([String]
debianCopyrightPath, [String]
otherLicensePaths) = (String -> Bool) -> [String] -> ([String], [String])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"debian/copyright") (PackageDescription -> [String]
Cabal.licenseFiles PackageDescription
pkgDesc)
#endif
license :: License
license = (License -> License)
-> (License -> License) -> Either License License -> License
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (\License
x -> String -> License
OtherLicense (String
"SPDX license: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ License -> String
forall a. Show a => a -> String
show License
x)) License -> License
fromCabalLicense (Either License License -> License)
-> Either License License -> License
forall a b. (a -> b) -> a -> b
$ PackageDescription -> Either License License
Cabal.licenseRaw PackageDescription
pkgDesc
pkgname :: String
pkgname = PackageName -> String
unPackageName (PackageName -> String)
-> (PackageDescription -> PackageName)
-> PackageDescription
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageIdentifier -> PackageName
Cabal.pkgName (PackageIdentifier -> PackageName)
-> (PackageDescription -> PackageIdentifier)
-> PackageDescription
-> PackageName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> PackageIdentifier
Cabal.package (PackageDescription -> String) -> PackageDescription -> String
forall a b. (a -> b) -> a -> b
$ PackageDescription
pkgDesc
maintainer :: ShortText
maintainer = PackageDescription -> ShortText
Cabal.maintainer (PackageDescription -> ShortText)
-> PackageDescription -> ShortText
forall a b. (a -> b) -> a -> b
$ PackageDescription
pkgDesc
#if MIN_VERSION_Cabal(3,6,0)
debianCopyrightText <- mapM (readFileMaybe . DUP.getSymbolicPath) debianCopyrightPath >>= return . listToMaybe . catMaybes
licenseCommentPairs <- mapM (readFileMaybe . DUP.getSymbolicPath) otherLicensePaths >>= return . filter (isJust . snd) . zip otherLicensePaths
#else
Maybe Text
debianCopyrightText <- (String -> IO (Maybe Text)) -> [String] -> IO [Maybe Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> IO (Maybe Text)
readFileMaybe [String]
debianCopyrightPath IO [Maybe Text]
-> ([Maybe Text] -> IO (Maybe Text)) -> IO (Maybe Text)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Text -> IO (Maybe Text))
-> ([Maybe Text] -> Maybe Text) -> [Maybe Text] -> IO (Maybe Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Maybe Text
forall a. [a] -> Maybe a
listToMaybe ([Text] -> Maybe Text)
-> ([Maybe Text] -> [Text]) -> [Maybe Text] -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe Text] -> [Text]
forall a. [Maybe a] -> [a]
catMaybes
[(String, Maybe Text)]
licenseCommentPairs <- (String -> IO (Maybe Text)) -> [String] -> IO [Maybe Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> IO (Maybe Text)
readFileMaybe [String]
otherLicensePaths IO [Maybe Text]
-> ([Maybe Text] -> IO [(String, Maybe Text)])
-> IO [(String, Maybe Text)]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [(String, Maybe Text)] -> IO [(String, Maybe Text)]
forall (m :: * -> *) a. Monad m => a -> m a
return ([(String, Maybe Text)] -> IO [(String, Maybe Text)])
-> ([Maybe Text] -> [(String, Maybe Text)])
-> [Maybe Text]
-> IO [(String, Maybe Text)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((String, Maybe Text) -> Bool)
-> [(String, Maybe Text)] -> [(String, Maybe Text)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust (Maybe Text -> Bool)
-> ((String, Maybe Text) -> Maybe Text)
-> (String, Maybe Text)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, Maybe Text) -> Maybe Text
forall a b. (a, b) -> b
snd) ([(String, Maybe Text)] -> [(String, Maybe Text)])
-> ([Maybe Text] -> [(String, Maybe Text)])
-> [Maybe Text]
-> [(String, Maybe Text)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [Maybe Text] -> [(String, Maybe Text)]
forall a b. [a] -> [b] -> [(a, b)]
zip [String]
otherLicensePaths
#endif
CopyrightDescription -> IO CopyrightDescription
forall (m :: * -> *) a. Monad m => a -> m a
return (CopyrightDescription -> IO CopyrightDescription)
-> CopyrightDescription -> IO CopyrightDescription
forall a b. (a -> b) -> a -> b
$ case Maybe Text
debianCopyrightText of
Just Text
t ->
CopyrightDescription
forall a. Default a => a
def { _summaryComment :: Maybe Text
_summaryComment = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t }
Maybe Text
Nothing ->
let copyrt :: Maybe Text
copyrt = (Text -> Text) -> Maybe Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
dots (Maybe Text -> Maybe Text) -> Maybe Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ (Text -> Bool) -> Text -> Maybe Text
forall a. (a -> Bool) -> a -> Maybe a
nothingIf (Text -> Bool
Text.null (Text -> Bool) -> (Text -> Text) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
strip) (ShortText -> Text
toText (PackageDescription -> ShortText
Cabal.copyright PackageDescription
pkgDesc)) in
CopyrightDescription
forall a. Default a => a
def { _filesAndLicenses :: [FilesOrLicenseDescription]
_filesAndLicenses =
[ Maybe Text -> License -> FilesOrLicenseDescription
sourceDefaultFilesDescription Maybe Text
copyrt License
license,
License -> FilesOrLicenseDescription
debianDefaultFilesDescription License
license ] [FilesOrLicenseDescription]
-> [FilesOrLicenseDescription] -> [FilesOrLicenseDescription]
forall a. [a] -> [a] -> [a]
++
#if MIN_VERSION_Cabal(3,6,0)
defaultLicenseDescriptions license (map (\(x,y) -> (DUP.getSymbolicPath x, y)) licenseCommentPairs)
#else
License -> [(String, Maybe Text)] -> [FilesOrLicenseDescription]
defaultLicenseDescriptions License
license [(String, Maybe Text)]
licenseCommentPairs
#endif
, _upstreamName :: Maybe Text
_upstreamName = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> (String -> Text) -> String -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack (String -> Maybe Text) -> String -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String
pkgname
, _upstreamSource :: Maybe Text
_upstreamSource = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> (String -> Text) -> String -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack (String -> Maybe Text) -> String -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String
"https://hackage.haskell.org/package/" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
pkgname
, _upstreamContact :: Maybe Text
_upstreamContact = (Text -> Bool) -> Text -> Maybe Text
forall a. (a -> Bool) -> a -> Maybe a
nothingIf Text -> Bool
Text.null (ShortText -> Text
toText ShortText
maintainer)
}
where
toText :: ShortText -> Text
toText =
#if MIN_VERSION_Cabal(3,2,0)
String -> Text
pack (String -> Text) -> (ShortText -> String) -> ShortText -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> String
ST.fromShortText
#else
pack
#endif
dots :: Text -> Text
dots :: Text -> Text
dots = [Text] -> Text
Text.unlines ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (\ Text
line -> if Text -> Bool
Text.null Text
line then Text
"." else Text
line) ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ((Char -> Bool) -> Text -> Text
Text.dropWhileEnd Char -> Bool
isSpace) ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
Text.lines
$()
$()