Cabal-2.4.0.1: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.SPDX

Contents

Description

This module implements SPDX specification version 2.1 with a version 3.0 license list.

Specification is available on https://spdx.org/specifications

Synopsis

License

data License Source #

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.

Constructors

NONE

if the package contains no license information whatsoever; or

License LicenseExpression

A valid SPDX License Expression as defined in Appendix IV.

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

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

toConstr :: License -> Constr Source #

dataTypeOf :: License -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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 :: Type -> Type Source #

Binary License # 
Instance details

Defined in Distribution.SPDX.License

NFData License # 
Instance details

Defined in Distribution.SPDX.License

Methods

rnf :: License -> () Source #

Pretty License # 
Instance details

Defined in Distribution.SPDX.License

Methods

pretty :: License -> Doc Source #

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

Newtype SpecLicense (Either License License) # 
Instance details

Defined in Distribution.Parsec.Newtypes

type Rep License # 
Instance details

Defined in Distribution.SPDX.License

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

License expression

data LicenseExpression Source #

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

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

toConstr :: LicenseExpression -> Constr Source #

dataTypeOf :: LicenseExpression -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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 :: Type -> Type Source #

Binary LicenseExpression # 
Instance details

Defined in Distribution.SPDX.LicenseExpression

NFData LicenseExpression # 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Methods

rnf :: LicenseExpression -> () Source #

Pretty LicenseExpression # 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Parsec LicenseExpression # 
Instance details

Defined in Distribution.SPDX.LicenseExpression

type Rep LicenseExpression # 
Instance details

Defined in Distribution.SPDX.LicenseExpression

data SimpleLicenseExpression Source #

Simple License Expressions.

Constructors

ELicenseId LicenseId

An SPDX License List Short Form Identifier. For example: GPL-2.0-only

ELicenseIdPlus LicenseId

An SPDX License List Short Form Identifier with a unary"+" operator suffix to represent the current version of the license or any later version. For example: GPL-2.0+

ELicenseRef LicenseRef

A SPDX user defined license reference: For example: LicenseRef-23, LicenseRef-MIT-Style-1, or DocumentRef-spdx-tool-1.2:LicenseRef-MIT-Style-2

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

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

toConstr :: SimpleLicenseExpression -> Constr Source #

dataTypeOf :: SimpleLicenseExpression -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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 :: Type -> Type Source #

Binary SimpleLicenseExpression # 
Instance details

Defined in Distribution.SPDX.LicenseExpression

NFData SimpleLicenseExpression # 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Pretty SimpleLicenseExpression # 
Instance details

Defined in Distribution.SPDX.LicenseExpression

Parsec SimpleLicenseExpression # 
Instance details

Defined in Distribution.SPDX.LicenseExpression

type Rep SimpleLicenseExpression # 
Instance details

Defined in Distribution.SPDX.LicenseExpression

License identifier

data LicenseId Source #

SPDX License identifier

Constructors

NullBSD

0BSD, BSD Zero Clause License

AAL

AAL, Attribution Assurance License

Abstyles

Abstyles, Abstyles License

Adobe_2006

Adobe-2006, Adobe Systems Incorporated Source Code License Agreement

Adobe_Glyph

Adobe-Glyph, Adobe Glyph List License

ADSL

ADSL, Amazon Digital Services License

AFL_1_1

AFL-1.1, Academic Free License v1.1

AFL_1_2

AFL-1.2, Academic Free License v1.2

AFL_2_0

AFL-2.0, Academic Free License v2.0

AFL_2_1

AFL-2.1, Academic Free License v2.1

AFL_3_0

AFL-3.0, Academic Free License v3.0

Afmparse

Afmparse, Afmparse License

AGPL_1_0

AGPL-1.0, Affero General Public License v1.0, SPDX License List 3.0

AGPL_1_0_only

AGPL-1.0-only, Affero General Public License v1.0 only, SPDX License List 3.2

AGPL_1_0_or_later

AGPL-1.0-or-later, Affero General Public License v1.0 or later, SPDX License List 3.2

AGPL_3_0_only

AGPL-3.0-only, GNU Affero General Public License v3.0 only

AGPL_3_0_or_later

AGPL-3.0-or-later, GNU Affero General Public License v3.0 or later

Aladdin

Aladdin, Aladdin Free Public License

AMDPLPA

AMDPLPA, AMD's plpa_map.c License

AML

AML, Apple MIT License

AMPAS

AMPAS, Academy of Motion Picture Arts and Sciences BSD

ANTLR_PD

ANTLR-PD, ANTLR Software Rights Notice

Apache_1_0

Apache-1.0, Apache License 1.0

Apache_1_1

Apache-1.1, Apache License 1.1

Apache_2_0

Apache-2.0, Apache License 2.0

APAFML

APAFML, Adobe Postscript AFM License

APL_1_0

APL-1.0, Adaptive Public License 1.0

