spdx-1: SPDX license expression language, Extras

Safe HaskellNone
LanguageHaskell98

Distribution.SPDX.Extra

Contents

Description

 
Synopsis

Types

We don't export the constructors, as they change with Cabal version.

data License #

Declared license. See section 3.15 of SPDX Specification 2.1

Note: the NOASSERTION case is omitted.

Old License can be migrated using following rules:

  • AllRightsReserved and UnspecifiedLicense to NONE. No license specified which legally defaults to All Rights Reserved. The package may not be legally modified or redistributed by anyone but the rightsholder.
  • OtherLicense can be converted to LicenseRef pointing to the file in the package.
  • UnknownLicense i.e. other licenses of the form name-x.y, should be covered by SPDX license list, otherwise use LicenseRef.
  • PublicDomain isn't covered. Consider using CC0. See https://wiki.spdx.org/view/Legal_Team/Decisions/Dealing_with_Public_Domain_within_SPDX_Files for more information.
Instances
Eq License 
Instance details

Defined in Distribution.SPDX.License

Methods

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

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

Data License 
Instance details

Defined in Distribution.SPDX.License

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 
Instance details

Defined in Distribution.SPDX.License

Read License 
Instance details

Defined in Distribution.SPDX.License

Show License 
Instance details

Defined in Distribution.SPDX.License

Generic License 
Instance details

Defined in Distribution.SPDX.License

Associated Types

type Rep License :: * -> * #

Methods

from :: License -> Rep License x #

to :: Rep License x -> License #

Parsec License
>>> eitherParsec "BSD-3-Clause AND MIT" :: Either String License
Right (License (EAnd (ELicense (ELicenseId BSD_3_Clause) Nothing) (ELicense (ELicenseId MIT) Nothing)))
>>> eitherParsec "NONE" :: Either String License
Right NONE
Instance details

Defined in Distribution.SPDX.License

Methods

parsec :: CabalParsing m => m License #

Pretty License 
Instance details

Defined in Distribution.SPDX.License

Methods

pretty :: License -> Doc #

NFData License 
Instance details

Defined in Distribution.SPDX.License

Methods

rnf :: License -> () #

Binary License 
Instance details

Defined in Distribution.SPDX.License

Methods

put :: License -> Put #

get :: Get License #

putList :: [License] -> Put #

type Rep License 
Instance details

Defined in Distribution.SPDX.License

type Rep License = D1 (MetaData "License" "Distribution.SPDX.License" "Cabal-2.4.0.1-6VMdF6KlH8vJ0qvAHqwzor" False) (C1 (MetaCons "NONE" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "License" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LicenseExpression)))

data LicenseExpression #

SPDX License Expression.

idstring              = 1*(ALPHA / DIGIT / "-" / "." )
license id            = <short form license identifier inAppendix I.1>
license exception id  = <short form license exception identifier inAppendix I.2>
license ref           = ["DocumentRef-"1*(idstring)":"]"LicenseRef-"1*(idstring)

simple expression     = license id / license id"+" / license ref

compound expression   = 1*1(simple expression /
                        simple expression "WITH" license exception id /
                        compound expression "AND" compound expression /
                        compound expression "OR" compound expression ) /
                        "(" compound expression ")" )

license expression    = 1*1(simple expression / compound expression)
Instances
Eq LicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Data LicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Methods

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

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

toConstr :: LicenseExpression -> Constr #

dataTypeOf :: LicenseExpression -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Read LicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Show LicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Generic LicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Associated Types

type Rep LicenseExpression :: * -> * #

Parsec LicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Pretty LicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

NFData LicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Methods

rnf :: LicenseExpression -> () #

Binary LicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

type Rep LicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

data SimpleLicenseExpression #

Simple License Expressions.

Instances
Eq SimpleLicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Data SimpleLicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Methods

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

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

toConstr :: SimpleLicenseExpression -> Constr #

dataTypeOf :: SimpleLicenseExpression -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SimpleLicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Read SimpleLicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Show SimpleLicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Generic SimpleLicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Associated Types

