Add SPDX List v3.16 to LicenseListVersion and the file format changelog (#8135)
[cabal.git] / templates / SPDX.LicenseId.template.hs
blob8185cc6d0ee3a6815c30c066767103fe6ba79e43
1 {-# LANGUAGE DeriveDataTypeable #-}
2 module Distribution.SPDX.LicenseId (
3 LicenseId (..),
4 licenseId,
5 licenseName,
6 licenseIsOsiApproved,
7 licenseIsFsfLibre,
8 mkLicenseId,
9 licenseIdList,
10 -- * Helpers
11 licenseIdMigrationMessage,
12 ) where
14 import Distribution.Compat.Prelude
15 import Prelude ()
17 import Distribution.Compat.Lens (set)
18 import Distribution.Pretty
19 import Distribution.Parsec
20 import Distribution.Utils.Generic (isAsciiAlphaNum)
21 import Distribution.Utils.Structured (Structured (..), nominalStructure, typeVersion)
22 import Distribution.SPDX.LicenseListVersion
24 import qualified Data.Binary.Get as Binary
25 import qualified Data.Binary.Put as Binary
26 import qualified Data.Map.Strict as Map
27 import qualified Distribution.Compat.CharParsing as P
28 import qualified Text.PrettyPrint as Disp
30 -------------------------------------------------------------------------------
31 -- LicenseId
32 -------------------------------------------------------------------------------
34 -- | SPDX License identifiers list v3.16
35 data LicenseId
36 {{ licenseIds }}
37 deriving (Eq, Ord, Enum, Bounded, Show, Read, Typeable, Data)
39 instance Binary LicenseId where
40 -- Word16 is encoded in big endianess
41 -- https://github.com/kolmodin/binary/blob/master/src/Data/Binary/Class.hs#L220-LL227
42 put = Binary.putWord16be . fromIntegral . fromEnum
43 get = do
44 i <- Binary.getWord16be
45 if i > fromIntegral (fromEnum (maxBound :: LicenseId))
46 then fail "Too large LicenseId tag"
47 else return (toEnum (fromIntegral i))
49 -- note: remember to bump version each time the definition changes
50 instance Structured LicenseId where
51 structure p = set typeVersion 306 $ nominalStructure p
53 instance Pretty LicenseId where
54 pretty = Disp.text . licenseId
56 -- |
57 -- >>> eitherParsec "BSD-3-Clause" :: Either String LicenseId
58 -- Right BSD_3_Clause
60 -- >>> eitherParsec "BSD3" :: Either String LicenseId
61 -- Left "...Unknown SPDX license identifier: 'BSD3' Do you mean BSD-3-Clause?"
63 instance Parsec LicenseId where
64 parsec = do
65 n <- some $ P.satisfy $ \c -> isAsciiAlphaNum c || c == '-' || c == '.'
66 v <- askCabalSpecVersion
67 maybe (fail $ "Unknown SPDX license identifier: '" ++ n ++ "' " ++ licenseIdMigrationMessage n) return $
68 mkLicenseId (cabalSpecVersionToSPDXListVersion v) n
70 instance NFData LicenseId where
71 rnf l = l `seq` ()
73 -- | Help message for migrating from non-SPDX license identifiers.
75 -- Old 'License' is almost SPDX, except for 'BSD2', 'BSD3'. This function
76 -- suggests SPDX variant:
78 -- >>> licenseIdMigrationMessage "BSD3"
79 -- "Do you mean BSD-3-Clause?"
81 -- Also 'OtherLicense', 'AllRightsReserved', and 'PublicDomain' aren't
82 -- valid SPDX identifiers
84 -- >>> traverse_ (print . licenseIdMigrationMessage) [ "OtherLicense", "AllRightsReserved", "PublicDomain" ]
85 -- "SPDX license list contains plenty of licenses. See https://spdx.org/licenses/. Also they can be combined into complex expressions with AND and OR."
86 -- "You can use NONE as a value of license field."
87 -- "Public Domain is a complex matter. See https://wiki.spdx.org/view/Legal_Team/Decisions/Dealing_with_Public_Domain_within_SPDX_Files. Consider using a proper license."
89 -- SPDX License list version 3.0 introduced "-only" and "-or-later" variants for GNU family of licenses.
90 -- See <https://spdx.org/news/news/2018/01/license-list-30-released>
91 -- >>> licenseIdMigrationMessage "GPL-2.0"
92 -- "SPDX license list 3.0 deprecated suffixless variants of GNU family of licenses. Use GPL-2.0-only or GPL-2.0-or-later."
94 -- For other common licenses their old license format coincides with the SPDX identifiers:
96 -- >>> traverse eitherParsec ["GPL-2.0-only", "GPL-3.0-only", "LGPL-2.1-only", "MIT", "ISC", "MPL-2.0", "Apache-2.0"] :: Either String [LicenseId]
97 -- Right [GPL_2_0_only,GPL_3_0_only,LGPL_2_1_only,MIT,ISC,MPL_2_0,Apache_2_0]
99 licenseIdMigrationMessage :: String -> String
100 licenseIdMigrationMessage = go where
101 go l | gnuVariant l = "SPDX license list 3.0 deprecated suffixless variants of GNU family of licenses. Use " ++ l ++ "-only or " ++ l ++ "-or-later."
102 go "BSD3" = "Do you mean BSD-3-Clause?"
103 go "BSD2" = "Do you mean BSD-2-Clause?"
104 go "AllRightsReserved" = "You can use NONE as a value of license field."
105 go "OtherLicense" = "SPDX license list contains plenty of licenses. See https://spdx.org/licenses/. Also they can be combined into complex expressions with AND and OR."
106 go "PublicDomain" = "Public Domain is a complex matter. See https://wiki.spdx.org/view/Legal_Team/Decisions/Dealing_with_Public_Domain_within_SPDX_Files. Consider using a proper license."
108 -- otherwise, we don't know
109 go _ = ""
111 gnuVariant = flip elem ["GPL-2.0", "GPL-3.0", "LGPL-2.1", "LGPL-3.0", "AGPL-3.0" ]
113 -------------------------------------------------------------------------------
114 -- License Data
115 -------------------------------------------------------------------------------
117 -- | License SPDX identifier, e.g. @"BSD-3-Clause"@.
118 licenseId :: LicenseId -> String
119 {% for l in licenses %}
120 licenseId {{l.constructor}} = {{l.id}}
121 {% endfor %}
123 -- | License name, e.g. @"GNU General Public License v2.0 only"@
124 licenseName :: LicenseId -> String
125 {% for l in licenses %}
126 licenseName {{l.constructor}} = {{l.name}}
127 {% endfor %}
129 -- | Whether the license is approved by Open Source Initiative (OSI).
131 -- See <https://opensource.org/licenses/alphabetical>.
132 licenseIsOsiApproved :: LicenseId -> Bool
133 {% for l in licenses %}
134 {% if l.isOsiApproved %}
135 licenseIsOsiApproved {{l.constructor}} = True
136 {% endif %}
137 {% endfor %}
138 licenseIsOsiApproved _ = False
140 -- | Whether the license is considered libre by Free Software Foundation (FSF).
142 -- See <https://www.gnu.org/licenses/license-list.en.html>
144 -- @since 3.4.0.0
146 licenseIsFsfLibre :: LicenseId -> Bool
147 {% for l in licenses %}
148 {% if l.isFsfLibre %}
149 licenseIsFsfLibre {{l.constructor}} = True
150 {% endif %}
151 {% endfor %}
152 licenseIsFsfLibre _ = False
154 -------------------------------------------------------------------------------
155 -- Creation
156 -------------------------------------------------------------------------------
158 licenseIdList :: LicenseListVersion -> [LicenseId]
159 licenseIdList LicenseListVersion_3_0 =
160 {{licenseList_perv.v_3_0}}
161 ++ bulkOfLicenses
162 licenseIdList LicenseListVersion_3_2 =
163 {{licenseList_perv.v_3_2}}
164 ++ bulkOfLicenses
165 licenseIdList LicenseListVersion_3_6 =
166 {{licenseList_perv.v_3_6}}
167 ++ bulkOfLicenses
168 licenseIdList LicenseListVersion_3_9 =
169 {{licenseList_perv.v_3_9}}
170 ++ bulkOfLicenses
171 licenseIdList LicenseListVersion_3_10 =
172 {{licenseList_perv.v_3_10}}
173 ++ bulkOfLicenses
174 licenseIdList LicenseListVersion_3_16 =
175 {{licenseList_perv.v_3_16}}
176 ++ bulkOfLicenses
178 -- | Create a 'LicenseId' from a 'String'.
179 mkLicenseId :: LicenseListVersion -> String -> Maybe LicenseId
180 mkLicenseId LicenseListVersion_3_0 s = Map.lookup s stringLookup_3_0
181 mkLicenseId LicenseListVersion_3_2 s = Map.lookup s stringLookup_3_2
182 mkLicenseId LicenseListVersion_3_6 s = Map.lookup s stringLookup_3_6
183 mkLicenseId LicenseListVersion_3_9 s = Map.lookup s stringLookup_3_9
184 mkLicenseId LicenseListVersion_3_10 s = Map.lookup s stringLookup_3_10
185 mkLicenseId LicenseListVersion_3_16 s = Map.lookup s stringLookup_3_16
187 stringLookup_3_0 :: Map String LicenseId
188 stringLookup_3_0 = Map.fromList $ map (\i -> (licenseId i, i)) $
189 licenseIdList LicenseListVersion_3_0
191 stringLookup_3_2 :: Map String LicenseId
192 stringLookup_3_2 = Map.fromList $ map (\i -> (licenseId i, i)) $
193 licenseIdList LicenseListVersion_3_2
195 stringLookup_3_6 :: Map String LicenseId
196 stringLookup_3_6 = Map.fromList $ map (\i -> (licenseId i, i)) $
197 licenseIdList LicenseListVersion_3_6
199 stringLookup_3_9 :: Map String LicenseId
200 stringLookup_3_9 = Map.fromList $ map (\i -> (licenseId i, i)) $
201 licenseIdList LicenseListVersion_3_9
203 stringLookup_3_10 :: Map String LicenseId
204 stringLookup_3_10 = Map.fromList $ map (\i -> (licenseId i, i)) $
205 licenseIdList LicenseListVersion_3_10
207 stringLookup_3_16 :: Map String LicenseId
208 stringLookup_3_16 = Map.fromList $ map (\i -> (licenseId i, i)) $
209 licenseIdList LicenseListVersion_3_16
211 -- | Licenses in all SPDX License lists
212 bulkOfLicenses :: [LicenseId]
213 bulkOfLicenses =
214 {{licenseList_all}}