APSL_1_0

APSL-1.0, Apple Public Source License 1.0

APSL_1_1

APSL-1.1, Apple Public Source License 1.1

APSL_1_2

APSL-1.2, Apple Public Source License 1.2

APSL_2_0

APSL-2.0, Apple Public Source License 2.0

Artistic_1_0_cl8

Artistic-1.0-cl8, Artistic License 1.0 w/clause 8

Artistic_1_0_Perl

Artistic-1.0-Perl, Artistic License 1.0 (Perl)

Artistic_1_0

Artistic-1.0, Artistic License 1.0

Artistic_2_0

Artistic-2.0, Artistic License 2.0

Bahyph

Bahyph, Bahyph License

Barr

Barr, Barr License

Beerware

Beerware, Beerware License

BitTorrent_1_0

BitTorrent-1.0, BitTorrent Open Source License v1.0

BitTorrent_1_1

BitTorrent-1.1, BitTorrent Open Source License v1.1

Borceux

Borceux, Borceux license

BSD_1_Clause

BSD-1-Clause, BSD 1-Clause License

BSD_2_Clause_FreeBSD

BSD-2-Clause-FreeBSD, BSD 2-Clause FreeBSD License

BSD_2_Clause_NetBSD

BSD-2-Clause-NetBSD, BSD 2-Clause NetBSD License

BSD_2_Clause_Patent

BSD-2-Clause-Patent, BSD-2-Clause Plus Patent License

BSD_2_Clause

BSD-2-Clause, BSD 2-Clause Simplified License

BSD_3_Clause_Attribution

BSD-3-Clause-Attribution, BSD with attribution

BSD_3_Clause_Clear

BSD-3-Clause-Clear, BSD 3-Clause Clear License

BSD_3_Clause_LBNL

BSD-3-Clause-LBNL, Lawrence Berkeley National Labs BSD variant license

BSD_3_Clause_No_Nuclear_License_2014

BSD-3-Clause-No-Nuclear-License-2014, BSD 3-Clause No Nuclear License 2014

BSD_3_Clause_No_Nuclear_License

BSD-3-Clause-No-Nuclear-License, BSD 3-Clause No Nuclear License

BSD_3_Clause_No_Nuclear_Warranty

BSD-3-Clause-No-Nuclear-Warranty, BSD 3-Clause No Nuclear Warranty

BSD_3_Clause

BSD-3-Clause, BSD 3-Clause New or Revised License

BSD_4_Clause_UC

BSD-4-Clause-UC, BSD-4-Clause (University of California-Specific)

BSD_4_Clause

BSD-4-Clause, BSD 4-Clause Original or Old License

BSD_Protection

BSD-Protection, BSD Protection License

BSD_Source_Code

BSD-Source-Code, BSD Source Code Attribution

BSL_1_0

BSL-1.0, Boost Software License 1.0

Bzip2_1_0_5

bzip2-1.0.5, bzip2 and libbzip2 License v1.0.5

Bzip2_1_0_6

bzip2-1.0.6, bzip2 and libbzip2 License v1.0.6

Caldera

Caldera, Caldera License

CATOSL_1_1

CATOSL-1.1, Computer Associates Trusted Open Source License 1.1

CC_BY_1_0

CC-BY-1.0, Creative Commons Attribution 1.0 Generic

CC_BY_2_0

CC-BY-2.0, Creative Commons Attribution 2.0 Generic

CC_BY_2_5

CC-BY-2.5, Creative Commons Attribution 2.5 Generic

CC_BY_3_0

CC-BY-3.0, Creative Commons Attribution 3.0 Unported

CC_BY_4_0

CC-BY-4.0, Creative Commons Attribution 4.0 International

CC_BY_NC_1_0

CC-BY-NC-1.0, Creative Commons Attribution Non Commercial 1.0 Generic

CC_BY_NC_2_0

CC-BY-NC-2.0, Creative Commons Attribution Non Commercial 2.0 Generic

CC_BY_NC_2_5

CC-BY-NC-2.5, Creative Commons Attribution Non Commercial 2.5 Generic

CC_BY_NC_3_0

CC-BY-NC-3.0, Creative Commons Attribution Non Commercial 3.0 Unported

CC_BY_NC_4_0

CC-BY-NC-4.0, Creative Commons Attribution Non Commercial 4.0 International

CC_BY_NC_ND_1_0

CC-BY-NC-ND-1.0, Creative Commons Attribution Non Commercial No Derivatives 1.0 Generic

CC_BY_NC_ND_2_0

CC-BY-NC-ND-2.0, Creative Commons Attribution Non Commercial No Derivatives 2.0 Generic

CC_BY_NC_ND_2_5

CC-BY-NC-ND-2.5, Creative Commons Attribution Non Commercial No Derivatives 2.5 Generic

CC_BY_NC_ND_3_0

