1-- This file is generated. See Makefile's spdx rule
2{-# LANGUAGE DeriveDataTypeable #-}
3{-# LANGUAGE DeriveGeneric      #-}
4module Distribution.SPDX.LicenseId (
5    LicenseId (..),
6    licenseId,
7    licenseName,
8    licenseIsOsiApproved,
9    mkLicenseId,
10    licenseIdList,
11    -- * Helpers
12    licenseIdMigrationMessage,
13    ) where
14
15import Distribution.Compat.Prelude
16import Prelude ()
17
18import Distribution.Compat.Lens (set)
19import Distribution.Pretty
20import Distribution.Parsec
21import Distribution.Utils.Generic (isAsciiAlphaNum)
22import Distribution.Utils.Structured (Structured (..), nominalStructure, typeVersion)
23import Distribution.SPDX.LicenseListVersion
24
25import qualified Data.Binary.Get as Binary
26import qualified Data.Binary.Put as Binary
27import qualified Data.Map.Strict as Map
28import qualified Distribution.Compat.CharParsing as P
29import qualified Text.PrettyPrint as Disp
30
31-------------------------------------------------------------------------------
32-- LicenseId
33-------------------------------------------------------------------------------
34
35-- | SPDX License identifier
36data LicenseId
37    = NullBSD -- ^ @0BSD@, BSD Zero Clause License
38    | AAL -- ^ @AAL@, Attribution Assurance License
39    | Abstyles -- ^ @Abstyles@, Abstyles License
40    | Adobe_2006 -- ^ @Adobe-2006@, Adobe Systems Incorporated Source Code License Agreement
41    | Adobe_Glyph -- ^ @Adobe-Glyph@, Adobe Glyph List License
42    | ADSL -- ^ @ADSL@, Amazon Digital Services License
43    | AFL_1_1 -- ^ @AFL-1.1@, Academic Free License v1.1
44    | AFL_1_2 -- ^ @AFL-1.2@, Academic Free License v1.2
45    | AFL_2_0 -- ^ @AFL-2.0@, Academic Free License v2.0
46    | AFL_2_1 -- ^ @AFL-2.1@, Academic Free License v2.1
47    | AFL_3_0 -- ^ @AFL-3.0@, Academic Free License v3.0
48    | Afmparse -- ^ @Afmparse@, Afmparse License
49    | AGPL_1_0 -- ^ @AGPL-1.0@, Affero General Public License v1.0, SPDX License List 3.0
50    | AGPL_1_0_only -- ^ @AGPL-1.0-only@, Affero General Public License v1.0 only, SPDX License List 3.2, SPDX License List 3.6
51    | AGPL_1_0_or_later -- ^ @AGPL-1.0-or-later@, Affero General Public License v1.0 or later, SPDX License List 3.2, SPDX License List 3.6
52    | AGPL_3_0_only -- ^ @AGPL-3.0-only@, GNU Affero General Public License v3.0 only
53    | AGPL_3_0_or_later -- ^ @AGPL-3.0-or-later@, GNU Affero General Public License v3.0 or later
54    | Aladdin -- ^ @Aladdin@, Aladdin Free Public License
55    | AMDPLPA -- ^ @AMDPLPA@, AMD's plpa_map.c License
56    | AML -- ^ @AML@, Apple MIT License
57    | AMPAS -- ^ @AMPAS@, Academy of Motion Picture Arts and Sciences BSD
58    | ANTLR_PD -- ^ @ANTLR-PD@, ANTLR Software Rights Notice
59    | Apache_1_0 -- ^ @Apache-1.0@, Apache License 1.0
60    | Apache_1_1 -- ^ @Apache-1.1@, Apache License 1.1
61    | Apache_2_0 -- ^ @Apache-2.0@, Apache License 2.0
62    | APAFML -- ^ @APAFML@, Adobe Postscript AFM License
63    | APL_1_0 -- ^ @APL-1.0@, Adaptive Public License 1.0
64    | APSL_1_0 -- ^ @APSL-1.0@, Apple Public Source License 1.0
65    | APSL_1_1 -- ^ @APSL-1.1@, Apple Public Source License 1.1
66    | APSL_1_2 -- ^ @APSL-1.2@, Apple Public Source License 1.2
67    | APSL_2_0 -- ^ @APSL-2.0@, Apple Public Source License 2.0
68    | Artistic_1_0_cl8 -- ^ @Artistic-1.0-cl8@, Artistic License 1.0 w/clause 8
69    | Artistic_1_0_Perl -- ^ @Artistic-1.0-Perl@, Artistic License 1.0 (Perl)
70    | Artistic_1_0 -- ^ @Artistic-1.0@, Artistic License 1.0
71    | Artistic_2_0 -- ^ @Artistic-2.0@, Artistic License 2.0
72    | Bahyph -- ^ @Bahyph@, Bahyph License
73    | Barr -- ^ @Barr@, Barr License
74    | Beerware -- ^ @Beerware@, Beerware License
75    | BitTorrent_1_0 -- ^ @BitTorrent-1.0@, BitTorrent Open Source License v1.0
76    | BitTorrent_1_1 -- ^ @BitTorrent-1.1@, BitTorrent Open Source License v1.1
77    | Blessing -- ^ @blessing@, SQLite Blessing, SPDX License List 3.6
78    | BlueOak_1_0_0 -- ^ @BlueOak-1.0.0@, Blue Oak Model License 1.0.0, SPDX License List 3.6
79    | Borceux -- ^ @Borceux@, Borceux license
80    | BSD_1_Clause -- ^ @BSD-1-Clause@, BSD 1-Clause License
81    | BSD_2_Clause_FreeBSD -- ^ @BSD-2-Clause-FreeBSD@, BSD 2-Clause FreeBSD License
82    | BSD_2_Clause_NetBSD -- ^ @BSD-2-Clause-NetBSD@, BSD 2-Clause NetBSD License
83    | BSD_2_Clause_Patent -- ^ @BSD-2-Clause-Patent@, BSD-2-Clause Plus Patent License
84    | BSD_2_Clause -- ^ @BSD-2-Clause@, BSD 2-Clause "Simplified" License
85    | BSD_3_Clause_Attribution -- ^ @BSD-3-Clause-Attribution@, BSD with attribution
86    | BSD_3_Clause_Clear -- ^ @BSD-3-Clause-Clear@, BSD 3-Clause Clear License
87    | BSD_3_Clause_LBNL -- ^ @BSD-3-Clause-LBNL@, Lawrence Berkeley National Labs BSD variant license
88    | BSD_3_Clause_No_Nuclear_License_2014 -- ^ @BSD-3-Clause-No-Nuclear-License-2014@, BSD 3-Clause No Nuclear License 2014
89    | BSD_3_Clause_No_Nuclear_License -- ^ @BSD-3-Clause-No-Nuclear-License@, BSD 3-Clause No Nuclear License
90    | BSD_3_Clause_No_Nuclear_Warranty -- ^ @BSD-3-Clause-No-Nuclear-Warranty@, BSD 3-Clause No Nuclear Warranty
91    | BSD_3_Clause_Open_MPI -- ^ @BSD-3-Clause-Open-MPI@, BSD 3-Clause Open MPI variant, SPDX License List 3.6
92    | BSD_3_Clause -- ^ @BSD-3-Clause@, BSD 3-Clause "New" or "Revised" License
93    | BSD_4_Clause_UC -- ^ @BSD-4-Clause-UC@, BSD-4-Clause (University of California-Specific)
94    | BSD_4_Clause -- ^ @BSD-4-Clause@, BSD 4-Clause "Original" or "Old" License
95    | BSD_Protection -- ^ @BSD-Protection@, BSD Protection License
96    | BSD_Source_Code -- ^ @BSD-Source-Code@, BSD Source Code Attribution
97    | BSL_1_0 -- ^ @BSL-1.0@, Boost Software License 1.0
98    | Bzip2_1_0_5 -- ^ @bzip2-1.0.5@, bzip2 and libbzip2 License v1.0.5
99    | Bzip2_1_0_6 -- ^ @bzip2-1.0.6@, bzip2 and libbzip2 License v1.0.6
100    | Caldera -- ^ @Caldera@, Caldera License
101    | CATOSL_1_1 -- ^ @CATOSL-1.1@, Computer Associates Trusted Open Source License 1.1
102    | CC_BY_1_0 -- ^ @CC-BY-1.0@, Creative Commons Attribution 1.0 Generic
103    | CC_BY_2_0 -- ^ @CC-BY-2.0@, Creative Commons Attribution 2.0 Generic
104    | CC_BY_2_5 -- ^ @CC-BY-2.5@, Creative Commons Attribution 2.5 Generic
105    | CC_BY_3_0 -- ^ @CC-BY-3.0@, Creative Commons Attribution 3.0 Unported
106    | CC_BY_4_0 -- ^ @CC-BY-4.0@, Creative Commons Attribution 4.0 International
107    | CC_BY_NC_1_0 -- ^ @CC-BY-NC-1.0@, Creative Commons Attribution Non Commercial 1.0 Generic
108    | CC_BY_NC_2_0 -- ^ @CC-BY-NC-2.0@, Creative Commons Attribution Non Commercial 2.0 Generic
109    | CC_BY_NC_2_5 -- ^ @CC-BY-NC-2.5@, Creative Commons Attribution Non Commercial 2.5 Generic
110    | CC_BY_NC_3_0 -- ^ @CC-BY-NC-3.0@, Creative Commons Attribution Non Commercial 3.0 Unported
111    | CC_BY_NC_4_0 -- ^ @CC-BY-NC-4.0@, Creative Commons Attribution Non Commercial 4.0 International
112    | CC_BY_NC_ND_1_0 -- ^ @CC-BY-NC-ND-1.0@, Creative Commons Attribution Non Commercial No Derivatives 1.0 Generic
113    | CC_BY_NC_ND_2_0 -- ^ @CC-BY-NC-ND-2.0@, Creative Commons Attribution Non Commercial No Derivatives 2.0 Generic
114    | CC_BY_NC_ND_2_5 -- ^ @CC-BY-NC-ND-2.5@, Creative Commons Attribution Non Commercial No Derivatives 2.5 Generic
115    | CC_BY_NC_ND_3_0 -- ^ @CC-BY-NC-ND-3.0@, Creative Commons Attribution Non Commercial No Derivatives 3.0 Unported
116    | CC_BY_NC_ND_4_0 -- ^ @CC-BY-NC-ND-4.0@, Creative Commons Attribution Non Commercial No Derivatives 4.0 International
117    | CC_BY_NC_SA_1_0 -- ^ @CC-BY-NC-SA-1.0@, Creative Commons Attribution Non Commercial Share Alike 1.0 Generic
118    | CC_BY_NC_SA_2_0 -- ^ @CC-BY-NC-SA-2.0@, Creative Commons Attribution Non Commercial Share Alike 2.0 Generic
119    | CC_BY_NC_SA_2_5 -- ^ @CC-BY-NC-SA-2.5@, Creative Commons Attribution Non Commercial Share Alike 2.5 Generic
120    | CC_BY_NC_SA_3_0 -- ^ @CC-BY-NC-SA-3.0@, Creative Commons Attribution Non Commercial Share Alike 3.0 Unported
121    | CC_BY_NC_SA_4_0 -- ^ @CC-BY-NC-SA-4.0@, Creative Commons Attribution Non Commercial Share Alike 4.0 International
122    | CC_BY_ND_1_0 -- ^ @CC-BY-ND-1.0@, Creative Commons Attribution No Derivatives 1.0 Generic
123    | CC_BY_ND_2_0 -- ^ @CC-BY-ND-2.0@, Creative Commons Attribution No Derivatives 2.0 Generic
124    | CC_BY_ND_2_5 -- ^ @CC-BY-ND-2.5@, Creative Commons Attribution No Derivatives 2.5 Generic
125    | CC_BY_ND_3_0 -- ^ @CC-BY-ND-3.0@, Creative Commons Attribution No Derivatives 3.0 Unported
126    | CC_BY_ND_4_0 -- ^ @CC-BY-ND-4.0@, Creative Commons Attribution No Derivatives 4.0 International
127    | CC_BY_SA_1_0 -- ^ @CC-BY-SA-1.0@, Creative Commons Attribution Share Alike 1.0 Generic
128    | CC_BY_SA_2_0 -- ^ @CC-BY-SA-2.0@, Creative Commons Attribution Share Alike 2.0 Generic
129    | CC_BY_SA_2_5 -- ^ @CC-BY-SA-2.5@, Creative Commons Attribution Share Alike 2.5 Generic
130    | CC_BY_SA_3_0 -- ^ @CC-BY-SA-3.0@, Creative Commons Attribution Share Alike 3.0 Unported
131    | CC_BY_SA_4_0 -- ^ @CC-BY-SA-4.0@, Creative Commons Attribution Share Alike 4.0 International
132    | CC_PDDC -- ^ @CC-PDDC@, Creative Commons Public Domain Dedication and Certification, SPDX License List 3.6
133    | CC0_1_0 -- ^ @CC0-1.0@, Creative Commons Zero v1.0 Universal
134    | CDDL_1_0 -- ^ @CDDL-1.0@, Common Development and Distribution License 1.0
135    | CDDL_1_1 -- ^ @CDDL-1.1@, Common Development and Distribution License 1.1
136    | CDLA_Permissive_1_0 -- ^ @CDLA-Permissive-1.0@, Community Data License Agreement Permissive 1.0
137    | CDLA_Sharing_1_0 -- ^ @CDLA-Sharing-1.0@, Community Data License Agreement Sharing 1.0
138    | CECILL_1_0 -- ^ @CECILL-1.0@, CeCILL Free Software License Agreement v1.0
139    | CECILL_1_1 -- ^ @CECILL-1.1@, CeCILL Free Software License Agreement v1.1
140    | CECILL_2_0 -- ^ @CECILL-2.0@, CeCILL Free Software License Agreement v2.0
141    | CECILL_2_1 -- ^ @CECILL-2.1@, CeCILL Free Software License Agreement v2.1
142    | CECILL_B -- ^ @CECILL-B@, CeCILL-B Free Software License Agreement
143    | CECILL_C -- ^ @CECILL-C@, CeCILL-C Free Software License Agreement
144    | CERN_OHL_1_1 -- ^ @CERN-OHL-1.1@, CERN Open Hardware License v1.1, SPDX License List 3.6
145    | CERN_OHL_1_2 -- ^ @CERN-OHL-1.2@, CERN Open Hardware Licence v1.2, SPDX License List 3.6
146    | ClArtistic -- ^ @ClArtistic@, Clarified Artistic License
147    | CNRI_Jython -- ^ @CNRI-Jython@, CNRI Jython License
148    | CNRI_Python_GPL_Compatible -- ^ @CNRI-Python-GPL-Compatible@, CNRI Python Open Source GPL Compatible License Agreement
149    | CNRI_Python -- ^ @CNRI-Python@, CNRI Python License
150    | Condor_1_1 -- ^ @Condor-1.1@, Condor Public License v1.1
151    | Copyleft_next_0_3_0 -- ^ @copyleft-next-0.3.0@, copyleft-next 0.3.0, SPDX License List 3.6
152    | Copyleft_next_0_3_1 -- ^ @copyleft-next-0.3.1@, copyleft-next 0.3.1, SPDX License List 3.6
153    | CPAL_1_0 -- ^ @CPAL-1.0@, Common Public Attribution License 1.0
154    | CPL_1_0 -- ^ @CPL-1.0@, Common Public License 1.0
155    | CPOL_1_02 -- ^ @CPOL-1.02@, Code Project Open License 1.02
156    | Crossword -- ^ @Crossword@, Crossword License
157    | CrystalStacker -- ^ @CrystalStacker@, CrystalStacker License
158    | CUA_OPL_1_0 -- ^ @CUA-OPL-1.0@, CUA Office Public License v1.0
159    | Cube -- ^ @Cube@, Cube License
160    | Curl -- ^ @curl@, curl License
161    | D_FSL_1_0 -- ^ @D-FSL-1.0@, Deutsche Freie Software Lizenz
162    | Diffmark -- ^ @diffmark@, diffmark license
163    | DOC -- ^ @DOC@, DOC License
164    | Dotseqn -- ^ @Dotseqn@, Dotseqn License
165    | DSDP -- ^ @DSDP@, DSDP License
166    | Dvipdfm -- ^ @dvipdfm@, dvipdfm License
167    | ECL_1_0 -- ^ @ECL-1.0@, Educational Community License v1.0
168    | ECL_2_0 -- ^ @ECL-2.0@, Educational Community License v2.0
169    | EFL_1_0 -- ^ @EFL-1.0@, Eiffel Forum License v1.0
170    | EFL_2_0 -- ^ @EFL-2.0@, Eiffel Forum License v2.0
171    | EGenix -- ^ @eGenix@, eGenix.com Public License 1.1.0
172    | Entessa -- ^ @Entessa@, Entessa Public License v1.0
173    | EPL_1_0 -- ^ @EPL-1.0@, Eclipse Public License 1.0
174    | EPL_2_0 -- ^ @EPL-2.0@, Eclipse Public License 2.0
175    | ErlPL_1_1 -- ^ @ErlPL-1.1@, Erlang Public License v1.1
176    | EUDatagrid -- ^ @EUDatagrid@, EU DataGrid Software License
177    | EUPL_1_0 -- ^ @EUPL-1.0@, European Union Public License 1.0
178    | EUPL_1_1 -- ^ @EUPL-1.1@, European Union Public License 1.1
179    | EUPL_1_2 -- ^ @EUPL-1.2@, European Union Public License 1.2
180    | Eurosym -- ^ @Eurosym@, Eurosym License
181    | Fair -- ^ @Fair@, Fair License
182    | Frameworx_1_0 -- ^ @Frameworx-1.0@, Frameworx Open License 1.0
183    | FreeImage -- ^ @FreeImage@, FreeImage Public License v1.0
184    | FSFAP -- ^ @FSFAP@, FSF All Permissive License
185    | FSFULLR -- ^ @FSFULLR@, FSF Unlimited License (with License Retention)
186    | FSFUL -- ^ @FSFUL@, FSF Unlimited License
187    | FTL -- ^ @FTL@, Freetype Project License
188    | GFDL_1_1_only -- ^ @GFDL-1.1-only@, GNU Free Documentation License v1.1 only
189    | GFDL_1_1_or_later -- ^ @GFDL-1.1-or-later@, GNU Free Documentation License v1.1 or later
190    | GFDL_1_2_only -- ^ @GFDL-1.2-only@, GNU Free Documentation License v1.2 only
191    | GFDL_1_2_or_later -- ^ @GFDL-1.2-or-later@, GNU Free Documentation License v1.2 or later
192    | GFDL_1_3_only -- ^ @GFDL-1.3-only@, GNU Free Documentation License v1.3 only
193    | GFDL_1_3_or_later -- ^ @GFDL-1.3-or-later@, GNU Free Documentation License v1.3 or later
194    | Giftware -- ^ @Giftware@, Giftware License
195    | GL2PS -- ^ @GL2PS@, GL2PS License
196    | Glide -- ^ @Glide@, 3dfx Glide License
197    | Glulxe -- ^ @Glulxe@, Glulxe License
198    | Gnuplot -- ^ @gnuplot@, gnuplot License
199    | GPL_1_0_only -- ^ @GPL-1.0-only@, GNU General Public License v1.0 only
200    | GPL_1_0_or_later -- ^ @GPL-1.0-or-later@, GNU General Public License v1.0 or later
201    | GPL_2_0_only -- ^ @GPL-2.0-only@, GNU General Public License v2.0 only
202    | GPL_2_0_or_later -- ^ @GPL-2.0-or-later@, GNU General Public License v2.0 or later
203    | GPL_3_0_only -- ^ @GPL-3.0-only@, GNU General Public License v3.0 only
204    | GPL_3_0_or_later -- ^ @GPL-3.0-or-later@, GNU General Public License v3.0 or later
205    | GSOAP_1_3b -- ^ @gSOAP-1.3b@, gSOAP Public License v1.3b
206    | HaskellReport -- ^ @HaskellReport@, Haskell Language Report License
207    | HPND_sell_variant -- ^ @HPND-sell-variant@, Historical Permission Notice and Disclaimer - sell variant, SPDX License List 3.6
208    | HPND -- ^ @HPND@, Historical Permission Notice and Disclaimer
209    | IBM_pibs -- ^ @IBM-pibs@, IBM PowerPC Initialization and Boot Software
210    | ICU -- ^ @ICU@, ICU License
211    | IJG -- ^ @IJG@, Independent JPEG Group License
212    | ImageMagick -- ^ @ImageMagick@, ImageMagick License
213    | IMatix -- ^ @iMatix@, iMatix Standard Function Library Agreement
214    | Imlib2 -- ^ @Imlib2@, Imlib2 License
215    | Info_ZIP -- ^ @Info-ZIP@, Info-ZIP License
216    | Intel_ACPI -- ^ @Intel-ACPI@, Intel ACPI Software License Agreement
217    | Intel -- ^ @Intel@, Intel Open Source License
218    | Interbase_1_0 -- ^ @Interbase-1.0@, Interbase Public License v1.0
219    | IPA -- ^ @IPA@, IPA Font License
220    | IPL_1_0 -- ^ @IPL-1.0@, IBM Public License v1.0
221    | ISC -- ^ @ISC@, ISC License
222    | JasPer_2_0 -- ^ @JasPer-2.0@, JasPer License
223    | JPNIC -- ^ @JPNIC@, Japan Network Information Center License, SPDX License List 3.6
224    | JSON -- ^ @JSON@, JSON License
225    | LAL_1_2 -- ^ @LAL-1.2@, Licence Art Libre 1.2
226    | LAL_1_3 -- ^ @LAL-1.3@, Licence Art Libre 1.3
227    | Latex2e -- ^ @Latex2e@, Latex2e License
228    | Leptonica -- ^ @Leptonica@, Leptonica License
229    | LGPL_2_0_only -- ^ @LGPL-2.0-only@, GNU Library General Public License v2 only
230    | LGPL_2_0_or_later -- ^ @LGPL-2.0-or-later@, GNU Library General Public License v2 or later
231    | LGPL_2_1_only -- ^ @LGPL-2.1-only@, GNU Lesser General Public License v2.1 only
232    | LGPL_2_1_or_later -- ^ @LGPL-2.1-or-later@, GNU Lesser General Public License v2.1 or later
233    | LGPL_3_0_only -- ^ @LGPL-3.0-only@, GNU Lesser General Public License v3.0 only
234    | LGPL_3_0_or_later -- ^ @LGPL-3.0-or-later@, GNU Lesser General Public License v3.0 or later
235    | LGPLLR -- ^ @LGPLLR@, Lesser General Public License For Linguistic Resources
236    | Libpng_2_0 -- ^ @libpng-2.0@, PNG Reference Library version 2, SPDX License List 3.6
237    | Libpng -- ^ @Libpng@, libpng License
238    | Libtiff -- ^ @libtiff@, libtiff License
239    | LiLiQ_P_1_1 -- ^ @LiLiQ-P-1.1@, Licence Libre du Québec – Permissive version 1.1
240    | LiLiQ_R_1_1 -- ^ @LiLiQ-R-1.1@, Licence Libre du Québec – Réciprocité version 1.1
241    | LiLiQ_Rplus_1_1 -- ^ @LiLiQ-Rplus-1.1@, Licence Libre du Québec – Réciprocité forte version 1.1
242    | Linux_OpenIB -- ^ @Linux-OpenIB@, Linux Kernel Variant of OpenIB.org license, SPDX License List 3.2, SPDX License List 3.6
243    | LPL_1_02 -- ^ @LPL-1.02@, Lucent Public License v1.02
244    | LPL_1_0 -- ^ @LPL-1.0@, Lucent Public License Version 1.0
245    | LPPL_1_0 -- ^ @LPPL-1.0@, LaTeX Project Public License v1.0
246    | LPPL_1_1 -- ^ @LPPL-1.1@, LaTeX Project Public License v1.1
247    | LPPL_1_2 -- ^ @LPPL-1.2@, LaTeX Project Public License v1.2
248    | LPPL_1_3a -- ^ @LPPL-1.3a@, LaTeX Project Public License v1.3a
249    | LPPL_1_3c -- ^ @LPPL-1.3c@, LaTeX Project Public License v1.3c
250    | MakeIndex -- ^ @MakeIndex@, MakeIndex License
251    | MirOS -- ^ @MirOS@, MirOS License
252    | MIT_0 -- ^ @MIT-0@, MIT No Attribution, SPDX License List 3.2, SPDX License List 3.6
253    | MIT_advertising -- ^ @MIT-advertising@, Enlightenment License (e16)
254    | MIT_CMU -- ^ @MIT-CMU@, CMU License
255    | MIT_enna -- ^ @MIT-enna@, enna License
256    | MIT_feh -- ^ @MIT-feh@, feh License
257    | MITNFA -- ^ @MITNFA@, MIT +no-false-attribs license
258    | MIT -- ^ @MIT@, MIT License
259    | Motosoto -- ^ @Motosoto@, Motosoto License
260    | Mpich2 -- ^ @mpich2@, mpich2 License
261    | MPL_1_0 -- ^ @MPL-1.0@, Mozilla Public License 1.0
262    | MPL_1_1 -- ^ @MPL-1.1@, Mozilla Public License 1.1
263    | MPL_2_0_no_copyleft_exception -- ^ @MPL-2.0-no-copyleft-exception@, Mozilla Public License 2.0 (no copyleft exception)
264    | MPL_2_0 -- ^ @MPL-2.0@, Mozilla Public License 2.0
265    | MS_PL -- ^ @MS-PL@, Microsoft Public License
266    | MS_RL -- ^ @MS-RL@, Microsoft Reciprocal License
267    | MTLL -- ^ @MTLL@, Matrix Template Library License
268    | Multics -- ^ @Multics@, Multics License
269    | Mup -- ^ @Mup@, Mup License
270    | NASA_1_3 -- ^ @NASA-1.3@, NASA Open Source Agreement 1.3
271    | Naumen -- ^ @Naumen@, Naumen Public License
272    | NBPL_1_0 -- ^ @NBPL-1.0@, Net Boolean Public License v1
273    | NCSA -- ^ @NCSA@, University of Illinois/NCSA Open Source License
274    | Net_SNMP -- ^ @Net-SNMP@, Net-SNMP License
275    | NetCDF -- ^ @NetCDF@, NetCDF license
276    | Newsletr -- ^ @Newsletr@, Newsletr License
277    | NGPL -- ^ @NGPL@, Nethack General Public License
278    | NLOD_1_0 -- ^ @NLOD-1.0@, Norwegian Licence for Open Government Data
279    | NLPL -- ^ @NLPL@, No Limit Public License
280    | Nokia -- ^ @Nokia@, Nokia Open Source License
281    | NOSL -- ^ @NOSL@, Netizen Open Source License
282    | Noweb -- ^ @Noweb@, Noweb License
283    | NPL_1_0 -- ^ @NPL-1.0@, Netscape Public License v1.0
284    | NPL_1_1 -- ^ @NPL-1.1@, Netscape Public License v1.1
285    | NPOSL_3_0 -- ^ @NPOSL-3.0@, Non-Profit Open Software License 3.0
286    | NRL -- ^ @NRL@, NRL License
287    | NTP -- ^ @NTP@, NTP License
288    | OCCT_PL -- ^ @OCCT-PL@, Open CASCADE Technology Public License
289    | OCLC_2_0 -- ^ @OCLC-2.0@, OCLC Research Public License 2.0
290    | ODbL_1_0 -- ^ @ODbL-1.0@, ODC Open Database License v1.0
291    | ODC_By_1_0 -- ^ @ODC-By-1.0@, Open Data Commons Attribution License v1.0, SPDX License List 3.2, SPDX License List 3.6
292    | OFL_1_0 -- ^ @OFL-1.0@, SIL Open Font License 1.0
293    | OFL_1_1 -- ^ @OFL-1.1@, SIL Open Font License 1.1
294    | OGL_UK_1_0 -- ^ @OGL-UK-1.0@, Open Government Licence v1.0, SPDX License List 3.6
295    | OGL_UK_2_0 -- ^ @OGL-UK-2.0@, Open Government Licence v2.0, SPDX License List 3.6
296    | OGL_UK_3_0 -- ^ @OGL-UK-3.0@, Open Government Licence v3.0, SPDX License List 3.6
297    | OGTSL -- ^ @OGTSL@, Open Group Test Suite License
298    | OLDAP_1_1 -- ^ @OLDAP-1.1@, Open LDAP Public License v1.1
299    | OLDAP_1_2 -- ^ @OLDAP-1.2@, Open LDAP Public License v1.2
300    | OLDAP_1_3 -- ^ @OLDAP-1.3@, Open LDAP Public License v1.3
301    | OLDAP_1_4 -- ^ @OLDAP-1.4@, Open LDAP Public License v1.4
302    | OLDAP_2_0_1 -- ^ @OLDAP-2.0.1@, Open LDAP Public License v2.0.1
303    | OLDAP_2_0 -- ^ @OLDAP-2.0@, Open LDAP Public License v2.0 (or possibly 2.0A and 2.0B)
304    | OLDAP_2_1 -- ^ @OLDAP-2.1@, Open LDAP Public License v2.1
305    | OLDAP_2_2_1 -- ^ @OLDAP-2.2.1@, Open LDAP Public License v2.2.1
306    | OLDAP_2_2_2 -- ^ @OLDAP-2.2.2@, Open LDAP Public License 2.2.2
307    | OLDAP_2_2 -- ^ @OLDAP-2.2@, Open LDAP Public License v2.2
308    | OLDAP_2_3 -- ^ @OLDAP-2.3@, Open LDAP Public License v2.3
309    | OLDAP_2_4 -- ^ @OLDAP-2.4@, Open LDAP Public License v2.4
310    | OLDAP_2_5 -- ^ @OLDAP-2.5@, Open LDAP Public License v2.5
311    | OLDAP_2_6 -- ^ @OLDAP-2.6@, Open LDAP Public License v2.6
312    | OLDAP_2_7 -- ^ @OLDAP-2.7@, Open LDAP Public License v2.7
313    | OLDAP_2_8 -- ^ @OLDAP-2.8@, Open LDAP Public License v2.8
314    | OML -- ^ @OML@, Open Market License
315    | OpenSSL -- ^ @OpenSSL@, OpenSSL License
316    | OPL_1_0 -- ^ @OPL-1.0@, Open Public License v1.0
317    | OSET_PL_2_1 -- ^ @OSET-PL-2.1@, OSET Public License version 2.1
318    | OSL_1_0 -- ^ @OSL-1.0@, Open Software License 1.0
319    | OSL_1_1 -- ^ @OSL-1.1@, Open Software License 1.1
320    | OSL_2_0 -- ^ @OSL-2.0@, Open Software License 2.0
321    | OSL_2_1 -- ^ @OSL-2.1@, Open Software License 2.1
322    | OSL_3_0 -- ^ @OSL-3.0@, Open Software License 3.0
323    | Parity_6_0_0 -- ^ @Parity-6.0.0@, The Parity Public License 6.0.0, SPDX License List 3.6
324    | PDDL_1_0 -- ^ @PDDL-1.0@, ODC Public Domain Dedication & License 1.0
325    | PHP_3_01 -- ^ @PHP-3.01@, PHP License v3.01
326    | PHP_3_0 -- ^ @PHP-3.0@, PHP License v3.0
327    | Plexus -- ^ @Plexus@, Plexus Classworlds License
328    | PostgreSQL -- ^ @PostgreSQL@, PostgreSQL License
329    | Psfrag -- ^ @psfrag@, psfrag License
330    | Psutils -- ^ @psutils@, psutils License
331    | Python_2_0 -- ^ @Python-2.0@, Python License 2.0
332    | Qhull -- ^ @Qhull@, Qhull License
333    | QPL_1_0 -- ^ @QPL-1.0@, Q Public License 1.0
334    | Rdisc -- ^ @Rdisc@, Rdisc License
335    | RHeCos_1_1 -- ^ @RHeCos-1.1@, Red Hat eCos Public License v1.1
336    | RPL_1_1 -- ^ @RPL-1.1@, Reciprocal Public License 1.1
337    | RPL_1_5 -- ^ @RPL-1.5@, Reciprocal Public License 1.5
338    | RPSL_1_0 -- ^ @RPSL-1.0@, RealNetworks Public Source License v1.0
339    | RSA_MD -- ^ @RSA-MD@, RSA Message-Digest License
340    | RSCPL -- ^ @RSCPL@, Ricoh Source Code Public License
341    | Ruby -- ^ @Ruby@, Ruby License
342    | SAX_PD -- ^ @SAX-PD@, Sax Public Domain Notice
343    | Saxpath -- ^ @Saxpath@, Saxpath License
344    | SCEA -- ^ @SCEA@, SCEA Shared Source License
345    | Sendmail_8_23 -- ^ @Sendmail-8.23@, Sendmail License 8.23, SPDX License List 3.6
346    | Sendmail -- ^ @Sendmail@, Sendmail License
347    | SGI_B_1_0 -- ^ @SGI-B-1.0@, SGI Free Software License B v1.0
348    | SGI_B_1_1 -- ^ @SGI-B-1.1@, SGI Free Software License B v1.1
349    | SGI_B_2_0 -- ^ @SGI-B-2.0@, SGI Free Software License B v2.0
350    | SHL_0_51 -- ^ @SHL-0.51@, Solderpad Hardware License, Version 0.51, SPDX License List 3.6
351    | SHL_0_5 -- ^ @SHL-0.5@, Solderpad Hardware License v0.5, SPDX License List 3.6
352    | SimPL_2_0 -- ^ @SimPL-2.0@, Simple Public License 2.0
353    | SISSL_1_2 -- ^ @SISSL-1.2@, Sun Industry Standards Source License v1.2
354    | SISSL -- ^ @SISSL@, Sun Industry Standards Source License v1.1
355    | Sleepycat -- ^ @Sleepycat@, Sleepycat License
356    | SMLNJ -- ^ @SMLNJ@, Standard ML of New Jersey License
357    | SMPPL -- ^ @SMPPL@, Secure Messaging Protocol Public License
358    | SNIA -- ^ @SNIA@, SNIA Public License 1.1
359    | Spencer_86 -- ^ @Spencer-86@, Spencer License 86
360    | Spencer_94 -- ^ @Spencer-94@, Spencer License 94
361    | Spencer_99 -- ^ @Spencer-99@, Spencer License 99
362    | SPL_1_0 -- ^ @SPL-1.0@, Sun Public License v1.0
363    | SSPL_1_0 -- ^ @SSPL-1.0@, Server Side Public License, v 1, SPDX License List 3.6
364    | SugarCRM_1_1_3 -- ^ @SugarCRM-1.1.3@, SugarCRM Public License v1.1.3
365    | SWL -- ^ @SWL@, Scheme Widget Library (SWL) Software License Agreement
366    | TAPR_OHL_1_0 -- ^ @TAPR-OHL-1.0@, TAPR Open Hardware License v1.0, SPDX License List 3.6
367    | TCL -- ^ @TCL@, TCL/TK License
368    | TCP_wrappers -- ^ @TCP-wrappers@, TCP Wrappers License
369    | TMate -- ^ @TMate@, TMate Open Source License
370    | TORQUE_1_1 -- ^ @TORQUE-1.1@, TORQUE v2.5+ Software License v1.1
371    | TOSL -- ^ @TOSL@, Trusster Open Source License
372    | TU_Berlin_1_0 -- ^ @TU-Berlin-1.0@, Technische Universitaet Berlin License 1.0, SPDX License List 3.2, SPDX License List 3.6
373    | TU_Berlin_2_0 -- ^ @TU-Berlin-2.0@, Technische Universitaet Berlin License 2.0, SPDX License List 3.2, SPDX License List 3.6
374    | Unicode_DFS_2015 -- ^ @Unicode-DFS-2015@, Unicode License Agreement - Data Files and Software (2015)
375    | Unicode_DFS_2016 -- ^ @Unicode-DFS-2016@, Unicode License Agreement - Data Files and Software (2016)
376    | Unicode_TOU -- ^ @Unicode-TOU@, Unicode Terms of Use
377    | Unlicense -- ^ @Unlicense@, The Unlicense
378    | UPL_1_0 -- ^ @UPL-1.0@, Universal Permissive License v1.0
379    | Vim -- ^ @Vim@, Vim License
380    | VOSTROM -- ^ @VOSTROM@, VOSTROM Public License for Open Source
381    | VSL_1_0 -- ^ @VSL-1.0@, Vovida Software License v1.0
382    | W3C_19980720 -- ^ @W3C-19980720@, W3C Software Notice and License (1998-07-20)
383    | W3C_20150513 -- ^ @W3C-20150513@, W3C Software Notice and Document License (2015-05-13)
384    | W3C -- ^ @W3C@, W3C Software Notice and License (2002-12-31)
385    | Watcom_1_0 -- ^ @Watcom-1.0@, Sybase Open Watcom Public License 1.0
386    | Wsuipa -- ^ @Wsuipa@, Wsuipa License
387    | WTFPL -- ^ @WTFPL@, Do What The F*ck You Want To Public License
388    | X11 -- ^ @X11@, X11 License
389    | Xerox -- ^ @Xerox@, Xerox License
390    | XFree86_1_1 -- ^ @XFree86-1.1@, XFree86 License 1.1
391    | Xinetd -- ^ @xinetd@, xinetd License
392    | Xnet -- ^ @Xnet@, X.Net License
393    | Xpp -- ^ @xpp@, XPP License
394    | XSkat -- ^ @XSkat@, XSkat License
395    | YPL_1_0 -- ^ @YPL-1.0@, Yahoo! Public License v1.0
396    | YPL_1_1 -- ^ @YPL-1.1@, Yahoo! Public License v1.1
397    | Zed -- ^ @Zed@, Zed License
398    | Zend_2_0 -- ^ @Zend-2.0@, Zend License v2.0
399    | Zimbra_1_3 -- ^ @Zimbra-1.3@, Zimbra Public License v1.3
400    | Zimbra_1_4 -- ^ @Zimbra-1.4@, Zimbra Public License v1.4
401    | Zlib_acknowledgement -- ^ @zlib-acknowledgement@, zlib/libpng License with Acknowledgement
402    | Zlib -- ^ @Zlib@, zlib License
403    | ZPL_1_1 -- ^ @ZPL-1.1@, Zope Public License 1.1
404    | ZPL_2_0 -- ^ @ZPL-2.0@, Zope Public License 2.0
405    | ZPL_2_1 -- ^ @ZPL-2.1@, Zope Public License 2.1
406  deriving (Eq, Ord, Enum, Bounded, Show, Read, Typeable, Data, Generic)
407
408instance Binary LicenseId where
409    -- Word16 is encoded in big endianess
410    -- https://github.com/kolmodin/binary/blob/master/src/Data/Binary/Class.hs#L220-LL227
411    put = Binary.putWord16be . fromIntegral . fromEnum
412    get = do
413        i <- Binary.getWord16be
414        if i > fromIntegral (fromEnum (maxBound :: LicenseId))
415        then fail "Too large LicenseId tag"
416        else return (toEnum (fromIntegral i))
417
418-- note: remember to bump version each time the definition changes
419instance Structured LicenseId where
420    structure p = set typeVersion 306 $ nominalStructure p
421
422instance Pretty LicenseId where
423    pretty = Disp.text . licenseId
424
425-- |
426-- >>> eitherParsec "BSD-3-Clause" :: Either String LicenseId
427-- Right BSD_3_Clause
428--
429-- >>> eitherParsec "BSD3" :: Either String LicenseId
430-- Left "...Unknown SPDX license identifier: 'BSD3' Do you mean BSD-3-Clause?"
431--
432instance Parsec LicenseId where
433    parsec = do
434        n <- some $ P.satisfy $ \c -> isAsciiAlphaNum c || c == '-' || c == '.'
435        v <- askCabalSpecVersion
436        maybe (fail $ "Unknown SPDX license identifier: '" ++  n ++ "' " ++ licenseIdMigrationMessage n) return $
437            mkLicenseId (cabalSpecVersionToSPDXListVersion v) n
438
439instance NFData LicenseId where
440    rnf l = l `seq` ()
441
442-- | Help message for migrating from non-SPDX license identifiers.
443--
444-- Old 'License' is almost SPDX, except for 'BSD2', 'BSD3'. This function
445-- suggests SPDX variant:
446--
447-- >>> licenseIdMigrationMessage "BSD3"
448-- "Do you mean BSD-3-Clause?"
449--
450-- Also 'OtherLicense', 'AllRightsReserved', and 'PublicDomain' aren't
451-- valid SPDX identifiers
452--
453-- >>> traverse_ (print . licenseIdMigrationMessage) [ "OtherLicense", "AllRightsReserved", "PublicDomain" ]
454-- "SPDX license list contains plenty of licenses. See https://spdx.org/licenses/. Also they can be combined into complex expressions with AND and OR."
455-- "You can use NONE as a value of license field."
456-- "Public Domain is a complex matter. See https://wiki.spdx.org/view/Legal_Team/Decisions/Dealing_with_Public_Domain_within_SPDX_Files. Consider using a proper license."
457--
458-- SPDX License list version 3.0 introduced "-only" and "-or-later" variants for GNU family of licenses.
459-- See <https://spdx.org/news/news/2018/01/license-list-30-released>
460-- >>> licenseIdMigrationMessage "GPL-2.0"
461-- "SPDX license list 3.0 deprecated suffixless variants of GNU family of licenses. Use GPL-2.0-only or GPL-2.0-or-later."
462--
463-- For other common licenses their old license format coincides with the SPDX identifiers:
464--
465-- >>> traverse eitherParsec ["GPL-2.0-only", "GPL-3.0-only", "LGPL-2.1-only", "MIT", "ISC", "MPL-2.0", "Apache-2.0"] :: Either String [LicenseId]
466-- Right [GPL_2_0_only,GPL_3_0_only,LGPL_2_1_only,MIT,ISC,MPL_2_0,Apache_2_0]
467--
468licenseIdMigrationMessage :: String -> String
469licenseIdMigrationMessage = go where
470    go l | gnuVariant l    = "SPDX license list 3.0 deprecated suffixless variants of GNU family of licenses. Use " ++ l ++ "-only or " ++ l ++ "-or-later."
471    go "BSD3"              = "Do you mean BSD-3-Clause?"
472    go "BSD2"              = "Do you mean BSD-2-Clause?"
473    go "AllRightsReserved" = "You can use NONE as a value of license field."
474    go "OtherLicense"      = "SPDX license list contains plenty of licenses. See https://spdx.org/licenses/. Also they can be combined into complex expressions with AND and OR."
475    go "PublicDomain"      = "Public Domain is a complex matter. See https://wiki.spdx.org/view/Legal_Team/Decisions/Dealing_with_Public_Domain_within_SPDX_Files. Consider using a proper license."
476
477    -- otherwise, we don't know
478    go _ = ""
479
480    gnuVariant = flip elem ["GPL-2.0", "GPL-3.0", "LGPL-2.1", "LGPL-3.0", "AGPL-3.0" ]
481
482-------------------------------------------------------------------------------
483-- License Data
484-------------------------------------------------------------------------------
485
486-- | License SPDX identifier, e.g. @"BSD-3-Clause"@.
487licenseId :: LicenseId -> String
488licenseId NullBSD = "0BSD"
489licenseId AAL = "AAL"
490licenseId Abstyles = "Abstyles"
491licenseId Adobe_2006 = "Adobe-2006"
492licenseId Adobe_Glyph = "Adobe-Glyph"
493licenseId ADSL = "ADSL"
494licenseId AFL_1_1 = "AFL-1.1"
495licenseId AFL_1_2 = "AFL-1.2"
496licenseId AFL_2_0 = "AFL-2.0"
497licenseId AFL_2_1 = "AFL-2.1"
498licenseId AFL_3_0 = "AFL-3.0"
499licenseId Afmparse = "Afmparse"
500licenseId AGPL_1_0 = "AGPL-1.0"
501licenseId AGPL_1_0_only = "AGPL-1.0-only"
502licenseId AGPL_1_0_or_later = "AGPL-1.0-or-later"
503licenseId AGPL_3_0_only = "AGPL-3.0-only"
504licenseId AGPL_3_0_or_later = "AGPL-3.0-or-later"
505licenseId Aladdin = "Aladdin"
506licenseId AMDPLPA = "AMDPLPA"
507licenseId AML = "AML"
508licenseId AMPAS = "AMPAS"
509licenseId ANTLR_PD = "ANTLR-PD"
510licenseId Apache_1_0 = "Apache-1.0"
511licenseId Apache_1_1 = "Apache-1.1"
512licenseId Apache_2_0 = "Apache-2.0"
513licenseId APAFML = "APAFML"
514licenseId APL_1_0 = "APL-1.0"
515licenseId APSL_1_0 = "APSL-1.0"
516licenseId APSL_1_1 = "APSL-1.1"
517licenseId APSL_1_2 = "APSL-1.2"
518licenseId APSL_2_0 = "APSL-2.0"
519licenseId Artistic_1_0_cl8 = "Artistic-1.0-cl8"
520licenseId Artistic_1_0_Perl = "Artistic-1.0-Perl"
521licenseId Artistic_1_0 = "Artistic-1.0"
522licenseId Artistic_2_0 = "Artistic-2.0"
523licenseId Bahyph = "Bahyph"
524licenseId Barr = "Barr"
525licenseId Beerware = "Beerware"
526licenseId BitTorrent_1_0 = "BitTorrent-1.0"
527licenseId BitTorrent_1_1 = "BitTorrent-1.1"
528licenseId Blessing = "blessing"
529licenseId BlueOak_1_0_0 = "BlueOak-1.0.0"
530licenseId Borceux = "Borceux"
531licenseId BSD_1_Clause = "BSD-1-Clause"
532licenseId BSD_2_Clause_FreeBSD = "BSD-2-Clause-FreeBSD"
533licenseId BSD_2_Clause_NetBSD = "BSD-2-Clause-NetBSD"
534licenseId BSD_2_Clause_Patent = "BSD-2-Clause-Patent"
535licenseId BSD_2_Clause = "BSD-2-Clause"
536licenseId BSD_3_Clause_Attribution = "BSD-3-Clause-Attribution"
537licenseId BSD_3_Clause_Clear = "BSD-3-Clause-Clear"
538licenseId BSD_3_Clause_LBNL = "BSD-3-Clause-LBNL"
539licenseId BSD_3_Clause_No_Nuclear_License_2014 = "BSD-3-Clause-No-Nuclear-License-2014"
540licenseId BSD_3_Clause_No_Nuclear_License = "BSD-3-Clause-No-Nuclear-License"
541licenseId BSD_3_Clause_No_Nuclear_Warranty = "BSD-3-Clause-No-Nuclear-Warranty"
542licenseId BSD_3_Clause_Open_MPI = "BSD-3-Clause-Open-MPI"
543licenseId BSD_3_Clause = "BSD-3-Clause"
544licenseId BSD_4_Clause_UC = "BSD-4-Clause-UC"
545licenseId BSD_4_Clause = "BSD-4-Clause"
546licenseId BSD_Protection = "BSD-Protection"
547licenseId BSD_Source_Code = "BSD-Source-Code"
548licenseId BSL_1_0 = "BSL-1.0"
549licenseId Bzip2_1_0_5 = "bzip2-1.0.5"
550licenseId Bzip2_1_0_6 = "bzip2-1.0.6"
551licenseId Caldera = "Caldera"
552licenseId CATOSL_1_1 = "CATOSL-1.1"
553licenseId CC_BY_1_0 = "CC-BY-1.0"
554licenseId CC_BY_2_0 = "CC-BY-2.0"
555licenseId CC_BY_2_5 = "CC-BY-2.5"
556licenseId CC_BY_3_0 = "CC-BY-3.0"
557licenseId CC_BY_4_0 = "CC-BY-4.0"
558licenseId CC_BY_NC_1_0 = "CC-BY-NC-1.0"
559licenseId CC_BY_NC_2_0 = "CC-BY-NC-2.0"
560licenseId CC_BY_NC_2_5 = "CC-BY-NC-2.5"
561licenseId CC_BY_NC_3_0 = "CC-BY-NC-3.0"
562licenseId CC_BY_NC_4_0 = "CC-BY-NC-4.0"
563licenseId CC_BY_NC_ND_1_0 = "CC-BY-NC-ND-1.0"
564licenseId CC_BY_NC_ND_2_0 = "CC-BY-NC-ND-2.0"
565licenseId CC_BY_NC_ND_2_5 = "CC-BY-NC-ND-2.5"
566licenseId CC_BY_NC_ND_3_0 = "CC-BY-NC-ND-3.0"
567licenseId CC_BY_NC_ND_4_0 = "CC-BY-NC-ND-4.0"
568licenseId CC_BY_NC_SA_1_0 = "CC-BY-NC-SA-1.0"
569licenseId CC_BY_NC_SA_2_0 = "CC-BY-NC-SA-2.0"
570licenseId CC_BY_NC_SA_2_5 = "CC-BY-NC-SA-2.5"
571licenseId CC_BY_NC_SA_3_0 = "CC-BY-NC-SA-3.0"
572licenseId CC_BY_NC_SA_4_0 = "CC-BY-NC-SA-4.0"
573licenseId CC_BY_ND_1_0 = "CC-BY-ND-1.0"
574licenseId CC_BY_ND_2_0 = "CC-BY-ND-2.0"
575licenseId CC_BY_ND_2_5 = "CC-BY-ND-2.5"
576licenseId CC_BY_ND_3_0 = "CC-BY-ND-3.0"
577licenseId CC_BY_ND_4_0 = "CC-BY-ND-4.0"
578licenseId CC_BY_SA_1_0 = "CC-BY-SA-1.0"
579licenseId CC_BY_SA_2_0 = "CC-BY-SA-2.0"
580licenseId CC_BY_SA_2_5 = "CC-BY-SA-2.5"
581licenseId CC_BY_SA_3_0 = "CC-BY-SA-3.0"
582licenseId CC_BY_SA_4_0 = "CC-BY-SA-4.0"
583licenseId CC_PDDC = "CC-PDDC"
584licenseId CC0_1_0 = "CC0-1.0"
585licenseId CDDL_1_0 = "CDDL-1.0"
586licenseId CDDL_1_1 = "CDDL-1.1"
587licenseId CDLA_Permissive_1_0 = "CDLA-Permissive-1.0"
588licenseId CDLA_Sharing_1_0 = "CDLA-Sharing-1.0"
589licenseId CECILL_1_0 = "CECILL-1.0"
590licenseId CECILL_1_1 = "CECILL-1.1"
591licenseId CECILL_2_0 = "CECILL-2.0"
592licenseId CECILL_2_1 = "CECILL-2.1"
593licenseId CECILL_B = "CECILL-B"
594licenseId CECILL_C = "CECILL-C"
595licenseId CERN_OHL_1_1 = "CERN-OHL-1.1"
596licenseId CERN_OHL_1_2 = "CERN-OHL-1.2"
597licenseId ClArtistic = "ClArtistic"
598licenseId CNRI_Jython = "CNRI-Jython"
599licenseId CNRI_Python_GPL_Compatible = "CNRI-Python-GPL-Compatible"
600licenseId CNRI_Python = "CNRI-Python"
601licenseId Condor_1_1 = "Condor-1.1"
602licenseId Copyleft_next_0_3_0 = "copyleft-next-0.3.0"
603licenseId Copyleft_next_0_3_1 = "copyleft-next-0.3.1"
604licenseId CPAL_1_0 = "CPAL-1.0"
605licenseId CPL_1_0 = "CPL-1.0"
606licenseId CPOL_1_02 = "CPOL-1.02"
607licenseId Crossword = "Crossword"
608licenseId CrystalStacker = "CrystalStacker"
609licenseId CUA_OPL_1_0 = "CUA-OPL-1.0"
610licenseId Cube = "Cube"
611licenseId Curl = "curl"
612licenseId D_FSL_1_0 = "D-FSL-1.0"
613licenseId Diffmark = "diffmark"
614licenseId DOC = "DOC"
615licenseId Dotseqn = "Dotseqn"
616licenseId DSDP = "DSDP"
617licenseId Dvipdfm = "dvipdfm"
618licenseId ECL_1_0 = "ECL-1.0"
619licenseId ECL_2_0 = "ECL-2.0"
620licenseId EFL_1_0 = "EFL-1.0"
621licenseId EFL_2_0 = "EFL-2.0"
622licenseId EGenix = "eGenix"
623licenseId Entessa = "Entessa"
624licenseId EPL_1_0 = "EPL-1.0"
625licenseId EPL_2_0 = "EPL-2.0"
626licenseId ErlPL_1_1 = "ErlPL-1.1"
627licenseId EUDatagrid = "EUDatagrid"
628licenseId EUPL_1_0 = "EUPL-1.0"
629licenseId EUPL_1_1 = "EUPL-1.1"
630licenseId EUPL_1_2 = "EUPL-1.2"
631licenseId Eurosym = "Eurosym"
632licenseId Fair = "Fair"
633licenseId Frameworx_1_0 = "Frameworx-1.0"
634licenseId FreeImage = "FreeImage"
635licenseId FSFAP = "FSFAP"
636licenseId FSFULLR = "FSFULLR"
637licenseId FSFUL = "FSFUL"
638licenseId FTL = "FTL"
639licenseId GFDL_1_1_only = "GFDL-1.1-only"
640licenseId GFDL_1_1_or_later = "GFDL-1.1-or-later"
641licenseId GFDL_1_2_only = "GFDL-1.2-only"
642licenseId GFDL_1_2_or_later = "GFDL-1.2-or-later"
643licenseId GFDL_1_3_only = "GFDL-1.3-only"
644licenseId GFDL_1_3_or_later = "GFDL-1.3-or-later"
645licenseId Giftware = "Giftware"
646licenseId GL2PS = "GL2PS"
647licenseId Glide = "Glide"
648licenseId Glulxe = "Glulxe"
649licenseId Gnuplot = "gnuplot"
650licenseId GPL_1_0_only = "GPL-1.0-only"
651licenseId GPL_1_0_or_later = "GPL-1.0-or-later"
652licenseId GPL_2_0_only = "GPL-2.0-only"
653licenseId GPL_2_0_or_later = "GPL-2.0-or-later"
654licenseId GPL_3_0_only = "GPL-3.0-only"
655licenseId GPL_3_0_or_later = "GPL-3.0-or-later"
656licenseId GSOAP_1_3b = "gSOAP-1.3b"
657licenseId HaskellReport = "HaskellReport"
658licenseId HPND_sell_variant = "HPND-sell-variant"
659licenseId HPND = "HPND"
660licenseId IBM_pibs = "IBM-pibs"
661licenseId ICU = "ICU"
662licenseId IJG = "IJG"
663licenseId ImageMagick = "ImageMagick"
664licenseId IMatix = "iMatix"
665licenseId Imlib2 = "Imlib2"
666licenseId Info_ZIP = "Info-ZIP"
667licenseId Intel_ACPI = "Intel-ACPI"
668licenseId Intel = "Intel"
669licenseId Interbase_1_0 = "Interbase-1.0"
670licenseId IPA = "IPA"
671licenseId IPL_1_0 = "IPL-1.0"
672licenseId ISC = "ISC"
673licenseId JasPer_2_0 = "JasPer-2.0"
674licenseId JPNIC = "JPNIC"
675licenseId JSON = "JSON"
676licenseId LAL_1_2 = "LAL-1.2"
677licenseId LAL_1_3 = "LAL-1.3"
678licenseId Latex2e = "Latex2e"
679licenseId Leptonica = "Leptonica"
680licenseId LGPL_2_0_only = "LGPL-2.0-only"
681licenseId LGPL_2_0_or_later = "LGPL-2.0-or-later"
682licenseId LGPL_2_1_only = "LGPL-2.1-only"
683licenseId LGPL_2_1_or_later = "LGPL-2.1-or-later"
684licenseId LGPL_3_0_only = "LGPL-3.0-only"
685licenseId LGPL_3_0_or_later = "LGPL-3.0-or-later"
686licenseId LGPLLR = "LGPLLR"
687licenseId Libpng_2_0 = "libpng-2.0"
688licenseId Libpng = "Libpng"
689licenseId Libtiff = "libtiff"
690licenseId LiLiQ_P_1_1 = "LiLiQ-P-1.1"
691licenseId LiLiQ_R_1_1 = "LiLiQ-R-1.1"
692licenseId LiLiQ_Rplus_1_1 = "LiLiQ-Rplus-1.1"
693licenseId Linux_OpenIB = "Linux-OpenIB"
694licenseId LPL_1_02 = "LPL-1.02"
695licenseId LPL_1_0 = "LPL-1.0"
696licenseId LPPL_1_0 = "LPPL-1.0"
697licenseId LPPL_1_1 = "LPPL-1.1"
698licenseId LPPL_1_2 = "LPPL-1.2"
699licenseId LPPL_1_3a = "LPPL-1.3a"
700licenseId LPPL_1_3c = "LPPL-1.3c"
701licenseId MakeIndex = "MakeIndex"
702licenseId MirOS = "MirOS"
703licenseId MIT_0 = "MIT-0"
704licenseId MIT_advertising = "MIT-advertising"
705licenseId MIT_CMU = "MIT-CMU"
706licenseId MIT_enna = "MIT-enna"
707licenseId MIT_feh = "MIT-feh"
708licenseId MITNFA = "MITNFA"
709licenseId MIT = "MIT"
710licenseId Motosoto = "Motosoto"
711licenseId Mpich2 = "mpich2"
712licenseId MPL_1_0 = "MPL-1.0"
713licenseId MPL_1_1 = "MPL-1.1"
714licenseId MPL_2_0_no_copyleft_exception = "MPL-2.0-no-copyleft-exception"
715licenseId MPL_2_0 = "MPL-2.0"
716licenseId MS_PL = "MS-PL"
717licenseId MS_RL = "MS-RL"
718licenseId MTLL = "MTLL"
719licenseId Multics = "Multics"
720licenseId Mup = "Mup"
721licenseId NASA_1_3 = "NASA-1.3"
722licenseId Naumen = "Naumen"
723licenseId NBPL_1_0 = "NBPL-1.0"
724licenseId NCSA = "NCSA"
725licenseId Net_SNMP = "Net-SNMP"
726licenseId NetCDF = "NetCDF"
727licenseId Newsletr = "Newsletr"
728licenseId NGPL = "NGPL"
729licenseId NLOD_1_0 = "NLOD-1.0"
730licenseId NLPL = "NLPL"
731licenseId Nokia = "Nokia"
732licenseId NOSL = "NOSL"
733licenseId Noweb = "Noweb"
734licenseId NPL_1_0 = "NPL-1.0"
735licenseId NPL_1_1 = "NPL-1.1"
736licenseId NPOSL_3_0 = "NPOSL-3.0"
737licenseId NRL = "NRL"
738licenseId NTP = "NTP"
739licenseId OCCT_PL = "OCCT-PL"
740licenseId OCLC_2_0 = "OCLC-2.0"
741licenseId ODbL_1_0 = "ODbL-1.0"
742licenseId ODC_By_1_0 = "ODC-By-1.0"
743licenseId OFL_1_0 = "OFL-1.0"
744licenseId OFL_1_1 = "OFL-1.1"
745licenseId OGL_UK_1_0 = "OGL-UK-1.0"
746licenseId OGL_UK_2_0 = "OGL-UK-2.0"
747licenseId OGL_UK_3_0 = "OGL-UK-3.0"
748licenseId OGTSL = "OGTSL"
749licenseId OLDAP_1_1 = "OLDAP-1.1"
750licenseId OLDAP_1_2 = "OLDAP-1.2"
751licenseId OLDAP_1_3 = "OLDAP-1.3"
752licenseId OLDAP_1_4 = "OLDAP-1.4"
753licenseId OLDAP_2_0_1 = "OLDAP-2.0.1"
754licenseId OLDAP_2_0 = "OLDAP-2.0"
755licenseId OLDAP_2_1 = "OLDAP-2.1"
756licenseId OLDAP_2_2_1 = "OLDAP-2.2.1"
757licenseId OLDAP_2_2_2 = "OLDAP-2.2.2"
758licenseId OLDAP_2_2 = "OLDAP-2.2"
759licenseId OLDAP_2_3 = "OLDAP-2.3"
760licenseId OLDAP_2_4 = "OLDAP-2.4"
761licenseId OLDAP_2_5 = "OLDAP-2.5"
762licenseId OLDAP_2_6 = "OLDAP-2.6"
763licenseId OLDAP_2_7 = "OLDAP-2.7"
764licenseId OLDAP_2_8 = "OLDAP-2.8"
765licenseId OML = "OML"
766licenseId OpenSSL = "OpenSSL"
767licenseId OPL_1_0 = "OPL-1.0"
768licenseId OSET_PL_2_1 = "OSET-PL-2.1"
769licenseId OSL_1_0 = "OSL-1.0"
770licenseId OSL_1_1 = "OSL-1.1"
771licenseId OSL_2_0 = "OSL-2.0"
772licenseId OSL_2_1 = "OSL-2.1"
773licenseId OSL_3_0 = "OSL-3.0"
774licenseId Parity_6_0_0 = "Parity-6.0.0"
775licenseId PDDL_1_0 = "PDDL-1.0"
776licenseId PHP_3_01 = "PHP-3.01"
777licenseId PHP_3_0 = "PHP-3.0"
778licenseId Plexus = "Plexus"
779licenseId PostgreSQL = "PostgreSQL"
780licenseId Psfrag = "psfrag"
781licenseId Psutils = "psutils"
782licenseId Python_2_0 = "Python-2.0"
783licenseId Qhull = "Qhull"
784licenseId QPL_1_0 = "QPL-1.0"
785licenseId Rdisc = "Rdisc"
786licenseId RHeCos_1_1 = "RHeCos-1.1"
787licenseId RPL_1_1 = "RPL-1.1"
788licenseId RPL_1_5 = "RPL-1.5"
789licenseId RPSL_1_0 = "RPSL-1.0"
790licenseId RSA_MD = "RSA-MD"
791licenseId RSCPL = "RSCPL"
792licenseId Ruby = "Ruby"
793licenseId SAX_PD = "SAX-PD"
794licenseId Saxpath = "Saxpath"
795licenseId SCEA = "SCEA"
796licenseId Sendmail_8_23 = "Sendmail-8.23"
797licenseId Sendmail = "Sendmail"
798licenseId SGI_B_1_0 = "SGI-B-1.0"
799licenseId SGI_B_1_1 = "SGI-B-1.1"
800licenseId SGI_B_2_0 = "SGI-B-2.0"
801licenseId SHL_0_51 = "SHL-0.51"
802licenseId SHL_0_5 = "SHL-0.5"
803licenseId SimPL_2_0 = "SimPL-2.0"
804licenseId SISSL_1_2 = "SISSL-1.2"
805licenseId SISSL = "SISSL"
806licenseId Sleepycat = "Sleepycat"
807licenseId SMLNJ = "SMLNJ"
808licenseId SMPPL = "SMPPL"
809licenseId SNIA = "SNIA"
810licenseId Spencer_86 = "Spencer-86"
811licenseId Spencer_94 = "Spencer-94"
812licenseId Spencer_99 = "Spencer-99"
813licenseId SPL_1_0 = "SPL-1.0"
814licenseId SSPL_1_0 = "SSPL-1.0"
815licenseId SugarCRM_1_1_3 = "SugarCRM-1.1.3"
816licenseId SWL = "SWL"
817licenseId TAPR_OHL_1_0 = "TAPR-OHL-1.0"
818licenseId TCL = "TCL"
819licenseId TCP_wrappers = "TCP-wrappers"
820licenseId TMate = "TMate"
821licenseId TORQUE_1_1 = "TORQUE-1.1"
822licenseId TOSL = "TOSL"
823licenseId TU_Berlin_1_0 = "TU-Berlin-1.0"
824licenseId TU_Berlin_2_0 = "TU-Berlin-2.0"
825licenseId Unicode_DFS_2015 = "Unicode-DFS-2015"
826licenseId Unicode_DFS_2016 = "Unicode-DFS-2016"
827licenseId Unicode_TOU = "Unicode-TOU"
828licenseId Unlicense = "Unlicense"
829licenseId UPL_1_0 = "UPL-1.0"
830licenseId Vim = "Vim"
831licenseId VOSTROM = "VOSTROM"
832licenseId VSL_1_0 = "VSL-1.0"
833licenseId W3C_19980720 = "W3C-19980720"
834licenseId W3C_20150513 = "W3C-20150513"
835licenseId W3C = "W3C"
836licenseId Watcom_1_0 = "Watcom-1.0"
837licenseId Wsuipa = "Wsuipa"
838licenseId WTFPL = "WTFPL"
839licenseId X11 = "X11"
840licenseId Xerox = "Xerox"
841licenseId XFree86_1_1 = "XFree86-1.1"
842licenseId Xinetd = "xinetd"
843licenseId Xnet = "Xnet"
844licenseId Xpp = "xpp"
845licenseId XSkat = "XSkat"
846licenseId YPL_1_0 = "YPL-1.0"
847licenseId YPL_1_1 = "YPL-1.1"
848licenseId Zed = "Zed"
849licenseId Zend_2_0 = "Zend-2.0"
850licenseId Zimbra_1_3 = "Zimbra-1.3"
851licenseId Zimbra_1_4 = "Zimbra-1.4"
852licenseId Zlib_acknowledgement = "zlib-acknowledgement"
853licenseId Zlib = "Zlib"
854licenseId ZPL_1_1 = "ZPL-1.1"
855licenseId ZPL_2_0 = "ZPL-2.0"
856licenseId ZPL_2_1 = "ZPL-2.1"
857
858-- | License name, e.g. @"GNU General Public License v2.0 only"@
859licenseName :: LicenseId -> String
860licenseName NullBSD = "BSD Zero Clause License"
861licenseName AAL = "Attribution Assurance License"
862licenseName Abstyles = "Abstyles License"
863licenseName Adobe_2006 = "Adobe Systems Incorporated Source Code License Agreement"
864licenseName Adobe_Glyph = "Adobe Glyph List License"
865licenseName ADSL = "Amazon Digital Services License"
866licenseName AFL_1_1 = "Academic Free License v1.1"
867licenseName AFL_1_2 = "Academic Free License v1.2"
868licenseName AFL_2_0 = "Academic Free License v2.0"
869licenseName AFL_2_1 = "Academic Free License v2.1"
870licenseName AFL_3_0 = "Academic Free License v3.0"
871licenseName Afmparse = "Afmparse License"
872licenseName AGPL_1_0 = "Affero General Public License v1.0"
873licenseName AGPL_1_0_only = "Affero General Public License v1.0 only"
874licenseName AGPL_1_0_or_later = "Affero General Public License v1.0 or later"
875licenseName AGPL_3_0_only = "GNU Affero General Public License v3.0 only"
876licenseName AGPL_3_0_or_later = "GNU Affero General Public License v3.0 or later"
877licenseName Aladdin = "Aladdin Free Public License"
878licenseName AMDPLPA = "AMD's plpa_map.c License"
879licenseName AML = "Apple MIT License"
880licenseName AMPAS = "Academy of Motion Picture Arts and Sciences BSD"
881licenseName ANTLR_PD = "ANTLR Software Rights Notice"
882licenseName Apache_1_0 = "Apache License 1.0"
883licenseName Apache_1_1 = "Apache License 1.1"
884licenseName Apache_2_0 = "Apache License 2.0"
885licenseName APAFML = "Adobe Postscript AFM License"
886licenseName APL_1_0 = "Adaptive Public License 1.0"
887licenseName APSL_1_0 = "Apple Public Source License 1.0"
888licenseName APSL_1_1 = "Apple Public Source License 1.1"
889licenseName APSL_1_2 = "Apple Public Source License 1.2"
890licenseName APSL_2_0 = "Apple Public Source License 2.0"
891licenseName Artistic_1_0_cl8 = "Artistic License 1.0 w/clause 8"
892licenseName Artistic_1_0_Perl = "Artistic License 1.0 (Perl)"
893licenseName Artistic_1_0 = "Artistic License 1.0"
894licenseName Artistic_2_0 = "Artistic License 2.0"
895licenseName Bahyph = "Bahyph License"
896licenseName Barr = "Barr License"
897licenseName Beerware = "Beerware License"
898licenseName BitTorrent_1_0 = "BitTorrent Open Source License v1.0"
899licenseName BitTorrent_1_1 = "BitTorrent Open Source License v1.1"
900licenseName Blessing = "SQLite Blessing"
901licenseName BlueOak_1_0_0 = "Blue Oak Model License 1.0.0"
902licenseName Borceux = "Borceux license"
903licenseName BSD_1_Clause = "BSD 1-Clause License"
904licenseName BSD_2_Clause_FreeBSD = "BSD 2-Clause FreeBSD License"
905licenseName BSD_2_Clause_NetBSD = "BSD 2-Clause NetBSD License"
906licenseName BSD_2_Clause_Patent = "BSD-2-Clause Plus Patent License"
907licenseName BSD_2_Clause = "BSD 2-Clause \"Simplified\" License"
908licenseName BSD_3_Clause_Attribution = "BSD with attribution"
909licenseName BSD_3_Clause_Clear = "BSD 3-Clause Clear License"
910licenseName BSD_3_Clause_LBNL = "Lawrence Berkeley National Labs BSD variant license"
911licenseName BSD_3_Clause_No_Nuclear_License_2014 = "BSD 3-Clause No Nuclear License 2014"
912licenseName BSD_3_Clause_No_Nuclear_License = "BSD 3-Clause No Nuclear License"
913licenseName BSD_3_Clause_No_Nuclear_Warranty = "BSD 3-Clause No Nuclear Warranty"
914licenseName BSD_3_Clause_Open_MPI = "BSD 3-Clause Open MPI variant"
915licenseName BSD_3_Clause = "BSD 3-Clause \"New\" or \"Revised\" License"
916licenseName BSD_4_Clause_UC = "BSD-4-Clause (University of California-Specific)"
917licenseName BSD_4_Clause = "BSD 4-Clause \"Original\" or \"Old\" License"
918licenseName BSD_Protection = "BSD Protection License"
919licenseName BSD_Source_Code = "BSD Source Code Attribution"
920licenseName BSL_1_0 = "Boost Software License 1.0"
921licenseName Bzip2_1_0_5 = "bzip2 and libbzip2 License v1.0.5"
922licenseName Bzip2_1_0_6 = "bzip2 and libbzip2 License v1.0.6"
923licenseName Caldera = "Caldera License"
924licenseName CATOSL_1_1 = "Computer Associates Trusted Open Source License 1.1"
925licenseName CC_BY_1_0 = "Creative Commons Attribution 1.0 Generic"
926licenseName CC_BY_2_0 = "Creative Commons Attribution 2.0 Generic"
927licenseName CC_BY_2_5 = "Creative Commons Attribution 2.5 Generic"
928licenseName CC_BY_3_0 = "Creative Commons Attribution 3.0 Unported"
929licenseName CC_BY_4_0 = "Creative Commons Attribution 4.0 International"
930licenseName CC_BY_NC_1_0 = "Creative Commons Attribution Non Commercial 1.0 Generic"
931licenseName CC_BY_NC_2_0 = "Creative Commons Attribution Non Commercial 2.0 Generic"
932licenseName CC_BY_NC_2_5 = "Creative Commons Attribution Non Commercial 2.5 Generic"
933licenseName CC_BY_NC_3_0 = "Creative Commons Attribution Non Commercial 3.0 Unported"
934licenseName CC_BY_NC_4_0 = "Creative Commons Attribution Non Commercial 4.0 International"
935licenseName CC_BY_NC_ND_1_0 = "Creative Commons Attribution Non Commercial No Derivatives 1.0 Generic"
936licenseName CC_BY_NC_ND_2_0 = "Creative Commons Attribution Non Commercial No Derivatives 2.0 Generic"
937licenseName CC_BY_NC_ND_2_5 = "Creative Commons Attribution Non Commercial No Derivatives 2.5 Generic"
938licenseName CC_BY_NC_ND_3_0 = "Creative Commons Attribution Non Commercial No Derivatives 3.0 Unported"
939licenseName CC_BY_NC_ND_4_0 = "Creative Commons Attribution Non Commercial No Derivatives 4.0 International"
940licenseName CC_BY_NC_SA_1_0 = "Creative Commons Attribution Non Commercial Share Alike 1.0 Generic"
941licenseName CC_BY_NC_SA_2_0 = "Creative Commons Attribution Non Commercial Share Alike 2.0 Generic"
942licenseName CC_BY_NC_SA_2_5 = "Creative Commons Attribution Non Commercial Share Alike 2.5 Generic"
943licenseName CC_BY_NC_SA_3_0 = "Creative Commons Attribution Non Commercial Share Alike 3.0 Unported"
944licenseName CC_BY_NC_SA_4_0 = "Creative Commons Attribution Non Commercial Share Alike 4.0 International"
945licenseName CC_BY_ND_1_0 = "Creative Commons Attribution No Derivatives 1.0 Generic"
946licenseName CC_BY_ND_2_0 = "Creative Commons Attribution No Derivatives 2.0 Generic"
947licenseName CC_BY_ND_2_5 = "Creative Commons Attribution No Derivatives 2.5 Generic"
948licenseName CC_BY_ND_3_0 = "Creative Commons Attribution No Derivatives 3.0 Unported"
949licenseName CC_BY_ND_4_0 = "Creative Commons Attribution No Derivatives 4.0 International"
950licenseName CC_BY_SA_1_0 = "Creative Commons Attribution Share Alike 1.0 Generic"
951licenseName CC_BY_SA_2_0 = "Creative Commons Attribution Share Alike 2.0 Generic"
952licenseName CC_BY_SA_2_5 = "Creative Commons Attribution Share Alike 2.5 Generic"
953licenseName CC_BY_SA_3_0 = "Creative Commons Attribution Share Alike 3.0 Unported"
954licenseName CC_BY_SA_4_0 = "Creative Commons Attribution Share Alike 4.0 International"
955licenseName CC_PDDC = "Creative Commons Public Domain Dedication and Certification"
956licenseName CC0_1_0 = "Creative Commons Zero v1.0 Universal"
957licenseName CDDL_1_0 = "Common Development and Distribution License 1.0"
958licenseName CDDL_1_1 = "Common Development and Distribution License 1.1"
959licenseName CDLA_Permissive_1_0 = "Community Data License Agreement Permissive 1.0"
960licenseName CDLA_Sharing_1_0 = "Community Data License Agreement Sharing 1.0"
961licenseName CECILL_1_0 = "CeCILL Free Software License Agreement v1.0"
962licenseName CECILL_1_1 = "CeCILL Free Software License Agreement v1.1"
963licenseName CECILL_2_0 = "CeCILL Free Software License Agreement v2.0"
964licenseName CECILL_2_1 = "CeCILL Free Software License Agreement v2.1"
965licenseName CECILL_B = "CeCILL-B Free Software License Agreement"
966licenseName CECILL_C = "CeCILL-C Free Software License Agreement"
967licenseName CERN_OHL_1_1 = "CERN Open Hardware License v1.1"
968licenseName CERN_OHL_1_2 = "CERN Open Hardware Licence v1.2"
969licenseName ClArtistic = "Clarified Artistic License"
970licenseName CNRI_Jython = "CNRI Jython License"
971licenseName CNRI_Python_GPL_Compatible = "CNRI Python Open Source GPL Compatible License Agreement"
972licenseName CNRI_Python = "CNRI Python License"
973licenseName Condor_1_1 = "Condor Public License v1.1"
974licenseName Copyleft_next_0_3_0 = "copyleft-next 0.3.0"
975licenseName Copyleft_next_0_3_1 = "copyleft-next 0.3.1"
976licenseName CPAL_1_0 = "Common Public Attribution License 1.0"
977licenseName CPL_1_0 = "Common Public License 1.0"
978licenseName CPOL_1_02 = "Code Project Open License 1.02"
979licenseName Crossword = "Crossword License"
980licenseName CrystalStacker = "CrystalStacker License"
981licenseName CUA_OPL_1_0 = "CUA Office Public License v1.0"
982licenseName Cube = "Cube License"
983licenseName Curl = "curl License"
984licenseName D_FSL_1_0 = "Deutsche Freie Software Lizenz"
985licenseName Diffmark = "diffmark license"
986licenseName DOC = "DOC License"
987licenseName Dotseqn = "Dotseqn License"
988licenseName DSDP = "DSDP License"
989licenseName Dvipdfm = "dvipdfm License"
990licenseName ECL_1_0 = "Educational Community License v1.0"
991licenseName ECL_2_0 = "Educational Community License v2.0"
992licenseName EFL_1_0 = "Eiffel Forum License v1.0"
993licenseName EFL_2_0 = "Eiffel Forum License v2.0"
994licenseName EGenix = "eGenix.com Public License 1.1.0"
995licenseName Entessa = "Entessa Public License v1.0"
996licenseName EPL_1_0 = "Eclipse Public License 1.0"
997licenseName EPL_2_0 = "Eclipse Public License 2.0"
998licenseName ErlPL_1_1 = "Erlang Public License v1.1"
999licenseName EUDatagrid = "EU DataGrid Software License"
1000licenseName EUPL_1_0 = "European Union Public License 1.0"
1001licenseName EUPL_1_1 = "European Union Public License 1.1"
1002licenseName EUPL_1_2 = "European Union Public License 1.2"
1003licenseName Eurosym = "Eurosym License"
1004licenseName Fair = "Fair License"
1005licenseName Frameworx_1_0 = "Frameworx Open License 1.0"
1006licenseName FreeImage = "FreeImage Public License v1.0"
1007licenseName FSFAP = "FSF All Permissive License"
1008licenseName FSFULLR = "FSF Unlimited License (with License Retention)"
1009licenseName FSFUL = "FSF Unlimited License"
1010licenseName FTL = "Freetype Project License"
1011licenseName GFDL_1_1_only = "GNU Free Documentation License v1.1 only"
1012licenseName GFDL_1_1_or_later = "GNU Free Documentation License v1.1 or later"
1013licenseName GFDL_1_2_only = "GNU Free Documentation License v1.2 only"
1014licenseName GFDL_1_2_or_later = "GNU Free Documentation License v1.2 or later"
1015licenseName GFDL_1_3_only = "GNU Free Documentation License v1.3 only"
1016licenseName GFDL_1_3_or_later = "GNU Free Documentation License v1.3 or later"
1017licenseName Giftware = "Giftware License"
1018licenseName GL2PS = "GL2PS License"
1019licenseName Glide = "3dfx Glide License"
1020licenseName Glulxe = "Glulxe License"
1021licenseName Gnuplot = "gnuplot License"
1022licenseName GPL_1_0_only = "GNU General Public License v1.0 only"
1023licenseName GPL_1_0_or_later = "GNU General Public License v1.0 or later"
1024licenseName GPL_2_0_only = "GNU General Public License v2.0 only"
1025licenseName GPL_2_0_or_later = "GNU General Public License v2.0 or later"
1026licenseName GPL_3_0_only = "GNU General Public License v3.0 only"
1027licenseName GPL_3_0_or_later = "GNU General Public License v3.0 or later"
1028licenseName GSOAP_1_3b = "gSOAP Public License v1.3b"
1029licenseName HaskellReport = "Haskell Language Report License"
1030licenseName HPND_sell_variant = "Historical Permission Notice and Disclaimer - sell variant"
1031licenseName HPND = "Historical Permission Notice and Disclaimer"
1032licenseName IBM_pibs = "IBM PowerPC Initialization and Boot Software"
1033licenseName ICU = "ICU License"
1034licenseName IJG = "Independent JPEG Group License"
1035licenseName ImageMagick = "ImageMagick License"
1036licenseName IMatix = "iMatix Standard Function Library Agreement"
1037licenseName Imlib2 = "Imlib2 License"
1038licenseName Info_ZIP = "Info-ZIP License"
1039licenseName Intel_ACPI = "Intel ACPI Software License Agreement"
1040licenseName Intel = "Intel Open Source License"
1041licenseName Interbase_1_0 = "Interbase Public License v1.0"
1042licenseName IPA = "IPA Font License"
1043licenseName IPL_1_0 = "IBM Public License v1.0"
1044licenseName ISC = "ISC License"
1045licenseName JasPer_2_0 = "JasPer License"
1046licenseName JPNIC = "Japan Network Information Center License"
1047licenseName JSON = "JSON License"
1048licenseName LAL_1_2 = "Licence Art Libre 1.2"
1049licenseName LAL_1_3 = "Licence Art Libre 1.3"
1050licenseName Latex2e = "Latex2e License"
1051licenseName Leptonica = "Leptonica License"
1052licenseName LGPL_2_0_only = "GNU Library General Public License v2 only"
1053licenseName LGPL_2_0_or_later = "GNU Library General Public License v2 or later"
1054licenseName LGPL_2_1_only = "GNU Lesser General Public License v2.1 only"
1055licenseName LGPL_2_1_or_later = "GNU Lesser General Public License v2.1 or later"
1056licenseName LGPL_3_0_only = "GNU Lesser General Public License v3.0 only"
1057licenseName LGPL_3_0_or_later = "GNU Lesser General Public License v3.0 or later"
1058licenseName LGPLLR = "Lesser General Public License For Linguistic Resources"
1059licenseName Libpng_2_0 = "PNG Reference Library version 2"
1060licenseName Libpng = "libpng License"
1061licenseName Libtiff = "libtiff License"
1062licenseName LiLiQ_P_1_1 = "Licence Libre du Qu\233bec \8211 Permissive version 1.1"
1063licenseName LiLiQ_R_1_1 = "Licence Libre du Qu\233bec \8211 R\233ciprocit\233 version 1.1"
1064licenseName LiLiQ_Rplus_1_1 = "Licence Libre du Qu\233bec \8211 R\233ciprocit\233 forte version 1.1"
1065licenseName Linux_OpenIB = "Linux Kernel Variant of OpenIB.org license"
1066licenseName LPL_1_02 = "Lucent Public License v1.02"
1067licenseName LPL_1_0 = "Lucent Public License Version 1.0"
1068licenseName LPPL_1_0 = "LaTeX Project Public License v1.0"
1069licenseName LPPL_1_1 = "LaTeX Project Public License v1.1"
1070licenseName LPPL_1_2 = "LaTeX Project Public License v1.2"
1071licenseName LPPL_1_3a = "LaTeX Project Public License v1.3a"
1072licenseName LPPL_1_3c = "LaTeX Project Public License v1.3c"
1073licenseName MakeIndex = "MakeIndex License"
1074licenseName MirOS = "MirOS License"
1075licenseName MIT_0 = "MIT No Attribution"
1076licenseName MIT_advertising = "Enlightenment License (e16)"
1077licenseName MIT_CMU = "CMU License"
1078licenseName MIT_enna = "enna License"
1079licenseName MIT_feh = "feh License"
1080licenseName MITNFA = "MIT +no-false-attribs license"
1081licenseName MIT = "MIT License"
1082licenseName Motosoto = "Motosoto License"
1083licenseName Mpich2 = "mpich2 License"
1084licenseName MPL_1_0 = "Mozilla Public License 1.0"
1085licenseName MPL_1_1 = "Mozilla Public License 1.1"
1086licenseName MPL_2_0_no_copyleft_exception = "Mozilla Public License 2.0 (no copyleft exception)"
1087licenseName MPL_2_0 = "Mozilla Public License 2.0"
1088licenseName MS_PL = "Microsoft Public License"
1089licenseName MS_RL = "Microsoft Reciprocal License"
1090licenseName MTLL = "Matrix Template Library License"
1091licenseName Multics = "Multics License"
1092licenseName Mup = "Mup License"
1093licenseName NASA_1_3 = "NASA Open Source Agreement 1.3"
1094licenseName Naumen = "Naumen Public License"
1095licenseName NBPL_1_0 = "Net Boolean Public License v1"
1096licenseName NCSA = "University of Illinois/NCSA Open Source License"
1097licenseName Net_SNMP = "Net-SNMP License"
1098licenseName NetCDF = "NetCDF license"
1099licenseName Newsletr = "Newsletr License"
1100licenseName NGPL = "Nethack General Public License"
1101licenseName NLOD_1_0 = "Norwegian Licence for Open Government Data"
1102licenseName NLPL = "No Limit Public License"
1103licenseName Nokia = "Nokia Open Source License"
1104licenseName NOSL = "Netizen Open Source License"
1105licenseName Noweb = "Noweb License"
1106licenseName NPL_1_0 = "Netscape Public License v1.0"
1107licenseName NPL_1_1 = "Netscape Public License v1.1"
1108licenseName NPOSL_3_0 = "Non-Profit Open Software License 3.0"
1109licenseName NRL = "NRL License"
1110licenseName NTP = "NTP License"
1111licenseName OCCT_PL = "Open CASCADE Technology Public License"
1112licenseName OCLC_2_0 = "OCLC Research Public License 2.0"
1113licenseName ODbL_1_0 = "ODC Open Database License v1.0"
1114licenseName ODC_By_1_0 = "Open Data Commons Attribution License v1.0"
1115licenseName OFL_1_0 = "SIL Open Font License 1.0"
1116licenseName OFL_1_1 = "SIL Open Font License 1.1"
1117licenseName OGL_UK_1_0 = "Open Government Licence v1.0"
1118licenseName OGL_UK_2_0 = "Open Government Licence v2.0"
1119licenseName OGL_UK_3_0 = "Open Government Licence v3.0"
1120licenseName OGTSL = "Open Group Test Suite License"
1121licenseName OLDAP_1_1 = "Open LDAP Public License v1.1"
1122licenseName OLDAP_1_2 = "Open LDAP Public License v1.2"
1123licenseName OLDAP_1_3 = "Open LDAP Public License v1.3"
1124licenseName OLDAP_1_4 = "Open LDAP Public License v1.4"
1125licenseName OLDAP_2_0_1 = "Open LDAP Public License v2.0.1"
1126licenseName OLDAP_2_0 = "Open LDAP Public License v2.0 (or possibly 2.0A and 2.0B)"
1127licenseName OLDAP_2_1 = "Open LDAP Public License v2.1"
1128licenseName OLDAP_2_2_1 = "Open LDAP Public License v2.2.1"
1129licenseName OLDAP_2_2_2 = "Open LDAP Public License 2.2.2"
1130licenseName OLDAP_2_2 = "Open LDAP Public License v2.2"
1131licenseName OLDAP_2_3 = "Open LDAP Public License v2.3"
1132licenseName OLDAP_2_4 = "Open LDAP Public License v2.4"
1133licenseName OLDAP_2_5 = "Open LDAP Public License v2.5"
1134licenseName OLDAP_2_6 = "Open LDAP Public License v2.6"
1135licenseName OLDAP_2_7 = "Open LDAP Public License v2.7"
1136licenseName OLDAP_2_8 = "Open LDAP Public License v2.8"
1137licenseName OML = "Open Market License"
1138licenseName OpenSSL = "OpenSSL License"
1139licenseName OPL_1_0 = "Open Public License v1.0"
1140licenseName OSET_PL_2_1 = "OSET Public License version 2.1"
1141licenseName OSL_1_0 = "Open Software License 1.0"
1142licenseName OSL_1_1 = "Open Software License 1.1"
1143licenseName OSL_2_0 = "Open Software License 2.0"
1144licenseName OSL_2_1 = "Open Software License 2.1"
1145licenseName OSL_3_0 = "Open Software License 3.0"
1146licenseName Parity_6_0_0 = "The Parity Public License 6.0.0"
1147licenseName PDDL_1_0 = "ODC Public Domain Dedication & License 1.0"
1148licenseName PHP_3_01 = "PHP License v3.01"
1149licenseName PHP_3_0 = "PHP License v3.0"
1150licenseName Plexus = "Plexus Classworlds License"
1151licenseName PostgreSQL = "PostgreSQL License"
1152licenseName Psfrag = "psfrag License"
1153licenseName Psutils = "psutils License"
1154licenseName Python_2_0 = "Python License 2.0"
1155licenseName Qhull = "Qhull License"
1156licenseName QPL_1_0 = "Q Public License 1.0"
1157licenseName Rdisc = "Rdisc License"
1158licenseName RHeCos_1_1 = "Red Hat eCos Public License v1.1"
1159licenseName RPL_1_1 = "Reciprocal Public License 1.1"
1160licenseName RPL_1_5 = "Reciprocal Public License 1.5"
1161licenseName RPSL_1_0 = "RealNetworks Public Source License v1.0"
1162licenseName RSA_MD = "RSA Message-Digest License "
1163licenseName RSCPL = "Ricoh Source Code Public License"
1164licenseName Ruby = "Ruby License"
1165licenseName SAX_PD = "Sax Public Domain Notice"
1166licenseName Saxpath = "Saxpath License"
1167licenseName SCEA = "SCEA Shared Source License"
1168licenseName Sendmail_8_23 = "Sendmail License 8.23"
1169licenseName Sendmail = "Sendmail License"
1170licenseName SGI_B_1_0 = "SGI Free Software License B v1.0"
1171licenseName SGI_B_1_1 = "SGI Free Software License B v1.1"
1172licenseName SGI_B_2_0 = "SGI Free Software License B v2.0"
1173licenseName SHL_0_51 = "Solderpad Hardware License, Version 0.51"
1174licenseName SHL_0_5 = "Solderpad Hardware License v0.5"
1175licenseName SimPL_2_0 = "Simple Public License 2.0"
1176licenseName SISSL_1_2 = "Sun Industry Standards Source License v1.2"
1177licenseName SISSL = "Sun Industry Standards Source License v1.1"
1178licenseName Sleepycat = "Sleepycat License"
1179licenseName SMLNJ = "Standard ML of New Jersey License"
1180licenseName SMPPL = "Secure Messaging Protocol Public License"
1181licenseName SNIA = "SNIA Public License 1.1"
1182licenseName Spencer_86 = "Spencer License 86"
1183licenseName Spencer_94 = "Spencer License 94"
1184licenseName Spencer_99 = "Spencer License 99"
1185licenseName SPL_1_0 = "Sun Public License v1.0"
1186licenseName SSPL_1_0 = "Server Side Public License, v 1"
1187licenseName SugarCRM_1_1_3 = "SugarCRM Public License v1.1.3"
1188licenseName SWL = "Scheme Widget Library (SWL) Software License Agreement"
1189licenseName TAPR_OHL_1_0 = "TAPR Open Hardware License v1.0"
1190licenseName TCL = "TCL/TK License"
1191licenseName TCP_wrappers = "TCP Wrappers License"
1192licenseName TMate = "TMate Open Source License"
1193licenseName TORQUE_1_1 = "TORQUE v2.5+ Software License v1.1"
1194licenseName TOSL = "Trusster Open Source License"
1195licenseName TU_Berlin_1_0 = "Technische Universitaet Berlin License 1.0"
1196licenseName TU_Berlin_2_0 = "Technische Universitaet Berlin License 2.0"
1197licenseName Unicode_DFS_2015 = "Unicode License Agreement - Data Files and Software (2015)"
1198licenseName Unicode_DFS_2016 = "Unicode License Agreement - Data Files and Software (2016)"
1199licenseName Unicode_TOU = "Unicode Terms of Use"
1200licenseName Unlicense = "The Unlicense"
1201licenseName UPL_1_0 = "Universal Permissive License v1.0"
1202licenseName Vim = "Vim License"
1203licenseName VOSTROM = "VOSTROM Public License for Open Source"
1204licenseName VSL_1_0 = "Vovida Software License v1.0"
1205licenseName W3C_19980720 = "W3C Software Notice and License (1998-07-20)"
1206licenseName W3C_20150513 = "W3C Software Notice and Document License (2015-05-13)"
1207licenseName W3C = "W3C Software Notice and License (2002-12-31)"
1208licenseName Watcom_1_0 = "Sybase Open Watcom Public License 1.0"
1209licenseName Wsuipa = "Wsuipa License"
1210licenseName WTFPL = "Do What The F*ck You Want To Public License"
1211licenseName X11 = "X11 License"
1212licenseName Xerox = "Xerox License"
1213licenseName XFree86_1_1 = "XFree86 License 1.1"
1214licenseName Xinetd = "xinetd License"
1215licenseName Xnet = "X.Net License"
1216licenseName Xpp = "XPP License"
1217licenseName XSkat = "XSkat License"
1218licenseName YPL_1_0 = "Yahoo! Public License v1.0"
1219licenseName YPL_1_1 = "Yahoo! Public License v1.1"
1220licenseName Zed = "Zed License"
1221licenseName Zend_2_0 = "Zend License v2.0"
1222licenseName Zimbra_1_3 = "Zimbra Public License v1.3"
1223licenseName Zimbra_1_4 = "Zimbra Public License v1.4"
1224licenseName Zlib_acknowledgement = "zlib/libpng License with Acknowledgement"
1225licenseName Zlib = "zlib License"
1226licenseName ZPL_1_1 = "Zope Public License 1.1"
1227licenseName ZPL_2_0 = "Zope Public License 2.0"
1228licenseName ZPL_2_1 = "Zope Public License 2.1"
1229
1230-- | Whether the license is approved by Open Source Initiative (OSI).
1231--
1232-- See <https://opensource.org/licenses/alphabetical>.
1233licenseIsOsiApproved :: LicenseId -> Bool
1234licenseIsOsiApproved NullBSD = True
1235licenseIsOsiApproved AAL = True
1236licenseIsOsiApproved Abstyles = False
1237licenseIsOsiApproved Adobe_2006 = False
1238licenseIsOsiApproved Adobe_Glyph = False
1239licenseIsOsiApproved ADSL = False
1240licenseIsOsiApproved AFL_1_1 = True
1241licenseIsOsiApproved AFL_1_2 = True
1242licenseIsOsiApproved AFL_2_0 = True
1243licenseIsOsiApproved AFL_2_1 = True
1244licenseIsOsiApproved AFL_3_0 = True
1245licenseIsOsiApproved Afmparse = False
1246licenseIsOsiApproved AGPL_1_0 = False
1247licenseIsOsiApproved AGPL_1_0_only = False
1248licenseIsOsiApproved AGPL_1_0_or_later = False
1249licenseIsOsiApproved AGPL_3_0_only = True
1250licenseIsOsiApproved AGPL_3_0_or_later = True
1251licenseIsOsiApproved Aladdin = False
1252licenseIsOsiApproved AMDPLPA = False
1253licenseIsOsiApproved AML = False
1254licenseIsOsiApproved AMPAS = False
1255licenseIsOsiApproved ANTLR_PD = False
1256licenseIsOsiApproved Apache_1_0 = False
1257licenseIsOsiApproved Apache_1_1 = True
1258licenseIsOsiApproved Apache_2_0 = True
1259licenseIsOsiApproved APAFML = False
1260licenseIsOsiApproved APL_1_0 = True
1261licenseIsOsiApproved APSL_1_0 = True
1262licenseIsOsiApproved APSL_1_1 = True
1263licenseIsOsiApproved APSL_1_2 = True
1264licenseIsOsiApproved APSL_2_0 = True
1265licenseIsOsiApproved Artistic_1_0_cl8 = True
1266licenseIsOsiApproved Artistic_1_0_Perl = True
1267licenseIsOsiApproved Artistic_1_0 = True
1268licenseIsOsiApproved Artistic_2_0 = True
1269licenseIsOsiApproved Bahyph = False
1270licenseIsOsiApproved Barr = False
1271licenseIsOsiApproved Beerware = False
1272licenseIsOsiApproved BitTorrent_1_0 = False
1273licenseIsOsiApproved BitTorrent_1_1 = False
1274licenseIsOsiApproved Blessing = False
1275licenseIsOsiApproved BlueOak_1_0_0 = False
1276licenseIsOsiApproved Borceux = False
1277licenseIsOsiApproved BSD_1_Clause = False
1278licenseIsOsiApproved BSD_2_Clause_FreeBSD = False
1279licenseIsOsiApproved BSD_2_Clause_NetBSD = False
1280licenseIsOsiApproved BSD_2_Clause_Patent = True
1281licenseIsOsiApproved BSD_2_Clause = True
1282licenseIsOsiApproved BSD_3_Clause_Attribution = False
1283licenseIsOsiApproved BSD_3_Clause_Clear = False
1284licenseIsOsiApproved BSD_3_Clause_LBNL = True
1285licenseIsOsiApproved BSD_3_Clause_No_Nuclear_License_2014 = False
1286licenseIsOsiApproved BSD_3_Clause_No_Nuclear_License = False
1287licenseIsOsiApproved BSD_3_Clause_No_Nuclear_Warranty = False
1288licenseIsOsiApproved BSD_3_Clause_Open_MPI = False
1289licenseIsOsiApproved BSD_3_Clause = True
1290licenseIsOsiApproved BSD_4_Clause_UC = False
1291licenseIsOsiApproved BSD_4_Clause = False
1292licenseIsOsiApproved BSD_Protection = False
1293licenseIsOsiApproved BSD_Source_Code = False
1294licenseIsOsiApproved BSL_1_0 = True
1295licenseIsOsiApproved Bzip2_1_0_5 = False
1296licenseIsOsiApproved Bzip2_1_0_6 = False
1297licenseIsOsiApproved Caldera = False
1298licenseIsOsiApproved CATOSL_1_1 = True
1299licenseIsOsiApproved CC_BY_1_0 = False
1300licenseIsOsiApproved CC_BY_2_0 = False
1301licenseIsOsiApproved CC_BY_2_5 = False
1302licenseIsOsiApproved CC_BY_3_0 = False
1303licenseIsOsiApproved CC_BY_4_0 = False
1304licenseIsOsiApproved CC_BY_NC_1_0 = False
1305licenseIsOsiApproved CC_BY_NC_2_0 = False
1306licenseIsOsiApproved CC_BY_NC_2_5 = False
1307licenseIsOsiApproved CC_BY_NC_3_0 = False
1308licenseIsOsiApproved CC_BY_NC_4_0 = False
1309licenseIsOsiApproved CC_BY_NC_ND_1_0 = False
1310licenseIsOsiApproved CC_BY_NC_ND_2_0 = False
1311licenseIsOsiApproved CC_BY_NC_ND_2_5 = False
1312licenseIsOsiApproved CC_BY_NC_ND_3_0 = False
1313licenseIsOsiApproved CC_BY_NC_ND_4_0 = False
1314licenseIsOsiApproved CC_BY_NC_SA_1_0 = False
1315licenseIsOsiApproved CC_BY_NC_SA_2_0 = False
1316licenseIsOsiApproved CC_BY_NC_SA_2_5 = False
1317licenseIsOsiApproved CC_BY_NC_SA_3_0 = False
1318licenseIsOsiApproved CC_BY_NC_SA_4_0 = False
1319licenseIsOsiApproved CC_BY_ND_1_0 = False
1320licenseIsOsiApproved CC_BY_ND_2_0 = False
1321licenseIsOsiApproved CC_BY_ND_2_5 = False
1322licenseIsOsiApproved CC_BY_ND_3_0 = False
1323licenseIsOsiApproved CC_BY_ND_4_0 = False
1324licenseIsOsiApproved CC_BY_SA_1_0 = False
1325licenseIsOsiApproved CC_BY_SA_2_0 = False
1326licenseIsOsiApproved CC_BY_SA_2_5 = False
1327licenseIsOsiApproved CC_BY_SA_3_0 = False
1328licenseIsOsiApproved CC_BY_SA_4_0 = False
1329licenseIsOsiApproved CC_PDDC = False
1330licenseIsOsiApproved CC0_1_0 = False
1331licenseIsOsiApproved CDDL_1_0 = True
1332licenseIsOsiApproved CDDL_1_1 = False
1333licenseIsOsiApproved CDLA_Permissive_1_0 = False
1334licenseIsOsiApproved CDLA_Sharing_1_0 = False
1335licenseIsOsiApproved CECILL_1_0 = False
1336licenseIsOsiApproved CECILL_1_1 = False
1337licenseIsOsiApproved CECILL_2_0 = False
1338licenseIsOsiApproved CECILL_2_1 = True
1339licenseIsOsiApproved CECILL_B = False
1340licenseIsOsiApproved CECILL_C = False
1341licenseIsOsiApproved CERN_OHL_1_1 = False
1342licenseIsOsiApproved CERN_OHL_1_2 = False
1343licenseIsOsiApproved ClArtistic = False
1344licenseIsOsiApproved CNRI_Jython = False
1345licenseIsOsiApproved CNRI_Python_GPL_Compatible = False
1346licenseIsOsiApproved CNRI_Python = True
1347licenseIsOsiApproved Condor_1_1 = False
1348licenseIsOsiApproved Copyleft_next_0_3_0 = False
1349licenseIsOsiApproved Copyleft_next_0_3_1 = False
1350licenseIsOsiApproved CPAL_1_0 = True
1351licenseIsOsiApproved CPL_1_0 = True
1352licenseIsOsiApproved CPOL_1_02 = False
1353licenseIsOsiApproved Crossword = False
1354licenseIsOsiApproved CrystalStacker = False
1355licenseIsOsiApproved CUA_OPL_1_0 = True
1356licenseIsOsiApproved Cube = False
1357licenseIsOsiApproved Curl = False
1358licenseIsOsiApproved D_FSL_1_0 = False
1359licenseIsOsiApproved Diffmark = False
1360licenseIsOsiApproved DOC = False
1361licenseIsOsiApproved Dotseqn = False
1362licenseIsOsiApproved DSDP = False
1363licenseIsOsiApproved Dvipdfm = False
1364licenseIsOsiApproved ECL_1_0 = True
1365licenseIsOsiApproved ECL_2_0 = True
1366licenseIsOsiApproved EFL_1_0 = True
1367licenseIsOsiApproved EFL_2_0 = True
1368licenseIsOsiApproved EGenix = False
1369licenseIsOsiApproved Entessa = True
1370licenseIsOsiApproved EPL_1_0 = True
1371licenseIsOsiApproved EPL_2_0 = True
1372licenseIsOsiApproved ErlPL_1_1 = False
1373licenseIsOsiApproved EUDatagrid = True
1374licenseIsOsiApproved EUPL_1_0 = False
1375licenseIsOsiApproved EUPL_1_1 = True
1376licenseIsOsiApproved EUPL_1_2 = True
1377licenseIsOsiApproved Eurosym = False
1378licenseIsOsiApproved Fair = True
1379licenseIsOsiApproved Frameworx_1_0 = True
1380licenseIsOsiApproved FreeImage = False
1381licenseIsOsiApproved FSFAP = False
1382licenseIsOsiApproved FSFULLR = False
1383licenseIsOsiApproved FSFUL = False
1384licenseIsOsiApproved FTL = False
1385licenseIsOsiApproved GFDL_1_1_only = False
1386licenseIsOsiApproved GFDL_1_1_or_later = False
1387licenseIsOsiApproved GFDL_1_2_only = False
1388licenseIsOsiApproved GFDL_1_2_or_later = False
1389licenseIsOsiApproved GFDL_1_3_only = False
1390licenseIsOsiApproved GFDL_1_3_or_later = False
1391licenseIsOsiApproved Giftware = False
1392licenseIsOsiApproved GL2PS = False
1393licenseIsOsiApproved Glide = False
1394licenseIsOsiApproved Glulxe = False
1395licenseIsOsiApproved Gnuplot = False
1396licenseIsOsiApproved GPL_1_0_only = False
1397licenseIsOsiApproved GPL_1_0_or_later = False
1398licenseIsOsiApproved GPL_2_0_only = True
1399licenseIsOsiApproved GPL_2_0_or_later = True
1400licenseIsOsiApproved GPL_3_0_only = True
1401licenseIsOsiApproved GPL_3_0_or_later = True
1402licenseIsOsiApproved GSOAP_1_3b = False
1403licenseIsOsiApproved HaskellReport = False
1404licenseIsOsiApproved HPND_sell_variant = False
1405licenseIsOsiApproved HPND = True
1406licenseIsOsiApproved IBM_pibs = False
1407licenseIsOsiApproved ICU = False
1408licenseIsOsiApproved IJG = False
1409licenseIsOsiApproved ImageMagick = False
1410licenseIsOsiApproved IMatix = False
1411licenseIsOsiApproved Imlib2 = False
1412licenseIsOsiApproved Info_ZIP = False
1413licenseIsOsiApproved Intel_ACPI = False
1414licenseIsOsiApproved Intel = True
1415licenseIsOsiApproved Interbase_1_0 = False
1416licenseIsOsiApproved IPA = True
1417licenseIsOsiApproved IPL_1_0 = True
1418licenseIsOsiApproved ISC = True
1419licenseIsOsiApproved JasPer_2_0 = False
1420licenseIsOsiApproved JPNIC = False
1421licenseIsOsiApproved JSON = False
1422licenseIsOsiApproved LAL_1_2 = False
1423licenseIsOsiApproved LAL_1_3 = False
1424licenseIsOsiApproved Latex2e = False
1425licenseIsOsiApproved Leptonica = False
1426licenseIsOsiApproved LGPL_2_0_only = True
1427licenseIsOsiApproved LGPL_2_0_or_later = True
1428licenseIsOsiApproved LGPL_2_1_only = True
1429licenseIsOsiApproved LGPL_2_1_or_later = True
1430licenseIsOsiApproved LGPL_3_0_only = True
1431licenseIsOsiApproved LGPL_3_0_or_later = True
1432licenseIsOsiApproved LGPLLR = False
1433licenseIsOsiApproved Libpng_2_0 = False
1434licenseIsOsiApproved Libpng = False
1435licenseIsOsiApproved Libtiff = False
1436licenseIsOsiApproved LiLiQ_P_1_1 = True
1437licenseIsOsiApproved LiLiQ_R_1_1 = True
1438licenseIsOsiApproved LiLiQ_Rplus_1_1 = True
1439licenseIsOsiApproved Linux_OpenIB = False
1440licenseIsOsiApproved LPL_1_02 = True
1441licenseIsOsiApproved LPL_1_0 = True
1442licenseIsOsiApproved LPPL_1_0 = False
1443licenseIsOsiApproved LPPL_1_1 = False
1444licenseIsOsiApproved LPPL_1_2 = False
1445licenseIsOsiApproved LPPL_1_3a = False
1446licenseIsOsiApproved LPPL_1_3c = True
1447licenseIsOsiApproved MakeIndex = False
1448licenseIsOsiApproved MirOS = True
1449licenseIsOsiApproved MIT_0 = True
1450licenseIsOsiApproved MIT_advertising = False
1451licenseIsOsiApproved MIT_CMU = False
1452licenseIsOsiApproved MIT_enna = False
1453licenseIsOsiApproved MIT_feh = False
1454licenseIsOsiApproved MITNFA = False
1455licenseIsOsiApproved MIT = True
1456licenseIsOsiApproved Motosoto = True
1457licenseIsOsiApproved Mpich2 = False
1458licenseIsOsiApproved MPL_1_0 = True
1459licenseIsOsiApproved MPL_1_1 = True
1460licenseIsOsiApproved MPL_2_0_no_copyleft_exception = True
1461licenseIsOsiApproved MPL_2_0 = True
1462licenseIsOsiApproved MS_PL = True
1463licenseIsOsiApproved MS_RL = True
1464licenseIsOsiApproved MTLL = False
1465licenseIsOsiApproved Multics = True
1466licenseIsOsiApproved Mup = False
1467licenseIsOsiApproved NASA_1_3 = True
1468licenseIsOsiApproved Naumen = True
1469licenseIsOsiApproved NBPL_1_0 = False
1470licenseIsOsiApproved NCSA = True
1471licenseIsOsiApproved Net_SNMP = False
1472licenseIsOsiApproved NetCDF = False
1473licenseIsOsiApproved Newsletr = False
1474licenseIsOsiApproved NGPL = True
1475licenseIsOsiApproved NLOD_1_0 = False
1476licenseIsOsiApproved NLPL = False
1477licenseIsOsiApproved Nokia = True
1478licenseIsOsiApproved NOSL = False
1479licenseIsOsiApproved Noweb = False
1480licenseIsOsiApproved NPL_1_0 = False
1481licenseIsOsiApproved NPL_1_1 = False
1482licenseIsOsiApproved NPOSL_3_0 = True
1483licenseIsOsiApproved NRL = False
1484licenseIsOsiApproved NTP = True
1485licenseIsOsiApproved OCCT_PL = False
1486licenseIsOsiApproved OCLC_2_0 = True
1487licenseIsOsiApproved ODbL_1_0 = False
1488licenseIsOsiApproved ODC_By_1_0 = False
1489licenseIsOsiApproved OFL_1_0 = False
1490licenseIsOsiApproved OFL_1_1 = True
1491licenseIsOsiApproved OGL_UK_1_0 = False
1492licenseIsOsiApproved OGL_UK_2_0 = False
1493licenseIsOsiApproved OGL_UK_3_0 = False
1494licenseIsOsiApproved OGTSL = True
1495licenseIsOsiApproved OLDAP_1_1 = False
1496licenseIsOsiApproved OLDAP_1_2 = False
1497licenseIsOsiApproved OLDAP_1_3 = False
1498licenseIsOsiApproved OLDAP_1_4 = False
1499licenseIsOsiApproved OLDAP_2_0_1 = False
1500licenseIsOsiApproved OLDAP_2_0 = False
1501licenseIsOsiApproved OLDAP_2_1 = False
1502licenseIsOsiApproved OLDAP_2_2_1 = False
1503licenseIsOsiApproved OLDAP_2_2_2 = False
1504licenseIsOsiApproved OLDAP_2_2 = False
1505licenseIsOsiApproved OLDAP_2_3 = False
1506licenseIsOsiApproved OLDAP_2_4 = False
1507licenseIsOsiApproved OLDAP_2_5 = False
1508licenseIsOsiApproved OLDAP_2_6 = False
1509licenseIsOsiApproved OLDAP_2_7 = False
1510licenseIsOsiApproved OLDAP_2_8 = False
1511licenseIsOsiApproved OML = False
1512licenseIsOsiApproved OpenSSL = False
1513licenseIsOsiApproved OPL_1_0 = False
1514licenseIsOsiApproved OSET_PL_2_1 = True
1515licenseIsOsiApproved OSL_1_0 = True
1516licenseIsOsiApproved OSL_1_1 = False
1517licenseIsOsiApproved OSL_2_0 = True
1518licenseIsOsiApproved OSL_2_1 = True
1519licenseIsOsiApproved OSL_3_0 = True
1520licenseIsOsiApproved Parity_6_0_0 = False
1521licenseIsOsiApproved PDDL_1_0 = False
1522licenseIsOsiApproved PHP_3_01 = False
1523licenseIsOsiApproved PHP_3_0 = True
1524licenseIsOsiApproved Plexus = False
1525licenseIsOsiApproved PostgreSQL = True
1526licenseIsOsiApproved Psfrag = False
1527licenseIsOsiApproved Psutils = False
1528licenseIsOsiApproved Python_2_0 = True
1529licenseIsOsiApproved Qhull = False
1530licenseIsOsiApproved QPL_1_0 = True
1531licenseIsOsiApproved Rdisc = False
1532licenseIsOsiApproved RHeCos_1_1 = False
1533licenseIsOsiApproved RPL_1_1 = True
1534licenseIsOsiApproved RPL_1_5 = True
1535licenseIsOsiApproved RPSL_1_0 = True
1536licenseIsOsiApproved RSA_MD = False
1537licenseIsOsiApproved RSCPL = True
1538licenseIsOsiApproved Ruby = False
1539licenseIsOsiApproved SAX_PD = False
1540licenseIsOsiApproved Saxpath = False
1541licenseIsOsiApproved SCEA = False
1542licenseIsOsiApproved Sendmail_8_23 = False
1543licenseIsOsiApproved Sendmail = False
1544licenseIsOsiApproved SGI_B_1_0 = False
1545licenseIsOsiApproved SGI_B_1_1 = False
1546licenseIsOsiApproved SGI_B_2_0 = False
1547licenseIsOsiApproved SHL_0_51 = False
1548licenseIsOsiApproved SHL_0_5 = False
1549licenseIsOsiApproved SimPL_2_0 = True
1550licenseIsOsiApproved SISSL_1_2 = False
1551licenseIsOsiApproved SISSL = True
1552licenseIsOsiApproved Sleepycat = True
1553licenseIsOsiApproved SMLNJ = False
1554licenseIsOsiApproved SMPPL = False
1555licenseIsOsiApproved SNIA = False
1556licenseIsOsiApproved Spencer_86 = False
1557licenseIsOsiApproved Spencer_94 = False
1558licenseIsOsiApproved Spencer_99 = False
1559licenseIsOsiApproved SPL_1_0 = True
1560licenseIsOsiApproved SSPL_1_0 = False
1561licenseIsOsiApproved SugarCRM_1_1_3 = False
1562licenseIsOsiApproved SWL = False
1563licenseIsOsiApproved TAPR_OHL_1_0 = False
1564licenseIsOsiApproved TCL = False
1565licenseIsOsiApproved TCP_wrappers = False
1566licenseIsOsiApproved TMate = False
1567licenseIsOsiApproved TORQUE_1_1 = False
1568licenseIsOsiApproved TOSL = False
1569licenseIsOsiApproved TU_Berlin_1_0 = False
1570licenseIsOsiApproved TU_Berlin_2_0 = False
1571licenseIsOsiApproved Unicode_DFS_2015 = False
1572licenseIsOsiApproved Unicode_DFS_2016 = False
1573licenseIsOsiApproved Unicode_TOU = False
1574licenseIsOsiApproved Unlicense = False
1575licenseIsOsiApproved UPL_1_0 = True
1576licenseIsOsiApproved Vim = False
1577licenseIsOsiApproved VOSTROM = False
1578licenseIsOsiApproved VSL_1_0 = True
1579licenseIsOsiApproved W3C_19980720 = False
1580licenseIsOsiApproved W3C_20150513 = False
1581licenseIsOsiApproved W3C = True
1582licenseIsOsiApproved Watcom_1_0 = True
1583licenseIsOsiApproved Wsuipa = False
1584licenseIsOsiApproved WTFPL = False
1585licenseIsOsiApproved X11 = False
1586licenseIsOsiApproved Xerox = False
1587licenseIsOsiApproved XFree86_1_1 = False
1588licenseIsOsiApproved Xinetd = False
1589licenseIsOsiApproved Xnet = True
1590licenseIsOsiApproved Xpp = False
1591licenseIsOsiApproved XSkat = False
1592licenseIsOsiApproved YPL_1_0 = False
1593licenseIsOsiApproved YPL_1_1 = False
1594licenseIsOsiApproved Zed = False
1595licenseIsOsiApproved Zend_2_0 = False
1596licenseIsOsiApproved Zimbra_1_3 = False
1597licenseIsOsiApproved Zimbra_1_4 = False
1598licenseIsOsiApproved Zlib_acknowledgement = False
1599licenseIsOsiApproved Zlib = True
1600licenseIsOsiApproved ZPL_1_1 = False
1601licenseIsOsiApproved ZPL_2_0 = True
1602licenseIsOsiApproved ZPL_2_1 = False
1603
1604-------------------------------------------------------------------------------
1605-- Creation
1606-------------------------------------------------------------------------------
1607
1608licenseIdList :: LicenseListVersion -> [LicenseId]
1609licenseIdList LicenseListVersion_3_0 =
1610    [ AGPL_1_0
1611    ]
1612    ++ bulkOfLicenses
1613licenseIdList LicenseListVersion_3_2 =
1614    [ AGPL_1_0_only
1615    , AGPL_1_0_or_later
1616    , Linux_OpenIB
1617    , MIT_0
1618    , ODC_By_1_0
1619    , TU_Berlin_1_0
1620    , TU_Berlin_2_0
1621    ]
1622    ++ bulkOfLicenses
1623licenseIdList LicenseListVersion_3_6 =
1624    [ AGPL_1_0_only
1625    , AGPL_1_0_or_later
1626    , Blessing
1627    , BlueOak_1_0_0
1628    , BSD_3_Clause_Open_MPI
1629    , CC_PDDC
1630    , CERN_OHL_1_1
1631    , CERN_OHL_1_2
1632    , Copyleft_next_0_3_0
1633    , Copyleft_next_0_3_1
1634    , HPND_sell_variant
1635    , JPNIC
1636    , Libpng_2_0
1637    , Linux_OpenIB
1638    , MIT_0
1639    , ODC_By_1_0
1640    , OGL_UK_1_0
1641    , OGL_UK_2_0
1642    , OGL_UK_3_0
1643    , Parity_6_0_0
1644    , Sendmail_8_23
1645    , SHL_0_51
1646    , SHL_0_5
1647    , SSPL_1_0
1648    , TAPR_OHL_1_0
1649    , TU_Berlin_1_0
1650    , TU_Berlin_2_0
1651    ]
1652    ++ bulkOfLicenses
1653
1654-- | Create a 'LicenseId' from a 'String'.
1655mkLicenseId :: LicenseListVersion -> String -> Maybe LicenseId
1656mkLicenseId LicenseListVersion_3_0 s = Map.lookup s stringLookup_3_0
1657mkLicenseId LicenseListVersion_3_2 s = Map.lookup s stringLookup_3_2
1658mkLicenseId LicenseListVersion_3_6 s = Map.lookup s stringLookup_3_6
1659
1660stringLookup_3_0 :: Map String LicenseId
1661stringLookup_3_0 = Map.fromList $ map (\i -> (licenseId i, i)) $
1662    licenseIdList LicenseListVersion_3_0
1663
1664stringLookup_3_2 :: Map String LicenseId
1665stringLookup_3_2 = Map.fromList $ map (\i -> (licenseId i, i)) $
1666    licenseIdList LicenseListVersion_3_2
1667
1668stringLookup_3_6 :: Map String LicenseId
1669stringLookup_3_6 = Map.fromList $ map (\i -> (licenseId i, i)) $
1670    licenseIdList LicenseListVersion_3_6
1671
1672--  | Licenses in all SPDX License lists
1673bulkOfLicenses :: [LicenseId]
1674bulkOfLicenses =
1675    [ NullBSD
1676    , AAL
1677    , Abstyles
1678    , Adobe_2006
1679    , Adobe_Glyph
1680    , ADSL
1681    , AFL_1_1
1682    , AFL_1_2
1683    , AFL_2_0
1684    , AFL_2_1
1685    , AFL_3_0
1686    , Afmparse
1687    , AGPL_3_0_only
1688    , AGPL_3_0_or_later
1689    , Aladdin
1690    , AMDPLPA
1691    , AML
1692    , AMPAS
1693    , ANTLR_PD
1694    , Apache_1_0
1695    , Apache_1_1
1696    , Apache_2_0
1697    , APAFML
1698    , APL_1_0
1699    , APSL_1_0
1700    , APSL_1_1
1701    , APSL_1_2
1702    , APSL_2_0
1703    , Artistic_1_0_cl8
1704    , Artistic_1_0_Perl
1705    , Artistic_1_0
1706    , Artistic_2_0
1707    , Bahyph
1708    , Barr
1709    , Beerware
1710    , BitTorrent_1_0
1711    , BitTorrent_1_1
1712    , Borceux
1713    , BSD_1_Clause
1714    , BSD_2_Clause_FreeBSD
1715    , BSD_2_Clause_NetBSD
1716    , BSD_2_Clause_Patent
1717    , BSD_2_Clause
1718    , BSD_3_Clause_Attribution
1719    , BSD_3_Clause_Clear
1720    , BSD_3_Clause_LBNL
1721    , BSD_3_Clause_No_Nuclear_License_2014
1722    , BSD_3_Clause_No_Nuclear_License
1723    , BSD_3_Clause_No_Nuclear_Warranty
1724    , BSD_3_Clause
1725    , BSD_4_Clause_UC
1726    , BSD_4_Clause
1727    , BSD_Protection
1728    , BSD_Source_Code
1729    , BSL_1_0
1730    , Bzip2_1_0_5
1731    , Bzip2_1_0_6
1732    , Caldera
1733    , CATOSL_1_1
1734    , CC_BY_1_0
1735    , CC_BY_2_0
1736    , CC_BY_2_5
1737    , CC_BY_3_0
1738    , CC_BY_4_0
1739    , CC_BY_NC_1_0
1740    , CC_BY_NC_2_0
1741    , CC_BY_NC_2_5
1742    , CC_BY_NC_3_0
1743    , CC_BY_NC_4_0
1744    , CC_BY_NC_ND_1_0
1745    , CC_BY_NC_ND_2_0
1746    , CC_BY_NC_ND_2_5
1747    , CC_BY_NC_ND_3_0
1748    , CC_BY_NC_ND_4_0
1749    , CC_BY_NC_SA_1_0
1750    , CC_BY_NC_SA_2_0
1751    , CC_BY_NC_SA_2_5
1752    , CC_BY_NC_SA_3_0
1753    , CC_BY_NC_SA_4_0
1754    , CC_BY_ND_1_0
1755    , CC_BY_ND_2_0
1756    , CC_BY_ND_2_5
1757    , CC_BY_ND_3_0
1758    , CC_BY_ND_4_0
1759    , CC_BY_SA_1_0
1760    , CC_BY_SA_2_0
1761    , CC_BY_SA_2_5
1762    , CC_BY_SA_3_0
1763    , CC_BY_SA_4_0
1764    , CC0_1_0
1765    , CDDL_1_0
1766    , CDDL_1_1
1767    , CDLA_Permissive_1_0
1768    , CDLA_Sharing_1_0
1769    , CECILL_1_0
1770    , CECILL_1_1
1771    , CECILL_2_0
1772    , CECILL_2_1
1773    , CECILL_B
1774    , CECILL_C
1775    , ClArtistic
1776    , CNRI_Jython
1777    , CNRI_Python_GPL_Compatible
1778    , CNRI_Python
1779    , Condor_1_1
1780    , CPAL_1_0
1781    , CPL_1_0
1782    , CPOL_1_02
1783    , Crossword
1784    , CrystalStacker
1785    , CUA_OPL_1_0
1786    , Cube
1787    , Curl
1788    , D_FSL_1_0
1789    , Diffmark
1790    , DOC
1791    , Dotseqn
1792    , DSDP
1793    , Dvipdfm
1794    , ECL_1_0
1795    , ECL_2_0
1796    , EFL_1_0
1797    , EFL_2_0
1798    , EGenix
1799    , Entessa
1800    , EPL_1_0
1801    , EPL_2_0
1802    , ErlPL_1_1
1803    , EUDatagrid
1804    , EUPL_1_0
1805    , EUPL_1_1
1806    , EUPL_1_2
1807    , Eurosym
1808    , Fair
1809    , Frameworx_1_0
1810    , FreeImage
1811    , FSFAP
1812    , FSFULLR
1813    , FSFUL
1814    , FTL
1815    , GFDL_1_1_only
1816    , GFDL_1_1_or_later
1817    , GFDL_1_2_only
1818    , GFDL_1_2_or_later
1819    , GFDL_1_3_only
1820    , GFDL_1_3_or_later
1821    , Giftware
1822    , GL2PS
1823    , Glide
1824    , Glulxe
1825    , Gnuplot
1826    , GPL_1_0_only
1827    , GPL_1_0_or_later
1828    , GPL_2_0_only
1829    , GPL_2_0_or_later
1830    , GPL_3_0_only
1831    , GPL_3_0_or_later
1832    , GSOAP_1_3b
1833    , HaskellReport
1834    , HPND
1835    , IBM_pibs
1836    , ICU
1837    , IJG
1838    , ImageMagick
1839    , IMatix
1840    , Imlib2
1841    , Info_ZIP
1842    , Intel_ACPI
1843    , Intel
1844    , Interbase_1_0
1845    , IPA
1846    , IPL_1_0
1847    , ISC
1848    , JasPer_2_0
1849    , JSON
1850    , LAL_1_2
1851    , LAL_1_3
1852    , Latex2e
1853    , Leptonica
1854    , LGPL_2_0_only
1855    , LGPL_2_0_or_later
1856    , LGPL_2_1_only
1857    , LGPL_2_1_or_later
1858    , LGPL_3_0_only
1859    , LGPL_3_0_or_later
1860    , LGPLLR
1861    , Libpng
1862    , Libtiff
1863    , LiLiQ_P_1_1
1864    , LiLiQ_R_1_1
1865    , LiLiQ_Rplus_1_1
1866    , LPL_1_02
1867    , LPL_1_0
1868    , LPPL_1_0
1869    , LPPL_1_1
1870    , LPPL_1_2
1871    , LPPL_1_3a
1872    , LPPL_1_3c
1873    , MakeIndex
1874    , MirOS
1875    , MIT_advertising
1876    , MIT_CMU
1877    , MIT_enna
1878    , MIT_feh
1879    , MITNFA
1880    , MIT
1881    , Motosoto
1882    , Mpich2
1883    , MPL_1_0
1884    , MPL_1_1
1885    , MPL_2_0_no_copyleft_exception
1886    , MPL_2_0
1887    , MS_PL
1888    , MS_RL
1889    , MTLL
1890    , Multics
1891    , Mup
1892    , NASA_1_3
1893    , Naumen
1894    , NBPL_1_0
1895    , NCSA
1896    , Net_SNMP
1897    , NetCDF
1898    , Newsletr
1899    , NGPL
1900    , NLOD_1_0
1901    , NLPL
1902    , Nokia
1903    , NOSL
1904    , Noweb
1905    , NPL_1_0
1906    , NPL_1_1
1907    , NPOSL_3_0
1908    , NRL
1909    , NTP
1910    , OCCT_PL
1911    , OCLC_2_0
1912    , ODbL_1_0
1913    , OFL_1_0
1914    , OFL_1_1
1915    , OGTSL
1916    , OLDAP_1_1
1917    , OLDAP_1_2
1918    , OLDAP_1_3
1919    , OLDAP_1_4
1920    , OLDAP_2_0_1
1921    , OLDAP_2_0
1922    , OLDAP_2_1
1923    , OLDAP_2_2_1
1924    , OLDAP_2_2_2
1925    , OLDAP_2_2
1926    , OLDAP_2_3
1927    , OLDAP_2_4
1928    , OLDAP_2_5
1929    , OLDAP_2_6
1930    , OLDAP_2_7
1931    , OLDAP_2_8
1932    , OML
1933    , OpenSSL
1934    , OPL_1_0
1935    , OSET_PL_2_1
1936    , OSL_1_0
1937    , OSL_1_1
1938    , OSL_2_0
1939    , OSL_2_1
1940    , OSL_3_0
1941    , PDDL_1_0
1942    , PHP_3_01
1943    , PHP_3_0
1944    , Plexus
1945    , PostgreSQL
1946    , Psfrag
1947    , Psutils
1948    , Python_2_0
1949    , Qhull
1950    , QPL_1_0
1951    , Rdisc
1952    , RHeCos_1_1
1953    , RPL_1_1
1954    , RPL_1_5
1955    , RPSL_1_0
1956    , RSA_MD
1957    , RSCPL
1958    , Ruby
1959    , SAX_PD
1960    , Saxpath
1961    , SCEA
1962    , Sendmail
1963    , SGI_B_1_0
1964    , SGI_B_1_1
1965    , SGI_B_2_0
1966    , SimPL_2_0
1967    , SISSL_1_2
1968    , SISSL
1969    , Sleepycat
1970    , SMLNJ
1971    , SMPPL
1972    , SNIA
1973    , Spencer_86
1974    , Spencer_94
1975    , Spencer_99
1976    , SPL_1_0
1977    , SugarCRM_1_1_3
1978    , SWL
1979    , TCL
1980    , TCP_wrappers
1981    , TMate
1982    , TORQUE_1_1
1983    , TOSL
1984    , Unicode_DFS_2015
1985    , Unicode_DFS_2016
1986    , Unicode_TOU
1987    , Unlicense
1988    , UPL_1_0
1989    , Vim
1990    , VOSTROM
1991    , VSL_1_0
1992    , W3C_19980720
1993    , W3C_20150513
1994    , W3C
1995    , Watcom_1_0
1996    , Wsuipa
1997    , WTFPL
1998    , X11
1999    , Xerox
2000    , XFree86_1_1
2001    , Xinetd
2002    , Xnet
2003    , Xpp
2004    , XSkat
2005    , YPL_1_0
2006    , YPL_1_1
2007    , Zed
2008    , Zend_2_0
2009    , Zimbra_1_3
2010    , Zimbra_1_4
2011    , Zlib_acknowledgement
2012    , Zlib
2013    , ZPL_1_1
2014    , ZPL_2_0
2015    , ZPL_2_1
2016    ]
2017