diff --git a/Cabal/Cabal.cabal b/Cabal/Cabal.cabal
index 697630ffde7ce793be57dd0aabb354a507983c7b..906878d277b792e7144ddecf97865d938a0d6cd7 100644
--- a/Cabal/Cabal.cabal
+++ b/Cabal/Cabal.cabal
@@ -230,6 +230,10 @@ library
     Distribution.Simple.UHC
     Distribution.Simple.UserHooks
     Distribution.Simple.Utils
+    Distribution.SPDX
+    Distribution.SPDX.LicenseId
+    Distribution.SPDX.LicenseExceptionId
+    Distribution.SPDX.LicenseReference
     Distribution.System
     Distribution.TestSuite
     Distribution.Text
@@ -406,6 +410,7 @@ test-suite unit-tests
     UnitTests.Distribution.Compat.Graph
     UnitTests.Distribution.Simple.Program.Internal
     UnitTests.Distribution.Simple.Utils
+    UnitTests.Distribution.SPDX
     UnitTests.Distribution.System
     UnitTests.Distribution.Utils.Generic
     UnitTests.Distribution.Utils.NubList
diff --git a/Cabal/Distribution/Parsec/Class.hs b/Cabal/Distribution/Parsec/Class.hs
index d157cde80d38e6d4fb2ac17f7cf3cfd06fb869ed..683058c58bafb1cf8eedd1fc73a70ddcfedc3d48 100644
--- a/Cabal/Distribution/Parsec/Class.hs
+++ b/Cabal/Distribution/Parsec/Class.hs
@@ -3,6 +3,7 @@ module Distribution.Parsec.Class (
     Parsec(..),
     ParsecParser,
     simpleParsec,
+    eitherParsec,
     -- * Warnings
     parsecWarning,
     PWarnType (..),
@@ -51,6 +52,12 @@ simpleParsec
     = either (const Nothing) Just
     . P.runParser (lexemeParsec <* P.eof) [] "<simpleParsec>"
 
+-- | Parse a 'String' with 'lexemeParsec'.
+eitherParsec :: Parsec a => String -> Either String a
+eitherParsec
+    = either (Left . show) Right
+    . P.runParser (lexemeParsec <* P.eof) [] "<eitherParsec>"
+
 parsecWarning :: PWarnType -> String -> P.Parsec s [PWarning] ()
 parsecWarning t w =
     Parsec.modifyState (PWarning t (Position 0 0) w :)
diff --git a/Cabal/Distribution/SPDX.hs b/Cabal/Distribution/SPDX.hs
new file mode 100644
index 0000000000000000000000000000000000000000..d8054546c0c8bb8581ba2a30ea471236f8e0d2a7
--- /dev/null
+++ b/Cabal/Distribution/SPDX.hs
@@ -0,0 +1,172 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveGeneric      #-}
+-- | This module contains a SPDX data from specification version 2.1
+--
+-- Specification is available on <https://spdx.org/specifications>
+module Distribution.SPDX (
+    -- * License expression
+    LicenseExpression (..),
+    simpleLicenseExpression,
+    OnlyOrAnyLater (..),
+    -- * License identifier
+    LicenseId (..),
+    licenseId,
+    licenseName,
+    licenseIsOsiApproved,
+    mkLicenseId,
+    -- * License exception
+    LicenseExceptionId (..),
+    licenseExceptionId,
+    licenseExceptionName,
+    mkLicenseExceptionId,
+    -- * License reference
+    LicenseRef,
+    licenseRef,
+    licenseDocumentRef,
+    mkLicenseRef,
+    mkLicenseRef',
+    unsafeMkLicenseRef,
+    ) where
+
+import Distribution.Compat.Prelude
+import Prelude ()
+
+import Distribution.Parsec.Class
+import Distribution.Pretty
+import Distribution.SPDX.LicenseExceptionId
+import Distribution.SPDX.LicenseId
+import Distribution.SPDX.LicenseReference
+import Distribution.Utils.Generic           (isAsciiAlphaNum)
+import Text.PrettyPrint                     ((<+>))
+
+import qualified Distribution.Compat.Parsec as P
+import qualified Text.PrettyPrint           as Disp
+
+-- | SPDX License Expression.
+--
+-- @
+-- idstring              = 1*(ALPHA \/ DIGIT \/ "-" \/ "." )
+-- license id            = \<short form license identifier inAppendix I.1>
+-- license exception id  = \<short form license exception identifier inAppendix I.2>
+-- license ref           = [\"DocumentRef-"1*(idstring)":"]\"LicenseRef-"1*(idstring)
+--
+-- simple expression     = license id \/ license id"+" \/ license ref
+--
+-- compound expression   = 1*1(simple expression \/
+--                         simple expression \"WITH" license exception id \/
+--                         compound expression \"AND" compound expression \/
+--                         compound expression \"OR" compound expression ) \/
+--                         "(" compound expression ")" )
+--
+-- license expression    = 1*1(simple expression / compound expression)
+-- @
+data LicenseExpression
+    = ELicense !(Either LicenseRef LicenseId) !OnlyOrAnyLater !(Maybe LicenseExceptionId)
+    | EAnd !LicenseExpression !LicenseExpression
+    | EOr !LicenseExpression !LicenseExpression
+    deriving (Show, Read, Eq, Typeable, Data, Generic)
+
+simpleLicenseExpression :: LicenseId -> LicenseExpression
+simpleLicenseExpression i = ELicense (Right i) Only Nothing
+
+instance Binary LicenseExpression
+
+instance Pretty LicenseExpression where
+    pretty = go 0
+      where
+        go :: Int -> LicenseExpression -> Disp.Doc
+        go _ (ELicense lic orLater exc) =
+            let doc = prettyId lic <<>> prettyOrLater orLater
+            in maybe id (\e d -> d <+> Disp.text "WITH" <+> pretty e) exc doc
+        go d (EAnd e1 e2) = parens (d < 0) $ go 0 e1 <+> Disp.text "AND" <+> go 0 e2
+        go d (EOr  e1 e2) = parens (d < 1) $ go 1 e1 <+> Disp.text "OR" <+> go 1 e2
+
+        prettyId (Right i) = pretty i
+        prettyId (Left r)  = pretty r
+
+        prettyOrLater Only       = mempty
+        prettyOrLater OrAnyLater = Disp.char '+'
+
+        parens False doc = doc
+        parens True  doc = Disp.parens doc
+
+instance Parsec LicenseExpression where
+    parsec = expr
+      where
+        expr = compoundOr
+
+        idstring = P.munch1 $ \c -> isAsciiAlphaNum c || c == '-' || c == '.'
+
+        -- this parses "simple expression / simple expression "WITH" license exception id"
+        simple = do
+            n <- idstring
+            i <- simple' n
+            orLater <- P.optionMaybe $ P.char '+'
+            _ <- P.spaces
+            exc <- P.optionMaybe $ P.try (P.string "WITH" *> spaces1) *> parsec
+            return $ ELicense i (maybe Only (const OrAnyLater) orLater) exc
+
+        simple' n
+            | Just l <- "LicenseRef-" `isPrefixOfMaybe` n =
+                maybe (fail $ "Incorrect LicenseRef format: " ++ n) (return . Left) $ mkLicenseRef Nothing l
+            | Just d <- "DocumentRef-" `isPrefixOfMaybe` n = do
+                _ <- P.string ":LicenseRef"
+                l <- idstring
+                maybe (fail $ "Incorrect LicenseRef format:" ++ n) (return . Left) $ mkLicenseRef (Just d) l
+            | otherwise =
+                maybe (fail $ "Unknown SPDX license identifier: " ++ n) (return . Right) $ mkLicenseId n
+
+        -- returns suffix part
+        isPrefixOfMaybe :: Eq a => [a] -> [a] -> Maybe [a]
+        isPrefixOfMaybe pfx s
+            | pfx `isPrefixOf` s = Just (drop (length pfx) s)
+            | otherwise          = Nothing
+
+        compoundOr = do
+            x <- compoundAnd
+            l <- P.optionMaybe $ P.try (P.string "OR" *> spaces1) *> compoundOr
+            return $ maybe id (flip EOr) l x
+
+        compoundAnd = do
+            x <- compound
+            l <- P.optionMaybe $ P.try (P.string "AND" *> spaces1) *> compoundAnd
+            return $ maybe id (flip EAnd) l x
+
+        compound = braces <|> simple
+
+        braces = do
+            _ <- P.char '('
+            _ <- P.spaces
+            x <- expr
+            _ <- P.char ')'
+            _ <- P.spaces
+            return x
+
+        spaces1 = P.space *> P.spaces
+
+-- notes:
+--
+-- There MUST NOT be whitespace between a license­id and any following "+".  This supports easy parsing and
+-- backwards compatibility.  There MUST be whitespace on either side of the operator "WITH".  There MUST be
+-- whitespace and/or parentheses on either side of the operators "AND" and "OR".
+--
+-- We handle that by having greedy 'idstring' parser, so MITAND would parse as invalid license identifier.
+
+instance NFData LicenseExpression where
+    rnf (ELicense b i e) = rnf b `seq` rnf i `seq` rnf e
+    rnf (EAnd x y)       = rnf x `seq` rnf y
+    rnf (EOr x y)        = rnf x `seq` rnf y
+
+-------------------------------------------------------------------------------
+-- OnlyOrAnyLater
+-------------------------------------------------------------------------------
+
+-- | License version range.
+data OnlyOrAnyLater = Only | OrAnyLater
+    deriving (Show, Read, Eq, Ord, Enum, Bounded, Typeable, Data, Generic)
+
+instance NFData OnlyOrAnyLater where
+    rnf Only       = ()
+    rnf OrAnyLater = ()
+
+instance Binary OnlyOrAnyLater
diff --git a/Cabal/Distribution/SPDX/LicenseExceptionId.hs b/Cabal/Distribution/SPDX/LicenseExceptionId.hs
new file mode 100644
index 0000000000000000000000000000000000000000..bd41a8c029fe89437b21ed28e839944830e1a985
--- /dev/null
+++ b/Cabal/Distribution/SPDX/LicenseExceptionId.hs
@@ -0,0 +1,137 @@
+-- This file is generated. See Makefile's spdx rule
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveGeneric      #-}
+module Distribution.SPDX.LicenseExceptionId (
+    LicenseExceptionId (..),
+    licenseExceptionId,
+    licenseExceptionName,
+    mkLicenseExceptionId,
+    ) where
+
+import Distribution.Compat.Prelude
+import Prelude ()
+
+import Distribution.Pretty
+import Distribution.Parsec.Class
+import Distribution.Utils.Generic (isAsciiAlphaNum)
+
+import qualified Distribution.Compat.Map.Strict as Map
+import qualified Distribution.Compat.Parsec as P
+import qualified Text.PrettyPrint as Disp
+
+-------------------------------------------------------------------------------
+-- LicenseExceptionId
+-------------------------------------------------------------------------------
+
+-- | SPDX License identifier
+data LicenseExceptionId
+    = DS389_exception -- ^ @389-exception@, 389 Directory Server Exception
+    | Autoconf_exception_2_0 -- ^ @Autoconf-exception-2.0@, Autoconf exception 2.0
+    | Autoconf_exception_3_0 -- ^ @Autoconf-exception-3.0@, Autoconf exception 3.0
+    | Bison_exception_2_2 -- ^ @Bison-exception-2.2@, Bison exception 2.2
+    | Classpath_exception_2_0 -- ^ @Classpath-exception-2.0@, Classpath exception 2.0
+    | CLISP_exception_2_0 -- ^ @CLISP-exception-2.0@, CLISP exception 2.0 
+    | DigiRule_FOSS_exception -- ^ @DigiRule-FOSS-exception@, DigiRule FOSS License Exception
+    | ECos_exception_2_0 -- ^ @eCos-exception-2.0@, eCos exception 2.0
+    | Fawkes_Runtime_exception -- ^ @Fawkes-Runtime-exception@, Fawkes Runtime Exception 
+    | FLTK_exception -- ^ @FLTK-exception@, FLTK exception
+    | Font_exception_2_0 -- ^ @Font-exception-2.0@, Font exception 2.0
+    | Freertos_exception_2_0 -- ^ @freertos-exception-2.0@, FreeRTOS Exception 2.0
+    | GCC_exception_2_0 -- ^ @GCC-exception-2.0@, GCC Runtime Library exception 2.0
+    | GCC_exception_3_1 -- ^ @GCC-exception-3.1@, GCC Runtime Library exception 3.1
+    | Gnu_javamail_exception -- ^ @gnu-javamail-exception@, GNU JavaMail exception
+    | I2p_gpl_java_exception -- ^ @i2p-gpl-java-exception@, i2p GPL+Java Exception
+    | Libtool_exception -- ^ @Libtool-exception@, Libtool Exception
+    | LZMA_exception -- ^ @LZMA-exception@, LZMA exception
+    | Mif_exception -- ^ @mif-exception@, Macros and Inline Functions Exception
+    | Nokia_Qt_exception_1_1 -- ^ @Nokia-Qt-exception-1.1@, Nokia Qt LGPL exception 1.1
+    | OCCT_exception_1_0 -- ^ @OCCT-exception-1.0@, Open CASCADE Exception 1.0
+    | Openvpn_openssl_exception -- ^ @openvpn-openssl-exception@, OpenVPN OpenSSL Exception
+    | Qwt_exception_1_0 -- ^ @Qwt-exception-1.0@, Qwt exception 1.0
+    | U_boot_exception_2_0 -- ^ @u-boot-exception-2.0@, U-Boot exception 2.0
+    | WxWindows_exception_3_1 -- ^ @WxWindows-exception-3.1@, WxWindows Library Exception 3.1
+  deriving (Eq, Ord, Enum, Bounded, Show, Read, Typeable, Data, Generic)
+
+instance Binary LicenseExceptionId
+
+instance Pretty LicenseExceptionId where
+    pretty = Disp.text . licenseExceptionId
+
+instance Parsec LicenseExceptionId where
+    parsec = do
+        n <- some $ P.satisfy $ \c -> isAsciiAlphaNum c || c == '-' || c == '.'
+        maybe (fail $ "Unknown SPDX license exception identifier: " ++ n) return $ mkLicenseExceptionId n
+
+instance NFData LicenseExceptionId where
+    rnf l = l `seq` ()
+
+-------------------------------------------------------------------------------
+-- License Data
+-------------------------------------------------------------------------------
+
+-- | License SPDX identifier, e.g. @"BSD-3-Clause"@.
+licenseExceptionId :: LicenseExceptionId -> String
+licenseExceptionId DS389_exception = "389-exception"
+licenseExceptionId Autoconf_exception_2_0 = "Autoconf-exception-2.0"
+licenseExceptionId Autoconf_exception_3_0 = "Autoconf-exception-3.0"
+licenseExceptionId Bison_exception_2_2 = "Bison-exception-2.2"
+licenseExceptionId Classpath_exception_2_0 = "Classpath-exception-2.0"
+licenseExceptionId CLISP_exception_2_0 = "CLISP-exception-2.0"
+licenseExceptionId DigiRule_FOSS_exception = "DigiRule-FOSS-exception"
+licenseExceptionId ECos_exception_2_0 = "eCos-exception-2.0"
+licenseExceptionId Fawkes_Runtime_exception = "Fawkes-Runtime-exception"
+licenseExceptionId FLTK_exception = "FLTK-exception"
+licenseExceptionId Font_exception_2_0 = "Font-exception-2.0"
+licenseExceptionId Freertos_exception_2_0 = "freertos-exception-2.0"
+licenseExceptionId GCC_exception_2_0 = "GCC-exception-2.0"
+licenseExceptionId GCC_exception_3_1 = "GCC-exception-3.1"
+licenseExceptionId Gnu_javamail_exception = "gnu-javamail-exception"
+licenseExceptionId I2p_gpl_java_exception = "i2p-gpl-java-exception"
+licenseExceptionId Libtool_exception = "Libtool-exception"
+licenseExceptionId LZMA_exception = "LZMA-exception"
+licenseExceptionId Mif_exception = "mif-exception"
+licenseExceptionId Nokia_Qt_exception_1_1 = "Nokia-Qt-exception-1.1"
+licenseExceptionId OCCT_exception_1_0 = "OCCT-exception-1.0"
+licenseExceptionId Openvpn_openssl_exception = "openvpn-openssl-exception"
+licenseExceptionId Qwt_exception_1_0 = "Qwt-exception-1.0"
+licenseExceptionId U_boot_exception_2_0 = "u-boot-exception-2.0"
+licenseExceptionId WxWindows_exception_3_1 = "WxWindows-exception-3.1"
+
+-- | License name, e.g. @"GNU General Public License v2.0 only"@
+licenseExceptionName :: LicenseExceptionId -> String
+licenseExceptionName DS389_exception = "389 Directory Server Exception"
+licenseExceptionName Autoconf_exception_2_0 = "Autoconf exception 2.0"
+licenseExceptionName Autoconf_exception_3_0 = "Autoconf exception 3.0"
+licenseExceptionName Bison_exception_2_2 = "Bison exception 2.2"
+licenseExceptionName Classpath_exception_2_0 = "Classpath exception 2.0"
+licenseExceptionName CLISP_exception_2_0 = "CLISP exception 2.0 "
+licenseExceptionName DigiRule_FOSS_exception = "DigiRule FOSS License Exception"
+licenseExceptionName ECos_exception_2_0 = "eCos exception 2.0"
+licenseExceptionName Fawkes_Runtime_exception = "Fawkes Runtime Exception "
+licenseExceptionName FLTK_exception = "FLTK exception"
+licenseExceptionName Font_exception_2_0 = "Font exception 2.0"
+licenseExceptionName Freertos_exception_2_0 = "FreeRTOS Exception 2.0"
+licenseExceptionName GCC_exception_2_0 = "GCC Runtime Library exception 2.0"
+licenseExceptionName GCC_exception_3_1 = "GCC Runtime Library exception 3.1"
+licenseExceptionName Gnu_javamail_exception = "GNU JavaMail exception"
+licenseExceptionName I2p_gpl_java_exception = "i2p GPL+Java Exception"
+licenseExceptionName Libtool_exception = "Libtool Exception"
+licenseExceptionName LZMA_exception = "LZMA exception"
+licenseExceptionName Mif_exception = "Macros and Inline Functions Exception"
+licenseExceptionName Nokia_Qt_exception_1_1 = "Nokia Qt LGPL exception 1.1"
+licenseExceptionName OCCT_exception_1_0 = "Open CASCADE Exception 1.0"
+licenseExceptionName Openvpn_openssl_exception = "OpenVPN OpenSSL Exception"
+licenseExceptionName Qwt_exception_1_0 = "Qwt exception 1.0"
+licenseExceptionName U_boot_exception_2_0 = "U-Boot exception 2.0"
+licenseExceptionName WxWindows_exception_3_1 = "WxWindows Library Exception 3.1"
+
+-------------------------------------------------------------------------------
+-- Creation
+-------------------------------------------------------------------------------
+
+-- | Create a 'LicenseExceptionId' from a 'String'.
+mkLicenseExceptionId :: String -> Maybe LicenseExceptionId
+mkLicenseExceptionId s = Map.lookup s stringLookup
+
+stringLookup :: Map String LicenseExceptionId
+stringLookup = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $ [minBound .. maxBound]
diff --git a/Cabal/Distribution/SPDX/LicenseId.hs b/Cabal/Distribution/SPDX/LicenseId.hs
new file mode 100644
index 0000000000000000000000000000000000000000..5c73b93ae7d3469a3d3f784fdb92a544282c360f
--- /dev/null
+++ b/Cabal/Distribution/SPDX/LicenseId.hs
@@ -0,0 +1,1376 @@
+-- This file is generated. See Makefile's spdx rule
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveGeneric      #-}
+module Distribution.SPDX.LicenseId (
+    LicenseId (..),
+    licenseId,
+    licenseName,
+    licenseIsOsiApproved,
+    mkLicenseId,
+    ) where
+
+import Distribution.Compat.Prelude
+import Prelude ()
+
+import Distribution.Pretty
+import Distribution.Parsec.Class
+import Distribution.Utils.Generic (isAsciiAlphaNum)
+
+import qualified Distribution.Compat.Map.Strict as Map
+import qualified Distribution.Compat.Parsec as P
+import qualified Text.PrettyPrint as Disp
+
+-------------------------------------------------------------------------------
+-- LicenseId
+-------------------------------------------------------------------------------
+
+-- | SPDX License identifier
+data LicenseId
+    = Glide -- ^ @Glide@, 3dfx Glide License
+    | Abstyles -- ^ @Abstyles@, Abstyles License
+    | AFL_1_1 -- ^ @AFL-1.1@, Academic Free License v1.1
+    | AFL_1_2 -- ^ @AFL-1.2@, Academic Free License v1.2
+    | AFL_2_0 -- ^ @AFL-2.0@, Academic Free License v2.0
+    | AFL_2_1 -- ^ @AFL-2.1@, Academic Free License v2.1
+    | AFL_3_0 -- ^ @AFL-3.0@, Academic Free License v3.0
+    | AMPAS -- ^ @AMPAS@, Academy of Motion Picture Arts and Sciences BSD
+    | APL_1_0 -- ^ @APL-1.0@, Adaptive Public License 1.0
+    | Adobe_Glyph -- ^ @Adobe-Glyph@, Adobe Glyph List License
+    | APAFML -- ^ @APAFML@, Adobe Postscript AFM License
+    | Adobe_2006 -- ^ @Adobe-2006@, Adobe Systems Incorporated Source Code License Agreement
+    | AGPL_1_0 -- ^ @AGPL-1.0@, Affero General Public License v1.0
+    | Afmparse -- ^ @Afmparse@, Afmparse License
+    | Aladdin -- ^ @Aladdin@, Aladdin Free Public License
+    | ADSL -- ^ @ADSL@, Amazon Digital Services License
+    | AMDPLPA -- ^ @AMDPLPA@, AMD's plpa_map.c License
+    | ANTLR_PD -- ^ @ANTLR-PD@, ANTLR Software Rights Notice
+    | Apache_1_0 -- ^ @Apache-1.0@, Apache License 1.0
+    | Apache_1_1 -- ^ @Apache-1.1@, Apache License 1.1
+    | Apache_2_0 -- ^ @Apache-2.0@, Apache License 2.0
+    | AML -- ^ @AML@, Apple MIT License
+    | APSL_1_0 -- ^ @APSL-1.0@, Apple Public Source License 1.0
+    | APSL_1_1 -- ^ @APSL-1.1@, Apple Public Source License 1.1
+    | APSL_1_2 -- ^ @APSL-1.2@, Apple Public Source License 1.2
+    | APSL_2_0 -- ^ @APSL-2.0@, Apple Public Source License 2.0
+    | Artistic_1_0 -- ^ @Artistic-1.0@, Artistic License 1.0
+    | Artistic_1_0_Perl -- ^ @Artistic-1.0-Perl@, Artistic License 1.0 (Perl)
+    | Artistic_1_0_cl8 -- ^ @Artistic-1.0-cl8@, Artistic License 1.0 w/clause 8
+    | Artistic_2_0 -- ^ @Artistic-2.0@, Artistic License 2.0
+    | AAL -- ^ @AAL@, Attribution Assurance License
+    | Bahyph -- ^ @Bahyph@, Bahyph License
+    | Barr -- ^ @Barr@, Barr License
+    | Beerware -- ^ @Beerware@, Beerware License
+    | BitTorrent_1_0 -- ^ @BitTorrent-1.0@, BitTorrent Open Source License v1.0
+    | BitTorrent_1_1 -- ^ @BitTorrent-1.1@, BitTorrent Open Source License v1.1
+    | BSL_1_0 -- ^ @BSL-1.0@, Boost Software License 1.0
+    | Borceux -- ^ @Borceux@, Borceux license
+    | BSD_2_Clause -- ^ @BSD-2-Clause@, BSD 2-clause "Simplified" License
+    | BSD_2_Clause_FreeBSD -- ^ @BSD-2-Clause-FreeBSD@, BSD 2-clause FreeBSD License
+    | BSD_2_Clause_NetBSD -- ^ @BSD-2-Clause-NetBSD@, BSD 2-clause NetBSD License
+    | BSD_3_Clause -- ^ @BSD-3-Clause@, BSD 3-clause "New" or "Revised" License
+    | BSD_3_Clause_Clear -- ^ @BSD-3-Clause-Clear@, BSD 3-clause Clear License
+    | BSD_3_Clause_No_Nuclear_License -- ^ @BSD-3-Clause-No-Nuclear-License@, BSD 3-Clause No Nuclear License
+    | BSD_3_Clause_No_Nuclear_License_2014 -- ^ @BSD-3-Clause-No-Nuclear-License-2014@, BSD 3-Clause No Nuclear License 2014
+    | BSD_3_Clause_No_Nuclear_Warranty -- ^ @BSD-3-Clause-No-Nuclear-Warranty@, BSD 3-Clause No Nuclear Warranty
+    | BSD_4_Clause -- ^ @BSD-4-Clause@, BSD 4-clause "Original" or "Old" License
+    | BSD_Protection -- ^ @BSD-Protection@, BSD Protection License
+    | BSD_Source_Code -- ^ @BSD-Source-Code@, BSD Source Code Attribution
+    | BSD_3_Clause_Attribution -- ^ @BSD-3-Clause-Attribution@, BSD with attribution
+    | NullBSD -- ^ @0BSD@, BSD Zero Clause License
+    | BSD_4_Clause_UC -- ^ @BSD-4-Clause-UC@, BSD-4-Clause (University of California-Specific)
+    | Bzip2_1_0_5 -- ^ @bzip2-1.0.5@, bzip2 and libbzip2 License v1.0.5
+    | Bzip2_1_0_6 -- ^ @bzip2-1.0.6@, bzip2 and libbzip2 License v1.0.6
+    | Caldera -- ^ @Caldera@, Caldera License
+    | CECILL_1_0 -- ^ @CECILL-1.0@, CeCILL Free Software License Agreement v1.0
+    | CECILL_1_1 -- ^ @CECILL-1.1@, CeCILL Free Software License Agreement v1.1
+    | CECILL_2_0 -- ^ @CECILL-2.0@, CeCILL Free Software License Agreement v2.0
+    | CECILL_2_1 -- ^ @CECILL-2.1@, CeCILL Free Software License Agreement v2.1
+    | CECILL_B -- ^ @CECILL-B@, CeCILL-B Free Software License Agreement
+    | CECILL_C -- ^ @CECILL-C@, CeCILL-C Free Software License Agreement
+    | ClArtistic -- ^ @ClArtistic@, Clarified Artistic License
+    | MIT_CMU -- ^ @MIT-CMU@, CMU License
+    | CNRI_Jython -- ^ @CNRI-Jython@, CNRI Jython License
+    | CNRI_Python -- ^ @CNRI-Python@, CNRI Python License
+    | CNRI_Python_GPL_Compatible -- ^ @CNRI-Python-GPL-Compatible@, CNRI Python Open Source GPL Compatible License Agreement
+    | CPOL_1_02 -- ^ @CPOL-1.02@, Code Project Open License 1.02
+    | CDDL_1_0 -- ^ @CDDL-1.0@, Common Development and Distribution License 1.0
+    | CDDL_1_1 -- ^ @CDDL-1.1@, Common Development and Distribution License 1.1
+    | CPAL_1_0 -- ^ @CPAL-1.0@, Common Public Attribution License 1.0
+    | CPL_1_0 -- ^ @CPL-1.0@, Common Public License 1.0
+    | CATOSL_1_1 -- ^ @CATOSL-1.1@, Computer Associates Trusted Open Source License 1.1
+    | Condor_1_1 -- ^ @Condor-1.1@, Condor Public License v1.1
+    | CC_BY_1_0 -- ^ @CC-BY-1.0@, Creative Commons Attribution 1.0
+    | CC_BY_2_0 -- ^ @CC-BY-2.0@, Creative Commons Attribution 2.0
+    | CC_BY_2_5 -- ^ @CC-BY-2.5@, Creative Commons Attribution 2.5
+    | CC_BY_3_0 -- ^ @CC-BY-3.0@, Creative Commons Attribution 3.0
+    | CC_BY_4_0 -- ^ @CC-BY-4.0@, Creative Commons Attribution 4.0
+    | CC_BY_ND_1_0 -- ^ @CC-BY-ND-1.0@, Creative Commons Attribution No Derivatives 1.0
+    | CC_BY_ND_2_0 -- ^ @CC-BY-ND-2.0@, Creative Commons Attribution No Derivatives 2.0
+    | CC_BY_ND_2_5 -- ^ @CC-BY-ND-2.5@, Creative Commons Attribution No Derivatives 2.5
+    | CC_BY_ND_3_0 -- ^ @CC-BY-ND-3.0@, Creative Commons Attribution No Derivatives 3.0
+    | CC_BY_ND_4_0 -- ^ @CC-BY-ND-4.0@, Creative Commons Attribution No Derivatives 4.0
+    | CC_BY_NC_1_0 -- ^ @CC-BY-NC-1.0@, Creative Commons Attribution Non Commercial 1.0
+    | CC_BY_NC_2_0 -- ^ @CC-BY-NC-2.0@, Creative Commons Attribution Non Commercial 2.0
+    | CC_BY_NC_2_5 -- ^ @CC-BY-NC-2.5@, Creative Commons Attribution Non Commercial 2.5
+    | CC_BY_NC_3_0 -- ^ @CC-BY-NC-3.0@, Creative Commons Attribution Non Commercial 3.0
+    | CC_BY_NC_4_0 -- ^ @CC-BY-NC-4.0@, Creative Commons Attribution Non Commercial 4.0
+    | CC_BY_NC_ND_1_0 -- ^ @CC-BY-NC-ND-1.0@, Creative Commons Attribution Non Commercial No Derivatives 1.0
+    | CC_BY_NC_ND_2_0 -- ^ @CC-BY-NC-ND-2.0@, Creative Commons Attribution Non Commercial No Derivatives 2.0
+    | CC_BY_NC_ND_2_5 -- ^ @CC-BY-NC-ND-2.5@, Creative Commons Attribution Non Commercial No Derivatives 2.5
+    | CC_BY_NC_ND_3_0 -- ^ @CC-BY-NC-ND-3.0@, Creative Commons Attribution Non Commercial No Derivatives 3.0
+    | CC_BY_NC_ND_4_0 -- ^ @CC-BY-NC-ND-4.0@, Creative Commons Attribution Non Commercial No Derivatives 4.0
+    | CC_BY_NC_SA_1_0 -- ^ @CC-BY-NC-SA-1.0@, Creative Commons Attribution Non Commercial Share Alike 1.0
+    | CC_BY_NC_SA_2_0 -- ^ @CC-BY-NC-SA-2.0@, Creative Commons Attribution Non Commercial Share Alike 2.0
+    | CC_BY_NC_SA_2_5 -- ^ @CC-BY-NC-SA-2.5@, Creative Commons Attribution Non Commercial Share Alike 2.5
+    | CC_BY_NC_SA_3_0 -- ^ @CC-BY-NC-SA-3.0@, Creative Commons Attribution Non Commercial Share Alike 3.0
+    | CC_BY_NC_SA_4_0 -- ^ @CC-BY-NC-SA-4.0@, Creative Commons Attribution Non Commercial Share Alike 4.0
+    | CC_BY_SA_1_0 -- ^ @CC-BY-SA-1.0@, Creative Commons Attribution Share Alike 1.0
+    | CC_BY_SA_2_0 -- ^ @CC-BY-SA-2.0@, Creative Commons Attribution Share Alike 2.0
+    | CC_BY_SA_2_5 -- ^ @CC-BY-SA-2.5@, Creative Commons Attribution Share Alike 2.5
+    | CC_BY_SA_3_0 -- ^ @CC-BY-SA-3.0@, Creative Commons Attribution Share Alike 3.0
+    | CC_BY_SA_4_0 -- ^ @CC-BY-SA-4.0@, Creative Commons Attribution Share Alike 4.0
+    | CC0_1_0 -- ^ @CC0-1.0@, Creative Commons Zero v1.0 Universal
+    | Crossword -- ^ @Crossword@, Crossword License
+    | CrystalStacker -- ^ @CrystalStacker@, CrystalStacker License
+    | CUA_OPL_1_0 -- ^ @CUA-OPL-1.0@, CUA Office Public License v1.0
+    | Cube -- ^ @Cube@, Cube License
+    | Curl -- ^ @curl@, curl License
+    | D_FSL_1_0 -- ^ @D-FSL-1.0@, Deutsche Freie Software Lizenz
+    | Diffmark -- ^ @diffmark@, diffmark license
+    | WTFPL -- ^ @WTFPL@, Do What The F*ck You Want To Public License
+    | DOC -- ^ @DOC@, DOC License
+    | Dotseqn -- ^ @Dotseqn@, Dotseqn License
+    | DSDP -- ^ @DSDP@, DSDP License
+    | Dvipdfm -- ^ @dvipdfm@, dvipdfm License
+    | EPL_1_0 -- ^ @EPL-1.0@, Eclipse Public License 1.0
+    | ECL_1_0 -- ^ @ECL-1.0@, Educational Community License v1.0
+    | ECL_2_0 -- ^ @ECL-2.0@, Educational Community License v2.0
+    | EGenix -- ^ @eGenix@, eGenix.com Public License 1.1.0
+    | EFL_1_0 -- ^ @EFL-1.0@, Eiffel Forum License v1.0
+    | EFL_2_0 -- ^ @EFL-2.0@, Eiffel Forum License v2.0
+    | MIT_advertising -- ^ @MIT-advertising@, Enlightenment License (e16)
+    | MIT_enna -- ^ @MIT-enna@, enna License
+    | Entessa -- ^ @Entessa@, Entessa Public License v1.0
+    | ErlPL_1_1 -- ^ @ErlPL-1.1@, Erlang Public License v1.1
+    | EUDatagrid -- ^ @EUDatagrid@, EU DataGrid Software License
+    | EUPL_1_0 -- ^ @EUPL-1.0@, European Union Public License 1.0
+    | EUPL_1_1 -- ^ @EUPL-1.1@, European Union Public License 1.1
+    | Eurosym -- ^ @Eurosym@, Eurosym License
+    | Fair -- ^ @Fair@, Fair License
+    | MIT_feh -- ^ @MIT-feh@, feh License
+    | Frameworx_1_0 -- ^ @Frameworx-1.0@, Frameworx Open License 1.0
+    | FreeImage -- ^ @FreeImage@, FreeImage Public License v1.0
+    | FTL -- ^ @FTL@, Freetype Project License
+    | FSFAP -- ^ @FSFAP@, FSF All Permissive License
+    | FSFUL -- ^ @FSFUL@, FSF Unlimited License
+    | FSFULLR -- ^ @FSFULLR@, FSF Unlimited License (with License Retention)
+    | Giftware -- ^ @Giftware@, Giftware License
+    | GL2PS -- ^ @GL2PS@, GL2PS License
+    | Glulxe -- ^ @Glulxe@, Glulxe License
+    | AGPL_3_0 -- ^ @AGPL-3.0@, GNU Affero General Public License v3.0
+    | GFDL_1_1 -- ^ @GFDL-1.1@, GNU Free Documentation License v1.1
+    | GFDL_1_2 -- ^ @GFDL-1.2@, GNU Free Documentation License v1.2
+    | GFDL_1_3 -- ^ @GFDL-1.3@, GNU Free Documentation License v1.3
+    | GPL_1_0 -- ^ @GPL-1.0@, GNU General Public License v1.0 only
+    | GPL_2_0 -- ^ @GPL-2.0@, GNU General Public License v2.0 only
+    | GPL_3_0 -- ^ @GPL-3.0@, GNU General Public License v3.0 only
+    | LGPL_2_1 -- ^ @LGPL-2.1@, GNU Lesser General Public License v2.1 only
+    | LGPL_3_0 -- ^ @LGPL-3.0@, GNU Lesser General Public License v3.0 only
+    | LGPL_2_0 -- ^ @LGPL-2.0@, GNU Library General Public License v2 only
+    | Gnuplot -- ^ @gnuplot@, gnuplot License
+    | GSOAP_1_3b -- ^ @gSOAP-1.3b@, gSOAP Public License v1.3b
+    | HaskellReport -- ^ @HaskellReport@, Haskell Language Report License
+    | HPND -- ^ @HPND@, Historic Permission Notice and Disclaimer
+    | IBM_pibs -- ^ @IBM-pibs@, IBM PowerPC Initialization and Boot Software
+    | IPL_1_0 -- ^ @IPL-1.0@, IBM Public License v1.0
+    | ICU -- ^ @ICU@, ICU License
+    | ImageMagick -- ^ @ImageMagick@, ImageMagick License
+    | IMatix -- ^ @iMatix@, iMatix Standard Function Library Agreement
+    | Imlib2 -- ^ @Imlib2@, Imlib2 License
+    | IJG -- ^ @IJG@, Independent JPEG Group License
+    | Info_ZIP -- ^ @Info-ZIP@, Info-ZIP License
+    | Intel_ACPI -- ^ @Intel-ACPI@, Intel ACPI Software License Agreement
+    | Intel -- ^ @Intel@, Intel Open Source License
+    | Interbase_1_0 -- ^ @Interbase-1.0@, Interbase Public License v1.0
+    | IPA -- ^ @IPA@, IPA Font License
+    | ISC -- ^ @ISC@, ISC License
+    | JasPer_2_0 -- ^ @JasPer-2.0@, JasPer License
+    | JSON -- ^ @JSON@, JSON License
+    | LPPL_1_0 -- ^ @LPPL-1.0@, LaTeX Project Public License v1.0
+    | LPPL_1_1 -- ^ @LPPL-1.1@, LaTeX Project Public License v1.1
+    | LPPL_1_2 -- ^ @LPPL-1.2@, LaTeX Project Public License v1.2
+    | LPPL_1_3a -- ^ @LPPL-1.3a@, LaTeX Project Public License v1.3a
+    | LPPL_1_3c -- ^ @LPPL-1.3c@, LaTeX Project Public License v1.3c
+    | Latex2e -- ^ @Latex2e@, Latex2e License
+    | BSD_3_Clause_LBNL -- ^ @BSD-3-Clause-LBNL@, Lawrence Berkeley National Labs BSD variant license
+    | Leptonica -- ^ @Leptonica@, Leptonica License
+    | LGPLLR -- ^ @LGPLLR@, Lesser General Public License For Linguistic Resources
+    | Libpng -- ^ @Libpng@, libpng License
+    | Libtiff -- ^ @libtiff@, libtiff License
+    | LAL_1_2 -- ^ @LAL-1.2@, Licence Art Libre 1.2
+    | LAL_1_3 -- ^ @LAL-1.3@, Licence Art Libre 1.3
+    | LiLiQ_P_1_1 -- ^ @LiLiQ-P-1.1@, Licence Libre du Québec – Permissive version 1.1
+    | LiLiQ_Rplus_1_1 -- ^ @LiLiQ-Rplus-1.1@, Licence Libre du Québec – Réciprocité forte version 1.1
+    | LiLiQ_R_1_1 -- ^ @LiLiQ-R-1.1@, Licence Libre du Québec – Réciprocité version 1.1
+    | LPL_1_02 -- ^ @LPL-1.02@, Lucent Public License v1.02
+    | LPL_1_0 -- ^ @LPL-1.0@, Lucent Public License Version 1.0
+    | MakeIndex -- ^ @MakeIndex@, MakeIndex License
+    | MTLL -- ^ @MTLL@, Matrix Template Library License
+    | MS_PL -- ^ @MS-PL@, Microsoft Public License
+    | MS_RL -- ^ @MS-RL@, Microsoft Reciprocal License
+    | MirOS -- ^ @MirOS@, MirOS Licence
+    | MITNFA -- ^ @MITNFA@, MIT +no-false-attribs license
+    | MIT -- ^ @MIT@, MIT License
+    | Motosoto -- ^ @Motosoto@, Motosoto License
+    | MPL_1_0 -- ^ @MPL-1.0@, Mozilla Public License 1.0
+    | MPL_1_1 -- ^ @MPL-1.1@, Mozilla Public License 1.1
+    | MPL_2_0 -- ^ @MPL-2.0@, Mozilla Public License 2.0
+    | MPL_2_0_no_copyleft_exception -- ^ @MPL-2.0-no-copyleft-exception@, Mozilla Public License 2.0 (no copyleft exception)
+    | Mpich2 -- ^ @mpich2@, mpich2 License
+    | Multics -- ^ @Multics@, Multics License
+    | Mup -- ^ @Mup@, Mup License
+    | NASA_1_3 -- ^ @NASA-1.3@, NASA Open Source Agreement 1.3
+    | Naumen -- ^ @Naumen@, Naumen Public License
+    | NBPL_1_0 -- ^ @NBPL-1.0@, Net Boolean Public License v1
+    | Net_SNMP -- ^ @Net-SNMP@, Net-SNMP License
+    | NetCDF -- ^ @NetCDF@, NetCDF license
+    | NGPL -- ^ @NGPL@, Nethack General Public License
+    | NOSL -- ^ @NOSL@, Netizen Open Source License
+    | NPL_1_0 -- ^ @NPL-1.0@, Netscape Public License v1.0
+    | NPL_1_1 -- ^ @NPL-1.1@, Netscape Public License v1.1
+    | Newsletr -- ^ @Newsletr@, Newsletr License
+    | NLPL -- ^ @NLPL@, No Limit Public License
+    | Nokia -- ^ @Nokia@, Nokia Open Source License
+    | NPOSL_3_0 -- ^ @NPOSL-3.0@, Non-Profit Open Software License 3.0
+    | NLOD_1_0 -- ^ @NLOD-1.0@, Norwegian Licence for Open Government Data
+    | Noweb -- ^ @Noweb@, Noweb License
+    | NRL -- ^ @NRL@, NRL License
+    | NTP -- ^ @NTP@, NTP License
+    | Nunit -- ^ @Nunit@, Nunit License
+    | OCLC_2_0 -- ^ @OCLC-2.0@, OCLC Research Public License 2.0
+    | ODbL_1_0 -- ^ @ODbL-1.0@, ODC Open Database License v1.0
+    | PDDL_1_0 -- ^ @PDDL-1.0@, ODC Public Domain Dedication & License 1.0
+    | OCCT_PL -- ^ @OCCT-PL@, Open CASCADE Technology Public License
+    | OGTSL -- ^ @OGTSL@, Open Group Test Suite License
+    | OLDAP_2_2_2 -- ^ @OLDAP-2.2.2@, Open LDAP Public License  2.2.2
+    | OLDAP_1_1 -- ^ @OLDAP-1.1@, Open LDAP Public License v1.1
+    | OLDAP_1_2 -- ^ @OLDAP-1.2@, Open LDAP Public License v1.2
+    | OLDAP_1_3 -- ^ @OLDAP-1.3@, Open LDAP Public License v1.3
+    | OLDAP_1_4 -- ^ @OLDAP-1.4@, Open LDAP Public License v1.4
+    | OLDAP_2_0 -- ^ @OLDAP-2.0@, Open LDAP Public License v2.0 (or possibly 2.0A and 2.0B)
+    | OLDAP_2_0_1 -- ^ @OLDAP-2.0.1@, Open LDAP Public License v2.0.1
+    | OLDAP_2_1 -- ^ @OLDAP-2.1@, Open LDAP Public License v2.1
+    | OLDAP_2_2 -- ^ @OLDAP-2.2@, Open LDAP Public License v2.2
+    | OLDAP_2_2_1 -- ^ @OLDAP-2.2.1@, Open LDAP Public License v2.2.1
+    | OLDAP_2_3 -- ^ @OLDAP-2.3@, Open LDAP Public License v2.3
+    | OLDAP_2_4 -- ^ @OLDAP-2.4@, Open LDAP Public License v2.4
+    | OLDAP_2_5 -- ^ @OLDAP-2.5@, Open LDAP Public License v2.5
+    | OLDAP_2_6 -- ^ @OLDAP-2.6@, Open LDAP Public License v2.6
+    | OLDAP_2_7 -- ^ @OLDAP-2.7@, Open LDAP Public License v2.7
+    | OLDAP_2_8 -- ^ @OLDAP-2.8@, Open LDAP Public License v2.8
+    | OML -- ^ @OML@, Open Market License
+    | OPL_1_0 -- ^ @OPL-1.0@, Open Public License v1.0
+    | OSL_1_0 -- ^ @OSL-1.0@, Open Software License 1.0
+    | OSL_1_1 -- ^ @OSL-1.1@, Open Software License 1.1
+    | OSL_2_0 -- ^ @OSL-2.0@, Open Software License 2.0
+    | OSL_2_1 -- ^ @OSL-2.1@, Open Software License 2.1
+    | OSL_3_0 -- ^ @OSL-3.0@, Open Software License 3.0
+    | OpenSSL -- ^ @OpenSSL@, OpenSSL License
+    | OSET_PL_2_1 -- ^ @OSET-PL-2.1@, OSET Public License version 2.1
+    | PHP_3_0 -- ^ @PHP-3.0@, PHP License v3.0
+    | PHP_3_01 -- ^ @PHP-3.01@, PHP License v3.01
+    | Plexus -- ^ @Plexus@, Plexus Classworlds License
+    | PostgreSQL -- ^ @PostgreSQL@, PostgreSQL License
+    | Psfrag -- ^ @psfrag@, psfrag License
+    | Psutils -- ^ @psutils@, psutils License
+    | Python_2_0 -- ^ @Python-2.0@, Python License 2.0
+    | QPL_1_0 -- ^ @QPL-1.0@, Q Public License 1.0
+    | Qhull -- ^ @Qhull@, Qhull License
+    | Rdisc -- ^ @Rdisc@, Rdisc License
+    | RPSL_1_0 -- ^ @RPSL-1.0@, RealNetworks Public Source License v1.0
+    | RPL_1_1 -- ^ @RPL-1.1@, Reciprocal Public License 1.1
+    | RPL_1_5 -- ^ @RPL-1.5@, Reciprocal Public License 1.5
+    | RHeCos_1_1 -- ^ @RHeCos-1.1@, Red Hat eCos Public License v1.1
+    | RSCPL -- ^ @RSCPL@, Ricoh Source Code Public License
+    | RSA_MD -- ^ @RSA-MD@, RSA Message-Digest License 
+    | Ruby -- ^ @Ruby@, Ruby License
+    | SAX_PD -- ^ @SAX-PD@, Sax Public Domain Notice
+    | Saxpath -- ^ @Saxpath@, Saxpath License
+    | SCEA -- ^ @SCEA@, SCEA Shared Source License
+    | SWL -- ^ @SWL@, Scheme Widget Library (SWL) Software License Agreement
+    | SMPPL -- ^ @SMPPL@, Secure Messaging Protocol Public License
+    | Sendmail -- ^ @Sendmail@, Sendmail License
+    | SGI_B_1_0 -- ^ @SGI-B-1.0@, SGI Free Software License B v1.0
+    | SGI_B_1_1 -- ^ @SGI-B-1.1@, SGI Free Software License B v1.1
+    | SGI_B_2_0 -- ^ @SGI-B-2.0@, SGI Free Software License B v2.0
+    | OFL_1_0 -- ^ @OFL-1.0@, SIL Open Font License 1.0
+    | OFL_1_1 -- ^ @OFL-1.1@, SIL Open Font License 1.1
+    | SimPL_2_0 -- ^ @SimPL-2.0@, Simple Public License 2.0
+    | Sleepycat -- ^ @Sleepycat@, Sleepycat License
+    | SNIA -- ^ @SNIA@, SNIA Public License 1.1
+    | Spencer_86 -- ^ @Spencer-86@, Spencer License 86
+    | Spencer_94 -- ^ @Spencer-94@, Spencer License 94
+    | Spencer_99 -- ^ @Spencer-99@, Spencer License 99
+    | SMLNJ -- ^ @SMLNJ@, Standard ML of New Jersey License
+    | SugarCRM_1_1_3 -- ^ @SugarCRM-1.1.3@, SugarCRM Public License v1.1.3
+    | SISSL -- ^ @SISSL@, Sun Industry Standards Source License v1.1
+    | SISSL_1_2 -- ^ @SISSL-1.2@, Sun Industry Standards Source License v1.2
+    | SPL_1_0 -- ^ @SPL-1.0@, Sun Public License v1.0
+    | Watcom_1_0 -- ^ @Watcom-1.0@, Sybase Open Watcom Public License 1.0
+    | TCL -- ^ @TCL@, TCL/TK License
+    | TCP_wrappers -- ^ @TCP-wrappers@, TCP Wrappers License
+    | Unlicense -- ^ @Unlicense@, The Unlicense
+    | TMate -- ^ @TMate@, TMate Open Source License
+    | TORQUE_1_1 -- ^ @TORQUE-1.1@, TORQUE v2.5+ Software License v1.1
+    | TOSL -- ^ @TOSL@, Trusster Open Source License
+    | Unicode_DFS_2015 -- ^ @Unicode-DFS-2015@, Unicode License Agreement - Data Files and Software (2015)
+    | Unicode_DFS_2016 -- ^ @Unicode-DFS-2016@, Unicode License Agreement - Data Files and Software (2016)
+    | Unicode_TOU -- ^ @Unicode-TOU@, Unicode Terms of Use
+    | UPL_1_0 -- ^ @UPL-1.0@, Universal Permissive License v1.0
+    | NCSA -- ^ @NCSA@, University of Illinois/NCSA Open Source License
+    | Vim -- ^ @Vim@, Vim License
+    | VOSTROM -- ^ @VOSTROM@, VOSTROM Public License for Open Source
+    | VSL_1_0 -- ^ @VSL-1.0@, Vovida Software License v1.0
+    | W3C_20150513 -- ^ @W3C-20150513@, W3C Software Notice and Document License (2015-05-13)
+    | W3C_19980720 -- ^ @W3C-19980720@, W3C Software Notice and License (1998-07-20)
+    | W3C -- ^ @W3C@, W3C Software Notice and License (2002-12-31)
+    | Wsuipa -- ^ @Wsuipa@, Wsuipa License
+    | Xnet -- ^ @Xnet@, X.Net License
+    | X11 -- ^ @X11@, X11 License
+    | Xerox -- ^ @Xerox@, Xerox License
+    | XFree86_1_1 -- ^ @XFree86-1.1@, XFree86 License 1.1
+    | Xinetd -- ^ @xinetd@, xinetd License
+    | Xpp -- ^ @xpp@, XPP License
+    | XSkat -- ^ @XSkat@, XSkat License
+    | YPL_1_0 -- ^ @YPL-1.0@, Yahoo! Public License v1.0
+    | YPL_1_1 -- ^ @YPL-1.1@, Yahoo! Public License v1.1
+    | Zed -- ^ @Zed@, Zed License
+    | Zend_2_0 -- ^ @Zend-2.0@, Zend License v2.0
+    | Zimbra_1_3 -- ^ @Zimbra-1.3@, Zimbra Public License v1.3
+    | Zimbra_1_4 -- ^ @Zimbra-1.4@, Zimbra Public License v1.4
+    | Zlib -- ^ @Zlib@, zlib License
+    | Zlib_acknowledgement -- ^ @zlib-acknowledgement@, zlib/libpng License with Acknowledgement
+    | ZPL_1_1 -- ^ @ZPL-1.1@, Zope Public License 1.1
+    | ZPL_2_0 -- ^ @ZPL-2.0@, Zope Public License 2.0
+    | ZPL_2_1 -- ^ @ZPL-2.1@, Zope Public License 2.1
+  deriving (Eq, Ord, Enum, Bounded, Show, Read, Typeable, Data, Generic)
+
+instance Binary LicenseId
+
+instance Pretty LicenseId where
+    pretty = Disp.text . licenseId
+
+instance Parsec LicenseId where
+    parsec = do
+        n <- some $ P.satisfy $ \c -> isAsciiAlphaNum c || c == '-' || c == '.'
+        maybe (fail $ "Unknown SPDX license identifier: " ++ n) return $ mkLicenseId n
+
+instance NFData LicenseId where
+    rnf l = l `seq` ()
+
+-------------------------------------------------------------------------------
+-- License Data
+-------------------------------------------------------------------------------
+
+-- | License SPDX identifier, e.g. @"BSD-3-Clause"@.
+licenseId :: LicenseId -> String
+licenseId Glide = "Glide"
+licenseId Abstyles = "Abstyles"
+licenseId AFL_1_1 = "AFL-1.1"
+licenseId AFL_1_2 = "AFL-1.2"
+licenseId AFL_2_0 = "AFL-2.0"
+licenseId AFL_2_1 = "AFL-2.1"
+licenseId AFL_3_0 = "AFL-3.0"
+licenseId AMPAS = "AMPAS"
+licenseId APL_1_0 = "APL-1.0"
+licenseId Adobe_Glyph = "Adobe-Glyph"
+licenseId APAFML = "APAFML"
+licenseId Adobe_2006 = "Adobe-2006"
+licenseId AGPL_1_0 = "AGPL-1.0"
+licenseId Afmparse = "Afmparse"
+licenseId Aladdin = "Aladdin"
+licenseId ADSL = "ADSL"
+licenseId AMDPLPA = "AMDPLPA"
+licenseId ANTLR_PD = "ANTLR-PD"
+licenseId Apache_1_0 = "Apache-1.0"
+licenseId Apache_1_1 = "Apache-1.1"
+licenseId Apache_2_0 = "Apache-2.0"
+licenseId AML = "AML"
+licenseId APSL_1_0 = "APSL-1.0"
+licenseId APSL_1_1 = "APSL-1.1"
+licenseId APSL_1_2 = "APSL-1.2"
+licenseId APSL_2_0 = "APSL-2.0"
+licenseId Artistic_1_0 = "Artistic-1.0"
+licenseId Artistic_1_0_Perl = "Artistic-1.0-Perl"
+licenseId Artistic_1_0_cl8 = "Artistic-1.0-cl8"
+licenseId Artistic_2_0 = "Artistic-2.0"
+licenseId AAL = "AAL"
+licenseId Bahyph = "Bahyph"
+licenseId Barr = "Barr"
+licenseId Beerware = "Beerware"
+licenseId BitTorrent_1_0 = "BitTorrent-1.0"
+licenseId BitTorrent_1_1 = "BitTorrent-1.1"
+licenseId BSL_1_0 = "BSL-1.0"
+licenseId Borceux = "Borceux"
+licenseId BSD_2_Clause = "BSD-2-Clause"
+licenseId BSD_2_Clause_FreeBSD = "BSD-2-Clause-FreeBSD"
+licenseId BSD_2_Clause_NetBSD = "BSD-2-Clause-NetBSD"
+licenseId BSD_3_Clause = "BSD-3-Clause"
+licenseId BSD_3_Clause_Clear = "BSD-3-Clause-Clear"
+licenseId BSD_3_Clause_No_Nuclear_License = "BSD-3-Clause-No-Nuclear-License"
+licenseId BSD_3_Clause_No_Nuclear_License_2014 = "BSD-3-Clause-No-Nuclear-License-2014"
+licenseId BSD_3_Clause_No_Nuclear_Warranty = "BSD-3-Clause-No-Nuclear-Warranty"
+licenseId BSD_4_Clause = "BSD-4-Clause"
+licenseId BSD_Protection = "BSD-Protection"
+licenseId BSD_Source_Code = "BSD-Source-Code"
+licenseId BSD_3_Clause_Attribution = "BSD-3-Clause-Attribution"
+licenseId NullBSD = "0BSD"
+licenseId BSD_4_Clause_UC = "BSD-4-Clause-UC"
+licenseId Bzip2_1_0_5 = "bzip2-1.0.5"
+licenseId Bzip2_1_0_6 = "bzip2-1.0.6"
+licenseId Caldera = "Caldera"
+licenseId CECILL_1_0 = "CECILL-1.0"
+licenseId CECILL_1_1 = "CECILL-1.1"
+licenseId CECILL_2_0 = "CECILL-2.0"
+licenseId CECILL_2_1 = "CECILL-2.1"
+licenseId CECILL_B = "CECILL-B"
+licenseId CECILL_C = "CECILL-C"
+licenseId ClArtistic = "ClArtistic"
+licenseId MIT_CMU = "MIT-CMU"
+licenseId CNRI_Jython = "CNRI-Jython"
+licenseId CNRI_Python = "CNRI-Python"
+licenseId CNRI_Python_GPL_Compatible = "CNRI-Python-GPL-Compatible"
+licenseId CPOL_1_02 = "CPOL-1.02"
+licenseId CDDL_1_0 = "CDDL-1.0"
+licenseId CDDL_1_1 = "CDDL-1.1"
+licenseId CPAL_1_0 = "CPAL-1.0"
+licenseId CPL_1_0 = "CPL-1.0"
+licenseId CATOSL_1_1 = "CATOSL-1.1"
+licenseId Condor_1_1 = "Condor-1.1"
+licenseId CC_BY_1_0 = "CC-BY-1.0"
+licenseId CC_BY_2_0 = "CC-BY-2.0"
+licenseId CC_BY_2_5 = "CC-BY-2.5"
+licenseId CC_BY_3_0 = "CC-BY-3.0"
+licenseId CC_BY_4_0 = "CC-BY-4.0"
+licenseId CC_BY_ND_1_0 = "CC-BY-ND-1.0"
+licenseId CC_BY_ND_2_0 = "CC-BY-ND-2.0"
+licenseId CC_BY_ND_2_5 = "CC-BY-ND-2.5"
+licenseId CC_BY_ND_3_0 = "CC-BY-ND-3.0"
+licenseId CC_BY_ND_4_0 = "CC-BY-ND-4.0"
+licenseId CC_BY_NC_1_0 = "CC-BY-NC-1.0"
+licenseId CC_BY_NC_2_0 = "CC-BY-NC-2.0"
+licenseId CC_BY_NC_2_5 = "CC-BY-NC-2.5"
+licenseId CC_BY_NC_3_0 = "CC-BY-NC-3.0"
+licenseId CC_BY_NC_4_0 = "CC-BY-NC-4.0"
+licenseId CC_BY_NC_ND_1_0 = "CC-BY-NC-ND-1.0"
+licenseId CC_BY_NC_ND_2_0 = "CC-BY-NC-ND-2.0"
+licenseId CC_BY_NC_ND_2_5 = "CC-BY-NC-ND-2.5"
+licenseId CC_BY_NC_ND_3_0 = "CC-BY-NC-ND-3.0"
+licenseId CC_BY_NC_ND_4_0 = "CC-BY-NC-ND-4.0"
+licenseId CC_BY_NC_SA_1_0 = "CC-BY-NC-SA-1.0"
+licenseId CC_BY_NC_SA_2_0 = "CC-BY-NC-SA-2.0"
+licenseId CC_BY_NC_SA_2_5 = "CC-BY-NC-SA-2.5"
+licenseId CC_BY_NC_SA_3_0 = "CC-BY-NC-SA-3.0"
+licenseId CC_BY_NC_SA_4_0 = "CC-BY-NC-SA-4.0"
+licenseId CC_BY_SA_1_0 = "CC-BY-SA-1.0"
+licenseId CC_BY_SA_2_0 = "CC-BY-SA-2.0"
+licenseId CC_BY_SA_2_5 = "CC-BY-SA-2.5"
+licenseId CC_BY_SA_3_0 = "CC-BY-SA-3.0"
+licenseId CC_BY_SA_4_0 = "CC-BY-SA-4.0"
+licenseId CC0_1_0 = "CC0-1.0"
+licenseId Crossword = "Crossword"
+licenseId CrystalStacker = "CrystalStacker"
+licenseId CUA_OPL_1_0 = "CUA-OPL-1.0"
+licenseId Cube = "Cube"
+licenseId Curl = "curl"
+licenseId D_FSL_1_0 = "D-FSL-1.0"
+licenseId Diffmark = "diffmark"
+licenseId WTFPL = "WTFPL"
+licenseId DOC = "DOC"
+licenseId Dotseqn = "Dotseqn"
+licenseId DSDP = "DSDP"
+licenseId Dvipdfm = "dvipdfm"
+licenseId EPL_1_0 = "EPL-1.0"
+licenseId ECL_1_0 = "ECL-1.0"
+licenseId ECL_2_0 = "ECL-2.0"
+licenseId EGenix = "eGenix"
+licenseId EFL_1_0 = "EFL-1.0"
+licenseId EFL_2_0 = "EFL-2.0"
+licenseId MIT_advertising = "MIT-advertising"
+licenseId MIT_enna = "MIT-enna"
+licenseId Entessa = "Entessa"
+licenseId ErlPL_1_1 = "ErlPL-1.1"
+licenseId EUDatagrid = "EUDatagrid"
+licenseId EUPL_1_0 = "EUPL-1.0"
+licenseId EUPL_1_1 = "EUPL-1.1"
+licenseId Eurosym = "Eurosym"
+licenseId Fair = "Fair"
+licenseId MIT_feh = "MIT-feh"
+licenseId Frameworx_1_0 = "Frameworx-1.0"
+licenseId FreeImage = "FreeImage"
+licenseId FTL = "FTL"
+licenseId FSFAP = "FSFAP"
+licenseId FSFUL = "FSFUL"
+licenseId FSFULLR = "FSFULLR"
+licenseId Giftware = "Giftware"
+licenseId GL2PS = "GL2PS"
+licenseId Glulxe = "Glulxe"
+licenseId AGPL_3_0 = "AGPL-3.0"
+licenseId GFDL_1_1 = "GFDL-1.1"
+licenseId GFDL_1_2 = "GFDL-1.2"
+licenseId GFDL_1_3 = "GFDL-1.3"
+licenseId GPL_1_0 = "GPL-1.0"
+licenseId GPL_2_0 = "GPL-2.0"
+licenseId GPL_3_0 = "GPL-3.0"
+licenseId LGPL_2_1 = "LGPL-2.1"
+licenseId LGPL_3_0 = "LGPL-3.0"
+licenseId LGPL_2_0 = "LGPL-2.0"
+licenseId Gnuplot = "gnuplot"
+licenseId GSOAP_1_3b = "gSOAP-1.3b"
+licenseId HaskellReport = "HaskellReport"
+licenseId HPND = "HPND"
+licenseId IBM_pibs = "IBM-pibs"
+licenseId IPL_1_0 = "IPL-1.0"
+licenseId ICU = "ICU"
+licenseId ImageMagick = "ImageMagick"
+licenseId IMatix = "iMatix"
+licenseId Imlib2 = "Imlib2"
+licenseId IJG = "IJG"
+licenseId Info_ZIP = "Info-ZIP"
+licenseId Intel_ACPI = "Intel-ACPI"
+licenseId Intel = "Intel"
+licenseId Interbase_1_0 = "Interbase-1.0"
+licenseId IPA = "IPA"
+licenseId ISC = "ISC"
+licenseId JasPer_2_0 = "JasPer-2.0"
+licenseId JSON = "JSON"
+licenseId LPPL_1_0 = "LPPL-1.0"
+licenseId LPPL_1_1 = "LPPL-1.1"
+licenseId LPPL_1_2 = "LPPL-1.2"
+licenseId LPPL_1_3a = "LPPL-1.3a"
+licenseId LPPL_1_3c = "LPPL-1.3c"
+licenseId Latex2e = "Latex2e"
+licenseId BSD_3_Clause_LBNL = "BSD-3-Clause-LBNL"
+licenseId Leptonica = "Leptonica"
+licenseId LGPLLR = "LGPLLR"
+licenseId Libpng = "Libpng"
+licenseId Libtiff = "libtiff"
+licenseId LAL_1_2 = "LAL-1.2"
+licenseId LAL_1_3 = "LAL-1.3"
+licenseId LiLiQ_P_1_1 = "LiLiQ-P-1.1"
+licenseId LiLiQ_Rplus_1_1 = "LiLiQ-Rplus-1.1"
+licenseId LiLiQ_R_1_1 = "LiLiQ-R-1.1"
+licenseId LPL_1_02 = "LPL-1.02"
+licenseId LPL_1_0 = "LPL-1.0"
+licenseId MakeIndex = "MakeIndex"
+licenseId MTLL = "MTLL"
+licenseId MS_PL = "MS-PL"
+licenseId MS_RL = "MS-RL"
+licenseId MirOS = "MirOS"
+licenseId MITNFA = "MITNFA"
+licenseId MIT = "MIT"
+licenseId Motosoto = "Motosoto"
+licenseId MPL_1_0 = "MPL-1.0"
+licenseId MPL_1_1 = "MPL-1.1"
+licenseId MPL_2_0 = "MPL-2.0"
+licenseId MPL_2_0_no_copyleft_exception = "MPL-2.0-no-copyleft-exception"
+licenseId Mpich2 = "mpich2"
+licenseId Multics = "Multics"
+licenseId Mup = "Mup"
+licenseId NASA_1_3 = "NASA-1.3"
+licenseId Naumen = "Naumen"
+licenseId NBPL_1_0 = "NBPL-1.0"
+licenseId Net_SNMP = "Net-SNMP"
+licenseId NetCDF = "NetCDF"
+licenseId NGPL = "NGPL"
+licenseId NOSL = "NOSL"
+licenseId NPL_1_0 = "NPL-1.0"
+licenseId NPL_1_1 = "NPL-1.1"
+licenseId Newsletr = "Newsletr"
+licenseId NLPL = "NLPL"
+licenseId Nokia = "Nokia"
+licenseId NPOSL_3_0 = "NPOSL-3.0"
+licenseId NLOD_1_0 = "NLOD-1.0"
+licenseId Noweb = "Noweb"
+licenseId NRL = "NRL"
+licenseId NTP = "NTP"
+licenseId Nunit = "Nunit"
+licenseId OCLC_2_0 = "OCLC-2.0"
+licenseId ODbL_1_0 = "ODbL-1.0"
+licenseId PDDL_1_0 = "PDDL-1.0"
+licenseId OCCT_PL = "OCCT-PL"
+licenseId OGTSL = "OGTSL"
+licenseId OLDAP_2_2_2 = "OLDAP-2.2.2"
+licenseId OLDAP_1_1 = "OLDAP-1.1"
+licenseId OLDAP_1_2 = "OLDAP-1.2"
+licenseId OLDAP_1_3 = "OLDAP-1.3"
+licenseId OLDAP_1_4 = "OLDAP-1.4"
+licenseId OLDAP_2_0 = "OLDAP-2.0"
+licenseId OLDAP_2_0_1 = "OLDAP-2.0.1"
+licenseId OLDAP_2_1 = "OLDAP-2.1"
+licenseId OLDAP_2_2 = "OLDAP-2.2"
+licenseId OLDAP_2_2_1 = "OLDAP-2.2.1"
+licenseId OLDAP_2_3 = "OLDAP-2.3"
+licenseId OLDAP_2_4 = "OLDAP-2.4"
+licenseId OLDAP_2_5 = "OLDAP-2.5"
+licenseId OLDAP_2_6 = "OLDAP-2.6"
+licenseId OLDAP_2_7 = "OLDAP-2.7"
+licenseId OLDAP_2_8 = "OLDAP-2.8"
+licenseId OML = "OML"
+licenseId OPL_1_0 = "OPL-1.0"
+licenseId OSL_1_0 = "OSL-1.0"
+licenseId OSL_1_1 = "OSL-1.1"
+licenseId OSL_2_0 = "OSL-2.0"
+licenseId OSL_2_1 = "OSL-2.1"
+licenseId OSL_3_0 = "OSL-3.0"
+licenseId OpenSSL = "OpenSSL"
+licenseId OSET_PL_2_1 = "OSET-PL-2.1"
+licenseId PHP_3_0 = "PHP-3.0"
+licenseId PHP_3_01 = "PHP-3.01"
+licenseId Plexus = "Plexus"
+licenseId PostgreSQL = "PostgreSQL"
+licenseId Psfrag = "psfrag"
+licenseId Psutils = "psutils"
+licenseId Python_2_0 = "Python-2.0"
+licenseId QPL_1_0 = "QPL-1.0"
+licenseId Qhull = "Qhull"
+licenseId Rdisc = "Rdisc"
+licenseId RPSL_1_0 = "RPSL-1.0"
+licenseId RPL_1_1 = "RPL-1.1"
+licenseId RPL_1_5 = "RPL-1.5"
+licenseId RHeCos_1_1 = "RHeCos-1.1"
+licenseId RSCPL = "RSCPL"
+licenseId RSA_MD = "RSA-MD"
+licenseId Ruby = "Ruby"
+licenseId SAX_PD = "SAX-PD"
+licenseId Saxpath = "Saxpath"
+licenseId SCEA = "SCEA"
+licenseId SWL = "SWL"
+licenseId SMPPL = "SMPPL"
+licenseId Sendmail = "Sendmail"
+licenseId SGI_B_1_0 = "SGI-B-1.0"
+licenseId SGI_B_1_1 = "SGI-B-1.1"
+licenseId SGI_B_2_0 = "SGI-B-2.0"
+licenseId OFL_1_0 = "OFL-1.0"
+licenseId OFL_1_1 = "OFL-1.1"
+licenseId SimPL_2_0 = "SimPL-2.0"
+licenseId Sleepycat = "Sleepycat"
+licenseId SNIA = "SNIA"
+licenseId Spencer_86 = "Spencer-86"
+licenseId Spencer_94 = "Spencer-94"
+licenseId Spencer_99 = "Spencer-99"
+licenseId SMLNJ = "SMLNJ"
+licenseId SugarCRM_1_1_3 = "SugarCRM-1.1.3"
+licenseId SISSL = "SISSL"
+licenseId SISSL_1_2 = "SISSL-1.2"
+licenseId SPL_1_0 = "SPL-1.0"
+licenseId Watcom_1_0 = "Watcom-1.0"
+licenseId TCL = "TCL"
+licenseId TCP_wrappers = "TCP-wrappers"
+licenseId Unlicense = "Unlicense"
+licenseId TMate = "TMate"
+licenseId TORQUE_1_1 = "TORQUE-1.1"
+licenseId TOSL = "TOSL"
+licenseId Unicode_DFS_2015 = "Unicode-DFS-2015"
+licenseId Unicode_DFS_2016 = "Unicode-DFS-2016"
+licenseId Unicode_TOU = "Unicode-TOU"
+licenseId UPL_1_0 = "UPL-1.0"
+licenseId NCSA = "NCSA"
+licenseId Vim = "Vim"
+licenseId VOSTROM = "VOSTROM"
+licenseId VSL_1_0 = "VSL-1.0"
+licenseId W3C_20150513 = "W3C-20150513"
+licenseId W3C_19980720 = "W3C-19980720"
+licenseId W3C = "W3C"
+licenseId Wsuipa = "Wsuipa"
+licenseId Xnet = "Xnet"
+licenseId X11 = "X11"
+licenseId Xerox = "Xerox"
+licenseId XFree86_1_1 = "XFree86-1.1"
+licenseId Xinetd = "xinetd"
+licenseId Xpp = "xpp"
+licenseId XSkat = "XSkat"
+licenseId YPL_1_0 = "YPL-1.0"
+licenseId YPL_1_1 = "YPL-1.1"
+licenseId Zed = "Zed"
+licenseId Zend_2_0 = "Zend-2.0"
+licenseId Zimbra_1_3 = "Zimbra-1.3"
+licenseId Zimbra_1_4 = "Zimbra-1.4"
+licenseId Zlib = "Zlib"
+licenseId Zlib_acknowledgement = "zlib-acknowledgement"
+licenseId ZPL_1_1 = "ZPL-1.1"
+licenseId ZPL_2_0 = "ZPL-2.0"
+licenseId ZPL_2_1 = "ZPL-2.1"
+
+-- | License name, e.g. @"GNU General Public License v2.0 only"@
+licenseName :: LicenseId -> String
+licenseName Glide = "3dfx Glide License"
+licenseName Abstyles = "Abstyles License"
+licenseName AFL_1_1 = "Academic Free License v1.1"
+licenseName AFL_1_2 = "Academic Free License v1.2"
+licenseName AFL_2_0 = "Academic Free License v2.0"
+licenseName AFL_2_1 = "Academic Free License v2.1"
+licenseName AFL_3_0 = "Academic Free License v3.0"
+licenseName AMPAS = "Academy of Motion Picture Arts and Sciences BSD"
+licenseName APL_1_0 = "Adaptive Public License 1.0"
+licenseName Adobe_Glyph = "Adobe Glyph List License"
+licenseName APAFML = "Adobe Postscript AFM License"
+licenseName Adobe_2006 = "Adobe Systems Incorporated Source Code License Agreement"
+licenseName AGPL_1_0 = "Affero General Public License v1.0"
+licenseName Afmparse = "Afmparse License"
+licenseName Aladdin = "Aladdin Free Public License"
+licenseName ADSL = "Amazon Digital Services License"
+licenseName AMDPLPA = "AMD's plpa_map.c License"
+licenseName ANTLR_PD = "ANTLR Software Rights Notice"
+licenseName Apache_1_0 = "Apache License 1.0"
+licenseName Apache_1_1 = "Apache License 1.1"
+licenseName Apache_2_0 = "Apache License 2.0"
+licenseName AML = "Apple MIT License"
+licenseName APSL_1_0 = "Apple Public Source License 1.0"
+licenseName APSL_1_1 = "Apple Public Source License 1.1"
+licenseName APSL_1_2 = "Apple Public Source License 1.2"
+licenseName APSL_2_0 = "Apple Public Source License 2.0"
+licenseName Artistic_1_0 = "Artistic License 1.0"
+licenseName Artistic_1_0_Perl = "Artistic License 1.0 (Perl)"
+licenseName Artistic_1_0_cl8 = "Artistic License 1.0 w/clause 8"
+licenseName Artistic_2_0 = "Artistic License 2.0"
+licenseName AAL = "Attribution Assurance License"
+licenseName Bahyph = "Bahyph License"
+licenseName Barr = "Barr License"
+licenseName Beerware = "Beerware License"
+licenseName BitTorrent_1_0 = "BitTorrent Open Source License v1.0"
+licenseName BitTorrent_1_1 = "BitTorrent Open Source License v1.1"
+licenseName BSL_1_0 = "Boost Software License 1.0"
+licenseName Borceux = "Borceux license"
+licenseName BSD_2_Clause = "BSD 2-clause \"Simplified\" License"
+licenseName BSD_2_Clause_FreeBSD = "BSD 2-clause FreeBSD License"
+licenseName BSD_2_Clause_NetBSD = "BSD 2-clause NetBSD License"
+licenseName BSD_3_Clause = "BSD 3-clause \"New\" or \"Revised\" License"
+licenseName BSD_3_Clause_Clear = "BSD 3-clause Clear License"
+licenseName BSD_3_Clause_No_Nuclear_License = "BSD 3-Clause No Nuclear License"
+licenseName BSD_3_Clause_No_Nuclear_License_2014 = "BSD 3-Clause No Nuclear License 2014"
+licenseName BSD_3_Clause_No_Nuclear_Warranty = "BSD 3-Clause No Nuclear Warranty"
+licenseName BSD_4_Clause = "BSD 4-clause \"Original\" or \"Old\" License"
+licenseName BSD_Protection = "BSD Protection License"
+licenseName BSD_Source_Code = "BSD Source Code Attribution"
+licenseName BSD_3_Clause_Attribution = "BSD with attribution"
+licenseName NullBSD = "BSD Zero Clause License"
+licenseName BSD_4_Clause_UC = "BSD-4-Clause (University of California-Specific)"
+licenseName Bzip2_1_0_5 = "bzip2 and libbzip2 License v1.0.5"
+licenseName Bzip2_1_0_6 = "bzip2 and libbzip2 License v1.0.6"
+licenseName Caldera = "Caldera License"
+licenseName CECILL_1_0 = "CeCILL Free Software License Agreement v1.0"
+licenseName CECILL_1_1 = "CeCILL Free Software License Agreement v1.1"
+licenseName CECILL_2_0 = "CeCILL Free Software License Agreement v2.0"
+licenseName CECILL_2_1 = "CeCILL Free Software License Agreement v2.1"
+licenseName CECILL_B = "CeCILL-B Free Software License Agreement"
+licenseName CECILL_C = "CeCILL-C Free Software License Agreement"
+licenseName ClArtistic = "Clarified Artistic License"
+licenseName MIT_CMU = "CMU License"
+licenseName CNRI_Jython = "CNRI Jython License"
+licenseName CNRI_Python = "CNRI Python License"
+licenseName CNRI_Python_GPL_Compatible = "CNRI Python Open Source GPL Compatible License Agreement"
+licenseName CPOL_1_02 = "Code Project Open License 1.02"
+licenseName CDDL_1_0 = "Common Development and Distribution License 1.0"
+licenseName CDDL_1_1 = "Common Development and Distribution License 1.1"
+licenseName CPAL_1_0 = "Common Public Attribution License 1.0"
+licenseName CPL_1_0 = "Common Public License 1.0"
+licenseName CATOSL_1_1 = "Computer Associates Trusted Open Source License 1.1"
+licenseName Condor_1_1 = "Condor Public License v1.1"
+licenseName CC_BY_1_0 = "Creative Commons Attribution 1.0"
+licenseName CC_BY_2_0 = "Creative Commons Attribution 2.0"
+licenseName CC_BY_2_5 = "Creative Commons Attribution 2.5"
+licenseName CC_BY_3_0 = "Creative Commons Attribution 3.0"
+licenseName CC_BY_4_0 = "Creative Commons Attribution 4.0"
+licenseName CC_BY_ND_1_0 = "Creative Commons Attribution No Derivatives 1.0"
+licenseName CC_BY_ND_2_0 = "Creative Commons Attribution No Derivatives 2.0"
+licenseName CC_BY_ND_2_5 = "Creative Commons Attribution No Derivatives 2.5"
+licenseName CC_BY_ND_3_0 = "Creative Commons Attribution No Derivatives 3.0"
+licenseName CC_BY_ND_4_0 = "Creative Commons Attribution No Derivatives 4.0"
+licenseName CC_BY_NC_1_0 = "Creative Commons Attribution Non Commercial 1.0"
+licenseName CC_BY_NC_2_0 = "Creative Commons Attribution Non Commercial 2.0"
+licenseName CC_BY_NC_2_5 = "Creative Commons Attribution Non Commercial 2.5"
+licenseName CC_BY_NC_3_0 = "Creative Commons Attribution Non Commercial 3.0"
+licenseName CC_BY_NC_4_0 = "Creative Commons Attribution Non Commercial 4.0"
+licenseName CC_BY_NC_ND_1_0 = "Creative Commons Attribution Non Commercial No Derivatives 1.0"
+licenseName CC_BY_NC_ND_2_0 = "Creative Commons Attribution Non Commercial No Derivatives 2.0"
+licenseName CC_BY_NC_ND_2_5 = "Creative Commons Attribution Non Commercial No Derivatives 2.5"
+licenseName CC_BY_NC_ND_3_0 = "Creative Commons Attribution Non Commercial No Derivatives 3.0"
+licenseName CC_BY_NC_ND_4_0 = "Creative Commons Attribution Non Commercial No Derivatives 4.0"
+licenseName CC_BY_NC_SA_1_0 = "Creative Commons Attribution Non Commercial Share Alike 1.0"
+licenseName CC_BY_NC_SA_2_0 = "Creative Commons Attribution Non Commercial Share Alike 2.0"
+licenseName CC_BY_NC_SA_2_5 = "Creative Commons Attribution Non Commercial Share Alike 2.5"
+licenseName CC_BY_NC_SA_3_0 = "Creative Commons Attribution Non Commercial Share Alike 3.0"
+licenseName CC_BY_NC_SA_4_0 = "Creative Commons Attribution Non Commercial Share Alike 4.0"
+licenseName CC_BY_SA_1_0 = "Creative Commons Attribution Share Alike 1.0"
+licenseName CC_BY_SA_2_0 = "Creative Commons Attribution Share Alike 2.0"
+licenseName CC_BY_SA_2_5 = "Creative Commons Attribution Share Alike 2.5"
+licenseName CC_BY_SA_3_0 = "Creative Commons Attribution Share Alike 3.0"
+licenseName CC_BY_SA_4_0 = "Creative Commons Attribution Share Alike 4.0"
+licenseName CC0_1_0 = "Creative Commons Zero v1.0 Universal"
+licenseName Crossword = "Crossword License"
+licenseName CrystalStacker = "CrystalStacker License"
+licenseName CUA_OPL_1_0 = "CUA Office Public License v1.0"
+licenseName Cube = "Cube License"
+licenseName Curl = "curl License"
+licenseName D_FSL_1_0 = "Deutsche Freie Software Lizenz"
+licenseName Diffmark = "diffmark license"
+licenseName WTFPL = "Do What The F*ck You Want To Public License"
+licenseName DOC = "DOC License"
+licenseName Dotseqn = "Dotseqn License"
+licenseName DSDP = "DSDP License"
+licenseName Dvipdfm = "dvipdfm License"
+licenseName EPL_1_0 = "Eclipse Public License 1.0"
+licenseName ECL_1_0 = "Educational Community License v1.0"
+licenseName ECL_2_0 = "Educational Community License v2.0"
+licenseName EGenix = "eGenix.com Public License 1.1.0"
+licenseName EFL_1_0 = "Eiffel Forum License v1.0"
+licenseName EFL_2_0 = "Eiffel Forum License v2.0"
+licenseName MIT_advertising = "Enlightenment License (e16)"
+licenseName MIT_enna = "enna License"
+licenseName Entessa = "Entessa Public License v1.0"
+licenseName ErlPL_1_1 = "Erlang Public License v1.1"
+licenseName EUDatagrid = "EU DataGrid Software License"
+licenseName EUPL_1_0 = "European Union Public License 1.0"
+licenseName EUPL_1_1 = "European Union Public License 1.1"
+licenseName Eurosym = "Eurosym License"
+licenseName Fair = "Fair License"
+licenseName MIT_feh = "feh License"
+licenseName Frameworx_1_0 = "Frameworx Open License 1.0"
+licenseName FreeImage = "FreeImage Public License v1.0"
+licenseName FTL = "Freetype Project License"
+licenseName FSFAP = "FSF All Permissive License"
+licenseName FSFUL = "FSF Unlimited License"
+licenseName FSFULLR = "FSF Unlimited License (with License Retention)"
+licenseName Giftware = "Giftware License"
+licenseName GL2PS = "GL2PS License"
+licenseName Glulxe = "Glulxe License"
+licenseName AGPL_3_0 = "GNU Affero General Public License v3.0"
+licenseName GFDL_1_1 = "GNU Free Documentation License v1.1"
+licenseName GFDL_1_2 = "GNU Free Documentation License v1.2"
+licenseName GFDL_1_3 = "GNU Free Documentation License v1.3"
+licenseName GPL_1_0 = "GNU General Public License v1.0 only"
+licenseName GPL_2_0 = "GNU General Public License v2.0 only"
+licenseName GPL_3_0 = "GNU General Public License v3.0 only"
+licenseName LGPL_2_1 = "GNU Lesser General Public License v2.1 only"
+licenseName LGPL_3_0 = "GNU Lesser General Public License v3.0 only"
+licenseName LGPL_2_0 = "GNU Library General Public License v2 only"
+licenseName Gnuplot = "gnuplot License"
+licenseName GSOAP_1_3b = "gSOAP Public License v1.3b"
+licenseName HaskellReport = "Haskell Language Report License"
+licenseName HPND = "Historic Permission Notice and Disclaimer"
+licenseName IBM_pibs = "IBM PowerPC Initialization and Boot Software"
+licenseName IPL_1_0 = "IBM Public License v1.0"
+licenseName ICU = "ICU License"
+licenseName ImageMagick = "ImageMagick License"
+licenseName IMatix = "iMatix Standard Function Library Agreement"
+licenseName Imlib2 = "Imlib2 License"
+licenseName IJG = "Independent JPEG Group License"
+licenseName Info_ZIP = "Info-ZIP License"
+licenseName Intel_ACPI = "Intel ACPI Software License Agreement"
+licenseName Intel = "Intel Open Source License"
+licenseName Interbase_1_0 = "Interbase Public License v1.0"
+licenseName IPA = "IPA Font License"
+licenseName ISC = "ISC License"
+licenseName JasPer_2_0 = "JasPer License"
+licenseName JSON = "JSON License"
+licenseName LPPL_1_0 = "LaTeX Project Public License v1.0"
+licenseName LPPL_1_1 = "LaTeX Project Public License v1.1"
+licenseName LPPL_1_2 = "LaTeX Project Public License v1.2"
+licenseName LPPL_1_3a = "LaTeX Project Public License v1.3a"
+licenseName LPPL_1_3c = "LaTeX Project Public License v1.3c"
+licenseName Latex2e = "Latex2e License"
+licenseName BSD_3_Clause_LBNL = "Lawrence Berkeley National Labs BSD variant license"
+licenseName Leptonica = "Leptonica License"
+licenseName LGPLLR = "Lesser General Public License For Linguistic Resources"
+licenseName Libpng = "libpng License"
+licenseName Libtiff = "libtiff License"
+licenseName LAL_1_2 = "Licence Art Libre 1.2"
+licenseName LAL_1_3 = "Licence Art Libre 1.3"
+licenseName LiLiQ_P_1_1 = "Licence Libre du Qu\233bec \8211 Permissive version 1.1"
+licenseName LiLiQ_Rplus_1_1 = "Licence Libre du Qu\233bec \8211 R\233ciprocit\233 forte version 1.1"
+licenseName LiLiQ_R_1_1 = "Licence Libre du Qu\233bec \8211 R\233ciprocit\233 version 1.1"
+licenseName LPL_1_02 = "Lucent Public License v1.02"
+licenseName LPL_1_0 = "Lucent Public License Version 1.0"
+licenseName MakeIndex = "MakeIndex License"
+licenseName MTLL = "Matrix Template Library License"
+licenseName MS_PL = "Microsoft Public License"
+licenseName MS_RL = "Microsoft Reciprocal License"
+licenseName MirOS = "MirOS Licence"
+licenseName MITNFA = "MIT +no-false-attribs license"
+licenseName MIT = "MIT License"
+licenseName Motosoto = "Motosoto License"
+licenseName MPL_1_0 = "Mozilla Public License 1.0"
+licenseName MPL_1_1 = "Mozilla Public License 1.1"
+licenseName MPL_2_0 = "Mozilla Public License 2.0"
+licenseName MPL_2_0_no_copyleft_exception = "Mozilla Public License 2.0 (no copyleft exception)"
+licenseName Mpich2 = "mpich2 License"
+licenseName Multics = "Multics License"
+licenseName Mup = "Mup License"
+licenseName NASA_1_3 = "NASA Open Source Agreement 1.3"
+licenseName Naumen = "Naumen Public License"
+licenseName NBPL_1_0 = "Net Boolean Public License v1"
+licenseName Net_SNMP = "Net-SNMP License"
+licenseName NetCDF = "NetCDF license"
+licenseName NGPL = "Nethack General Public License"
+licenseName NOSL = "Netizen Open Source License"
+licenseName NPL_1_0 = "Netscape Public License v1.0"
+licenseName NPL_1_1 = "Netscape Public License v1.1"
+licenseName Newsletr = "Newsletr License"
+licenseName NLPL = "No Limit Public License"
+licenseName Nokia = "Nokia Open Source License"
+licenseName NPOSL_3_0 = "Non-Profit Open Software License 3.0"
+licenseName NLOD_1_0 = "Norwegian Licence for Open Government Data"
+licenseName Noweb = "Noweb License"
+licenseName NRL = "NRL License"
+licenseName NTP = "NTP License"
+licenseName Nunit = "Nunit License"
+licenseName OCLC_2_0 = "OCLC Research Public License 2.0"
+licenseName ODbL_1_0 = "ODC Open Database License v1.0"
+licenseName PDDL_1_0 = "ODC Public Domain Dedication & License 1.0"
+licenseName OCCT_PL = "Open CASCADE Technology Public License"
+licenseName OGTSL = "Open Group Test Suite License"
+licenseName OLDAP_2_2_2 = "Open LDAP Public License  2.2.2"
+licenseName OLDAP_1_1 = "Open LDAP Public License v1.1"
+licenseName OLDAP_1_2 = "Open LDAP Public License v1.2"
+licenseName OLDAP_1_3 = "Open LDAP Public License v1.3"
+licenseName OLDAP_1_4 = "Open LDAP Public License v1.4"
+licenseName OLDAP_2_0 = "Open LDAP Public License v2.0 (or possibly 2.0A and 2.0B)"
+licenseName OLDAP_2_0_1 = "Open LDAP Public License v2.0.1"
+licenseName OLDAP_2_1 = "Open LDAP Public License v2.1"
+licenseName OLDAP_2_2 = "Open LDAP Public License v2.2"
+licenseName OLDAP_2_2_1 = "Open LDAP Public License v2.2.1"
+licenseName OLDAP_2_3 = "Open LDAP Public License v2.3"
+licenseName OLDAP_2_4 = "Open LDAP Public License v2.4"
+licenseName OLDAP_2_5 = "Open LDAP Public License v2.5"
+licenseName OLDAP_2_6 = "Open LDAP Public License v2.6"
+licenseName OLDAP_2_7 = "Open LDAP Public License v2.7"
+licenseName OLDAP_2_8 = "Open LDAP Public License v2.8"
+licenseName OML = "Open Market License"
+licenseName OPL_1_0 = "Open Public License v1.0"
+licenseName OSL_1_0 = "Open Software License 1.0"
+licenseName OSL_1_1 = "Open Software License 1.1"
+licenseName OSL_2_0 = "Open Software License 2.0"
+licenseName OSL_2_1 = "Open Software License 2.1"
+licenseName OSL_3_0 = "Open Software License 3.0"
+licenseName OpenSSL = "OpenSSL License"
+licenseName OSET_PL_2_1 = "OSET Public License version 2.1"
+licenseName PHP_3_0 = "PHP License v3.0"
+licenseName PHP_3_01 = "PHP License v3.01"
+licenseName Plexus = "Plexus Classworlds License"
+licenseName PostgreSQL = "PostgreSQL License"
+licenseName Psfrag = "psfrag License"
+licenseName Psutils = "psutils License"
+licenseName Python_2_0 = "Python License 2.0"
+licenseName QPL_1_0 = "Q Public License 1.0"
+licenseName Qhull = "Qhull License"
+licenseName Rdisc = "Rdisc License"
+licenseName RPSL_1_0 = "RealNetworks Public Source License v1.0"
+licenseName RPL_1_1 = "Reciprocal Public License 1.1"
+licenseName RPL_1_5 = "Reciprocal Public License 1.5"
+licenseName RHeCos_1_1 = "Red Hat eCos Public License v1.1"
+licenseName RSCPL = "Ricoh Source Code Public License"
+licenseName RSA_MD = "RSA Message-Digest License "
+licenseName Ruby = "Ruby License"
+licenseName SAX_PD = "Sax Public Domain Notice"
+licenseName Saxpath = "Saxpath License"
+licenseName SCEA = "SCEA Shared Source License"
+licenseName SWL = "Scheme Widget Library (SWL) Software License Agreement"
+licenseName SMPPL = "Secure Messaging Protocol Public License"
+licenseName Sendmail = "Sendmail License"
+licenseName SGI_B_1_0 = "SGI Free Software License B v1.0"
+licenseName SGI_B_1_1 = "SGI Free Software License B v1.1"
+licenseName SGI_B_2_0 = "SGI Free Software License B v2.0"
+licenseName OFL_1_0 = "SIL Open Font License 1.0"
+licenseName OFL_1_1 = "SIL Open Font License 1.1"
+licenseName SimPL_2_0 = "Simple Public License 2.0"
+licenseName Sleepycat = "Sleepycat License"
+licenseName SNIA = "SNIA Public License 1.1"
+licenseName Spencer_86 = "Spencer License 86"
+licenseName Spencer_94 = "Spencer License 94"
+licenseName Spencer_99 = "Spencer License 99"
+licenseName SMLNJ = "Standard ML of New Jersey License"
+licenseName SugarCRM_1_1_3 = "SugarCRM Public License v1.1.3"
+licenseName SISSL = "Sun Industry Standards Source License v1.1"
+licenseName SISSL_1_2 = "Sun Industry Standards Source License v1.2"
+licenseName SPL_1_0 = "Sun Public License v1.0"
+licenseName Watcom_1_0 = "Sybase Open Watcom Public License 1.0"
+licenseName TCL = "TCL/TK License"
+licenseName TCP_wrappers = "TCP Wrappers License"
+licenseName Unlicense = "The Unlicense"
+licenseName TMate = "TMate Open Source License"
+licenseName TORQUE_1_1 = "TORQUE v2.5+ Software License v1.1"
+licenseName TOSL = "Trusster Open Source License"
+licenseName Unicode_DFS_2015 = "Unicode License Agreement - Data Files and Software (2015)"
+licenseName Unicode_DFS_2016 = "Unicode License Agreement - Data Files and Software (2016)"
+licenseName Unicode_TOU = "Unicode Terms of Use"
+licenseName UPL_1_0 = "Universal Permissive License v1.0"
+licenseName NCSA = "University of Illinois/NCSA Open Source License"
+licenseName Vim = "Vim License"
+licenseName VOSTROM = "VOSTROM Public License for Open Source"
+licenseName VSL_1_0 = "Vovida Software License v1.0"
+licenseName W3C_20150513 = "W3C Software Notice and Document License (2015-05-13)"
+licenseName W3C_19980720 = "W3C Software Notice and License (1998-07-20)"
+licenseName W3C = "W3C Software Notice and License (2002-12-31)"
+licenseName Wsuipa = "Wsuipa License"
+licenseName Xnet = "X.Net License"
+licenseName X11 = "X11 License"
+licenseName Xerox = "Xerox License"
+licenseName XFree86_1_1 = "XFree86 License 1.1"
+licenseName Xinetd = "xinetd License"
+licenseName Xpp = "XPP License"
+licenseName XSkat = "XSkat License"
+licenseName YPL_1_0 = "Yahoo! Public License v1.0"
+licenseName YPL_1_1 = "Yahoo! Public License v1.1"
+licenseName Zed = "Zed License"
+licenseName Zend_2_0 = "Zend License v2.0"
+licenseName Zimbra_1_3 = "Zimbra Public License v1.3"
+licenseName Zimbra_1_4 = "Zimbra Public License v1.4"
+licenseName Zlib = "zlib License"
+licenseName Zlib_acknowledgement = "zlib/libpng License with Acknowledgement"
+licenseName ZPL_1_1 = "Zope Public License 1.1"
+licenseName ZPL_2_0 = "Zope Public License 2.0"
+licenseName ZPL_2_1 = "Zope Public License 2.1"
+
+-- | Whether the license is approved by Open Source Initiative (OSI).
+--
+-- See <https://opensource.org/licenses/alphabetical>.
+licenseIsOsiApproved :: LicenseId -> Bool
+licenseIsOsiApproved Glide = False
+licenseIsOsiApproved Abstyles = False
+licenseIsOsiApproved AFL_1_1 = True
+licenseIsOsiApproved AFL_1_2 = True
+licenseIsOsiApproved AFL_2_0 = True
+licenseIsOsiApproved AFL_2_1 = True
+licenseIsOsiApproved AFL_3_0 = True
+licenseIsOsiApproved AMPAS = False
+licenseIsOsiApproved APL_1_0 = True
+licenseIsOsiApproved Adobe_Glyph = False
+licenseIsOsiApproved APAFML = False
+licenseIsOsiApproved Adobe_2006 = False
+licenseIsOsiApproved AGPL_1_0 = False
+licenseIsOsiApproved Afmparse = False
+licenseIsOsiApproved Aladdin = False
+licenseIsOsiApproved ADSL = False
+licenseIsOsiApproved AMDPLPA = False
+licenseIsOsiApproved ANTLR_PD = False
+licenseIsOsiApproved Apache_1_0 = False
+licenseIsOsiApproved Apache_1_1 = True
+licenseIsOsiApproved Apache_2_0 = True
+licenseIsOsiApproved AML = False
+licenseIsOsiApproved APSL_1_0 = True
+licenseIsOsiApproved APSL_1_1 = True
+licenseIsOsiApproved APSL_1_2 = True
+licenseIsOsiApproved APSL_2_0 = True
+licenseIsOsiApproved Artistic_1_0 = True
+licenseIsOsiApproved Artistic_1_0_Perl = True
+licenseIsOsiApproved Artistic_1_0_cl8 = True
+licenseIsOsiApproved Artistic_2_0 = True
+licenseIsOsiApproved AAL = True
+licenseIsOsiApproved Bahyph = False
+licenseIsOsiApproved Barr = False
+licenseIsOsiApproved Beerware = False
+licenseIsOsiApproved BitTorrent_1_0 = False
+licenseIsOsiApproved BitTorrent_1_1 = False
+licenseIsOsiApproved BSL_1_0 = True
+licenseIsOsiApproved Borceux = False
+licenseIsOsiApproved BSD_2_Clause = True
+licenseIsOsiApproved BSD_2_Clause_FreeBSD = False
+licenseIsOsiApproved BSD_2_Clause_NetBSD = False
+licenseIsOsiApproved BSD_3_Clause = True
+licenseIsOsiApproved BSD_3_Clause_Clear = False
+licenseIsOsiApproved BSD_3_Clause_No_Nuclear_License = False
+licenseIsOsiApproved BSD_3_Clause_No_Nuclear_License_2014 = False
+licenseIsOsiApproved BSD_3_Clause_No_Nuclear_Warranty = False
+licenseIsOsiApproved BSD_4_Clause = False
+licenseIsOsiApproved BSD_Protection = False
+licenseIsOsiApproved BSD_Source_Code = False
+licenseIsOsiApproved BSD_3_Clause_Attribution = False
+licenseIsOsiApproved NullBSD = True
+licenseIsOsiApproved BSD_4_Clause_UC = False
+licenseIsOsiApproved Bzip2_1_0_5 = False
+licenseIsOsiApproved Bzip2_1_0_6 = False
+licenseIsOsiApproved Caldera = False
+licenseIsOsiApproved CECILL_1_0 = False
+licenseIsOsiApproved CECILL_1_1 = False
+licenseIsOsiApproved CECILL_2_0 = False
+licenseIsOsiApproved CECILL_2_1 = True
+licenseIsOsiApproved CECILL_B = False
+licenseIsOsiApproved CECILL_C = False
+licenseIsOsiApproved ClArtistic = False
+licenseIsOsiApproved MIT_CMU = False
+licenseIsOsiApproved CNRI_Jython = False
+licenseIsOsiApproved CNRI_Python = True
+licenseIsOsiApproved CNRI_Python_GPL_Compatible = False
+licenseIsOsiApproved CPOL_1_02 = False
+licenseIsOsiApproved CDDL_1_0 = True
+licenseIsOsiApproved CDDL_1_1 = False
+licenseIsOsiApproved CPAL_1_0 = True
+licenseIsOsiApproved CPL_1_0 = True
+licenseIsOsiApproved CATOSL_1_1 = True
+licenseIsOsiApproved Condor_1_1 = False
+licenseIsOsiApproved CC_BY_1_0 = False
+licenseIsOsiApproved CC_BY_2_0 = False
+licenseIsOsiApproved CC_BY_2_5 = False
+licenseIsOsiApproved CC_BY_3_0 = False
+licenseIsOsiApproved CC_BY_4_0 = False
+licenseIsOsiApproved CC_BY_ND_1_0 = False
+licenseIsOsiApproved CC_BY_ND_2_0 = False
+licenseIsOsiApproved CC_BY_ND_2_5 = False
+licenseIsOsiApproved CC_BY_ND_3_0 = False
+licenseIsOsiApproved CC_BY_ND_4_0 = False
+licenseIsOsiApproved CC_BY_NC_1_0 = False
+licenseIsOsiApproved CC_BY_NC_2_0 = False
+licenseIsOsiApproved CC_BY_NC_2_5 = False
+licenseIsOsiApproved CC_BY_NC_3_0 = False
+licenseIsOsiApproved CC_BY_NC_4_0 = False
+licenseIsOsiApproved CC_BY_NC_ND_1_0 = False
+licenseIsOsiApproved CC_BY_NC_ND_2_0 = False
+licenseIsOsiApproved CC_BY_NC_ND_2_5 = False
+licenseIsOsiApproved CC_BY_NC_ND_3_0 = False
+licenseIsOsiApproved CC_BY_NC_ND_4_0 = False
+licenseIsOsiApproved CC_BY_NC_SA_1_0 = False
+licenseIsOsiApproved CC_BY_NC_SA_2_0 = False
+licenseIsOsiApproved CC_BY_NC_SA_2_5 = False
+licenseIsOsiApproved CC_BY_NC_SA_3_0 = False
+licenseIsOsiApproved CC_BY_NC_SA_4_0 = False
+licenseIsOsiApproved CC_BY_SA_1_0 = False
+licenseIsOsiApproved CC_BY_SA_2_0 = False
+licenseIsOsiApproved CC_BY_SA_2_5 = False
+licenseIsOsiApproved CC_BY_SA_3_0 = False
+licenseIsOsiApproved CC_BY_SA_4_0 = False
+licenseIsOsiApproved CC0_1_0 = False
+licenseIsOsiApproved Crossword = False
+licenseIsOsiApproved CrystalStacker = False
+licenseIsOsiApproved CUA_OPL_1_0 = True
+licenseIsOsiApproved Cube = False
+licenseIsOsiApproved Curl = False
+licenseIsOsiApproved D_FSL_1_0 = False
+licenseIsOsiApproved Diffmark = False
+licenseIsOsiApproved WTFPL = False
+licenseIsOsiApproved DOC = False
+licenseIsOsiApproved Dotseqn = False
+licenseIsOsiApproved DSDP = False
+licenseIsOsiApproved Dvipdfm = False
+licenseIsOsiApproved EPL_1_0 = True
+licenseIsOsiApproved ECL_1_0 = True
+licenseIsOsiApproved ECL_2_0 = True
+licenseIsOsiApproved EGenix = False
+licenseIsOsiApproved EFL_1_0 = True
+licenseIsOsiApproved EFL_2_0 = True
+licenseIsOsiApproved MIT_advertising = False
+licenseIsOsiApproved MIT_enna = False
+licenseIsOsiApproved Entessa = True
+licenseIsOsiApproved ErlPL_1_1 = False
+licenseIsOsiApproved EUDatagrid = True
+licenseIsOsiApproved EUPL_1_0 = False
+licenseIsOsiApproved EUPL_1_1 = True
+licenseIsOsiApproved Eurosym = False
+licenseIsOsiApproved Fair = True
+licenseIsOsiApproved MIT_feh = False
+licenseIsOsiApproved Frameworx_1_0 = True
+licenseIsOsiApproved FreeImage = False
+licenseIsOsiApproved FTL = False
+licenseIsOsiApproved FSFAP = False
+licenseIsOsiApproved FSFUL = False
+licenseIsOsiApproved FSFULLR = False
+licenseIsOsiApproved Giftware = False
+licenseIsOsiApproved GL2PS = False
+licenseIsOsiApproved Glulxe = False
+licenseIsOsiApproved AGPL_3_0 = True
+licenseIsOsiApproved GFDL_1_1 = False
+licenseIsOsiApproved GFDL_1_2 = False
+licenseIsOsiApproved GFDL_1_3 = False
+licenseIsOsiApproved GPL_1_0 = False
+licenseIsOsiApproved GPL_2_0 = True
+licenseIsOsiApproved GPL_3_0 = True
+licenseIsOsiApproved LGPL_2_1 = True
+licenseIsOsiApproved LGPL_3_0 = True
+licenseIsOsiApproved LGPL_2_0 = True
+licenseIsOsiApproved Gnuplot = False
+licenseIsOsiApproved GSOAP_1_3b = False
+licenseIsOsiApproved HaskellReport = False
+licenseIsOsiApproved HPND = True
+licenseIsOsiApproved IBM_pibs = False
+licenseIsOsiApproved IPL_1_0 = True
+licenseIsOsiApproved ICU = False
+licenseIsOsiApproved ImageMagick = False
+licenseIsOsiApproved IMatix = False
+licenseIsOsiApproved Imlib2 = False
+licenseIsOsiApproved IJG = False
+licenseIsOsiApproved Info_ZIP = False
+licenseIsOsiApproved Intel_ACPI = False
+licenseIsOsiApproved Intel = True
+licenseIsOsiApproved Interbase_1_0 = False
+licenseIsOsiApproved IPA = True
+licenseIsOsiApproved ISC = True
+licenseIsOsiApproved JasPer_2_0 = False
+licenseIsOsiApproved JSON = False
+licenseIsOsiApproved LPPL_1_0 = False
+licenseIsOsiApproved LPPL_1_1 = False
+licenseIsOsiApproved LPPL_1_2 = False
+licenseIsOsiApproved LPPL_1_3a = False
+licenseIsOsiApproved LPPL_1_3c = True
+licenseIsOsiApproved Latex2e = False
+licenseIsOsiApproved BSD_3_Clause_LBNL = False
+licenseIsOsiApproved Leptonica = False
+licenseIsOsiApproved LGPLLR = False
+licenseIsOsiApproved Libpng = False
+licenseIsOsiApproved Libtiff = False
+licenseIsOsiApproved LAL_1_2 = False
+licenseIsOsiApproved LAL_1_3 = False
+licenseIsOsiApproved LiLiQ_P_1_1 = True
+licenseIsOsiApproved LiLiQ_Rplus_1_1 = True
+licenseIsOsiApproved LiLiQ_R_1_1 = True
+licenseIsOsiApproved LPL_1_02 = True
+licenseIsOsiApproved LPL_1_0 = True
+licenseIsOsiApproved MakeIndex = False
+licenseIsOsiApproved MTLL = False
+licenseIsOsiApproved MS_PL = True
+licenseIsOsiApproved MS_RL = True
+licenseIsOsiApproved MirOS = True
+licenseIsOsiApproved MITNFA = False
+licenseIsOsiApproved MIT = True
+licenseIsOsiApproved Motosoto = True
+licenseIsOsiApproved MPL_1_0 = True
+licenseIsOsiApproved MPL_1_1 = True
+licenseIsOsiApproved MPL_2_0 = True
+licenseIsOsiApproved MPL_2_0_no_copyleft_exception = True
+licenseIsOsiApproved Mpich2 = False
+licenseIsOsiApproved Multics = True
+licenseIsOsiApproved Mup = False
+licenseIsOsiApproved NASA_1_3 = True
+licenseIsOsiApproved Naumen = True
+licenseIsOsiApproved NBPL_1_0 = False
+licenseIsOsiApproved Net_SNMP = False
+licenseIsOsiApproved NetCDF = False
+licenseIsOsiApproved NGPL = True
+licenseIsOsiApproved NOSL = False
+licenseIsOsiApproved NPL_1_0 = False
+licenseIsOsiApproved NPL_1_1 = False
+licenseIsOsiApproved Newsletr = False
+licenseIsOsiApproved NLPL = False
+licenseIsOsiApproved Nokia = True
+licenseIsOsiApproved NPOSL_3_0 = True
+licenseIsOsiApproved NLOD_1_0 = False
+licenseIsOsiApproved Noweb = False
+licenseIsOsiApproved NRL = False
+licenseIsOsiApproved NTP = True
+licenseIsOsiApproved Nunit = False
+licenseIsOsiApproved OCLC_2_0 = True
+licenseIsOsiApproved ODbL_1_0 = False
+licenseIsOsiApproved PDDL_1_0 = False
+licenseIsOsiApproved OCCT_PL = False
+licenseIsOsiApproved OGTSL = True
+licenseIsOsiApproved OLDAP_2_2_2 = False
+licenseIsOsiApproved OLDAP_1_1 = False
+licenseIsOsiApproved OLDAP_1_2 = False
+licenseIsOsiApproved OLDAP_1_3 = False
+licenseIsOsiApproved OLDAP_1_4 = False
+licenseIsOsiApproved OLDAP_2_0 = False
+licenseIsOsiApproved OLDAP_2_0_1 = False
+licenseIsOsiApproved OLDAP_2_1 = False
+licenseIsOsiApproved OLDAP_2_2 = False
+licenseIsOsiApproved OLDAP_2_2_1 = False
+licenseIsOsiApproved OLDAP_2_3 = False
+licenseIsOsiApproved OLDAP_2_4 = False
+licenseIsOsiApproved OLDAP_2_5 = False
+licenseIsOsiApproved OLDAP_2_6 = False
+licenseIsOsiApproved OLDAP_2_7 = False
+licenseIsOsiApproved OLDAP_2_8 = False
+licenseIsOsiApproved OML = False
+licenseIsOsiApproved OPL_1_0 = False
+licenseIsOsiApproved OSL_1_0 = True
+licenseIsOsiApproved OSL_1_1 = False
+licenseIsOsiApproved OSL_2_0 = True
+licenseIsOsiApproved OSL_2_1 = True
+licenseIsOsiApproved OSL_3_0 = True
+licenseIsOsiApproved OpenSSL = False
+licenseIsOsiApproved OSET_PL_2_1 = True
+licenseIsOsiApproved PHP_3_0 = True
+licenseIsOsiApproved PHP_3_01 = False
+licenseIsOsiApproved Plexus = False
+licenseIsOsiApproved PostgreSQL = True
+licenseIsOsiApproved Psfrag = False
+licenseIsOsiApproved Psutils = False
+licenseIsOsiApproved Python_2_0 = True
+licenseIsOsiApproved QPL_1_0 = True
+licenseIsOsiApproved Qhull = False
+licenseIsOsiApproved Rdisc = False
+licenseIsOsiApproved RPSL_1_0 = True
+licenseIsOsiApproved RPL_1_1 = True
+licenseIsOsiApproved RPL_1_5 = True
+licenseIsOsiApproved RHeCos_1_1 = False
+licenseIsOsiApproved RSCPL = True
+licenseIsOsiApproved RSA_MD = False
+licenseIsOsiApproved Ruby = False
+licenseIsOsiApproved SAX_PD = False
+licenseIsOsiApproved Saxpath = False
+licenseIsOsiApproved SCEA = False
+licenseIsOsiApproved SWL = False
+licenseIsOsiApproved SMPPL = False
+licenseIsOsiApproved Sendmail = False
+licenseIsOsiApproved SGI_B_1_0 = False
+licenseIsOsiApproved SGI_B_1_1 = False
+licenseIsOsiApproved SGI_B_2_0 = False
+licenseIsOsiApproved OFL_1_0 = False
+licenseIsOsiApproved OFL_1_1 = True
+licenseIsOsiApproved SimPL_2_0 = True
+licenseIsOsiApproved Sleepycat = True
+licenseIsOsiApproved SNIA = False
+licenseIsOsiApproved Spencer_86 = False
+licenseIsOsiApproved Spencer_94 = False
+licenseIsOsiApproved Spencer_99 = False
+licenseIsOsiApproved SMLNJ = False
+licenseIsOsiApproved SugarCRM_1_1_3 = False
+licenseIsOsiApproved SISSL = True
+licenseIsOsiApproved SISSL_1_2 = False
+licenseIsOsiApproved SPL_1_0 = True
+licenseIsOsiApproved Watcom_1_0 = True
+licenseIsOsiApproved TCL = False
+licenseIsOsiApproved TCP_wrappers = False
+licenseIsOsiApproved Unlicense = False
+licenseIsOsiApproved TMate = False
+licenseIsOsiApproved TORQUE_1_1 = False
+licenseIsOsiApproved TOSL = False
+licenseIsOsiApproved Unicode_DFS_2015 = False
+licenseIsOsiApproved Unicode_DFS_2016 = False
+licenseIsOsiApproved Unicode_TOU = False
+licenseIsOsiApproved UPL_1_0 = True
+licenseIsOsiApproved NCSA = True
+licenseIsOsiApproved Vim = False
+licenseIsOsiApproved VOSTROM = False
+licenseIsOsiApproved VSL_1_0 = True
+licenseIsOsiApproved W3C_20150513 = False
+licenseIsOsiApproved W3C_19980720 = False
+licenseIsOsiApproved W3C = True
+licenseIsOsiApproved Wsuipa = False
+licenseIsOsiApproved Xnet = True
+licenseIsOsiApproved X11 = False
+licenseIsOsiApproved Xerox = False
+licenseIsOsiApproved XFree86_1_1 = False
+licenseIsOsiApproved Xinetd = False
+licenseIsOsiApproved Xpp = False
+licenseIsOsiApproved XSkat = False
+licenseIsOsiApproved YPL_1_0 = False
+licenseIsOsiApproved YPL_1_1 = False
+licenseIsOsiApproved Zed = False
+licenseIsOsiApproved Zend_2_0 = False
+licenseIsOsiApproved Zimbra_1_3 = False
+licenseIsOsiApproved Zimbra_1_4 = False
+licenseIsOsiApproved Zlib = True
+licenseIsOsiApproved Zlib_acknowledgement = False
+licenseIsOsiApproved ZPL_1_1 = False
+licenseIsOsiApproved ZPL_2_0 = True
+licenseIsOsiApproved ZPL_2_1 = False
+
+-------------------------------------------------------------------------------
+-- Creation
+-------------------------------------------------------------------------------
+
+-- | Create a 'LicenseId' from a 'String'.
+mkLicenseId :: String -> Maybe LicenseId
+mkLicenseId s = Map.lookup s stringLookup
+
+stringLookup :: Map String LicenseId
+stringLookup = Map.fromList $ map (\i -> (licenseId i, i)) $ [minBound .. maxBound]
diff --git a/Cabal/Distribution/SPDX/LicenseReference.hs b/Cabal/Distribution/SPDX/LicenseReference.hs
new file mode 100644
index 0000000000000000000000000000000000000000..0a5bf84f55d52371b7185830c94e26ef7a4c39ce
--- /dev/null
+++ b/Cabal/Distribution/SPDX/LicenseReference.hs
@@ -0,0 +1,86 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveGeneric #-}
+module Distribution.SPDX.LicenseReference (
+    LicenseRef,
+    licenseRef,
+    licenseDocumentRef,
+    mkLicenseRef,
+    mkLicenseRef',
+    unsafeMkLicenseRef,
+    ) where
+
+import Prelude ()
+import Distribution.Compat.Prelude
+
+import Distribution.Utils.Generic (isAsciiAlphaNum)
+import Distribution.Pretty
+import Distribution.Parsec.Class
+
+import qualified Distribution.Compat.Parsec as P
+import qualified Text.PrettyPrint as Disp
+
+-- | A user defined license reference denoted by @LicenseRef-[idstring]@ (for a license not on the SPDX License List);
+data LicenseRef = LicenseRef
+    { _lrDocument :: !(Maybe String)
+    , _lrLicense  :: !String
+    }
+  deriving (Show, Read, Eq, Typeable, Data, Generic)
+
+-- | License reference.
+licenseRef :: LicenseRef -> String
+licenseRef = _lrLicense
+
+-- | Document reference.
+licenseDocumentRef :: LicenseRef -> Maybe String
+licenseDocumentRef = _lrDocument
+
+instance Binary LicenseRef
+
+instance NFData LicenseRef where
+    rnf (LicenseRef d l) = rnf d `seq` rnf l
+
+instance Pretty LicenseRef where
+    pretty (LicenseRef Nothing l) = Disp.text "LicenseRef-" <<>> Disp.text l
+    pretty (LicenseRef (Just d) l) =
+        Disp.text "DocumentRef-" <<>> Disp.text d <<>> Disp.char ':' <<>> Disp.text "LicenseRef-" <<>> Disp.text l
+
+instance Parsec LicenseRef where
+    parsec = name <|> doc
+      where
+        name = do
+            _ <- P.string "LicenseRef-"
+            n <- some $ P.satisfy $ \c -> isAsciiAlphaNum c || c == '-' || c == '.'
+            pure (LicenseRef Nothing n)
+
+        doc = do
+            _ <- P.string "DocumentRef-"
+            d <- some $ P.satisfy $ \c -> isAsciiAlphaNum c || c == '-' || c == '.'
+            _ <- P.char ':'
+            _ <- P.string "LicenseRef-"
+            n <- some $ P.satisfy $ \c -> isAsciiAlphaNum c || c == '-' || c == '.'
+            pure (LicenseRef (Just d) n)
+
+-- | Create 'LicenseRef' from optional document ref and name.
+mkLicenseRef :: Maybe String -> String -> Maybe LicenseRef
+mkLicenseRef d l = do
+    d' <- traverse checkIdString d
+    l' <- checkIdString l
+    pure (LicenseRef d' l')
+  where
+    checkIdString s
+        | all (\c -> isAsciiAlphaNum c || c == '-' || c == '.') s = Just s
+        | otherwise = Nothing
+
+-- | Like 'mkLicenseRef' but convert invalid characters into @-@.
+mkLicenseRef' :: Maybe String -> String -> LicenseRef
+mkLicenseRef' d l = LicenseRef (fmap f d) (f l)
+  where
+    f = map g
+    g c | isAsciiAlphaNum c || c == '-' || c == '.' = c
+        | otherwise                                 = '-'
+
+-- | Unsafe 'mkLicenseRef'. Consider using 'mkLicenseRef''.
+unsafeMkLicenseRef :: Maybe String -> String -> LicenseRef
+unsafeMkLicenseRef d l = case mkLicenseRef d l of
+    Nothing -> error $ "unsafeMkLicenseRef: panic" ++ show (d, l)
+    Just x  -> x
diff --git a/Cabal/Distribution/Utils/Generic.hs b/Cabal/Distribution/Utils/Generic.hs
index f77e2bb892f3abf16a7ce9c4dd48b2299c357bf0..c90132986dc025f17a5bc609f27ad39a72a07bc3 100644
--- a/Cabal/Distribution/Utils/Generic.hs
+++ b/Cabal/Distribution/Utils/Generic.hs
@@ -353,7 +353,7 @@ isAsciiAlpha c = ('a' <= c && c <= 'z')
 -- False
 --
 isAsciiAlphaNum :: Char -> Bool
