Skip to content

Commit f843b95

Browse files
committed
Avoid fixed-point implicit dependencies by eagerly loading build tool versions up front
1 parent 4b8fe70 commit f843b95

File tree

3 files changed

+44
-60
lines changed

3 files changed

+44
-60
lines changed

hie-bios.cabal

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -170,6 +170,7 @@ Library
170170
Build-Depends:
171171
base >= 4.16 && < 5,
172172
aeson >= 1.4.4 && < 2.3,
173+
async >= 2.1 && <2.3,
173174
base16-bytestring >= 0.1.1 && < 1.1,
174175
bytestring >= 0.10.8 && < 0.13,
175176
co-log-core ^>= 0.3.0,
@@ -199,7 +200,7 @@ Executable hie-bios
199200
Main-Is: Main.hs
200201
Other-Modules: Paths_hie_bios
201202
autogen-modules: Paths_hie_bios
202-
GHC-Options: -Wall
203+
GHC-Options: -threaded -Wall
203204
HS-Source-Dirs: exe
204205
Build-Depends: base >= 4.16 && < 5
205206
, co-log-core

src/HIE/Bios/Cradle.hs

Lines changed: 39 additions & 57 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,9 @@
11
{-# LANGUAGE BangPatterns #-}
2+
{-# LANGUAGE DeriveTraversable #-}
23
{-# LANGUAGE OverloadedStrings #-}
34
{-# LANGUAGE ScopedTypeVariables #-}
45
{-# LANGUAGE TupleSections #-}
56
{-# LANGUAGE LambdaCase #-}
6-
{-# LANGUAGE RecursiveDo #-}
7-
{-# LANGUAGE RecordWildCards #-}
87
module HIE.Bios.Cradle (
98
findCradle
109
, loadCradle
@@ -28,11 +27,13 @@ module HIE.Bios.Cradle (
2827

2928
-- expose to tests
3029
, makeVersions
30+
, getGhcVersion
3131
, isCabalMultipleCompSupported
32-
, ProgramVersions
32+
, BuildToolVersions
3333
) where
3434

3535
import Control.Applicative ((<|>), optional)
36+
import Control.Concurrent.Async (mapConcurrently)
3637
import Control.DeepSeq
3738
import Control.Exception (handleJust)
3839
import qualified Data.Yaml as Yaml
@@ -82,7 +83,6 @@ import GHC.Fingerprint (fingerprintString)
8283
import GHC.ResponseFile (escapeArgs)
8384

8485
import Data.Version
85-
import Data.IORef
8686
import Text.ParserCombinators.ReadP (readP_to_S)
8787
import Data.Tuple.Extra (fst3, snd3, thd3)
8888

@@ -157,35 +157,18 @@ data ResolvedCradles a
157157
= ResolvedCradles
158158
{ cradleRoot :: FilePath
159159
, resolvedCradles :: [ResolvedCradle a] -- ^ In order of decreasing specificity
160-
, cradleProgramVersions :: ProgramVersions
160+
, cradleBuildToolVersions :: BuildToolVersions
161161
}
162162

163-
data ProgramVersions =
164-
ProgramVersions { cabalVersion :: CachedIO (Maybe Version)
165-
, stackVersion :: CachedIO (Maybe Version)
166-
, ghcVersion :: CachedIO (Maybe Version)
167-
}
168-
169-
newtype CachedIO a = CachedIO (IORef (Either (IO a) a))
170-
171-
makeCachedIO :: IO a -> IO (CachedIO a)
172-
makeCachedIO act = CachedIO <$> newIORef (Left act)
173-
174-
runCachedIO :: CachedIO a -> IO a
175-
runCachedIO (CachedIO ref) =
176-
readIORef ref >>= \case
177-
Right x -> pure x
178-
Left act -> do
179-
x <- act
180-
writeIORef ref (Right x)
181-
pure x
182-
183-
makeVersions :: LogAction IO (WithSeverity Log) -> FilePath -> ([String] -> IO (CradleLoadResult String)) -> IO ProgramVersions
184-
makeVersions l wdir ghc = do
185-
cabalVersion <- makeCachedIO $ getCabalVersion l wdir
186-
stackVersion <- makeCachedIO $ getStackVersion l wdir
187-
ghcVersion <- makeCachedIO $ getGhcVersion ghc
188-
pure ProgramVersions{..}
163+
type BuildToolVersions = BuildToolVersions' (Maybe Version)
164+
data BuildToolVersions' v =
165+
BuildToolVersions { cabalVersion :: v
166+
, stackVersion :: v
167+
}
168+
deriving (Functor, Foldable, Traversable)
169+
170+
makeVersions :: LogAction IO (WithSeverity Log) -> FilePath -> IO BuildToolVersions
171+
makeVersions l wdir = mapConcurrently (\v -> v l wdir) $ BuildToolVersions getCabalVersion getStackVersion
189172

190173
getCabalVersion :: LogAction IO (WithSeverity Log) -> FilePath -> IO (Maybe Version)
191174
getCabalVersion l wdir = do
@@ -224,9 +207,11 @@ addActionDeps deps =
224207
(\err -> CradleFail (err { cradleErrorDependencies = cradleErrorDependencies err `union` deps }))
225208
(\(ComponentOptions os' dir ds) -> CradleSuccess (ComponentOptions os' dir (ds `union` deps)))
226209

227-
228210
resolvedCradlesToCradle :: Show a => LogAction IO (WithSeverity Log) -> (b -> CradleAction a) -> FilePath -> [ResolvedCradle b] -> IO (Cradle a)
229-
resolvedCradlesToCradle logger buildCustomCradle root cs = mdo
211+
resolvedCradlesToCradle logger buildCustomCradle root cs = do
212+
versions <- makeVersions logger root
213+
cradleActions <- for cs $ \c ->
214+
fmap (c,) $ resolveCradleAction logger buildCustomCradle (ResolvedCradles root cs versions) root c
230215
let run_ghc_cmd args =
231216
-- We're being lazy here and just returning the ghc path for the
232217
-- first non-none cradle. This shouldn't matter in practice: all
@@ -237,10 +222,6 @@ resolvedCradlesToCradle logger buildCustomCradle root cs = mdo
237222
runGhcCmd
238223
act
239224
args
240-
versions <- makeVersions logger root run_ghc_cmd
241-
cradleActions <- for cs $ \c ->
242-
fmap (c,) $ resolveCradleAction logger buildCustomCradle (ResolvedCradles root cs versions) root c
243-
let
244225
err_msg fp
245226
= ["Multi Cradle: No prefixes matched"
246227
, "pwd: " ++ root
@@ -608,16 +589,13 @@ projectLocationOrDefault = \case
608589
-- Works for new-build by invoking `v2-repl`.
609590
cabalCradle :: LogAction IO (WithSeverity Log) -> ResolvedCradles b -> FilePath -> Maybe String -> CradleProjectConfig -> IO (CradleAction a)
610591
cabalCradle l cs wdir mc projectFile = do
611-
res <- runCradleResultT $ callCabalPathForCompilerPath l (cradleProgramVersions cs) wdir projectFile
592+
res <- runCradleResultT $ callCabalPathForCompilerPath l (cradleBuildToolVersions cs) wdir projectFile
612593
let
613594
ghcPath = case res of
614595
CradleSuccess path -> path
615596
_ -> Nothing
616597

617-
pure $ CradleAction
618-
{ actionName = Types.Cabal
619-
, runCradle = \fp -> runCradleResultT . cabalAction cs wdir ghcPath mc l projectFile fp
620-
, runGhcCmd = \args -> runCradleResultT $ do
598+
runGhcCmd args = runCradleResultT $ do
621599
case ghcPath of
622600
Just p -> readProcessWithCwd_ l wdir p args ""
623601
Nothing -> do
@@ -628,6 +606,13 @@ cabalCradle l cs wdir mc projectFile = do
628606
-- Need to pass -v0 otherwise we get "resolving dependencies..."
629607
cabalProc <- cabalProcess l projectFile wdir Nothing "v2-exec" $ ["ghc", "-v0", "--"] ++ args
630608
readProcessWithCwd' l cabalProc ""
609+
610+
pure $ CradleAction
611+
{ actionName = Types.Cabal
612+
, runCradle = \fp ls -> do
613+
v <- getGhcVersion runGhcCmd
614+
runCradleResultT $ cabalAction cs wdir ghcPath v mc l projectFile fp ls
615+
, runGhcCmd = runGhcCmd
631616
}
632617

633618

@@ -868,9 +853,9 @@ cabalGhcDirs l cabalProject workDir = do
868853
where
869854
projectFileArgs = projectFileProcessArgs cabalProject
870855

871-
callCabalPathForCompilerPath :: LogAction IO (WithSeverity Log) -> ProgramVersions -> FilePath -> CradleProjectConfig -> CradleLoadResultT IO (Maybe FilePath)
856+
callCabalPathForCompilerPath :: LogAction IO (WithSeverity Log) -> BuildToolVersions -> FilePath -> CradleProjectConfig -> CradleLoadResultT IO (Maybe FilePath)
872857
callCabalPathForCompilerPath l vs workDir projectFile = do
873-
isCabalPathSupported vs >>= \case
858+
case isCabalPathSupported vs of
874859
False -> pure Nothing
875860
True -> do
876861
let
@@ -885,32 +870,29 @@ callCabalPathForCompilerPath l vs workDir projectFile = do
885870
pure Nothing
886871
Right a -> pure a
887872

888-
isCabalPathSupported :: MonadIO m => ProgramVersions -> m Bool
889-
isCabalPathSupported vs = do
890-
v <- liftIO $ runCachedIO $ cabalVersion vs
891-
pure $ maybe False (>= makeVersion [3,14]) v
873+
isCabalPathSupported :: BuildToolVersions -> Bool
874+
isCabalPathSupported = maybe False (>= makeVersion [3,14]) . cabalVersion
892875

893-
isCabalMultipleCompSupported :: MonadIO m => ProgramVersions -> m Bool
894-
isCabalMultipleCompSupported vs = do
895-
cabal_version <- liftIO $ runCachedIO $ cabalVersion vs
896-
ghc_version <- liftIO $ runCachedIO $ ghcVersion vs
876+
isCabalMultipleCompSupported :: BuildToolVersions -> Maybe Version -> Bool
877+
isCabalMultipleCompSupported vs ghcVersion = do
897878
-- determine which load style is supported by this cabal cradle.
898-
case (cabal_version, ghc_version) of
899-
(Just cabal, Just ghc) -> pure $ ghc >= makeVersion [9, 4] && cabal >= makeVersion [3, 11]
900-
_ -> pure False
879+
case (cabalVersion vs, ghcVersion) of
880+
(Just cabal, Just ghc) -> ghc >= makeVersion [9, 4] && cabal >= makeVersion [3, 11]
881+
_ -> False
901882

902883
cabalAction
903884
:: ResolvedCradles a
904885
-> FilePath
905886
-> Maybe FilePath
887+
-> Maybe Version
906888
-> Maybe String
907889
-> LogAction IO (WithSeverity Log)
908890
-> CradleProjectConfig
909891
-> FilePath
910892
-> LoadStyle
911893
-> CradleLoadResultT IO ComponentOptions
912-
cabalAction (ResolvedCradles root cs vs) workDir ghcPath mc l projectFile fp loadStyle = do
913-
multiCompSupport <- isCabalMultipleCompSupported vs
894+
cabalAction (ResolvedCradles root cs vs) workDir ghcPath ghcVersion mc l projectFile fp loadStyle = do
895+
let multiCompSupport = isCabalMultipleCompSupported vs ghcVersion
914896
-- determine which load style is supported by this cabal cradle.
915897
determinedLoadStyle <- case loadStyle of
916898
LoadWithContext _ | not multiCompSupport -> do

tests/Utils.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -319,8 +319,9 @@ isCabalMultipleCompSupported' :: TestM Bool
319319
isCabalMultipleCompSupported' = do
320320
cr <- askCradle
321321
root <- askRoot
322-
versions <- liftIO $ makeVersions (cradleLogger cr) root ((runGhcCmd . cradleOptsProg) cr)
323-
liftIO $ isCabalMultipleCompSupported versions
322+
versions <- liftIO $ makeVersions (cradleLogger cr) root
323+
v <- liftIO $ getGhcVersion ((runGhcCmd . cradleOptsProg) cr)
324+
pure $ isCabalMultipleCompSupported versions v
324325

325326
inCradleRootDir :: TestM a -> TestM a
326327
inCradleRootDir act = do

0 commit comments

Comments
 (0)