diff --git a/ChangeLog.md b/ChangeLog.md index 87e64958..2aa9aea0 100644 --- a/ChangeLog.md +++ b/ChangeLog.md @@ -1,3 +1,7 @@ +## 0.6.0 + +* Upload bundle V2 stuff + ## 0.5.2 * Upload LTS to Hackage with the name LTSHaskell diff --git a/Stackage/CompleteBuild.hs b/Stackage/CompleteBuild.hs index 80693dad..5f4735e6 100644 --- a/Stackage/CompleteBuild.hs +++ b/Stackage/CompleteBuild.hs @@ -8,6 +8,7 @@ module Stackage.CompleteBuild , completeBuild , justCheck , justUploadNightly + , getStackageAuthToken ) where import Control.Concurrent (threadDelay) @@ -39,6 +40,7 @@ data BuildFlags = BuildFlags , bfEnableExecDyn :: !Bool , bfVerbose :: !Bool , bfSkipCheck :: !Bool + , bfUploadV2 :: !Bool } deriving (Show) data BuildType = Nightly | LTS BumpType @@ -57,6 +59,8 @@ data Settings = Settings , setArgs :: Text -> UploadBundle -> UploadBundle , postBuild :: IO () , distroName :: Text -- ^ distro name on Hackage + , snapshotType :: SnapshotType + , bundleDest :: FilePath } nightlyPlanFile :: Text -- ^ day @@ -81,6 +85,8 @@ nightlySettings day plan' = Settings , plan = plan' , postBuild = return () , distroName = "Stackage" + , snapshotType = STNightly + , bundleDest = fpFromText $ "stackage-nightly-" ++ day ++ ".bundle" } where slug' = "nightly-" ++ day @@ -142,6 +148,10 @@ getSettings man (LTS bumpType) = do putStrLn "Pushing to Git repository" git ["push"] , distroName = "LTSHaskell" + , snapshotType = + case new of + LTSVer x y -> STLTS x y + , bundleDest = fpFromText $ "stackage-lts-" ++ tshow new ++ ".bundle" } data LTSVer = LTSVer !Int !Int @@ -231,10 +241,19 @@ completeBuild buildType buildFlags = withManager tlsManagerSettings $ \man -> do checkBuildPlan plan putStrLn "Performing build" - performBuild (getPerformBuild buildFlags settings) >>= mapM_ putStrLn + let pb = getPerformBuild buildFlags settings + performBuild pb >>= mapM_ putStrLn + + putStrLn $ "Creating bundle (v2) at: " ++ fpToText bundleDest + createBundleV2 CreateBundleV2 + { cb2Plan = plan + , cb2Type = snapshotType + , cb2DocsDir = pbDocDir pb + , cb2Dest = bundleDest + } when (bfDoUpload buildFlags) $ - finallyUpload settings man + finallyUpload (bfUploadV2 buildFlags) settings man justUploadNightly :: Text -- ^ nightly date @@ -242,41 +261,63 @@ justUploadNightly justUploadNightly day = do plan <- decodeFileEither (fpToString $ nightlyPlanFile day) >>= either throwM return - withManager tlsManagerSettings $ finallyUpload $ nightlySettings day plan + withManager tlsManagerSettings $ finallyUpload False $ nightlySettings day plan + +getStackageAuthToken :: IO Text +getStackageAuthToken = do + mtoken <- lookupEnv "STACKAGE_AUTH_TOKEN" + case mtoken of + Nothing -> decodeUtf8 <$> readFile "/auth-token" + Just token -> return $ pack token -- | The final part of the complete build process: uploading a bundle, -- docs and a distro to hackage. -finallyUpload :: Settings -> Manager -> IO () -finallyUpload settings@Settings{..} man = do +finallyUpload :: Bool -- ^ use v2 upload + -> Settings -> Manager -> IO () +finallyUpload useV2 settings@Settings{..} man = do putStrLn "Uploading bundle to Stackage Server" - mtoken <- lookupEnv "STACKAGE_AUTH_TOKEN" - token <- - case mtoken of - Nothing -> decodeUtf8 <$> readFile "/auth-token" - Just token -> return $ pack token + token <- getStackageAuthToken - now <- epochTime - let ghcVer = display $ siGhcVersion $ bpSystemInfo plan - (ident, mloc) <- flip uploadBundle man $ setArgs ghcVer def - { ubContents = serverBundle now (title ghcVer) slug plan - , ubAuthToken = token - } - putStrLn $ "New ident: " ++ unSnapshotIdent ident - forM_ mloc $ \loc -> - putStrLn $ "Track progress at: " ++ loc + if useV2 + then do + res <- flip uploadBundleV2 man UploadBundleV2 + { ub2Server = def + , ub2AuthToken = token + , ub2Bundle = bundleDest + } + putStrLn $ "New snapshot available at: " ++ res + else do + now <- epochTime + let ghcVer = display $ siGhcVersion $ bpSystemInfo plan + (ident, mloc) <- flip uploadBundle man $ setArgs ghcVer def + { ubContents = serverBundle now (title ghcVer) slug plan + , ubAuthToken = token + } + putStrLn $ "New ident: " ++ unSnapshotIdent ident + forM_ mloc $ \loc -> + putStrLn $ "Track progress at: " ++ loc + + putStrLn "Uploading docs to Stackage Server" + res1 <- tryAny $ uploadDocs UploadDocs + { udServer = def + , udAuthToken = token + , udDocs = pbDocDir pb + , udSnapshot = ident + } man + putStrLn $ "Doc upload response: " ++ tshow res1 + + putStrLn "Uploading doc map" + tryAny (uploadDocMap UploadDocMap + { udmServer = def + , udmAuthToken = token + , udmSnapshot = ident + , udmDocDir = pbDocDir pb + , udmPlan = plan + } man) >>= print postBuild `catchAny` print - putStrLn "Uploading docs to Stackage Server" - res1 <- uploadDocs UploadDocs - { udServer = def - , udAuthToken = token - , udDocs = pbDocDir pb - , udSnapshot = ident - } man - putStrLn $ "Doc upload response: " ++ tshow res1 - ecreds <- tryIO $ readFile "/hackage-creds" case map encodeUtf8 $ words $ decodeUtf8 $ either (const "") id ecreds of [username, password] -> do @@ -284,14 +325,5 @@ finallyUpload settings@Settings{..} man = do res2 <- uploadHackageDistroNamed distroName plan username password man putStrLn $ "Distro upload response: " ++ tshow res2 _ -> putStrLn "No creds found, skipping Hackage distro upload" - - putStrLn "Uploading doc map" - uploadDocMap UploadDocMap - { udmServer = def - , udmAuthToken = token - , udmSnapshot = ident - , udmDocDir = pbDocDir pb - , udmPlan = plan - } man >>= print where pb = getPerformBuild (error "finallyUpload.buildFlags") settings diff --git a/Stackage/PerformBuild.hs b/Stackage/PerformBuild.hs index 2b333044..9ed578b9 100644 --- a/Stackage/PerformBuild.hs +++ b/Stackage/PerformBuild.hs @@ -495,16 +495,6 @@ singleBuild pb@PerformBuild {..} registeredPackages SingleBuild {..} = renameOrCopy :: FilePath -> FilePath -> IO () renameOrCopy src dest = rename src dest `catchIO` \_ -> copyDir src dest -copyDir :: FilePath -> FilePath -> IO () -copyDir src dest = - runResourceT $ sourceDirectoryDeep False src $$ mapM_C go - where - src' = src > "" - go fp = forM_ (F.stripPrefix src' fp) $ \suffix -> do - let dest' = dest > suffix - liftIO $ createTree $ parent dest' - sourceFile fp $$ (sinkFile dest' :: Sink ByteString (ResourceT IO) ()) - copyBuiltInHaddocks :: FilePath -> IO () copyBuiltInHaddocks docdir = do mghc <- findExecutable "ghc" diff --git a/Stackage/Prelude.hs b/Stackage/Prelude.hs index ab2187fc..28fff061 100644 --- a/Stackage/Prelude.hs +++ b/Stackage/Prelude.hs @@ -20,6 +20,9 @@ import Distribution.Version as X (Version (..), VersionRange) import Distribution.Version as X (withinRange) import qualified Distribution.Version as C +import Filesystem (createTree) +import Filesystem.Path (parent) +import qualified Filesystem.Path as F unPackageName :: PackageName -> Text unPackageName (PackageName str) = pack str @@ -101,3 +104,13 @@ topologicalSort toFinal toDeps = data TopologicalSortException key = NoEmptyDeps (Map key (Set key)) deriving (Show, Typeable) instance (Show key, Typeable key) => Exception (TopologicalSortException key) + +copyDir :: FilePath -> FilePath -> IO () +copyDir src dest = + runResourceT $ sourceDirectoryDeep False src $$ mapM_C go + where + src' = src > "" + go fp = forM_ (F.stripPrefix src' fp) $ \suffix -> do + let dest' = dest > suffix + liftIO $ createTree $ parent dest' + sourceFile fp $$ (sinkFile dest' :: Sink ByteString (ResourceT IO) ()) diff --git a/Stackage/ServerBundle.hs b/Stackage/ServerBundle.hs index 6cdf5cb4..5aedb090 100644 --- a/Stackage/ServerBundle.hs +++ b/Stackage/ServerBundle.hs @@ -7,21 +7,31 @@ module Stackage.ServerBundle , epochTime , bpAllPackages , docsListing + , createBundleV2 + , CreateBundleV2 (..) + , SnapshotType (..) + , writeIndexStyle + , DocMap + , PackageDocs (..) ) where import qualified Codec.Archive.Tar as Tar import qualified Codec.Archive.Tar.Entry as Tar import qualified Codec.Compression.GZip as GZip import qualified Data.Map as M +import Data.Aeson (ToJSON (..), (.=), object, FromJSON (..), (.:), withObject) +import System.IO.Temp (withTempDirectory) import qualified Data.Yaml as Y -import Filesystem (isFile) +import Filesystem (isFile, getWorkingDirectory, listDirectory, isDirectory, canonicalizePath) import Foreign.C.Types (CTime (CTime)) import Stackage.BuildConstraints import Stackage.BuildPlan import Stackage.Prelude +import System.IO.Temp (withTempDirectory) import qualified System.PosixCompat.Time as PC import qualified Text.XML as X import Text.XML.Cursor +import System.PosixCompat.Files (createSymbolicLink) -- | Get current time epochTime :: IO Tar.EpochTime @@ -73,13 +83,30 @@ serverBundle time title slug bp@BuildPlan {..} = GZip.compress $ Tar.write map (\(PackageName name) -> name) (M.keys $ siCorePackages bpSystemInfo) +-- | Package name is key +type DocMap = Map Text PackageDocs +data PackageDocs = PackageDocs + { pdVersion :: Text + , pdModules :: Map Text [Text] + -- ^ module name, path + } +instance ToJSON PackageDocs where + toJSON PackageDocs {..} = object + [ "version" .= pdVersion + , "modules" .= pdModules + ] +instance FromJSON PackageDocs where + parseJSON = withObject "PackageDocs" $ \o -> PackageDocs + <$> o .: "version" + <*> o .: "modules" + docsListing :: BuildPlan -> FilePath -- ^ docs directory - -> IO ByteString + -> IO DocMap docsListing bp docsDir = - fmap (Y.encode . fold) $ mapM go $ mapToList $ bpAllPackages bp + fmap fold $ mapM go $ mapToList $ bpAllPackages bp where - go :: (PackageName, Version) -> IO (Map Text Y.Value) + go :: (PackageName, Version) -> IO DocMap go (package, version) = do -- handleAny (const $ return mempty) $ do let dirname = fpFromText (concat [ display package @@ -107,8 +134,138 @@ docsListing bp docsDir = return $ if e then asMap $ singletonMap name [fpToText dirname, href] else mempty - return $ singletonMap (display package) $ Y.object - [ "version" Y..= display version - , "modules" Y..= m - ] + return $ singletonMap (display package) $ PackageDocs + { pdVersion = display version + , pdModules = m + } else return mempty + +data SnapshotType = STNightly + | STLTS !Int !Int -- ^ major, minor + deriving (Show, Read, Eq, Ord) + +instance ToJSON SnapshotType where + toJSON STNightly = object + [ "type" .= asText "nightly" + ] + toJSON (STLTS major minor) = object + [ "type" .= asText "lts" + , "major" .= major + , "minor" .= minor + ] +instance FromJSON SnapshotType where + parseJSON = withObject "SnapshotType" $ \o -> do + t <- o .: "type" + case asText t of + "nightly" -> return STNightly + "lts" -> STLTS + <$> o .: "major" + <*> o .: "minor" + _ -> fail $ "Unknown type for SnapshotType: " ++ unpack t + +data CreateBundleV2 = CreateBundleV2 + { cb2Plan :: BuildPlan + , cb2Type :: SnapshotType + , cb2DocsDir :: FilePath + , cb2Dest :: FilePath + } + +-- | Create a V2 bundle, which contains the build plan, metadata, docs, and doc +-- map. +createBundleV2 :: CreateBundleV2 -> IO () +createBundleV2 CreateBundleV2 {..} = do + docsDir <- canonicalizePath cb2DocsDir + docMap <- docsListing cb2Plan cb2DocsDir + + Y.encodeFile (fpToString $ docsDir > "build-plan.yaml") cb2Plan + Y.encodeFile (fpToString $ docsDir > "build-type.yaml") cb2Type + Y.encodeFile (fpToString $ docsDir > "docs-map.yaml") docMap + void $ writeIndexStyle Nothing cb2DocsDir + + currentDir <- getWorkingDirectory + files <- listDirectory docsDir + + let args = "cfJ" + : fpToString (currentDir > cb2Dest) + : "--dereference" + : map (fpToString . filename) files + cp = (proc "tar" args) { cwd = Just $ fpToString docsDir } + withCheckedProcess cp $ \ClosedStream Inherited Inherited -> return () + +writeIndexStyle :: Maybe Text -- ^ snapshot id + -> FilePath -- ^ docs dir + -> IO [String] +writeIndexStyle msnapid dir = do + dirs <- fmap sort + $ runResourceT + $ sourceDirectory dir + $$ filterMC (liftIO . isDirectory) + =$ mapC (fpToString . filename) + =$ sinkList + writeFile (dir > "index.html") $ mkIndex + (unpack <$> msnapid) + dirs + writeFile (dir > "style.css") styleCss + return dirs + +mkIndex :: Maybe String -> [String] -> String +mkIndex msnapid dirs = concat + [ "\n