Add build dependencies to package pages

Closes #59
This commit is contained in:
Andrea Bedini 2023-05-23 16:52:04 +08:00
parent eb0e97d919
commit 1f899fe101
3 changed files with 78 additions and 64 deletions

View File

@ -12,11 +12,12 @@
module Distribution.Aeson where
import Data.Aeson
import Data.Aeson.Key (fromString)
import Data.Aeson.Key qualified as Key
import Data.Aeson.KeyMap qualified as KeyMap
import Data.Aeson.Types
import Data.Bifunctor (second)
import Data.List (foldl1')
import Data.String (fromString)
import Distribution.CabalSpecVersion
import Distribution.Compat.Lens hiding ((.=))
import Distribution.Compat.Newtype
@ -192,7 +193,7 @@ instance FieldGrammar ToJSON JSONFieldGrammar where
prefixedFields :: FieldName -> ALens' s [(String, String)] -> JSONFieldGrammar s [(String, String)]
prefixedFields _fnPfx l = JsonFG $ \_v _cs s ->
[fromString n .= v | (n, v) <- aview l s]
[Key.fromString n .= v | (n, v) <- aview l s]
knownField :: FieldName -> JSONFieldGrammar s ()
knownField _ = pure ()
@ -213,8 +214,8 @@ jsonField :: [Condition ConfVar] -> FieldName -> Value -> [Pair]
jsonField cs fn v
| v == emptyArray = mempty
| v == emptyString = mempty
| null cs = [fromString (fromUTF8BS fn) .= v]
| otherwise = [fromString (fromUTF8BS fn) .= v']
| null cs = [Key.fromString (fromUTF8BS fn) .= v]
| otherwise = [Key.fromString (fromUTF8BS fn) .= v']
where
v' = object ["if" .= toJSON (foldl1' CAnd cs), "then" .= v]
@ -223,12 +224,7 @@ jsonField cs fn v
emptyString = String ""
jsonGenericPackageDescription :: GenericPackageDescription -> Value
jsonGenericPackageDescription gpd = jsonGenericPackageDescription' v gpd
where
v = specVersion $ packageDescription gpd
jsonGenericPackageDescription' :: CabalSpecVersion -> GenericPackageDescription -> Value
jsonGenericPackageDescription' v gpd =
jsonGenericPackageDescription gpd =
object $
concat
[ jsonPackageDescription v (packageDescription gpd),
@ -241,6 +237,8 @@ jsonGenericPackageDescription' v gpd =
jsonCondTestSuites v (condTestSuites gpd),
jsonCondBenchmarks v (condBenchmarks gpd)
]
where
v = specVersion $ packageDescription gpd
jsonPackageDescription :: CabalSpecVersion -> PackageDescription -> [Pair]
jsonPackageDescription v pd =
@ -272,7 +270,7 @@ jsonGenPackageFlags v flags
where
flags' =
object
[ fromString (unFlagName name) .= object (jsonFieldGrammar v [] (flagFieldGrammar name) flag)
[ Key.fromString (unFlagName name) .= object (jsonFieldGrammar v [] (flagFieldGrammar name) flag)
| flag@(MkPackageFlag name _ _ _) <- flags
]
@ -288,11 +286,10 @@ jsonCondSubLibraries v libs
| otherwise = ["sub-libraries" .= libs']
where
libs' =
object
[ fromString (unUnqualComponentName n)
.= jsonCondTree2 v (libraryFieldGrammar $ LSubLibName n) condTree
| (n, condTree) <- libs
]
[ KeyMap.insert "name" (fromString $ unUnqualComponentName n) $
jsonCondTree2 v (libraryFieldGrammar $ LSubLibName n) condTree
| (n, condTree) <- libs
]
jsonCondForeignLibs :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)] -> [Pair]
jsonCondForeignLibs v flibs
@ -300,11 +297,10 @@ jsonCondForeignLibs v flibs
| otherwise = ["foreign-libraries" .= flibs']
where
flibs' =
object
[ fromString (unUnqualComponentName n)
.= jsonCondTree2 v (foreignLibFieldGrammar n) condTree
| (n, condTree) <- flibs
]
[ KeyMap.insert "name" (fromString $ unUnqualComponentName n) $
jsonCondTree2 v (foreignLibFieldGrammar n) condTree
| (n, condTree) <- flibs
]
jsonCondExecutables :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)] -> [Pair]
jsonCondExecutables v exes
@ -312,11 +308,10 @@ jsonCondExecutables v exes
| otherwise = ["executables" .= exes']
where
exes' =
object
[ fromString (unUnqualComponentName n)
.= jsonCondTree2 v (executableFieldGrammar n) condTree
| (n, condTree) <- exes
]
[ KeyMap.insert "name" (fromString $ unUnqualComponentName n) $
jsonCondTree2 v (executableFieldGrammar n) condTree
| (n, condTree) <- exes
]
jsonCondTestSuites :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)] -> [Pair]
jsonCondTestSuites v suites
@ -324,11 +319,10 @@ jsonCondTestSuites v suites
| otherwise = ["test-suites" .= suites']
where
suites' =
object
[ fromString (unUnqualComponentName n)
.= jsonCondTree2 v testSuiteFieldGrammar (fmap unvalidateTestSuite condTree)
| (n, condTree) <- suites
]
[ KeyMap.insert "name" (fromString $ unUnqualComponentName n) $
jsonCondTree2 v testSuiteFieldGrammar (fmap unvalidateTestSuite condTree)
| (n, condTree) <- suites
]
jsonCondBenchmarks :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)] -> [Pair]
jsonCondBenchmarks v suites
@ -336,13 +330,12 @@ jsonCondBenchmarks v suites
| otherwise = ["benchmarks" .= suites']
where
suites' =
object
[ fromString (unUnqualComponentName n)
.= jsonCondTree2 v benchmarkFieldGrammar (fmap unvalidateBenchmark condTree)
| (n, condTree) <- suites
]
[ KeyMap.insert "name" (fromString $ unUnqualComponentName n) $
jsonCondTree2 v benchmarkFieldGrammar (fmap unvalidateBenchmark condTree)
| (n, condTree) <- suites
]
jsonCondTree2 :: CabalSpecVersion -> JSONFieldGrammar' s -> CondTree ConfVar [Dependency] s -> Value
jsonCondTree2 :: CabalSpecVersion -> JSONFieldGrammar' s -> CondTree ConfVar [Dependency] s -> KeyMap.KeyMap Value
jsonCondTree2 v grammar = merge . go []
where
go cs (CondNode it _ ifs) =
@ -353,5 +346,5 @@ jsonCondTree2 v grammar = merge . go []
jsonIf cs (CondBranch c thenTree (Just elseTree)) =
go (c : cs) thenTree ++ go (CNot c : cs) elseTree
merge :: [Pair] -> Value
merge = Object . fmap toJSON . KeyMap.fromListWith (++) . map (second (: []))
merge :: [Pair] -> KeyMap.KeyMap Value
merge = fmap toJSON . KeyMap.fromListWith (<>) . map (second (: []))

View File

@ -143,18 +143,20 @@ makeAllPackageVersionsPage currentTime outputDir packageVersions =
& sortOn (Down . allPackageVersionsPageEntryTimestamp)
makePackageVersionPage :: FilePath -> PreparedPackageVersion -> Action ()
makePackageVersionPage outputDir PreparedPackageVersion {pkgId, pkgTimestamp, pkgVersionSource, pkgDesc, cabalFileRevisions, pkgVersionIsDeprecated} = do
traced ("webpages / package / " ++ prettyShow pkgId) $ do
IO.createDirectoryIfMissing True (outputDir </> "package" </> prettyShow pkgId)
TL.writeFile (outputDir </> "package" </> prettyShow pkgId </> "index.html") $
renderMustache packageVersionPageTemplate $
object
[ "pkgVersionSource" .= pkgVersionSource,
"cabalFileRevisions" .= map fst cabalFileRevisions,
"pkgDesc" .= jsonGenericPackageDescription pkgDesc,
"pkgTimestamp" .= pkgTimestamp,
"pkgVersionDeprecated" .= pkgVersionIsDeprecated
]
makePackageVersionPage
outputDir
PreparedPackageVersion {pkgId, pkgTimestamp, pkgVersionSource, pkgDesc, cabalFileRevisions, pkgVersionIsDeprecated} =
traced ("webpages / package / " ++ prettyShow pkgId) $ do
IO.createDirectoryIfMissing True (outputDir </> "package" </> prettyShow pkgId)
TL.writeFile (outputDir </> "package" </> prettyShow pkgId </> "index.html") $
renderMustache packageVersionPageTemplate $
object
[ "pkgVersionSource" .= pkgVersionSource,
"cabalFileRevisions" .= map fst cabalFileRevisions,
"pkgDesc" .= jsonGenericPackageDescription pkgDesc,
"pkgTimestamp" .= pkgTimestamp,
"pkgVersionDeprecated" .= pkgVersionIsDeprecated
]
indexPageTemplate :: Template
indexPageTemplate = $(compileMustacheDir "index" "templates")

View File

@ -4,18 +4,13 @@
<!-- Required meta tags -->
<meta charset="utf-8">
<meta name="viewport" content="width=device-width, initial-scale=1">
<!-- Bootstrap CSS -->
<link href="https://cdn.jsdelivr.net/npm/bootstrap@5.0.2/dist/css/bootstrap.min.css" rel="stylesheet" integrity="sha384-EVSTQN3/azprG1Anm3QDgpJLIm9Nao0Yz1ztcQTwFspd3yD65VohhpuuCOmLASjC" crossorigin="anonymous">
<title>
{{#pkgDesc}}
{{name}}-{{version}}
{{/pkgDesc}}
{{pkgDesc.name}}-{{pkgDesc.version}}
</title>
</head>
<body>
{{#pkgDesc}}
<div class="container px-4 py-5">
<ul class="nav">
<li class="nav-item">
@ -29,7 +24,7 @@
</li>
</ul>
<h1 class="py-5">
{{name}}-{{version}}
{{pkgDesc.name}}-{{pkgDesc.version}}
</h1>
<dl class="row class="px-4 py-5">
{{#pkgVersionDeprecated}}
@ -37,16 +32,15 @@
<dd></dd>
{{/pkgVersionDeprecated}}
<dt class="col-sm-3">Synopsis</dt>
<dd class="col-sm-9"><p>{{synopsis}}</p></dd>
<dd class="col-sm-9"><p>{{pkgDesc.synopsis}}</p></dd>
<dt class="col-sm-3">Description</dt>
<dd class="col-sm-9"><p>{{description}}</p></dd>
<dd class="col-sm-9"><p>{{pkgDesc.description}}</p></dd>
<dt class="col-sm-3">Author</dt>
<dd class="col-sm-9"><p>{{author}}</p></dd>
<dd class="col-sm-9"><p>{{pkgDesc.author}}</p></dd>
<dt class="col-sm-3">Maintainer</dt>
<dd class="col-sm-9"><p>{{maintainer}}</p></dd>
<dd class="col-sm-9"><p>{{pkgDesc.maintainer}}</p></dd>
<dt class="col-sm-3">License</dt>
<dd class="col-sm-9"><p>{{license}}</p></dd>
{{/pkgDesc}}
<dd class="col-sm-9"><p>{{pkgDesc.license}}</p></dd>
{{#pkgVersionSource}}
<dt class="col-sm-3">Source</dt>
<dd class="col-sm-9">
@ -66,6 +60,31 @@
<p>None</p>
{{/cabalFileRevisions}}
</dd>
{{#pkgDesc.library}}
<dt class="col-sm-3">Dependencies</dt>
<dd class="col-sm-9">{{#build-depends}}{{#.}}{{.}}<br>{{/.}}{{/build-depends}}</dd>
{{/pkgDesc.library}}
</dd>
{{#pkgDesc.sub-libraries}}
<dt class="col-sm-3">sub-library {{name}}</dt>
<dd class="col-sm-9">{{#build-depends}}{{#.}}{{.}}<br>{{/.}}{{/build-depends}}</dd>
{{/pkgDesc.sub-libraries}}
{{#pkgDesc.foreign-libraries}}
<dt class="col-sm-3">foreign-library {{name}}</dt>
<dd class="col-sm-9">{{#build-depends}}{{#.}}{{.}}<br>{{/.}}{{/build-depends}}</dd>
{{/pkgDesc.foreign-libraries}}
{{#pkgDesc.executables}}
<dt class="col-sm-3">executable {{name}}</dt>
<dd class="col-sm-9">{{#build-depends}}{{#.}}{{.}}<br>{{/.}}{{/build-depends}}</dd>
{{/pkgDesc.executables}}
{{#pkgDesc.test-suites}}
<dt class="col-sm-3">test-suite {{name}}</dt>
<dd class="col-sm-9">{{#build-depends}}{{#.}}{{.}}<br>{{/.}}{{/build-depends}}</dd>
{{/pkgDesc.test-suites}}
{{#pkgDesc.benchmarks}}
<dt class="col-sm-3">benchmark {{name}}</dt>
<dd class="col-sm-9">{{#build-depends}}{{#.}}{{.}}<br>{{/.}}{{/build-depends}}</dd>
{{/pkgDesc.benchmarks}}
</dl>
</div>
</body>