regenerate bootstrap files without arch-native
[cabal.git] / cabal-dev-scripts / src / GenSPDX.hs
blobadb3276a1bd14a43f1f6de008e328421378e2d1f
1 {-# LANGUAGE DeriveGeneric #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 module Main (main) where
5 import Control.Lens (imap)
6 import Data.Aeson (FromJSON (..), eitherDecode, withObject, (.!=), (.:), (.:?))
7 import Data.List (sortOn)
8 import Data.Text (Text)
9 import Data.Traversable (for)
11 import qualified Data.ByteString.Lazy as LBS
12 import qualified Data.Set as Set
13 import qualified Data.Text as T
14 import qualified Options.Applicative as O
15 import qualified Zinza as Z
17 import GenUtils
19 data Opts = Opts FilePath (PerV FilePath) FilePath
21 main :: IO ()
22 main = generate =<< O.execParser opts where
23 opts = O.info (O.helper <*> parser) $ mconcat
24 [ O.fullDesc
25 , O.progDesc "Generate SPDX LicenseId module"
28 parser :: O.Parser Opts
29 parser = Opts <$> template <*> licensesAll <*> output
31 licensesAll = PerV
32 <$> licenses "3.0"
33 <*> licenses "3.2"
34 <*> licenses "3.6"
35 <*> licenses "3.9"
36 <*> licenses "3.10"
37 <*> licenses "3.16"
38 <*> licenses "3.23"
40 template = O.strArgument $ mconcat
41 [ O.metavar "SPDX.LicenseId.template.hs"
42 , O.help "Module template file"
45 licenses ver = O.strArgument $ mconcat
46 [ O.metavar $ "licenses-" ++ ver ++ ".json"
47 , O.help "Licenses JSON. https://github.com/spdx/license-list-data"
50 output = O.strArgument $ mconcat
51 [ O.metavar "Output.hs"
52 , O.help "Output file"
55 generate :: Opts -> IO ()
56 generate (Opts tmplFile fns out) = do
57 lss <- for fns $ \fn -> either fail pure . eitherDecode =<< LBS.readFile fn
58 template <- Z.parseAndCompileTemplateIO tmplFile
59 output <- generate' lss template
60 writeFile out (header <> "\n" <> output)
61 putStrLn $ "Generated file " ++ out
63 generate'
64 :: PerV LicenseList
65 -> (Input -> IO String)
66 -> IO String
67 generate' lss template = template $ Input
68 { inputLicenseIds = licenseIds
69 , inputLicenses = licenseValues
70 , inputLicenseList_all = mkLicenseList (== allVers)
71 , inputLicenseList_perv = tabulate $ \ver -> mkLicenseList
72 (\vers -> vers /= allVers && Set.member ver vers)
74 where
75 constructorNames :: [(Text, License, Set.Set SPDXLicenseListVersion)]
76 constructorNames
77 = map (\(l, tags) -> (toConstructorName $ licenseId l, l, tags))
78 $ combine licenseId $ \ver -> filterDeprecated $ unLL $ index ver lss
80 filterDeprecated = filter (not . licenseDeprecated)
82 licenseValues :: [InputLicense]
83 licenseValues = flip map constructorNames $ \(c, l, _) -> InputLicense
84 { ilConstructor = c
85 , ilId = textShow (licenseId l)
86 , ilName = textShow (licenseName l)
87 , ilIsOsiApproved = licenseOsiApproved l
88 , ilIsFsfLibre = licenseFsfLibre l
91 licenseIds :: Text
92 licenseIds = T.intercalate "\n" $ flip imap constructorNames $ \i (c, l, vers) ->
93 let pfx = if i == 0 then " = " else " | "
94 versInfo
95 | vers == allVers = ""
96 | otherwise = foldMap (\v -> ", " <> prettyVer v) vers
97 in pfx <> c <> " -- ^ @" <> licenseId l <> "@, " <> licenseName l <> versInfo
99 mkLicenseList :: (Set.Set SPDXLicenseListVersion -> Bool) -> Text
100 mkLicenseList p = mkList [ n | (n, _, vers) <- constructorNames, p vers ]
102 -------------------------------------------------------------------------------
103 -- JSON inputs
104 -------------------------------------------------------------------------------
106 data License = License
107 { licenseId :: !Text
108 , licenseName :: !Text
109 , licenseOsiApproved :: !Bool
110 , licenseFsfLibre :: !Bool
111 , licenseDeprecated :: !Bool
113 deriving (Show)
115 newtype LicenseList = LL { unLL :: [License] }
116 deriving (Show)
118 instance FromJSON License where
119 parseJSON = withObject "License" $ \obj -> License
120 <$> obj .: "licenseId"
121 <*> obj .: "name"
122 <*> obj .: "isOsiApproved"
123 <*> obj .:? "isFsfLibre" .!= False
124 <*> obj .: "isDeprecatedLicenseId"
126 instance FromJSON LicenseList where
127 parseJSON = withObject "License list" $ \obj ->
128 LL . sortOn (OrdT . T.toLower . licenseId)
129 <$> obj .: "licenses"