2
2
{-# LANGUAGE DeriveGeneric #-}
3
3
{-# LANGUAGE EmptyDataDecls #-}
4
4
{-# LANGUAGE FlexibleContexts #-}
5
+ {-# LANGUAGE GADTs #-}
5
6
{-# LANGUAGE OverloadedStrings #-}
6
7
{-# LANGUAGE TemplateHaskell #-}
7
8
{-# LANGUAGE TupleSections #-}
@@ -20,6 +21,7 @@ module Stack.BuildPlan
20
21
, gpdPackageName
21
22
, MiniBuildPlan (.. )
22
23
, MiniPackageInfo (.. )
24
+ , loadResolver
23
25
, loadMiniBuildPlan
24
26
, removeSrcPkgDefaultFlags
25
27
, resolveBuildPlan
@@ -43,7 +45,7 @@ import Control.Monad.State.Strict (State, execState, get, modify,
43
45
import Control.Monad.Trans.Control (MonadBaseControl )
44
46
import qualified Crypto.Hash.SHA256 as SHA256
45
47
import Data.Aeson.Extended (WithJSONWarnings (.. ), logJSONWarnings )
46
- import Data.Binary.VersionTagged (taggedDecodeOrLoad )
48
+ import Data.Binary.VersionTagged (taggedDecodeOrLoad , decodeFileOrFailDeep )
47
49
import qualified Data.ByteString as S
48
50
import qualified Data.ByteString.Base16 as B16
49
51
import qualified Data.ByteString.Char8 as S8
@@ -55,13 +57,13 @@ import Data.List.NonEmpty (NonEmpty(..))
55
57
import qualified Data.List.NonEmpty as NonEmpty
56
58
import Data.Map (Map )
57
59
import qualified Data.Map as Map
58
- import Data.Maybe (fromMaybe , mapMaybe )
60
+ import Data.Maybe (fromMaybe , mapMaybe , isNothing )
59
61
import Data.Monoid
60
62
import Data.Set (Set )
61
63
import qualified Data.Set as Set
62
64
import Data.Text (Text )
63
65
import qualified Data.Text as T
64
- import Data.Text.Encoding (encodeUtf8 )
66
+ import Data.Text.Encoding (encodeUtf8 , decodeUtf8 )
65
67
import qualified Data.Traversable as Tr
66
68
import Data.Typeable (Typeable )
67
69
import Data.Yaml (decodeEither' , decodeFileEither )
@@ -86,8 +88,6 @@ import Stack.Package
86
88
import Stack.PackageIndex
87
89
import Stack.Types
88
90
import Stack.Types.StackT
89
- import qualified System.Directory as D
90
- import qualified System.FilePath as FP
91
91
92
92
data BuildPlanException
93
93
= UnknownPackages
@@ -96,6 +96,7 @@ data BuildPlanException
96
96
(Map PackageName (Set PackageIdentifier )) -- shadowed
97
97
| SnapshotNotFound SnapName
98
98
| FilepathInDownloadedSnapshot T. Text
99
+ | NeitherCompilerOrResolverSpecified T. Text
99
100
deriving (Typeable )
100
101
instance Exception BuildPlanException
101
102
instance Show BuildPlanException where
@@ -180,6 +181,10 @@ instance Show BuildPlanException where
180
181
, " field, but filepaths are not allowed in downloaded snapshots.\n "
181
182
, " Filepath specified: " ++ T. unpack url
182
183
]
184
+ show (NeitherCompilerOrResolverSpecified url) =
185
+ " Failed to load custom snapshot at " ++
186
+ T. unpack url ++
187
+ " , because no 'compiler' or 'resolver' is specified."
183
188
184
189
-- | Determine the necessary packages to install to have the given set of
185
190
-- packages available.
@@ -417,19 +422,25 @@ loadResolver
417
422
:: (MonadIO m , MonadThrow m , MonadLogger m , MonadReader env m , HasHttpManager env , HasConfig env , HasGHCVariant env , MonadBaseControl IO m , MonadMask m )
418
423
=> Maybe (Path Abs File )
419
424
-> Resolver
420
- -> m MiniBuildPlan
425
+ -> m ( MiniBuildPlan , LoadedResolver )
421
426
loadResolver mconfigPath resolver =
422
427
case resolver of
423
- ResolverSnapshot snap -> loadMiniBuildPlan snap
428
+ ResolverSnapshot snap ->
429
+ liftM (, ResolverSnapshot snap) $ loadMiniBuildPlan snap
424
430
-- TODO(mgsloan): Not sure what this FIXME means
425
431
-- FIXME instead of passing the stackYaml dir we should maintain
426
432
-- 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
+ )
433
444
434
445
-- | Load up a 'MiniBuildPlan', preferably from cache
435
446
loadMiniBuildPlan
@@ -914,82 +925,147 @@ shadowMiniBuildPlan (MiniBuildPlan cv pkgs0 allowNewer) shadowed =
914
925
Just False -> Right
915
926
Nothing -> assert False Right
916
927
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
+
917
960
parseCustomMiniBuildPlan
918
961
:: (MonadIO m , MonadMask m , MonadLogger m , MonadReader env m , HasHttpManager env , HasConfig env , HasGHCVariant env , MonadBaseControl IO m )
919
962
=> Maybe (Path Abs File ) -- ^ Root directory for when url is a filepath
920
963
-> T. Text
921
- -> m MiniBuildPlan
922
- parseCustomMiniBuildPlan mconfigPath url0 = do
964
+ -> m ( MiniBuildPlan , S8. ByteString )
965
+ parseCustomMiniBuildPlan mconfigPath0 url0 = do
923
966
$ 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 <-
940
1056
either (throwM . ParseCustomSnapshotException url0) return $
941
1057
decodeEither' yamlBS
942
1058
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
+ }
967
1065
getCustomPlanDir = do
968
1066
root <- asks $ configStackRoot . getConfig
969
1067
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
993
1069
994
1070
applyCustomSnapshot
995
1071
:: (MonadIO m , MonadLogger m , MonadReader env m , HasHttpManager env , MonadThrow m , HasConfig env , MonadBaseControl IO m , MonadMask m )
0 commit comments