CC-BY-NC-ND-3.0, Creative Commons Attribution Non Commercial No Derivatives 3.0 Unported

CC_BY_NC_ND_4_0

CC-BY-NC-ND-4.0, Creative Commons Attribution Non Commercial No Derivatives 4.0 International

CC_BY_NC_SA_1_0

CC-BY-NC-SA-1.0, Creative Commons Attribution Non Commercial Share Alike 1.0 Generic

CC_BY_NC_SA_2_0

CC-BY-NC-SA-2.0, Creative Commons Attribution Non Commercial Share Alike 2.0 Generic

CC_BY_NC_SA_2_5

CC-BY-NC-SA-2.5, Creative Commons Attribution Non Commercial Share Alike 2.5 Generic

CC_BY_NC_SA_3_0

CC-BY-NC-SA-3.0, Creative Commons Attribution Non Commercial Share Alike 3.0 Unported

CC_BY_NC_SA_4_0

CC-BY-NC-SA-4.0, Creative Commons Attribution Non Commercial Share Alike 4.0 International

CC_BY_ND_1_0

CC-BY-ND-1.0, Creative Commons Attribution No Derivatives 1.0 Generic

CC_BY_ND_2_0

CC-BY-ND-2.0, Creative Commons Attribution No Derivatives 2.0 Generic

CC_BY_ND_2_5

CC-BY-ND-2.5, Creative Commons Attribution No Derivatives 2.5 Generic

CC_BY_ND_3_0

CC-BY-ND-3.0, Creative Commons Attribution No Derivatives 3.0 Unported

CC_BY_ND_4_0

CC-BY-ND-4.0, Creative Commons Attribution No Derivatives 4.0 International

CC_BY_SA_1_0

CC-BY-SA-1.0, Creative Commons Attribution Share Alike 1.0 Generic

CC_BY_SA_2_0

CC-BY-SA-2.0, Creative Commons Attribution Share Alike 2.0 Generic

CC_BY_SA_2_5

CC-BY-SA-2.5, Creative Commons Attribution Share Alike 2.5 Generic

CC_BY_SA_3_0

CC-BY-SA-3.0, Creative Commons Attribution Share Alike 3.0 Unported

CC_BY_SA_4_0

CC-BY-SA-4.0, Creative Commons Attribution Share Alike 4.0 International

CC0_1_0

CC0-1.0, Creative Commons Zero v1.0 Universal

CDDL_1_0

CDDL-1.0, Common Development and Distribution License 1.0

CDDL_1_1

CDDL-1.1, Common Development and Distribution License 1.1

CDLA_Permissive_1_0

CDLA-Permissive-1.0, Community Data License Agreement Permissive 1.0

CDLA_Sharing_1_0

CDLA-Sharing-1.0, Community Data License Agreement Sharing 1.0

CECILL_1_0

CECILL-1.0, CeCILL Free Software License Agreement v1.0

CECILL_1_1

CECILL-1.1, CeCILL Free Software License Agreement v1.1

CECILL_2_0

CECILL-2.0, CeCILL Free Software License Agreement v2.0

CECILL_2_1

CECILL-2.1, CeCILL Free Software License Agreement v2.1

CECILL_B

CECILL-B, CeCILL-B Free Software License Agreement

CECILL_C

CECILL-C, CeCILL-C Free Software License Agreement

ClArtistic

ClArtistic, Clarified Artistic License

CNRI_Jython

CNRI-Jython, CNRI Jython License

CNRI_Python_GPL_Compatible

CNRI-Python-GPL-Compatible, CNRI Python Open Source GPL Compatible License Agreement

CNRI_Python

CNRI-Python, CNRI Python License

Condor_1_1

Condor-1.1, Condor Public License v1.1

CPAL_1_0

CPAL-1.0, Common Public Attribution License 1.0

CPL_1_0

CPL-1.0, Common Public License 1.0

CPOL_1_02

CPOL-1.02, Code Project Open License 1.02

Crossword

Crossword, Crossword License

CrystalStacker

CrystalStacker, CrystalStacker License

CUA_OPL_1_0

CUA-OPL-1.0, CUA Office Public License v1.0

Cube

Cube, Cube License

Curl

curl, curl License

D_FSL_1_0

D-FSL-1.0, Deutsche Freie Software Lizenz

Diffmark

diffmark, diffmark license

DOC

DOC, DOC License

Dotseqn

Dotseqn, Dotseqn License

DSDP

DSDP, DSDP License

Dvipdfm

dvipdfm, dvipdfm License

ECL_1_0

ECL-1.0, Educational Community License v1.0

ECL_2_0

ECL-2.0, Educational Community License v2.0

EFL_1_0

EFL-1.0, Eiffel Forum License v1.0

EFL_2_0

EFL-2.0, Eiffel Forum License v2.0

EGenix

eGenix, eGenix.com Public License 1.1.0

Entessa

