1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE DeriveGeneric #-}
3 module Distribution
.SPDX
.LicenseId
(
12 licenseIdMigrationMessage
,
15 import Distribution
.Compat
.Prelude
18 import Distribution
.Compat
.Lens
(set
)
19 import Distribution
.Pretty
20 import Distribution
.Parsec
21 import Distribution
.Utils
.Generic
(isAsciiAlphaNum
)
22 import Distribution
.Utils
.Structured
(Structured
(..), nominalStructure
, typeVersion
)
23 import Distribution
.SPDX
.LicenseListVersion
25 import qualified Data
.Binary
.Get
as Binary
26 import qualified Data
.Binary
.Put
as Binary
27 import qualified Data
.Map
.Strict
as Map
28 import qualified Distribution
.Compat
.CharParsing
as P
29 import qualified Text
.PrettyPrint
as Disp
31 -------------------------------------------------------------------------------
33 -------------------------------------------------------------------------------
35 -- | SPDX License identifier
38 deriving (Eq
, Ord
, Enum
, Bounded
, Show, Read, Typeable
, Data
, Generic
)
40 instance Binary LicenseId
where
41 -- Word16 is encoded in big endianess
42 -- https://github.com/kolmodin/binary/blob/master/src/Data/Binary/Class.hs#L220-LL227
43 put
= Binary
.putWord16be
. fromIntegral . fromEnum
45 i
<- Binary
.getWord16be
46 if i
> fromIntegral (fromEnum (maxBound :: LicenseId
))
47 then fail "Too large LicenseId tag"
48 else return (toEnum (fromIntegral i
))
50 -- note: remember to bump version each time the definition changes
51 instance Structured LicenseId
where
52 structure p
= set typeVersion
306 $ nominalStructure p
54 instance Pretty LicenseId
where
55 pretty
= Disp
.text
. licenseId
58 -- >>> eitherParsec "BSD-3-Clause" :: Either String LicenseId
61 -- >>> eitherParsec "BSD3" :: Either String LicenseId
62 -- Left "...Unknown SPDX license identifier: 'BSD3' Do you mean BSD-3-Clause?"
64 instance Parsec LicenseId
where
66 n
<- some
$ P
.satisfy
$ \c
-> isAsciiAlphaNum c || c
== '-' || c
== '.'
67 v
<- askCabalSpecVersion
68 maybe (fail $ "Unknown SPDX license identifier: '" ++ n
++ "' " ++ licenseIdMigrationMessage n
) return $
69 mkLicenseId
(cabalSpecVersionToSPDXListVersion v
) n
71 instance NFData LicenseId
where
74 -- | Help message for migrating from non-SPDX license identifiers.
76 -- Old 'License' is almost SPDX, except for 'BSD2', 'BSD3'. This function
77 -- suggests SPDX variant:
79 -- >>> licenseIdMigrationMessage "BSD3"
80 -- "Do you mean BSD-3-Clause?"
82 -- Also 'OtherLicense', 'AllRightsReserved', and 'PublicDomain' aren't
83 -- valid SPDX identifiers
85 -- >>> traverse_ (print . licenseIdMigrationMessage) [ "OtherLicense", "AllRightsReserved", "PublicDomain" ]
86 -- "SPDX license list contains plenty of licenses. See https://spdx.org/licenses/. Also they can be combined into complex expressions with AND and OR."
87 -- "You can use NONE as a value of license field."
88 -- "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."
90 -- SPDX License list version 3.0 introduced "-only" and "-or-later" variants for GNU family of licenses.
91 -- See <https://spdx.org/news/news/2018/01/license-list-30-released>
92 -- >>> licenseIdMigrationMessage "GPL-2.0"
93 -- "SPDX license list 3.0 deprecated suffixless variants of GNU family of licenses. Use GPL-2.0-only or GPL-2.0-or-later."
95 -- For other common licenses their old license format coincides with the SPDX identifiers:
97 -- >>> 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]
98 -- Right [GPL_2_0_only,GPL_3_0_only,LGPL_2_1_only,MIT,ISC,MPL_2_0,Apache_2_0]
100 licenseIdMigrationMessage
:: String -> String
101 licenseIdMigrationMessage
= go
where
102 go l | gnuVariant l
= "SPDX license list 3.0 deprecated suffixless variants of GNU family of licenses. Use " ++ l
++ "-only or " ++ l
++ "-or-later."
103 go
"BSD3" = "Do you mean BSD-3-Clause?"
104 go
"BSD2" = "Do you mean BSD-2-Clause?"
105 go
"AllRightsReserved" = "You can use NONE as a value of license field."
106 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."
107 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."
109 -- otherwise, we don't know
112 gnuVariant
= flip elem ["GPL-2.0", "GPL-3.0", "LGPL-2.1", "LGPL-3.0", "AGPL-3.0" ]
114 -------------------------------------------------------------------------------
116 -------------------------------------------------------------------------------
118 -- | License SPDX identifier, e.g. @"BSD-3-Clause"@.
119 licenseId
:: LicenseId
-> String
120 {% for l
in licenses
%}
121 licenseId
{{l
.constructor
}} = {{l
.id}}
124 -- | License name, e.g. @"GNU General Public License v2.0 only"@
125 licenseName
:: LicenseId
-> String
126 {% for l
in licenses
%}
127 licenseName
{{l
.constructor
}} = {{l
.name
}}
130 -- | Whether the license is approved by Open Source Initiative (OSI).
132 -- See <https://opensource.org/licenses/alphabetical>.
133 licenseIsOsiApproved
:: LicenseId
-> Bool
134 {% for l
in licenses
%}
135 {% if l
.isOsiApproved
%}
136 licenseIsOsiApproved
{{l
.constructor
}} = True
139 licenseIsOsiApproved _
= False
141 -- | Whether the license is considered libre by Free Software Foundation (FSF).
143 -- See <https://www.gnu.org/licenses/license-list.en.html>
147 licenseIsFsfLibre
:: LicenseId
-> Bool
148 {% for l
in licenses
%}
149 {% if l
.isFsfLibre
%}
150 licenseIsFsfLibre
{{l
.constructor
}} = True
153 licenseIsFsfLibre _
= False
155 -------------------------------------------------------------------------------
157 -------------------------------------------------------------------------------
159 licenseIdList
:: LicenseListVersion
-> [LicenseId
]
160 licenseIdList LicenseListVersion_3_0
=
161 {{licenseList_perv
.v_3_0
}}
163 licenseIdList LicenseListVersion_3_2
=
164 {{licenseList_perv
.v_3_2
}}
166 licenseIdList LicenseListVersion_3_6
=
167 {{licenseList_perv
.v_3_6
}}
169 licenseIdList LicenseListVersion_3_9
=
170 {{licenseList_perv
.v_3_9
}}
172 licenseIdList LicenseListVersion_3_10
=
173 {{licenseList_perv
.v_3_9
}}
176 -- | Create a 'LicenseId' from a 'String'.
177 mkLicenseId
:: LicenseListVersion
-> String -> Maybe LicenseId
178 mkLicenseId LicenseListVersion_3_0 s
= Map
.lookup s stringLookup_3_0
179 mkLicenseId LicenseListVersion_3_2 s
= Map
.lookup s stringLookup_3_2
180 mkLicenseId LicenseListVersion_3_6 s
= Map
.lookup s stringLookup_3_6
181 mkLicenseId LicenseListVersion_3_9 s
= Map
.lookup s stringLookup_3_9
182 mkLicenseId LicenseListVersion_3_10 s
= Map
.lookup s stringLookup_3_10
184 stringLookup_3_0
:: Map
String LicenseId
185 stringLookup_3_0
= Map
.fromList
$ map (\i
-> (licenseId i
, i
)) $
186 licenseIdList LicenseListVersion_3_0
188 stringLookup_3_2
:: Map
String LicenseId
189 stringLookup_3_2
= Map
.fromList
$ map (\i
-> (licenseId i
, i
)) $
190 licenseIdList LicenseListVersion_3_2
192 stringLookup_3_6
:: Map
String LicenseId
193 stringLookup_3_6
= Map
.fromList
$ map (\i
-> (licenseId i
, i
)) $
194 licenseIdList LicenseListVersion_3_6
196 stringLookup_3_9
:: Map
String LicenseId
197 stringLookup_3_9
= Map
.fromList
$ map (\i
-> (licenseId i
, i
)) $
198 licenseIdList LicenseListVersion_3_9
200 stringLookup_3_10
:: Map
String LicenseId
201 stringLookup_3_10
= Map
.fromList
$ map (\i
-> (licenseId i
, i
)) $
202 licenseIdList LicenseListVersion_3_10
204 -- | Licenses in all SPDX License lists
205 bulkOfLicenses
:: [LicenseId
]