{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 701
{-# LANGUAGE Safe #-}
#endif
module Data.SPDX.Licenses (
    licenses
  , licenseIdentifiers
  , mkLicenseId
  , isOsiApproved
  , licenseExceptions
  ) where

import Data.Foldable
import Data.Maybe

import Data.SPDX.Types

licenseExceptions :: [LicenseExceptionId]
licenseExceptions = map LicenseExceptionId [
  "Autoconf-exception-2.0",
  "Autoconf-exception-3.0",
  "Bison-exception-2.2",
  "Classpath-exception-2.0",
  "eCos-exception-2.0",
  "Font-exception-2.0",
  "GCC-exception-2.0",
  "GCC-exception-3.1",
  "WxWindows-exception-3.1"
  ]

-- | A list of SPDX licenses identifiers.
--
-- See <http://spdx.org/licenses/>.
licenseIdentifiers :: [LicenseId]
licenseIdentifiers = map fstOf3 licenses

fstOf3 :: (a, b, c) -> a
fstOf3 (x,_,_) = x

--sndOf3 :: (a, b, c) -> b
--sndOf3 (_,x,_) = x

trdOf3 :: (a, b, c) -> c
trdOf3 (_,_,x) = x

-- | Lookup `LicenseId` by string representation
mkLicenseId :: String -> Maybe LicenseId
mkLicenseId str = find ((== str) . getLicenseId) licenseIdentifiers

-- | Whether license is OSI approved
--
-- See <http://opensource.org/licenses/alphabetical>
isOsiApproved :: LicenseId -> Bool
isOsiApproved l = trdOf3 $ fromJust $ find ((==l) . fstOf3) licenses

-- | A list of `LicenseId`, license name and whether the license is OSI approved.
--
-- See <http://spdx.org/licenses/>.
licenses :: [(LicenseId, String, Bool)]
licenses =
  [ (LicenseId "AAL", "Attribution Assurance License", True)
  , (LicenseId "ADSL", "Amazon Digital Services License", False)
  , (LicenseId "AFL-1.1", "Academic Free License v1.1", True)
  , (LicenseId "AFL-1.2", "Academic Free License v1.2", True)
  , (LicenseId "AFL-2.0", "Academic Free License v2.0", True)
  , (LicenseId "AFL-2.1", "Academic Free License v2.1", True)
  , (LicenseId "AFL-3.0", "Academic Free License v3.0", True)
  , (LicenseId "AGPL-1.0", "Affero General Public License v1.0", False)
  , (LicenseId "AGPL-3.0", "GNU Affero General Public License v3.0", True)
  , (LicenseId "AMDPLPA", "AMD's plpa_map.c License", False)
  , (LicenseId "AML", "Apple MIT License", False)
  , (LicenseId "AMPAS", "Academy of Motion Picture Arts and Sciences BSD", False)
  , (LicenseId "ANTLR-PD", "ANTLR Software Rights Notice", False)
  , (LicenseId "APAFML", "Adobe Postscript AFM License", False)
  , (LicenseId "APL-1.0", "Adaptive Public License 1.0", True)
  , (LicenseId "APSL-1.0", "Apple Public Source License 1.0", True)
  , (LicenseId "APSL-1.1", "Apple Public Source License 1.1", True)
  , (LicenseId "APSL-1.2", "Apple Public Source License 1.2", True)
  , (LicenseId "APSL-2.0", "Apple Public Source License 2.0", True)
  , (LicenseId "Abstyles", "Abstyles License", False)
  , (LicenseId "Adobe-2006", "Adobe Systems Incorporated Source Code License Agreement", False)
  , (LicenseId "Adobe-Glyph", "Adobe Glyph List License", False)
  , (LicenseId "Afmparse", "Afmparse License", False)
  , (LicenseId "Aladdin", "Aladdin Free Public License", False)
  , (LicenseId "Apache-1.0", "Apache License 1.0", False)
  , (LicenseId "Apache-1.1", "Apache License 1.1", True)
  , (LicenseId "Apache-2.0", "Apache License 2.0", True)
  , (LicenseId "Artistic-1.0", "Artistic License 1.0", True)
  , (LicenseId "Artistic-1.0-Perl", "Artistic License 1.0 (Perl)", True)
  , (LicenseId "Artistic-1.0-cl8", "Artistic License 1.0 w/clause 8", True)
  , (LicenseId "Artistic-2.0", "Artistic License 2.0", True)
  , (LicenseId "BSD-2-Clause", "BSD 2-clause \"Simplified\" License", True)
  , (LicenseId "BSD-2-Clause-FreeBSD", "BSD 2-clause FreeBSD License", False)
  , (LicenseId "BSD-2-Clause-NetBSD", "BSD 2-clause NetBSD License", False)
  , (LicenseId "BSD-3-Clause", "BSD 3-clause \"New\" or \"Revised\" License", True)
  , (LicenseId "BSD-3-Clause-Attribution", "BSD with attribution", False)
  , (LicenseId "BSD-3-Clause-Clear", "BSD 3-clause Clear License", False)
  , (LicenseId "BSD-3-Clause-LBNL", "Lawrence Berkeley National Labs BSD variant license", False)
  , (LicenseId "BSD-4-Clause", "BSD 4-clause \"Original\" or \"Old\" License", False)
  , (LicenseId "BSD-4-Clause-UC", "BSD-4-Clause (University of California-Specific)", False)
  , (LicenseId "BSD-Protection", "BSD Protection License", False)
  , (LicenseId "BSL-1.0", "Boost Software License 1.0", True)
  , (LicenseId "Bahyph", "Bahyph License", False)
  , (LicenseId "Barr", "Barr License", False)
  , (LicenseId "Beerware", "Beerware License", False)
  , (LicenseId "BitTorrent-1.0", "BitTorrent Open Source License v1.0", False)
  , (LicenseId "BitTorrent-1.1", "BitTorrent Open Source License v1.1", False)
  , (LicenseId "Borceux", "Borceux license", False)
  , (LicenseId "CATOSL-1.1", "Computer Associates Trusted Open Source License 1.1", True)
  , (LicenseId "CC-BY-1.0", "Creative Commons Attribution 1.0", False)
  , (LicenseId "CC-BY-2.0", "Creative Commons Attribution 2.0", False)
  , (LicenseId "CC-BY-2.5", "Creative Commons Attribution 2.5", False)
  , (LicenseId "CC-BY-3.0", "Creative Commons Attribution 3.0", False)
  , (LicenseId "CC-BY-4.0", "Creative Commons Attribution 4.0", False)
  , (LicenseId "CC-BY-NC-1.0", "Creative Commons Attribution Non Commercial 1.0", False)
  , (LicenseId "CC-BY-NC-2.0", "Creative Commons Attribution Non Commercial 2.0", False)
  , (LicenseId "CC-BY-NC-2.5", "Creative Commons Attribution Non Commercial 2.5", False)
  , (LicenseId "CC-BY-NC-3.0", "Creative Commons Attribution Non Commercial 3.0", False)
  , (LicenseId "CC-BY-NC-4.0", "Creative Commons Attribution Non Commercial 4.0", False)
  , (LicenseId "CC-BY-NC-ND-1.0", "Creative Commons Attribution Non Commercial No Derivatives 1.0", False)
  , (LicenseId "CC-BY-NC-ND-2.0", "Creative Commons Attribution Non Commercial No Derivatives 2.0", False)
  , (LicenseId "CC-BY-NC-ND-2.5", "Creative Commons Attribution Non Commercial No Derivatives 2.5", False)
  , (LicenseId "CC-BY-NC-ND-3.0", "Creative Commons Attribution Non Commercial No Derivatives 3.0", False)
  , (LicenseId "CC-BY-NC-ND-4.0", "Creative Commons Attribution Non Commercial No Derivatives 4.0", False)
  , (LicenseId "CC-BY-NC-SA-1.0", "Creative Commons Attribution Non Commercial Share Alike 1.0", False)
  , (LicenseId "CC-BY-NC-SA-2.0", "Creative Commons Attribution Non Commercial Share Alike 2.0", False)
  , (LicenseId "CC-BY-NC-SA-2.5", "Creative Commons Attribution Non Commercial Share Alike 2.5", False)
  , (LicenseId "CC-BY-NC-SA-3.0", "Creative Commons Attribution Non Commercial Share Alike 3.0", False)
  , (LicenseId "CC-BY-NC-SA-4.0", "Creative Commons Attribution Non Commercial Share Alike 4.0", False)
  , (LicenseId "CC-BY-ND-1.0", "Creative Commons Attribution No Derivatives 1.0", False)
  , (LicenseId "CC-BY-ND-2.0", "Creative Commons Attribution No Derivatives 2.0", False)
  , (LicenseId "CC-BY-ND-2.5", "Creative Commons Attribution No Derivatives 2.5", False)
  , (LicenseId "CC-BY-ND-3.0", "Creative Commons Attribution No Derivatives 3.0", False)
  , (LicenseId "CC-BY-ND-4.0", "Creative Commons Attribution No Derivatives 4.0", False)
  , (LicenseId "CC-BY-SA-1.0", "Creative Commons Attribution Share Alike 1.0", False)
  , (LicenseId "CC-BY-SA-2.0", "Creative Commons Attribution Share Alike 2.0", False)
  , (LicenseId "CC-BY-SA-2.5", "Creative Commons Attribution Share Alike 2.5", False)
  , (LicenseId "CC-BY-SA-3.0", "Creative Commons Attribution Share Alike 3.0", False)
  , (LicenseId "CC-BY-SA-4.0", "Creative Commons Attribution Share Alike 4.0", False)
  , (LicenseId "CC0-1.0", "Creative Commons Zero v1.0 Universal", False)
  , (LicenseId "CDDL-1.0", "Common Development and Distribution License 1.0", True)
  , (LicenseId "CDDL-1.1", "Common Development and Distribution License 1.1", False)
  , (LicenseId "CECILL-1.0", "CeCILL Free Software License Agreement v1.0", False)
  , (LicenseId "CECILL-1.1", "CeCILL Free Software License Agreement v1.1", False)
  , (LicenseId "CECILL-2.0", "CeCILL Free Software License Agreement v2.0", False)
  , (LicenseId "CECILL-B", "CeCILL-B Free Software License Agreement", False)
  , (LicenseId "CECILL-C", "CeCILL-C Free Software License Agreement", False)
  , (LicenseId "CNRI-Python", "CNRI Python License", True)
  , (LicenseId "CNRI-Python-GPL-Compatible", "CNRI Python Open Source GPL Compatible License Agreement", False)
  , (LicenseId "CPAL-1.0", "Common Public Attribution License 1.0", True)
  , (LicenseId "CPL-1.0", "Common Public License 1.0", True)
  , (LicenseId "CPOL-1.02", "Code Project Open License 1.02", False)
  , (LicenseId "CUA-OPL-1.0", "CUA Office Public License v1.0", True)
  , (LicenseId "Caldera", "Caldera License", False)
  , (LicenseId "ClArtistic", "Clarified Artistic License", False)
  , (LicenseId "Condor-1.1", "Condor Public License v1.1", False)
  , (LicenseId "Crossword", "Crossword License", False)
  , (LicenseId "Cube", "Cube License", False)
  , (LicenseId "D-FSL-1.0", "Deutsche Freie Software Lizenz", False)
  , (LicenseId "DOC", "DOC License", False)
  , (LicenseId "DSDP", "DSDP License", False)
  , (LicenseId "Dotseqn", "Dotseqn License", False)
  , (LicenseId "ECL-1.0", "Educational Community License v1.0", True)
  , (LicenseId "ECL-2.0", "Educational Community License v2.0", True)
  , (LicenseId "EFL-1.0", "Eiffel Forum License v1.0", True)
  , (LicenseId "EFL-2.0", "Eiffel Forum License v2.0", True)
  , (LicenseId "EPL-1.0", "Eclipse Public License 1.0", True)
  , (LicenseId "EUDatagrid", "EU DataGrid Software License", True)
  , (LicenseId "EUPL-1.0", "European Union Public License 1.0", False)
  , (LicenseId "EUPL-1.1", "European Union Public License 1.1", True)
  , (LicenseId "Entessa", "Entessa Public License v1.0", True)
  , (LicenseId "ErlPL-1.1", "Erlang Public License v1.1", False)
  , (LicenseId "Eurosym", "Eurosym License", False)
  , (LicenseId "FSFUL", "FSF Unlimited License", False)
  , (LicenseId "FSFULLR", "FSF Unlimited License (with License Retention)", False)
  , (LicenseId "FTL", "Freetype Project License", False)
  , (LicenseId "Fair", "Fair License", True)
  , (LicenseId "Frameworx-1.0", "Frameworx Open License 1.0", True)
  , (LicenseId "FreeImage", "FreeImage Public License v1.0", False)
  , (LicenseId "GFDL-1.1", "GNU Free Documentation License v1.1", False)
  , (LicenseId "GFDL-1.2", "GNU Free Documentation License v1.2", False)
  , (LicenseId "GFDL-1.3", "GNU Free Documentation License v1.3", False)
  , (LicenseId "GL2PS", "GL2PS License", False)
  , (LicenseId "GPL-1.0", "GNU General Public License v1.0 only", False)
  , (LicenseId "GPL-2.0", "GNU General Public License v2.0 only", True)
  , (LicenseId "GPL-3.0", "GNU General Public License v3.0 only", True)
  , (LicenseId "Giftware", "Giftware License", False)
  , (LicenseId "Glide", "3dfx Glide License", False)
  , (LicenseId "Glulxe", "Glulxe License", False)
  , (LicenseId "HPND", "Historic Permission Notice and Disclaimer", True)
  , (LicenseId "HaskellReport", "Haskell Language Report License", False)
  , (LicenseId "IBM-pibs", "IBM PowerPC Initialization and Boot Software", False)
  , (LicenseId "ICU", "ICU License", False)
  , (LicenseId "IJG", "Independent JPEG Group License", False)
  , (LicenseId "IPA", "IPA Font License", True)
  , (LicenseId "IPL-1.0", "IBM Public License v1.0", True)
  , (LicenseId "ISC", "ISC License", True)
  , (LicenseId "ImageMagick", "ImageMagick License", False)
  , (LicenseId "Imlib2", "Imlib2 License", False)
  , (LicenseId "Intel", "Intel Open Source License", True)
  , (LicenseId "Intel-ACPI", "Intel ACPI Software License Agreement", False)
  , (LicenseId "JSON", "JSON License", False)
  , (LicenseId "JasPer-2.0", "JasPer License", False)
  , (LicenseId "LGPL-2.0", "GNU Library General Public License v2 only", True)
  , (LicenseId "LGPL-2.1", "GNU Lesser General Public License v2.1 only", True)
  , (LicenseId "LGPL-3.0", "GNU Lesser General Public License v3.0 only", True)
  , (LicenseId "LPL-1.0", "Lucent Public License Version 1.0", True)
  , (LicenseId "LPL-1.02", "Lucent Public License v1.02", True)
  , (LicenseId "LPPL-1.0", "LaTeX Project Public License v1.0", False)
  , (LicenseId "LPPL-1.1", "LaTeX Project Public License v1.1", False)
  , (LicenseId "LPPL-1.2", "LaTeX Project Public License v1.2", False)
  , (LicenseId "LPPL-1.3a", "LaTeX Project Public License 1.3a", False)
  , (LicenseId "LPPL-1.3c", "LaTeX Project Public License v1.3c", True)
  , (LicenseId "Latex2e", "Latex2e License", False)
  , (LicenseId "Leptonica", "Leptonica License", False)
  , (LicenseId "Libpng", "libpng License", False)
  , (LicenseId "License Identifier", "Full name of License", False)
  , (LicenseId "MIT", "MIT License", True)
  , (LicenseId "MIT-CMU", "CMU License", False)
  , (LicenseId "MIT-advertising", "Enlightenment License (e16)", False)
  , (LicenseId "MIT-enna", "enna License", False)
  , (LicenseId "MIT-feh", "feh License", False)
  , (LicenseId "MITNFA", "MIT +no-false-attribs license", False)
  , (LicenseId "MPL-1.0", "Mozilla Public License 1.0", True)
  , (LicenseId "MPL-1.1", "Mozilla Public License 1.1", True)
  , (LicenseId "MPL-2.0", "Mozilla Public License 2.0", True)
  , (LicenseId "MPL-2.0-no-copyleft-exception", "Mozilla Public License 2.0 (no copyleft exception)", True)
  , (LicenseId "MS-PL", "Microsoft Public License", True)
  , (LicenseId "MS-RL", "Microsoft Reciprocal License", True)
  , (LicenseId "MTLL", "Matrix Template Library License", False)
  , (LicenseId "MakeIndex", "MakeIndex License", False)
  , (LicenseId "MirOS", "MirOS Licence", True)
  , (LicenseId "Motosoto", "Motosoto License", True)
  , (LicenseId "Multics", "Multics License", True)
  , (LicenseId "Mup", "Mup License", False)
  , (LicenseId "NASA-1.3", "NASA Open Source Agreement 1.3", True)
  , (LicenseId "NBPL-1.0", "Net Boolean Public License v1", False)
  , (LicenseId "NCSA", "University of Illinois/NCSA Open Source License", True)
  , (LicenseId "NGPL", "Nethack General Public License", True)
  , (LicenseId "NLPL", "No Limit Public License", False)
  , (LicenseId "NOSL", "Netizen Open Source License", False)
  , (LicenseId "NPL-1.0", "Netscape Public License v1.0", False)
  , (LicenseId "NPL-1.1", "Netscape Public License v1.1", False)
  , (LicenseId "NPOSL-3.0", "Non-Profit Open Software License 3.0", True)
  , (LicenseId "NRL", "NRL License", False)
  , (LicenseId "NTP", "NTP License", True)
  , (LicenseId "Naumen", "Naumen Public License", True)
  , (LicenseId "NetCDF", "NetCDF license", False)
  , (LicenseId "Newsletr", "Newsletr License", False)
  , (LicenseId "Nokia", "Nokia Open Source License", True)
  , (LicenseId "Noweb", "Noweb License", False)
  , (LicenseId "Nunit", "Nunit License", False)
  , (LicenseId "OCLC-2.0", "OCLC Research Public License 2.0", True)
  , (LicenseId "ODbL-1.0", "ODC Open Database License v1.0", False)
  , (LicenseId "OFL-1.0", "SIL Open Font License 1.0", False)
  , (LicenseId "OFL-1.1", "SIL Open Font License 1.1", True)
  , (LicenseId "OGTSL", "Open Group Test Suite License", True)
  , (LicenseId "OLDAP-1.1", "Open LDAP Public License v1.1", False)
  , (LicenseId "OLDAP-1.2", "Open LDAP Public License v1.2", False)
  , (LicenseId "OLDAP-1.3", "Open LDAP Public License v1.3", False)
  , (LicenseId "OLDAP-1.4", "Open LDAP Public License v1.4", False)
  , (LicenseId "OLDAP-2.0", "Open LDAP Public License v2.0 (or possibly 2.0A and 2.0B)", False)
  , (LicenseId "OLDAP-2.0.1", "Open LDAP Public License v2.0.1", False)
  , (LicenseId "OLDAP-2.1", "Open LDAP Public License v2.1", False)
  , (LicenseId "OLDAP-2.2", "Open LDAP Public License v2.2", False)
  , (LicenseId "OLDAP-2.2.1", "Open LDAP Public License v2.2.1", False)
  , (LicenseId "OLDAP-2.2.2", "Open LDAP Public License  2.2.2", False)
  , (LicenseId "OLDAP-2.3", "Open LDAP Public License v2.3", False)
  , (LicenseId "OLDAP-2.4", "Open LDAP Public License v2.4", False)
  , (LicenseId "OLDAP-2.5", "Open LDAP Public License v2.5", False)
  , (LicenseId "OLDAP-2.6", "Open LDAP Public License v2.6", False)
  , (LicenseId "OLDAP-2.7", "Open LDAP Public License v2.7", False)
  , (LicenseId "OLDAP-2.8", "Open LDAP Public License v2.8", False)
  , (LicenseId "OML", "Open Market License", False)
  , (LicenseId "OPL-1.0", "Open Public License v1.0", False)
  , (LicenseId "OSL-1.0", "Open Software License 1.0", True)
  , (LicenseId "OSL-1.1", "Open Software License 1.1", False)
  , (LicenseId "OSL-2.0", "Open Software License 2.0", True)
  , (LicenseId "OSL-2.1", "Open Software License 2.1", True)
  , (LicenseId "OSL-3.0", "Open Software License 3.0", True)
  , (LicenseId "OpenSSL", "OpenSSL License", False)
  , (LicenseId "PDDL-1.0", "ODC Public Domain Dedication & License 1.0", False)
  , (LicenseId "PHP-3.0", "PHP License v3.0", True)
  , (LicenseId "PHP-3.01", "PHP License v3.01", False)
  , (LicenseId "Plexus", "Plexus Classworlds License", False)
  , (LicenseId "PostgreSQL", "PostgreSQL License", True)
  , (LicenseId "Python-2.0", "Python License 2.0", True)
  , (LicenseId "QPL-1.0", "Q Public License 1.0", True)
  , (LicenseId "Qhull", "Qhull License", False)
  , (LicenseId "RHeCos-1.1", "Red Hat eCos Public License v1.1", False)
  , (LicenseId "RPL-1.1", "Reciprocal Public License 1.1", True)
  , (LicenseId "RPL-1.5", "Reciprocal Public License 1.5", True)
  , (LicenseId "RPSL-1.0", "RealNetworks Public Source License v1.0", True)
  , (LicenseId "RSCPL", "Ricoh Source Code Public License", True)
  , (LicenseId "Rdisc", "Rdisc License", False)
  , (LicenseId "Ruby", "Ruby License", False)
  , (LicenseId "SAX-PD", "Sax Public Domain Notice", False)
  , (LicenseId "SCEA", "SCEA Shared Source License", False)
  , (LicenseId "SGI-B-1.0", "SGI Free Software License B v1.0", False)
  , (LicenseId "SGI-B-1.1", "SGI Free Software License B v1.1", False)
  , (LicenseId "SGI-B-2.0", "SGI Free Software License B v2.0", False)
  , (LicenseId "SISSL", "Sun Industry Standards Source License v1.1", True)
  , (LicenseId "SISSL-1.2", "Sun Industry Standards Source License v1.2", False)
  , (LicenseId "SMLNJ", "Standard ML of New Jersey License", False)
  , (LicenseId "SNIA", "SNIA Public License 1.1", False)
  , (LicenseId "SPL-1.0", "Sun Public License v1.0", True)
  , (LicenseId "SWL", "Scheme Widget Library (SWL) Software License Agreement", False)
  , (LicenseId "Saxpath", "Saxpath License", False)
  , (LicenseId "SimPL-2.0", "Simple Public License 2.0", True)
  , (LicenseId "Sleepycat", "Sleepycat License", True)
  , (LicenseId "SugarCRM-1.1.3", "SugarCRM Public License v1.1.3", False)
  , (LicenseId "TCL", "TCL/TK License", False)
  , (LicenseId "TMate", "TMate Open Source License", False)
  , (LicenseId "TORQUE-1.1", "TORQUE v2.5+ Software License v1.1", False)
  , (LicenseId "TOSL", "Trusster Open Source License", False)
  , (LicenseId "Unicode-TOU", "Unicode Terms of Use", False)
  , (LicenseId "Unlicense", "The Unlicense", False)
  , (LicenseId "VOSTROM", "VOSTROM Public License for Open Source", False)
  , (LicenseId "VSL-1.0", "Vovida Software License v1.0", True)
  , (LicenseId "Vim", "Vim License", False)
  , (LicenseId "W3C", "W3C Software Notice and License (2002-12-31)", True)
  , (LicenseId "W3C-19980720", "W3C Software Notice and License (1998-07-20)", False)
  , (LicenseId "WTFPL", "Do What The F*ck You Want To Public License", False)
  , (LicenseId "Watcom-1.0", "Sybase Open Watcom Public License 1.0", True)
  , (LicenseId "Wsuipa", "Wsuipa License", False)
  , (LicenseId "X11", "X11 License", False)
  , (LicenseId "XFree86-1.1", "XFree86 License 1.1", False)
  , (LicenseId "XSkat", "XSkat License", False)
  , (LicenseId "Xerox", "Xerox License", False)
  , (LicenseId "Xnet", "X.Net License", True)
  , (LicenseId "YPL-1.0", "Yahoo! Public License v1.0", False)
  , (LicenseId "YPL-1.1", "Yahoo! Public License v1.1", False)
  , (LicenseId "ZPL-1.1", "Zope Public License 1.1", False)
  , (LicenseId "ZPL-2.0", "Zope Public License 2.0", True)
  , (LicenseId "ZPL-2.1", "Zope Public License 2.1", False)
  , (LicenseId "Zed", "Zed License", False)
  , (LicenseId "Zend-2.0", "Zend License v2.0", False)
  , (LicenseId "Zimbra-1.3", "Zimbra Public License v1.3", False)
  , (LicenseId "Zimbra-1.4", "Zimbra Public License v1.4", False)
  , (LicenseId "Zlib", "zlib License", True)
  , (LicenseId "bzip2-1.0.5", "bzip2 and libbzip2 License v1.0.5", False)
  , (LicenseId "bzip2-1.0.6", "bzip2 and libbzip2 License v1.0.6", False)
  , (LicenseId "diffmark", "diffmark license", False)
  , (LicenseId "dvipdfm", "dvipdfm License", False)
  , (LicenseId "eGenix", "eGenix.com Public License 1.1.0", False)
  , (LicenseId "gSOAP-1.3b", "gSOAP Public License v1.3b", False)
  , (LicenseId "gnuplot", "gnuplot License", False)
  , (LicenseId "iMatix", "iMatix Standard Function Library Agreement", False)
  , (LicenseId "libtiff", "libtiff License", False)
  , (LicenseId "mpich2", "mpich2 License", False)
  , (LicenseId "psfrag", "psfrag License", False)
  , (LicenseId "psutils", "psutils License", False)
  , (LicenseId "xinetd", "xinetd License", False)
  , (LicenseId "xpp", "XPP License", False)
  , (LicenseId "zlib-acknowledgement", "zlib/libpng License with Acknowledgement", False)
  ]