Entessa, Entessa Public License v1.0

EPL_1_0

EPL-1.0, Eclipse Public License 1.0

EPL_2_0

EPL-2.0, Eclipse Public License 2.0

ErlPL_1_1

ErlPL-1.1, Erlang Public License v1.1

EUDatagrid

EUDatagrid, EU DataGrid Software License

EUPL_1_0

EUPL-1.0, European Union Public License 1.0

EUPL_1_1

EUPL-1.1, European Union Public License 1.1

EUPL_1_2

EUPL-1.2, European Union Public License 1.2

Eurosym

Eurosym, Eurosym License

Fair

Fair, Fair License

Frameworx_1_0

Frameworx-1.0, Frameworx Open License 1.0

FreeImage

FreeImage, FreeImage Public License v1.0

FSFAP

FSFAP, FSF All Permissive License

FSFUL

FSFUL, FSF Unlimited License

FSFULLR

FSFULLR, FSF Unlimited License (with License Retention)

FTL

FTL, Freetype Project License

GFDL_1_1_only

GFDL-1.1-only, GNU Free Documentation License v1.1 only

GFDL_1_1_or_later

GFDL-1.1-or-later, GNU Free Documentation License v1.1 or later

GFDL_1_2_only

GFDL-1.2-only, GNU Free Documentation License v1.2 only

GFDL_1_2_or_later

GFDL-1.2-or-later, GNU Free Documentation License v1.2 or later

GFDL_1_3_only

GFDL-1.3-only, GNU Free Documentation License v1.3 only

GFDL_1_3_or_later

GFDL-1.3-or-later, GNU Free Documentation License v1.3 or later

Giftware

Giftware, Giftware License

GL2PS

GL2PS, GL2PS License

Glide

Glide, 3dfx Glide License

Glulxe

Glulxe, Glulxe License

Gnuplot

gnuplot, gnuplot License

GPL_1_0_only

GPL-1.0-only, GNU General Public License v1.0 only

GPL_1_0_or_later

GPL-1.0-or-later, GNU General Public License v1.0 or later

GPL_2_0_only

GPL-2.0-only, GNU General Public License v2.0 only

GPL_2_0_or_later

GPL-2.0-or-later, GNU General Public License v2.0 or later

GPL_3_0_only

GPL-3.0-only, GNU General Public License v3.0 only

GPL_3_0_or_later

GPL-3.0-or-later, GNU General Public License v3.0 or later

GSOAP_1_3b

gSOAP-1.3b, gSOAP Public License v1.3b

HaskellReport

HaskellReport, Haskell Language Report License

HPND

HPND, Historical Permission Notice and Disclaimer

IBM_pibs

IBM-pibs, IBM PowerPC Initialization and Boot Software

ICU

ICU, ICU License

IJG

IJG, Independent JPEG Group License

ImageMagick

ImageMagick, ImageMagick License

IMatix

iMatix, iMatix Standard Function Library Agreement

Imlib2

Imlib2, Imlib2 License

Info_ZIP

Info-ZIP, Info-ZIP License

Intel_ACPI

Intel-ACPI, Intel ACPI Software License Agreement

Intel

Intel, Intel Open Source License

Interbase_1_0

Interbase-1.0, Interbase Public License v1.0

IPA

IPA, IPA Font License

IPL_1_0

IPL-1.0, IBM Public License v1.0

ISC

ISC, ISC License

JasPer_2_0

JasPer-2.0, JasPer License

JSON

JSON, JSON License

LAL_1_2

LAL-1.2, Licence Art Libre 1.2

LAL_1_3

LAL-1.3, Licence Art Libre 1.3

Latex2e

Latex2e, Latex2e License

Leptonica

Leptonica, Leptonica License

LGPL_2_0_only

LGPL-2.0-only, GNU Library General Public License v2 only

LGPL_2_0_or_later

LGPL-2.0-or-later, GNU Library General Public License v2 or later

LGPL_2_1_only

LGPL-2.1-only, GNU Lesser General Public License v2.1 only

LGPL_2_1_or_later

LGPL-2.1-or-later, GNU Lesser General Public License v2.1 or later

LGPL_3_0_only

LGPL-3.0-only, GNU Lesser General Public License v3.0 only

LGPL_3_0_or_later

LGPL-3.0-or-later, GNU Lesser General Public License v3.0 or later

LGPLLR

LGPLLR, Lesser General Public License For Linguistic Resources

Libpng

Libpng, libpng License

Libtiff

libtiff, libtiff License

LiLiQ_P_1_1

LiLiQ-P-1.1, Licence Libre du Québec – Permissive version 1.1

LiLiQ_R_1_1

LiLiQ-R-1.1, Licence Libre du Québec – Réciprocité version 1.1

LiLiQ_Rplus_1_1

LiLiQ-Rplus-1.1, Licence Libre du Québec – Réciprocité forte version 1.1

