Sed-replace CRLF files
[cabal.git] / templates / SPDX.LicenseExceptionId.template.hs
blob5881bec600b4f9179cc2e63e92353fc6bcebe569
1 {- FOURMOLU_DISABLE -}
2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE DeriveGeneric #-}
4 module Distribution.SPDX.LicenseExceptionId (
5 LicenseExceptionId (..),
6 licenseExceptionId,
7 licenseExceptionName,
8 mkLicenseExceptionId,
9 licenseExceptionIdList,
10 ) where
12 import Distribution.Compat.Prelude
13 import Prelude ()
15 import Distribution.Compat.Lens (set)
16 import Distribution.Pretty
17 import Distribution.Parsec
18 import Distribution.Utils.Generic (isAsciiAlphaNum)
19 import Distribution.Utils.Structured (Structured (..), nominalStructure, typeVersion)
20 import Distribution.SPDX.LicenseListVersion
22 import qualified Data.Binary.Get as Binary
23 import qualified Data.Binary.Put as Binary
24 import qualified Data.Map.Strict as Map
25 import qualified Distribution.Compat.CharParsing as P
26 import qualified Text.PrettyPrint as Disp
28 -------------------------------------------------------------------------------
29 -- LicenseExceptionId
30 -------------------------------------------------------------------------------
32 -- | SPDX License Exceptions identifiers list v3.16
33 data LicenseExceptionId
34 {{ licenseIds }}
35 deriving (Eq, Ord, Enum, Bounded, Show, Read, Typeable, Data, Generic)
37 instance Binary LicenseExceptionId where
38 put = Binary.putWord8 . fromIntegral . fromEnum
39 get = do
40 i <- Binary.getWord8
41 if i > fromIntegral (fromEnum (maxBound :: LicenseExceptionId))
42 then fail "Too large LicenseExceptionId tag"
43 else return (toEnum (fromIntegral i))
45 -- note: remember to bump version each time the definition changes
46 instance Structured LicenseExceptionId where
47 structure p = set typeVersion 306 $ nominalStructure p
49 instance Pretty LicenseExceptionId where
50 pretty = Disp.text . licenseExceptionId
52 instance Parsec LicenseExceptionId where
53 parsec = do
54 n <- some $ P.satisfy $ \c -> isAsciiAlphaNum c || c == '-' || c == '.'
55 v <- askCabalSpecVersion
56 maybe (fail $ "Unknown SPDX license exception identifier: " ++ n) return $
57 mkLicenseExceptionId (cabalSpecVersionToSPDXListVersion v) n
59 instance NFData LicenseExceptionId where
60 rnf l = l `seq` ()
62 -------------------------------------------------------------------------------
63 -- License Data
64 -------------------------------------------------------------------------------
66 -- | License SPDX identifier, e.g. @"BSD-3-Clause"@.
67 licenseExceptionId :: LicenseExceptionId -> String
68 {% for l in licenses %}
69 licenseExceptionId {{l.constructor}} = {{l.id}}
70 {% endfor %}
72 -- | License name, e.g. @"GNU General Public License v2.0 only"@
73 licenseExceptionName :: LicenseExceptionId -> String
74 {% for l in licenses %}
75 licenseExceptionName {{l.constructor}} = {{l.name}}
76 {% endfor %}
78 -------------------------------------------------------------------------------
79 -- Creation
80 -------------------------------------------------------------------------------
82 licenseExceptionIdList :: LicenseListVersion -> [LicenseExceptionId]
83 licenseExceptionIdList LicenseListVersion_3_0 =
84 {{licenseList_perv.v_3_0}}
85 ++ bulkOfLicenses
86 licenseExceptionIdList LicenseListVersion_3_2 =
87 {{licenseList_perv.v_3_2}}
88 ++ bulkOfLicenses
89 licenseExceptionIdList LicenseListVersion_3_6 =
90 {{licenseList_perv.v_3_6}}
91 ++ bulkOfLicenses
92 licenseExceptionIdList LicenseListVersion_3_9 =
93 {{licenseList_perv.v_3_9}}
94 ++ bulkOfLicenses
95 licenseExceptionIdList LicenseListVersion_3_10 =
96 {{licenseList_perv.v_3_10}}
97 ++ bulkOfLicenses
98 licenseExceptionIdList LicenseListVersion_3_16 =
99 {{licenseList_perv.v_3_16}}
100 ++ bulkOfLicenses
102 -- | Create a 'LicenseExceptionId' from a 'String'.
103 mkLicenseExceptionId :: LicenseListVersion -> String -> Maybe LicenseExceptionId
104 mkLicenseExceptionId LicenseListVersion_3_0 s = Map.lookup s stringLookup_3_0
105 mkLicenseExceptionId LicenseListVersion_3_2 s = Map.lookup s stringLookup_3_2
106 mkLicenseExceptionId LicenseListVersion_3_6 s = Map.lookup s stringLookup_3_6
107 mkLicenseExceptionId LicenseListVersion_3_9 s = Map.lookup s stringLookup_3_9
108 mkLicenseExceptionId LicenseListVersion_3_10 s = Map.lookup s stringLookup_3_10
109 mkLicenseExceptionId LicenseListVersion_3_16 s = Map.lookup s stringLookup_3_16
111 stringLookup_3_0 :: Map String LicenseExceptionId
112 stringLookup_3_0 = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $
113 licenseExceptionIdList LicenseListVersion_3_0
115 stringLookup_3_2 :: Map String LicenseExceptionId
116 stringLookup_3_2 = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $
117 licenseExceptionIdList LicenseListVersion_3_2
119 stringLookup_3_6 :: Map String LicenseExceptionId
120 stringLookup_3_6 = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $
121 licenseExceptionIdList LicenseListVersion_3_6
123 stringLookup_3_9 :: Map String LicenseExceptionId
124 stringLookup_3_9 = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $
125 licenseExceptionIdList LicenseListVersion_3_9
127 stringLookup_3_10 :: Map String LicenseExceptionId
128 stringLookup_3_10 = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $
129 licenseExceptionIdList LicenseListVersion_3_10
131 stringLookup_3_16 :: Map String LicenseExceptionId
132 stringLookup_3_16 = Map.fromList $ map (\i -> (licenseExceptionId i, i)) $
133 licenseExceptionIdList LicenseListVersion_3_16
135 -- | License exceptions in all SPDX License lists
136 bulkOfLicenses :: [LicenseExceptionId]
137 bulkOfLicenses =
138 {{licenseList_all}}