diff --git a/app/Distribution/Aeson.hs b/app/Distribution/Aeson.hs index 9e6c2bc..b6a65b7 100644 --- a/app/Distribution/Aeson.hs +++ b/app/Distribution/Aeson.hs @@ -3,8 +3,10 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE ImportQualifiedPost #-} {-# LANGUAGE InstanceSigs #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -Wno-orphans #-} @@ -12,11 +14,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.List.NonEmpty qualified as NE +import Data.Vector qualified as V import Distribution.CabalSpecVersion import Distribution.Compat.Lens hiding ((.=)) import Distribution.Compat.Newtype @@ -27,7 +30,6 @@ import Distribution.ModuleName hiding (fromString) import Distribution.PackageDescription import Distribution.PackageDescription.FieldGrammar import Distribution.Pretty -import Distribution.System import Distribution.Types.Version import Distribution.Types.VersionRange import Distribution.Utils.Generic (fromUTF8BS) @@ -35,112 +37,45 @@ import Distribution.Utils.Path import Distribution.Utils.ShortText qualified as ST import Language.Haskell.Extension -newtype ViaPretty a = ViaPretty a - -instance Pretty a => ToJSON (ViaPretty a) where - toJSON (ViaPretty a) = toJSON $ prettyShow a - -newtype ViaUnpack a = ViaUnpack a - -instance (ToJSON o, Newtype o n) => ToJSON (ViaUnpack n) where - toJSON (ViaUnpack n) = toJSON $ unpack n - -deriving via String instance ToJSON Token - -deriving via String instance ToJSON Token' - -deriving via String instance ToJSON FilePathNT - -deriving via String instance ToJSON CompatFilePath - -deriving via ViaUnpack CompatLicenseFile instance ToJSON CompatLicenseFile - -deriving via (ViaPretty VersionRange) instance ToJSON VersionRange - -deriving via ViaUnpack TestedWith instance ToJSON TestedWith - -deriving via (ViaPretty CompilerFlavor) instance ToJSON CompilerFlavor - -deriving via (ViaPretty SpecVersion) instance ToJSON SpecVersion - -deriving via (ViaPretty SpecLicense) instance ToJSON SpecLicense - -deriving via (ViaUnpack (List sep b a)) instance ToJSON a => ToJSON (List sep b a) - -deriving via (ViaPretty (SymbolicPath from to)) instance ToJSON (SymbolicPath from to) - -deriving via (ViaPretty BuildType) instance ToJSON BuildType - -deriving via (ViaPretty PackageName) instance ToJSON PackageName - -deriving via (ViaPretty Version) instance ToJSON Version - -instance ToJSON RepoType - -instance ToJSON KnownRepoType - -deriving via (ViaPretty Extension) instance ToJSON Extension - -deriving via (ViaPretty Language) instance ToJSON Language - -deriving via (ViaUnpack (MQuoted a)) instance ToJSON a => ToJSON (MQuoted a) - -deriving via (ViaPretty Dependency) instance ToJSON Dependency - -deriving via (ViaPretty BenchmarkType) instance ToJSON BenchmarkType - -deriving via (ViaPretty ForeignLibType) instance ToJSON ForeignLibType - -deriving via (ViaPretty TestType) instance ToJSON TestType - -deriving via (ViaPretty ExecutableScope) instance ToJSON ExecutableScope - -deriving via (ViaPretty ForeignLibOption) instance ToJSON ForeignLibOption - -deriving via (ViaPretty LibVersionInfo) instance ToJSON LibVersionInfo - -deriving via (ViaPretty ModuleName) instance ToJSON ModuleName - -deriving via (ViaPretty ModuleReexport) instance ToJSON ModuleReexport - -deriving via (ViaPretty Mixin) instance ToJSON Mixin - -deriving via (ViaPretty PkgconfigDependency) instance ToJSON PkgconfigDependency - -deriving via (ViaPretty ExeDependency) instance ToJSON ExeDependency - -deriving via (ViaPretty LegacyExeDependency) instance ToJSON LegacyExeDependency - -deriving via (ViaPretty LibraryVisibility) instance ToJSON LibraryVisibility - -deriving via (ViaPretty FlagName) instance ToJSON FlagName - -deriving via (ViaPretty Arch) instance ToJSON Arch - -deriving via (ViaPretty OS) instance ToJSON OS - -instance ToJSON ConfVar where - toJSON (OS os) = object ["os" .= os] - toJSON (Arch arch) = object ["arcg" .= arch] - toJSON (PackageFlag flag) = object ["os" .= flag] - toJSON (Impl compiler version) = object ["compiler" .= compiler, "version" .= version] - -instance ToJSON c => ToJSON (Condition c) where - toJSON (Var v) = toJSON v - toJSON (Lit b) = toJSON b - toJSON (CNot c) = object ["not" .= c] - toJSON (COr l r) = object ["or" .= [l, r]] - toJSON (CAnd l r) = object ["and" .= [l, r]] +-- Note: this JSONFieldGrammar is not quite general purpose. +-- +-- To help with the rendering of conditional dependencies, here we "push" +-- all the conditionals down. +-- So while the build-dependencies in a GenericPackageDescription could +-- be represented as: +-- +-- { +-- "build-depends": ["a", "b", "c"], +-- "conditionals": [{ +-- "if": {"os": "darwin"}, +-- "then": { +-- "build-depends": ["d"] +-- } +-- }] +-- } +-- +-- we decide to represent them as +-- +-- { +-- "build-depends": [ +-- "a", +-- "b", +-- "c", +-- { "if": "os(darwin)", "then": "d" } +-- ] +-- } +-- +-- Note: we also pretty-print the condition. newtype JSONFieldGrammar s a = JsonFG - { fieldGrammarJSON :: CabalSpecVersion -> [Condition ConfVar] -> s -> [Pair] + { runJSONFieldGrammar :: CabalSpecVersion -> [Condition ConfVar] -> s -> [Pair] } deriving (Functor) type JSONFieldGrammar' s = JSONFieldGrammar s s jsonFieldGrammar :: CabalSpecVersion -> [Condition ConfVar] -> JSONFieldGrammar s a -> s -> [Pair] -jsonFieldGrammar v cs fg = fieldGrammarJSON fg v cs +jsonFieldGrammar v cs fg = runJSONFieldGrammar fg v cs instance Applicative (JSONFieldGrammar s) where pure _ = JsonFG (\_ _ _ -> mempty) @@ -192,7 +127,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,10 +148,10 @@ 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] + v' = object ["if" .= showCondition (foldl1' cAnd cs), "then" .= v] -- Should be added to aeson emptyString :: Value @@ -232,7 +167,7 @@ jsonGenericPackageDescription' v gpd = object $ concat [ jsonPackageDescription v (packageDescription gpd), - jsonSetupBInfo v (setupBuildInfo (packageDescription gpd)), + jsonSetupBuildInfo v (setupBuildInfo (packageDescription gpd)), jsonGenPackageFlags v (genPackageFlags gpd), jsonCondLibrary v (condLibrary gpd), jsonCondSubLibraries v (condSubLibraries gpd), @@ -243,115 +178,191 @@ jsonGenericPackageDescription' v gpd = ] jsonPackageDescription :: CabalSpecVersion -> PackageDescription -> [Pair] -jsonPackageDescription v pd = +jsonPackageDescription v pd@PackageDescription {sourceRepos, setupBuildInfo} = jsonFieldGrammar v [] packageDescriptionFieldGrammar pd - ++ ["source-repos" .= jsonSourceRepos v (sourceRepos pd)] + <> jsonSourceRepos v sourceRepos + <> jsonSetupBuildInfo v setupBuildInfo -jsonSourceRepos :: CabalSpecVersion -> [SourceRepo] -> [Value] -jsonSourceRepos v = map (jsonSourceRepo v) +jsonSourceRepos :: CabalSpecVersion -> [SourceRepo] -> [Pair] +jsonSourceRepos v = + concatMap (\neRepos -> ["source-repository" .= NE.map (jsonSourceRepo v) neRepos]) . NE.nonEmpty jsonSourceRepo :: CabalSpecVersion -> SourceRepo -> Value -jsonSourceRepo v repo = - object (jsonFieldGrammar v [] (sourceRepoFieldGrammar kind) repo) - where - kind = repoKind repo - -jsonSetupBInfo :: CabalSpecVersion -> Maybe SetupBuildInfo -> [Pair] -jsonSetupBInfo _ Nothing = mempty -jsonSetupBInfo v (Just sbi) - | defaultSetupDepends sbi = mempty - | null vs = mempty - | otherwise = ["custom-setup" .= object vs] - where - vs = jsonFieldGrammar v [] (setupBInfoFieldGrammar False) sbi +jsonSourceRepo v repo@SourceRepo {repoKind} = + object $ jsonFieldGrammar v [] (sourceRepoFieldGrammar repoKind) repo + +jsonSetupBuildInfo :: CabalSpecVersion -> Maybe SetupBuildInfo -> [Pair] +jsonSetupBuildInfo v = + concatMap (\sbi -> ["custom-setup" .= jsonFieldGrammar v [] (setupBInfoFieldGrammar False) sbi]) jsonGenPackageFlags :: CabalSpecVersion -> [PackageFlag] -> [Pair] -jsonGenPackageFlags v flags - | null flags = mempty - | otherwise = ["flags" .= flags'] - where - flags' = - object - [ fromString (unFlagName name) .= object (jsonFieldGrammar v [] (flagFieldGrammar name) flag) - | flag@(MkPackageFlag name _ _ _) <- flags - ] +jsonGenPackageFlags v = + concatMap (\neFlags -> ["flags" .= object (NE.toList $ NE.map (jsonFlag v) neFlags)]) . NE.nonEmpty + +jsonFlag :: CabalSpecVersion -> PackageFlag -> Pair +jsonFlag v flag@(MkPackageFlag name _ _ _) = + Key.fromString (unFlagName name) .= object (jsonFieldGrammar v [] (flagFieldGrammar name) flag) jsonCondLibrary :: CabalSpecVersion -> Maybe (CondTree ConfVar [Dependency] Library) -> [Pair] -jsonCondLibrary _ Nothing = mempty -jsonCondLibrary v (Just condTree) = ["library" .= condTree'] - where - condTree' = jsonCondTree2 v (libraryFieldGrammar LMainLibName) condTree +jsonCondLibrary v = + concatMap (\condTree -> ["library" .= object (jsonCondTree v (libraryFieldGrammar LMainLibName) condTree)]) jsonCondSubLibraries :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)] -> [Pair] -jsonCondSubLibraries v libs - | null libs = mempty - | otherwise = ["sub-libraries" .= libs'] - where - libs' = - object - [ fromString (unUnqualComponentName n) - .= jsonCondTree2 v (libraryFieldGrammar $ LSubLibName n) condTree - | (n, condTree) <- libs - ] +jsonCondSubLibraries v = + concatMap (\neLibs -> ["sub-libraries" .= NE.map (jsonSubLibrary v) neLibs]) . NE.nonEmpty + +jsonSubLibrary :: CabalSpecVersion -> (UnqualComponentName, CondTree ConfVar [Dependency] Library) -> Value +jsonSubLibrary v (n, condTree) = + withName (unUnqualComponentName n) $ + jsonCondTree v (libraryFieldGrammar $ LSubLibName n) condTree jsonCondForeignLibs :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)] -> [Pair] -jsonCondForeignLibs v flibs - | null flibs = mempty - | otherwise = ["foreign-libraries" .= flibs'] - where - flibs' = - object - [ fromString (unUnqualComponentName n) - .= jsonCondTree2 v (foreignLibFieldGrammar n) condTree - | (n, condTree) <- flibs - ] +jsonCondForeignLibs v = + concatMap (\neFLibs -> ["foreign-libraries" .= NE.map (jsonForeignLibrary v) neFLibs]) . NE.nonEmpty + +jsonForeignLibrary :: CabalSpecVersion -> (UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib) -> Value +jsonForeignLibrary v (n, condTree) = + withName (unUnqualComponentName n) $ + jsonCondTree v (foreignLibFieldGrammar n) condTree jsonCondExecutables :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)] -> [Pair] -jsonCondExecutables v exes - | null exes = mempty - | otherwise = ["executables" .= exes'] - where - exes' = - object - [ fromString (unUnqualComponentName n) - .= jsonCondTree2 v (executableFieldGrammar n) condTree - | (n, condTree) <- exes - ] +jsonCondExecutables v = + concatMap (\neExes -> ["executables" .= NE.map (jsonCondExecutable v) neExes]) . NE.nonEmpty + +jsonCondExecutable :: CabalSpecVersion -> (UnqualComponentName, CondTree ConfVar [Dependency] Executable) -> Value +jsonCondExecutable v (n, condTree) = + withName (unUnqualComponentName n) $ + jsonCondTree v (executableFieldGrammar n) condTree jsonCondTestSuites :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)] -> [Pair] -jsonCondTestSuites v suites - | null suites = mempty - | otherwise = ["test-suites" .= suites'] - where - suites' = - object - [ fromString (unUnqualComponentName n) - .= jsonCondTree2 v testSuiteFieldGrammar (fmap unvalidateTestSuite condTree) - | (n, condTree) <- suites - ] +jsonCondTestSuites v = + concatMap (\neSuites -> ["test-suites" .= NE.map (jsonCondTestSuite v) neSuites]) . NE.nonEmpty + +jsonCondTestSuite :: CabalSpecVersion -> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite) -> Value +jsonCondTestSuite v (n, condTree) = + withName (unUnqualComponentName n) $ + jsonCondTree v testSuiteFieldGrammar (fmap unvalidateTestSuite condTree) jsonCondBenchmarks :: CabalSpecVersion -> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)] -> [Pair] -jsonCondBenchmarks v suites - | null suites = mempty - | otherwise = ["benchmarks" .= suites'] - where - suites' = - object - [ fromString (unUnqualComponentName n) - .= jsonCondTree2 v benchmarkFieldGrammar (fmap unvalidateBenchmark condTree) - | (n, condTree) <- suites - ] - -jsonCondTree2 :: CabalSpecVersion -> JSONFieldGrammar' s -> CondTree ConfVar [Dependency] s -> Value -jsonCondTree2 v grammar = merge . go [] +jsonCondBenchmarks v = + concatMap (\neSuites -> ["test-suites" .= NE.map (jsonCondBenchmark v) neSuites]) . NE.nonEmpty + +jsonCondBenchmark :: CabalSpecVersion -> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark) -> Value +jsonCondBenchmark v (n, condTree) = + withName (unUnqualComponentName n) $ + jsonCondTree v benchmarkFieldGrammar (fmap unvalidateBenchmark condTree) + +jsonCondTree :: forall s. CabalSpecVersion -> JSONFieldGrammar' s -> CondTree ConfVar [Dependency] s -> [Pair] +jsonCondTree v grammar = go [] where go cs (CondNode it _ ifs) = - jsonFieldGrammar v cs grammar it ++ concatMap (jsonIf cs) ifs + KeyMap.toList $ foldr merge (KeyMap.fromList $ jsonFieldGrammar v cs grammar it) $ concatMap (jsonIf cs) ifs + jsonIf :: [Condition ConfVar] -> CondBranch ConfVar c s -> [Pair] jsonIf cs (CondBranch c thenTree Nothing) = go (c : cs) thenTree jsonIf cs (CondBranch c thenTree (Just elseTree)) = - go (c : cs) thenTree ++ go (CNot c : cs) elseTree + go (c : cs) thenTree ++ go (cNot c : cs) elseTree + + merge :: Pair -> KeyMap.KeyMap Value -> KeyMap.KeyMap Value + merge = uncurry $ KeyMap.insertWith $ \new -> + \case + (Array a) -> Array (a `V.snoc` new) + old -> Array (V.fromList [old, new]) + +withName :: (ToJSON v) => v -> [Pair] -> Value +withName n s = object $ ("name" .= n) : s + +showCondition :: Condition ConfVar -> String +showCondition (Var x) = showConfVar x +showCondition (Lit b) = show b +showCondition (CNot c) = "!" <> showCondition c +showCondition (COr c1 c2) = "(" <> unwords [showCondition c1, "||", showCondition c2] <> ")" +showCondition (CAnd c1 c2) = "(" <> unwords [showCondition c1, "&&", showCondition c2] <> ")" + +showConfVar :: ConfVar -> String +showConfVar (OS os) = "os(" <> prettyShow os <> ")" +showConfVar (Arch arch) = "arch(" <> prettyShow arch <> ")" +showConfVar (PackageFlag name) = "flag(" <> unFlagName name <> ")" +showConfVar (Impl c v) = "impl(" <> prettyShow c <> " " <> prettyShow v <> ")" + +showIfCondition :: Condition ConfVar -> String +showIfCondition c = "if " <> showCondition c + +newtype ViaPretty a = ViaPretty a + +instance (Pretty a) => ToJSON (ViaPretty a) where + toJSON (ViaPretty a) = toJSON $ prettyShow a + +newtype ViaUnpack a = ViaUnpack a + +instance (ToJSON o, Newtype o n) => ToJSON (ViaUnpack n) where + toJSON (ViaUnpack n) = toJSON $ unpack n - merge :: [Pair] -> Value - merge = Object . fmap toJSON . KeyMap.fromListWith (++) . map (second (: [])) +deriving via String instance ToJSON Token + +deriving via String instance ToJSON Token' + +deriving via String instance ToJSON FilePathNT + +deriving via String instance ToJSON CompatFilePath + +deriving via ViaUnpack CompatLicenseFile instance ToJSON CompatLicenseFile + +deriving via (ViaPretty VersionRange) instance ToJSON VersionRange + +deriving via ViaUnpack TestedWith instance ToJSON TestedWith + +deriving via (ViaPretty CompilerFlavor) instance ToJSON CompilerFlavor + +deriving via (ViaPretty SpecVersion) instance ToJSON SpecVersion + +deriving via (ViaPretty SpecLicense) instance ToJSON SpecLicense + +deriving via (ViaUnpack (List sep b a)) instance (ToJSON a) => ToJSON (List sep b a) + +deriving via (ViaPretty (SymbolicPath from to)) instance ToJSON (SymbolicPath from to) + +deriving via (ViaPretty BuildType) instance ToJSON BuildType + +deriving via (ViaPretty PackageName) instance ToJSON PackageName + +deriving via (ViaPretty Version) instance ToJSON Version + +instance ToJSON RepoType + +instance ToJSON KnownRepoType + +deriving via (ViaPretty Extension) instance ToJSON Extension + +deriving via (ViaPretty Language) instance ToJSON Language + +deriving via (ViaUnpack (MQuoted a)) instance (ToJSON a) => ToJSON (MQuoted a) + +deriving via (ViaPretty Dependency) instance ToJSON Dependency + +deriving via (ViaPretty BenchmarkType) instance ToJSON BenchmarkType + +deriving via (ViaPretty ForeignLibType) instance ToJSON ForeignLibType + +deriving via (ViaPretty TestType) instance ToJSON TestType + +deriving via (ViaPretty ExecutableScope) instance ToJSON ExecutableScope + +deriving via (ViaPretty ForeignLibOption) instance ToJSON ForeignLibOption + +deriving via (ViaPretty LibVersionInfo) instance ToJSON LibVersionInfo + +deriving via (ViaPretty ModuleName) instance ToJSON ModuleName + +deriving via (ViaPretty ModuleReexport) instance ToJSON ModuleReexport + +deriving via (ViaPretty Mixin) instance ToJSON Mixin + +deriving via (ViaPretty PkgconfigDependency) instance ToJSON PkgconfigDependency + +deriving via (ViaPretty ExeDependency) instance ToJSON ExeDependency + +deriving via (ViaPretty LegacyExeDependency) instance ToJSON LegacyExeDependency + +deriving via (ViaPretty LibraryVisibility) instance ToJSON LibraryVisibility diff --git a/foliage.cabal b/foliage.cabal index 65a4714..b694cd6 100644 --- a/foliage.cabal +++ b/foliage.cabal @@ -65,5 +65,6 @@ executable foliage time >=1.9.3 && <1.13, time-compat >=1.9.6.1 && <1.10, tomland >=1.3.3.1 && <1.4, + vector >=0.13.0.0 && <0.14, with-utf8 >=1.0.2.3 && <1.1, - zlib >=0.6.2.3 && <0.7 + zlib >=0.6.2.3 && <0.7, diff --git a/templates/dependencies.mustache b/templates/dependencies.mustache new file mode 100644 index 0000000..292c1cf --- /dev/null +++ b/templates/dependencies.mustache @@ -0,0 +1,17 @@ + +{{#build-depends}} +{{#if}} +