Linux_OpenIB

Linux-OpenIB, Linux Kernel Variant of OpenIB.org license, SPDX License List 3.2

LPL_1_0

LPL-1.0, Lucent Public License Version 1.0

LPL_1_02

LPL-1.02, Lucent Public License v1.02

LPPL_1_0

LPPL-1.0, LaTeX Project Public License v1.0

LPPL_1_1

LPPL-1.1, LaTeX Project Public License v1.1

LPPL_1_2

LPPL-1.2, LaTeX Project Public License v1.2

LPPL_1_3a

LPPL-1.3a, LaTeX Project Public License v1.3a

LPPL_1_3c

LPPL-1.3c, LaTeX Project Public License v1.3c

MakeIndex

MakeIndex, MakeIndex License

MirOS

MirOS, MirOS License

MIT_0

MIT-0, MIT No Attribution, SPDX License List 3.2

MIT_advertising

MIT-advertising, Enlightenment License (e16)

MIT_CMU

MIT-CMU, CMU License

MIT_enna

MIT-enna, enna License

MIT_feh

MIT-feh, feh License

MIT

MIT, MIT License

MITNFA

MITNFA, MIT +no-false-attribs license

Motosoto

Motosoto, Motosoto License

Mpich2

mpich2, mpich2 License

MPL_1_0

MPL-1.0, Mozilla Public License 1.0

MPL_1_1

MPL-1.1, Mozilla Public License 1.1

MPL_2_0_no_copyleft_exception

MPL-2.0-no-copyleft-exception, Mozilla Public License 2.0 (no copyleft exception)

MPL_2_0

MPL-2.0, Mozilla Public License 2.0

MS_PL

MS-PL, Microsoft Public License

MS_RL

MS-RL, Microsoft Reciprocal License

MTLL

MTLL, Matrix Template Library License

Multics

Multics, Multics License

Mup

Mup, Mup License

NASA_1_3

NASA-1.3, NASA Open Source Agreement 1.3

Naumen

Naumen, Naumen Public License

NBPL_1_0

NBPL-1.0, Net Boolean Public License v1

NCSA

NCSA, University of Illinois/NCSA Open Source License

Net_SNMP

Net-SNMP, Net-SNMP License

NetCDF

NetCDF, NetCDF license

Newsletr

Newsletr, Newsletr License

NGPL

NGPL, Nethack General Public License

NLOD_1_0

NLOD-1.0, Norwegian Licence for Open Government Data

NLPL

NLPL, No Limit Public License

Nokia

Nokia, Nokia Open Source License

NOSL

NOSL, Netizen Open Source License

Noweb

Noweb, Noweb License

NPL_1_0

NPL-1.0, Netscape Public License v1.0

NPL_1_1

NPL-1.1, Netscape Public License v1.1

NPOSL_3_0

NPOSL-3.0, Non-Profit Open Software License 3.0

NRL

NRL, NRL License

NTP

NTP, NTP License

OCCT_PL

OCCT-PL, Open CASCADE Technology Public License

OCLC_2_0

OCLC-2.0, OCLC Research Public License 2.0

ODbL_1_0

ODbL-1.0, ODC Open Database License v1.0

ODC_By_1_0

ODC-By-1.0, Open Data Commons Attribution License v1.0, SPDX License List 3.2

OFL_1_0

OFL-1.0, SIL Open Font License 1.0

OFL_1_1

OFL-1.1, SIL Open Font License 1.1

OGTSL

OGTSL, Open Group Test Suite License

OLDAP_1_1

OLDAP-1.1, Open LDAP Public License v1.1

OLDAP_1_2

OLDAP-1.2, Open LDAP Public License v1.2

OLDAP_1_3

OLDAP-1.3, Open LDAP Public License v1.3

OLDAP_1_4

OLDAP-1.4, Open LDAP Public License v1.4

OLDAP_2_0_1

OLDAP-2.0.1, Open LDAP Public License v2.0.1

OLDAP_2_0

OLDAP-2.0, Open LDAP Public License v2.0 (or possibly 2.0A and 2.0B)

OLDAP_2_1

OLDAP-2.1, Open LDAP Public License v2.1

OLDAP_2_2_1

OLDAP-2.2.1, Open LDAP Public License v2.2.1

OLDAP_2_2_2

OLDAP-2.2.2, Open LDAP Public License 2.2.2

OLDAP_2_2

OLDAP-2.2, Open LDAP Public License v2.2

OLDAP_2_3

OLDAP-2.3, Open LDAP Public License v2.3

OLDAP_2_4

OLDAP-2.4, Open LDAP Public License v2.4

OLDAP_2_5

OLDAP-2.5, Open LDAP Public License v2.5

OLDAP_2_6

OLDAP-2.6, Open LDAP Public License v2.6

OLDAP_2_7

OLDAP-2.7, Open LDAP Public License v2.7

