Fix a test.
[cabal.git] / boot / SPDX.LicenseExceptionId.template.hs
blob978cd497c825da09f13e04462d2e8d8fa5db658e
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE DeriveGeneric #-}
3 module Distribution.SPDX.LicenseExceptionId (
4 LicenseExceptionId (..),
5 licenseExceptionId,
6 licenseExceptionName,
7 mkLicenseExceptionId,
8 licenseExceptionIdList,
9 ) where
11 import Distribution.Compat.Prelude
12 import Prelude ()
14 import Distribution.Pretty
15 import Distribution.Parsec.Class
16 import Distribution.Utils.Generic (isAsciiAlphaNum)
17 import Distribution.SPDX.LicenseListVersion
19 import qualified Data.Map.Strict as Map
20 import qualified Distribution.Compat.CharParsing as P
21 import qualified Text.PrettyPrint as Disp
23 -------------------------------------------------------------------------------
24 -- LicenseExceptionId
25 -------------------------------------------------------------------------------
27 -- | SPDX License identifier
28 data LicenseExceptionId
29 {{{ licenseIds }}}
30 deriving (Eq, Ord, Enum, Bounded, Show, Read, Typeable, Data, Generic)
32 instance Binary LicenseExceptionId
34 instance Pretty LicenseExceptionId where
35 pretty = Disp.text . licenseExceptionId
37 instance Parsec LicenseExceptionId where
38 parsec = do
39 n <- some $ P.satisfy $ \c -> isAsciiAlphaNum c || c == '-' || c == '.'
40 v <- askCabalSpecVersion
41 maybe (fail $ "Unknown SPDX license exception identifier: " ++ n) return $
42 mkLicenseExceptionId (cabalSpecVersionToSPDXListVersion v) n
44 instance NFData LicenseExceptionId where
45 rnf l = l `seq` ()
47 -------------------------------------------------------------------------------
48 -- License Data
49 -------------------------------------------------------------------------------
51 -- | License SPDX identifier, e.g. @"BSD-3-Clause"@.
52 licenseExceptionId :: LicenseExceptionId -> String
53 {{#licenses}}
54 licenseExceptionId {{licenseCon}} = {{{licenseId}}}
55 {{/licenses}}
57 -- | License name, e.g. @"GNU General Public License v2.0 only"@
58 licenseExceptionName :: LicenseExceptionId -> String
59 {{#licenses}}
60 licenseExceptionName {{licenseCon}} = {{{licenseName}}}
61 {{/licenses}}
63 -------------------------------------------------------------------------------
64 -- Creation
65 -------------------------------------------------------------------------------
67 licenseExceptionIdList :: LicenseListVersion -> [LicenseExceptionId]
68 licenseExceptionIdList LicenseListVersion_3_0 =
69 {{{licenseList_3_0}}}
70 ++ bulkOfLicenses
71 licenseExceptionIdList LicenseListVersion_3_2 =
72 {{{licenseList_3_2}}}
73 ++ bulkOfLicenses
75 -- | Create a 'LicenseExceptionId' from a 'String'.
76 mkLicenseExceptionId :: LicenseListVersion -> String -> Maybe LicenseExceptionId
77 mkLicenseExceptionId LicenseListVersion_3_0 s = Map.lookup s stringLookup_3_0
78 mkLicenseExceptionId LicenseListVersion_3_2 s = Map.lookup s stringLookup_3_2
80 stringLookup_3_0 :: Map String LicenseExceptionId
81 stringLookup_3_0 = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $
82 licenseExceptionIdList LicenseListVersion_3_0
84 stringLookup_3_2 :: Map String LicenseExceptionId
85 stringLookup_3_2 = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $
86 licenseExceptionIdList LicenseListVersion_3_2
88 -- | License exceptions in all SPDX License lists
89 bulkOfLicenses :: [LicenseExceptionId]
90 bulkOfLicenses =
91 {{{licenseList_all}}}