mirror of
https://github.com/commercialhaskell/stackage-server.git
synced 2026-01-25 02:11:55 +01:00
Revert to previous pinned version of pantry
The new pantry version in lts-22.6 was not compatible with the database and/or config on the stackage server.
This commit is contained in:
parent
33e5cb2589
commit
5cb5668295
@ -2,6 +2,7 @@
|
|||||||
{-# LANGUAGE NoImplicitPrelude #-}
|
{-# LANGUAGE NoImplicitPrelude #-}
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
|
{-# LANGUAGE TypeOperators #-}
|
||||||
module Data.WebsiteContent
|
module Data.WebsiteContent
|
||||||
( WebsiteContent (..)
|
( WebsiteContent (..)
|
||||||
, StackRelease (..)
|
, StackRelease (..)
|
||||||
|
|||||||
@ -42,9 +42,9 @@ import Network.HTTP.Types (status200, status404)
|
|||||||
import Pantry (CabalFileInfo(..), DidUpdateOccur(..),
|
import Pantry (CabalFileInfo(..), DidUpdateOccur(..),
|
||||||
HpackExecutable(HpackBundled), PackageIdentifierRevision(..),
|
HpackExecutable(HpackBundled), PackageIdentifierRevision(..),
|
||||||
defaultCasaMaxPerRequest, defaultCasaRepoPrefix,
|
defaultCasaMaxPerRequest, defaultCasaRepoPrefix,
|
||||||
defaultPackageIndexConfig,
|
defaultHackageSecurityConfig, defaultSnapshotLocation)
|
||||||
defaultSnapshotLocation, withPantryConfig, PantryConfig)
|
import Pantry.Internal.Stackage (HackageTarballResult(..), PantryConfig(..),
|
||||||
import Pantry.Internal.Stackage (HackageTarballResult(..), forceUpdateHackageIndex,
|
Storage(..), forceUpdateHackageIndex,
|
||||||
getHackageTarball, packageTreeKey)
|
getHackageTarball, packageTreeKey)
|
||||||
import Path (parseAbsDir, toFilePath)
|
import Path (parseAbsDir, toFilePath)
|
||||||
import RIO
|
import RIO
|
||||||
@ -57,6 +57,7 @@ import RIO.Process (mkDefaultProcessContext)
|
|||||||
import qualified RIO.Set as Set
|
import qualified RIO.Set as Set
|
||||||
import qualified RIO.Text as T
|
import qualified RIO.Text as T
|
||||||
import RIO.Time
|
import RIO.Time
|
||||||
|
import Settings
|
||||||
import Stackage.Database.Github
|
import Stackage.Database.Github
|
||||||
import Stackage.Database.PackageInfo
|
import Stackage.Database.PackageInfo
|
||||||
import Stackage.Database.Query
|
import Stackage.Database.Query
|
||||||
@ -88,6 +89,11 @@ hoogleUrl n haddockBucketUrl = T.concat
|
|||||||
hackageDeprecatedUrl :: Request
|
hackageDeprecatedUrl :: Request
|
||||||
hackageDeprecatedUrl = "https://hackage.haskell.org/packages/deprecated.json"
|
hackageDeprecatedUrl = "https://hackage.haskell.org/packages/deprecated.json"
|
||||||
|
|
||||||
|
withStorage :: (Storage -> IO a) -> IO a
|
||||||
|
withStorage inner = do
|
||||||
|
as <- getAppSettings
|
||||||
|
withStackageDatabase False (appDatabase as) (\db -> inner (Storage (runDatabase db) id))
|
||||||
|
|
||||||
getStackageSnapshotsDir :: RIO StackageCron FilePath
|
getStackageSnapshotsDir :: RIO StackageCron FilePath
|
||||||
getStackageSnapshotsDir = do
|
getStackageSnapshotsDir = do
|
||||||
cron <- ask
|
cron <- ask
|
||||||
@ -151,52 +157,58 @@ stackageServerCron StackageCronOptions {..} = do
|
|||||||
catchIO (bindPortTCP 17834 "127.0.0.1") $
|
catchIO (bindPortTCP 17834 "127.0.0.1") $
|
||||||
const $ throwString "Stackage Cron loader process already running, exiting."
|
const $ throwString "Stackage Cron loader process already running, exiting."
|
||||||
connectionCount <- getNumCapabilities
|
connectionCount <- getNumCapabilities
|
||||||
lo <- logOptionsHandle stdout True
|
withStorage $ \storage -> do
|
||||||
stackageRootDir <- getAppUserDataDirectory "stackage"
|
lo <- logOptionsHandle stdout True
|
||||||
pantryRootDir <- parseAbsDir (stackageRootDir </> "pantry")
|
stackageRootDir <- getAppUserDataDirectory "stackage"
|
||||||
createDirectoryIfMissing True (toFilePath pantryRootDir)
|
pantryRootDir <- parseAbsDir (stackageRootDir </> "pantry")
|
||||||
gpdCache <- newIORef IntMap.empty
|
createDirectoryIfMissing True (toFilePath pantryRootDir)
|
||||||
defaultProcessContext <- mkDefaultProcessContext
|
updateRef <- newMVar True
|
||||||
aws <- do
|
cabalImmutable <- newIORef Map.empty
|
||||||
aws' <- newEnv discover
|
cabalMutable <- newIORef Map.empty
|
||||||
endpoint <- lookup "AWS_S3_ENDPOINT" <$> getEnvironment
|
gpdCache <- newIORef IntMap.empty
|
||||||
pure $ case endpoint of
|
defaultProcessContext <- mkDefaultProcessContext
|
||||||
Nothing -> aws'
|
aws <- do
|
||||||
Just ep -> configureService (setEndpoint True (BS8.pack ep) 443 Amazonka.S3.defaultService) aws'
|
aws' <- newEnv discover
|
||||||
withLogFunc (setLogMinLevel scoLogLevel lo) $ \logFunc -> do
|
endpoint <- lookup "AWS_S3_ENDPOINT" <$> getEnvironment
|
||||||
let cronWithPantryConfig :: HasLogFunc env => (PantryConfig -> RIO env a) -> RIO env a
|
pure $ case endpoint of
|
||||||
cronWithPantryConfig =
|
Nothing -> aws'
|
||||||
withPantryConfig
|
Just ep -> configureService (setEndpoint True (BS8.pack ep) 443 Amazonka.S3.defaultService) aws'
|
||||||
pantryRootDir
|
withLogFunc (setLogMinLevel scoLogLevel lo) $ \logFunc -> do
|
||||||
defaultPackageIndexConfig
|
let pantryConfig =
|
||||||
HpackBundled
|
PantryConfig
|
||||||
connectionCount
|
{ pcHackageSecurity = defaultHackageSecurityConfig
|
||||||
defaultCasaRepoPrefix
|
, pcHpackExecutable = HpackBundled
|
||||||
defaultCasaMaxPerRequest
|
, pcRootDir = pantryRootDir
|
||||||
defaultSnapshotLocation
|
, pcStorage = storage
|
||||||
|
, pcUpdateRef = updateRef
|
||||||
currentHoogleVersionId <- runRIO logFunc $ do
|
, pcParsedCabalFilesRawImmutable = cabalImmutable
|
||||||
cronWithPantryConfig $ \pantryConfig -> do
|
, pcParsedCabalFilesMutable = cabalMutable
|
||||||
|
, pcConnectionCount = connectionCount
|
||||||
|
, pcCasaRepoPrefix = defaultCasaRepoPrefix
|
||||||
|
, pcCasaMaxPerRequest = defaultCasaMaxPerRequest
|
||||||
|
, pcSnapshotLocation = defaultSnapshotLocation
|
||||||
|
}
|
||||||
|
currentHoogleVersionId <- runRIO logFunc $ do
|
||||||
runStackageMigrations' pantryConfig
|
runStackageMigrations' pantryConfig
|
||||||
getCurrentHoogleVersionIdWithPantryConfig pantryConfig
|
getCurrentHoogleVersionIdWithPantryConfig pantryConfig
|
||||||
let stackage pantryConfig =
|
let stackage =
|
||||||
StackageCron
|
StackageCron
|
||||||
{ scPantryConfig = pantryConfig
|
{ scPantryConfig = pantryConfig
|
||||||
, scStackageRoot = stackageRootDir
|
, scStackageRoot = stackageRootDir
|
||||||
, scProcessContext = defaultProcessContext
|
, scProcessContext = defaultProcessContext
|
||||||
, scLogFunc = logFunc
|
, scLogFunc = logFunc
|
||||||
, scForceFullUpdate = scoForceUpdate
|
, scForceFullUpdate = scoForceUpdate
|
||||||
, scCachedGPD = gpdCache
|
, scCachedGPD = gpdCache
|
||||||
, scEnvAWS = aws
|
, scEnvAWS = aws
|
||||||
, scDownloadBucketName = scoDownloadBucketName
|
, scDownloadBucketName = scoDownloadBucketName
|
||||||
, scDownloadBucketUrl = scoDownloadBucketUrl
|
, scDownloadBucketUrl = scoDownloadBucketUrl
|
||||||
, scUploadBucketName = scoUploadBucketName
|
, scUploadBucketName = scoUploadBucketName
|
||||||
, scSnapshotsRepo = scoSnapshotsRepo
|
, scSnapshotsRepo = scoSnapshotsRepo
|
||||||
, scReportProgress = scoReportProgress
|
, scReportProgress = scoReportProgress
|
||||||
, scCacheCabalFiles = scoCacheCabalFiles
|
, scCacheCabalFiles = scoCacheCabalFiles
|
||||||
, scHoogleVersionId = currentHoogleVersionId
|
, scHoogleVersionId = currentHoogleVersionId
|
||||||
}
|
}
|
||||||
runRIO logFunc $ cronWithPantryConfig $ \pantryConfig -> runRIO (stackage pantryConfig) (runStackageUpdate scoDoNotUpload)
|
runRIO stackage (runStackageUpdate scoDoNotUpload)
|
||||||
|
|
||||||
|
|
||||||
runStackageUpdate :: Bool -> RIO StackageCron ()
|
runStackageUpdate :: Bool -> RIO StackageCron ()
|
||||||
|
|||||||
@ -2,6 +2,10 @@ resolver: lts-22.6
|
|||||||
extra-deps:
|
extra-deps:
|
||||||
- hoogle-5.0.18.4@sha256:1372458e97dff541fcda099236af7936bf93ee6b8c5d15695ee6d9426dff5eed,3171
|
- hoogle-5.0.18.4@sha256:1372458e97dff541fcda099236af7936bf93ee6b8c5d15695ee6d9426dff5eed,3171
|
||||||
- safe-0.3.20@sha256:7813ad56161f57d5162a924de5597d454162a2faed06be6e268b37bb5c19d48d,2312
|
- safe-0.3.20@sha256:7813ad56161f57d5162a924de5597d454162a2faed06be6e268b37bb5c19d48d,2312
|
||||||
|
- Cabal-3.8.1.0@sha256:77121d8e1aff14a0fd95684b751599db78a7dd26d55862d9fcef27c88b193e9d,12609
|
||||||
|
- Cabal-syntax-3.8.1.0@sha256:ed2d937ba6c6a20b75850349eedd41374885fc42369ef152d69e2ba70f44f593,7620
|
||||||
|
- git: https://github.com/commercialhaskell/pantry.git
|
||||||
|
commit: 5df643cc1deb561d9c52a9cb6f593aba2bc4c08e
|
||||||
|
|
||||||
nix:
|
nix:
|
||||||
packages:
|
packages:
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user