OLDAP_2_8

OLDAP-2.8, Open LDAP Public License v2.8

OML

OML, Open Market License

OpenSSL

OpenSSL, OpenSSL License

OPL_1_0

OPL-1.0, Open Public License v1.0

OSET_PL_2_1

OSET-PL-2.1, OSET Public License version 2.1

OSL_1_0

OSL-1.0, Open Software License 1.0

OSL_1_1

OSL-1.1, Open Software License 1.1

OSL_2_0

OSL-2.0, Open Software License 2.0

OSL_2_1

OSL-2.1, Open Software License 2.1

OSL_3_0

OSL-3.0, Open Software License 3.0

PDDL_1_0

PDDL-1.0, ODC Public Domain Dedication & License 1.0

PHP_3_0

PHP-3.0, PHP License v3.0

PHP_3_01

PHP-3.01, PHP License v3.01

Plexus

Plexus, Plexus Classworlds License

PostgreSQL

PostgreSQL, PostgreSQL License

Psfrag

psfrag, psfrag License

Psutils

psutils, psutils License

Python_2_0

Python-2.0, Python License 2.0

Qhull

Qhull, Qhull License

QPL_1_0

QPL-1.0, Q Public License 1.0

Rdisc

Rdisc, Rdisc License

RHeCos_1_1

RHeCos-1.1, Red Hat eCos Public License v1.1

RPL_1_1

RPL-1.1, Reciprocal Public License 1.1

RPL_1_5

RPL-1.5, Reciprocal Public License 1.5

RPSL_1_0

RPSL-1.0, RealNetworks Public Source License v1.0

RSA_MD

RSA-MD, RSA Message-Digest License

RSCPL

RSCPL, Ricoh Source Code Public License

Ruby

Ruby, Ruby License

SAX_PD

SAX-PD, Sax Public Domain Notice

Saxpath

Saxpath, Saxpath License

SCEA

SCEA, SCEA Shared Source License

Sendmail

Sendmail, Sendmail License

SGI_B_1_0

SGI-B-1.0, SGI Free Software License B v1.0

SGI_B_1_1

SGI-B-1.1, SGI Free Software License B v1.1

SGI_B_2_0

SGI-B-2.0, SGI Free Software License B v2.0

SimPL_2_0

SimPL-2.0, Simple Public License 2.0

SISSL_1_2

SISSL-1.2, Sun Industry Standards Source License v1.2

SISSL

SISSL, Sun Industry Standards Source License v1.1

Sleepycat

Sleepycat, Sleepycat License

SMLNJ

SMLNJ, Standard ML of New Jersey License

SMPPL

SMPPL, Secure Messaging Protocol Public License

SNIA

SNIA, SNIA Public License 1.1

Spencer_86

Spencer-86, Spencer License 86

Spencer_94

Spencer-94, Spencer License 94

Spencer_99

Spencer-99, Spencer License 99

SPL_1_0

SPL-1.0, Sun Public License v1.0

SugarCRM_1_1_3

SugarCRM-1.1.3, SugarCRM Public License v1.1.3

SWL

SWL, Scheme Widget Library (SWL) Software License Agreement

TCL

TCL, TCL/TK License

TCP_wrappers

TCP-wrappers, TCP Wrappers License

TMate

TMate, TMate Open Source License

TORQUE_1_1

TORQUE-1.1, TORQUE v2.5+ Software License v1.1

TOSL

TOSL, Trusster Open Source License

TU_Berlin_1_0

TU-Berlin-1.0, Technische Universitaet Berlin License 1.0, SPDX License List 3.2

TU_Berlin_2_0

TU-Berlin-2.0, Technische Universitaet Berlin License 2.0, SPDX License List 3.2

Unicode_DFS_2015

Unicode-DFS-2015, Unicode License Agreement - Data Files and Software (2015)

Unicode_DFS_2016

Unicode-DFS-2016, Unicode License Agreement - Data Files and Software (2016)

Unicode_TOU

Unicode-TOU, Unicode Terms of Use

Unlicense

Unlicense, The Unlicense

UPL_1_0

UPL-1.0, Universal Permissive License v1.0

Vim

Vim, Vim License

VOSTROM

VOSTROM, VOSTROM Public License for Open Source

VSL_1_0

VSL-1.0, Vovida Software License v1.0

W3C_19980720

W3C-19980720, W3C Software Notice and License (1998-07-20)

W3C_20150513

W3C-20150513, W3C Software Notice and Document License (2015-05-13)

W3C

W3C, W3C Software Notice and License (2002-12-31)

Watcom_1_0

Watcom-1.0, Sybase Open Watcom Public License 1.0

Wsuipa

Wsuipa, Wsuipa License

WTFPL

WTFPL, Do What The F*ck You Want To Public License

X11

X11, X11 License

Xerox

Xerox, Xerox License

XFree86_1_1