-isAsciiAlphaNum c = isAscii c ||  isDigit c
+isAsciiAlphaNum c = isAscii c && isAlphaNum c
 
 unintersperse :: Char -> String -> [String]
 unintersperse mark = unfoldr unintersperse1 where
diff --git a/Cabal/tests/UnitTests.hs b/Cabal/tests/UnitTests.hs
index 48bf6825dd08cb05462dbfbd6e754f7c0de74f68..f671a8067c5d90fc5e712f0ce8ad72cf405ca570 100644
--- a/Cabal/tests/UnitTests.hs
+++ b/Cabal/tests/UnitTests.hs
@@ -24,6 +24,7 @@ import qualified UnitTests.Distribution.Utils.Generic
 import qualified UnitTests.Distribution.Utils.NubList
 import qualified UnitTests.Distribution.Utils.ShortText
 import qualified UnitTests.Distribution.Version (versionTests)
+import qualified UnitTests.Distribution.SPDX (spdxTests)
 
 tests :: Int -> TestTree
 tests mtimeChangeCalibrated =
@@ -55,6 +56,8 @@ tests mtimeChangeCalibrated =
         UnitTests.Distribution.System.tests
     , testGroup "Distribution.Version"
         UnitTests.Distribution.Version.versionTests
+    , testGroup "Distribution.SPDX"
+        UnitTests.Distribution.SPDX.spdxTests
     ]
 
 extraOptions :: [OptionDescription]
