{-# 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.CharParsing as P
import qualified Text.PrettyPrint as Disp
data LicenseExceptionId
    = DS389_exception 
    | Autoconf_exception_2_0 
    | Autoconf_exception_3_0 
    | Bison_exception_2_2 
    | Bootloader_exception 
    | Classpath_exception_2_0 
    | CLISP_exception_2_0 
    | DigiRule_FOSS_exception 
    | ECos_exception_2_0 
    | Fawkes_Runtime_exception 
    | FLTK_exception 
    | Font_exception_2_0 
    | Freertos_exception_2_0 
    | GCC_exception_2_0 
    | GCC_exception_3_1 
    | Gnu_javamail_exception 
    | I2p_gpl_java_exception 
    | Libtool_exception 
    | Linux_syscall_note 
    | LZMA_exception 
    | Mif_exception 
    | Nokia_Qt_exception_1_1 
    | OCCT_exception_1_0 
    | Openvpn_openssl_exception 
    | Qwt_exception_1_0 
    | U_boot_exception_2_0 
    | WxWindows_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` ()
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 Bootloader_exception = "Bootloader-exception"
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 Linux_syscall_note = "Linux-syscall-note"
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"
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 Bootloader_exception = "Bootloader Distribution Exception"
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 Linux_syscall_note = "Linux Syscall Note"
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"
mkLicenseExceptionId :: String -> Maybe LicenseExceptionId
mkLicenseExceptionId s = Map.lookup s stringLookup
stringLookup :: Map String LicenseExceptionId
stringLookup = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $ [minBound .. maxBound]