Skip to content

Commit 6916f90

Browse files
committed
Make custom snaps use hash in dir name #863 #1408
1 parent db52f16 commit 6916f90

File tree

6 files changed

+245
-145
lines changed

6 files changed

+245
-145
lines changed

src/Stack/Build/Source.hs

Lines changed: 2 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -58,8 +58,7 @@ import Path.IO
5858
import Prelude
5959
import Stack.Build.Cache
6060
import Stack.Build.Target
61-
import Stack.BuildPlan (loadMiniBuildPlan, shadowMiniBuildPlan,
62-
parseCustomMiniBuildPlan)
61+
import Stack.BuildPlan (shadowMiniBuildPlan)
6362
import Stack.Constants (wiredInPackages)
6463
import Stack.Package
6564
import Stack.PackageIndex (getPackageVersions)
@@ -198,9 +197,6 @@ parseTargetsFromBuildOpts needTargets boptscli = do
198197
bconfig <- asks getBuildConfig
199198
mbp0 <-
200199
case bcResolver bconfig of
201-
ResolverSnapshot snapName -> do
202-
$logDebug $ "Checking resolver: " <> renderSnapName snapName
203-
loadMiniBuildPlan snapName
204200
ResolverCompiler _ -> do
205201
-- We ignore the resolver version, as it might be
206202
-- GhcMajorVersion, and we want the exact version
@@ -211,9 +207,7 @@ parseTargetsFromBuildOpts needTargets boptscli = do
211207
, mbpPackages = Map.empty
212208
, mbpAllowNewer = False
213209
}
214-
ResolverCustom _ url -> do
215-
stackYamlFP <- asks $ bcStackYaml . getBuildConfig
216-
parseCustomMiniBuildPlan (Just stackYamlFP) url
210+
_ -> return (bcWantedMiniBuildPlan bconfig)
217211
rawLocals <- getLocalPackageViews
218212
workingDir <- getCurrentDir
219213

src/Stack/BuildPlan.hs