XFree86-1.1, XFree86 License 1.1

Xinetd

xinetd, xinetd License

Xnet

Xnet, X.Net License

Xpp

xpp, XPP License

XSkat

XSkat, XSkat License

YPL_1_0

YPL-1.0, Yahoo! Public License v1.0

YPL_1_1

YPL-1.1, Yahoo! Public License v1.1

Zed

Zed, Zed License

Zend_2_0

Zend-2.0, Zend License v2.0

Zimbra_1_3

Zimbra-1.3, Zimbra Public License v1.3

Zimbra_1_4

Zimbra-1.4, Zimbra Public License v1.4

Zlib_acknowledgement

zlib-acknowledgement, zlib/libpng License with Acknowledgement

Zlib

Zlib, zlib License

ZPL_1_1

ZPL-1.1, Zope Public License 1.1

ZPL_2_0

ZPL-2.0, Zope Public License 2.0

ZPL_2_1

ZPL-2.1, Zope Public License 2.1

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

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

toConstr :: LicenseId -> Constr Source #

dataTypeOf :: LicenseId -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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 :: Type -> Type Source #

Binary LicenseId # 
Instance details

Defined in Distribution.SPDX.LicenseId

NFData LicenseId # 
Instance details

Defined in Distribution.SPDX.LicenseId

Methods

rnf :: LicenseId -> () Source #

Pretty LicenseId # 
Instance details

Defined in Distribution.SPDX.LicenseId

Methods

pretty :: LicenseId -> Doc Source #

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

type Rep LicenseId # 
Instance details

Defined in Distribution.SPDX.LicenseId

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

licenseId :: LicenseId -> String Source #

License SPDX identifier, e.g. "BSD-3-Clause".

licenseName :: LicenseId -> String Source #

License name, e.g. "GNU General Public License v2.0 only"

licenseIsOsiApproved :: LicenseId -> Bool Source #

Whether the license is approved by Open Source Initiative (OSI).

See https://opensource.org/licenses/alphabetical.

License exception

data LicenseExceptionId Source #

SPDX License identifier

Constructors

DS389_exception

389-exception, 389 Directory Server Exception

Autoconf_exception_2_0

Autoconf-exception-2.0, Autoconf exception 2.0

Autoconf_exception_3_0

Autoconf-exception-3.0, Autoconf exception 3.0

Bison_exception_2_2

Bison-exception-2.2, Bison exception 2.2

Bootloader_exception

Bootloader-exception, Bootloader Distribution Exception

Classpath_exception_2_0

Classpath-exception-2.0, Classpath exception 2.0

CLISP_exception_2_0

CLISP-exception-2.0, CLISP exception 2.0

DigiRule_FOSS_exception

DigiRule-FOSS-exception, DigiRule FOSS License Exception

ECos_exception_2_0

eCos-exception-2.0, eCos exception 2.0

Fawkes_Runtime_exception

Fawkes-Runtime-exception, Fawkes Runtime Exception

FLTK_exception

FLTK-exception, FLTK exception

Font_exception_2_0

Font-exception-2.0, Font exception 2.0

Freertos_exception_2_0

freertos-exception-2.0, FreeRTOS Exception 2.0

GCC_exception_2_0

GCC-exception-2.0, GCC Runtime Library exception 2.0

GCC_exception_3_1

GCC-exception-3.1, GCC Runtime Library exception 3.1

Gnu_javamail_exception

gnu-javamail-exception, GNU JavaMail exception

I2p_gpl_java_exception

i2p-gpl-java-exception, i2p GPL+Java Exception

Libtool_exception

Libtool-exception, Libtool Exception

Linux_syscall_note

Linux-syscall-note, Linux Syscall Note

LLVM_exception

LLVM-exception, LLVM Exception, SPDX License List 3.2

LZMA_exception

LZMA-exception, LZMA exception

Mif_exception

mif-exception, Macros and Inline Functions Exception

Nokia_Qt_exception_1_1

Nokia-Qt-exception-1.1, Nokia Qt LGPL exception 1.1

OCCT_exception_1_0

OCCT-exception-1.0, Open CASCADE Exception 1.0

OpenJDK_assembly_exception_1_0

OpenJDK-assembly-exception-1.0, OpenJDK Assembly exception 1.0, SPDX License List 3.2

Openvpn_openssl_exception

openvpn-openssl-exception, OpenVPN OpenSSL Exception

PS_or_PDF_font_exception_20170817

PS-or-PDF-font-exception-20170817, PS/PDF font exception (2017-08-17), SPDX License List 3.2

Qt_GPL_exception_1_0

Qt-GPL-exception-1.0, Qt GPL exception 1.0, SPDX License List 3.2

Qt_LGPL_exception_1_1

Qt-LGPL-exception-1.1, Qt LGPL exception 1.1, SPDX License List 3.2

Qwt_exception_1_0

