2022-03-28 07:53:39 +03:00
{- # OPTIONS_GHC - Wno - name - shadowing # -}
module Foliage.CmdBuild ( cmdBuild ) where
import Codec.Archive.Tar qualified as Tar
import Codec.Archive.Tar.Entry qualified as Tar
import Codec.Compression.GZip qualified as GZip
2022-03-30 07:56:17 +03:00
import Control.Monad ( unless , when )
2022-03-28 07:53:39 +03:00
import Data.ByteString.Lazy qualified as BSL
import Data.Foldable ( for_ )
2022-05-16 09:39:53 +03:00
import Data.List ( isPrefixOf , sortOn )
2022-03-29 12:10:19 +03:00
import Data.Maybe ( fromMaybe )
2022-03-28 07:53:39 +03:00
import Data.Traversable ( for )
import Development.Shake
import Development.Shake.FilePath
2022-05-18 07:12:20 +03:00
import Distribution.Parsec ( simpleParsec )
2022-03-28 07:53:39 +03:00
import Foliage.HackageSecurity
import Foliage.Meta
import Foliage.Options
import Foliage.Package
2022-05-16 09:39:53 +03:00
import Foliage.RemoteAsset ( addBuiltinRemoteAssetRule , remoteAssetNeed )
2022-03-28 07:53:39 +03:00
import Foliage.Shake
import Foliage.Shake.Oracle
import Foliage.Time qualified as Time
2022-05-18 07:12:20 +03:00
import Foliage.UpdateCabalFile ( rewritePackageVersion )
2022-03-28 07:53:39 +03:00
import System.Directory qualified as IO
cmdBuild :: BuildOptions -> IO ()
2022-03-29 12:10:19 +03:00
cmdBuild
BuildOptions
{ buildOptsKeysPath = keysPath ,
buildOptsCurrentTime = mCurrentTime ,
buildOptsInputDir = inputDir ,
buildOptsOutputDir = outputDir
} = do
ks <- IO . doesDirectoryExist keysPath
unless ks $ do
2022-05-16 09:39:53 +03:00
putStrLn $ " You don't seem to have created a set of TUF keys. I will create one in " <> keysPath
2022-03-29 12:10:19 +03:00
createKeys keysPath
let opts =
shakeOptions
{ shakeChange = ChangeDigest ,
2022-05-16 09:39:53 +03:00
shakeFiles = " _cache " ,
shakeVerbosity = Info
2022-03-29 12:10:19 +03:00
}
2022-03-28 07:53:39 +03:00
2022-03-29 12:10:19 +03:00
shake opts $ do
2022-05-16 09:39:53 +03:00
addBuiltinRemoteAssetRule ( " _cache " </> " downloads " )
2022-03-29 12:10:19 +03:00
--
-- Oracles
--
getCurrentTime <- addOracle $ \ GetCurrentTime ->
case mCurrentTime of
Nothing -> do
t <- Time . truncateSeconds <$> liftIO Time . getCurrentTime
2022-05-16 09:39:53 +03:00
putInfo $ " Current time set to " <> Time . iso8601Show t <> " . You can set a fixed time using the --current-time option. "
2022-03-29 12:10:19 +03:00
return t
Just t -> do
2022-05-16 09:39:53 +03:00
putInfo $ " Current time set to " <> Time . iso8601Show t <> " . "
2022-03-29 12:10:19 +03:00
return t
2022-05-16 09:39:53 +03:00
getExpiryTime <- addOracleCache $ \ GetExpiryTime -> do
2022-03-29 12:10:19 +03:00
t <- Time . addUTCTime ( Time . nominalDay * 365 ) <$> getCurrentTime GetCurrentTime
2022-05-16 09:39:53 +03:00
putInfo $ " Expiry time set to " <> Time . iso8601Show t <> " (a year from now). "
2022-03-29 12:10:19 +03:00
return t
2022-05-19 09:42:41 +03:00
getPackageVersionMeta <- addOracleCache $ \ ( GetPackageVersionMeta pkgId @ PackageId { pkgName , pkgVersion } ) -> do
meta <- readPackageVersionMeta' $ inputDir </> pkgName </> pkgVersion </> " meta.toml "
2022-05-16 12:23:18 +03:00
-- Here we do some validation of the package metadata. We could
-- fine a better place for it.
case meta of
2022-05-19 09:42:41 +03:00
PackageVersionMeta { packageVersionRevisions , packageVersionTimestamp = Nothing }
| not ( null packageVersionRevisions ) -> do
2022-05-16 12:23:18 +03:00
putError $
" Package " <> pkgIdToString pkgId
<> " has cabal file revisions but the original package has no timestamp. This combination doesn't make sense. Either add a timestamp on the original package or remove the revisions "
fail " invalid package metadata "
2022-05-19 09:42:41 +03:00
PackageVersionMeta { packageVersionRevisions , packageVersionTimestamp = Just pkgTs }
| any ( ( < pkgTs ) . revisionTimestamp ) packageVersionRevisions -> do
2022-05-16 12:23:18 +03:00
putError $
" Package " <> pkgIdToString pkgId
<> " has a revision with timestamp earlier than the package itself. Adjust the timestamps so that all revisions come after the original package "
fail " invalid package metadata "
_ ->
return meta
2022-03-29 12:10:19 +03:00
2022-05-16 09:39:53 +03:00
preparePackageSource <- addOracleCache $ \ ( PreparePackageSource pkgId @ PackageId { pkgName , pkgVersion } ) -> do
2022-05-19 09:42:41 +03:00
PackageVersionMeta { packageVersionSource , packageVersionForce } <- getPackageVersionMeta ( GetPackageVersionMeta pkgId )
2022-03-29 12:10:19 +03:00
2022-04-01 04:08:33 +03:00
let srcDir = " _cache " </> " packages " </> pkgName </> pkgVersion
2022-03-29 12:10:19 +03:00
2022-04-01 04:08:33 +03:00
-- FIXME too much rework?
-- this action only depends on the tarball and the package metadata
-- delete everything inside the package source tree
liftIO $ do
-- FIXME this should only delete inside srcDir but apparently
-- also deletes srcDir itself
removeFiles srcDir [ " //* " ]
IO . createDirectoryIfMissing True srcDir
2022-05-19 09:42:41 +03:00
case packageVersionSource of
2022-04-01 04:08:33 +03:00
TarballSource url mSubdir -> do
2022-05-16 09:39:53 +03:00
tarballPath <- remoteAssetNeed url
2022-04-01 04:08:33 +03:00
withTempDir $ \ tmpDir -> do
cmd_ [ " tar " , " xzf " , tarballPath , " -C " , tmpDir ]
2022-03-29 12:10:19 +03:00
2022-04-01 04:08:33 +03:00
-- Special treatment of top-level directory: we remove it
--
-- Note: Don't let shake look into tmpDir! it will cause
-- unnecessary rework because tmpDir is always new
ls <- liftIO $ IO . getDirectoryContents tmpDir
let ls' = filter ( not . all ( == '.' ) ) ls
let fix1 = case ls' of [ l ] -> ( </> l ) ; _ -> id
fix2 = case mSubdir of Just s -> ( </> s ) ; _ -> id
tdir = fix2 $ fix1 tmpDir
cmd_ [ " cp " , " --recursive " , " --no-target-directory " , " --dereference " , tdir , srcDir ]
-- Delete cabal.project files if present
projectFiles <- liftIO $ filter ( " cabal.project " ` isPrefixOf ` ) <$> IO . getDirectoryContents srcDir
unless ( null projectFiles ) $ do
2022-05-16 09:39:53 +03:00
putWarn $ " Deleting cabal project files from " ++ srcDir
2022-04-01 04:08:33 +03:00
liftIO $ for_ projectFiles $ IO . removeFile . ( srcDir </> )
2022-03-30 10:05:08 +03:00
2022-04-01 08:01:45 +03:00
applyPatches inputDir srcDir pkgId
2022-05-19 09:42:41 +03:00
when packageVersionForce $
2022-03-31 10:02:00 +03:00
forcePackageVersion srcDir pkgId
2022-03-30 10:05:08 +03:00
return srcDir
2022-03-29 12:10:19 +03:00
2022-05-16 09:39:53 +03:00
getPackages <- addOracleCache $ \ GetPackages -> do
2022-03-29 12:10:19 +03:00
metaFiles <- getDirectoryFiles inputDir [ " */*/meta.toml " ]
2022-04-13 10:47:38 +03:00
when ( null metaFiles ) $ do
putError $
unlines
[ " We could not find any package metadata file (i.e. _sources/<name>/<version>/meta.toml) " ,
" Make sure you are passing the right input directory. The default input directory is _sources "
]
fail " no package metadata found "
2022-03-29 12:10:19 +03:00
return $
[ PackageId pkgName pkgVersion
| path <- metaFiles ,
let [ pkgName , pkgVersion , _ ] = splitDirectories path
]
--
-- Entrypoint
--
-- This triggers the whole chain of TUF metadata
want [ outputDir </> " timestamp.json " ]
-- This build the current index entry for all packages
action $ do
pkgIds <- getPackages GetPackages
need
[ outputDir </> " index " </> pkgName </> pkgVersion </> pkgName <.> " cabal "
| PackageId pkgName pkgVersion <- pkgIds
]
--
-- timestamp.json
--
outputDir </> " timestamp.json " %> \ path -> do
snapshotInfo <- computeFileInfoSimple' ( outputDir </> " snapshot.json " )
expires <- getExpiryTime GetExpiryTime
let timestamp =
Timestamp
{ timestampVersion = FileVersion 1 ,
timestampExpires = FileExpires ( Just expires ) ,
timestampInfoSnapshot = snapshotInfo
}
keys <- readKeysAt ( keysPath </> " timestamp " )
let timestampSigned = withSignatures hackageRepoLayout keys timestamp
2022-05-16 11:54:27 +03:00
traced " writing " $
liftIO $ do
p <- makeAbsolute ( fromFilePath path )
writeJSON hackageRepoLayout p timestampSigned
2022-03-29 12:10:19 +03:00
--
-- snapshot.json
--
outputDir </> " snapshot.json " %> \ path -> do
rootInfo <- computeFileInfoSimple' ( outputDir </> " root.json " )
mirrorsInfo <- computeFileInfoSimple' ( outputDir </> " mirrors.json " )
tarInfo <- computeFileInfoSimple' ( outputDir </> " 01-index.tar " )
tarGzInfo <- computeFileInfoSimple' ( outputDir </> " 01-index.tar.gz " )
expires <- getExpiryTime GetExpiryTime
let snapshot =
Snapshot
{ snapshotVersion = FileVersion 1 ,
snapshotExpires = FileExpires ( Just expires ) ,
snapshotInfoRoot = rootInfo ,
snapshotInfoMirrors = mirrorsInfo ,
snapshotInfoTar = Just tarInfo ,
snapshotInfoTarGz = tarGzInfo
}
keys <- readKeysAt ( keysPath </> " snapshot " )
let snapshotSigned = withSignatures hackageRepoLayout keys snapshot
2022-05-16 11:54:27 +03:00
traced " writing " $
liftIO $ do
p <- makeAbsolute ( fromFilePath path )
writeJSON hackageRepoLayout p snapshotSigned
2022-03-29 12:10:19 +03:00
--
-- root.json
--
outputDir </> " root.json " %> \ path -> do
expires <- getExpiryTime GetExpiryTime
privateKeysRoot <- readKeysAt ( keysPath </> " root " )
privateKeysTarget <- readKeysAt ( keysPath </> " target " )
privateKeysSnapshot <- readKeysAt ( keysPath </> " snapshot " )
privateKeysTimestamp <- readKeysAt ( keysPath </> " timestamp " )
privateKeysMirrors <- readKeysAt ( keysPath </> " mirrors " )
let root =
Root
{ rootVersion = FileVersion 1 ,
rootExpires = FileExpires ( Just expires ) ,
rootKeys =
fromKeys $
concat
[ privateKeysRoot ,
privateKeysTarget ,
privateKeysSnapshot ,
privateKeysTimestamp ,
privateKeysMirrors
] ,
rootRoles =
RootRoles
{ rootRolesRoot =
RoleSpec
{ roleSpecKeys = map somePublicKey privateKeysRoot ,
roleSpecThreshold = KeyThreshold 2
} ,
rootRolesSnapshot =
RoleSpec
{ roleSpecKeys = map somePublicKey privateKeysSnapshot ,
roleSpecThreshold = KeyThreshold 1
} ,
rootRolesTargets =
RoleSpec
{ roleSpecKeys = map somePublicKey privateKeysTarget ,
roleSpecThreshold = KeyThreshold 1
} ,
rootRolesTimestamp =
RoleSpec
{ roleSpecKeys = map somePublicKey privateKeysTimestamp ,
roleSpecThreshold = KeyThreshold 1
} ,
rootRolesMirrors =
RoleSpec
{ roleSpecKeys = map somePublicKey privateKeysMirrors ,
roleSpecThreshold = KeyThreshold 1
}
}
}
keys <- readKeysAt ( keysPath </> " root " )
let signedRoot = withSignatures hackageRepoLayout keys root
2022-05-16 11:54:27 +03:00
traced " writing " $
liftIO $ do
p <- makeAbsolute ( fromFilePath path )
writeJSON hackageRepoLayout p signedRoot
2022-03-29 12:10:19 +03:00
--
-- mirrors.json
--
outputDir </> " mirrors.json " %> \ path -> do
expires <- getExpiryTime GetExpiryTime
let mirrors =
Mirrors
{ mirrorsVersion = FileVersion 1 ,
mirrorsExpires = FileExpires ( Just expires ) ,
mirrorsMirrors = []
}
keys <- readKeysAt ( keysPath </> " mirrors " )
let signedMirrors = withSignatures hackageRepoLayout keys mirrors
2022-05-16 11:54:27 +03:00
traced " writing " $
liftIO $ do
p <- makeAbsolute ( fromFilePath path )
writeJSON hackageRepoLayout p signedMirrors
2022-03-29 12:10:19 +03:00
--
-- 01-index.tar
--
outputDir </> " 01-index.tar " %> \ path -> do
pkgIds <- getPackages GetPackages
entries <-
2022-05-16 11:54:27 +03:00
flip foldMap pkgIds $ \ pkgId -> do
let PackageId { pkgName , pkgVersion } = pkgId
2022-05-19 09:42:41 +03:00
PackageVersionMeta { packageVersionTimestamp , packageVersionRevisions } <- getPackageVersionMeta ( GetPackageVersionMeta pkgId )
2022-05-16 11:54:27 +03:00
srcDir <- preparePackageSource $ PreparePackageSource pkgId
now <- getCurrentTime GetCurrentTime
-- original cabal file
cabalEntry <-
mkTarEntry
( srcDir </> pkgName <.> " cabal " )
( pkgName </> pkgVersion </> pkgName <.> " cabal " )
2022-05-19 09:42:41 +03:00
( fromMaybe now packageVersionTimestamp )
2022-05-16 11:54:27 +03:00
-- package.json
packageEntry <-
mkTarEntry
( outputDir </> " index " </> pkgName </> pkgVersion </> " package.json " )
( pkgName </> pkgVersion </> " package.json " )
2022-05-19 09:42:41 +03:00
( fromMaybe now packageVersionTimestamp )
2022-05-16 11:54:27 +03:00
-- revised cabal files
2022-05-19 09:42:41 +03:00
revisionEntries <- for packageVersionRevisions $ \ RevisionMeta { revisionNumber , revisionTimestamp } ->
2022-05-16 11:54:27 +03:00
mkTarEntry
( inputDir </> pkgName </> pkgVersion </> " revisions " </> show revisionNumber <.> " cabal " )
( pkgName </> pkgVersion </> pkgName <.> " cabal " )
2022-05-16 12:23:18 +03:00
revisionTimestamp
2022-05-16 11:54:27 +03:00
return $ cabalEntry : packageEntry : revisionEntries
traced " writing " $ liftIO $ BSL . writeFile path $ Tar . write ( sortOn Tar . entryTime entries )
2022-03-29 12:10:19 +03:00
--
-- 01-index.tar.gz
--
outputDir </> " 01-index.tar.gz " %> \ path -> do
tar <- readFileByteStringLazy ( outputDir </> " 01-index.tar " )
2022-05-16 11:54:27 +03:00
traced " writing " $ liftIO $ BSL . writeFile path ( GZip . compress tar )
2022-03-29 12:10:19 +03:00
--
2022-04-01 04:08:33 +03:00
-- index cabal files
--
-- these come either from the package source or the revision files
2022-03-29 12:10:19 +03:00
--
outputDir </> " index/*/*/*.cabal " %> \ path -> do
let [ _ , _ , pkgName , pkgVersion , _ ] = splitDirectories path
let pkgId = PackageId pkgName pkgVersion
2022-05-19 09:42:41 +03:00
meta <- getPackageVersionMeta $ GetPackageVersionMeta pkgId
2022-03-29 12:10:19 +03:00
case latestRevisionNumber meta of
Nothing -> do
2022-04-01 04:08:33 +03:00
srcDir <- preparePackageSource $ PreparePackageSource pkgId
2022-03-29 12:10:19 +03:00
copyFileChanged ( srcDir </> pkgName <.> " cabal " ) path
Just revNum -> do
2022-04-01 04:08:33 +03:00
let revisionFile = inputDir </> pkgName </> pkgVersion </> " revisions " </> show revNum <.> " cabal "
copyFileChanged revisionFile path
2022-03-29 12:10:19 +03:00
--
-- index package files (only depends on the source distribution)
--
outputDir </> " index/*/*/package.json " %> \ path -> do
let [ _ , _ , pkgName , pkgVersion , _ ] = splitDirectories path
let packagePath = " package " </> pkgName <> " - " <> pkgVersion <.> " tar.gz "
let targetPath = rootPath $ fromUnrootedFilePath packagePath
targetFileInfo <- computeFileInfoSimple' ( " _repo " </> packagePath )
expires <- getExpiryTime GetExpiryTime
let targets =
Targets
{ targetsVersion = FileVersion 1 ,
targetsExpires = FileExpires ( Just expires ) ,
targetsTargets = fromList [ ( TargetPathRepo targetPath , targetFileInfo ) ] ,
targetsDelegations = Nothing
}
keys <- readKeysAt ( keysPath </> " target " )
let signedTargets = withSignatures hackageRepoLayout keys targets
liftIO $ do
p <- makeAbsolute ( fromFilePath path )
writeJSON hackageRepoLayout p signedTargets
--
2022-04-01 04:08:33 +03:00
-- source distributions, including patching
2022-03-29 12:10:19 +03:00
--
outputDir </> " package/*.tar.gz " %> \ path -> do
let [ _ , _ , filename ] = splitDirectories path
2022-03-30 10:05:08 +03:00
let Just pkgId = parsePkgId <$> stripExtension " tar.gz " filename
2022-03-29 12:10:19 +03:00
2022-04-01 04:08:33 +03:00
srcDir <- preparePackageSource $ PreparePackageSource pkgId
putInfo srcDir
2022-03-29 12:10:19 +03:00
withTempDir $ \ tmpDir -> do
2022-04-01 04:08:33 +03:00
putInfo $ " Creating source distribution for " <> pkgIdToString pkgId
2022-03-29 12:10:19 +03:00
cmd_ Shell ( Cwd srcDir ) ( FileStdout path ) ( " cabal sdist --ignore-project --output-directory " <> tmpDir )
-- check cabal sdist has produced a single tarball with the
-- expected name
ls <- liftIO $ IO . getDirectoryContents tmpDir
let ls' = filter ( not . all ( == '.' ) ) ls
case ls' of
[ l ]
| l == filename ->
cmd_ Shell [ " mv " , tmpDir </> l , path ]
[ l ]
| l /= filename ->
fail $ " cabal sdist produced a different package. I expected " <> filename <> " but found " <> l
_ ->
fail $ " cabal sdist for " <> pkgIdToString pkgId <> " did not produce a single tarball! "
2022-05-16 09:39:53 +03:00
putStrLn $ " All done. The repository is now available in " <> outputDir <> " . "
2022-04-01 04:08:33 +03:00
2022-03-28 07:53:39 +03:00
mkTarEntry :: FilePath -> [ Char ] -> UTCTime -> Action Tar . Entry
mkTarEntry filePath indexPath timestamp = do
let Right tarPath = Tar . toTarPath False indexPath
contents <- readFileByteStringLazy filePath
return
( Tar . fileEntry tarPath contents )
{ Tar . entryTime = floor $ Time . utcTimeToPOSIXSeconds timestamp ,
Tar . entryOwnership =
Tar . Ownership
{ Tar . ownerName = " foliage " ,
Tar . groupName = " foliage " ,
Tar . ownerId = 0 ,
Tar . groupId = 0
}
}
2022-03-31 10:02:00 +03:00
2022-04-01 04:08:33 +03:00
applyPatches :: [ Char ] -> FilePath -> PackageId -> Action ()
2022-03-31 10:02:00 +03:00
applyPatches inputDir srcDir PackageId { pkgName , pkgVersion } = do
let patchesDir = inputDir </> pkgName </> pkgVersion </> " patches "
hasPatches <- doesDirectoryExist patchesDir
when hasPatches $ do
2022-04-01 04:08:33 +03:00
patchfiles <- getDirectoryFiles patchesDir [ " *.patch " ]
for_ patchfiles $ \ patchfile -> do
let patch = patchesDir </> patchfile
cmd_ Shell ( Cwd srcDir ) ( FileStdin patch ) " patch -p1 "
2022-03-31 10:02:00 +03:00
forcePackageVersion :: FilePath -> PackageId -> Action ()
forcePackageVersion srcDir PackageId { pkgName , pkgVersion } = do
let cabalFilePath = srcDir </> pkgName <.> " cabal "
2022-05-18 07:12:20 +03:00
let Just version = simpleParsec pkgVersion
liftIO $ rewritePackageVersion cabalFilePath version