mirror of
https://github.com/input-output-hk/foliage.git
synced 2024-11-29 14:33:39 +03:00
Finish off pages
- Summary page has the list of all packages available (with details of the latest version) - Timeline page has the list of all entries as they appear in the index Also: - Rebuild sdists is they are missing
This commit is contained in:
parent
db3fe215de
commit
c0714b1b3d
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE DerivingVia #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
@ -8,41 +7,28 @@ import Codec.Archive.Tar qualified as Tar
|
||||
import Codec.Archive.Tar.Entry qualified as Tar
|
||||
import Codec.Compression.GZip qualified as GZip
|
||||
import Control.Monad (unless, when)
|
||||
import Data.Aeson (object, (.=))
|
||||
import Data.Aeson.Types (ToJSON)
|
||||
import Data.ByteString.Lazy qualified as BL
|
||||
import Data.ByteString.Lazy qualified as BSL
|
||||
import Data.Foldable (for_)
|
||||
import Data.List (sortOn)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.Ord
|
||||
import Data.Text.Lazy.IO qualified as TL
|
||||
import Data.Time.Clock.POSIX (POSIXTime, utcTimeToPOSIXSeconds)
|
||||
import Data.Traversable (for)
|
||||
import Development.Shake
|
||||
import Development.Shake.FilePath
|
||||
import Distribution.Aeson
|
||||
import Distribution.Package
|
||||
import Distribution.PackageDescription (GenericPackageDescription)
|
||||
import Distribution.Parsec (simpleParsec)
|
||||
import Distribution.Pretty (prettyShow)
|
||||
import Distribution.Simple.PackageDescription (readGenericPackageDescription)
|
||||
import Distribution.Verbosity qualified as Verbosity
|
||||
import Foliage.HackageSecurity hiding (ToJSON, toJSON)
|
||||
import Foliage.Meta
|
||||
import Foliage.Meta.Aeson ()
|
||||
import Foliage.Options
|
||||
import Foliage.Pages (indexPageTemplate, packageVersionPageTemplate)
|
||||
import Foliage.Pages
|
||||
import Foliage.PrepareSdist
|
||||
import Foliage.PrepareSource (addPrepareSourceRule, prepareSource)
|
||||
import Foliage.RemoteAsset (addFetchRemoteAssetRule)
|
||||
import Foliage.Shake
|
||||
import Foliage.Time qualified as Time
|
||||
import Foliage.Utils.Aeson
|
||||
import GHC.Generics (Generic)
|
||||
import Hackage.Security.Util.Path (castRoot, toFilePath)
|
||||
import System.Directory qualified as IO
|
||||
import Text.Mustache (renderMustache)
|
||||
|
||||
cmdBuild :: BuildOptions -> IO ()
|
||||
cmdBuild buildOptions = do
|
||||
@ -97,13 +83,15 @@ buildAction
|
||||
putInfo $ "Current time set to " <> Time.iso8601Show t <> "."
|
||||
return t
|
||||
|
||||
packages <- getPackages inputDir
|
||||
packageVersions <- getPackageVersions inputDir
|
||||
|
||||
makeIndexPage currentTime outputDir packages
|
||||
makeSummaryPage currentTime outputDir packageVersions
|
||||
|
||||
for_ packages $ makePackageVersionPage inputDir outputDir
|
||||
makeTimelinePage currentTime outputDir packageVersions
|
||||
|
||||
for_ packages $ \pkgMeta@PackageVersionMeta {pkgId} -> do
|
||||
for_ packageVersions $ makePackageVersionPage inputDir outputDir
|
||||
|
||||
for_ packageVersions $ \pkgMeta@PackageVersionMeta {pkgId} -> do
|
||||
let PackageIdentifier {pkgName, pkgVersion} = pkgId
|
||||
cabalFilePath <- maybe (originalCabalFile pkgMeta) pure (revisedCabalFile inputDir pkgMeta)
|
||||
copyFileChanged cabalFilePath (outputDir </> "index" </> prettyShow pkgName </> prettyShow pkgVersion </> prettyShow pkgName <.> "cabal")
|
||||
@ -129,11 +117,11 @@ buildAction
|
||||
|
||||
return $ cf : revcf
|
||||
)
|
||||
packages
|
||||
packageVersions
|
||||
|
||||
targetKeys <- maybeReadKeysAt "target"
|
||||
metadataEntries <-
|
||||
for packages $ \pkg@PackageVersionMeta {pkgId, pkgSpec} -> do
|
||||
for packageVersions $ \pkg@PackageVersionMeta {pkgId, pkgSpec} -> do
|
||||
let PackageIdentifier {pkgName, pkgVersion} = pkgId
|
||||
let PackageVersionSpec {packageVersionTimestamp} = pkgSpec
|
||||
targets <- prepareIndexPkgMetadata expiryTime pkg
|
||||
@ -233,66 +221,8 @@ buildAction
|
||||
timestampInfoSnapshot = snapshotInfo
|
||||
}
|
||||
|
||||
data IndexEntry
|
||||
= IndexEntryPackage
|
||||
{ indexEntryPkgId :: PackageIdentifier,
|
||||
indexEntryTimestamp :: UTCTime,
|
||||
indexEntryTimestampPosix :: POSIXTime,
|
||||
indexEntrySource :: PackageVersionSource
|
||||
}
|
||||
| IndexEntryRevision
|
||||
{ indexEntryPkgId :: PackageIdentifier,
|
||||
indexEntryTimestamp :: UTCTime,
|
||||
indexEntryTimestampPosix :: POSIXTime
|
||||
}
|
||||
deriving stock (Generic)
|
||||
deriving (ToJSON) via MyAesonEncoding IndexEntry
|
||||
|
||||
makeIndexPage :: UTCTime -> FilePath -> [PackageVersionMeta] -> Action ()
|
||||
makeIndexPage currentTime outputDir packages = do
|
||||
let entries =
|
||||
sortOn (Down . indexEntryTimestamp) $
|
||||
foldMap
|
||||
( \PackageVersionMeta {pkgId, pkgSpec = PackageVersionSpec {packageVersionTimestamp, packageVersionRevisions, packageVersionSource}} ->
|
||||
IndexEntryPackage
|
||||
{ indexEntryPkgId = pkgId,
|
||||
indexEntryTimestamp = fromMaybe currentTime packageVersionTimestamp,
|
||||
indexEntryTimestampPosix = utcTimeToPOSIXSeconds (fromMaybe currentTime packageVersionTimestamp),
|
||||
indexEntrySource = packageVersionSource
|
||||
} :
|
||||
map
|
||||
( \RevisionSpec {revisionTimestamp} ->
|
||||
IndexEntryRevision
|
||||
{ indexEntryPkgId = pkgId,
|
||||
indexEntryTimestamp = revisionTimestamp,
|
||||
indexEntryTimestampPosix = utcTimeToPOSIXSeconds revisionTimestamp
|
||||
}
|
||||
)
|
||||
packageVersionRevisions
|
||||
)
|
||||
packages
|
||||
|
||||
liftIO $ do
|
||||
IO.createDirectoryIfMissing True outputDir
|
||||
TL.writeFile (outputDir </> "index.html") $
|
||||
renderMustache indexPageTemplate $
|
||||
object ["entries" .= entries]
|
||||
|
||||
makePackageVersionPage :: FilePath -> FilePath -> PackageVersionMeta -> Action ()
|
||||
makePackageVersionPage inputDir outputDir pkgMeta@PackageVersionMeta {pkgId, pkgSpec} = do
|
||||
cabalFilePath <- maybe (originalCabalFile pkgMeta) pure (revisedCabalFile inputDir pkgMeta)
|
||||
pkgDesc <- readGenericPackageDescription' cabalFilePath
|
||||
liftIO $ do
|
||||
IO.createDirectoryIfMissing True (outputDir </> "package" </> prettyShow pkgId)
|
||||
TL.writeFile (outputDir </> "package" </> prettyShow pkgId </> "index.html") $
|
||||
renderMustache packageVersionPageTemplate $
|
||||
object
|
||||
[ "pkgSpec" .= pkgSpec,
|
||||
"pkgDesc" .= jsonGenericPackageDescription pkgDesc
|
||||
]
|
||||
|
||||
getPackages :: FilePath -> Action [PackageVersionMeta]
|
||||
getPackages inputDir = do
|
||||
getPackageVersions :: FilePath -> Action [PackageVersionMeta]
|
||||
getPackageVersions inputDir = do
|
||||
metaFiles <- getDirectoryFiles inputDir ["*/*/meta.toml"]
|
||||
|
||||
when (null metaFiles) $ do
|
||||
@ -332,11 +262,6 @@ getPackages inputDir = do
|
||||
|
||||
return $ PackageVersionMeta pkgId pkgSpec
|
||||
|
||||
readGenericPackageDescription' :: FilePath -> Action GenericPackageDescription
|
||||
readGenericPackageDescription' fp = do
|
||||
need [fp]
|
||||
liftIO $ readGenericPackageDescription Verbosity.silent fp
|
||||
|
||||
prepareIndexPkgCabal :: PackageId -> UTCTime -> FilePath -> Action Tar.Entry
|
||||
prepareIndexPkgCabal pkgId timestamp filePath = do
|
||||
need [filePath]
|
||||
@ -376,16 +301,3 @@ mkTarEntry contents indexFile timestamp =
|
||||
anchorPath :: Path Absolute -> (RepoLayout -> RepoPath) -> FilePath
|
||||
anchorPath outputDirRoot p =
|
||||
toFilePath $ anchorRepoPathLocally outputDirRoot $ p hackageRepoLayout
|
||||
|
||||
cabalFileRevisionPath :: FilePath -> PackageIdentifier -> Int -> FilePath
|
||||
cabalFileRevisionPath inputDir PackageIdentifier {pkgName, pkgVersion} revisionNumber =
|
||||
inputDir </> unPackageName pkgName </> prettyShow pkgVersion </> "revisions" </> show revisionNumber <.> "cabal"
|
||||
|
||||
originalCabalFile :: PackageVersionMeta -> Action FilePath
|
||||
originalCabalFile PackageVersionMeta {pkgId, pkgSpec} = do
|
||||
srcDir <- prepareSource pkgId pkgSpec
|
||||
return $ srcDir </> unPackageName (pkgName pkgId) <.> "cabal"
|
||||
|
||||
revisedCabalFile :: FilePath -> PackageVersionMeta -> Maybe FilePath
|
||||
revisedCabalFile inputDir PackageVersionMeta {pkgId, pkgSpec} = do
|
||||
cabalFileRevisionPath inputDir pkgId <$> latestRevisionNumber pkgSpec
|
||||
|
@ -32,6 +32,8 @@ module Foliage.Meta
|
||||
UTCTime,
|
||||
latestRevisionNumber,
|
||||
consolidateRanges,
|
||||
cabalFileRevisionPath,
|
||||
revisedCabalFile,
|
||||
)
|
||||
where
|
||||
|
||||
@ -43,32 +45,21 @@ import Data.Ord (Down (Down))
|
||||
import Data.Text (Text)
|
||||
import Data.Text qualified as T
|
||||
import Data.Time.LocalTime (utc, utcToZonedTime, zonedTimeToUTC)
|
||||
import Development.Shake.Classes
|
||||
( Binary,
|
||||
Hashable,
|
||||
NFData,
|
||||
)
|
||||
import Development.Shake.Classes (Binary, Hashable, NFData)
|
||||
import Distribution.Aeson ()
|
||||
import Distribution.Parsec (simpleParsec)
|
||||
import Distribution.Pretty (prettyShow)
|
||||
import Distribution.Types.Orphans ()
|
||||
import Distribution.Types.PackageId (PackageIdentifier)
|
||||
import Distribution.Types.PackageId (PackageIdentifier (..))
|
||||
import Distribution.Types.PackageName (unPackageName)
|
||||
import Distribution.Types.Version (Version)
|
||||
import Distribution.Types.VersionRange
|
||||
( VersionRange,
|
||||
anyVersion,
|
||||
intersectVersionRanges,
|
||||
notThisVersion,
|
||||
)
|
||||
import Distribution.Version
|
||||
( isAnyVersion,
|
||||
isNoVersion,
|
||||
simplifyVersionRange,
|
||||
)
|
||||
import Distribution.Types.VersionRange (VersionRange, anyVersion, intersectVersionRanges, notThisVersion)
|
||||
import Distribution.Version (isAnyVersion, isNoVersion, simplifyVersionRange)
|
||||
import Foliage.Time (UTCTime)
|
||||
import GHC.Generics (Generic)
|
||||
import Network.URI (URI, parseURI)
|
||||
import Network.URI.Orphans ()
|
||||
import System.FilePath ((<.>), (</>))
|
||||
import Toml (TomlCodec, (.=))
|
||||
import Toml qualified
|
||||
|
||||
@ -245,4 +236,13 @@ data PackageVersionMeta = PackageVersionMeta
|
||||
{ pkgId :: PackageIdentifier,
|
||||
pkgSpec :: PackageVersionSpec
|
||||
}
|
||||
deriving (Show, Eq)
|
||||
deriving (Generic)
|
||||
|
||||
cabalFileRevisionPath :: FilePath -> PackageIdentifier -> Int -> FilePath
|
||||
cabalFileRevisionPath inputDir PackageIdentifier {pkgName, pkgVersion} revisionNumber =
|
||||
inputDir </> unPackageName pkgName </> prettyShow pkgVersion </> "revisions" </> show revisionNumber <.> "cabal"
|
||||
|
||||
revisedCabalFile :: FilePath -> PackageVersionMeta -> Maybe FilePath
|
||||
revisedCabalFile inputDir PackageVersionMeta {pkgId, pkgSpec} = do
|
||||
cabalFileRevisionPath inputDir pkgId <$> latestRevisionNumber pkgSpec
|
||||
|
@ -1,6 +1,7 @@
|
||||
{-# LANGUAGE DerivingVia #-}
|
||||
{-# LANGUAGE StandaloneDeriving #-}
|
||||
{-# OPTIONS_GHC -Wno-orphans #-}
|
||||
{-# LANGUAGE InstanceSigs #-}
|
||||
|
||||
module Foliage.Meta.Aeson where
|
||||
|
||||
@ -30,7 +31,9 @@ instance ToJSON PackageVersionSource where
|
||||
genericToJSON
|
||||
defaultOptions
|
||||
{ sumEncoding = ObjectWithSingleField
|
||||
, omitNothingFields = True
|
||||
}
|
||||
|
||||
instance ToJSON URI where
|
||||
toJSON :: URI -> Value
|
||||
toJSON = toJSON . show
|
||||
|
@ -1,17 +1,140 @@
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE DerivingVia #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
||||
module Foliage.Pages
|
||||
( indexPageTemplate,
|
||||
( summaryPageTemplate,
|
||||
timelinePageTemplate,
|
||||
packageVersionPageTemplate,
|
||||
makeSummaryPage,
|
||||
makePackageVersionPage,
|
||||
makeTimelinePage,
|
||||
)
|
||||
where
|
||||
|
||||
import Data.Aeson (KeyValue ((.=)), ToJSON, object)
|
||||
import Data.Function (on)
|
||||
import Data.List (groupBy, sortOn)
|
||||
import Data.Maybe (fromMaybe, listToMaybe)
|
||||
import Data.Ord (Down (Down))
|
||||
import Data.Text.Lazy.IO.Utf8 qualified as TL
|
||||
import Data.Time (UTCTime)
|
||||
import Data.Time.Clock.POSIX (POSIXTime, utcTimeToPOSIXSeconds)
|
||||
import Development.Shake (Action, liftIO)
|
||||
import Distribution.Aeson (jsonGenericPackageDescription)
|
||||
import Distribution.Package (PackageIdentifier (pkgName, pkgVersion))
|
||||
import Distribution.Pretty (prettyShow)
|
||||
import Foliage.Meta (PackageVersionMeta (..), PackageVersionSource, PackageVersionSpec (PackageVersionSpec, packageVersionRevisions, packageVersionSource, packageVersionTimestamp), RevisionSpec (RevisionSpec, revisionTimestamp), revisedCabalFile)
|
||||
import Foliage.Meta.Aeson ()
|
||||
import Foliage.Shake (originalCabalFile, readGenericPackageDescription')
|
||||
import Foliage.Utils.Aeson (MyAesonEncoding (..))
|
||||
import GHC.Generics (Generic)
|
||||
import System.Directory qualified as IO
|
||||
import System.FilePath ((</>))
|
||||
import Text.Mustache (Template)
|
||||
import Text.Mustache.Compile.TH (compileMustacheDir)
|
||||
import Text.Mustache.Render (renderMustache)
|
||||
|
||||
indexPageTemplate :: Template
|
||||
indexPageTemplate = $(compileMustacheDir "index" "templates")
|
||||
data SummaryPageEntry = SummaryPageEntry
|
||||
{ summaryPageEntryPkgId :: PackageIdentifier,
|
||||
summaryPageEntryTimestamp :: UTCTime,
|
||||
summaryPageEntryTimestampPosix :: POSIXTime,
|
||||
summaryPageEntrySource :: PackageVersionSource,
|
||||
summaryPageEntryRevision :: Maybe RevisionSpec
|
||||
}
|
||||
deriving stock (Generic)
|
||||
deriving (ToJSON) via MyAesonEncoding SummaryPageEntry
|
||||
|
||||
makeSummaryPage :: UTCTime -> FilePath -> [PackageVersionMeta] -> Action ()
|
||||
makeSummaryPage currentTime outputDir packageVersions = do
|
||||
let packages =
|
||||
sortOn summaryPageEntryPkgId $
|
||||
map
|
||||
( ( \PackageVersionMeta {pkgId, pkgSpec = PackageVersionSpec {packageVersionTimestamp, packageVersionRevisions, packageVersionSource}} ->
|
||||
SummaryPageEntry
|
||||
{ summaryPageEntryPkgId = pkgId,
|
||||
summaryPageEntryTimestamp = fromMaybe currentTime packageVersionTimestamp,
|
||||
summaryPageEntryTimestampPosix = utcTimeToPOSIXSeconds (fromMaybe currentTime packageVersionTimestamp),
|
||||
summaryPageEntrySource = packageVersionSource,
|
||||
summaryPageEntryRevision = listToMaybe packageVersionRevisions
|
||||
}
|
||||
)
|
||||
. head
|
||||
. sortOn (Down . pkgVersion . pkgId)
|
||||
)
|
||||
$ groupBy ((==) `on` (pkgName . pkgId)) packageVersions
|
||||
liftIO $ do
|
||||
IO.createDirectoryIfMissing True outputDir
|
||||
IO.createDirectoryIfMissing True (outputDir </> "summary")
|
||||
TL.writeFile (outputDir </> "summary" </> "index.html") $
|
||||
renderMustache summaryPageTemplate $
|
||||
object ["packages" .= packages]
|
||||
|
||||
data TimelinePageEntry
|
||||
= TimelinePageEntryPackage
|
||||
{ timelinePageEntryPkgId :: PackageIdentifier,
|
||||
timelinePageEntryTimestamp :: UTCTime,
|
||||
timelinePageEntryTimestampPosix :: POSIXTime,
|
||||
timelinePageEntrySource :: PackageVersionSource
|
||||
}
|
||||
| TimelinePageEntryRevision
|
||||
{ timelinePageEntryPkgId :: PackageIdentifier,
|
||||
timelinePageEntryTimestamp :: UTCTime,
|
||||
timelinePageEntryTimestampPosix :: POSIXTime
|
||||
}
|
||||
deriving stock (Generic)
|
||||
deriving (ToJSON) via MyAesonEncoding TimelinePageEntry
|
||||
|
||||
makeTimelinePage :: UTCTime -> FilePath -> [PackageVersionMeta] -> Action ()
|
||||
makeTimelinePage currentTime outputDir packageVersions = do
|
||||
let entries =
|
||||
sortOn (Down . timelinePageEntryTimestamp) $
|
||||
foldMap
|
||||
( \PackageVersionMeta {pkgId, pkgSpec = PackageVersionSpec {packageVersionTimestamp, packageVersionRevisions, packageVersionSource}} ->
|
||||
TimelinePageEntryPackage
|
||||
{ timelinePageEntryPkgId = pkgId,
|
||||
timelinePageEntryTimestamp = fromMaybe currentTime packageVersionTimestamp,
|
||||
timelinePageEntryTimestampPosix = utcTimeToPOSIXSeconds (fromMaybe currentTime packageVersionTimestamp),
|
||||
timelinePageEntrySource = packageVersionSource
|
||||
} :
|
||||
map
|
||||
( \RevisionSpec {revisionTimestamp} ->
|
||||
TimelinePageEntryRevision
|
||||
{ timelinePageEntryPkgId = pkgId,
|
||||
timelinePageEntryTimestamp = revisionTimestamp,
|
||||
timelinePageEntryTimestampPosix = utcTimeToPOSIXSeconds revisionTimestamp
|
||||
}
|
||||
)
|
||||
packageVersionRevisions
|
||||
)
|
||||
packageVersions
|
||||
|
||||
liftIO $ do
|
||||
IO.createDirectoryIfMissing True outputDir
|
||||
IO.createDirectoryIfMissing True (outputDir </> "timeline")
|
||||
TL.writeFile (outputDir </> "timeline" </> "index.html") $
|
||||
renderMustache timelinePageTemplate $
|
||||
object ["entries" .= entries]
|
||||
|
||||
makePackageVersionPage :: FilePath -> FilePath -> PackageVersionMeta -> Action ()
|
||||
makePackageVersionPage inputDir outputDir pkgMeta@PackageVersionMeta {pkgId, pkgSpec} = do
|
||||
cabalFilePath <- maybe (originalCabalFile pkgMeta) pure (revisedCabalFile inputDir pkgMeta)
|
||||
pkgDesc <- readGenericPackageDescription' cabalFilePath
|
||||
liftIO $ do
|
||||
IO.createDirectoryIfMissing True (outputDir </> "package" </> prettyShow pkgId)
|
||||
TL.writeFile (outputDir </> "package" </> prettyShow pkgId </> "index.html") $
|
||||
renderMustache packageVersionPageTemplate $
|
||||
object
|
||||
[ "pkgSpec" .= pkgSpec,
|
||||
"pkgDesc" .= jsonGenericPackageDescription pkgDesc
|
||||
]
|
||||
|
||||
summaryPageTemplate :: Template
|
||||
summaryPageTemplate = $(compileMustacheDir "summary" "templates")
|
||||
|
||||
timelinePageTemplate :: Template
|
||||
timelinePageTemplate = $(compileMustacheDir "timeline" "templates")
|
||||
|
||||
packageVersionPageTemplate :: Template
|
||||
packageVersionPageTemplate = $(compileMustacheDir "packageVersion" "templates")
|
||||
|
@ -11,15 +11,15 @@ module Foliage.PrepareSdist
|
||||
where
|
||||
|
||||
import Control.Monad (when)
|
||||
import Data.Binary qualified as Binary
|
||||
import Data.ByteString qualified as BS
|
||||
import Data.ByteString.Lazy qualified as BSL
|
||||
import Development.Shake
|
||||
import Development.Shake.Classes
|
||||
import Development.Shake.FilePath
|
||||
import Development.Shake.Rule
|
||||
import Distribution.Client.HashValue (HashValue, hashValue, showHashValue)
|
||||
import Distribution.Client.HashValue (HashValue, hashValue, readFileHashValue, showHashValue)
|
||||
import Distribution.Client.SrcDist (packageDirToSdist)
|
||||
import Distribution.Compat.Binary (decode, encode)
|
||||
import Distribution.Package (packageId)
|
||||
import Distribution.Simple.PackageDescription (readGenericPackageDescription)
|
||||
import Distribution.Verbosity qualified as Verbosity
|
||||
@ -28,6 +28,7 @@ import Foliage.Meta ()
|
||||
import GHC.Generics (Generic)
|
||||
import Hackage.Security.Util.Path (toFilePath)
|
||||
import System.Directory qualified as IO
|
||||
import System.IO.Error (tryIOError)
|
||||
|
||||
newtype PrepareSdistRule = PrepareSdistRule FilePath
|
||||
deriving (Show, Eq, Generic)
|
||||
@ -42,28 +43,32 @@ addPrepareSdistRule :: Path Absolute -> Rules ()
|
||||
addPrepareSdistRule outputDirRoot = addBuiltinRule noLint noIdentity run
|
||||
where
|
||||
run :: PrepareSdistRule -> Maybe BS.ByteString -> RunMode -> Action (RunResult FilePath)
|
||||
run (PrepareSdistRule _srcDir) (Just old) RunDependenciesSame =
|
||||
let (_, path) = load old
|
||||
in return $ RunResult ChangedNothing old path
|
||||
run (PrepareSdistRule srcDir) old _ = do
|
||||
cabalFile <- do
|
||||
getDirectoryFiles srcDir ["*.cabal"] >>= \case
|
||||
[f] -> pure f
|
||||
fs -> fail $ "Invalid srcDir: " ++ srcDir ++ ". It contains multiple cabal files: " ++ unwords fs
|
||||
(hv, path) <- traced "cabal sdist" $ do
|
||||
gpd <- readGenericPackageDescription Verbosity.normal (srcDir </> cabalFile)
|
||||
let pkgId = packageId gpd
|
||||
packagePath = repoLayoutPkgTarGz hackageRepoLayout pkgId
|
||||
path = toFilePath $ anchorRepoPathLocally outputDirRoot packagePath
|
||||
IO.createDirectoryIfMissing True (takeDirectory path)
|
||||
sdist <- packageDirToSdist Verbosity.normal gpd srcDir
|
||||
BSL.writeFile path sdist
|
||||
return (hashValue sdist, path)
|
||||
run (PrepareSdistRule srcDir) (Just old) RunDependenciesSame = do
|
||||
let (hvExpected, path) = load old
|
||||
|
||||
-- Check of has of the sdist, if the sdist is still there and it is
|
||||
-- indeed what we expect, signal that nothing changed. Otherwise
|
||||
-- warn the user and proceed to recompute.
|
||||
ehvExisting <- liftIO $ tryIOError $ readFileHashValue path
|
||||
case ehvExisting of
|
||||
Right hvExisting
|
||||
| hvExisting == hvExpected ->
|
||||
return RunResult {runChanged = ChangedNothing, runStore = old, runValue = path}
|
||||
Right hvExisting -> do
|
||||
putWarn $ "Changed " ++ path ++ " (expecting hash " ++ showHashValue hvExpected ++ " found " ++ showHashValue hvExisting ++ "). I will rebuild it."
|
||||
run (PrepareSdistRule srcDir) (Just old) RunDependenciesChanged
|
||||
Left _e -> do
|
||||
putWarn $ "Unable to read " ++ path ++ ". I will rebuild it."
|
||||
run (PrepareSdistRule srcDir) (Just old) RunDependenciesChanged
|
||||
run (PrepareSdistRule srcDir) old _mode = do
|
||||
-- create the sdist distribution
|
||||
(hv, path) <- makeSdist srcDir
|
||||
|
||||
let new = save (hv, path)
|
||||
|
||||
let changed = case old of
|
||||
Just old' | fst (load old') == hv -> ChangedRecomputeSame
|
||||
_ -> ChangedRecomputeDiff
|
||||
let changed = case fmap ((== hv) . fst . load) old of
|
||||
Just True -> ChangedRecomputeSame
|
||||
_differentOrMissing -> ChangedRecomputeDiff
|
||||
|
||||
when (changed == ChangedRecomputeSame) $
|
||||
putInfo $ "Wrote " ++ path ++ " (same hash " ++ showHashValue hv ++ ")"
|
||||
@ -73,8 +78,24 @@ addPrepareSdistRule outputDirRoot = addBuiltinRule noLint noIdentity run
|
||||
|
||||
return $ RunResult {runChanged = changed, runStore = new, runValue = path}
|
||||
|
||||
makeSdist srcDir = do
|
||||
cabalFile <- do
|
||||
getDirectoryFiles srcDir ["*.cabal"] >>= \case
|
||||
[f] -> pure f
|
||||
fs -> fail $ "Invalid srcDir: " ++ srcDir ++ ". It contains multiple cabal files: " ++ unwords fs
|
||||
|
||||
traced "cabal sdist" $ do
|
||||
gpd <- readGenericPackageDescription Verbosity.normal (srcDir </> cabalFile)
|
||||
let pkgId = packageId gpd
|
||||
packagePath = repoLayoutPkgTarGz hackageRepoLayout pkgId
|
||||
path = toFilePath $ anchorRepoPathLocally outputDirRoot packagePath
|
||||
IO.createDirectoryIfMissing True (takeDirectory path)
|
||||
sdist <- packageDirToSdist Verbosity.normal gpd srcDir
|
||||
BSL.writeFile path sdist
|
||||
return (hashValue sdist, path)
|
||||
|
||||
save :: (HashValue, FilePath) -> BS.ByteString
|
||||
save = BSL.toStrict . encode
|
||||
save = BSL.toStrict . Binary.encode
|
||||
|
||||
load :: BS.ByteString -> (HashValue, FilePath)
|
||||
load = decode . BSL.fromStrict
|
||||
load = Binary.decode . BSL.fromStrict
|
||||
|
@ -48,11 +48,11 @@ addFetchRemoteAssetRule cacheDir = addBuiltinRule noLint noIdentity run
|
||||
let oldETag = fromMaybe BS.empty old
|
||||
|
||||
newETag <-
|
||||
withTempFile $ \fp -> do
|
||||
liftIO $ BS.writeFile fp oldETag
|
||||
liftIO $ createDirectoryIfMissing True (takeDirectory path)
|
||||
withTempFile $ \fp -> traced "curl" $ do
|
||||
BS.writeFile fp oldETag
|
||||
createDirectoryIfMissing True (takeDirectory path)
|
||||
cmd_ Shell ["curl", "--silent", "--location", "--etag-compare", fp, "--etag-save", fp, "--output", path, show uri]
|
||||
liftIO $ BS.readFile fp
|
||||
BS.readFile fp
|
||||
|
||||
let changed = if newETag == oldETag then ChangedRecomputeSame else ChangedRecomputeDiff
|
||||
return $ RunResult {runChanged = changed, runStore = newETag, runValue = path}
|
||||
|
@ -2,14 +2,22 @@ module Foliage.Shake
|
||||
( computeFileInfoSimple',
|
||||
readKeysAt,
|
||||
readPackageVersionSpec',
|
||||
readGenericPackageDescription',
|
||||
originalCabalFile,
|
||||
)
|
||||
where
|
||||
|
||||
import Data.Traversable (for)
|
||||
import Development.Shake
|
||||
import Development.Shake.FilePath
|
||||
import Distribution.Simple.PackageDescription
|
||||
import Distribution.Types.GenericPackageDescription
|
||||
import Distribution.Types.PackageId
|
||||
import Distribution.Types.PackageName
|
||||
import Distribution.Verbosity qualified as Verbosity
|
||||
import Foliage.HackageSecurity
|
||||
import Foliage.Meta
|
||||
import Foliage.PrepareSource
|
||||
|
||||
computeFileInfoSimple' :: FilePath -> Action FileInfo
|
||||
computeFileInfoSimple' fp = do
|
||||
@ -28,3 +36,13 @@ readPackageVersionSpec' :: FilePath -> Action PackageVersionSpec
|
||||
readPackageVersionSpec' fp = do
|
||||
need [fp]
|
||||
liftIO $ readPackageVersionSpec fp
|
||||
|
||||
readGenericPackageDescription' :: FilePath -> Action GenericPackageDescription
|
||||
readGenericPackageDescription' fp = do
|
||||
need [fp]
|
||||
liftIO $ readGenericPackageDescription Verbosity.silent fp
|
||||
|
||||
originalCabalFile :: PackageVersionMeta -> Action FilePath
|
||||
originalCabalFile PackageVersionMeta {pkgId, pkgSpec} = do
|
||||
srcDir <- prepareSource pkgId pkgSpec
|
||||
return $ srcDir </> unPackageName (pkgName pkgId) <.> "cabal"
|
||||
|
@ -45,6 +45,7 @@ executable foliage
|
||||
base >=4.14.3.0 && <4.18,
|
||||
aeson >=2.0.3.0 && <2.2,
|
||||
base64 >=0.4.2.3 && <0.5,
|
||||
binary,
|
||||
bytestring >=0.10.12.0 && <0.12,
|
||||
Cabal >=3.8 && <3.9,
|
||||
Cabal-syntax >=3.8 && <3.9,
|
||||
|
@ -19,8 +19,8 @@
|
||||
<div class="container px-4 py-5">
|
||||
<nav aria-label="breadcrumb">
|
||||
<ol class="breadcrumb">
|
||||
<li class="breadcrumb-item"><a href="/">Home</a></li>
|
||||
<li class="breadcrumb-item"><a href="/?q={{name}}">{{name}}</a></li>
|
||||
<li class="breadcrumb-item"><a href="/timeline/">Timeline</a></li>
|
||||
<li class="breadcrumb-item"><a href="/timeline/?q={{name}}">{{name}}</a></li>
|
||||
<li class="breadcrumb-item active" aria-current="page">{{version}}</li>
|
||||
</ol>
|
||||
</nav>
|
||||
|
@ -1,5 +1,4 @@
|
||||
{{#TarballSource}}
|
||||
<dt>Tarball</dt>
|
||||
<dd><a href="{{tarballSourceURI}}">{{tarballSourceURI}}</a></dd>
|
||||
{{#subdir}}
|
||||
<dt>Subdir</dt>
|
||||
@ -7,7 +6,6 @@
|
||||
{{/subdir}}
|
||||
{{/TarballSource}}
|
||||
{{#GitHubSource}}
|
||||
<dt>GitHub</dt>
|
||||
<dd>
|
||||
{{#subdir}}
|
||||
<a href="https://github.com/{{githubRepo}}/tree/{{githubRev}}/{{subdir}}">https://github.com/{{githubRepo}}</a>
|
||||
|
@ -12,66 +12,66 @@
|
||||
<link rel="stylesheet" href="https://cdn.datatables.net/v/bs5/dt-1.12.1/datatables.min.css" integrity="sha384-4+3RMUungd+Oh0juS2Jl3yQ7mPlVfsgr10NLSsqltLXIECi9ExY4d1cTtmf9aN8E" crossorigin="anonymous">
|
||||
<script src="https://cdn.datatables.net/v/bs5/jq-3.6.0/dt-1.12.1/datatables.min.js" integrity="sha384-eU1uLDC5C4YCIouMauJZjbrnSmIiICWWAPdnZjRkNnuDxG+eJFN/EhW5GlKPAIVl" crossorigin="anonymous"></script>
|
||||
<title>
|
||||
Repository's content
|
||||
Index summary
|
||||
</title>
|
||||
</head>
|
||||
<body>
|
||||
<div class="container px-4 py-5">
|
||||
<nav aria-label="breadcrumb">
|
||||
<ol class="breadcrumb">
|
||||
<li class="breadcrumb-item active" aria-current="page"><a href="/">Home</a></li>
|
||||
<li class="breadcrumb-item active" aria-current="page"><a href="/summary/">Summary</a></li>
|
||||
</ol>
|
||||
</nav>
|
||||
<h1 class="py-5">
|
||||
Repository's entries
|
||||
Index summary
|
||||
</h1>
|
||||
<table id="entries" class="table table-hover">
|
||||
<p>
|
||||
This page lists the latest version and revision of all packages in the index.
|
||||
</p>
|
||||
<table class="table table-hover">
|
||||
<thead>
|
||||
<tr>
|
||||
<th>Package identifier</th>
|
||||
<th>Type</th>
|
||||
<th>Timestamp</th>
|
||||
<th>Package</th>
|
||||
<th>Added on</th>
|
||||
<th>Source</th>
|
||||
<th>Revision</th>
|
||||
</th>
|
||||
</thead>
|
||||
<tbody>
|
||||
{{#entries}}
|
||||
{{#IndexEntryPackage}}
|
||||
{{#packages}}
|
||||
<tr>
|
||||
<td class="col-sm-2"><a href="package/{{indexEntryPkgId}}">{{indexEntryPkgId}}</a></td>
|
||||
<td class="col-sm-1">package</td>
|
||||
<td class="col-sm-3" data-order="{{indexEntryTimestampPosix}}">{{indexEntryTimestamp}}</td>
|
||||
<td class="col-sm-2"><a href="/package/{{summaryPageEntryPkgId}}">{{summaryPageEntryPkgId}}</a></td>
|
||||
<td class="col-sm-3" data-order="{{summaryPageEntryTimestampPosix}}">{{summaryPageEntryTimestamp}}</td>
|
||||
<td class="col-sm-6">
|
||||
<dl class="row">
|
||||
{{#indexEntrySource}}
|
||||
{{#summaryPageEntrySource}}
|
||||
{{> packageVersionSource}}
|
||||
{{/indexEntrySource}}
|
||||
{{/summaryPageEntrySource}}
|
||||
</dl>
|
||||
</td>
|
||||
<td class="col-sm-3">
|
||||
{{#summaryPageEntryRevision}}
|
||||
Last revision at {{revisionTimestamp}}
|
||||
{{/summaryPageEntryRevision}}
|
||||
{{^summaryPageEntryRevision}}
|
||||
No revision
|
||||
{{/summaryPageEntryRevision}}
|
||||
</td>
|
||||
</tr>
|
||||
{{/IndexEntryPackage}}
|
||||
{{#IndexEntryRevision}}
|
||||
<tr>
|
||||
<td>{{indexEntryPkgId}}</td>
|
||||
<td>revision</td>
|
||||
<td data-order="{{indexEntryTimestampPosix}}">{{indexEntryTimestamp}}</td>
|
||||
<td></td>
|
||||
</tr>
|
||||
{{/IndexEntryRevision}}
|
||||
{{/entries}}
|
||||
{{/packages}}
|
||||
</tbody>
|
||||
</table>
|
||||
</div>
|
||||
<script>
|
||||
$(document).ready(function () {
|
||||
const urlParams = new URLSearchParams(location.search);
|
||||
$('#entries').DataTable({
|
||||
order: [[2, 'desc']],
|
||||
lengthMenu: [ [50, 100, 500, -1], [50, 100, 500, "All"] ],
|
||||
search: {
|
||||
search: urlParams.has('q') ? urlParams.get('q') : null,
|
||||
}
|
||||
});
|
||||
const table = $('table').DataTable({
|
||||
order: [[0, 'asc']],
|
||||
lengthMenu: [ [50, 100, 500, -1], [50, 100, 500, "All"] ]
|
||||
})
|
||||
const urlParams = new URLSearchParams(location.search)
|
||||
if (urlParams.has('q')) {
|
||||
table.search(urlParams.get('q')).draw()
|
||||
}
|
||||
});
|
||||
</script>
|
||||
</body>
|
83
templates/timeline.mustache
Normal file
83
templates/timeline.mustache
Normal file
@ -0,0 +1,83 @@
|
||||
<!doctype html>
|
||||
<html lang="en">
|
||||
<head>
|
||||
<!-- Required meta tags -->
|
||||
<meta charset="utf-8">
|
||||
<meta name="viewport" content="width=device-width, initial-scale=1">
|
||||
|
||||
<!-- Bootstrap CSS -->
|
||||
<link rel="stylesheet" href="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/5.1.3/css/bootstrap.min.css" integrity="sha384-1BmE4kWBq78iYhFldvKuhfTAU6auU8tT94WrHftjDbrCEXSU1oBoqyl2QvZ6jIW3" crossorigin="anonymous">
|
||||
<script src="https://cdnjs.cloudflare.com/ajax/libs/twitter-bootstrap/5.1.3/js/bootstrap.bundle.min.js" integrity="sha384-ka7Sk0Gln4gmtz2MlQnikT1wXgYsOg+OMhuP+IlRH9sENBO0LRn5q+8nbTov4+1p" crossorigin="anonymous"></script>
|
||||
<!-- DataTables -->
|
||||
<link rel="stylesheet" href="https://cdn.datatables.net/v/bs5/dt-1.12.1/datatables.min.css" integrity="sha384-4+3RMUungd+Oh0juS2Jl3yQ7mPlVfsgr10NLSsqltLXIECi9ExY4d1cTtmf9aN8E" crossorigin="anonymous">
|
||||
<!-- <script src="https://cdn.datatables.net/v/bs5/jq-3.6.0/dt-1.12.1/datatables.min.js" integrity="sha384-eU1uLDC5C4YCIouMauJZjbrnSmIiICWWAPdnZjRkNnuDxG+eJFN/EhW5GlKPAIVl" crossorigin="anonymous"></script>
|
||||
-->
|
||||
<script src="https://cdn.datatables.net/v/bs5/jq-3.6.0/dt-1.12.1/datatables.js"></script>
|
||||
<title>
|
||||
Index timeline
|
||||
</title>
|
||||
</head>
|
||||
<body>
|
||||
<div class="container px-4 py-5">
|
||||
<nav aria-label="breadcrumb">
|
||||
<ol class="breadcrumb">
|
||||
<li class="breadcrumb-item active" aria-current="page"><a href="/timeline/">Timeline</a></li>
|
||||
</ol>
|
||||
</nav>
|
||||
<h1 class="py-5">
|
||||
Index timeline
|
||||
</h1>
|
||||
<p>
|
||||
This page lists all package versions and revisions in the index.
|
||||
</p>
|
||||
<table class="table table-hover">
|
||||
<thead>
|
||||
<tr>
|
||||
<th>Package</th>
|
||||
<th>Version/Revision</th>
|
||||
<th>Added on</th>
|
||||
<th>Source</th>
|
||||
</th>
|
||||
</thead>
|
||||
<tbody>
|
||||
{{#entries}}
|
||||
{{#TimelinePageEntryPackage}}
|
||||
<tr>
|
||||
<td class="col-sm-2"><a href="/package/{{timelinePageEntryPkgId}}">{{timelinePageEntryPkgId}}</a></td>
|
||||
<td class="col-sm-1">Version</td>
|
||||
<td class="col-sm-3" data-order="{{timelinePageEntryTimestampPosix}}">{{timelinePageEntryTimestamp}}</td>
|
||||
<td class="col-sm-6">
|
||||
<dl class="row">
|
||||
{{#timelinePageEntrySource}}
|
||||
{{> packageVersionSource}}
|
||||
{{/timelinePageEntrySource}}
|
||||
</dl>
|
||||
</td>
|
||||
</tr>
|
||||
{{/TimelinePageEntryPackage}}
|
||||
{{#TimelinePageEntryRevision}}
|
||||
<tr>
|
||||
<td>{{timelinePageEntryPkgId}}</td>
|
||||
<td>Revision</td>
|
||||
<td data-order="{{timelinePageEntryTimestampPosix}}">{{timelinePageEntryTimestamp}}</td>
|
||||
<td></td>
|
||||
</tr>
|
||||
{{/TimelinePageEntryRevision}}
|
||||
{{/entries}}
|
||||
</tbody>
|
||||
</table>
|
||||
</div>
|
||||
<script>
|
||||
$(document).ready(function () {
|
||||
const table = $('table').DataTable({
|
||||
order: [[2, 'desc']],
|
||||
lengthMenu: [ [50, 100, 500, -1], [50, 100, 500, "All"] ]
|
||||
})
|
||||
const urlParams = new URLSearchParams(location.search)
|
||||
if (urlParams.has('q')) {
|
||||
table.search(urlParams.get('q')).draw()
|
||||
}
|
||||
});
|
||||
</script>
|
||||
</body>
|
||||
</html>
|
Loading…
Reference in New Issue
Block a user