Lines changed: 154 additions & 78 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
{-# LANGUAGE DeriveGeneric #-}
33
{-# LANGUAGE EmptyDataDecls #-}
44
{-# LANGUAGE FlexibleContexts #-}
5+
{-# LANGUAGE GADTs #-}
56
{-# LANGUAGE OverloadedStrings #-}
67
{-# LANGUAGE TemplateHaskell #-}
78
{-# LANGUAGE TupleSections #-}
@@ -20,6 +21,7 @@ module Stack.BuildPlan
2021
, gpdPackageName
2122
, MiniBuildPlan(..)
2223
, MiniPackageInfo(..)
24+
, loadResolver
2325
, loadMiniBuildPlan
2426
, removeSrcPkgDefaultFlags
2527
, resolveBuildPlan
@@ -43,7 +45,7 @@ import Control.Monad.State.Strict (State, execState, get, modify,
4345
import Control.Monad.Trans.Control (MonadBaseControl)
4446
import qualified Crypto.Hash.SHA256 as SHA256
4547
import Data.Aeson.Extended (WithJSONWarnings(..), logJSONWarnings)
46-
import Data.Binary.VersionTagged (taggedDecodeOrLoad)
48+
import Data.Binary.VersionTagged (taggedDecodeOrLoad, decodeFileOrFailDeep)
4749
import qualified Data.ByteString as S
4850
import qualified Data.ByteString.Base16 as B16
4951
import qualified Data.ByteString.Char8 as S8
@@ -55,13 +57,13 @@ import Data.List.NonEmpty (NonEmpty(..))
5557
import qualified Data.List.NonEmpty as NonEmpty
5658
import Data.Map (Map)
5759
import qualified Data.Map as Map
58-
import Data.Maybe (fromMaybe, mapMaybe)
60+
import Data.Maybe (fromMaybe, mapMaybe, isNothing)
5961
import Data.Monoid
6062
import Data.Set (Set)
6163
import qualified Data.Set as Set
6264
import Data.Text (Text)
6365
import qualified Data.Text as T
64-
import Data.Text.Encoding (encodeUtf8)
66+
import Data.Text.Encoding (encodeUtf8, decodeUtf8)
6567
import qualified Data.Traversable as Tr
6668
import Data.Typeable (Typeable)
6769
import Data.Yaml (decodeEither', decodeFileEither)
@@ -86,8 +88,6 @@ import Stack.Package
8688
import Stack.PackageIndex
8789
import Stack.Types
8890
import Stack.Types.StackT
89-
import qualified System.Directory as D
90-
import qualified System.FilePath as FP
9191

9292
data BuildPlanException
9393
= UnknownPackages
@@ -96,6 +96,7 @@ data BuildPlanException
9696
(Map PackageName (Set PackageIdentifier)) -- shadowed
9797
| SnapshotNotFound SnapName
9898
| FilepathInDownloadedSnapshot T.Text
99+
| NeitherCompilerOrResolverSpecified T.Text
99100
deriving (Typeable)
100101
instance Exception BuildPlanException
101102
instance Show BuildPlanException where
@@ -180,6 +181,10 @@ instance Show BuildPlanException where
180181
, "field, but filepaths are not allowed in downloaded snapshots.\n"
181182
, "Filepath specified: " ++ T.unpack url
182183
]
184+
show (NeitherCompilerOrResolverSpecified url) =
185+
"Failed to load custom snapshot at " ++
186+
T.unpack url ++
187+
", because no 'compiler' or 'resolver' is specified."
183188

184189
-- | Determine the necessary packages to install to have the given set of
185190
-- packages available.
@@ -417,19 +422,25 @@ loadResolver
417422
:: (MonadIO m, MonadThrow m, MonadLogger m, MonadReader env m, HasHttpManager env, HasConfig env, HasGHCVariant env, MonadBaseControl IO m, MonadMask m)
418423
=> Maybe (Path Abs File)
419424
-> Resolver
420-
-> m MiniBuildPlan
425+
-> m (MiniBuildPlan, LoadedResolver)
421426
loadResolver mconfigPath resolver =
422427
case resolver of
423-
ResolverSnapshot snap -> loadMiniBuildPlan snap
428+
ResolverSnapshot snap ->
429+
liftM (, ResolverSnapshot snap) $ loadMiniBuildPlan snap
424430
-- TODO(mgsloan): Not sure what this FIXME means
425431
-- FIXME instead of passing the stackYaml dir we should maintain
426432
-- the file URL in the custom resolver always relative to stackYaml.
427-
ResolverCustom _ url -> parseCustomMiniBuildPlan mconfigPath url
428-
ResolverCompiler compiler -> return MiniBuildPlan
429-
{ mbpCompilerVersion = compiler
430-
, mbpPackages = mempty
431-
, mbpAllowNewer = False
432-
}
433+
ResolverCustom name url -> do
434+
(mbp, hash) <- parseCustomMiniBuildPlan mconfigPath url
435+
return (mbp, ResolverCustomLoaded name url (decodeUtf8 hash))
436+
ResolverCompiler compiler -> return
437+
( MiniBuildPlan
438+
{ mbpCompilerVersion = compiler
439+
, mbpPackages = mempty
440+
, mbpAllowNewer = False
441+
}
442+
, ResolverCompiler compiler
443+
)
433444

434445
-- | Load up a 'MiniBuildPlan', preferably from cache
435446
loadMiniBuildPlan
@@ -914,82 +925,147 @@ shadowMiniBuildPlan (MiniBuildPlan cv pkgs0 allowNewer) shadowed =
914925
Just False -> Right
915926
Nothing -> assert False Right
916927

928+
-- This works differently for snapshots fetched from URL and those
929+
-- fetched from file:
930+
--
931+
-- 1) If downloading the snapshot from a URL, assume the fetched data is
932+
-- immutable. Hash the URL in order to determine the location of the
933+
-- cached download. The file contents of the snapshot determines the
934+
-- hash for looking up cached MBP.
935+
--
936+
-- 2) If loading the snapshot from a file, load all of the involved
937+
-- snapshot files. The hash used to determine the cached MBP is the hash
938+
-- of the concatenation of the parent's hash with the snapshot contents.
939+
--
940+
-- Why this difference? We want to make it easy to simply edit snapshots
941+
-- in the filesystem, but we want caching for remote snapshots. In order
942+
-- to avoid reparsing / reloading all the yaml for remote snapshots, we
943+
-- need a different hash system.
944+
945+
-- TODO: This could probably be more efficient if it first merged the
946+
-- custom snapshots, and then applied them to the MBP. It is nice to
947+
-- apply directly, because then we have the guarantee that it's
948+
-- semantically identical to snapshot extension. If this optimization is
949+
-- implemented, note that the direct Monoid for CustomSnapshot is not
950+
-- correct. Crucially, if a package is present in the snapshot, its
951+
-- flags and ghc-options are not based on settings from prior snapshots.
952+
-- TODO: This semantics should be discussed / documented more.
953+
954+
-- TODO: allow a hash check in the resolver. This adds safety /
955+
-- correctness, allowing you to ensure that you are indeed getting the
956+
-- right custom snapshot.
957+
958+
-- TODO: Allow custom plan to specify a name.
959+
917960
parseCustomMiniBuildPlan
918961
:: (MonadIO m, MonadMask m, MonadLogger m, MonadReader env m, HasHttpManager env, HasConfig env, HasGHCVariant env, MonadBaseControl IO m)
919962
=> Maybe (Path Abs File) -- ^ Root directory for when url is a filepath
920963
-> T.Text
921-
-> m MiniBuildPlan
922-
parseCustomMiniBuildPlan mconfigPath url0 = do
964+
-> m (MiniBuildPlan, S8.ByteString)
965+
parseCustomMiniBuildPlan mconfigPath0 url0 = do
923966
$logDebug $ "Loading " <> url0 <> " build plan"
924-
eyamlFP <- getYamlFP url0
925-
let yamlFP = either id id eyamlFP
926-
927-
-- FIXME: determine custom snapshot path based on contents. Ideally,
928-
-- use a hash scheme that ignores formatting differences (works on
929-
-- the data), so that an implicit snapshot (TBD) will hash to the
930-
-- same thing as a custom snapshot.
931-
932-
yamlBS <- liftIO $ S.readFile $ toFilePath yamlFP
933-
let yamlHash = S8.unpack $ B16.encode $ SHA256.hash yamlBS
934-
binaryFilename <- parseRelFile $ yamlHash ++ ".bin"
935-
customPlanDir <- getCustomPlanDir
936-
let binaryFP = customPlanDir </> $(mkRelDir "bin") </> binaryFilename
937-
938-
taggedDecodeOrLoad binaryFP $ do
939-
WithJSONWarnings (cs0, mresolver) warnings <-
967+
case parseUrl $ T.unpack url0 of
968+
Just req -> downloadCustom url0 req
969+
Nothing ->
970+
case mconfigPath0 of
971+
Nothing -> throwM $ FilepathInDownloadedSnapshot url0
972+
Just configPath -> do
973+
(getMbp, hash) <- readCustom configPath url0
974+
mbp <- getMbp
975+
return (mbp, hash)
976+
where
977+
downloadCustom url req = do
978+
let urlHash = S8.unpack $ B16.encode $ SHA256.hash $ encodeUtf8 url
979+
hashFP <- parseRelFile $ urlHash ++ ".yaml"
980+
customPlanDir <- getCustomPlanDir
981+
let cacheFP = customPlanDir </> $(mkRelDir "yaml") </> hashFP
982+
_ <- download req cacheFP
983+
yamlBS <- liftIO $ S.readFile $ toFilePath cacheFP
984+
let yamlHash = b16Hash yamlBS
985+
binaryPath <- getBinaryPath yamlHash
986+
liftM (, yamlHash) $ taggedDecodeOrLoad binaryPath $ do
987+
(cs, mresolver) <- decodeYaml yamlBS
988+
parentMbp <- case (csCompilerVersion cs, mresolver) of
989+
(Nothing, Nothing) -> throwM (NeitherCompilerOrResolverSpecified url)
990+
(Just cv, Nothing) -> return (compilerBuildPlan cv)
991+
-- NOTE: ignoring the parent's hash, even though
992+
-- there could be one. URL snapshot's hash are
993+
-- determined just from their contents.
994+
(_, Just resolver) -> liftM fst (loadResolver Nothing resolver)
995+
applyCustomSnapshot cs parentMbp
996+
readCustom configPath path = do
997+
yamlFP <- resolveFile (parent configPath) (T.unpack $ fromMaybe path $
998+
T.stripPrefix "file://" path <|> T.stripPrefix "file:" path)
999+
yamlBS <- liftIO $ S.readFile $ toFilePath yamlFP
1000+
(cs, mresolver) <- decodeYaml yamlBS
1001+
(getMbp, hash) <- case mresolver of
1002+
Just (ResolverCustom _ url ) ->
1003+
case parseUrl $ T.unpack url of
1004+
Just req -> do
1005+
let getMbp = do
1006+
-- Ignore custom hash, under the
1007+
-- assumption that the URL is sufficient
1008+
-- for identity.
1009+
(mbp, _) <- downloadCustom url req
1010+
return mbp
1011+
return (getMbp, b16Hash yamlBS)
1012+
Nothing -> do
1013+
(getMbp0, hash0) <- readCustom yamlFP url
1014+
let hash = b16Hash (hash0 <> yamlBS)
1015+
getMbp = do
1016+
binaryPath <- getBinaryPath hash
1017+
-- Idea here is to not waste time
1018+
-- writing out intermediate cache files,
1019+
-- but check for them.
1020+
exists <- doesFileExist binaryPath
1021+
if exists
1022+
then do
1023+
eres <- decodeFileOrFailDeep binaryPath
1024+
case eres of
1025+
Right (Just mbp) -> return mbp
1026+
-- Invalid format cache file, remove.
1027+
_ -> do
1028+
removeFile binaryPath
1029+
getMbp0
1030+
else getMbp0
1031+
return (getMbp, hash)
1032+
Just resolver -> do
1033+
-- NOTE: in the cases where we don't have a hash, the
1034+
-- normal resolver name is enough. Since this name is
1035+
-- part of the yaml file, it ends up in our hash.
1036+
let hash = b16Hash yamlBS
1037+
getMbp = do
1038+
(mbp, resolver') <- loadResolver (Just configPath) resolver
1039+
let mhash = customResolverHash resolver'
1040+
assert (isNothing mhash) (return mbp)
1041+
return (getMbp, hash)
1042+
Nothing -> do
1043+
case csCompilerVersion cs of
1044+
Nothing -> throwM (NeitherCompilerOrResolverSpecified path)
1045+
Just cv -> do
1046+
let hash = b16Hash yamlBS
1047+
getMbp = return (compilerBuildPlan cv)
1048+
return (getMbp, hash)
1049+
return (applyCustomSnapshot cs =<< getMbp, hash)
1050+
getBinaryPath hash = do
1051+
binaryFilename <- parseRelFile $ S8.unpack hash ++ ".bin"
1052+
customPlanDir <- getCustomPlanDir
1053+
return $ customPlanDir </> $(mkRelDir "bin") </> binaryFilename
1054+
decodeYaml yamlBS = do
1055+
WithJSONWarnings res warnings <-
9401056
either (throwM . ParseCustomSnapshotException url0) return $
9411057
decodeEither' yamlBS
9421058
logJSONWarnings (T.unpack url0) warnings
943-
case (mresolver, csCompilerVersion cs0) of
944-
(Nothing, Nothing) ->
945-
fail $ "Failed to load custom snapshot at " ++
946-
T.unpack url0 ++
947-
", because no 'compiler' or 'resolver' is specified."
948-
(Nothing, Just cv) ->
949-
applyCustomSnapshot cs0 MiniBuildPlan
950-
{ mbpCompilerVersion = cv
951-
, mbpPackages = mempty
952-
, mbpAllowNewer = False
953-
}
954-
-- Even though we ignore the compiler version here, it gets
955-
-- used due to applyCustomSnapshot
956-
(Just resolver, _) -> do
957-
-- Load referenced resolver. If the custom snapshot is
958-
-- stored at a user location, then allow relative
959-
-- filepath custom snapshots.
960-
mbp <- loadResolver customFile resolver
961-
applyCustomSnapshot cs0 mbp
962-
where
963-
customFile = case eyamlFP of
964-
Left _ -> Nothing
965-
Right fp -> Just fp
966-
where
1059+
return res
1060+
compilerBuildPlan cv = MiniBuildPlan
1061+
{ mbpCompilerVersion = cv
1062+
, mbpPackages = mempty
1063+
, mbpAllowNewer = False
1064+
}
9671065
getCustomPlanDir = do
9681066
root <- asks $ configStackRoot . getConfig
9691067
return $ root </> $(mkRelDir "custom-plan")
970-
971-
-- Get the path to the YAML file
972-
getYamlFP url =
973-
case parseUrl $ T.unpack url of
974-
Just req -> getYamlFPFromReq url req
975-
Nothing -> getYamlFPFromFile url
976-
977-
getYamlFPFromReq url req = do
978-
let hashStr = S8.unpack $ B16.encode $ SHA256.hash $ encodeUtf8 url
979-
hashFP <- parseRelFile $ hashStr ++ ".yaml"
980-
customPlanDir <- getCustomPlanDir
981-
982-
let cacheFP = customPlanDir </> $(mkRelDir "yaml") </> hashFP
983-
_ <- download req cacheFP
984-
return (Left cacheFP)
985-
986-
getYamlFPFromFile url =
987-
case mconfigPath of
988-
Nothing -> throwM $ FilepathInDownloadedSnapshot url
989-
Just configPath -> do
990-
fp <- liftIO $ D.canonicalizePath $ toFilePath (parent configPath) FP.</> T.unpack (fromMaybe url $
991-
T.stripPrefix "file://" url <|> T.stripPrefix "file:" url)
992-
Right <$> parseAbsFile fp
1068+
b16Hash = B16.encode . SHA256.hash
9931069

9941070
applyCustomSnapshot
9951071
:: (MonadIO m, MonadLogger m, MonadReader env m, HasHttpManager env, MonadThrow m, HasConfig env, MonadBaseControl IO m, MonadMask m)

src/Stack/Config.hs

Lines changed: 4 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -512,24 +512,15 @@ loadBuildConfig mproject config mresolver mcompiler = do
512512
, projectCompiler = mcompiler <|> projectCompiler project'
513513
}
514514

515-
wantedCompiler <-
516-
case projectCompiler project of
517-
Just wantedCompiler -> return wantedCompiler
518-
Nothing -> case projectResolver project of
519-
ResolverSnapshot snapName -> do
520-
mbp <- runReaderT (loadMiniBuildPlan snapName) miniConfig
521-
return $ mbpCompilerVersion mbp
522-
ResolverCustom _name url -> do
523-
mbp <- runReaderT (parseCustomMiniBuildPlan (Just stackYamlFP) url) miniConfig
524-
return $ mbpCompilerVersion mbp
525-
ResolverCompiler wantedCompiler -> return wantedCompiler
515+
(mbp, loadedResolver) <- flip runReaderT miniConfig $
516+
loadResolver (Just stackYamlFP) (projectResolver project)
526517

527518
extraPackageDBs <- mapM resolveDir' (projectExtraPackageDBs project)
528519

529520
return BuildConfig
530521
{ bcConfig = config
531-
, bcResolver = projectResolver project
532-
, bcWantedCompiler = wantedCompiler
522+
, bcResolver = loadedResolver
523+
, bcWantedMiniBuildPlan = mbp
533524
, bcPackageEntries = projectPackages project
534525
, bcExtraDeps = projectExtraDeps project
535526
, bcExtraPackageDBs = extraPackageDBs

src/Stack/ConfigCmd.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -45,6 +45,7 @@ cfgCmdSet (ConfigCmdSetResolver newResolver) = do
4545
(projectYamlConfig :: Yaml.Object) <-
4646
liftIO (Yaml.decodeFileEither stackYamlFp) >>=
4747
either throwM return
48+
-- TODO: custom snapshot support?
4849
newResolverText <- fmap resolverName (makeConcreteResolver newResolver)
4950
-- We checking here that the snapshot actually exists
5051
snap <- parseSnapName newResolverText

0 commit comments

Comments
 (0)