if {{.}}

+ +{{/if}} +{{/build-depends}} diff --git a/templates/packageVersion.mustache b/templates/packageVersion.mustache index 8784008..9003b06 100644 --- a/templates/packageVersion.mustache +++ b/templates/packageVersion.mustache @@ -1,72 +1,136 @@ - - - - - - + + + + + + + + {{pkgDesc.name}}-{{pkgDesc.version}} + + + + + +
+ +

+ {{pkgDesc.name}}-{{pkgDesc.version}} +

+
+ {{#pkgVersionDeprecated}} +
Deprecated
+
+ {{/pkgVersionDeprecated}} +
Synopsis
+
+

{{pkgDesc.synopsis}}

+
+
Description
+
+

{{pkgDesc.description}}

+
+
Author
+
+

{{pkgDesc.author}}

+
+
Maintainer
+
+

{{pkgDesc.maintainer}}

+
+
License
+
+

{{pkgDesc.license}}

+
+ {{#pkgVersionSource}} +
Source
+
+
+ {{> packageVersionSource}} +
+
+ {{/pkgVersionSource}} +
Timestamp
+
+

{{pkgTimestamp}}

+
+
Revisions
+
+ {{#cabalFileRevisions}} +

{{.}}

+ {{/cabalFileRevisions}} + {{^cabalFileRevisions}} +

None

+ {{/cabalFileRevisions}} +
+
Dependencies
+
+
+ {{#pkgDesc.library}} +
library {{pkgDesc.name}}:
+
+ {{> dependencies}} +
+ {{/pkgDesc.library}} + {{#pkgDesc.sub-libraries}} +
library {{name}}:
+
+ {{> dependencies}} +
+ {{/pkgDesc.sub-libraries}} + {{#pkgDesc.foreign-libraries}} +
foreign library {{name}}:
+
+ {{> dependencies}} +
+ {{/pkgDesc.foreign-libraries}} + {{#pkgDesc.executables}} +
executable {{name}}:
+
+ {{> dependencies}} +
+ {{/pkgDesc.executables}} + {{#pkgDesc.test-suites}} +
test-suite {{name}}:
+
+ {{> dependencies}} +
+ {{/pkgDesc.test-suites}} + {{#pkgDesc.benchmarks}} +
benchmark {{name}}:
+
+ {{> dependencies}} +
+ {{/pkgDesc.benchmarks}} +
+
+
+
+ - - {{#pkgDesc}} - {{name}}-{{version}} - {{/pkgDesc}} - - - - {{#pkgDesc}} -
- -

- {{name}}-{{version}} -

-
- {{#pkgVersionDeprecated}} -
Deprecated
-
- {{/pkgVersionDeprecated}} -
Synopsis
-

{{synopsis}}

-
Description
-

{{description}}

-
Author
-

{{author}}

-
Maintainer
-

{{maintainer}}

-
License
-

{{license}}

- {{/pkgDesc}} - {{#pkgVersionSource}} -
Source
-
-
- {{> packageVersionSource}} -
-
- {{/pkgVersionSource}} -
Timestamp
-

{{pkgTimestamp}}

-
Revisions
-
- {{#cabalFileRevisions}} -

{{.}}

- {{/cabalFileRevisions}} - {{^cabalFileRevisions}} -

None

- {{/cabalFileRevisions}} -
-
-
-