diff --git a/Cabal/tests/UnitTests/Distribution/SPDX.hs b/Cabal/tests/UnitTests/Distribution/SPDX.hs
new file mode 100644
index 0000000000000000000000000000000000000000..f431cd20e858009caeafa084eafc104a1213dfc8
--- /dev/null
+++ b/Cabal/tests/UnitTests/Distribution/SPDX.hs
@@ -0,0 +1,79 @@
+{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-deprecations #-}
+module UnitTests.Distribution.SPDX (spdxTests) where
+
+import Distribution.Compat.Prelude.Internal
+import Prelude ()
+
+import Distribution.SPDX
+import Distribution.Parsec.Class (eitherParsec)
+import Distribution.Pretty (prettyShow)
+
+import Test.Tasty
+import Test.Tasty.QuickCheck
+
+spdxTests :: [TestTree]
+spdxTests =
+    [ testProperty "LicenseId roundtrip" licenseIdRoundtrip
+    , testProperty "LicenseExceptionId roundtrip" licenseExceptionIdRoundtrip
+    , testProperty "LicenseExpression roundtrip" licenseExpressionRoundtrip
+    ]
+
+licenseIdRoundtrip :: LicenseId -> Property
+licenseIdRoundtrip x = 
+    counterexample (prettyShow x) $
+    Right x === eitherParsec (prettyShow x)
+
+licenseExceptionIdRoundtrip :: LicenseExceptionId -> Property
+licenseExceptionIdRoundtrip x =
+    counterexample (prettyShow x) $
+    Right x === eitherParsec (prettyShow x)
+
+licenseExpressionRoundtrip :: LicenseExpression -> Property
+licenseExpressionRoundtrip x = 
+    counterexample (prettyShow x) $
+    Right (reassoc x) === eitherParsec (prettyShow x)
+
+-- Parser produces right biased trees of and/or expressions
+reassoc :: LicenseExpression -> LicenseExpression
+reassoc (EOr a b) = case reassoc a of
+    EOr x y -> EOr x (reassoc (EOr y b))
+    x       -> EOr x (reassoc b)
+reassoc (EAnd a b) = case reassoc a of
+    EAnd x y -> EAnd x (reassoc (EAnd y b))
+    x       -> EAnd x (reassoc b)
+reassoc l = l
+
+-------------------------------------------------------------------------------
+-- Instances
+-------------------------------------------------------------------------------
+
+instance Arbitrary LicenseId where
+    arbitrary = arbitraryBoundedEnum
+
+instance Arbitrary LicenseExceptionId where
+    arbitrary = arbitraryBoundedEnum
+
+instance Arbitrary OnlyOrAnyLater where
+    arbitrary = arbitraryBoundedEnum
+
+instance Arbitrary LicenseExpression where
+    arbitrary = sized arb
+      where
+        arb n
+            | n <= 0     = simple
+            | otherwise = oneof
+                [ simple
+                , EAnd <$> arbA <*> arbB
+                , EOr <$> arbA <*> arbB
+                ]
+              where
+                m = n `div` 2
+                arbA = arb m 
+                arbB = arb (n - m)
+
+        simple = ELicense <$> (Right <$> arbitrary) <*> arbitrary <*> pure Nothing -- arbitrary
+
+    shrink (EAnd a b) = a : b : map (uncurry EAnd) (shrink (a, b))
+    shrink (EOr a b)  = a : b : map (uncurry EOr) (shrink (a, b))
+    shrink _          = []
+
diff --git a/Makefile b/Makefile
index da6c32283663541f9d4cf4c9bc2ff16d061b2516..4ded796d7a27e5182da05d2c75d82f94c2a7a731 100644
--- a/Makefile
+++ b/Makefile
@@ -1,21 +1,31 @@
-.PHONY : all lexer lib exe doctest gen-extra-source-files
+.PHONY : all lexer sdpx lib exe doctest gen-extra-source-files
 
 LEXER_HS:=Cabal/Distribution/Parsec/Lexer.hs
+SPDX_LICENSE_HS:=Cabal/Distribution/SPDX/LicenseId.hs
+SPDX_EXCEPTION_HS:=Cabal/Distribution/SPDX/LicenseExceptionId.hs
 
 all : exe lib
 
 lexer : $(LEXER_HS)
 
+spdx : $(SPDX_LICENSE_HS) $(SPDX_EXCEPTION_HS)
+
 $(LEXER_HS) : boot/Lexer.x
 	alex --latin1 --ghc -o $@ $^
 	cat -s $@ > Lexer.tmp
 	mv Lexer.tmp $@
 
+$(SPDX_LICENSE_HS) : boot/SPDX.LicenseId.template.hs cabal-dev-scripts/src/GenSPDX.hs license-list-data/licenses.json
+	cabal new-run --builddir=dist-newstyle-meta --project-file=cabal.project.meta gen-spdx -- boot/SPDX.LicenseId.template.hs license-list-data/licenses.json $(SPDX_LICENSE_HS)
+
+$(SPDX_EXCEPTION_HS) : boot/SPDX.LicenseExceptionId.template.hs cabal-dev-scripts/src/GenSPDXExc.hs license-list-data/licenses.json
+	cabal new-run --builddir=dist-newstyle-meta --project-file=cabal.project.meta gen-spdx-exc -- boot/SPDX.LicenseExceptionId.template.hs license-list-data/exceptions.json $(SPDX_EXCEPTION_HS)
+
 lib : $(LEXER_HS)
 	cabal new-build --enable-tests Cabal
 
 exe : $(LEXER_HS)
-	cabal new-build --enable-tests cabal
+	cabal new-build --enable-tests cabal-install
 
 doctest :
 	doctest --fast Cabal/Distribution Cabal/Language
diff --git a/boot/SPDX.LicenseExceptionId.template.hs b/boot/SPDX.LicenseExceptionId.template.hs
new file mode 100644
index 0000000000000000000000000000000000000000..7bf4fc8762973927875c8453f05d8bfaa4b27d5b
--- /dev/null
+++ b/boot/SPDX.LicenseExceptionId.template.hs
@@ -0,0 +1,68 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveGeneric      #-}
+module Distribution.SPDX.LicenseExceptionId (
+    LicenseExceptionId (..),
+    licenseExceptionId,
+    licenseExceptionName,
+    mkLicenseExceptionId,
+    ) where
+
+import Distribution.Compat.Prelude
+import Prelude ()
+
+import Distribution.Pretty
+import Distribution.Parsec.Class
+import Distribution.Utils.Generic (isAsciiAlphaNum)
+
+import qualified Distribution.Compat.Map.Strict as Map
+import qualified Distribution.Compat.Parsec as P
+import qualified Text.PrettyPrint as Disp
+
+-------------------------------------------------------------------------------
+-- LicenseExceptionId
+-------------------------------------------------------------------------------
+
+-- | SPDX License identifier
+data LicenseExceptionId
+{{{ licenseIds }}}
+  deriving (Eq, Ord, Enum, Bounded, Show, Read, Typeable, Data, Generic)
+
+instance Binary LicenseExceptionId
+
+instance Pretty LicenseExceptionId where
+    pretty = Disp.text . licenseExceptionId
+
+instance Parsec LicenseExceptionId where
+    parsec = do
+        n <- some $ P.satisfy $ \c -> isAsciiAlphaNum c || c == '-' || c == '.'
+        maybe (fail $ "Unknown SPDX license exception identifier: " ++ n) return $ mkLicenseExceptionId n
+
+instance NFData LicenseExceptionId where
+    rnf l = l `seq` ()
+
+-------------------------------------------------------------------------------
+-- License Data
+-------------------------------------------------------------------------------
+
+-- | License SPDX identifier, e.g. @"BSD-3-Clause"@.
+licenseExceptionId :: LicenseExceptionId -> String
+{{#licenses}}
+licenseExceptionId {{licenseCon}} = {{{licenseId}}}
+{{/licenses}}
+
+-- | License name, e.g. @"GNU General Public License v2.0 only"@
+licenseExceptionName :: LicenseExceptionId -> String
+{{#licenses}}
+licenseExceptionName {{licenseCon}} = {{{licenseName}}}
+{{/licenses}}
+
+-------------------------------------------------------------------------------
+-- Creation
+-------------------------------------------------------------------------------
+
+-- | Create a 'LicenseExceptionId' from a 'String'.
+mkLicenseExceptionId :: String -> Maybe LicenseExceptionId
+mkLicenseExceptionId s = Map.lookup s stringLookup
+
+stringLookup :: Map String LicenseExceptionId
+stringLookup = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $ [minBound .. maxBound]
diff --git a/boot/SPDX.LicenseId.template.hs b/boot/SPDX.LicenseId.template.hs
new file mode 100644
index 0000000000000000000000000000000000000000..3873872fad3058cba559dc67abe00f12b97a1125
--- /dev/null
+++ b/boot/SPDX.LicenseId.template.hs
@@ -0,0 +1,77 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveGeneric      #-}
+module Distribution.SPDX.LicenseId (
+    LicenseId (..),
+    licenseId,
+    licenseName,
+    licenseIsOsiApproved,
+    mkLicenseId,
+    ) where
+
+import Distribution.Compat.Prelude
+import Prelude ()
+
+import Distribution.Pretty
+import Distribution.Parsec.Class
+import Distribution.Utils.Generic (isAsciiAlphaNum)
+
+import qualified Distribution.Compat.Map.Strict as Map
+import qualified Distribution.Compat.Parsec as P
+import qualified Text.PrettyPrint as Disp
+
+-------------------------------------------------------------------------------
+-- LicenseId
+-------------------------------------------------------------------------------
+
+-- | SPDX License identifier
+data LicenseId
+{{{ licenseIds }}}
+  deriving (Eq, Ord, Enum, Bounded, Show, Read, Typeable, Data, Generic)
+
+instance Binary LicenseId
+
+instance Pretty LicenseId where
+    pretty = Disp.text . licenseId
+
+instance Parsec LicenseId where
+    parsec = do
+        n <- some $ P.satisfy $ \c -> isAsciiAlphaNum c || c == '-' || c == '.'
+        maybe (fail $ "Unknown SPDX license identifier: " ++ n) return $ mkLicenseId n
+
+instance NFData LicenseId where
+    rnf l = l `seq` ()
+
+-------------------------------------------------------------------------------
+-- License Data
+-------------------------------------------------------------------------------
+
+-- | License SPDX identifier, e.g. @"BSD-3-Clause"@.
+licenseId :: LicenseId -> String
+{{#licenses}}
+licenseId {{licenseCon}} = {{{licenseId}}}
+{{/licenses}}
+
+-- | License name, e.g. @"GNU General Public License v2.0 only"@
+licenseName :: LicenseId -> String
+{{#licenses}}
+licenseName {{licenseCon}} = {{{licenseName}}}
+{{/licenses}}
+
+-- | Whether the license is approved by Open Source Initiative (OSI).
+--
+-- See <https://opensource.org/licenses/alphabetical>.
+licenseIsOsiApproved :: LicenseId -> Bool
+{{#licenses}}
+licenseIsOsiApproved {{licenseCon}} = {{#isOsiApproved}}True{{/isOsiApproved}}{{^isOsiApproved}}False{{/isOsiApproved}}
+{{/licenses}}
+
+-------------------------------------------------------------------------------
+-- Creation
+-------------------------------------------------------------------------------
+
+-- | Create a 'LicenseId' from a 'String'.
+mkLicenseId :: String -> Maybe LicenseId
+mkLicenseId s = Map.lookup s stringLookup
+
+stringLookup :: Map String LicenseId
+stringLookup = Map.fromList $ map (\i -> (licenseId i, i)) $ [minBound .. maxBound]
diff --git a/cabal-dev-scripts/cabal-dev-scripts.cabal b/cabal-dev-scripts/cabal-dev-scripts.cabal
index c42cacc92d07104cb567c4a8ed02b74da0c19c1b..26e4e29c457c7857a5478e8488cb2c0b5270fc02 100644
--- a/cabal-dev-scripts/cabal-dev-scripts.cabal
+++ b/cabal-dev-scripts/cabal-dev-scripts.cabal
@@ -21,3 +21,31 @@ executable gen-extra-source-files
     directory,
     filepath,
     process
+
+executable gen-spdx
+  default-language:    Haskell2010
+  main-is:             GenSPDX.hs
+  hs-source-dirs:      src
+  build-depends:
+    base                 >=4.10    && <4.11,
+    aeson                >=1.2.3.0 && <1.3,
+    bytestring,
+    containers,
+    lens                 >=4.15.4  && <4.16,
+    microstache          >=1.0.1.1 && <1.1,
+    optparse-applicative >=0.14    && <0.15,
+    text
+
+executable gen-spdx-exc
+  default-language:    Haskell2010
+  main-is:             GenSPDXExc.hs
+  hs-source-dirs:      src
+  build-depends:
+    base                 >=4.10    && <4.11,
+    aeson                >=1.2.3.0 && <1.3,
+    bytestring,
+    containers,
+    lens                 >=4.15.4  && <4.16,
+    microstache          >=1.0.1.1 && <1.1,
+    optparse-applicative >=0.14    && <0.15,
+    text
diff --git a/cabal-dev-scripts/src/GenSPDX.hs b/cabal-dev-scripts/src/GenSPDX.hs
new file mode 100644
index 0000000000000000000000000000000000000000..720459d9650856fca39ad9c9ac7db2e977bb88df
--- /dev/null
+++ b/cabal-dev-scripts/src/GenSPDX.hs
@@ -0,0 +1,126 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Main (main) where
+
+import Control.Lens   hiding ((.=))
+import Data.Aeson     (FromJSON (..), Value, eitherDecode, object, withObject, (.:), (.=))
+import Data.Char      (toUpper, isAlpha)
+import Data.Foldable  (for_)
+import Data.Semigroup ((<>))
+import Data.Text      (Text)
+
+import qualified Data.ByteString.Lazy as LBS
+import qualified Data.Text            as T
+import qualified Data.Text.IO         as T
+import qualified Data.Text.Lazy       as TL
+import qualified Data.Text.Lazy.IO    as TL
+import qualified Options.Applicative  as O
+import qualified Text.Microstache     as M
+
+data Opts = Opts FilePath FilePath FilePath
+
+main :: IO ()
+main = generate =<< O.execParser opts where
+    opts = O.info (O.helper <*> parser) $ mconcat
+        [ O.fullDesc
+        , O.progDesc "Generate SPDX LicenseId module"
+        ]
+
+    parser :: O.Parser Opts
+    parser = Opts <$> template <*> licenses <*> output
+
+    template = O.strArgument $ mconcat
+        [ O.metavar "SPDX.LicenseId.template.hs"
+        , O.help    "Module template file"
+        ]
+
+    licenses = O.strArgument $ mconcat
+        [ O.metavar "licenses.json"
+        , O.help    "Licenses JSON. https://github.com/spdx/license-list-data"
+        ]
+
+    output = O.strArgument $ mconcat
+        [ O.metavar "Output.hs"
+        , O.help    "Output file"
+        ]
+
+generate :: Opts -> IO ()
+generate (Opts tmplFile fn out) = do
+    contents <- LBS.readFile fn
+    LicenseList ls <- either fail pure $ eitherDecode contents
+    template <- M.compileMustacheFile tmplFile
+    let (ws, rendered) = generate' ls template
+    for_ ws $ putStrLn . M.displayMustacheWarning
+    TL.writeFile out (header <> "\n" <> rendered)
+    putStrLn $ "Generated file " ++ out
+
+header :: TL.Text
+header = "-- This file is generated. See Makefile's spdx rule"
+
+generate' :: [License] -> M.Template -> ([M.MustacheWarning], TL.Text)
+generate' ls template = M.renderMustacheW template $ object
+    [ "licenseIds" .= licenseIds
+    , "licenses"   .= licenseValues
+    ]
+  where
+    constructorNames :: [(Text,License)]
+    constructorNames
+        = map (\l -> (toConstructorName $ licenseId l, l))
+        $ filter (not . licenseDeprecated)
+        $ ls
+
+    licenseValues :: [Value]
+    licenseValues = flip map constructorNames $ \(c, l) -> object
+        [ "licenseCon"    .= c
+        , "licenseId"     .= textShow (licenseId l)
+        , "licenseName"   .= textShow (licenseName l)
+        , "isOsiApproved" .= licenseOsiApproved l
+        ]
+
+    licenseIds :: Text
+    licenseIds = T.intercalate "\n" $ flip imap constructorNames $ \i (c, l) ->
+        let pfx = if i == 0 then "    = " else "    | "
+        in pfx <> c <> " -- ^ @" <> licenseId l <> "@, " <> licenseName l
+
+textShow :: Text -> Text
+textShow = T.pack . show
+
+toConstructorName :: Text -> Text
+toConstructorName t = t
+    & each %~ f
+    & ix 0 %~ toUpper
+    & special
+  where
+    f '.' = '_'
+    f '-' = '_'
+    f '+' = '\''
+    f c   = c
+
+    special :: Text -> Text
+    special "0BSD" = "NullBSD"
+    special t      = t
+
+-------------------------------------------------------------------------------
+-- Licenses
+-------------------------------------------------------------------------------
+
+data License = License
+    { licenseId          :: !Text
+    , licenseName        :: !Text
+    , licenseOsiApproved :: !Bool
+    , licenseDeprecated  :: !Bool
+    }
+  deriving (Show)
+
+instance FromJSON License where
+    parseJSON = withObject "License" $ \obj -> License
+        <$> obj .: "licenseId"
+        <*> obj .: "name"
+        <*> obj .: "isOsiApproved"
+        <*> obj .: "isDeprecatedLicenseId"
+
+newtype LicenseList = LicenseList [License]
+  deriving (Show)
+
+instance FromJSON LicenseList where
+    parseJSON = withObject "License list" $ \obj -> LicenseList
+        <$> obj .: "licenses"
diff --git a/cabal-dev-scripts/src/GenSPDXExc.hs b/cabal-dev-scripts/src/GenSPDXExc.hs
new file mode 100644
index 0000000000000000000000000000000000000000..813636497de3de087fa984c8453eb98ebbfffdd9
--- /dev/null
+++ b/cabal-dev-scripts/src/GenSPDXExc.hs
@@ -0,0 +1,127 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Main (main) where
+
+import Control.Lens   hiding ((.=))
+import Data.Aeson     (FromJSON (..), Value, eitherDecode, object, withObject, (.:), (.=))
+import Data.Char      (toUpper, isAlpha)
+import Data.Foldable  (for_)
+import Data.Semigroup ((<>))
+import Data.Text      (Text)
+
+import qualified Data.ByteString.Lazy as LBS
+import qualified Data.Text            as T
+import qualified Data.Text.IO         as T
+import qualified Data.Text.Lazy       as TL
+import qualified Data.Text.Lazy.IO    as TL
+import qualified Options.Applicative  as O
+import qualified Text.Microstache     as M
+
+data Opts = Opts FilePath FilePath FilePath
+
+main :: IO ()
+main = generate =<< O.execParser opts where
+    opts = O.info (O.helper <*> parser) $ mconcat
+        [ O.fullDesc
+        , O.progDesc "Generate SPDX LicenseExceptionId module"
+        ]
+
+    parser :: O.Parser Opts
+    parser = Opts <$> template <*> licenses <*> output
+
+    template = O.strArgument $ mconcat
+        [ O.metavar "SPDX.LicenseExceptionId.template.hs"
+        , O.help    "Module template file"
+        ]
+
+    licenses = O.strArgument $ mconcat
+        [ O.metavar "exceptions.json"
+        , O.help    "Exceptions JSON. https://github.com/spdx/license-list-data"
+        ]
+
+    output = O.strArgument $ mconcat
+        [ O.metavar "Output.hs"
+        , O.help    "Output file"
+        ]
+
+generate :: Opts -> IO ()
+generate (Opts tmplFile fn out) = do
+    contents <- LBS.readFile fn
+    LicenseList ls <- either fail pure $ eitherDecode contents
+    template <- M.compileMustacheFile tmplFile
+    let (ws, rendered) = generate' ls template
+    for_ ws $ putStrLn . M.displayMustacheWarning
+    TL.writeFile out (header <> "\n" <> rendered)
+    putStrLn $ "Generated file " ++ out
+
+header :: TL.Text
+header = "-- This file is generated. See Makefile's spdx rule"
+
+generate' :: [License] -> M.Template -> ([M.MustacheWarning], TL.Text)
+generate' ls template = M.renderMustacheW template $ object
+    [ "licenseIds" .= licenseIds
+    , "licenses"   .= licenseValues
+    ]
+  where
+    constructorNames :: [(Text,License)]
+    constructorNames
+        = map (\l -> (toConstructorName $ licenseId l, l))
+        $ filter (not . licenseDeprecated)
+        $ ls
+
+    licenseValues :: [Value]
+    licenseValues = flip map constructorNames $ \(c, l) -> object
+        [ "licenseCon"    .= c
+        , "licenseId"     .= textShow (licenseId l)
+        , "licenseName"   .= textShow (licenseName l)
+        ]
+
+    licenseIds :: Text
+    licenseIds = T.intercalate "\n" $ flip imap constructorNames $ \i (c, l) ->
+        let pfx = if i == 0 then "    = " else "    | "
+        in pfx <> c <> " -- ^ @" <> licenseId l <> "@, " <> licenseName l
+
+textShow :: Text -> Text
+textShow = T.pack . show
+
+toConstructorName :: Text -> Text
+toConstructorName t = t
+    & each %~ f
+    & ix 0 %~ toUpper
+    & special
+  where
+    f '.' = '_'
+    f '-' = '_'
+    f '+' = '\''
+    f c   = c
+
+    special :: Text -> Text
+    special "389_exception" = "DS389_exception"
+    special t      = t
+
+-------------------------------------------------------------------------------
+-- Licenses
+-------------------------------------------------------------------------------
+
+-- TODO: move to common module, confusing naming. This is LicenseException!
+data License = License
+    { licenseId          :: !Text
+    , licenseName        :: !Text
+    , licenseDeprecated  :: !Bool
+    }
+  deriving (Show)
+
+instance FromJSON License where
+    parseJSON = withObject "License" $ \obj -> License
+        <$> obj .: "licenseExceptionId"
+        <*> fmap (T.map fixSpace) (obj .: "name")
+        <*> obj .: "isDeprecatedLicenseId"
+      where
+        fixSpace '\n' = ' '
+        fixSpace c =   c
+
+newtype LicenseList = LicenseList [License]
+  deriving (Show)
+
+instance FromJSON LicenseList where
+    parseJSON = withObject "Exceptions list" $ \obj -> LicenseList
+        <$> obj .: "exceptions"
diff --git a/cabal.project.meta b/cabal.project.meta
index 99eaaa5435927c354f88626a3368a5e71cccb231..304b2a50e583e993963d5f714db533ec3bbcb627 100644
--- a/cabal.project.meta
+++ b/cabal.project.meta
@@ -1 +1,2 @@
 packages: cabal-dev-scripts
+optional-packages:
diff --git a/license-list-data/exceptions.json b/license-list-data/exceptions.json
new file mode 100644
index 0000000000000000000000000000000000000000..3e0ab3a7837ca63fb97db0eb746c48e4569be336
--- /dev/null
+++ b/license-list-data/exceptions.json
@@ -0,0 +1,282 @@
+{
+  "licenseListVersion": "3/23/2017",
+  "releaseDate": "Jun 30, 2016",
+  "exceptions": [
+    {
+      "reference": "./389-exception.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/389-exception.json",
+      "referenceNumber": "1",
+      "name": "389 Directory Server\nException",
+      "seeAlso": [
+        "http://directory.fedoraproject.org/wiki/GPL_Exception_License_Text"
+      ],
+      "licenseExceptionId": "389-exception"
+    },
+    {
+      "reference": "./Autoconf-exception-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Autoconf-exception-2.0.json",
+      "referenceNumber": "2",
+      "name": "Autoconf exception 2.0",
+      "seeAlso": [
+        "http://ac-archive.sourceforge.net/doc/copyright.html"
+      ],
+      "licenseExceptionId": "Autoconf-exception-2.0"
+    },
+    {
+      "reference": "./Autoconf-exception-3.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Autoconf-exception-3.0.json",
+      "referenceNumber": "3",
+      "name": "Autoconf exception 3.0",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/autoconf-exception-3.0.html"
+      ],
+      "licenseExceptionId": "Autoconf-exception-3.0"
+    },
+    {
+      "reference": "./Bison-exception-2.2.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Bison-exception-2.2.json",
+      "referenceNumber": "4",
+      "name": "Bison exception 2.2",
+      "seeAlso": [
+        ""
+      ],
+      "licenseExceptionId": "Bison-exception-2.2"
+    },
+    {
+      "reference": "./Classpath-exception-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Classpath-exception-2.0.json",
+      "referenceNumber": "5",
+      "name": "Classpath exception 2.0",
+      "seeAlso": [
+        "http://www.gnu.org/software/classpath/license.html",
+        "https://fedoraproject.org/wiki/Licensing/GPL_Classpath_Exception"
+      ],
+      "licenseExceptionId": "Classpath-exception-2.0"
+    },
+    {
+      "reference": "./CLISP-exception-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CLISP-exception-2.0.json",
+      "referenceNumber": "6",
+      "name": "CLISP exception 2.0 ",
+      "seeAlso": [
+        "http://sourceforge.net/p/clisp/clisp/ci/default/tree/COPYRIGHT"
+      ],
+      "licenseExceptionId": "CLISP-exception-2.0"
+    },
+    {
+      "reference": "./DigiRule-FOSS-exception.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/DigiRule-FOSS-exception.json",
+      "referenceNumber": "7",
+      "name": "DigiRule FOSS License Exception",
+      "seeAlso": [
+        "http://www.digirulesolutions.com/drupal/foss"
+      ],
+      "licenseExceptionId": "DigiRule-FOSS-exception"
+    },
+    {
+      "reference": "./eCos-exception-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/eCos-exception-2.0.json",
+      "referenceNumber": "8",
+      "name": "eCos exception 2.0",
+      "seeAlso": [
+        "http://ecos.sourceware.org/license-overview.html"
+      ],
+      "licenseExceptionId": "eCos-exception-2.0"
+    },
+    {
+      "reference": "./Fawkes-Runtime-exception.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Fawkes-Runtime-exception.json",
+      "referenceNumber": "9",
+      "name": "Fawkes Runtime Exception ",
+      "seeAlso": [
+        "http://www.fawkesrobotics.org/about/license/"
+      ],
+      "licenseExceptionId": "Fawkes-Runtime-exception"
+    },
+    {
+      "reference": "./FLTK-exception.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/FLTK-exception.json",
+      "referenceNumber": "10",
+      "name": "FLTK exception",
+      "seeAlso": [
+        "http://www.fltk.org/COPYING.php"
+      ],
+      "licenseExceptionId": "FLTK-exception"
+    },
+    {
+      "reference": "./Font-exception-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Font-exception-2.0.json",
+      "referenceNumber": "11",
+      "name": "Font exception 2.0",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/gpl-faq.html#FontException"
+      ],
+      "licenseExceptionId": "Font-exception-2.0"
+    },
+    {
+      "reference": "./freertos-exception-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/freertos-exception-2.0.json",
+      "referenceNumber": "12",
+      "name": "FreeRTOS Exception 2.0",
+      "seeAlso": [
+        "http://www.freertos.org/a00114.html#exception"
+      ],
+      "licenseExceptionId": "freertos-exception-2.0"
+    },
+    {
+      "reference": "./GCC-exception-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/GCC-exception-2.0.json",
+      "referenceNumber": "13",
+      "name": "GCC Runtime Library exception 2.0",
+      "seeAlso": [
+        ""
+      ],
+      "licenseExceptionId": "GCC-exception-2.0"
+    },
+    {
+      "reference": "./GCC-exception-3.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/GCC-exception-3.1.json",
+      "referenceNumber": "14",
+      "name": "GCC Runtime Library exception 3.1",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/gcc-exception-3.1.html"
+      ],
+      "licenseExceptionId": "GCC-exception-3.1"
+    },
+    {
+      "reference": "./gnu-javamail-exception.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/gnu-javamail-exception.json",
+      "referenceNumber": "15",
+      "name": "GNU JavaMail exception",
+      "seeAlso": [
+        "http://www.gnu.org/software/classpathx/javamail/javamail.html"
+      ],
+      "licenseExceptionId": "gnu-javamail-exception"
+    },
+    {
+      "reference": "./i2p-gpl-java-exception.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/i2p-gpl-java-exception.json",
+      "referenceNumber": "16",
+      "name": "i2p GPL+Java Exception",
+      "seeAlso": [
+        "http://geti2p.net/en/get-involved/develop/licenses#java_exception"
+      ],
+      "licenseExceptionId": "i2p-gpl-java-exception"
+    },
+    {
+      "reference": "./Libtool-exception.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Libtool-exception.json",
+      "referenceNumber": "17",
+      "name": "Libtool Exception",
+      "seeAlso": [
+        "http://git.savannah.gnu.org/cgit/libtool.git/tree/m4/libtool.m4"
+      ],
+      "licenseExceptionId": "Libtool-exception"
+    },
+    {
+      "reference": "./LZMA-exception.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LZMA-exception.json",
+      "referenceNumber": "18",
+      "name": "LZMA exception",
+      "seeAlso": [
+        "http://nsis.sourceforge.net/Docs/AppendixI.html#I.6"
+      ],
+      "licenseExceptionId": "LZMA-exception"
+    },
+    {
+      "reference": "./mif-exception.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/mif-exception.json",
+      "referenceNumber": "19",
+      "name": "Macros and Inline Functions Exception",
+      "seeAlso": [
+        "http://www.scs.stanford.edu/histar/src/lib/cppsup/exception"
+      ],
+      "licenseExceptionId": "mif-exception"
+    },
+    {
+      "reference": "./Nokia-Qt-exception-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Nokia-Qt-exception-1.1.json",
+      "referenceNumber": "20",
+      "name": "Nokia Qt LGPL exception 1.1",
+      "seeAlso": [
+        "https://www.keepassx.org/dev/projects/keepassx/repository/revisions/b8dfb9cc4d5133e0f09cd7533d15a4f1c19a40f2/entry/LICENSE.NOKIA-LGPL-EXCEPTION"
+      ],
+      "licenseExceptionId": "Nokia-Qt-exception-1.1"
+    },
+    {
+      "reference": "./OCCT-exception-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OCCT-exception-1.0.json",
+      "referenceNumber": "21",
+      "name": "Open CASCADE Exception 1.0",
+      "seeAlso": [
+        "http://www.opencascade.com/content/licensing"
+      ],
+      "licenseExceptionId": "OCCT-exception-1.0"
+    },
+    {
+      "reference": "./openvpn-openssl-exception.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/openvpn-openssl-exception.json",
+      "referenceNumber": "22",
+      "name": "OpenVPN OpenSSL Exception",
+      "seeAlso": [
+        "http://openvpn.net/index.php/license.html"
+      ],
+      "licenseExceptionId": "openvpn-openssl-exception"
+    },
+    {
+      "reference": "./Qwt-exception-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Qwt-exception-1.0.json",
+      "referenceNumber": "23",
+      "name": "Qwt exception 1.0",
+      "seeAlso": [
+        "http://qwt.sourceforge.net/qwtlicense.html"
+      ],
+      "licenseExceptionId": "Qwt-exception-1.0"
+    },
+    {
+      "reference": "./u-boot-exception-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/u-boot-exception-2.0.json",
+      "referenceNumber": "24",
+      "name": "U-Boot exception 2.0",
+      "seeAlso": [
+        "http://git.denx.de/?p\u003du-boot.git;a\u003dblob;f\u003dLicenses/Exceptions"
+      ],
+      "licenseExceptionId": "u-boot-exception-2.0"
+    },
+    {
+      "reference": "./WxWindows-exception-3.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/WxWindows-exception-3.1.json",
+      "referenceNumber": "25",
+      "name": "WxWindows Library Exception 3.1",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/WXwindows"
+      ],
+      "licenseExceptionId": "WxWindows-exception-3.1"
+    }
+  ]
+}
\ No newline at end of file
diff --git a/license-list-data/licenses.json b/license-list-data/licenses.json
new file mode 100644
index 0000000000000000000000000000000000000000..fbeeb7b0f3772dbe8a6392cb2f1641de78000942
--- /dev/null
+++ b/license-list-data/licenses.json
@@ -0,0 +1,4180 @@
+{
+  "licenseListVersion": "3/23/2017",
+  "licenses": [
+    {
+      "reference": "./Glide.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Glide.json",
+      "referenceNumber": "1",
+      "name": "3dfx Glide License",
+      "licenseId": "Glide",
+      "seeAlso": [
+        "http://www.users.on.net/~triforce/glidexp/COPYING.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Abstyles.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Abstyles.json",
+      "referenceNumber": "2",
+      "name": "Abstyles License",
+      "licenseId": "Abstyles",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Abstyles"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./AFL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/AFL-1.1.json",
+      "referenceNumber": "3",
+      "name": "Academic Free License v1.1",
+      "licenseId": "AFL-1.1",
+      "seeAlso": [
+        "http://opensource.linux-mirror.org/licenses/afl-1.1.txt"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./AFL-1.2.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/AFL-1.2.json",
+      "referenceNumber": "4",
+      "name": "Academic Free License v1.2",
+      "licenseId": "AFL-1.2",
+      "seeAlso": [
+        "http://opensource.linux-mirror.org/licenses/afl-1.2.txt"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./AFL-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/AFL-2.0.json",
+      "referenceNumber": "5",
+      "name": "Academic Free License v2.0",
+      "licenseId": "AFL-2.0",
+      "seeAlso": [
+        "http://opensource.linux-mirror.org/licenses/afl-2.0.txt"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./AFL-2.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/AFL-2.1.json",
+      "referenceNumber": "6",
+      "name": "Academic Free License v2.1",
+      "licenseId": "AFL-2.1",
+      "seeAlso": [
+        "http://opensource.linux-mirror.org/licenses/afl-2.1.txt"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./AFL-3.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/AFL-3.0.json",
+      "referenceNumber": "7",
+      "name": "Academic Free License v3.0",
+      "licenseId": "AFL-3.0",
+      "seeAlso": [
+        "http://www.rosenlaw.com/AFL3.0.htm",
+        "http://www.opensource.org/licenses/afl-3.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./AMPAS.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/AMPAS.json",
+      "referenceNumber": "8",
+      "name": "Academy of Motion Picture Arts and Sciences BSD",
+      "licenseId": "AMPAS",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/BSD#AMPASBSD"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./APL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/APL-1.0.json",
+      "referenceNumber": "9",
+      "name": "Adaptive Public License 1.0",
+      "licenseId": "APL-1.0",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/APL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Adobe-Glyph.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Adobe-Glyph.json",
+      "referenceNumber": "10",
+      "name": "Adobe Glyph List License",
+      "licenseId": "Adobe-Glyph",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/MIT#AdobeGlyph"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./APAFML.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/APAFML.json",
+      "referenceNumber": "11",
+      "name": "Adobe Postscript AFM License",
+      "licenseId": "APAFML",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/AdobePostscriptAFM"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Adobe-2006.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Adobe-2006.json",
+      "referenceNumber": "12",
+      "name": "Adobe Systems Incorporated Source Code License Agreement",
+      "licenseId": "Adobe-2006",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/AdobeLicense"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./AGPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/AGPL-1.0.json",
+      "referenceNumber": "13",
+      "name": "Affero General Public License v1.0",
+      "licenseId": "AGPL-1.0",
+      "seeAlso": [
+        "http://www.affero.org/oagpl.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Afmparse.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Afmparse.json",
+      "referenceNumber": "14",
+      "name": "Afmparse License",
+      "licenseId": "Afmparse",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Afmparse"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Aladdin.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Aladdin.json",
+      "referenceNumber": "15",
+      "name": "Aladdin Free Public License",
+      "licenseId": "Aladdin",
+      "seeAlso": [
+        "http://pages.cs.wisc.edu/~ghost/doc/AFPL/6.01/Public.htm"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./ADSL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/ADSL.json",
+      "referenceNumber": "16",
+      "name": "Amazon Digital Services License",
+      "licenseId": "ADSL",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/AmazonDigitalServicesLicense"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./AMDPLPA.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/AMDPLPA.json",
+      "referenceNumber": "17",
+      "name": "AMD\u0027s plpa_map.c License",
+      "licenseId": "AMDPLPA",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/AMD_plpa_map_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./ANTLR-PD.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/ANTLR-PD.json",
+      "referenceNumber": "18",
+      "name": "ANTLR Software Rights Notice",
+      "licenseId": "ANTLR-PD",
+      "seeAlso": [
+        "http://www.antlr2.org/license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Apache-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Apache-1.0.json",
+      "referenceNumber": "19",
+      "name": "Apache License 1.0",
+      "licenseId": "Apache-1.0",
+      "seeAlso": [
+        "http://www.apache.org/licenses/LICENSE-1.0"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Apache-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Apache-1.1.json",
+      "referenceNumber": "20",
+      "name": "Apache License 1.1",
+      "licenseId": "Apache-1.1",
+      "seeAlso": [
+        "http://apache.org/licenses/LICENSE-1.1",
+        "http://opensource.org/licenses/Apache-1.1"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Apache-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Apache-2.0.json",
+      "referenceNumber": "21",
+      "name": "Apache License 2.0",
+      "licenseId": "Apache-2.0",
+      "seeAlso": [
+        "http://www.apache.org/licenses/LICENSE-2.0",
+        "http://www.opensource.org/licenses/Apache-2.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./AML.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/AML.json",
+      "referenceNumber": "22",
+      "name": "Apple MIT License",
+      "licenseId": "AML",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Apple_MIT_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./APSL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/APSL-1.0.json",
+      "referenceNumber": "23",
+      "name": "Apple Public Source License 1.0",
+      "licenseId": "APSL-1.0",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Apple_Public_Source_License_1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./APSL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/APSL-1.1.json",
+      "referenceNumber": "24",
+      "name": "Apple Public Source License 1.1",
+      "licenseId": "APSL-1.1",
+      "seeAlso": [
+        "http://www.opensource.apple.com/source/IOSerialFamily/IOSerialFamily-7/APPLE_LICENSE"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./APSL-1.2.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/APSL-1.2.json",
+      "referenceNumber": "25",
+      "name": "Apple Public Source License 1.2",
+      "licenseId": "APSL-1.2",
+      "seeAlso": [
+        "http://www.samurajdata.se/opensource/mirror/licenses/apsl.php"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./APSL-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/APSL-2.0.json",
+      "referenceNumber": "26",
+      "name": "Apple Public Source License 2.0",
+      "licenseId": "APSL-2.0",
+      "seeAlso": [
+        "http://www.opensource.apple.com/license/apsl/"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Artistic-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Artistic-1.0.json",
+      "referenceNumber": "27",
+      "name": "Artistic License 1.0",
+      "licenseId": "Artistic-1.0",
+      "seeAlso": [
+        "http://opensource.org/licenses/Artistic-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Artistic-1.0-Perl.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Artistic-1.0-Perl.json",
+      "referenceNumber": "28",
+      "name": "Artistic License 1.0 (Perl)",
+      "licenseId": "Artistic-1.0-Perl",
+      "seeAlso": [
+        "http://dev.perl.org/licenses/artistic.html"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Artistic-1.0-cl8.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Artistic-1.0-cl8.json",
+      "referenceNumber": "29",
+      "name": "Artistic License 1.0 w/clause 8",
+      "licenseId": "Artistic-1.0-cl8",
+      "seeAlso": [
+        "http://opensource.org/licenses/Artistic-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Artistic-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Artistic-2.0.json",
+      "referenceNumber": "30",
+      "name": "Artistic License 2.0",
+      "licenseId": "Artistic-2.0",
+      "seeAlso": [
+        "http://www.perlfoundation.org/artistic_license_2_0",
+        "",
+        "",
+        "http://www.opensource.org/licenses/artistic-license-2.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./AAL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/AAL.json",
+      "referenceNumber": "31",
+      "name": "Attribution Assurance License",
+      "licenseId": "AAL",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/attribution"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Bahyph.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Bahyph.json",
+      "referenceNumber": "32",
+      "name": "Bahyph License",
+      "licenseId": "Bahyph",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Bahyph"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Barr.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Barr.json",
+      "referenceNumber": "33",
+      "name": "Barr License",
+      "licenseId": "Barr",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Barr"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Beerware.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Beerware.json",
+      "referenceNumber": "34",
+      "name": "Beerware License",
+      "licenseId": "Beerware",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Beerware"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./BitTorrent-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BitTorrent-1.0.json",
+      "referenceNumber": "35",
+      "name": "BitTorrent Open Source License v1.0",
+      "licenseId": "BitTorrent-1.0",
+      "seeAlso": [
+        "http://sources.gentoo.org/cgi-bin/viewvc.cgi/gentoo-x86/licenses/BitTorrent?r1\u003d1.1\u0026r2\u003d1.1.1.1\u0026diff_format\u003ds"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./BitTorrent-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BitTorrent-1.1.json",
+      "referenceNumber": "36",
+      "name": "BitTorrent Open Source License v1.1",
+      "licenseId": "BitTorrent-1.1",
+      "seeAlso": [
+        "http://directory.fsf.org/wiki/License:BitTorrentOSL1.1"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./BSL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BSL-1.0.json",
+      "referenceNumber": "37",
+      "name": "Boost Software License 1.0",
+      "licenseId": "BSL-1.0",
+      "seeAlso": [
+        "http://www.boost.org/LICENSE_1_0.txt",
+        "http://www.opensource.org/licenses/BSL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Borceux.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Borceux.json",
+      "referenceNumber": "38",
+      "name": "Borceux license",
+      "licenseId": "Borceux",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Borceux"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./BSD-2-Clause.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BSD-2-Clause.json",
+      "referenceNumber": "39",
+      "name": "BSD 2-clause \"Simplified\" License",
+      "licenseId": "BSD-2-Clause",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/BSD-2-Clause"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./BSD-2-Clause-FreeBSD.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BSD-2-Clause-FreeBSD.json",
+      "referenceNumber": "40",
+      "name": "BSD 2-clause FreeBSD License",
+      "licenseId": "BSD-2-Clause-FreeBSD",
+      "seeAlso": [
+        "http://www.freebsd.org/copyright/freebsd-license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./BSD-2-Clause-NetBSD.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BSD-2-Clause-NetBSD.json",
+      "referenceNumber": "41",
+      "name": "BSD 2-clause NetBSD License",
+      "licenseId": "BSD-2-Clause-NetBSD",
+      "seeAlso": [
+        "http://www.netbsd.org/about/redistribution.html#default"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./BSD-3-Clause.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BSD-3-Clause.json",
+      "referenceNumber": "42",
+      "name": "BSD 3-clause \"New\" or \"Revised\" License",
+      "licenseId": "BSD-3-Clause",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/BSD-3-Clause"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./BSD-3-Clause-Clear.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BSD-3-Clause-Clear.json",
+      "referenceNumber": "43",
+      "name": "BSD 3-clause Clear License",
+      "licenseId": "BSD-3-Clause-Clear",
+      "seeAlso": [
+        "http://labs.metacarta.com/license-explanation.html#license"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./BSD-3-Clause-No-Nuclear-License.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BSD-3-Clause-No-Nuclear-License.json",
+      "referenceNumber": "44",
+      "name": "BSD 3-Clause No Nuclear License",
+      "licenseId": "BSD-3-Clause-No-Nuclear-License",
+      "seeAlso": [
+        "http://download.oracle.com/otn-pub/java/licenses/bsd.txt?AuthParam\u003d1467140197_43d516ce1776bd08a58235a7785be1cc"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./BSD-3-Clause-No-Nuclear-License-2014.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BSD-3-Clause-No-Nuclear-License-2014.json",
+      "referenceNumber": "45",
+      "name": "BSD 3-Clause No Nuclear License 2014",
+      "licenseId": "BSD-3-Clause-No-Nuclear-License-2014",
+      "seeAlso": [
+        "https://java.net/projects/javaeetutorial/pages/BerkeleyLicense"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./BSD-3-Clause-No-Nuclear-Warranty.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BSD-3-Clause-No-Nuclear-Warranty.json",
+      "referenceNumber": "46",
+      "name": "BSD 3-Clause No Nuclear Warranty",
+      "licenseId": "BSD-3-Clause-No-Nuclear-Warranty",
+      "seeAlso": [
+        "https://jogamp.org/git/?p\u003dgluegen.git;a\u003dblob_plain;f\u003dLICENSE.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./BSD-4-Clause.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BSD-4-Clause.json",
+      "referenceNumber": "47",
+      "name": "BSD 4-clause \"Original\" or \"Old\" License",
+      "licenseId": "BSD-4-Clause",
+      "seeAlso": [
+        "http://directory.fsf.org/wiki/License:BSD_4Clause"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./BSD-Protection.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BSD-Protection.json",
+      "referenceNumber": "48",
+      "name": "BSD Protection License",
+      "licenseId": "BSD-Protection",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/BSD_Protection_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./BSD-Source-Code.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BSD-Source-Code.json",
+      "referenceNumber": "49",
+      "name": "BSD Source Code Attribution",
+      "licenseId": "BSD-Source-Code",
+      "seeAlso": [
+        "https://github.com/robbiehanson/CocoaHTTPServer/blob/master/LICENSE.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./BSD-3-Clause-Attribution.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BSD-3-Clause-Attribution.json",
+      "referenceNumber": "50",
+      "name": "BSD with attribution",
+      "licenseId": "BSD-3-Clause-Attribution",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/BSD_with_Attribution"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./0BSD.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/0BSD.json",
+      "referenceNumber": "51",
+      "name": "BSD Zero Clause License",
+      "licenseId": "0BSD",
+      "seeAlso": [
+        "http://landley.net/toybox/license.html"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./BSD-4-Clause-UC.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BSD-4-Clause-UC.json",
+      "referenceNumber": "52",
+      "name": "BSD-4-Clause (University of California-Specific)",
+      "licenseId": "BSD-4-Clause-UC",
+      "seeAlso": [
+        "http://www.freebsd.org/copyright/license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./bzip2-1.0.5.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/bzip2-1.0.5.json",
+      "referenceNumber": "53",
+      "name": "bzip2 and libbzip2 License v1.0.5",
+      "licenseId": "bzip2-1.0.5",
+      "seeAlso": [
+        "http://bzip.org/1.0.5/bzip2-manual-1.0.5.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./bzip2-1.0.6.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/bzip2-1.0.6.json",
+      "referenceNumber": "54",
+      "name": "bzip2 and libbzip2 License v1.0.6",
+      "licenseId": "bzip2-1.0.6",
+      "seeAlso": [
+        "https://github.com/asimonov-im/bzip2/blob/master/LICENSE"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Caldera.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Caldera.json",
+      "referenceNumber": "55",
+      "name": "Caldera License",
+      "licenseId": "Caldera",
+      "seeAlso": [
+        "http://www.lemis.com/grog/UNIX/ancient-source-all.pdf"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CECILL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CECILL-1.0.json",
+      "referenceNumber": "56",
+      "name": "CeCILL Free Software License Agreement v1.0",
+      "licenseId": "CECILL-1.0",
+      "seeAlso": [
+        "http://www.cecill.info/licences/Licence_CeCILL_V1-fr.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CECILL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CECILL-1.1.json",
+      "referenceNumber": "57",
+      "name": "CeCILL Free Software License Agreement v1.1",
+      "licenseId": "CECILL-1.1",
+      "seeAlso": [
+        "http://www.cecill.info/licences/Licence_CeCILL_V1.1-US.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CECILL-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CECILL-2.0.json",
+      "referenceNumber": "58",
+      "name": "CeCILL Free Software License Agreement v2.0",
+      "licenseId": "CECILL-2.0",
+      "seeAlso": [
+        "http://www.cecill.info/licences/Licence_CeCILL_V2-fr.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CECILL-2.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CECILL-2.1.json",
+      "referenceNumber": "59",
+      "name": "CeCILL Free Software License Agreement v2.1",
+      "licenseId": "CECILL-2.1",
+      "seeAlso": [
+        "http://www.cecill.info/licences/Licence_CeCILL_V2.1-fr.html",
+        "http://opensource.org/licenses/CECILL-2.1"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./CECILL-B.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CECILL-B.json",
+      "referenceNumber": "60",
+      "name": "CeCILL-B Free Software License Agreement",
+      "licenseId": "CECILL-B",
+      "seeAlso": [
+        "http://www.cecill.info/licences/Licence_CeCILL-B_V1-fr.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CECILL-C.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CECILL-C.json",
+      "referenceNumber": "61",
+      "name": "CeCILL-C Free Software License Agreement",
+      "licenseId": "CECILL-C",
+      "seeAlso": [
+        "http://www.cecill.info/licences/Licence_CeCILL-C_V1-fr.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./ClArtistic.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/ClArtistic.json",
+      "referenceNumber": "62",
+      "name": "Clarified Artistic License",
+      "licenseId": "ClArtistic",
+      "seeAlso": [
+        "http://www.ncftp.com/ncftp/doc/LICENSE.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./MIT-CMU.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/MIT-CMU.json",
+      "referenceNumber": "63",
+      "name": "CMU License",
+      "licenseId": "MIT-CMU",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing:MIT?rd\u003dLicensing/MIT#CMU_Style"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CNRI-Jython.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CNRI-Jython.json",
+      "referenceNumber": "64",
+      "name": "CNRI Jython License",
+      "licenseId": "CNRI-Jython",
+      "seeAlso": [
+        "http://www.jython.org/license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CNRI-Python.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CNRI-Python.json",
+      "referenceNumber": "65",
+      "name": "CNRI Python License",
+      "licenseId": "CNRI-Python",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/CNRI-Python"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./CNRI-Python-GPL-Compatible.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CNRI-Python-GPL-Compatible.json",
+      "referenceNumber": "66",
+      "name": "CNRI Python Open Source GPL Compatible License Agreement",
+      "licenseId": "CNRI-Python-GPL-Compatible",
+      "seeAlso": [
+        "http://www.python.org/download/releases/1.6.1/download_win/"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CPOL-1.02.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CPOL-1.02.json",
+      "referenceNumber": "67",
+      "name": "Code Project Open License 1.02",
+      "licenseId": "CPOL-1.02",
+      "seeAlso": [
+        "http://www.codeproject.com/info/cpol10.aspx"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CDDL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CDDL-1.0.json",
+      "referenceNumber": "68",
+      "name": "Common Development and Distribution License 1.0",
+      "licenseId": "CDDL-1.0",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/cddl1"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./CDDL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CDDL-1.1.json",
+      "referenceNumber": "69",
+      "name": "Common Development and Distribution License 1.1",
+      "licenseId": "CDDL-1.1",
+      "seeAlso": [
+        "http://glassfish.java.net/public/CDDL+GPL_1_1.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CPAL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CPAL-1.0.json",
+      "referenceNumber": "70",
+      "name": "Common Public Attribution License 1.0",
+      "licenseId": "CPAL-1.0",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/CPAL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./CPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CPL-1.0.json",
+      "referenceNumber": "71",
+      "name": "Common Public License 1.0",
+      "licenseId": "CPL-1.0",
+      "seeAlso": [
+        "http://opensource.org/licenses/CPL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./CATOSL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CATOSL-1.1.json",
+      "referenceNumber": "72",
+      "name": "Computer Associates Trusted Open Source License 1.1",
+      "licenseId": "CATOSL-1.1",
+      "seeAlso": [
+        "http://opensource.org/licenses/CATOSL-1.1"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Condor-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Condor-1.1.json",
+      "referenceNumber": "73",
+      "name": "Condor Public License v1.1",
+      "licenseId": "Condor-1.1",
+      "seeAlso": [
+        "http://research.cs.wisc.edu/condor/license.html#condor"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-1.0.json",
+      "referenceNumber": "74",
+      "name": "Creative Commons Attribution 1.0",
+      "licenseId": "CC-BY-1.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by/1.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-2.0.json",
+      "referenceNumber": "75",
+      "name": "Creative Commons Attribution 2.0",
+      "licenseId": "CC-BY-2.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by/2.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-2.5.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-2.5.json",
+      "referenceNumber": "76",
+      "name": "Creative Commons Attribution 2.5",
+      "licenseId": "CC-BY-2.5",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by/2.5/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-3.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-3.0.json",
+      "referenceNumber": "77",
+      "name": "Creative Commons Attribution 3.0",
+      "licenseId": "CC-BY-3.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by/3.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-4.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-4.0.json",
+      "referenceNumber": "78",
+      "name": "Creative Commons Attribution 4.0",
+      "licenseId": "CC-BY-4.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by/4.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-ND-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-ND-1.0.json",
+      "referenceNumber": "79",
+      "name": "Creative Commons Attribution No Derivatives 1.0",
+      "licenseId": "CC-BY-ND-1.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nd/1.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-ND-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-ND-2.0.json",
+      "referenceNumber": "80",
+      "name": "Creative Commons Attribution No Derivatives 2.0",
+      "licenseId": "CC-BY-ND-2.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nd/2.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-ND-2.5.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-ND-2.5.json",
+      "referenceNumber": "81",
+      "name": "Creative Commons Attribution No Derivatives 2.5",
+      "licenseId": "CC-BY-ND-2.5",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nd/2.5/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-ND-3.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-ND-3.0.json",
+      "referenceNumber": "82",
+      "name": "Creative Commons Attribution No Derivatives 3.0",
+      "licenseId": "CC-BY-ND-3.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nd/3.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-ND-4.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-ND-4.0.json",
+      "referenceNumber": "83",
+      "name": "Creative Commons Attribution No Derivatives 4.0",
+      "licenseId": "CC-BY-ND-4.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nd/4.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-NC-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-NC-1.0.json",
+      "referenceNumber": "84",
+      "name": "Creative Commons Attribution Non Commercial 1.0",
+      "licenseId": "CC-BY-NC-1.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nc/1.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-NC-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-NC-2.0.json",
+      "referenceNumber": "85",
+      "name": "Creative Commons Attribution Non Commercial 2.0",
+      "licenseId": "CC-BY-NC-2.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nc/2.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-NC-2.5.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-NC-2.5.json",
+      "referenceNumber": "86",
+      "name": "Creative Commons Attribution Non Commercial 2.5",
+      "licenseId": "CC-BY-NC-2.5",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nc/2.5/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-NC-3.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-NC-3.0.json",
+      "referenceNumber": "87",
+      "name": "Creative Commons Attribution Non Commercial 3.0",
+      "licenseId": "CC-BY-NC-3.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nc/3.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-NC-4.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-NC-4.0.json",
+      "referenceNumber": "88",
+      "name": "Creative Commons Attribution Non Commercial 4.0",
+      "licenseId": "CC-BY-NC-4.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nc/4.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-NC-ND-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-NC-ND-1.0.json",
+      "referenceNumber": "89",
+      "name": "Creative Commons Attribution Non Commercial No Derivatives 1.0",
+      "licenseId": "CC-BY-NC-ND-1.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nd-nc/1.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-NC-ND-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-NC-ND-2.0.json",
+      "referenceNumber": "90",
+      "name": "Creative Commons Attribution Non Commercial No Derivatives 2.0",
+      "licenseId": "CC-BY-NC-ND-2.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nc-nd/2.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-NC-ND-2.5.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-NC-ND-2.5.json",
+      "referenceNumber": "91",
+      "name": "Creative Commons Attribution Non Commercial No Derivatives 2.5",
+      "licenseId": "CC-BY-NC-ND-2.5",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nc-nd/2.5/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-NC-ND-3.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-NC-ND-3.0.json",
+      "referenceNumber": "92",
+      "name": "Creative Commons Attribution Non Commercial No Derivatives 3.0",
+      "licenseId": "CC-BY-NC-ND-3.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nc-nd/3.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-NC-ND-4.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-NC-ND-4.0.json",
+      "referenceNumber": "93",
+      "name": "Creative Commons Attribution Non Commercial No Derivatives 4.0",
+      "licenseId": "CC-BY-NC-ND-4.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nc-nd/4.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-NC-SA-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-NC-SA-1.0.json",
+      "referenceNumber": "94",
+      "name": "Creative Commons Attribution Non Commercial Share Alike 1.0",
+      "licenseId": "CC-BY-NC-SA-1.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nc-sa/1.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-NC-SA-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-NC-SA-2.0.json",
+      "referenceNumber": "95",
+      "name": "Creative Commons Attribution Non Commercial Share Alike 2.0",
+      "licenseId": "CC-BY-NC-SA-2.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nc-sa/2.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-NC-SA-2.5.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-NC-SA-2.5.json",
+      "referenceNumber": "96",
+      "name": "Creative Commons Attribution Non Commercial Share Alike 2.5",
+      "licenseId": "CC-BY-NC-SA-2.5",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nc-sa/2.5/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-NC-SA-3.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-NC-SA-3.0.json",
+      "referenceNumber": "97",
+      "name": "Creative Commons Attribution Non Commercial Share Alike 3.0",
+      "licenseId": "CC-BY-NC-SA-3.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nc-sa/3.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-NC-SA-4.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-NC-SA-4.0.json",
+      "referenceNumber": "98",
+      "name": "Creative Commons Attribution Non Commercial Share Alike 4.0",
+      "licenseId": "CC-BY-NC-SA-4.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-nc-sa/4.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-SA-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-SA-1.0.json",
+      "referenceNumber": "99",
+      "name": "Creative Commons Attribution Share Alike 1.0",
+      "licenseId": "CC-BY-SA-1.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-sa/1.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-SA-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-SA-2.0.json",
+      "referenceNumber": "100",
+      "name": "Creative Commons Attribution Share Alike 2.0",
+      "licenseId": "CC-BY-SA-2.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-sa/2.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-SA-2.5.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-SA-2.5.json",
+      "referenceNumber": "101",
+      "name": "Creative Commons Attribution Share Alike 2.5",
+      "licenseId": "CC-BY-SA-2.5",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-sa/2.5/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-SA-3.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-SA-3.0.json",
+      "referenceNumber": "102",
+      "name": "Creative Commons Attribution Share Alike 3.0",
+      "licenseId": "CC-BY-SA-3.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-sa/3.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC-BY-SA-4.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC-BY-SA-4.0.json",
+      "referenceNumber": "103",
+      "name": "Creative Commons Attribution Share Alike 4.0",
+      "licenseId": "CC-BY-SA-4.0",
+      "seeAlso": [
+        "http://creativecommons.org/licenses/by-sa/4.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CC0-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CC0-1.0.json",
+      "referenceNumber": "104",
+      "name": "Creative Commons Zero v1.0 Universal",
+      "licenseId": "CC0-1.0",
+      "seeAlso": [
+        "http://creativecommons.org/publicdomain/zero/1.0/legalcode"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Crossword.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Crossword.json",
+      "referenceNumber": "105",
+      "name": "Crossword License",
+      "licenseId": "Crossword",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Crossword"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CrystalStacker.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CrystalStacker.json",
+      "referenceNumber": "106",
+      "name": "CrystalStacker License",
+      "licenseId": "CrystalStacker",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing:CrystalStacker?rd\u003dLicensing/CrystalStacker"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./CUA-OPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/CUA-OPL-1.0.json",
+      "referenceNumber": "107",
+      "name": "CUA Office Public License v1.0",
+      "licenseId": "CUA-OPL-1.0",
+      "seeAlso": [
+        "http://opensource.org/licenses/CUA-OPL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Cube.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Cube.json",
+      "referenceNumber": "108",
+      "name": "Cube License",
+      "licenseId": "Cube",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Cube"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./curl.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/curl.json",
+      "referenceNumber": "109",
+      "name": "curl License",
+      "licenseId": "curl",
+      "seeAlso": [
+        "https://github.com/bagder/curl/blob/master/COPYING"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./D-FSL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/D-FSL-1.0.json",
+      "referenceNumber": "110",
+      "name": "Deutsche Freie Software Lizenz",
+      "licenseId": "D-FSL-1.0",
+      "seeAlso": [
+        "http://www.dipp.nrw.de/d-fsl/lizenzen/",
+        "http://www.dipp.nrw.de/d-fsl/index_html/lizenzen/de/D-FSL-1_0_de.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./diffmark.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/diffmark.json",
+      "referenceNumber": "111",
+      "name": "diffmark license",
+      "licenseId": "diffmark",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/diffmark"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./WTFPL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/WTFPL.json",
+      "referenceNumber": "112",
+      "name": "Do What The F*ck You Want To Public License",
+      "licenseId": "WTFPL",
+      "seeAlso": [
+        "http://sam.zoy.org/wtfpl/COPYING"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./DOC.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/DOC.json",
+      "referenceNumber": "113",
+      "name": "DOC License",
+      "licenseId": "DOC",
+      "seeAlso": [
+        "http://www.cs.wustl.edu/~schmidt/ACE-copying.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Dotseqn.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Dotseqn.json",
+      "referenceNumber": "114",
+      "name": "Dotseqn License",
+      "licenseId": "Dotseqn",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Dotseqn"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./DSDP.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/DSDP.json",
+      "referenceNumber": "115",
+      "name": "DSDP License",
+      "licenseId": "DSDP",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/DSDP"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./dvipdfm.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/dvipdfm.json",
+      "referenceNumber": "116",
+      "name": "dvipdfm License",
+      "licenseId": "dvipdfm",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/dvipdfm"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./EPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/EPL-1.0.json",
+      "referenceNumber": "117",
+      "name": "Eclipse Public License 1.0",
+      "licenseId": "EPL-1.0",
+      "seeAlso": [
+        "http://www.eclipse.org/legal/epl-v10.html",
+        "http://www.opensource.org/licenses/EPL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./ECL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/ECL-1.0.json",
+      "referenceNumber": "118",
+      "name": "Educational Community License v1.0",
+      "licenseId": "ECL-1.0",
+      "seeAlso": [
+        "http://opensource.org/licenses/ECL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./ECL-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/ECL-2.0.json",
+      "referenceNumber": "119",
+      "name": "Educational Community License v2.0",
+      "licenseId": "ECL-2.0",
+      "seeAlso": [
+        "http://opensource.org/licenses/ECL-2.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./eGenix.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/eGenix.json",
+      "referenceNumber": "120",
+      "name": "eGenix.com Public License 1.1.0",
+      "licenseId": "eGenix",
+      "seeAlso": [
+        "http://www.egenix.com/products/eGenix.com-Public-License-1.1.0.pdf",
+        "https://fedoraproject.org/wiki/Licensing/eGenix.com_Public_License_1.1.0"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./EFL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/EFL-1.0.json",
+      "referenceNumber": "121",
+      "name": "Eiffel Forum License v1.0",
+      "licenseId": "EFL-1.0",
+      "seeAlso": [
+        "http://www.eiffel-nice.org/license/forum.txt",
+        "http://opensource.org/licenses/EFL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./EFL-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/EFL-2.0.json",
+      "referenceNumber": "122",
+      "name": "Eiffel Forum License v2.0",
+      "licenseId": "EFL-2.0",
+      "seeAlso": [
+        "http://www.eiffel-nice.org/license/eiffel-forum-license-2.html",
+        "http://opensource.org/licenses/EFL-2.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./MIT-advertising.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/MIT-advertising.json",
+      "referenceNumber": "123",
+      "name": "Enlightenment License (e16)",
+      "licenseId": "MIT-advertising",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/MIT_With_Advertising"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./MIT-enna.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/MIT-enna.json",
+      "referenceNumber": "124",
+      "name": "enna License",
+      "licenseId": "MIT-enna",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/MIT#enna"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Entessa.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Entessa.json",
+      "referenceNumber": "125",
+      "name": "Entessa Public License v1.0",
+      "licenseId": "Entessa",
+      "seeAlso": [
+        "http://opensource.org/licenses/Entessa"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./ErlPL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/ErlPL-1.1.json",
+      "referenceNumber": "126",
+      "name": "Erlang Public License v1.1",
+      "licenseId": "ErlPL-1.1",
+      "seeAlso": [
+        "http://www.erlang.org/EPLICENSE"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./EUDatagrid.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/EUDatagrid.json",
+      "referenceNumber": "127",
+      "name": "EU DataGrid Software License",
+      "licenseId": "EUDatagrid",
+      "seeAlso": [
+        "http://eu-datagrid.web.cern.ch/eu-datagrid/license.html",
+        "http://www.opensource.org/licenses/EUDatagrid"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./EUPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/EUPL-1.0.json",
+      "referenceNumber": "128",
+      "name": "European Union Public License 1.0",
+      "licenseId": "EUPL-1.0",
+      "seeAlso": [
+        "http://ec.europa.eu/idabc/en/document/7330.html",
+        "http://ec.europa.eu/idabc/servlets/Doc027f.pdf?id\u003d31096"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./EUPL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/EUPL-1.1.json",
+      "referenceNumber": "129",
+      "name": "European Union Public License 1.1",
+      "licenseId": "EUPL-1.1",
+      "seeAlso": [
+        "https://joinup.ec.europa.eu/software/page/eupl/licence-eupl",
+        "https://joinup.ec.europa.eu/system/files/EN/EUPL%20v.1.1%20-%20Licence.pdf",
+        "http://www.opensource.org/licenses/EUPL-1.1"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Eurosym.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Eurosym.json",
+      "referenceNumber": "130",
+      "name": "Eurosym License",
+      "licenseId": "Eurosym",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Eurosym"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Fair.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Fair.json",
+      "referenceNumber": "131",
+      "name": "Fair License",
+      "licenseId": "Fair",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/Fair"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./MIT-feh.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/MIT-feh.json",
+      "referenceNumber": "132",
+      "name": "feh License",
+      "licenseId": "MIT-feh",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/MIT#feh"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Frameworx-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Frameworx-1.0.json",
+      "referenceNumber": "133",
+      "name": "Frameworx Open License 1.0",
+      "licenseId": "Frameworx-1.0",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/Frameworx-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./FreeImage.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/FreeImage.json",
+      "referenceNumber": "134",
+      "name": "FreeImage Public License v1.0",
+      "licenseId": "FreeImage",
+      "seeAlso": [
+        "http://freeimage.sourceforge.net/freeimage-license.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./FTL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/FTL.json",
+      "referenceNumber": "135",
+      "name": "Freetype Project License",
+      "licenseId": "FTL",
+      "seeAlso": [
+        "http://freetype.fis.uniroma2.it/FTL.TXT"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./FSFAP.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/FSFAP.json",
+      "referenceNumber": "136",
+      "name": "FSF All Permissive License",
+      "licenseId": "FSFAP",
+      "seeAlso": [
+        "http://www.gnu.org/prep/maintain/html_node/License-Notices-for-Other-Files.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./FSFUL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/FSFUL.json",
+      "referenceNumber": "137",
+      "name": "FSF Unlimited License",
+      "licenseId": "FSFUL",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/FSF_Unlimited_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./FSFULLR.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/FSFULLR.json",
+      "referenceNumber": "138",
+      "name": "FSF Unlimited License (with License Retention)",
+      "licenseId": "FSFULLR",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/FSF_Unlimited_License#License_Retention_Variant"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Giftware.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Giftware.json",
+      "referenceNumber": "139",
+      "name": "Giftware License",
+      "licenseId": "Giftware",
+      "seeAlso": [
+        "http://alleg.sourceforge.net//license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./GL2PS.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/GL2PS.json",
+      "referenceNumber": "140",
+      "name": "GL2PS License",
+      "licenseId": "GL2PS",
+      "seeAlso": [
+        "http://www.geuz.org/gl2ps/COPYING.GL2PS"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Glulxe.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Glulxe.json",
+      "referenceNumber": "141",
+      "name": "Glulxe License",
+      "licenseId": "Glulxe",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Glulxe"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./AGPL-3.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/AGPL-3.0.json",
+      "referenceNumber": "142",
+      "name": "GNU Affero General Public License v3.0",
+      "licenseId": "AGPL-3.0",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/agpl.txt",
+        "http://www.opensource.org/licenses/AGPL-3.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./GFDL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/GFDL-1.1.json",
+      "referenceNumber": "143",
+      "name": "GNU Free Documentation License v1.1",
+      "licenseId": "GFDL-1.1",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/old-licenses/fdl-1.1.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./GFDL-1.2.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/GFDL-1.2.json",
+      "referenceNumber": "144",
+      "name": "GNU Free Documentation License v1.2",
+      "licenseId": "GFDL-1.2",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/old-licenses/fdl-1.2.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./GFDL-1.3.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/GFDL-1.3.json",
+      "referenceNumber": "145",
+      "name": "GNU Free Documentation License v1.3",
+      "licenseId": "GFDL-1.3",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/fdl-1.3.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./GPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/GPL-1.0.json",
+      "referenceNumber": "146",
+      "name": "GNU General Public License v1.0 only",
+      "licenseId": "GPL-1.0",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/old-licenses/gpl-1.0-standalone.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./GPL-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/GPL-2.0.json",
+      "referenceNumber": "147",
+      "name": "GNU General Public License v2.0 only",
+      "licenseId": "GPL-2.0",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/old-licenses/gpl-2.0-standalone.html",
+        "http://www.opensource.org/licenses/GPL-2.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./GPL-3.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/GPL-3.0.json",
+      "referenceNumber": "148",
+      "name": "GNU General Public License v3.0 only",
+      "licenseId": "GPL-3.0",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/gpl-3.0-standalone.html",
+        "http://www.opensource.org/licenses/GPL-3.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./LGPL-2.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LGPL-2.1.json",
+      "referenceNumber": "149",
+      "name": "GNU Lesser General Public License v2.1 only",
+      "licenseId": "LGPL-2.1",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/old-licenses/lgpl-2.1-standalone.html",
+        "http://www.opensource.org/licenses/LGPL-2.1"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./LGPL-3.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LGPL-3.0.json",
+      "referenceNumber": "150",
+      "name": "GNU Lesser General Public License v3.0 only",
+      "licenseId": "LGPL-3.0",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/lgpl-3.0-standalone.html",
+        "http://www.opensource.org/licenses/LGPL-3.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./LGPL-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LGPL-2.0.json",
+      "referenceNumber": "151",
+      "name": "GNU Library General Public License v2 only",
+      "licenseId": "LGPL-2.0",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/old-licenses/lgpl-2.0-standalone.html"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./gnuplot.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/gnuplot.json",
+      "referenceNumber": "152",
+      "name": "gnuplot License",
+      "licenseId": "gnuplot",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Gnuplot"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./gSOAP-1.3b.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/gSOAP-1.3b.json",
+      "referenceNumber": "153",
+      "name": "gSOAP Public License v1.3b",
+      "licenseId": "gSOAP-1.3b",
+      "seeAlso": [
+        "http://www.cs.fsu.edu/~engelen/license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./HaskellReport.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/HaskellReport.json",
+      "referenceNumber": "154",
+      "name": "Haskell Language Report License",
+      "licenseId": "HaskellReport",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Haskell_Language_Report_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./HPND.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/HPND.json",
+      "referenceNumber": "155",
+      "name": "Historic Permission Notice and Disclaimer",
+      "licenseId": "HPND",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/HPND"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./IBM-pibs.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/IBM-pibs.json",
+      "referenceNumber": "156",
+      "name": "IBM PowerPC Initialization and Boot Software",
+      "licenseId": "IBM-pibs",
+      "seeAlso": [
+        "http://git.denx.de/?p\u003du-boot.git;a\u003dblob;f\u003darch/powerpc/cpu/ppc4xx/miiphy.c;h\u003d297155fdafa064b955e53e9832de93bfb0cfb85b;hb\u003d9fab4bf4cc077c21e43941866f3f2c196f28670d"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./IPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/IPL-1.0.json",
+      "referenceNumber": "157",
+      "name": "IBM Public License v1.0",
+      "licenseId": "IPL-1.0",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/IPL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./ICU.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/ICU.json",
+      "referenceNumber": "158",
+      "name": "ICU License",
+      "licenseId": "ICU",
+      "seeAlso": [
+        "http://source.icu-project.org/repos/icu/icu/trunk/license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./ImageMagick.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/ImageMagick.json",
+      "referenceNumber": "159",
+      "name": "ImageMagick License",
+      "licenseId": "ImageMagick",
+      "seeAlso": [
+        "http://www.imagemagick.org/script/license.php"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./iMatix.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/iMatix.json",
+      "referenceNumber": "160",
+      "name": "iMatix Standard Function Library Agreement",
+      "licenseId": "iMatix",
+      "seeAlso": [
+        "http://legacy.imatix.com/html/sfl/sfl4.htm#license"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Imlib2.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Imlib2.json",
+      "referenceNumber": "161",
+      "name": "Imlib2 License",
+      "licenseId": "Imlib2",
+      "seeAlso": [
+        "http://trac.enlightenment.org/e/browser/trunk/imlib2/COPYING"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./IJG.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/IJG.json",
+      "referenceNumber": "162",
+      "name": "Independent JPEG Group License",
+      "licenseId": "IJG",
+      "seeAlso": [
+        "http://dev.w3.org/cvsweb/Amaya/libjpeg/Attic/README?rev\u003d1.2"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Info-ZIP.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Info-ZIP.json",
+      "referenceNumber": "163",
+      "name": "Info-ZIP License",
+      "licenseId": "Info-ZIP",
+      "seeAlso": [
+        "http://www.info-zip.org/license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Intel-ACPI.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Intel-ACPI.json",
+      "referenceNumber": "164",
+      "name": "Intel ACPI Software License Agreement",
+      "licenseId": "Intel-ACPI",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Intel_ACPI_Software_License_Agreement"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Intel.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Intel.json",
+      "referenceNumber": "165",
+      "name": "Intel Open Source License",
+      "licenseId": "Intel",
+      "seeAlso": [
+        "http://opensource.org/licenses/Intel"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Interbase-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Interbase-1.0.json",
+      "referenceNumber": "166",
+      "name": "Interbase Public License v1.0",
+      "licenseId": "Interbase-1.0",
+      "seeAlso": [
+        "https://web.archive.org/web/20060319014854/http://info.borland.com/devsupport/interbase/opensource/IPL.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./IPA.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/IPA.json",
+      "referenceNumber": "167",
+      "name": "IPA Font License",
+      "licenseId": "IPA",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/IPA"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./ISC.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/ISC.json",
+      "referenceNumber": "168",
+      "name": "ISC License",
+      "licenseId": "ISC",
+      "seeAlso": [
+        "http://www.isc.org/software/license",
+        "http://www.opensource.org/licenses/ISC"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./JasPer-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/JasPer-2.0.json",
+      "referenceNumber": "169",
+      "name": "JasPer License",
+      "licenseId": "JasPer-2.0",
+      "seeAlso": [
+        "http://www.ece.uvic.ca/~mdadams/jasper/LICENSE"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./JSON.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/JSON.json",
+      "referenceNumber": "170",
+      "name": "JSON License",
+      "licenseId": "JSON",
+      "seeAlso": [
+        "http://www.json.org/license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./LPPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LPPL-1.0.json",
+      "referenceNumber": "171",
+      "name": "LaTeX Project Public License v1.0",
+      "licenseId": "LPPL-1.0",
+      "seeAlso": [
+        "http://www.latex-project.org/lppl/lppl-1-0.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./LPPL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LPPL-1.1.json",
+      "referenceNumber": "172",
+      "name": "LaTeX Project Public License v1.1",
+      "licenseId": "LPPL-1.1",
+      "seeAlso": [
+        "http://www.latex-project.org/lppl/lppl-1-1.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./LPPL-1.2.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LPPL-1.2.json",
+      "referenceNumber": "173",
+      "name": "LaTeX Project Public License v1.2",
+      "licenseId": "LPPL-1.2",
+      "seeAlso": [
+        "http://www.latex-project.org/lppl/lppl-1-2.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./LPPL-1.3a.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LPPL-1.3a.json",
+      "referenceNumber": "174",
+      "name": "LaTeX Project Public License v1.3a",
+      "licenseId": "LPPL-1.3a",
+      "seeAlso": [
+        "http://www.latex-project.org/lppl/lppl-1-3a.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./LPPL-1.3c.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LPPL-1.3c.json",
+      "referenceNumber": "175",
+      "name": "LaTeX Project Public License v1.3c",
+      "licenseId": "LPPL-1.3c",
+      "seeAlso": [
+        "http://www.latex-project.org/lppl/lppl-1-3c.txt",
+        "http://www.opensource.org/licenses/LPPL-1.3c"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Latex2e.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Latex2e.json",
+      "referenceNumber": "176",
+      "name": "Latex2e License",
+      "licenseId": "Latex2e",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Latex2e"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./BSD-3-Clause-LBNL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/BSD-3-Clause-LBNL.json",
+      "referenceNumber": "177",
+      "name": "Lawrence Berkeley National Labs BSD variant license",
+      "licenseId": "BSD-3-Clause-LBNL",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/LBNLBSD"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Leptonica.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Leptonica.json",
+      "referenceNumber": "178",
+      "name": "Leptonica License",
+      "licenseId": "Leptonica",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Leptonica"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./LGPLLR.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LGPLLR.json",
+      "referenceNumber": "179",
+      "name": "Lesser General Public License For Linguistic Resources",
+      "licenseId": "LGPLLR",
+      "seeAlso": [
+        "http://www-igm.univ-mlv.fr/~unitex/lgpllr.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Libpng.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Libpng.json",
+      "referenceNumber": "180",
+      "name": "libpng License",
+      "licenseId": "Libpng",
+      "seeAlso": [
+        "http://www.libpng.org/pub/png/src/libpng-LICENSE.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./libtiff.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/libtiff.json",
+      "referenceNumber": "181",
+      "name": "libtiff License",
+      "licenseId": "libtiff",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/libtiff"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./LAL-1.2.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LAL-1.2.json",
+      "referenceNumber": "182",
+      "name": "Licence Art Libre 1.2",
+      "licenseId": "LAL-1.2",
+      "seeAlso": [
+        "http://artlibre.org/licence/lal/licence-art-libre-12/"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./LAL-1.3.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LAL-1.3.json",
+      "referenceNumber": "183",
+      "name": "Licence Art Libre 1.3",
+      "licenseId": "LAL-1.3",
+      "seeAlso": [
+        "http://artlibre.org/"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./LiLiQ-P-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LiLiQ-P-1.1.json",
+      "referenceNumber": "184",
+      "name": "Licence Libre du Québec – Permissive version 1.1",
+      "licenseId": "LiLiQ-P-1.1",
+      "seeAlso": [
+        "http://opensource.org/licenses/LiLiQ-P-1.1",
+        "https://www.forge.gouv.qc.ca/participez/licence-logicielle/licence-libre-du-quebec-liliq-en-francais/licence-libre-du-quebec-liliq-en-francais-v1-0/licence-libre-du-quebec-reciprocite-liliq-r-v1-0/"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./LiLiQ-Rplus-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LiLiQ-Rplus-1.1.json",
+      "referenceNumber": "185",
+      "name": "Licence Libre du Québec – Réciprocité forte version 1.1",
+      "licenseId": "LiLiQ-Rplus-1.1",
+      "seeAlso": [
+        "http://opensource.org/licenses/LiLiQ-Rplus-1.1",
+        "https://www.forge.gouv.qc.ca/participez/licence-logicielle/licence-libre-du-quebec-liliq-en-francais/licence-libre-du-quebec-reciprocite-forte-liliq-r-v1-1/"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./LiLiQ-R-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LiLiQ-R-1.1.json",
+      "referenceNumber": "186",
+      "name": "Licence Libre du Québec – Réciprocité version 1.1",
+      "licenseId": "LiLiQ-R-1.1",
+      "seeAlso": [
+        "http://opensource.org/licenses/LiLiQ-R-1.1",
+        "https://www.forge.gouv.qc.ca/participez/licence-logicielle/licence-libre-du-quebec-liliq-en-francais/licence-libre-du-quebec-reciprocite-liliq-r-v1-1/"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./LPL-1.02.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LPL-1.02.json",
+      "referenceNumber": "187",
+      "name": "Lucent Public License v1.02",
+      "licenseId": "LPL-1.02",
+      "seeAlso": [
+        "http://plan9.bell-labs.com/plan9/license.html",
+        "http://www.opensource.org/licenses/LPL-1.02"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./LPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/LPL-1.0.json",
+      "referenceNumber": "188",
+      "name": "Lucent Public License Version 1.0",
+      "licenseId": "LPL-1.0",
+      "seeAlso": [
+        "http://opensource.org/licenses/LPL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./MakeIndex.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/MakeIndex.json",
+      "referenceNumber": "189",
+      "name": "MakeIndex License",
+      "licenseId": "MakeIndex",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/MakeIndex"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./MTLL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/MTLL.json",
+      "referenceNumber": "190",
+      "name": "Matrix Template Library License",
+      "licenseId": "MTLL",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Matrix_Template_Library_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./MS-PL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/MS-PL.json",
+      "referenceNumber": "191",
+      "name": "Microsoft Public License",
+      "licenseId": "MS-PL",
+      "seeAlso": [
+        "http://www.microsoft.com/opensource/licenses.mspx",
+        "http://www.opensource.org/licenses/MS-PL"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./MS-RL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/MS-RL.json",
+      "referenceNumber": "192",
+      "name": "Microsoft Reciprocal License",
+      "licenseId": "MS-RL",
+      "seeAlso": [
+        "http://www.microsoft.com/opensource/licenses.mspx",
+        "http://www.opensource.org/licenses/MS-RL"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./MirOS.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/MirOS.json",
+      "referenceNumber": "193",
+      "name": "MirOS Licence",
+      "licenseId": "MirOS",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/MirOS"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./MITNFA.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/MITNFA.json",
+      "referenceNumber": "194",
+      "name": "MIT +no-false-attribs license",
+      "licenseId": "MITNFA",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/MITNFA"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./MIT.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/MIT.json",
+      "referenceNumber": "195",
+      "name": "MIT License",
+      "licenseId": "MIT",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/MIT"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Motosoto.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Motosoto.json",
+      "referenceNumber": "196",
+      "name": "Motosoto License",
+      "licenseId": "Motosoto",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/Motosoto"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./MPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/MPL-1.0.json",
+      "referenceNumber": "197",
+      "name": "Mozilla Public License 1.0",
+      "licenseId": "MPL-1.0",
+      "seeAlso": [
+        "http://www.mozilla.org/MPL/MPL-1.0.html",
+        "http://opensource.org/licenses/MPL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./MPL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/MPL-1.1.json",
+      "referenceNumber": "198",
+      "name": "Mozilla Public License 1.1",
+      "licenseId": "MPL-1.1",
+      "seeAlso": [
+        "http://www.mozilla.org/MPL/MPL-1.1.html",
+        "http://www.opensource.org/licenses/MPL-1.1"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./MPL-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/MPL-2.0.json",
+      "referenceNumber": "199",
+      "name": "Mozilla Public License 2.0",
+      "licenseId": "MPL-2.0",
+      "seeAlso": [
+        "http://www.mozilla.org/MPL/2.0/",
+        "http://opensource.org/licenses/MPL-2.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./MPL-2.0-no-copyleft-exception.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/MPL-2.0-no-copyleft-exception.json",
+      "referenceNumber": "200",
+      "name": "Mozilla Public License 2.0 (no copyleft exception)",
+      "licenseId": "MPL-2.0-no-copyleft-exception",
+      "seeAlso": [
+        "http://www.mozilla.org/MPL/2.0/",
+        "http://opensource.org/licenses/MPL-2.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./mpich2.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/mpich2.json",
+      "referenceNumber": "201",
+      "name": "mpich2 License",
+      "licenseId": "mpich2",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/MIT"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Multics.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Multics.json",
+      "referenceNumber": "202",
+      "name": "Multics License",
+      "licenseId": "Multics",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/Multics"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Mup.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Mup.json",
+      "referenceNumber": "203",
+      "name": "Mup License",
+      "licenseId": "Mup",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Mup"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./NASA-1.3.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/NASA-1.3.json",
+      "referenceNumber": "204",
+      "name": "NASA Open Source Agreement 1.3",
+      "licenseId": "NASA-1.3",
+      "seeAlso": [
+        "http://ti.arc.nasa.gov/opensource/nosa/",
+        "http://www.opensource.org/licenses/NASA-1.3"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Naumen.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Naumen.json",
+      "referenceNumber": "205",
+      "name": "Naumen Public License",
+      "licenseId": "Naumen",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/Naumen"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./NBPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/NBPL-1.0.json",
+      "referenceNumber": "206",
+      "name": "Net Boolean Public License v1",
+      "licenseId": "NBPL-1.0",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003d37b4b3f6cc4bf34e1d3dec61e69914b9819d8894"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Net-SNMP.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Net-SNMP.json",
+      "referenceNumber": "207",
+      "name": "Net-SNMP License",
+      "licenseId": "Net-SNMP",
+      "seeAlso": [
+        "http://net-snmp.sourceforge.net/about/license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./NetCDF.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/NetCDF.json",
+      "referenceNumber": "208",
+      "name": "NetCDF license",
+      "licenseId": "NetCDF",
+      "seeAlso": [
+        "http://www.unidata.ucar.edu/software/netcdf/copyright.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./NGPL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/NGPL.json",
+      "referenceNumber": "209",
+      "name": "Nethack General Public License",
+      "licenseId": "NGPL",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/NGPL"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./NOSL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/NOSL.json",
+      "referenceNumber": "210",
+      "name": "Netizen Open Source License",
+      "licenseId": "NOSL",
+      "seeAlso": [
+        "http://bits.netizen.com.au/licenses/NOSL/nosl.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./NPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/NPL-1.0.json",
+      "referenceNumber": "211",
+      "name": "Netscape Public License v1.0",
+      "licenseId": "NPL-1.0",
+      "seeAlso": [
+        "http://www.mozilla.org/MPL/NPL/1.0/"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./NPL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/NPL-1.1.json",
+      "referenceNumber": "212",
+      "name": "Netscape Public License v1.1",
+      "licenseId": "NPL-1.1",
+      "seeAlso": [
+        "http://www.mozilla.org/MPL/NPL/1.1/"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Newsletr.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Newsletr.json",
+      "referenceNumber": "213",
+      "name": "Newsletr License",
+      "licenseId": "Newsletr",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Newsletr"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./NLPL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/NLPL.json",
+      "referenceNumber": "214",
+      "name": "No Limit Public License",
+      "licenseId": "NLPL",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/NLPL"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Nokia.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Nokia.json",
+      "referenceNumber": "215",
+      "name": "Nokia Open Source License",
+      "licenseId": "Nokia",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/nokia"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./NPOSL-3.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/NPOSL-3.0.json",
+      "referenceNumber": "216",
+      "name": "Non-Profit Open Software License 3.0",
+      "licenseId": "NPOSL-3.0",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/NOSL3.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./NLOD-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/NLOD-1.0.json",
+      "referenceNumber": "217",
+      "name": "Norwegian Licence for Open Government Data",
+      "licenseId": "NLOD-1.0",
+      "seeAlso": [
+        "http://data.norge.no/nlod/en/1.0"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Noweb.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Noweb.json",
+      "referenceNumber": "218",
+      "name": "Noweb License",
+      "licenseId": "Noweb",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Noweb"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./NRL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/NRL.json",
+      "referenceNumber": "219",
+      "name": "NRL License",
+      "licenseId": "NRL",
+      "seeAlso": [
+        "http://web.mit.edu/network/isakmp/nrllicense.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./NTP.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/NTP.json",
+      "referenceNumber": "220",
+      "name": "NTP License",
+      "licenseId": "NTP",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/NTP"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Nunit.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Nunit.json",
+      "referenceNumber": "221",
+      "name": "Nunit License",
+      "licenseId": "Nunit",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Nunit"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OCLC-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OCLC-2.0.json",
+      "referenceNumber": "222",
+      "name": "OCLC Research Public License 2.0",
+      "licenseId": "OCLC-2.0",
+      "seeAlso": [
+        "http://www.oclc.org/research/activities/software/license/v2final.htm",
+        "http://www.opensource.org/licenses/OCLC-2.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./ODbL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/ODbL-1.0.json",
+      "referenceNumber": "223",
+      "name": "ODC Open Database License v1.0",
+      "licenseId": "ODbL-1.0",
+      "seeAlso": [
+        "http://www.opendatacommons.org/licenses/odbl/1.0/"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./PDDL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/PDDL-1.0.json",
+      "referenceNumber": "224",
+      "name": "ODC Public Domain Dedication \u0026 License 1.0",
+      "licenseId": "PDDL-1.0",
+      "seeAlso": [
+        "http://opendatacommons.org/licenses/pddl/1.0/"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OCCT-PL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OCCT-PL.json",
+      "referenceNumber": "225",
+      "name": "Open CASCADE Technology Public License",
+      "licenseId": "OCCT-PL",
+      "seeAlso": [
+        "http://www.opencascade.com/content/occt-public-license"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OGTSL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OGTSL.json",
+      "referenceNumber": "226",
+      "name": "Open Group Test Suite License",
+      "licenseId": "OGTSL",
+      "seeAlso": [
+        "http://www.opengroup.org/testing/downloads/The_Open_Group_TSL.txt",
+        "http://www.opensource.org/licenses/OGTSL"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./OLDAP-2.2.2.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-2.2.2.json",
+      "referenceNumber": "227",
+      "name": "Open LDAP Public License  2.2.2",
+      "licenseId": "OLDAP-2.2.2",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003ddf2cc1e21eb7c160695f5b7cffd6296c151ba188"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OLDAP-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-1.1.json",
+      "referenceNumber": "228",
+      "name": "Open LDAP Public License v1.1",
+      "licenseId": "OLDAP-1.1",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003d806557a5ad59804ef3a44d5abfbe91d706b0791f"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OLDAP-1.2.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-1.2.json",
+      "referenceNumber": "229",
+      "name": "Open LDAP Public License v1.2",
+      "licenseId": "OLDAP-1.2",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003d42b0383c50c299977b5893ee695cf4e486fb0dc7"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OLDAP-1.3.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-1.3.json",
+      "referenceNumber": "230",
+      "name": "Open LDAP Public License v1.3",
+      "licenseId": "OLDAP-1.3",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003de5f8117f0ce088d0bd7a8e18ddf37eaa40eb09b1"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OLDAP-1.4.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-1.4.json",
+      "referenceNumber": "231",
+      "name": "Open LDAP Public License v1.4",
+      "licenseId": "OLDAP-1.4",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003dc9f95c2f3f2ffb5e0ae55fe7388af75547660941"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OLDAP-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-2.0.json",
+      "referenceNumber": "232",
+      "name": "Open LDAP Public License v2.0 (or possibly 2.0A and 2.0B)",
+      "licenseId": "OLDAP-2.0",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003dcbf50f4e1185a21abd4c0a54d3f4341fe28f36ea"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OLDAP-2.0.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-2.0.1.json",
+      "referenceNumber": "233",
+      "name": "Open LDAP Public License v2.0.1",
+      "licenseId": "OLDAP-2.0.1",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003db6d68acd14e51ca3aab4428bf26522aa74873f0e"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OLDAP-2.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-2.1.json",
+      "referenceNumber": "234",
+      "name": "Open LDAP Public License v2.1",
+      "licenseId": "OLDAP-2.1",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003db0d176738e96a0d3b9f85cb51e140a86f21be715"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OLDAP-2.2.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-2.2.json",
+      "referenceNumber": "235",
+      "name": "Open LDAP Public License v2.2",
+      "licenseId": "OLDAP-2.2",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003d470b0c18ec67621c85881b2733057fecf4a1acc3"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OLDAP-2.2.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-2.2.1.json",
+      "referenceNumber": "236",
+      "name": "Open LDAP Public License v2.2.1",
+      "licenseId": "OLDAP-2.2.1",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003d4bc786f34b50aa301be6f5600f58a980070f481e"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OLDAP-2.3.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-2.3.json",
+      "referenceNumber": "237",
+      "name": "Open LDAP Public License v2.3",
+      "licenseId": "OLDAP-2.3",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003dd32cf54a32d581ab475d23c810b0a7fbaf8d63c3"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OLDAP-2.4.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-2.4.json",
+      "referenceNumber": "238",
+      "name": "Open LDAP Public License v2.4",
+      "licenseId": "OLDAP-2.4",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003dcd1284c4a91a8a380d904eee68d1583f989ed386"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OLDAP-2.5.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-2.5.json",
+      "referenceNumber": "239",
+      "name": "Open LDAP Public License v2.5",
+      "licenseId": "OLDAP-2.5",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003d6852b9d90022e8593c98205413380536b1b5a7cf"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OLDAP-2.6.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-2.6.json",
+      "referenceNumber": "240",
+      "name": "Open LDAP Public License v2.6",
+      "licenseId": "OLDAP-2.6",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003d1cae062821881f41b73012ba816434897abf4205"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OLDAP-2.7.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-2.7.json",
+      "referenceNumber": "241",
+      "name": "Open LDAP Public License v2.7",
+      "licenseId": "OLDAP-2.7",
+      "seeAlso": [
+        "http://www.openldap.org/devel/gitweb.cgi?p\u003dopenldap.git;a\u003dblob;f\u003dLICENSE;hb\u003d47c2415c1df81556eeb39be6cad458ef87c534a2"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OLDAP-2.8.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OLDAP-2.8.json",
+      "referenceNumber": "242",
+      "name": "Open LDAP Public License v2.8",
+      "licenseId": "OLDAP-2.8",
+      "seeAlso": [
+        "http://www.openldap.org/software/release/license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OML.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OML.json",
+      "referenceNumber": "243",
+      "name": "Open Market License",
+      "licenseId": "OML",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Open_Market_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OPL-1.0.json",
+      "referenceNumber": "244",
+      "name": "Open Public License v1.0",
+      "licenseId": "OPL-1.0",
+      "seeAlso": [
+        "http://old.koalateam.com/jackaroo/OPL_1_0.TXT",
+        "https://fedoraproject.org/wiki/Licensing/Open_Public_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OSL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OSL-1.0.json",
+      "referenceNumber": "245",
+      "name": "Open Software License 1.0",
+      "licenseId": "OSL-1.0",
+      "seeAlso": [
+        "http://opensource.org/licenses/OSL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./OSL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OSL-1.1.json",
+      "referenceNumber": "246",
+      "name": "Open Software License 1.1",
+      "licenseId": "OSL-1.1",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/OSL1.1"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OSL-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OSL-2.0.json",
+      "referenceNumber": "247",
+      "name": "Open Software License 2.0",
+      "licenseId": "OSL-2.0",
+      "seeAlso": [
+        "http://web.archive.org/web/20041020171434/http://www.rosenlaw.com/osl2.0.html"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./OSL-2.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OSL-2.1.json",
+      "referenceNumber": "248",
+      "name": "Open Software License 2.1",
+      "licenseId": "OSL-2.1",
+      "seeAlso": [
+        "http://opensource.org/licenses/OSL-2.1",
+        "http://web.archive.org/web/20050212003940/http://www.rosenlaw.com/osl21.htm"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./OSL-3.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OSL-3.0.json",
+      "referenceNumber": "249",
+      "name": "Open Software License 3.0",
+      "licenseId": "OSL-3.0",
+      "seeAlso": [
+        "http://www.rosenlaw.com/OSL3.0.htm",
+        "http://www.opensource.org/licenses/OSL-3.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./OpenSSL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OpenSSL.json",
+      "referenceNumber": "250",
+      "name": "OpenSSL License",
+      "licenseId": "OpenSSL",
+      "seeAlso": [
+        "http://www.openssl.org/source/license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OSET-PL-2.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OSET-PL-2.1.json",
+      "referenceNumber": "251",
+      "name": "OSET Public License version 2.1",
+      "licenseId": "OSET-PL-2.1",
+      "seeAlso": [
+        "http://opensource.org/licenses/OPL-2.1",
+        "http://www.osetfoundation.org/public-license/#"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./PHP-3.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/PHP-3.0.json",
+      "referenceNumber": "252",
+      "name": "PHP License v3.0",
+      "licenseId": "PHP-3.0",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/PHP-3.0",
+        "http://www.php.net/license/3_0.txt"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./PHP-3.01.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/PHP-3.01.json",
+      "referenceNumber": "253",
+      "name": "PHP License v3.01",
+      "licenseId": "PHP-3.01",
+      "seeAlso": [
+        "http://www.php.net/license/3_01.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Plexus.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Plexus.json",
+      "referenceNumber": "254",
+      "name": "Plexus Classworlds License",
+      "licenseId": "Plexus",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Plexus_Classworlds_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./PostgreSQL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/PostgreSQL.json",
+      "referenceNumber": "255",
+      "name": "PostgreSQL License",
+      "licenseId": "PostgreSQL",
+      "seeAlso": [
+        "http://www.postgresql.org/about/licence",
+        "http://www.opensource.org/licenses/PostgreSQL"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./psfrag.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/psfrag.json",
+      "referenceNumber": "256",
+      "name": "psfrag License",
+      "licenseId": "psfrag",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/psfrag"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./psutils.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/psutils.json",
+      "referenceNumber": "257",
+      "name": "psutils License",
+      "licenseId": "psutils",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/psutils"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Python-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Python-2.0.json",
+      "referenceNumber": "258",
+      "name": "Python License 2.0",
+      "licenseId": "Python-2.0",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/Python-2.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./QPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/QPL-1.0.json",
+      "referenceNumber": "259",
+      "name": "Q Public License 1.0",
+      "licenseId": "QPL-1.0",
+      "seeAlso": [
+        "http://doc.qt.nokia.com/3.3/license.html",
+        "http://www.opensource.org/licenses/QPL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Qhull.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Qhull.json",
+      "referenceNumber": "260",
+      "name": "Qhull License",
+      "licenseId": "Qhull",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Qhull"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Rdisc.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Rdisc.json",
+      "referenceNumber": "261",
+      "name": "Rdisc License",
+      "licenseId": "Rdisc",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Rdisc_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./RPSL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/RPSL-1.0.json",
+      "referenceNumber": "262",
+      "name": "RealNetworks Public Source License v1.0",
+      "licenseId": "RPSL-1.0",
+      "seeAlso": [
+        "https://helixcommunity.org/content/rpsl",
+        "http://www.opensource.org/licenses/RPSL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./RPL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/RPL-1.1.json",
+      "referenceNumber": "263",
+      "name": "Reciprocal Public License 1.1",
+      "licenseId": "RPL-1.1",
+      "seeAlso": [
+        "http://opensource.org/licenses/RPL-1.1"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./RPL-1.5.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/RPL-1.5.json",
+      "referenceNumber": "264",
+      "name": "Reciprocal Public License 1.5",
+      "licenseId": "RPL-1.5",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/RPL-1.5"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./RHeCos-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/RHeCos-1.1.json",
+      "referenceNumber": "265",
+      "name": "Red Hat eCos Public License v1.1",
+      "licenseId": "RHeCos-1.1",
+      "seeAlso": [
+        "http://ecos.sourceware.org/old-license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./RSCPL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/RSCPL.json",
+      "referenceNumber": "266",
+      "name": "Ricoh Source Code Public License",
+      "licenseId": "RSCPL",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/RSCPL"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./RSA-MD.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/RSA-MD.json",
+      "referenceNumber": "267",
+      "name": "RSA Message-Digest License ",
+      "licenseId": "RSA-MD",
+      "seeAlso": [
+        "http://www.faqs.org/rfcs/rfc1321.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Ruby.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Ruby.json",
+      "referenceNumber": "268",
+      "name": "Ruby License",
+      "licenseId": "Ruby",
+      "seeAlso": [
+        "http://www.ruby-lang.org/en/LICENSE.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./SAX-PD.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/SAX-PD.json",
+      "referenceNumber": "269",
+      "name": "Sax Public Domain Notice",
+      "licenseId": "SAX-PD",
+      "seeAlso": [
+        "http://www.saxproject.org/copying.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Saxpath.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Saxpath.json",
+      "referenceNumber": "270",
+      "name": "Saxpath License",
+      "licenseId": "Saxpath",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Saxpath_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./SCEA.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/SCEA.json",
+      "referenceNumber": "271",
+      "name": "SCEA Shared Source License",
+      "licenseId": "SCEA",
+      "seeAlso": [
+        "http://research.scea.com/scea_shared_source_license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./SWL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/SWL.json",
+      "referenceNumber": "272",
+      "name": "Scheme Widget Library (SWL) Software License Agreement",
+      "licenseId": "SWL",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/SWL"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./SMPPL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/SMPPL.json",
+      "referenceNumber": "273",
+      "name": "Secure Messaging Protocol Public License",
+      "licenseId": "SMPPL",
+      "seeAlso": [
+        "https://github.com/dcblake/SMP/blob/master/Documentation/License.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Sendmail.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Sendmail.json",
+      "referenceNumber": "274",
+      "name": "Sendmail License",
+      "licenseId": "Sendmail",
+      "seeAlso": [
+        "http://www.sendmail.com/pdfs/open_source/sendmail_license.pdf"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./SGI-B-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/SGI-B-1.0.json",
+      "referenceNumber": "275",
+      "name": "SGI Free Software License B v1.0",
+      "licenseId": "SGI-B-1.0",
+      "seeAlso": [
+        "http://oss.sgi.com/projects/FreeB/SGIFreeSWLicB.1.0.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./SGI-B-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/SGI-B-1.1.json",
+      "referenceNumber": "276",
+      "name": "SGI Free Software License B v1.1",
+      "licenseId": "SGI-B-1.1",
+      "seeAlso": [
+        "http://oss.sgi.com/projects/FreeB/"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./SGI-B-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/SGI-B-2.0.json",
+      "referenceNumber": "277",
+      "name": "SGI Free Software License B v2.0",
+      "licenseId": "SGI-B-2.0",
+      "seeAlso": [
+        "http://oss.sgi.com/projects/FreeB/SGIFreeSWLicB.2.0.pdf"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OFL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OFL-1.0.json",
+      "referenceNumber": "278",
+      "name": "SIL Open Font License 1.0",
+      "licenseId": "OFL-1.0",
+      "seeAlso": [
+        "http://scripts.sil.org/cms/scripts/page.php?item_id\u003dOFL10_web"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./OFL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/OFL-1.1.json",
+      "referenceNumber": "279",
+      "name": "SIL Open Font License 1.1",
+      "licenseId": "OFL-1.1",
+      "seeAlso": [
+        "http://scripts.sil.org/cms/scripts/page.php?item_id\u003dOFL_web",
+        "http://www.opensource.org/licenses/OFL-1.1"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./SimPL-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/SimPL-2.0.json",
+      "referenceNumber": "280",
+      "name": "Simple Public License 2.0",
+      "licenseId": "SimPL-2.0",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/SimPL-2.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Sleepycat.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Sleepycat.json",
+      "referenceNumber": "281",
+      "name": "Sleepycat License",
+      "licenseId": "Sleepycat",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/Sleepycat"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./SNIA.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/SNIA.json",
+      "referenceNumber": "282",
+      "name": "SNIA Public License 1.1",
+      "licenseId": "SNIA",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/SNIA_Public_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Spencer-86.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Spencer-86.json",
+      "referenceNumber": "283",
+      "name": "Spencer License 86",
+      "licenseId": "Spencer-86",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Henry_Spencer_Reg-Ex_Library_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Spencer-94.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Spencer-94.json",
+      "referenceNumber": "284",
+      "name": "Spencer License 94",
+      "licenseId": "Spencer-94",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Henry_Spencer_Reg-Ex_Library_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Spencer-99.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Spencer-99.json",
+      "referenceNumber": "285",
+      "name": "Spencer License 99",
+      "licenseId": "Spencer-99",
+      "seeAlso": [
+        "http://www.opensource.apple.com/source/tcl/tcl-5/tcl/generic/regfronts.c"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./SMLNJ.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/SMLNJ.json",
+      "referenceNumber": "286",
+      "name": "Standard ML of New Jersey License",
+      "licenseId": "SMLNJ",
+      "seeAlso": [
+        "http://www.smlnj.org//license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./SugarCRM-1.1.3.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/SugarCRM-1.1.3.json",
+      "referenceNumber": "287",
+      "name": "SugarCRM Public License v1.1.3",
+      "licenseId": "SugarCRM-1.1.3",
+      "seeAlso": [
+        "http://www.sugarcrm.com/crm/SPL"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./SISSL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/SISSL.json",
+      "referenceNumber": "288",
+      "name": "Sun Industry Standards Source License v1.1",
+      "licenseId": "SISSL",
+      "seeAlso": [
+        "http://www.openoffice.org/licenses/sissl_license.html",
+        "http://opensource.org/licenses/SISSL"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./SISSL-1.2.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/SISSL-1.2.json",
+      "referenceNumber": "289",
+      "name": "Sun Industry Standards Source License v1.2",
+      "licenseId": "SISSL-1.2",
+      "seeAlso": [
+        "http://gridscheduler.sourceforge.net/Gridengine_SISSL_license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./SPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/SPL-1.0.json",
+      "referenceNumber": "290",
+      "name": "Sun Public License v1.0",
+      "licenseId": "SPL-1.0",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/SPL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Watcom-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Watcom-1.0.json",
+      "referenceNumber": "291",
+      "name": "Sybase Open Watcom Public License 1.0",
+      "licenseId": "Watcom-1.0",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/Watcom-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./TCL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/TCL.json",
+      "referenceNumber": "292",
+      "name": "TCL/TK License",
+      "licenseId": "TCL",
+      "seeAlso": [
+        "http://www.tcl.tk/software/tcltk/license.html",
+        "https://fedoraproject.org/wiki/Licensing/TCL"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./TCP-wrappers.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/TCP-wrappers.json",
+      "referenceNumber": "293",
+      "name": "TCP Wrappers License",
+      "licenseId": "TCP-wrappers",
+      "seeAlso": [
+        "http://rc.quest.com/topics/openssh/license.php#tcpwrappers"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Unlicense.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Unlicense.json",
+      "referenceNumber": "294",
+      "name": "The Unlicense",
+      "licenseId": "Unlicense",
+      "seeAlso": [
+        "http://unlicense.org/"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./TMate.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/TMate.json",
+      "referenceNumber": "295",
+      "name": "TMate Open Source License",
+      "licenseId": "TMate",
+      "seeAlso": [
+        "http://svnkit.com/license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./TORQUE-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/TORQUE-1.1.json",
+      "referenceNumber": "296",
+      "name": "TORQUE v2.5+ Software License v1.1",
+      "licenseId": "TORQUE-1.1",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/TORQUEv1.1"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./TOSL.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/TOSL.json",
+      "referenceNumber": "297",
+      "name": "Trusster Open Source License",
+      "licenseId": "TOSL",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/TOSL"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Unicode-DFS-2015.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Unicode-DFS-2015.json",
+      "referenceNumber": "298",
+      "name": "Unicode License Agreement - Data Files and Software (2015)",
+      "licenseId": "Unicode-DFS-2015",
+      "seeAlso": [
+        "https://web.archive.org/web/20151224134844/http://unicode.org/copyright.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Unicode-DFS-2016.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Unicode-DFS-2016.json",
+      "referenceNumber": "299",
+      "name": "Unicode License Agreement - Data Files and Software (2016)",
+      "licenseId": "Unicode-DFS-2016",
+      "seeAlso": [
+        "http://www.unicode.org/copyright.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Unicode-TOU.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Unicode-TOU.json",
+      "referenceNumber": "300",
+      "name": "Unicode Terms of Use",
+      "licenseId": "Unicode-TOU",
+      "seeAlso": [
+        "http://www.unicode.org/copyright.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./UPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/UPL-1.0.json",
+      "referenceNumber": "301",
+      "name": "Universal Permissive License v1.0",
+      "licenseId": "UPL-1.0",
+      "seeAlso": [
+        "http://opensource.org/licenses/UPL"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./NCSA.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/NCSA.json",
+      "referenceNumber": "302",
+      "name": "University of Illinois/NCSA Open Source License",
+      "licenseId": "NCSA",
+      "seeAlso": [
+        "http://otm.illinois.edu/uiuc_openSource",
+        "http://www.opensource.org/licenses/NCSA"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Vim.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Vim.json",
+      "referenceNumber": "303",
+      "name": "Vim License",
+      "licenseId": "Vim",
+      "seeAlso": [
+        "http://vimdoc.sourceforge.net/htmldoc/uganda.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./VOSTROM.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/VOSTROM.json",
+      "referenceNumber": "304",
+      "name": "VOSTROM Public License for Open Source",
+      "licenseId": "VOSTROM",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/VOSTROM"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./VSL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/VSL-1.0.json",
+      "referenceNumber": "305",
+      "name": "Vovida Software License v1.0",
+      "licenseId": "VSL-1.0",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/VSL-1.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./W3C-20150513.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/W3C-20150513.json",
+      "referenceNumber": "306",
+      "name": "W3C Software Notice and Document License (2015-05-13)",
+      "licenseId": "W3C-20150513",
+      "seeAlso": [
+        "https://www.w3.org/Consortium/Legal/2015/copyright-software-and-document"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./W3C-19980720.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/W3C-19980720.json",
+      "referenceNumber": "307",
+      "name": "W3C Software Notice and License (1998-07-20)",
+      "licenseId": "W3C-19980720",
+      "seeAlso": [
+        "http://www.w3.org/Consortium/Legal/copyright-software-19980720.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./W3C.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/W3C.json",
+      "referenceNumber": "308",
+      "name": "W3C Software Notice and License (2002-12-31)",
+      "licenseId": "W3C",
+      "seeAlso": [
+        "http://www.w3.org/Consortium/Legal/2002/copyright-software-20021231.html",
+        "http://www.opensource.org/licenses/W3C"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./Wsuipa.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Wsuipa.json",
+      "referenceNumber": "309",
+      "name": "Wsuipa License",
+      "licenseId": "Wsuipa",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Wsuipa"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Xnet.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Xnet.json",
+      "referenceNumber": "310",
+      "name": "X.Net License",
+      "licenseId": "Xnet",
+      "seeAlso": [
+        "http://opensource.org/licenses/Xnet"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./X11.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/X11.json",
+      "referenceNumber": "311",
+      "name": "X11 License",
+      "licenseId": "X11",
+      "seeAlso": [
+        "http://www.xfree86.org/3.3.6/COPYRIGHT2.html#3"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Xerox.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Xerox.json",
+      "referenceNumber": "312",
+      "name": "Xerox License",
+      "licenseId": "Xerox",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Xerox"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./XFree86-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/XFree86-1.1.json",
+      "referenceNumber": "313",
+      "name": "XFree86 License 1.1",
+      "licenseId": "XFree86-1.1",
+      "seeAlso": [
+        "http://www.xfree86.org/current/LICENSE4.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./xinetd.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/xinetd.json",
+      "referenceNumber": "314",
+      "name": "xinetd License",
+      "licenseId": "xinetd",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Xinetd_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./xpp.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/xpp.json",
+      "referenceNumber": "315",
+      "name": "XPP License",
+      "licenseId": "xpp",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/xpp"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./XSkat.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/XSkat.json",
+      "referenceNumber": "316",
+      "name": "XSkat License",
+      "licenseId": "XSkat",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/XSkat_License"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./YPL-1.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/YPL-1.0.json",
+      "referenceNumber": "317",
+      "name": "Yahoo! Public License v1.0",
+      "licenseId": "YPL-1.0",
+      "seeAlso": [
+        "http://www.zimbra.com/license/yahoo_public_license_1.0.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./YPL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/YPL-1.1.json",
+      "referenceNumber": "318",
+      "name": "Yahoo! Public License v1.1",
+      "licenseId": "YPL-1.1",
+      "seeAlso": [
+        "http://www.zimbra.com/license/yahoo_public_license_1.1.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Zed.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Zed.json",
+      "referenceNumber": "319",
+      "name": "Zed License",
+      "licenseId": "Zed",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/Zed"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Zend-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Zend-2.0.json",
+      "referenceNumber": "320",
+      "name": "Zend License v2.0",
+      "licenseId": "Zend-2.0",
+      "seeAlso": [
+        "https://web.archive.org/web/20130517195954/http://www.zend.com/license/2_00.txt"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Zimbra-1.3.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Zimbra-1.3.json",
+      "referenceNumber": "321",
+      "name": "Zimbra Public License v1.3",
+      "licenseId": "Zimbra-1.3",
+      "seeAlso": [
+        ""
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Zimbra-1.4.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Zimbra-1.4.json",
+      "referenceNumber": "322",
+      "name": "Zimbra Public License v1.4",
+      "licenseId": "Zimbra-1.4",
+      "seeAlso": [
+        "http://www.zimbra.com/legal/zimbra-public-license-1-4"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./Zlib.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/Zlib.json",
+      "referenceNumber": "323",
+      "name": "zlib License",
+      "licenseId": "Zlib",
+      "seeAlso": [
+        "http://www.zlib.net/zlib_license.html",
+        "http://www.opensource.org/licenses/Zlib"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./zlib-acknowledgement.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/zlib-acknowledgement.json",
+      "referenceNumber": "324",
+      "name": "zlib/libpng License with Acknowledgement",
+      "licenseId": "zlib-acknowledgement",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing/ZlibWithAcknowledgement"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./ZPL-1.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/ZPL-1.1.json",
+      "referenceNumber": "325",
+      "name": "Zope Public License 1.1",
+      "licenseId": "ZPL-1.1",
+      "seeAlso": [
+        "http://old.zope.org/Resources/License/ZPL-1.1"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./ZPL-2.0.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/ZPL-2.0.json",
+      "referenceNumber": "326",
+      "name": "Zope Public License 2.0",
+      "licenseId": "ZPL-2.0",
+      "seeAlso": [
+        "http://old.zope.org/Resources/License/ZPL-2.0",
+        "http://opensource.org/licenses/ZPL-2.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./ZPL-2.1.html",
+      "isDeprecatedLicenseId": false,
+      "detailsUrl": "http://spdx.org/licenses/ZPL-2.1.json",
+      "referenceNumber": "327",
+      "name": "Zope Public License 2.1",
+      "licenseId": "ZPL-2.1",
+      "seeAlso": [
+        "http://old.zope.org/Resources/ZPL/"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./eCos-2.0.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/eCos-2.0.json",
+      "referenceNumber": "328",
+      "name": "eCos license version 2.0",
+      "licenseId": "eCos-2.0",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/ecos-license.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./GPL-1.0+.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/GPL-1.0+.json",
+      "referenceNumber": "329",
+      "name": "GNU General Public License v1.0 or later",
+      "licenseId": "GPL-1.0+",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/old-licenses/gpl-1.0-standalone.html"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./GPL-2.0+.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/GPL-2.0+.json",
+      "referenceNumber": "330",
+      "name": "GNU General Public License v2.0 or later",
+      "licenseId": "GPL-2.0+",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/old-licenses/gpl-2.0-standalone.html",
+        "http://www.opensource.org/licenses/GPL-2.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./GPL-2.0-with-autoconf-exception.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/GPL-2.0-with-autoconf-exception.json",
+      "referenceNumber": "331",
+      "name": "GNU General Public License v2.0 w/Autoconf exception",
+      "licenseId": "GPL-2.0-with-autoconf-exception",
+      "seeAlso": [
+        "http://ac-archive.sourceforge.net/doc/copyright.html"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./GPL-2.0-with-bison-exception.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/GPL-2.0-with-bison-exception.json",
+      "referenceNumber": "332",
+      "name": "GNU General Public License v2.0 w/Bison exception",
+      "licenseId": "GPL-2.0-with-bison-exception",
+      "seeAlso": [
+        "none",
+        "found"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./GPL-2.0-with-classpath-exception.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/GPL-2.0-with-classpath-exception.json",
+      "referenceNumber": "333",
+      "name": "GNU General Public License v2.0 w/Classpath exception",
+      "licenseId": "GPL-2.0-with-classpath-exception",
+      "seeAlso": [
+        "http://www.gnu.org/software/classpath/license.html"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./GPL-2.0-with-font-exception.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/GPL-2.0-with-font-exception.json",
+      "referenceNumber": "334",
+      "name": "GNU General Public License v2.0 w/Font exception",
+      "licenseId": "GPL-2.0-with-font-exception",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/gpl-faq.html#FontException"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./GPL-2.0-with-GCC-exception.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/GPL-2.0-with-GCC-exception.json",
+      "referenceNumber": "335",
+      "name": "GNU General Public License v2.0 w/GCC Runtime Library exception",
+      "licenseId": "GPL-2.0-with-GCC-exception",
+      "seeAlso": [
+        "none",
+        "found"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./GPL-3.0+.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/GPL-3.0+.json",
+      "referenceNumber": "336",
+      "name": "GNU General Public License v3.0 or later",
+      "licenseId": "GPL-3.0+",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/gpl-3.0-standalone.html",
+        "http://www.opensource.org/licenses/GPL-3.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./GPL-3.0-with-autoconf-exception.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/GPL-3.0-with-autoconf-exception.json",
+      "referenceNumber": "337",
+      "name": "GNU General Public License v3.0 w/Autoconf exception",
+      "licenseId": "GPL-3.0-with-autoconf-exception",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/autoconf-exception-3.0.html"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./GPL-3.0-with-GCC-exception.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/GPL-3.0-with-GCC-exception.json",
+      "referenceNumber": "338",
+      "name": "GNU General Public License v3.0 w/GCC Runtime Library exception",
+      "licenseId": "GPL-3.0-with-GCC-exception",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/gcc-exception-3.1.html"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./LGPL-2.1+.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/LGPL-2.1+.json",
+      "referenceNumber": "339",
+      "name": "GNU Lesser General Public License v2.1 or later",
+      "licenseId": "LGPL-2.1+",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/old-licenses/lgpl-2.1-standalone.html",
+        "http://www.opensource.org/licenses/LGPL-2.1"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./LGPL-3.0+.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/LGPL-3.0+.json",
+      "referenceNumber": "340",
+      "name": "GNU Lesser General Public License v3.0 or later",
+      "licenseId": "LGPL-3.0+",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/lgpl-3.0-standalone.html",
+        "http://www.opensource.org/licenses/LGPL-3.0"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./LGPL-2.0+.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/LGPL-2.0+.json",
+      "referenceNumber": "341",
+      "name": "GNU Library General Public License v2 or later",
+      "licenseId": "LGPL-2.0+",
+      "seeAlso": [
+        "http://www.gnu.org/licenses/old-licenses/lgpl-2.0-standalone.html"
+      ],
+      "isOsiApproved": true
+    },
+    {
+      "reference": "./StandardML-NJ.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/StandardML-NJ.json",
+      "referenceNumber": "342",
+      "name": "Standard ML of New Jersey License",
+      "licenseId": "StandardML-NJ",
+      "seeAlso": [
+        "https://fedoraproject.org/wiki/Licensing:MIT?rd\u003dLicensing/MIT#Standard_ML_of_New_Jersey_Variant"
+      ],
+      "isOsiApproved": false
+    },
+    {
+      "reference": "./WXwindows.html",
+      "isDeprecatedLicenseId": true,
+      "detailsUrl": "http://spdx.org/licenses/WXwindows.json",
+      "referenceNumber": "343",
+      "name": "wxWindows Library License",
+      "licenseId": "WXwindows",
+      "seeAlso": [
+        "http://www.opensource.org/licenses/WXwindows"
+      ],
+      "isOsiApproved": true
+    }
+  ],
+  "releaseDate": "Jun 30, 2016"
+}
\ No newline at end of file
diff --git a/travis-meta.sh b/travis-meta.sh
index b2da29e56af9e685523eaaa1cab0a1999c0323bd..cd1ef6b20969394f211c3ced3ceb4030bf4d50ac 100755
--- a/travis-meta.sh
+++ b/travis-meta.sh
@@ -12,9 +12,12 @@ export PATH=/opt/cabal/head/bin:$PATH
 # Currently doesn't work because Travis uses --depth=50 when cloning.
 #./Cabal/misc/gen-authors.sh > AUTHORS
 
+timed cabal update
+
 # Regenerate files
 timed make lexer
 timed make gen-extra-source-files
+timed make spdx
 
 # Fail if the diff is not empty.
 timed ./Cabal/misc/travis-diff-files.sh