{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Distribution.License (
License(..),
knownLicenses,
licenseToSPDX,
licenseFromSPDX,
) where
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.Parsec
import Distribution.Pretty
import Distribution.Version
import qualified Distribution.Compat.CharParsing as P
import qualified Data.Map.Strict as Map
import qualified Distribution.SPDX as SPDX
import qualified Text.PrettyPrint as Disp
data License =
GPL (Maybe Version)
| AGPL (Maybe Version)
| LGPL (Maybe Version)
| BSD2
| BSD3
| BSD4
| MIT
| ISC
| MPL Version
| Apache (Maybe Version)
| PublicDomain
| AllRightsReserved
| UnspecifiedLicense
| OtherLicense
| UnknownLicense String
deriving ((forall x. License -> Rep License x)
-> (forall x. Rep License x -> License) -> Generic License
forall x. Rep License x -> License
forall x. License -> Rep License x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep License x -> License
$cfrom :: forall x. License -> Rep License x
Generic, ReadPrec [License]
ReadPrec License
Int -> ReadS License
ReadS [License]
(Int -> ReadS License)
-> ReadS [License]
-> ReadPrec License
-> ReadPrec [License]
-> Read License
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [License]
$creadListPrec :: ReadPrec [License]
readPrec :: ReadPrec License
$creadPrec :: ReadPrec License
readList :: ReadS [License]
$creadList :: ReadS [License]
readsPrec :: Int -> ReadS License
$creadsPrec :: Int -> ReadS License
External instance of the constraint type Read Char
External instance of the constraint type Read Version
External instance of the constraint type Read Char
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type Read Version
External instance of the constraint type forall a. Read a => Read (Maybe a)
External instance of the constraint type forall a. Read a => Read (Maybe a)
External instance of the constraint type Read Version
External instance of the constraint type Monad ReadPrec
External instance of the constraint type Monad ReadPrec
Instance of class: Read of the constraint type Read License
Read, Int -> License -> ShowS
[License] -> ShowS
License -> String
(Int -> License -> ShowS)
-> (License -> String) -> ([License] -> ShowS) -> Show License
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [License] -> ShowS
$cshowList :: [License] -> ShowS
show :: License -> String
$cshow :: License -> String
showsPrec :: Int -> License -> ShowS
$cshowsPrec :: Int -> License -> ShowS
External instance of the constraint type Show Char
External instance of the constraint type Show Version
External instance of the constraint type Show Char
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type Show Version
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type forall a. Show a => Show (Maybe a)
External instance of the constraint type Show Version
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
Show, License -> License -> Bool
(License -> License -> Bool)
-> (License -> License -> Bool) -> Eq License
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: License -> License -> Bool
$c/= :: License -> License -> Bool
== :: License -> License -> Bool
$c== :: License -> License -> Bool
External instance of the constraint type Eq Char
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Version
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type Eq Version
Eq, Typeable, Typeable License
DataType
Constr
Typeable License
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> License -> c License)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c License)
-> (License -> Constr)
-> (License -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c License))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License))
-> ((forall b. Data b => b -> b) -> License -> License)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r)
-> (forall u. (forall d. Data d => d -> u) -> License -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> License -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> License -> m License)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License)
-> Data License
License -> DataType
License -> Constr
(forall b. Data b => b -> b) -> License -> License
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> License -> c License
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c License
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) -> License -> u
forall u. (forall d. Data d => d -> u) -> License -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> License -> m License
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c License
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> License -> c License
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c License)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License)
$cUnknownLicense :: Constr
$cOtherLicense :: Constr
$cUnspecifiedLicense :: Constr
$cAllRightsReserved :: Constr
$cPublicDomain :: Constr
$cApache :: Constr
$cMPL :: Constr
$cISC :: Constr
$cMIT :: Constr
$cBSD4 :: Constr
$cBSD3 :: Constr
$cBSD2 :: Constr
$cLGPL :: Constr
$cAGPL :: Constr
$cGPL :: Constr
$tLicense :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> License -> m License
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License
gmapMp :: (forall d. Data d => d -> m d) -> License -> m License
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> License -> m License
gmapM :: (forall d. Data d => d -> m d) -> License -> m License
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> License -> m License
gmapQi :: Int -> (forall d. Data d => d -> u) -> License -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> License -> u
gmapQ :: (forall d. Data d => d -> u) -> License -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> License -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> License -> r
gmapT :: (forall b. Data b => b -> b) -> License -> License
$cgmapT :: (forall b. Data b => b -> b) -> License -> License
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c License)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c License)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c License)
dataTypeOf :: License -> DataType
$cdataTypeOf :: License -> DataType
toConstr :: License -> Constr
$ctoConstr :: License -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c License
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c License
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> License -> c License
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> License -> c License
External instance of the constraint type Data Char
External instance of the constraint type Data Version
External instance of the constraint type Data Char
External instance of the constraint type Data Version
External instance of the constraint type forall a. Data a => Data (Maybe a)
External instance of the constraint type Data Version
External instance of the constraint type Data Char
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data Version
External instance of the constraint type forall a. Data a => Data (Maybe a)
External instance of the constraint type forall a. Data a => Data (Maybe a)
External instance of the constraint type Data Version
Data)
instance Binary License
instance Structured License
instance NFData License where rnf :: License -> ()
rnf = License -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData (Maybe a)
External instance of the constraint type NFData Version
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData (Maybe a)
External instance of the constraint type NFData Version
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData (Maybe a)
External instance of the constraint type NFData Version
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type NFData Version
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData (Maybe a)
External instance of the constraint type NFData Version
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) (b :: * -> *).
(GNFData a, GNFData b) =>
GNFData (a :+: b)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type GNFData U1
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall (a :: * -> *) i (c :: Meta). GNFData a => GNFData (M1 i c a)
External instance of the constraint type forall a i. NFData a => GNFData (K1 i a)
External instance of the constraint type forall a. NFData a => NFData [a]
External instance of the constraint type NFData Char
Instance of class: Generic of the constraint type Generic License
genericRnf
knownLicenses :: [License]
knownLicenses :: [License]
knownLicenses = [ Maybe Version -> License
GPL Maybe Version
forall {a}. Maybe a
unversioned, Maybe Version -> License
GPL ([Int] -> Maybe Version
version [Int
2]), Maybe Version -> License
GPL ([Int] -> Maybe Version
version [Int
3])
, Maybe Version -> License
LGPL Maybe Version
forall {a}. Maybe a
unversioned, Maybe Version -> License
LGPL ([Int] -> Maybe Version
version [Int
2, Int
1]), Maybe Version -> License
LGPL ([Int] -> Maybe Version
version [Int
3])
, Maybe Version -> License
AGPL Maybe Version
forall {a}. Maybe a
unversioned, Maybe Version -> License
AGPL ([Int] -> Maybe Version
version [Int
3])
, License
BSD2, License
BSD3, License
MIT, License
ISC
, Version -> License
MPL ([Int] -> Version
mkVersion [Int
2, Int
0])
, Maybe Version -> License
Apache Maybe Version
forall {a}. Maybe a
unversioned, Maybe Version -> License
Apache ([Int] -> Maybe Version
version [Int
2, Int
0])
, License
PublicDomain, License
AllRightsReserved, License
OtherLicense]
where
unversioned :: Maybe a
unversioned = Maybe a
forall {a}. Maybe a
Nothing
version :: [Int] -> Maybe Version
version = Version -> Maybe Version
forall a. a -> Maybe a
Just (Version -> Maybe Version)
-> ([Int] -> Version) -> [Int] -> Maybe Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> Version
mkVersion
licenseToSPDX :: License -> SPDX.License
licenseToSPDX :: License -> License
licenseToSPDX License
l = case License
l of
GPL Maybe Version
v | Maybe Version
v Maybe Version -> Maybe Version -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type Eq Version
== [Int] -> Maybe Version
version [Int
2] -> LicenseId -> License
spdx LicenseId
SPDX.GPL_2_0_only
GPL Maybe Version
v | Maybe Version
v Maybe Version -> Maybe Version -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type Eq Version
== [Int] -> Maybe Version
version [Int
3] -> LicenseId -> License
spdx LicenseId
SPDX.GPL_3_0_only
LGPL Maybe Version
v | Maybe Version
v Maybe Version -> Maybe Version -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type Eq Version
== [Int] -> Maybe Version
version [Int
2,Int
1] -> LicenseId -> License
spdx LicenseId
SPDX.LGPL_2_1_only
LGPL Maybe Version
v | Maybe Version
v Maybe Version -> Maybe Version -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type Eq Version
== [Int] -> Maybe Version
version [Int
3] -> LicenseId -> License
spdx LicenseId
SPDX.LGPL_3_0_only
AGPL Maybe Version
v | Maybe Version
v Maybe Version -> Maybe Version -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type Eq Version
== [Int] -> Maybe Version
version [Int
3] -> LicenseId -> License
spdx LicenseId
SPDX.AGPL_3_0_only
License
BSD2 -> LicenseId -> License
spdx LicenseId
SPDX.BSD_2_Clause
License
BSD3 -> LicenseId -> License
spdx LicenseId
SPDX.BSD_3_Clause
License
BSD4 -> LicenseId -> License
spdx LicenseId
SPDX.BSD_4_Clause
License
MIT -> LicenseId -> License
spdx LicenseId
SPDX.MIT
License
ISC -> LicenseId -> License
spdx LicenseId
SPDX.ISC
MPL Version
v | Version
v Version -> Version -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Version
== [Int] -> Version
mkVersion [Int
2,Int
0] -> LicenseId -> License
spdx LicenseId
SPDX.MPL_2_0
Apache Maybe Version
v | Maybe Version
v Maybe Version -> Maybe Version -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type Eq Version
== [Int] -> Maybe Version
version [Int
2,Int
0] -> LicenseId -> License
spdx LicenseId
SPDX.Apache_2_0
License
AllRightsReserved -> License
SPDX.NONE
License
UnspecifiedLicense -> License
SPDX.NONE
License
OtherLicense -> LicenseRef -> License
ref (Maybe String -> String -> LicenseRef
SPDX.mkLicenseRef' Maybe String
forall {a}. Maybe a
Nothing String
"OtherLicense")
License
PublicDomain -> LicenseRef -> License
ref (Maybe String -> String -> LicenseRef
SPDX.mkLicenseRef' Maybe String
forall {a}. Maybe a
Nothing String
"PublicDomain")
UnknownLicense String
str -> LicenseRef -> License
ref (Maybe String -> String -> LicenseRef
SPDX.mkLicenseRef' Maybe String
forall {a}. Maybe a
Nothing String
str)
License
_ -> LicenseRef -> License
ref (Maybe String -> String -> LicenseRef
SPDX.mkLicenseRef' Maybe String
forall {a}. Maybe a
Nothing (String -> LicenseRef) -> String -> LicenseRef
forall a b. (a -> b) -> a -> b
$ License -> String
forall a. Pretty a => a -> String
Instance of class: Pretty of the constraint type Pretty License
prettyShow License
l)
where
version :: [Int] -> Maybe Version
version = Version -> Maybe Version
forall a. a -> Maybe a
Just (Version -> Maybe Version)
-> ([Int] -> Version) -> [Int] -> Maybe Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> Version
mkVersion
spdx :: LicenseId -> License
spdx = LicenseExpression -> License
SPDX.License (LicenseExpression -> License)
-> (LicenseId -> LicenseExpression) -> LicenseId -> License
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LicenseId -> LicenseExpression
SPDX.simpleLicenseExpression
ref :: LicenseRef -> License
ref LicenseRef
r = LicenseExpression -> License
SPDX.License (LicenseExpression -> License) -> LicenseExpression -> License
forall a b. (a -> b) -> a -> b
$ SimpleLicenseExpression
-> Maybe LicenseExceptionId -> LicenseExpression
SPDX.ELicense (LicenseRef -> SimpleLicenseExpression
SPDX.ELicenseRef LicenseRef
r) Maybe LicenseExceptionId
forall {a}. Maybe a
Nothing
licenseFromSPDX :: SPDX.License -> License
licenseFromSPDX :: License -> License
licenseFromSPDX License
SPDX.NONE = License
AllRightsReserved
licenseFromSPDX License
l =
License -> Maybe License -> License
forall a. a -> Maybe a -> a
fromMaybe (String -> License
mungle (String -> License) -> String -> License
forall a b. (a -> b) -> a -> b
$ License -> String
forall a. Pretty a => a -> String
External instance of the constraint type Pretty License
prettyShow License
l) (Maybe License -> License) -> Maybe License -> License
forall a b. (a -> b) -> a -> b
$ License -> Map License License -> Maybe License
forall k a. Ord k => k -> Map k a -> Maybe a
External instance of the constraint type Ord License
Map.lookup License
l Map License License
m
where
m :: Map.Map SPDX.License License
m :: Map License License
m = [(License, License)] -> Map License License
forall k a. Ord k => [(k, a)] -> Map k a
External instance of the constraint type Ord License
Map.fromList ([(License, License)] -> Map License License)
-> [(License, License)] -> Map License License
forall a b. (a -> b) -> a -> b
$ ((License, License) -> Bool)
-> [(License, License)] -> [(License, License)]
forall a. (a -> Bool) -> [a] -> [a]
filter (License -> Bool
isSimple (License -> Bool)
-> ((License, License) -> License) -> (License, License) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (License, License) -> License
forall a b. (a, b) -> a
fst ) ([(License, License)] -> [(License, License)])
-> [(License, License)] -> [(License, License)]
forall a b. (a -> b) -> a -> b
$
(License -> (License, License))
-> [License] -> [(License, License)]
forall a b. (a -> b) -> [a] -> [b]
map (\License
x -> (License -> License
licenseToSPDX License
x, License
x)) [License]
knownLicenses
isSimple :: License -> Bool
isSimple (SPDX.License (SPDX.ELicense (SPDX.ELicenseId LicenseId
_) Maybe LicenseExceptionId
Nothing)) = Bool
True
isSimple License
_ = Bool
False
mungle :: String -> License
mungle String
name = License -> Maybe License -> License
forall a. a -> Maybe a -> a
fromMaybe (String -> License
UnknownLicense ((Char -> Maybe Char) -> ShowS
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Char -> Maybe Char
mangle String
name)) (String -> Maybe License
forall a. Parsec a => String -> Maybe a
Instance of class: Parsec of the constraint type Parsec License
simpleParsec String
name)
mangle :: Char -> Maybe Char
mangle Char
c
| Char -> Bool
isAlphaNum Char
c = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
c
| Bool
otherwise = Maybe Char
forall {a}. Maybe a
Nothing
instance Pretty License where
pretty :: License -> Doc
pretty (GPL Maybe Version
version) = String -> Doc
Disp.text String
"GPL" Doc -> Doc -> Doc
<<>> Maybe Version -> Doc
dispOptVersion Maybe Version
version
pretty (LGPL Maybe Version
version) = String -> Doc
Disp.text String
"LGPL" Doc -> Doc -> Doc
<<>> Maybe Version -> Doc
dispOptVersion Maybe Version
version
pretty (AGPL Maybe Version
version) = String -> Doc
Disp.text String
"AGPL" Doc -> Doc -> Doc
<<>> Maybe Version -> Doc
dispOptVersion Maybe Version
version
pretty (MPL Version
version) = String -> Doc
Disp.text String
"MPL" Doc -> Doc -> Doc
<<>> Version -> Doc
dispVersion Version
version
pretty (Apache Maybe Version
version) = String -> Doc
Disp.text String
"Apache" Doc -> Doc -> Doc
<<>> Maybe Version -> Doc
dispOptVersion Maybe Version
version
pretty (UnknownLicense String
other) = String -> Doc
Disp.text String
other
pretty License
other = String -> Doc
Disp.text (License -> String
forall a. Show a => a -> String
Instance of class: Show of the constraint type Show License
show License
other)
instance Parsec License where
parsec :: m License
parsec = do
String
name <- (Char -> Bool) -> m String
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m String
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.munch1 Char -> Bool
isAlphaNum
Maybe Version
version <- m Version -> m (Maybe Version)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.optional (Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
P.char Char
'-' m Char -> m Version -> m Version
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
External instance of the constraint type forall (f :: * -> *). Alternative f => Applicative f
External instance of the constraint type forall (m :: * -> *). Parsing m => Alternative m
External instance of the constraint type forall (m :: * -> *). CharParsing m => Parsing m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => CharParsing m
Evidence bound by a type signature of the constraint type CabalParsing m
*> m Version
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
Evidence bound by a type signature of the constraint type CabalParsing m
External instance of the constraint type Parsec Version
parsec)
License -> m License
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall (m :: * -> *). MonadPlus m => Monad m
External instance of the constraint type forall (m :: * -> *). CabalParsing m => MonadPlus m
Evidence bound by a type signature of the constraint type CabalParsing m
return (License -> m License) -> License -> m License
forall a b. (a -> b) -> a -> b
$! case (String
name, Maybe Version
version :: Maybe Version) of
(String
"GPL", Maybe Version
_ ) -> Maybe Version -> License
GPL Maybe Version
version
(String
"LGPL", Maybe Version
_ ) -> Maybe Version -> License
LGPL Maybe Version
version
(String
"AGPL", Maybe Version
_ ) -> Maybe Version -> License
AGPL Maybe Version
version
(String
"BSD2", Maybe Version
Nothing) -> License
BSD2
(String
"BSD3", Maybe Version
Nothing) -> License
BSD3
(String
"BSD4", Maybe Version
Nothing) -> License
BSD4
(String
"ISC", Maybe Version
Nothing) -> License
ISC
(String
"MIT", Maybe Version
Nothing) -> License
MIT
(String
"MPL", Just Version
version') -> Version -> License
MPL Version
version'
(String
"Apache", Maybe Version
_ ) -> Maybe Version -> License
Apache Maybe Version
version
(String
"PublicDomain", Maybe Version
Nothing) -> License
PublicDomain
(String
"AllRightsReserved", Maybe Version
Nothing) -> License
AllRightsReserved
(String
"OtherLicense", Maybe Version
Nothing) -> License
OtherLicense
(String, Maybe Version)
_ -> String -> License
UnknownLicense (String -> License) -> String -> License
forall a b. (a -> b) -> a -> b
$ String
name String -> ShowS
forall a. [a] -> [a] -> [a]
++
String -> (Version -> String) -> Maybe Version -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" ((Char
'-'Char -> ShowS
forall a. a -> [a] -> [a]
:) ShowS -> (Version -> String) -> Version -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> String
forall a. Pretty a => a -> String
External instance of the constraint type Pretty Version
prettyShow) Maybe Version
version
dispOptVersion :: Maybe Version -> Disp.Doc
dispOptVersion :: Maybe Version -> Doc
dispOptVersion Maybe Version
Nothing = Doc
Disp.empty
dispOptVersion (Just Version
v) = Version -> Doc
dispVersion Version
v
dispVersion :: Version -> Disp.Doc
dispVersion :: Version -> Doc
dispVersion Version
v = Char -> Doc
Disp.char Char
'-' Doc -> Doc -> Doc
<<>> Version -> Doc
forall a. Pretty a => a -> Doc
External instance of the constraint type Pretty Version
pretty Version
v