type Rep SimpleLicenseExpression :: * -> * #

Parsec SimpleLicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Pretty SimpleLicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

NFData SimpleLicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Methods

rnf :: SimpleLicenseExpression -> () #

Binary SimpleLicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

type Rep SimpleLicenseExpression 
Instance details

Defined in Distribution.SPDX.LicenseExpression

data LicenseId #

SPDX License identifier

Instances
Bounded LicenseId 
Instance details

Defined in Distribution.SPDX.LicenseId

Enum LicenseId 
Instance details

Defined in Distribution.SPDX.LicenseId

Eq LicenseId 
Instance details

Defined in Distribution.SPDX.LicenseId

Data LicenseId 
Instance details

Defined in Distribution.SPDX.LicenseId

Methods

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

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

toConstr :: LicenseId -> Constr #

dataTypeOf :: LicenseId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LicenseId 
Instance details

Defined in Distribution.SPDX.LicenseId

Read LicenseId 
Instance details

Defined in Distribution.SPDX.LicenseId

Show LicenseId 
Instance details

Defined in Distribution.SPDX.LicenseId

Generic LicenseId 
Instance details

Defined in Distribution.SPDX.LicenseId

Associated Types

type Rep LicenseId :: * -> * #

Parsec LicenseId
>>> eitherParsec "BSD-3-Clause" :: Either String LicenseId
Right BSD_3_Clause
>>> eitherParsec "BSD3" :: Either String LicenseId
Left "...Unknown SPDX license identifier: 'BSD3' Do you mean BSD-3-Clause?"
Instance details

Defined in Distribution.SPDX.LicenseId

Methods

parsec :: CabalParsing m => m LicenseId #

Pretty LicenseId 
Instance details

Defined in Distribution.SPDX.LicenseId

Methods

pretty :: LicenseId -> Doc #

NFData LicenseId 
Instance details

Defined in Distribution.SPDX.LicenseId

Methods

rnf :: LicenseId -> () #

Binary LicenseId 
Instance details

Defined in Distribution.SPDX.LicenseId

type Rep LicenseId 
Instance details

Defined in Distribution.SPDX.LicenseId

