CI: mergify should label automatic backports as such (#8516)
[cabal.git] / templates / SPDX.LicenseExceptionId.template.hs
blobd18641c3768fa87be312efba782d0dbbf45a9b2e
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.Compat.Lens (set)
15 import Distribution.Pretty
16 import Distribution.Parsec
17 import Distribution.Utils.Generic (isAsciiAlphaNum)
18 import Distribution.Utils.Structured (Structured (..), nominalStructure, typeVersion)
19 import Distribution.SPDX.LicenseListVersion
21 import qualified Data.Binary.Get as Binary
22 import qualified Data.Binary.Put as Binary
23 import qualified Data.Map.Strict as Map
24 import qualified Distribution.Compat.CharParsing as P
25 import qualified Text.PrettyPrint as Disp
27 -------------------------------------------------------------------------------
28 -- LicenseExceptionId
29 -------------------------------------------------------------------------------
31 -- | SPDX License Exceptions identifiers list v3.16
32 data LicenseExceptionId
33 {{ licenseIds }}
34 deriving (Eq, Ord, Enum, Bounded, Show, Read, Typeable, Data, Generic)
36 instance Binary LicenseExceptionId where
37 put = Binary.putWord8 . fromIntegral . fromEnum
38 get = do
39 i <- Binary.getWord8
40 if i > fromIntegral (fromEnum (maxBound :: LicenseExceptionId))
41 then fail "Too large LicenseExceptionId tag"
42 else return (toEnum (fromIntegral i))
44 -- note: remember to bump version each time the definition changes
45 instance Structured LicenseExceptionId where
46 structure p = set typeVersion 306 $ nominalStructure p
48 instance Pretty LicenseExceptionId where
49 pretty = Disp.text . licenseExceptionId
51 instance Parsec LicenseExceptionId where
52 parsec = do
53 n <- some $ P.satisfy $ \c -> isAsciiAlphaNum c || c == '-' || c == '.'
54 v <- askCabalSpecVersion
55 maybe (fail $ "Unknown SPDX license exception identifier: " ++ n) return $
56 mkLicenseExceptionId (cabalSpecVersionToSPDXListVersion v) n
58 instance NFData LicenseExceptionId where
59 rnf l = l `seq` ()
61 -------------------------------------------------------------------------------
62 -- License Data
63 -------------------------------------------------------------------------------
65 -- | License SPDX identifier, e.g. @"BSD-3-Clause"@.
66 licenseExceptionId :: LicenseExceptionId -> String
67 {% for l in licenses %}
68 licenseExceptionId {{l.constructor}} = {{l.id}}
69 {% endfor %}
71 -- | License name, e.g. @"GNU General Public License v2.0 only"@
72 licenseExceptionName :: LicenseExceptionId -> String
73 {% for l in licenses %}
74 licenseExceptionName {{l.constructor}} = {{l.name}}
75 {% endfor %}
77 -------------------------------------------------------------------------------
78 -- Creation
79 -------------------------------------------------------------------------------
81 licenseExceptionIdList :: LicenseListVersion -> [LicenseExceptionId]
82 licenseExceptionIdList LicenseListVersion_3_0 =
83 {{licenseList_perv.v_3_0}}
84 ++ bulkOfLicenses
85 licenseExceptionIdList LicenseListVersion_3_2 =
86 {{licenseList_perv.v_3_2}}
87 ++ bulkOfLicenses
88 licenseExceptionIdList LicenseListVersion_3_6 =
89 {{licenseList_perv.v_3_6}}
90 ++ bulkOfLicenses
91 licenseExceptionIdList LicenseListVersion_3_9 =
92 {{licenseList_perv.v_3_9}}
93 ++ bulkOfLicenses
94 licenseExceptionIdList LicenseListVersion_3_10 =
95 {{licenseList_perv.v_3_10}}
96 ++ bulkOfLicenses
97 licenseExceptionIdList LicenseListVersion_3_16 =
98 {{licenseList_perv.v_3_16}}
99 ++ bulkOfLicenses
101 -- | Create a 'LicenseExceptionId' from a 'String'.
102 mkLicenseExceptionId :: LicenseListVersion -> String -> Maybe LicenseExceptionId
103 mkLicenseExceptionId LicenseListVersion_3_0 s = Map.lookup s stringLookup_3_0
104 mkLicenseExceptionId LicenseListVersion_3_2 s = Map.lookup s stringLookup_3_2
105 mkLicenseExceptionId LicenseListVersion_3_6 s = Map.lookup s stringLookup_3_6
106 mkLicenseExceptionId LicenseListVersion_3_9 s = Map.lookup s stringLookup_3_9
107 mkLicenseExceptionId LicenseListVersion_3_10 s = Map.lookup s stringLookup_3_10
108 mkLicenseExceptionId LicenseListVersion_3_16 s = Map.lookup s stringLookup_3_16
110 stringLookup_3_0 :: Map String LicenseExceptionId
111 stringLookup_3_0 = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $
112 licenseExceptionIdList LicenseListVersion_3_0
114 stringLookup_3_2 :: Map String LicenseExceptionId
115 stringLookup_3_2 = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $
116 licenseExceptionIdList LicenseListVersion_3_2
118 stringLookup_3_6 :: Map String LicenseExceptionId
119 stringLookup_3_6 = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $
120 licenseExceptionIdList LicenseListVersion_3_6
122 stringLookup_3_9 :: Map String LicenseExceptionId
123 stringLookup_3_9 = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $
124 licenseExceptionIdList LicenseListVersion_3_9
126 stringLookup_3_10 :: Map String LicenseExceptionId
127 stringLookup_3_10 = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $
128 licenseExceptionIdList LicenseListVersion_3_10
130 stringLookup_3_16 :: Map String LicenseExceptionId
131 stringLookup_3_16 = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $
132 licenseExceptionIdList LicenseListVersion_3_16
134 -- | License exceptions in all SPDX License lists
135 bulkOfLicenses :: [LicenseExceptionId]
136 bulkOfLicenses =
137 {{licenseList_all}}