Qwt-exception-1.0, Qwt exception 1.0

U_boot_exception_2_0

u-boot-exception-2.0, U-Boot exception 2.0

WxWindows_exception_3_1

WxWindows-exception-3.1, WxWindows Library Exception 3.1

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

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

toConstr :: LicenseExceptionId -> Constr Source #

dataTypeOf :: LicenseExceptionId -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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 :: Type -> Type Source #

Binary LicenseExceptionId # 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

NFData LicenseExceptionId # 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

Methods

rnf :: LicenseExceptionId -> () Source #

Pretty LicenseExceptionId # 
Instance details

Defined in Distribution.SPDX.LicenseExceptionId

Parsec 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" False) (((((C1 (MetaCons "DS389_exception" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Autoconf_exception_2_0" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Autoconf_exception_3_0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Bison_exception_2_2" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Bootloader_exception" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Classpath_exception_2_0" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CLISP_exception_2_0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DigiRule_FOSS_exception" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "ECos_exception_2_0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Fawkes_Runtime_exception" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "FLTK_exception" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Font_exception_2_0" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Freertos_exception_2_0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GCC_exception_2_0" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "GCC_exception_3_1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Gnu_javamail_exception" PrefixI False) (U1 :: Type -> Type))))) :+: ((((C1 (MetaCons "I2p_gpl_java_exception" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Libtool_exception" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Linux_syscall_note" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LLVM_exception" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "LZMA_exception" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Mif_exception" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Nokia_Qt_exception_1_1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OCCT_exception_1_0" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "OpenJDK_assembly_exception_1_0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Openvpn_openssl_exception" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "PS_or_PDF_font_exception_20170817" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Qt_GPL_exception_1_0" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Qt_LGPL_exception_1_1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Qwt_exception_1_0" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "U_boot_exception_2_0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WxWindows_exception_3_1" PrefixI False) (U1 :: Type -> Type))))))

licenseExceptionId :: LicenseExceptionId -> String Source #

License SPDX identifier, e.g. "BSD-3-Clause".

licenseExceptionName :: LicenseExceptionId -> String Source #

License name, e.g. "GNU General Public License v2.0 only"

License reference

data LicenseRef Source #

A user defined license reference denoted by LicenseRef-[idstring] (for a license not on the SPDX License List);

Instances
Eq LicenseRef # 
Instance details

Defined in Distribution.SPDX.LicenseReference

Data LicenseRef # 
Instance details

Defined in Distribution.SPDX.LicenseReference

Methods

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

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

toConstr :: LicenseRef -> Constr Source #

dataTypeOf :: LicenseRef -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord LicenseRef # 
Instance details

Defined in Distribution.SPDX.LicenseReference

Read LicenseRef # 
Instance details

Defined in Distribution.SPDX.LicenseReference

Show LicenseRef # 
Instance details

Defined in Distribution.SPDX.LicenseReference

Generic LicenseRef # 
Instance details

Defined in Distribution.SPDX.LicenseReference

Associated Types

type Rep LicenseRef :: Type -> Type Source #

Binary LicenseRef # 
Instance details

Defined in Distribution.SPDX.LicenseReference

NFData LicenseRef # 
Instance details

Defined in Distribution.SPDX.LicenseReference

Methods

rnf :: LicenseRef -> () Source #

Pretty LicenseRef # 
Instance details

Defined in Distribution.SPDX.LicenseReference

Parsec LicenseRef # 
Instance details

Defined in Distribution.SPDX.LicenseReference

type Rep LicenseRef # 
Instance details

Defined in Distribution.SPDX.LicenseReference

type Rep LicenseRef = D1 (MetaData "LicenseRef" "Distribution.SPDX.LicenseReference" "Cabal-2.4.0.1" False) (C1 (MetaCons "LicenseRef" PrefixI True) (S1 (MetaSel (Just "_lrDocument") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe String)) :*: S1 (MetaSel (Just "_lrLicense") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 String)))

licenseRef :: LicenseRef -> String Source #

License reference.

mkLicenseRef :: Maybe String -> String -> Maybe LicenseRef Source #

Create LicenseRef from optional document ref and name.

mkLicenseRef' :: Maybe String -> String -> LicenseRef Source #

Like mkLicenseRef but convert invalid characters into -.

License list version

data LicenseListVersion Source #

SPDX License List version Cabal is aware of.

Instances
Bounded LicenseListVersion # 
Instance details

Defined in Distribution.SPDX.LicenseListVersion

Enum LicenseListVersion # 
Instance details

Defined in Distribution.SPDX.LicenseListVersion

Eq LicenseListVersion # 
Instance details

Defined in Distribution.SPDX.LicenseListVersion

Ord LicenseListVersion # 
Instance details

Defined in Distribution.SPDX.LicenseListVersion

Show LicenseListVersion # 
Instance details

Defined in Distribution.SPDX.LicenseListVersion