type Rep LicenseId = D1 (MetaData "LicenseId" "Distribution.SPDX.LicenseId" "Cabal-2.4.0.1-6VMdF6KlH8vJ0qvAHqwzor" False) ((((((((C1 (MetaCons "NullBSD" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "AAL" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Abstyles" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Adobe_2006" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Adobe_Glyph" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "ADSL" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "AFL_1_1" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "AFL_1_2" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "AFL_2_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "AFL_2_1" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "AFL_3_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Afmparse" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "AGPL_1_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "AGPL_1_0_only" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "AGPL_1_0_or_later" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "AGPL_3_0_only" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "AGPL_3_0_or_later" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Aladdin" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "AMDPLPA" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "AML" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "AMPAS" PrefixI False) (U1 :: * -> *)))))) :+: ((((C1 (MetaCons "ANTLR_PD" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Apache_1_0" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Apache_1_1" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Apache_2_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "APAFML" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "APL_1_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "APSL_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "APSL_1_1" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "APSL_1_2" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "APSL_2_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Artistic_1_0_cl8" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "Artistic_1_0_Perl" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Artistic_1_0" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Artistic_2_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Bahyph" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Barr" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "Beerware" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "BitTorrent_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "BitTorrent_1_1" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "Borceux" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "BSD_1_Clause" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "BSD_2_Clause_FreeBSD" PrefixI False) (U1 :: * -> *))))))) :+: (((((C1 (MetaCons "BSD_2_Clause_NetBSD" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "BSD_2_Clause_Patent" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "BSD_2_Clause" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "BSD_3_Clause_Attribution" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "BSD_3_Clause_Clear" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "BSD_3_Clause_LBNL" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "BSD_3_Clause_No_Nuclear_License_2014" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "BSD_3_Clause_No_Nuclear_License" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "BSD_3_Clause_No_Nuclear_Warranty" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "BSD_3_Clause" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "BSD_4_Clause_UC" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "BSD_4_Clause" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "BSD_Protection" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "BSD_Source_Code" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "BSL_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Bzip2_1_0_5" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "Bzip2_1_0_6" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Caldera" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CATOSL_1_1" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "CC_BY_1_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "CC_BY_2_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CC_BY_2_5" PrefixI False) (U1 :: * -> *)))))) :+: ((((C1 (MetaCons "CC_BY_3_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CC_BY_4_0" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "CC_BY_NC_1_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "CC_BY_NC_2_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CC_BY_NC_2_5" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "CC_BY_NC_3_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "CC_BY_NC_4_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CC_BY_NC_ND_1_0" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "CC_BY_NC_ND_2_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "CC_BY_NC_ND_2_5" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CC_BY_NC_ND_3_0" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "CC_BY_NC_ND_4_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CC_BY_NC_SA_1_0" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "CC_BY_NC_SA_2_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "CC_BY_NC_SA_2_5" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CC_BY_NC_SA_3_0" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "CC_BY_NC_SA_4_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "CC_BY_ND_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CC_BY_ND_2_0" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "CC_BY_ND_2_5" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "CC_BY_ND_3_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CC_BY_ND_4_0" PrefixI False) (U1 :: * -> *)))))))) :+: ((((((C1 (MetaCons "CC_BY_SA_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CC_BY_SA_2_0" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "CC_BY_SA_2_5" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "CC_BY_SA_3_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CC_BY_SA_4_0" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "CC0_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CDDL_1_0" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "CDDL_1_1" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "CDLA_Permissive_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CDLA_Sharing_1_0" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "CECILL_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CECILL_1_1" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "CECILL_2_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "CECILL_2_1" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CECILL_B" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "CECILL_C" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "ClArtistic" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CNRI_Jython" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "CNRI_Python_GPL_Compatible" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "CNRI_Python" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Condor_1_1" PrefixI False) (U1 :: * -> *)))))) :+: ((((C1 (MetaCons "CPAL_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CPL_1_0" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "CPOL_1_02" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Crossword" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CrystalStacker" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "CUA_OPL_1_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Cube" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Curl" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "D_FSL_1_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Diffmark" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "DOC" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "Dotseqn" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "DSDP" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Dvipdfm" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "ECL_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ECL_2_0" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "EFL_1_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "EFL_2_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "EGenix" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "Entessa" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "EPL_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "EPL_2_0" PrefixI False) (U1 :: * -> *))))))) :+: (((((C1 (MetaCons "ErlPL_1_1" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "EUDatagrid" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "EUPL_1_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "EUPL_1_1" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "EUPL_1_2" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "Eurosym" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Fair" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Frameworx_1_0" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "FreeImage" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "FSFAP" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "FSFUL" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "FSFULLR" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "FTL" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "GFDL_1_1_only" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "GFDL_1_1_or_later" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "GFDL_1_2_only" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "GFDL_1_2_or_later" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "GFDL_1_3_only" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "GFDL_1_3_or_later" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "Giftware" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "GL2PS" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Glide" PrefixI False) (U1 :: * -> *)))))) :+: ((((C1 (MetaCons "Glulxe" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Gnuplot" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "GPL_1_0_only" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "GPL_1_0_or_later" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "GPL_2_0_only" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "GPL_2_0_or_later" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "GPL_3_0_only" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "GPL_3_0_or_later" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "GSOAP_1_3b" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "HaskellReport" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "HPND" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "IBM_pibs" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ICU" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "IJG" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "ImageMagick" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "IMatix" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "Imlib2" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Info_ZIP" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Intel_ACPI" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "Intel" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Interbase_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "IPA" PrefixI False) (U1 :: * -> *))))))))) :+: (((((((C1 (MetaCons "IPL_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ISC" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "JasPer_2_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "JSON" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LAL_1_2" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "LAL_1_3" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Latex2e" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Leptonica" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "LGPL_2_0_only" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LGPL_2_0_or_later" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "LGPL_2_1_only" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LGPL_2_1_or_later" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "LGPL_3_0_only" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "LGPL_3_0_or_later" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LGPLLR" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "Libpng" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Libtiff" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LiLiQ_P_1_1" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "LiLiQ_R_1_1" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "LiLiQ_Rplus_1_1" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Linux_OpenIB" PrefixI False) (U1 :: * -> *)))))) :+: ((((C1 (MetaCons "LPL_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LPL_1_02" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "LPPL_1_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "LPPL_1_1" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LPPL_1_2" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "LPPL_1_3a" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "LPPL_1_3c" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MakeIndex" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "MirOS" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "MIT_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MIT_advertising" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "MIT_CMU" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MIT_enna" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "MIT_feh" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "MIT" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MITNFA" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "Motosoto" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Mpich2" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MPL_1_0" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "MPL_1_1" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "MPL_2_0_no_copyleft_exception" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MPL_2_0" PrefixI False) (U1 :: * -> *))))))) :+: (((((C1 (MetaCons "MS_PL" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MS_RL" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "MTLL" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Multics" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Mup" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "NASA_1_3" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Naumen" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NBPL_1_0" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "NCSA" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Net_SNMP" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NetCDF" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "Newsletr" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NGPL" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "NLOD_1_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "NLPL" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Nokia" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "NOSL" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Noweb" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NPL_1_0" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "NPL_1_1" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "NPOSL_3_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NRL" PrefixI False) (U1 :: * -> *)))))) :+: ((((C1 (MetaCons "NTP" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OCCT_PL" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OCLC_2_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "ODbL_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ODC_By_1_0" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "OFL_1_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OFL_1_1" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OGTSL" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "OLDAP_1_1" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OLDAP_1_2" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OLDAP_1_3" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "OLDAP_1_4" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OLDAP_2_0_1" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OLDAP_2_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OLDAP_2_1" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OLDAP_2_2_1" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "OLDAP_2_2_2" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OLDAP_2_2" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OLDAP_2_3" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "OLDAP_2_4" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OLDAP_2_5" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OLDAP_2_6" PrefixI False) (U1 :: * -> *)))))))) :+: ((((((C1 (MetaCons "OLDAP_2_7" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OLDAP_2_8" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OML" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OpenSSL" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OPL_1_0" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "OSET_PL_2_1" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OSL_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OSL_1_1" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "OSL_2_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OSL_2_1" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OSL_3_0" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "PDDL_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "PHP_3_0" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "PHP_3_01" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Plexus" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "PostgreSQL" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "Psfrag" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Psutils" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Python_2_0" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "Qhull" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "QPL_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Rdisc" PrefixI False) (U1 :: * -> *)))))) :+: ((((C1 (MetaCons "RHeCos_1_1" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "RPL_1_1" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "RPL_1_5" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "RPSL_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "RSA_MD" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "RSCPL" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Ruby" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SAX_PD" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "Saxpath" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "SCEA" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Sendmail" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "SGI_B_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SGI_B_1_1" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "SGI_B_2_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "SimPL_2_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SISSL_1_2" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "SISSL" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Sleepycat" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SMLNJ" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "SMPPL" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "SNIA" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Spencer_86" PrefixI False) (U1 :: * -> *))))))) :+: (((((C1 (MetaCons "Spencer_94" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Spencer_99" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "SPL_1_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "SugarCRM_1_1_3" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SWL" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "TCL" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "TCP_wrappers" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "TMate" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "TORQUE_1_1" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "TOSL" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "TU_Berlin_1_0" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "TU_Berlin_2_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Unicode_DFS_2015" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Unicode_DFS_2016" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Unicode_TOU" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Unlicense" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "UPL_1_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Vim" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "VOSTROM" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "VSL_1_0" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "W3C_19980720" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "W3C_20150513" PrefixI False) (U1 :: * -> *)))))) :+: ((((C1 (MetaCons "W3C" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Watcom_1_0" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Wsuipa" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "WTFPL" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "X11" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "Xerox" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "XFree86_1_1" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Xinetd" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "Xnet" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Xpp" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "XSkat" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "YPL_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "YPL_1_1" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Zed" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Zend_2_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Zimbra_1_3" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "Zimbra_1_4" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Zlib_acknowledgement" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Zlib" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "ZPL_1_1" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "ZPL_2_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ZPL_2_1" PrefixI False) (U1 :: * -> *))))))))))

data LicenseExceptionId #

SPDX License identifier

Instances
Bounded LicenseExceptionId 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

Enum LicenseExceptionId 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

Eq LicenseExceptionId 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

Data LicenseExceptionId 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

Methods

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

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

toConstr :: LicenseExceptionId -> Constr #

dataTypeOf :: LicenseExceptionId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LicenseExceptionId 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

Read LicenseExceptionId 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

Show LicenseExceptionId 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

Generic LicenseExceptionId 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

Associated Types

type Rep LicenseExceptionId :: * -> * #

Parsec LicenseExceptionId 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

Pretty LicenseExceptionId 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

NFData LicenseExceptionId 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

Methods

rnf :: LicenseExceptionId -> () #

Binary LicenseExceptionId 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

type Rep LicenseExceptionId 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

type Rep LicenseExceptionId = D1 (MetaData "LicenseExceptionId" "Distribution.SPDX.LicenseExceptionId" "Cabal-2.4.0.1-6VMdF6KlH8vJ0qvAHqwzor" False) (((((C1 (MetaCons "DS389_exception" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Autoconf_exception_2_0" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Autoconf_exception_3_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Bison_exception_2_2" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "Bootloader_exception" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Classpath_exception_2_0" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "CLISP_exception_2_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "DigiRule_FOSS_exception" PrefixI False) (U1 :: * -> *)))) :+: (((C1 (MetaCons "ECos_exception_2_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Fawkes_Runtime_exception" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "FLTK_exception" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Font_exception_2_0" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "Freertos_exception_2_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "GCC_exception_2_0" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "GCC_exception_3_1" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Gnu_javamail_exception" PrefixI False) (U1 :: * -> *))))) :+: ((((C1 (MetaCons "I2p_gpl_java_exception" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Libtool_exception" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Linux_syscall_note" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LLVM_exception" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "LZMA_exception" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Mif_exception" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Nokia_Qt_exception_1_1" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OCCT_exception_1_0" PrefixI False) (U1 :: * -> *)))) :+: (((C1 (MetaCons "OpenJDK_assembly_exception_1_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Openvpn_openssl_exception" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "PS_or_PDF_font_exception_20170817" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Qt_GPL_exception_1_0" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "Qt_LGPL_exception_1_1" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Qwt_exception_1_0" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "U_boot_exception_2_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "WxWindows_exception_3_1" PrefixI False) (U1 :: * -> *))))))

Logic

satisfies Source #

Arguments

:: License

package license

-> License

license policy

-> Bool 
⟦ satisfies a b ⟧ ≡ a ≥ b ≡ a ∧ b = b
>>> unsafeParseExpr "GPL-3.0-only" `satisfies` unsafeParseExpr "ISC AND MIT"
False
>>> unsafeParseExpr "Zlib" `satisfies` unsafeParseExpr "ISC AND MIT AND Zlib"
True
>>> unsafeParseExpr "(MIT OR GPL-2.0-only)" `satisfies` unsafeParseExpr "(ISC AND MIT)"
True
>>> unsafeParseExpr "(MIT AND GPL-2.0-only)" `satisfies` unsafeParseExpr "(MIT AND GPL-2.0-only)"
True
>>> unsafeParseExpr "(MIT AND GPL-2.0-only)" `satisfies` unsafeParseExpr "(ISC AND GPL-2.0-only)"
False

equivalent :: License -> License -> Bool Source #

Check wheather two LicenseExpression are equivalent.

>>> unsafeParseExpr "(MIT AND GPL-2.0-only)" `equivalent` unsafeParseExpr "(GPL-2.0-only AND MIT)"
True
>>> unsafeParseExpr "MIT" `equivalent` unsafeParseExpr "MIT OR BSD-3-Clause"
False