diff --git a/.gitmodules b/.gitmodules index 7faeadd5ea..a52b36f97a 100644 --- a/.gitmodules +++ b/.gitmodules @@ -11,4 +11,5 @@ [submodule "ghcide"] path = ghcide # url = https://github.com/digital-asset/ghcide.git - url = https://github.com/alanz/ghcide.git + # url = https://github.com/alanz/ghcide.git + url = https://github.com/wz1000/ghcide.git diff --git a/cabal.project b/cabal.project index 3d0f651488..19824ae865 100644 --- a/cabal.project +++ b/cabal.project @@ -2,11 +2,6 @@ packages: ./ ghcide -source-repository-package - type: git - location: https://github.com/wz1000/shake - tag: fb3859dca2e54d1bbb2c873e68ed225fa179fbef - -- See https://github.com/haskell-hvr/cabal-plan/pull/55 source-repository-package type: git @@ -23,4 +18,4 @@ package ghcide write-ghc-environment-files: never -index-state: 2020-05-24T12:28:23Z +index-state: 2020-06-18T17:03:29Z diff --git a/exe/Main.hs b/exe/Main.hs index 19b1534ff2..4541d29243 100644 --- a/exe/Main.hs +++ b/exe/Main.hs @@ -4,8 +4,11 @@ {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -Wno-dodgy-imports #-} -- GHC no longer exports def in GHC 8.6 and above {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} @@ -15,14 +18,18 @@ module Main(main) where import Arguments import Control.Concurrent.Async import Control.Concurrent.Extra -import Control.Exception +-- import Control.Exception +import Control.Exception.Safe import Control.Monad.Extra import Control.Monad.IO.Class import qualified Crypto.Hash.SHA1 as H +import Data.Aeson (ToJSON(toJSON)) import Data.ByteString.Base16 (encode) import qualified Data.ByteString.Char8 as B import Data.Default import Data.Either +import Data.Either.Extra +import Data.Foldable import Data.Function import qualified Data.HashMap.Strict as HM import qualified Data.HashSet as HashSet @@ -33,7 +40,7 @@ import Data.Maybe import qualified Data.Text as T import qualified Data.Text.IO as T import Data.Time.Clock (UTCTime) --- import Data.Version +import Data.Version -- import Development.GitRev import Development.IDE.Core.Debouncer import Development.IDE.Core.FileStore @@ -55,7 +62,7 @@ import DynFlags (gopt_set, gopt_unset, updOptLevel) import DynFlags (PackageFlag(..), PackageArg(..)) import GHC hiding (def) -import GHC.Check ( VersionCheck(..), makeGhcVersionChecker ) +import GHC.Check -- import GhcMonad import HIE.Bios.Cradle import HIE.Bios.Environment (addCmdOpts, makeDynFlagsAbsolute) @@ -67,7 +74,7 @@ import Ide.Plugin import Ide.Plugin.Config import Ide.Types (IdePlugins, ipMap) import Language.Haskell.LSP.Messages -import Language.Haskell.LSP.Types (LspId(IdInt)) +import Language.Haskell.LSP.Types import Linker (initDynLinker) import Module import NameCache @@ -79,7 +86,7 @@ import qualified System.Directory.Extra as IO import System.Exit import System.FilePath import System.IO -import System.Log.Logger as L +import qualified System.Log.Logger as L import System.Time.Extra -- --------------------------------------------------------------------- @@ -99,6 +106,7 @@ import Ide.Plugin.StylishHaskell as StylishHaskell import Ide.Plugin.Brittany as Brittany #endif import Ide.Plugin.Pragmas as Pragmas +-- import Data.Typeable (Typeable) -- --------------------------------------------------------------------- @@ -181,25 +189,25 @@ main = do options = def { LSP.executeCommandCommands = Just commandIds , LSP.completionTriggerCharacters = Just "." } + if argLSP then do t <- offsetTime hPutStrLn stderr "Starting (haskell-language-server)LSP server..." hPutStrLn stderr $ " with arguments: " <> show args hPutStrLn stderr $ " with plugins: " <> show (Map.keys $ ipMap idePlugins') hPutStrLn stderr "If you are seeing this in a terminal, you probably should have run ghcide WITHOUT the --lsp option!" - runLanguageServer options (pluginHandler plugins) getInitialConfig getConfigFromNotification $ \getLspId event vfs caps -> do + runLanguageServer options (pluginHandler plugins) getInitialConfig getConfigFromNotification $ \getLspId event vfs caps wProg wIndefProg -> do t <- t hPutStrLn stderr $ "Started LSP server in " ++ showDuration t - let options = (defaultIdeOptions $ loadSession dir) + let options = (defaultIdeOptions $ loadSessionShake dir) { optReportProgress = clientSupportsProgress caps , optShakeProfiling = argsShakeProfiling - , optTesting = argsTesting + , optTesting = IdeTesting argsTesting , optThreads = argsThreads - , optInterfaceLoadingDiagnostics = argsTesting } debouncer <- newAsyncDebouncer - fst <$> initialise caps (mainRule >> pluginRules plugins) - getLspId event hlsLogger debouncer options vfs + initialise caps (mainRule >> pluginRules plugins) + getLspId event wProg wIndefProg hlsLogger debouncer options vfs else do -- GHC produces messages with UTF8 in them, so make sure the terminal doesn't error hSetEncoding stdout utf8 @@ -208,27 +216,33 @@ main = do putStrLn $ "(haskell-language-server)Ghcide setup tester in " ++ dir ++ "." putStrLn "Report bugs at https://github.com/haskell/haskell-language-server/issues" - putStrLn $ "\nStep 1/6: Finding files to test in " ++ dir + putStrLn $ "\nStep 1/4: Finding files to test in " ++ dir files <- expandFiles (argFiles ++ ["." | null argFiles]) -- LSP works with absolute file paths, so try and behave similarly files <- nubOrd <$> mapM IO.canonicalizePath files putStrLn $ "Found " ++ show (length files) ++ " files" - putStrLn "\nStep 2/6: Looking for hie.yaml files that control setup" + putStrLn "\nStep 2/4: Looking for hie.yaml files that control setup" cradles <- mapM findCradle files let ucradles = nubOrd cradles let n = length ucradles putStrLn $ "Found " ++ show n ++ " cradle" ++ ['s' | n /= 1] - putStrLn "\nStep 3/6: Initializing the IDE" + putStrLn "\nStep 3/4: Initializing the IDE" vfs <- makeVFSHandle debouncer <- newAsyncDebouncer - (ide, worker) <- initialise def mainRule (pure $ IdInt 0) (showEvent lock) (logger Info) debouncer (defaultIdeOptions $ loadSession dir) vfs + let dummyWithProg _ _ f = f (const (pure ())) + ide <- initialise def mainRule (pure $ IdInt 0) (showEvent lock) dummyWithProg (const (const id)) (logger Info) debouncer (defaultIdeOptions $ loadSessionShake dir) vfs - putStrLn "\nStep 4/6: Type checking the files" + putStrLn "\nStep 4/4: Type checking the files" setFilesOfInterest ide $ HashSet.fromList $ map toNormalizedFilePath' files - _ <- runActionSync "TypecheckTest" ide $ uses TypeCheck (map toNormalizedFilePath' files) - cancel worker - return () + results <- runAction "User TypeCheck" ide $ uses TypeCheck (map toNormalizedFilePath' files) + let (worked, failed) = partition fst $ zip (map isJust results) files + when (failed /= []) $ + putStr $ unlines $ "Files that failed:" : map ((++) " * " . snd) failed + + let files xs = let n = length xs in if n == 1 then "1 file" else show n ++ " files" + putStrLn $ "\nCompleted (" ++ files worked ++ " worked, " ++ files failed ++ " failed)" + unless (null failed) (exitWith $ ExitFailure (length failed)) expandFiles :: [FilePath] -> IO [FilePath] expandFiles = concatMapM $ \x -> do @@ -242,14 +256,6 @@ expandFiles = concatMapM $ \x -> do fail $ "Couldn't find any .hs/.lhs files inside directory: " ++ x return files --- Running this every hover is too expensive, 0.2s on GHC for example -{- -kick :: Action () -kick = do - files <- getFilesOfInterest - void $ uses TypeCheck $ HashSet.toList files - -} - -- | Print an LSP event. showEvent :: Lock -> FromServerMessage -> IO () showEvent _ (EventFileDiagnostics _ []) = return () @@ -258,17 +264,17 @@ showEvent lock (EventFileDiagnostics (toNormalizedFilePath' -> file) diags) = showEvent lock e = withLock lock $ print e +-- | Run the specific cradle on a specific FilePath via hie-bios. cradleToSessionOpts :: Cradle a -> FilePath -> IO (Either [CradleError] ComponentOptions) cradleToSessionOpts cradle file = do let showLine s = putStrLn ("> " ++ s) cradleRes <- runCradle (cradleOptsProg cradle) showLine file - opts <- case cradleRes of + case cradleRes of CradleSuccess r -> pure (Right r) CradleFail err -> return (Left [err]) -- For the None cradle perhaps we still want to report an Info -- message about the fact that the file is being ignored. CradleNone -> return (Left []) - pure opts emptyHscEnv :: IORef NameCache -> IO HscEnv emptyHscEnv nc = do @@ -277,222 +283,253 @@ emptyHscEnv nc = do initDynLinker env pure $ setNameCache nc env --- Convert a target to a list of potential absolute paths. +-- | Convert a target to a list of potential absolute paths. -- A TargetModule can be anywhere listed by the supplied include -- directories -- A target file is a relative path but with a specific prefix so just need -- to canonicalise it. targetToFile :: [FilePath] -> TargetId -> IO [NormalizedFilePath] targetToFile is (TargetModule mod) = do - let fps = [i (moduleNameSlashes mod) -<.> ext | ext <- exts, i <- is ] + let fps = [i moduleNameSlashes mod -<.> ext | ext <- exts, i <- is ] exts = ["hs", "hs-boot", "lhs"] mapM (fmap toNormalizedFilePath' . canonicalizePath) fps targetToFile _ (TargetFile f _) = do f' <- canonicalizePath f - return [(toNormalizedFilePath' f')] + return [toNormalizedFilePath' f'] setNameCache :: IORef NameCache -> HscEnv -> HscEnv setNameCache nc hsc = hsc { hsc_NC = nc } --- This is the key function which implements multi-component support. All --- components mapping to the same hie,yaml file are mapped to the same --- HscEnv which is updated as new components are discovered. -loadSession :: FilePath -> Action (FilePath -> Action (IdeResult HscEnvEq)) -loadSession dir = do - nc <- ideNc <$> getShakeExtras - liftIO $ do - -- Mapping from hie.yaml file to HscEnv, one per hie.yaml file - hscEnvs <- newVar Map.empty - -- Mapping from a filepath to HscEnv - fileToFlags <- newVar Map.empty - - -- This caches the mapping from Mod.hs -> hie.yaml - cradleLoc <- memoIO $ \v -> do - res <- findCradle v - -- Sometimes we get C:, sometimes we get c:, and sometimes we get a relative path - -- try and normalise that - -- e.g. see https://github.com/digital-asset/ghcide/issues/126 - res' <- traverse IO.makeAbsolute res - return $ normalise <$> res' - - -- Create a new HscEnv from a hieYaml root and a set of options - -- If the hieYaml file already has an HscEnv, the new component is - -- combined with the components in the old HscEnv into a new HscEnv - -- which contains both. - packageSetup <- return $ \(hieYaml, cfp, opts) -> do - -- Parse DynFlags for the newly discovered component - hscEnv <- emptyHscEnv nc - (df, targets) <- evalGhcEnv hscEnv $ do - setOptions opts (hsc_dflags hscEnv) - dep_info <- getDependencyInfo (componentDependencies opts) - -- Now lookup to see whether we are combining with an exisiting HscEnv - -- or making a new one. The lookup returns the HscEnv and a list of - -- information about other components loaded into the HscEnv - -- (unitId, DynFlag, Targets) - modifyVar hscEnvs $ \m -> do - -- Just deps if there's already an HscEnv - -- Nothing is it's the first time we are making an HscEnv - let oldDeps = Map.lookup hieYaml m - let -- Add the raw information about this component to the list - -- We will modify the unitId and DynFlags used for - -- compilation but these are the true source of - -- information. - new_deps = (thisInstalledUnitId df, df, targets, cfp, opts, dep_info) : maybe [] snd oldDeps - -- Get all the unit-ids for things in this component - inplace = map (\(a, _, _, _, _, _) -> a) new_deps - - -- Note [Avoiding bad interface files] - new_deps' <- forM new_deps $ \(uid, df1, ts, cfp, opts, di) -> do - -- let (uid, (df1, _target, ts, cfp, opts, di)) = do_one componentInfo - -- Remove all inplace dependencies from package flags for - -- components in this HscEnv - let (df2, uids) = removeInplacePackages inplace df1 - let prefix = show $ thisInstalledUnitId df1 - df <- setCacheDir prefix (sort $ map show uids) opts df2 - -- All deps, but without any packages which are also loaded - -- into memory - pure $ (uid, (df, uids, ts, cfp, opts, di)) - -- Make a new HscEnv, we have to recompile everything from - -- scratch again (for now) - -- It's important to keep the same NameCache though for reasons - -- that I do not fully understand - print ("Making new HscEnv" ++ (show inplace)) - hscEnv <- emptyHscEnv nc - newHscEnv <- - -- Add the options for the current component to the HscEnv - evalGhcEnv hscEnv $ do - _ <- setSessionDynFlags df - getSession - -- Modify the map so the hieYaml now maps to the newly created - -- HscEnv - -- Returns - -- * the new HscEnv so it can be used to modify the - -- FilePath -> HscEnv map - -- * The information for the new component which caused this cache miss - -- * The modified information (without -inplace flags) for - -- existing packages - pure (Map.insert hieYaml (newHscEnv, new_deps) m, (newHscEnv, head new_deps', tail new_deps')) - - - session <- return $ \(hieYaml, cfp, opts) -> do - (hscEnv, new, old_deps) <- packageSetup (hieYaml, cfp, opts) - -- TODO Handle the case where there is no hie.yaml - -- Make a map from unit-id to DynFlags, this is used when trying to - -- resolve imports. - let uids = map (\(iuid, (df, _uis, _targets, _cfp, _opts, _di)) -> (iuid, df)) (new : old_deps) - - -- For each component, now make a new HscEnvEq which contains the - -- HscEnv for the hie.yaml file but the DynFlags for that component - -- - -- Then look at the targets for each component and create a map - -- from FilePath to the HscEnv - let new_cache (_iuid, (df, _uis, targets, cfp, _opts, di)) = do - let hscEnv' = hscEnv { hsc_dflags = df - , hsc_IC = (hsc_IC hscEnv) { ic_dflags = df } } - - versionMismatch <- checkGhcVersion - henv <- case versionMismatch of - Just mismatch -> return mismatch - Nothing -> newHscEnvEq hscEnv' uids - let res = (([], Just henv), di) - print res - - let is = importPaths df - ctargets <- concatMapM (targetToFile is . targetId) targets - -- A special target for the file which caused this wonderful - -- component to be created. - let special_target = (cfp, res) - --pprTraceM "TARGETS" (ppr (map (text . show) ctargets)) - let xs = map (,res) ctargets - return (special_target:xs, res) - - -- New HscEnv for the component in question - (cs, res) <- new_cache new - -- Modified cache targets for everything else in the hie.yaml file - -- which now uses the same EPS and so on - cached_targets <- concatMapM (fmap fst . new_cache) old_deps - modifyVar_ fileToFlags $ \var -> do - pure $ Map.insert hieYaml (HM.fromList (cs ++ cached_targets)) var - - return (cs, res) - - lock <- newLock - - -- This caches the mapping from hie.yaml + Mod.hs -> [String] - sessionOpts <- return $ \(hieYaml, file) -> do - - - fm <- readVar fileToFlags - let mv = Map.lookup hieYaml fm - let v = fromMaybe HM.empty mv - cfp <- liftIO $ canonicalizePath file - case HM.lookup (toNormalizedFilePath' cfp) v of - Just (_, old_di) -> do - deps_ok <- checkDependencyInfo old_di - unless deps_ok $ do - modifyVar_ fileToFlags (const (return Map.empty)) - -- Keep the same name cache - modifyVar_ hscEnvs (return . Map.adjust (\(h, _) -> (h, [])) hieYaml ) - Nothing -> return () - -- We sort so exact matches come first. - case HM.lookup (toNormalizedFilePath' cfp) v of - Just opts -> do - --putStrLn $ "Cached component of " <> show file - pure ([], fst opts) - Nothing-> do - finished_barrier <- newBarrier - -- fork a new thread here which won't be killed by shake - -- throwing an async exception - void $ forkIO $ do - putStrLn $ "Consulting the cradle for " <> show file - cradle <- maybe (loadImplicitCradle $ addTrailingPathSeparator dir) loadCradle hieYaml - eopts <- cradleToSessionOpts cradle cfp - print eopts - case eopts of - Right opts -> do - (cs, res) <- session (hieYaml, toNormalizedFilePath' cfp, opts) - signalBarrier finished_barrier (cs, fst res) - Left err -> do - dep_info <- getDependencyInfo ([fp | Just fp <- [hieYaml]]) - let ncfp = toNormalizedFilePath' cfp - let res = (map (renderCradleError ncfp) err, Nothing) - modifyVar_ fileToFlags $ \var -> do - pure $ Map.insertWith HM.union hieYaml (HM.singleton ncfp (res, dep_info)) var - signalBarrier finished_barrier ([(ncfp, (res, dep_info) )], res) - waitBarrier finished_barrier - - dummyAs <- async $ return (error "Uninitialised") - runningCradle <- newIORef dummyAs - -- The main function which gets options for a file. We only want one of these running - -- at a time. - let getOptions file = do - hieYaml <- cradleLoc file - sessionOpts (hieYaml, file) - -- The lock is on the `runningCradle` resource - return $ \file -> do - (cs, opts) <- - liftIO $ withLock lock $ do - as <- readIORef runningCradle - finished <- poll as - case finished of - Just {} -> do - as <- async $ getOptions file - writeIORef runningCradle as - wait as - -- If it's not finished then wait and then get options, this could of course be killed still - Nothing -> do - _ <- wait as - getOptions file - let cfps = map fst cs - -- Delayed to avoid recursion and only run if something changed. - unless (null cs) ( - delay "InitialLoad" ("InitialLoad" :: String, cfps) (void $ do - cfps' <- liftIO $ filterM (IO.doesFileExist . fromNormalizedFilePath) cfps - mmt <- uses GetModificationTime cfps' - let cs_exist = catMaybes (zipWith (<$) cfps' mmt) - uses GetModIface cs_exist)) - return opts +loadSessionShake :: FilePath -> Action (FilePath -> Action (IdeResult HscEnvEq)) +loadSessionShake fp = do + se <- getShakeExtras + IdeOptions{optTesting = IdeTesting ideTesting} <- getIdeOptions + res <- liftIO $ loadSession ideTesting se fp + return res +-- | This is the key function which implements multi-component support. All +-- components mapping to the same hie.yaml file are mapped to the same +-- HscEnv which is updated as new components are discovered. +loadSession :: Bool -> ShakeExtras -> FilePath -> IO (FilePath -> Action (IdeResult HscEnvEq)) +loadSession optTesting ShakeExtras{logger, eventer, withIndefiniteProgress, ideNc} dir = do + -- Mapping from hie.yaml file to HscEnv, one per hie.yaml file + hscEnvs <- newVar Map.empty :: IO (Var HieMap) + -- Mapping from a Filepath to HscEnv + fileToFlags <- newVar Map.empty :: IO (Var FlagsMap) + + libdir <- getLibdir + installationCheck <- ghcVersionChecker libdir + + case installationCheck of + InstallationNotFound{..} -> + error $ "GHC installation not found in libdir: " <> libdir + InstallationMismatch{..} -> + return $ \fp -> return ([renderPackageSetupException compileTime fp GhcVersionMismatch{..}], Nothing) + InstallationChecked compileTime ghcLibCheck -> do + -- This caches the mapping from Mod.hs -> hie.yaml + cradleLoc <- memoIO $ \v -> do + res <- findCradle v + -- Sometimes we get C:, sometimes we get c:, and sometimes we get a relative path + -- try and normalise that + -- e.g. see https://github.com/digital-asset/ghcide/issues/126 + res' <- traverse IO.makeAbsolute res + return $ normalise <$> res' + + -- Create a new HscEnv from a hieYaml root and a set of options + -- If the hieYaml file already has an HscEnv, the new component is + -- combined with the components in the old HscEnv into a new HscEnv + -- which contains the union. + let packageSetup :: (Maybe FilePath, NormalizedFilePath, ComponentOptions) + -> IO (HscEnv, ComponentInfo, [ComponentInfo]) + packageSetup (hieYaml, cfp, opts) = do + -- Parse DynFlags for the newly discovered component + hscEnv <- emptyHscEnv ideNc + (df, targets) <- evalGhcEnv hscEnv $ + setOptions opts (hsc_dflags hscEnv) + dep_info <- getDependencyInfo (componentDependencies opts ++ maybeToList hieYaml) + -- Now lookup to see whether we are combining with an existing HscEnv + -- or making a new one. The lookup returns the HscEnv and a list of + -- information about other components loaded into the HscEnv + -- (unitId, DynFlag, Targets) + modifyVar hscEnvs $ \m -> do + -- Just deps if there's already an HscEnv + -- Nothing is it's the first time we are making an HscEnv + let oldDeps = Map.lookup hieYaml m + let -- Add the raw information about this component to the list + -- We will modify the unitId and DynFlags used for + -- compilation but these are the true source of + -- information. + new_deps = RawComponentInfo (thisInstalledUnitId df) df targets cfp opts dep_info + : maybe [] snd oldDeps + -- Get all the unit-ids for things in this component + inplace = map rawComponentUnitId new_deps + + new_deps' <- forM new_deps $ \RawComponentInfo{..} -> do + -- Remove all inplace dependencies from package flags for + -- components in this HscEnv + let (df2, uids) = removeInplacePackages inplace rawComponentDynFlags + let prefix = show rawComponentUnitId + -- See Note [Avoiding bad interface files] + processed_df <- setCacheDir logger prefix (sort $ map show uids) opts df2 + -- The final component information, mostly the same but the DynFlags don't + -- contain any packages which are also loaded + -- into the same component. + pure $ ComponentInfo rawComponentUnitId + processed_df + uids + rawComponentTargets + rawComponentFP + rawComponentCOptions + rawComponentDependencyInfo + -- Make a new HscEnv, we have to recompile everything from + -- scratch again (for now) + -- It's important to keep the same NameCache though for reasons + -- that I do not fully understand + logInfo logger (T.pack ("Making new HscEnv" ++ show inplace)) + hscEnv <- emptyHscEnv ideNc + newHscEnv <- + -- Add the options for the current component to the HscEnv + evalGhcEnv hscEnv $ do + _ <- setSessionDynFlags df + checkSession logger ghcLibCheck + getSession + + -- Modify the map so the hieYaml now maps to the newly created + -- HscEnv + -- Returns + -- . the new HscEnv so it can be used to modify the + -- FilePath -> HscEnv map (fileToFlags) + -- . The information for the new component which caused this cache miss + -- . The modified information (without -inplace flags) for + -- existing packages + pure (Map.insert hieYaml (newHscEnv, new_deps) m, (newHscEnv, head new_deps', tail new_deps')) + + let session :: (Maybe FilePath, NormalizedFilePath, ComponentOptions) -> IO ([NormalizedFilePath],IdeResult HscEnvEq) + session (hieYaml, cfp, opts) = do + (hscEnv, new, old_deps) <- packageSetup (hieYaml, cfp, opts) + -- Make a map from unit-id to DynFlags, this is used when trying to + -- resolve imports. (especially PackageImports) + let uids = map (\ci -> (componentUnitId ci, componentDynFlags ci)) (new : old_deps) + + -- For each component, now make a new HscEnvEq which contains the + -- HscEnv for the hie.yaml file but the DynFlags for that component + + -- New HscEnv for the component in question, returns the new HscEnvEq and + -- a mapping from FilePath to the newly created HscEnvEq. + let new_cache = newComponentCache logger hscEnv uids + (cs, res) <- new_cache new + -- Modified cache targets for everything else in the hie.yaml file + -- which now uses the same EPS and so on + cached_targets <- concatMapM (fmap fst . new_cache) old_deps + modifyVar_ fileToFlags $ \var -> do + pure $ Map.insert hieYaml (HM.fromList (cs ++ cached_targets)) var + + -- Invalidate all the existing GhcSession build nodes by restarting the Shake session + -- restartShakeSession [kick] + + return (map fst cs, fst res) + + let consultCradle :: Maybe FilePath -> FilePath -> IO ([NormalizedFilePath], IdeResult HscEnvEq) + consultCradle hieYaml cfp = do + when optTesting $ eventer $ notifyCradleLoaded cfp + logInfo logger $ T.pack ("Consulting the cradle for " <> show cfp) + + cradle <- maybe (loadImplicitCradle $ addTrailingPathSeparator dir) loadCradle hieYaml + -- Display a user friendly progress message here: They probably don't know what a + -- cradle is + let progMsg = "Setting up project " <> T.pack (takeBaseName (cradleRootDir cradle)) + eopts <- withIndefiniteProgress progMsg LSP.NotCancellable $ + cradleToSessionOpts cradle cfp + + logDebug logger $ T.pack ("Session loading result: " <> show eopts) + case eopts of + -- The cradle gave us some options so get to work turning them + -- into and HscEnv. + Right opts -> do + session (hieYaml, toNormalizedFilePath' cfp, opts) + -- Failure case, either a cradle error or the none cradle + Left err -> do + dep_info <- getDependencyInfo (maybeToList hieYaml) + let ncfp = toNormalizedFilePath' cfp + let res = (map (renderCradleError ncfp) err, Nothing) + modifyVar_ fileToFlags $ \var -> do + pure $ Map.insertWith HM.union hieYaml (HM.singleton ncfp (res, dep_info)) var + return ([ncfp],res) + + -- This caches the mapping from hie.yaml + Mod.hs -> [String] + let sessionOpts :: (Maybe FilePath, FilePath) -> IO ([NormalizedFilePath],IdeResult HscEnvEq) + sessionOpts (hieYaml, file) = do + v <- fromMaybe HM.empty . Map.lookup hieYaml <$> readVar fileToFlags + cfp <- canonicalizePath file + case HM.lookup (toNormalizedFilePath' cfp) v of + Just (opts, old_di) -> do + deps_ok <- checkDependencyInfo old_di + if not deps_ok + then do + -- If the dependencies are out of date then clear both caches and start + -- again. + modifyVar_ fileToFlags (const (return Map.empty)) + -- Keep the same name cache + modifyVar_ hscEnvs (return . Map.adjust (\(h, _) -> (h, [])) hieYaml ) + consultCradle hieYaml cfp + else return ([], opts) + Nothing -> consultCradle hieYaml cfp + + dummyAs <- async $ return (error "Uninitialised") + runningCradle <- newVar dummyAs :: IO (Var (Async (IdeResult HscEnvEq))) + -- The main function which gets options for a file. We only want one of these running + -- at a time. Therefore the IORef contains the currently running cradle, if we try + -- to get some more options then we wait for the currently running action to finish + -- before attempting to do so. + let getOptions :: FilePath -> IO ([NormalizedFilePath],IdeResult HscEnvEq) + getOptions file = do + hieYaml <- cradleLoc file + sessionOpts (hieYaml, file) `catch` \e -> do + return ([],([renderPackageSetupException compileTime file e], Nothing)) + + return $ \file -> do + (cs, opts) <- liftIO $ join $ mask_ $ modifyVar runningCradle $ \as -> do + -- If the cradle is not finished, then wait for it to finish. + void $ wait as + as <- async $ getOptions file + return $ (fmap snd as, wait as) + let cfps = cs + unless (null cs) $ + delay "InitialLoad" $ void $ do + cfps' <- liftIO $ filterM (IO.doesFileExist . fromNormalizedFilePath) cfps + mmt <- uses GetModificationTime cfps' + let cs_exist = catMaybes (zipWith (<$) cfps' mmt) + uses GetModIface cs_exist + pure opts + + + +-- | Create a mapping from FilePaths to HscEnvEqs +newComponentCache + :: Logger + -> HscEnv + -> [(InstalledUnitId, DynFlags)] + -> ComponentInfo + -> IO ([(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))], (IdeResult HscEnvEq, DependencyInfo)) +newComponentCache logger hsc_env uids ci = do + let df = componentDynFlags ci + let hscEnv' = hsc_env { hsc_dflags = df + , hsc_IC = (hsc_IC hsc_env) { ic_dflags = df } } + + henv <- newHscEnvEq hscEnv' uids + let res = (([], Just henv), componentDependencyInfo ci) + logDebug logger ("New Component Cache HscEnvEq: " <> T.pack (show res)) + + let is = importPaths df + ctargets <- concatMapM (targetToFile is . targetId) (componentTargets ci) + -- A special target for the file which caused this wonderful + -- component to be created. In case the cradle doesn't list all the targets for + -- the component, in which case things will be horribly broken anyway. + -- Otherwise, we will immediately attempt to reload this module which + -- causes an infinite loop and high CPU usage. + let special_target = (componentFP ci, res) + let xs = map (,res) ctargets + return (special_target:xs, res) {- Note [Avoiding bad interface files] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -546,40 +583,92 @@ E.g. when you load two executables, they can not depend on each other. They should be filtered out, such that we dont have to re-compile everything. -} - -setCacheDir :: MonadIO m => String -> [String] -> ComponentOptions -> DynFlags -> m DynFlags -setCacheDir prefix hscComponents comps dflags = do +-- | Set the cache-directory based on the ComponentOptions and a list of +-- internal packages. +-- For the exact reason, see Note [Avoiding bad interface files]. +setCacheDir :: MonadIO m => Logger -> String -> [String] -> ComponentOptions -> DynFlags -> m DynFlags +setCacheDir logger prefix hscComponents comps dflags = do cacheDir <- liftIO $ getCacheDir prefix (hscComponents ++ componentOptions comps) + liftIO $ logInfo logger $ "Using interface files cache dir: " <> T.pack cacheDir pure $ dflags & setHiDir cacheDir - & setDefaultHieDir cacheDir + & setHieDir cacheDir renderCradleError :: NormalizedFilePath -> CradleError -> FileDiagnostic renderCradleError nfp (CradleError _ec t) = - ideErrorText nfp (T.unlines (map T.pack t)) + ideErrorWithSource (Just "cradle") (Just DsError) nfp (T.unlines (map T.pack t)) + +-- See Note [Multi Cradle Dependency Info] +type DependencyInfo = Map.Map FilePath (Maybe UTCTime) +type HieMap = Map.Map (Maybe FilePath) (HscEnv, [RawComponentInfo]) +type FlagsMap = Map.Map (Maybe FilePath) (HM.HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)) + +-- This is pristine information about a component +data RawComponentInfo = RawComponentInfo + { rawComponentUnitId :: InstalledUnitId + -- | Unprocessed DynFlags. Contains inplace packages such as libraries. + -- We do not want to use them unprocessed. + , rawComponentDynFlags :: DynFlags + -- | All targets of this components. + , rawComponentTargets :: [Target] + -- | Filepath which caused the creation of this component + , rawComponentFP :: NormalizedFilePath + -- | Component Options used to load the component. + , rawComponentCOptions :: ComponentOptions + -- | Maps cradle dependencies, such as `stack.yaml`, or `.cabal` file + -- to last modification time. See Note [Multi Cradle Dependency Info]. + , rawComponentDependencyInfo :: DependencyInfo + } +-- This is processed information about the component, in particular the dynflags will be modified. +data ComponentInfo = ComponentInfo + { componentUnitId :: InstalledUnitId + -- | Processed DynFlags. Does not contain inplace packages such as local + -- libraries. Can be used to actually load this Component. + , componentDynFlags :: DynFlags + -- | Internal units, such as local libraries, that this component + -- is loaded with. These have been extracted from the original + -- ComponentOptions. + , componentInternalUnits :: [InstalledUnitId] + -- | All targets of this components. + , componentTargets :: [Target] + -- | Filepath which caused the creation of this component + , componentFP :: NormalizedFilePath + -- | Component Options used to load the component. + , componentCOptions :: ComponentOptions + -- | Maps cradle dependencies, such as `stack.yaml`, or `.cabal` file + -- to last modification time. See Note [Multi Cradle Dependency Info] + , componentDependencyInfo :: DependencyInfo + } -checkDependencyInfo :: Map.Map FilePath (Maybe UTCTime) -> IO Bool +-- | Check if any dependency has been modified lately. +checkDependencyInfo :: DependencyInfo -> IO Bool checkDependencyInfo old_di = do di <- getDependencyInfo (Map.keys old_di) return (di == old_di) - - -getDependencyInfo :: [FilePath] -> IO (Map.Map FilePath (Maybe UTCTime)) +-- Note [Multi Cradle Dependency Info] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- Why do we implement our own file modification tracking here? +-- The primary reason is that the custom caching logic is quite complicated and going into shake +-- adds even more complexity and more indirection. I did try for about 5 hours to work out how to +-- use shake rules rather than IO but eventually gave up. + +-- | Computes a mapping from a filepath to its latest modification date. +-- See Note [Multi Cradle Dependency Info] why we do this ourselves instead +-- of letting shake take care of it. +getDependencyInfo :: [FilePath] -> IO DependencyInfo getDependencyInfo fs = Map.fromList <$> mapM do_one fs where - do_one fp = do - exists <- IO.doesFileExist fp - if exists - then do - mtime <- getModificationTime fp - return (fp, Just mtime) - else return (fp, Nothing) - --- This function removes all the -package flags which refer to packages we + tryIO :: IO a -> IO (Either IOException a) + tryIO = try + + do_one :: FilePath -> IO (FilePath, Maybe UTCTime) + do_one fp = (fp,) . eitherToMaybe <$> tryIO (getModificationTime fp) + +-- | This function removes all the -package flags which refer to packages we -- are going to deal with ourselves. For example, if a executable depends -- on a library component, then this function will remove the library flag -- from the package flags for the executable @@ -593,7 +682,9 @@ removeInplacePackages us df = (df { packageFlags = ps where (uids, ps) = partitionEithers (map go (packageFlags df)) fake_uid = toInstalledUnitId (stringToUnitId "fake_uid") - go p@(ExposePackage _ (UnitIdArg u) _) = if (toInstalledUnitId u `elem` us) then Left (toInstalledUnitId u) else Right p + go p@(ExposePackage _ (UnitIdArg u) _) = if toInstalledUnitId u `elem` us + then Left (toInstalledUnitId u) + else Right p go p = Right p -- | Memoize an IO function, with the characteristics: @@ -613,10 +704,10 @@ memoIO op = do return (Map.insert k res mp, res) Just res -> return (mp, res) -setOptions :: GhcMonad m =>ComponentOptions -> DynFlags -> m (DynFlags, [Target]) +-- | Throws if package flags are unsatisfiable +setOptions :: GhcMonad m => ComponentOptions -> DynFlags -> m (DynFlags, [Target]) setOptions (ComponentOptions theOpts compRoot _) dflags = do - (dflags_, targets) <- addCmdOpts theOpts dflags - let dflags' = makeDynFlagsAbsolute compRoot dflags_ + (dflags', targets) <- addCmdOpts theOpts dflags let dflags'' = -- disabled, generated directly by ghcide instead flip gopt_unset Opt_WriteInterface $ @@ -625,11 +716,12 @@ setOptions (ComponentOptions theOpts compRoot _) dflags = do dontWriteHieFiles $ setIgnoreInterfacePragmas $ setLinkerOptions $ - disableOptimisation dflags' + disableOptimisation $ + makeDynFlagsAbsolute compRoot dflags' -- initPackages parses the -package flags and -- sets up the visibility for each component. - (final_df, _) <- liftIO $ initPackages dflags'' --- let df'' = gopt_unset df' Opt_WarnIsError + -- Throws if a -package flag cannot be satisfied. + (final_df, _) <- liftIO $ wrapPackageSetupException $ initPackages dflags'' return (final_df, targets) @@ -660,23 +752,79 @@ getCacheDir prefix opts = IO.getXdgDirectory IO.XdgCache (cacheDir prefix ++ where -- Create a unique folder per set of different GHC options, assuming that each different set of -- GHC options will create incompatible interface files. - opts_hash = B.unpack $ encode $ H.finalize $ H.updates H.init $ (map B.pack opts) + opts_hash = B.unpack $ encode $ H.finalize $ H.updates H.init (map B.pack opts) --- Prefix for the cache path +-- | Sub directory for the cache path cacheDir :: String cacheDir = "ghcide" -ghcVersionChecker :: IO VersionCheck -ghcVersionChecker = $$(makeGhcVersionChecker (pure <$> getLibdir)) - -checkGhcVersion :: IO (Maybe HscEnvEq) -checkGhcVersion = do - res <- ghcVersionChecker - case res of - Failure err -> do - putStrLn $ "Error while checking GHC version: " ++ show err - return Nothing - Mismatch {..} -> - return $ Just GhcVersionMismatch {..} - _ -> - return Nothing +notifyCradleLoaded :: FilePath -> FromServerMessage +notifyCradleLoaded fp = + NotCustomServer $ + NotificationMessage "2.0" (CustomServerMethod cradleLoadedMethod) $ + toJSON fp + +cradleLoadedMethod :: T.Text +cradleLoadedMethod = "ghcide/cradle/loaded" + +---------------------------------------------------------------------------------------------------- + +ghcVersionChecker :: GhcVersionChecker +ghcVersionChecker = $$(makeGhcVersionChecker getLibdir) + +-- | Throws a 'PackageSetupException' if the 'Session' cannot be used by ghcide +checkSession :: Logger -> Ghc PackageCheckResult -> Ghc () +checkSession logger ghcLibCheck = + ghcLibCheck >>= \res -> case guessCompatibility res of + ProbablyCompatible mbWarning -> + for_ mbWarning $ liftIO . logInfo logger . T.pack + NotCompatible err -> + liftIO $ throwIO $ PackageCheckFailed err + +data PackageSetupException + = PackageSetupException + { message :: !String + } + | GhcVersionMismatch + { compileTime :: !Version + , runTime :: !Version + } + | PackageCheckFailed !NotCompatibleReason + deriving (Eq, Show, Typeable) + +instance Exception PackageSetupException + +-- | Wrap any exception as a 'PackageSetupException' +wrapPackageSetupException :: IO a -> IO a +wrapPackageSetupException = handleAny $ \case + e | Just (pkgE :: PackageSetupException) <- fromException e -> throwIO pkgE + e -> (throwIO . PackageSetupException . show) e + +showPackageSetupException :: Version -> PackageSetupException -> String +showPackageSetupException _ GhcVersionMismatch{..} = unwords + ["ghcide compiled against GHC" + ,showVersion compileTime + ,"but currently using" + ,showVersion runTime + ,"\nThis is unsupported, ghcide must be compiled with the same GHC version as the project." + ] +showPackageSetupException compileTime PackageSetupException{..} = unwords + [ "ghcide compiled by GHC", showVersion compileTime + , "failed to load packages:", message <> "." + , "\nPlease ensure that ghcide is compiled with the same GHC installation as the project."] +showPackageSetupException _ (PackageCheckFailed PackageVersionMismatch{..}) = unwords + ["ghcide compiled with package " + , packageName <> "-" <> showVersion compileTime + ,"but project uses package" + , packageName <> "-" <> showVersion runTime + ,"\nThis is unsupported, ghcide must be compiled with the same GHC installation as the project." + ] +showPackageSetupException _ (PackageCheckFailed BasePackageAbiMismatch{..}) = unwords + ["ghcide compiled with base-" <> showVersion compileTime <> "-" <> compileTimeAbi + ,"but project uses base-" <> showVersion compileTime <> "-" <> runTimeAbi + ,"\nThis is unsupported, ghcide must be compiled with the same GHC installation as the project." + ] + +renderPackageSetupException :: Version -> FilePath -> PackageSetupException -> (NormalizedFilePath, ShowDiagnostic, Diagnostic) +renderPackageSetupException compileTime fp e = + ideErrorWithSource (Just "cradle") (Just DsError) (toNormalizedFilePath' fp) (T.pack $ showPackageSetupException compileTime e) diff --git a/ghcide b/ghcide index 3ee692a4cd..977663126b 160000 --- a/ghcide +++ b/ghcide @@ -1 +1 @@ -Subproject commit 3ee692a4cdb98792c371765c9f8adb5237d0a515 +Subproject commit 977663126b938cd99c8746150458f9bd1031f01a diff --git a/haskell-language-server.cabal b/haskell-language-server.cabal index 187d75e6b5..ca8b41cadd 100644 --- a/haskell-language-server.cabal +++ b/haskell-language-server.cabal @@ -154,7 +154,7 @@ executable haskell-language-server -- which works for now. , ghc -------------------------------------------------------------- - , ghc-check >= 0.3.0.1 && < 0.4 + , ghc-check >= 0.5.0.1 && < 0.6 , ghc-paths , ghcide , gitrev @@ -164,6 +164,7 @@ executable haskell-language-server , haskell-language-server , hslogger , optparse-applicative + , safe-exceptions , shake >= 0.17.5 , text , time diff --git a/src/Ide/Plugin/Example.hs b/src/Ide/Plugin/Example.hs index 17ecb08efc..63f7083b37 100644 --- a/src/Ide/Plugin/Example.hs +++ b/src/Ide/Plugin/Example.hs @@ -122,7 +122,7 @@ codeLens _lf ideState plId CodeLensParams{_textDocument=TextDocumentIdentifier u logInfo (ideLogger ideState) "Example.codeLens entered (ideLogger)" -- AZ case uriToFilePath' uri of Just (toNormalizedFilePath -> filePath) -> do - _ <- runIdeAction "Example.codeLens" ideState $ runMaybeT $ useE TypeCheck filePath + _ <- runIdeAction "Example.codeLens" (shakeExtras ideState) $ runMaybeT $ useE TypeCheck filePath _diag <- getDiagnostics ideState _hDiag <- getHiddenDiagnostics ideState let diff --git a/src/Ide/Plugin/Example2.hs b/src/Ide/Plugin/Example2.hs index d91d14e296..acfdbffdd2 100644 --- a/src/Ide/Plugin/Example2.hs +++ b/src/Ide/Plugin/Example2.hs @@ -122,7 +122,7 @@ codeLens _lf ideState plId CodeLensParams{_textDocument=TextDocumentIdentifier u logInfo (ideLogger ideState) "Example2.codeLens entered (ideLogger)" -- AZ case uriToFilePath' uri of Just (toNormalizedFilePath -> filePath) -> do - _ <- runIdeAction (fromNormalizedFilePath filePath) ideState $ runMaybeT $ useE TypeCheck filePath + _ <- runIdeAction (fromNormalizedFilePath filePath) (shakeExtras ideState) $ runMaybeT $ useE TypeCheck filePath _diag <- getDiagnostics ideState _hDiag <- getHiddenDiagnostics ideState let diff --git a/stack-8.10.1.yaml b/stack-8.10.1.yaml index 2cc5a3a9a0..06455feb25 100644 --- a/stack-8.10.1.yaml +++ b/stack-8.10.1.yaml @@ -1,4 +1,4 @@ -resolver: nightly-2020-05-12 +resolver: nightly-2020-06-15 compiler: ghc-8.10.1 packages: @@ -7,22 +7,21 @@ packages: extra-deps: - Cabal-3.2.0.0 -- cabal-helper-1.1.0.0 -# See https://github.com/haskell-hvr/cabal-plan/pull/55 -- github: peti/cabal-plan - commit: 894b76c0b6bf8f7d2f881431df1f13959a8fce87 +# - cabal-helper-1.1.0.0 +- github: DanielG/cabal-helper + commit: 79a5608778493bf32e74b54bbf1ea2729941e50f +- cabal-plan-0.7.0.0 - clock-0.7.2 - floskell-0.10.3 -# - ghcide-0.1.0 - ghc-exactprint-0.6.3 -- ghc-lib-parser-8.10.1.20200523 - lens-4.19.1 +- lsp-test-0.11.0.2 - monad-dijkstra-0.1.1.2 - optics-core-0.3 -- github: wz1000/shake - commit: fb3859dca2e54d1bbb2c873e68ed225fa179fbef +- ormolu-0.0.5.0 - semigroups-0.18.5 - temporary-1.2.1.1 +- these-1.1 flags: haskell-language-server: @@ -37,4 +36,4 @@ flags: nix: packages: [ icu libcxx zlib ] -concurrent-tests: false \ No newline at end of file +concurrent-tests: false diff --git a/stack-8.6.4.yaml b/stack-8.6.4.yaml index b45f9048a5..932bfdf120 100644 --- a/stack-8.6.4.yaml +++ b/stack-8.6.4.yaml @@ -18,7 +18,7 @@ extra-deps: - extra-1.6.21 - floskell-0.10.3 - fuzzy-0.1.0.0 -- ghc-check-0.3.0.1 +- ghc-check-0.5.0.1 - ghc-exactprint-0.6.2 # for HaRe - ghc-lib-parser-8.10.1.20200523 - ghc-lib-parser-ex-8.10.0.4 @@ -36,7 +36,7 @@ extra-deps: - HsYAML-0.2.1.0@rev:1 - HsYAML-aeson-0.2.0.0@rev:1 - lens-4.18 -- lsp-test-0.10.3.0 +- lsp-test-0.11.0.2 - microlens-th-0.4.2.3@rev:1 - monad-dijkstra-0.1.1.2 - monad-memo-0.4.1 @@ -47,9 +47,9 @@ extra-deps: - regex-base-0.94.0.0 - regex-tdfa-1.3.1.0 - rope-utf16-splay-0.3.1.0 -# - shake-0.18.5 -- github: wz1000/shake - commit: fb3859dca2e54d1bbb2c873e68ed225fa179fbef +- shake-0.19.1 +# - github: wz1000/shake +# commit: fb3859dca2e54d1bbb2c873e68ed225fa179fbef - stylish-haskell-0.11.0.0 - syz-0.2.0.0 - tasty-rerun-1.1.17 diff --git a/stack-8.6.5.yaml b/stack-8.6.5.yaml index f30a7efe53..1dcf7de917 100644 --- a/stack-8.6.5.yaml +++ b/stack-8.6.5.yaml @@ -1,4 +1,4 @@ -resolver: lts-14.27 # Last 8.6.5 +resolver: lts-14.27 # Last 8.6.5 packages: - . @@ -17,7 +17,7 @@ extra-deps: - floskell-0.10.3 - fuzzy-0.1.0.0 # - ghcide-0.1.0 -- ghc-check-0.3.0.1 +- ghc-check-0.5.0.1 - ghc-lib-parser-8.10.1.20200523 - ghc-lib-parser-ex-8.10.0.4 - haddock-api-2.22.0@rev:1 @@ -29,7 +29,7 @@ extra-deps: - HsYAML-aeson-0.2.0.0@rev:1 - indexed-profunctors-0.1 - lens-4.18 -- lsp-test-0.10.3.0 +- lsp-test-0.11.0.2 - monad-dijkstra-0.1.1.2 - opentelemetry-0.4.0 - optics-core-0.2 @@ -40,8 +40,8 @@ extra-deps: - regex-pcre-builtin-0.95.1.1.8.43 - regex-tdfa-1.3.1.0 - semialign-1.1 -- github: wz1000/shake - commit: fb3859dca2e54d1bbb2c873e68ed225fa179fbef +# - github: wz1000/shake +# commit: fb3859dca2e54d1bbb2c873e68ed225fa179fbef - stylish-haskell-0.11.0.0 - tasty-rerun-1.1.17 - temporary-1.2.1.1 diff --git a/stack-8.8.2.yaml b/stack-8.8.2.yaml index ea55a65fb0..08fd97a8c7 100644 --- a/stack-8.8.2.yaml +++ b/stack-8.8.2.yaml @@ -12,7 +12,7 @@ extra-deps: - constrained-dynamic-0.1.0.0 - floskell-0.10.3 # - ghcide-0.1.0 -- ghc-check-0.3.0.1 +- ghc-check-0.5.0.1 - ghc-lib-parser-8.10.1.20200523 - ghc-lib-parser-ex-8.10.0.4 - haddock-library-1.8.0 @@ -26,13 +26,13 @@ extra-deps: - HsYAML-0.2.1.0@rev:1 - HsYAML-aeson-0.2.0.0@rev:1 - ilist-0.3.1.0 -- lsp-test-0.10.3.0 +- lsp-test-0.11.0.2 - monad-dijkstra-0.1.1.2 - opentelemetry-0.4.0 - ormolu-0.0.5.0 - semigroups-0.18.5 -- github: wz1000/shake - commit: fb3859dca2e54d1bbb2c873e68ed225fa179fbef +# - github: wz1000/shake +# commit: fb3859dca2e54d1bbb2c873e68ed225fa179fbef - stylish-haskell-0.11.0.0 - temporary-1.2.1.1 diff --git a/stack-8.8.3.yaml b/stack-8.8.3.yaml index a8d218f591..d3a7018519 100644 --- a/stack-8.8.3.yaml +++ b/stack-8.8.3.yaml @@ -12,7 +12,7 @@ extra-deps: - constrained-dynamic-0.1.0.0 - floskell-0.10.3 # - ghcide-0.1.0 -- ghc-check-0.3.0.1 +- ghc-check-0.5.0.1 - ghc-lib-parser-8.10.1.20200523 - ghc-lib-parser-ex-8.10.0.4 - haskell-lsp-0.22.0.0 @@ -23,13 +23,13 @@ extra-deps: - hoogle-5.0.17.11 - hsimport-0.11.0 - ilist-0.3.1.0 -- lsp-test-0.10.3.0 +- lsp-test-0.11.0.2 - monad-dijkstra-0.1.1.2 - opentelemetry-0.4.0 - ormolu-0.0.5.0 - semigroups-0.18.5 -- github: wz1000/shake - commit: fb3859dca2e54d1bbb2c873e68ed225fa179fbef +# - github: wz1000/shake +# commit: fb3859dca2e54d1bbb2c873e68ed225fa179fbef - stylish-haskell-0.11.0.0 - temporary-1.2.1.1 diff --git a/stack.yaml b/stack.yaml index b2e872a84e..1dcf7de917 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,4 +1,4 @@ -resolver: lts-14.27 # Last 8.6.5 +resolver: lts-14.27 # Last 8.6.5 packages: - . @@ -14,10 +14,10 @@ extra-deps: - cabal-plan-0.6.2.0 - clock-0.7.2 - extra-1.7.1 -- floskell-0.10.2 +- floskell-0.10.3 - fuzzy-0.1.0.0 # - ghcide-0.1.0 -- ghc-check-0.3.0.1 +- ghc-check-0.5.0.1 - ghc-lib-parser-8.10.1.20200523 - ghc-lib-parser-ex-8.10.0.4 - haddock-api-2.22.0@rev:1 @@ -29,7 +29,7 @@ extra-deps: - HsYAML-aeson-0.2.0.0@rev:1 - indexed-profunctors-0.1 - lens-4.18 -- lsp-test-0.10.3.0 +- lsp-test-0.11.0.2 - monad-dijkstra-0.1.1.2 - opentelemetry-0.4.0 - optics-core-0.2 @@ -40,8 +40,8 @@ extra-deps: - regex-pcre-builtin-0.95.1.1.8.43 - regex-tdfa-1.3.1.0 - semialign-1.1 -- github: wz1000/shake - commit: fb3859dca2e54d1bbb2c873e68ed225fa179fbef +# - github: wz1000/shake +# commit: fb3859dca2e54d1bbb2c873e68ed225fa179fbef - stylish-haskell-0.11.0.0 - tasty-rerun-1.1.17 - temporary-1.2.1.1