From 8fd5cba63213736e8720799a57afab32c8ef544b Mon Sep 17 00:00:00 2001 From: Samuel Pilz Date: Tue, 9 Apr 2019 00:54:16 +0200 Subject: [PATCH 01/13] improve consistency in the install.hs script --- install.hs | 192 +++++++++++++++++++++++++---------------------------- 1 file changed, 91 insertions(+), 101 deletions(-) diff --git a/install.hs b/install.hs index 6484b5ce4..81f35cbf0 100755 --- a/install.hs +++ b/install.hs @@ -4,11 +4,17 @@ --resolver nightly-2018-12-15 --package shake --package directory + --package extra -} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE TupleSections #-} import Development.Shake import Development.Shake.Command import Development.Shake.FilePath import Control.Monad +import Control.Monad.IO.Class +import Control.Monad.Extra (unlessM, mapMaybeM) +import Data.Maybe (isJust) import System.Directory ( findExecutable ) import System.Environment ( getProgName , unsetEnv @@ -19,6 +25,7 @@ import System.Info ( os import Data.List ( dropWhileEnd , intersperse + , intercalate ) import Data.Char ( isSpace ) @@ -57,7 +64,7 @@ main = do want ["short-help"] -- general purpose targets phony "submodules" updateSubmodules - phony "cabal" (getStackGhcPath mostRecentHieVersion >>= installCabal) + phony "cabal" installCabal phony "short-help" shortHelpMessage phony "all" shortHelpMessage phony "help" helpMessage @@ -72,11 +79,9 @@ main = do ) liftIO $ putStrLn $ embedInStars msg - -- stack specific targets phony "build" (need (reverse $ map ("hie-" ++) hieVersions)) - phony "build-all" (need ["build-docs", "build"]) - phony "build-docs" (need (reverse $ map ("build-doc-" ++) hieVersions)) + phony "build-all" (need ["build-doc", "build"]) phony "test" $ do need ["submodules"] need ["cabal"] @@ -84,14 +89,11 @@ main = do phony "build-copy-compiler-tool" $ forM_ hieVersions buildCopyCompilerTool - phony "stack-build-doc" stackBuildDoc - forM_ - hieVersions - (\version -> phony ("build-doc-" ++ version) $ do + phony "build-doc" $ do need ["submodules"] - need ["cabal"] - need ["stack-build-doc"] - ) + stackBuildDoc + + -- main targets for building hie with `stack` forM_ hieVersions (\version -> phony ("hie-" ++ version) $ do @@ -103,22 +105,17 @@ main = do -- cabal specific targets phony "cabal-build" (need (map ("cabal-hie-" ++) ghcVersions)) - phony "cabal-build-all" (need ["cabal-build-docs", "cabal-build"]) - phony "cabal-build-docs" (need (map ("cabal-build-doc-" ++) ghcVersions)) + phony "cabal-build-all" (need ["cabal-build-doc", "cabal-build"]) + phony "cabal-build-doc" $ do + need ["submodules"] + need ["cabal"] + cabalBuildDoc phony "cabal-test" $ do need ["submodules"] need ["cabal"] forM_ ghcVersions cabalTest - phony "cabal-doc" cabalBuildDoc - forM_ - hieVersions - (\version -> phony ("cabal-build-doc-" ++ version) $ do - need ["submodules"] - need ["cabal"] - need ["cabal-doc"] - ) forM_ hieVersions (\version -> phony ("cabal-hie-" ++ version) $ do @@ -145,6 +142,7 @@ buildIcuMacosFix version = execStackWithYaml_ , "--extra-include-dirs=/usr/local/opt/icu4c/include" ] +-- |update the submodules that the project is in the state as required by the `stack.yaml` files updateSubmodules :: Action () updateSubmodules = do command_ [] "git" ["submodule", "sync", "--recursive"] @@ -157,9 +155,8 @@ validateCabalNewInstallIsSupported = when (os `elem` ["mingw32", "win32"]) $ do configureCabal :: VersionNumber -> Action () configureCabal versionNumber = do - ghcPath' <- liftIO $ getGhcPath versionNumber - ghcPath <- case ghcPath' of - Nothing -> do + ghcPath <- getGhcPath versionNumber >>= \case + Nothing -> do -- TODO: this is better written using a monad-transformer liftIO $ putStrLn $ embedInStars (ghcVersionNotFound versionNumber) error (ghcVersionNotFound versionNumber) Just p -> return p @@ -167,14 +164,12 @@ configureCabal versionNumber = do ["new-configure", "-w", ghcPath, "--write-ghc-environment-files=never"] findInstalledGhcs :: IO [(VersionNumber, GhcPath)] -findInstalledGhcs = foldM - (\found version -> do - path <- getGhcPath version - case path of - Nothing -> return found - Just p -> return $ (version, p) : found +findInstalledGhcs = mapMaybeM + (\version -> do + getGhcPath version >>= \case + Nothing -> return Nothing + Just p -> return $ Just (version, p) ) - [] hieVersions cabalBuildHie :: VersionNumber -> Action () @@ -198,36 +193,30 @@ cabalInstallHie versionNumber = do (localBin "hie-" ++ dropExtension versionNumber <.> exe) cabalBuildDoc :: Action () -cabalBuildDoc = generateHoogleDatabase $ do - localBin <- getLocalBin - execCabal_ ["new-install", "--symlink-bindir=" ++ localBin, "hoogle"] +cabalBuildDoc = do + execCabal_ ["new-build", "hoogle", "generate"] execCabal_ ["new-exec", "hoogle", "generate"] -generateHoogleDatabase :: Action () -> Action () -generateHoogleDatabase installIfNecessary = do - mayHoogle <- liftIO $ findExecutable "hoogle" - case mayHoogle of - Nothing -> installIfNecessary - Just hoogle -> command_ [] "hoogle" ["generate"] - - cabalTest :: VersionNumber -> Action () cabalTest versionNumber = do configureCabal versionNumber execCabal_ ["new-test"] -installCabal :: GhcPath -> Action () -installCabal ghc = do - execStack_ ["install", "--stack-yaml=shake.yaml", "cabal-install"] +installCabal :: Action () +installCabal = do + -- install `cabal-install` if not already installed + unlessM (existsExecutable "cabal") $ do + execStack_ ["install", "--stack-yaml=shake.yaml", "cabal-install"] execCabal_ ["update"] + ghc <- getStackGhcPath mostRecentHieVersion execCabal_ ["install", "Cabal-2.4.1.0", "--with-compiler=" ++ ghc] stackBuildHie :: VersionNumber -> Action () stackBuildHie versionNumber = do - execStackWithYaml_ versionNumber ["install", "happy"] execStackWithYaml_ versionNumber ["build"] `actionOnException` liftIO (putStrLn stackBuildFailMsg) +-- | copy the built binaries into the localBinDir stackInstallHie :: VersionNumber -> Action () stackInstallHie versionNumber = do execStackWithYaml_ versionNumber ["install"] @@ -247,10 +236,11 @@ stackTest :: VersionNumber -> Action () stackTest versionNumber = execStackWithYaml_ versionNumber ["test"] stackBuildDoc :: Action () -stackBuildDoc = generateHoogleDatabase $ do - execStack_ ["--stack-yaml=shake.yaml", "install", "hoogle"] +stackBuildDoc = do + execStack_ ["--stack-yaml=shake.yaml", "build", "hoogle"] execStack_ ["--stack-yaml=shake.yaml", "exec", "hoogle", "generate"] +-- | short help message is printed by default shortHelpMessage :: Action () shortHelpMessage = do let out = liftIO . putStrLn @@ -275,25 +265,19 @@ shortHelpMessage = do ++ allVersionMessage hieVersions ++ ")" ) - , ( "build-all" - , "Builds hie and hoogle databases for all supported GHC versions" - ) + , stackBuildAllTarget , stackHieTarget mostRecentHieVersion - , stackBuildDocTarget mostRecentHieVersion + , stackBuildDocTarget , stackHieTarget "8.4.4" - , stackBuildDocTarget "8.4.4" , emptyTarget , ( "cabal-ghcs" , "Show all GHC versions that can be installed via `cabal-build` and `cabal-build-all`." ) - , ("cabal-build", "Builds hie with cabal with all installed GHCs.") - , ( "cabal-build-all" - , "Builds hie and hoogle databases for all installed GHC versions with cabal" - ) + , cabalBuildTarget + , cabalBuildAllTarget , cabalHieTarget mostRecentHieVersion - , cabalBuildDocTarget mostRecentHieVersion + , cabalBuildDocTarget , cabalHieTarget "8.4.4" - , cabalBuildDocTarget "8.4.4" ] @@ -315,13 +299,13 @@ helpMessage = do -- All targets the shake file supports targets :: [(String, String)] targets = - generalTargets - ++ [emptyTarget] - ++ stackTargets - ++ [emptyTarget] - ++ cabalTargets - ++ [emptyTarget] - ++ macosTargets + intercalate + [emptyTarget] + [ generalTargets + , stackTargets + , cabalTargets + , macosTargets + ] -- All targets with their respective help message. generalTargets = @@ -339,39 +323,29 @@ helpMessage = do ++ allVersionMessage hieVersions ++ ")" ) - , ( "build-all" - , "Builds hie and hoogle databases for all supported GHC versions" - ) - , ( "build-docs" - , "Builds the Hoogle database for all supported GHC versions" - ) + , stackBuildAllTarget + , stackBuildDocTarget , ("test", "Runs hie tests with stack") ] ++ map stackHieTarget hieVersions - ++ map stackBuildDocTarget hieVersions cabalTargets = [ ( "cabal-ghcs" , "Show all GHC versions that can be installed via `cabal-build` and `cabal-build-all`." ) - , ("cabal-build", "Builds hie with cabal with all installed GHCs.") - , ( "cabal-build-all" - , "Builds hie and hoogle databases for all installed GHC versions with cabal" - ) - , ( "cabal-build-docs" - , "Builds the Hoogle database for all installed GHC versions with cabal" - ) + , cabalBuildTarget + , cabalBuildAllTarget + , cabalBuildDocTarget , ("cabal-test", "Runs hie tests with cabal") ] ++ map cabalHieTarget hieVersions - ++ map cabalBuildDocTarget hieVersions -- | Empty target. Purpose is to introduce a newline between the targets emptyTarget :: (String, String) emptyTarget = ("", "") -- |Number of spaces the target name including whitespace should have. --- At least twenty, maybe more if target names are long. At most length of the longest target plus five. +-- At least twenty, maybe more if target names are long and at least the length of the longest target plus five. space :: [(String, String)] -> Int space phonyTargets = maximum (20 : map ((+ 5) . length . fst) phonyTargets) @@ -395,20 +369,32 @@ cabalHieTarget version = , "Builds hie for GHC version " ++ version ++ " only with cabal new-build" ) -stackBuildDocTarget :: VersionNumber -> (String, String) -stackBuildDocTarget version = - ( "build-doc-" ++ version - , "Builds the Hoogle database for GHC version " - ++ version - ++ " only with stack" +stackBuildDocTarget :: (String, String) +stackBuildDocTarget = + ( "build-doc" + , "Builds the Hoogle database" + ) + +stackBuildAllTarget :: (String, String) +stackBuildAllTarget = + ( "build-all" + , "Builds hie for all supported GHC versions and the hoogle database" + ) + +cabalBuildTarget :: (String, String) +cabalBuildTarget = + ("cabal-build", "Builds hie with cabal with all installed GHCs.") + +cabalBuildDocTarget :: (String, String) +cabalBuildDocTarget = + ( "cabal-build-doc" + , "Builds the Hoogle database with cabal" ) -cabalBuildDocTarget :: VersionNumber -> (String, String) -cabalBuildDocTarget version = - ( "cabal-build-doc-" ++ version - , "Builds the Hoogle database for GHC version " - ++ version - ++ " only with cabal" +cabalBuildAllTarget :: (String, String) +cabalBuildAllTarget = + ( "cabal-build-all" + , "Builds hie for all installed GHC versions and the hoogle database with cabal" ) -- | Creates a message of the form "a, b, c and d", where a,b,c,d are GHC versions. @@ -422,6 +408,9 @@ allVersionMessage wordList = case wordList of lastVersion = last msg in concat $ (init $ init msg) ++ [" and ", lastVersion] + +-- TODO: more sophisticated interface to stack and cabal + execStackWithYaml_ :: VersionNumber -> [String] -> Action () execStackWithYaml_ versionNumber args = do let stackFile = "stack-" ++ versionNumber ++ ".yaml" @@ -441,6 +430,9 @@ execStack_ = command_ [] "stack" execCabal_ :: [String] -> Action () execCabal_ = command_ [] "cabal" +existsExecutable :: MonadIO m => String -> m Bool +existsExecutable executable = liftIO $ isJust <$> findExecutable executable + -- |Get the path to the GHC compiler executable linked to the local `stack-$GHCVER.yaml`. -- Equal to the command `stack path --stack-yaml $stack-yaml --compiler-exe`. -- This might install a GHC if it is not already installed, thus, might fail if stack fails to install the GHC. @@ -453,14 +445,12 @@ getStackGhcPath ghcVersion = do -- If no such GHC can be found, Nothing is returned. -- First, it is checked whether there is a GHC with the name `ghc-$VersionNumber`. -- If this yields no result, it is checked, whether the numeric-version of the `ghc` --- command fits to the desired version. -getGhcPath :: VersionNumber -> IO (Maybe GhcPath) -getGhcPath ghcVersion = do - pathMay <- findExecutable ("ghc-" ++ ghcVersion) - case pathMay of +-- command fits to the desired version. +getGhcPath :: MonadIO m => VersionNumber -> m (Maybe GhcPath) +getGhcPath ghcVersion = liftIO $ do + findExecutable ("ghc-" ++ ghcVersion) >>= \case Nothing -> do - noPrefixPathMay <- findExecutable "ghc" - case noPrefixPathMay of + findExecutable "ghc" >>= \case Nothing -> return Nothing Just p -> do Stdout version <- cmd p ["--numeric-version"] :: IO (Stdout String) From e0fb0a6c5394c037f2cdaaf18c60d1cc916a8a51 Mon Sep 17 00:00:00 2001 From: Samuel Pilz Date: Tue, 9 Apr 2019 12:01:08 +0200 Subject: [PATCH 02/13] include @fendor's comments --- install.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/install.hs b/install.hs index 81f35cbf0..260b798b2 100755 --- a/install.hs +++ b/install.hs @@ -156,7 +156,7 @@ validateCabalNewInstallIsSupported = when (os `elem` ["mingw32", "win32"]) $ do configureCabal :: VersionNumber -> Action () configureCabal versionNumber = do ghcPath <- getGhcPath versionNumber >>= \case - Nothing -> do -- TODO: this is better written using a monad-transformer + Nothing -> do liftIO $ putStrLn $ embedInStars (ghcVersionNotFound versionNumber) error (ghcVersionNotFound versionNumber) Just p -> return p @@ -170,7 +170,7 @@ findInstalledGhcs = mapMaybeM Nothing -> return Nothing Just p -> return $ Just (version, p) ) - hieVersions + (reverse hieVersions) cabalBuildHie :: VersionNumber -> Action () cabalBuildHie versionNumber = do @@ -345,7 +345,7 @@ emptyTarget :: (String, String) emptyTarget = ("", "") -- |Number of spaces the target name including whitespace should have. --- At least twenty, maybe more if target names are long and at least the length of the longest target plus five. +-- At least twenty, maybe more if target names are long. At most the length of the longest target plus five. space :: [(String, String)] -> Int space phonyTargets = maximum (20 : map ((+ 5) . length . fst) phonyTargets) From aa5ea40bc3862fdfc0f585b160d44107508c06aa Mon Sep 17 00:00:00 2001 From: Samuel Pilz Date: Tue, 9 Apr 2019 14:16:18 +0200 Subject: [PATCH 03/13] check version of existing cabal before using that --- install.hs | 113 +++++++++++++++++++++++++++++++---------------------- 1 file changed, 66 insertions(+), 47 deletions(-) diff --git a/install.hs b/install.hs index 260b798b2..061c31830 100755 --- a/install.hs +++ b/install.hs @@ -12,22 +12,31 @@ import Development.Shake import Development.Shake.Command import Development.Shake.FilePath import Control.Monad +import Control.Monad import Control.Monad.IO.Class -import Control.Monad.Extra (unlessM, mapMaybeM) -import Data.Maybe (isJust) -import System.Directory ( findExecutable ) -import System.Environment ( getProgName - , unsetEnv - ) -import System.Info ( os - , arch - ) - -import Data.List ( dropWhileEnd - , intersperse - , intercalate - ) -import Data.Char ( isSpace ) +import Control.Monad.Extra ( unlessM + , mapMaybeM + ) +import Data.Maybe ( isJust ) +import System.Directory ( findExecutable ) +import System.Environment ( getProgName + , unsetEnv + ) +import System.Info ( os + , arch + ) + +import Data.Maybe ( isNothing ) +import Data.List ( dropWhileEnd + , intersperse + , intercalate + ) +import Data.Char ( isSpace ) +import Data.Version ( parseVersion + , makeVersion + ) +import Data.Function ( (&) ) +import Text.ParserCombinators.ReadP ( readP_to_S ) type VersionNumber = String type GhcPath = String @@ -80,8 +89,8 @@ main = do liftIO $ putStrLn $ embedInStars msg -- stack specific targets - phony "build" (need (reverse $ map ("hie-" ++) hieVersions)) - phony "build-all" (need ["build-doc", "build"]) + phony "build" (need (reverse $ map ("hie-" ++) hieVersions)) + phony "build-all" (need ["build-doc", "build"]) phony "test" $ do need ["submodules"] need ["cabal"] @@ -90,8 +99,8 @@ main = do phony "build-copy-compiler-tool" $ forM_ hieVersions buildCopyCompilerTool phony "build-doc" $ do - need ["submodules"] - stackBuildDoc + need ["submodules"] + stackBuildDoc -- main targets for building hie with `stack` forM_ @@ -104,12 +113,12 @@ main = do ) -- cabal specific targets - phony "cabal-build" (need (map ("cabal-hie-" ++) ghcVersions)) - phony "cabal-build-all" (need ["cabal-build-doc", "cabal-build"]) + phony "cabal-build" (need (map ("cabal-hie-" ++) ghcVersions)) + phony "cabal-build-all" (need ["cabal-build-doc", "cabal-build"]) phony "cabal-build-doc" $ do - need ["submodules"] - need ["cabal"] - cabalBuildDoc + need ["submodules"] + need ["cabal"] + cabalBuildDoc phony "cabal-test" $ do need ["submodules"] @@ -149,7 +158,7 @@ updateSubmodules = do command_ [] "git" ["submodule", "update", "--init", "--recursive"] validateCabalNewInstallIsSupported :: Action () -validateCabalNewInstallIsSupported = when (os `elem` ["mingw32", "win32"]) $ do +validateCabalNewInstallIsSupported = when isWindowsSystem $ do liftIO $ putStrLn $ embedInStars cabalInstallNotSuported error cabalInstallNotSuported @@ -165,10 +174,9 @@ configureCabal versionNumber = do findInstalledGhcs :: IO [(VersionNumber, GhcPath)] findInstalledGhcs = mapMaybeM - (\version -> do - getGhcPath version >>= \case - Nothing -> return Nothing - Just p -> return $ Just (version, p) + (\version -> getGhcPath version >>= \case + Nothing -> return Nothing + Just p -> return $ Just (version, p) ) (reverse hieVersions) @@ -204,8 +212,22 @@ cabalTest versionNumber = do installCabal :: Action () installCabal = do + -- try to find existing `cabal` executable with appropriate version + cabalExe <- liftIO (findExecutable "cabal") >>= \case + Nothing -> return Nothing + Just cabalExe -> do + Stdout cabalVersion <- execCabal ["--numeric-version"] + let (parsedVersion, "") : _ = + cabalVersion & trim & readP_to_S parseVersion & filter + (("" ==) . snd) + + return $ if parsedVersion >= makeVersion [2, 4, 1, 0] + then Just cabalExe + else Nothing + + -- install `cabal-install` if not already installed - unlessM (existsExecutable "cabal") $ do + when (isNothing cabalExe) $ execStack_ ["install", "--stack-yaml=shake.yaml", "cabal-install"] execCabal_ ["update"] ghc <- getStackGhcPath mostRecentHieVersion @@ -298,14 +320,9 @@ helpMessage = do spaces = space targets -- All targets the shake file supports targets :: [(String, String)] - targets = - intercalate - [emptyTarget] - [ generalTargets - , stackTargets - , cabalTargets - , macosTargets - ] + targets = intercalate + [emptyTarget] + [generalTargets, stackTargets, cabalTargets, macosTargets] -- All targets with their respective help message. generalTargets = @@ -327,7 +344,7 @@ helpMessage = do , stackBuildDocTarget , ("test", "Runs hie tests with stack") ] - ++ map stackHieTarget hieVersions + ++ map stackHieTarget hieVersions cabalTargets = [ ( "cabal-ghcs" @@ -338,7 +355,7 @@ helpMessage = do , cabalBuildDocTarget , ("cabal-test", "Runs hie tests with cabal") ] - ++ map cabalHieTarget hieVersions + ++ map cabalHieTarget hieVersions -- | Empty target. Purpose is to introduce a newline between the targets emptyTarget :: (String, String) @@ -370,10 +387,7 @@ cabalHieTarget version = ) stackBuildDocTarget :: (String, String) -stackBuildDocTarget = - ( "build-doc" - , "Builds the Hoogle database" - ) +stackBuildDocTarget = ("build-doc", "Builds the Hoogle database") stackBuildAllTarget :: (String, String) stackBuildAllTarget = @@ -387,9 +401,7 @@ cabalBuildTarget = cabalBuildDocTarget :: (String, String) cabalBuildDocTarget = - ( "cabal-build-doc" - , "Builds the Hoogle database with cabal" - ) + ("cabal-build-doc", "Builds the Hoogle database with cabal") cabalBuildAllTarget :: (String, String) cabalBuildAllTarget = @@ -427,12 +439,19 @@ execStack = command [] "stack" execStack_ :: [String] -> Action () execStack_ = command_ [] "stack" +execCabal :: CmdResult r => [String] -> Action r +execCabal = command [] "cabal" + execCabal_ :: [String] -> Action () execCabal_ = command_ [] "cabal" existsExecutable :: MonadIO m => String -> m Bool existsExecutable executable = liftIO $ isJust <$> findExecutable executable +-- |Check if the current system is windows +isWindowsSystem :: Bool +isWindowsSystem = os `elem` ["mingw32", "win32"] + -- |Get the path to the GHC compiler executable linked to the local `stack-$GHCVER.yaml`. -- Equal to the command `stack path --stack-yaml $stack-yaml --compiler-exe`. -- This might install a GHC if it is not already installed, thus, might fail if stack fails to install the GHC. From 36b0f998f56088c88f5ca9f8b47191cf5423fb6c Mon Sep 17 00:00:00 2001 From: Samuel Pilz Date: Sat, 13 Apr 2019 15:47:48 +0200 Subject: [PATCH 04/13] implement check for `stack` version --- install.hs | 36 ++++++++++++++++++++++++++++-------- 1 file changed, 28 insertions(+), 8 deletions(-) diff --git a/install.hs b/install.hs index 061c31830..c8c46e481 100755 --- a/install.hs +++ b/install.hs @@ -72,11 +72,12 @@ main = do shakeArgs shakeOptions { shakeFiles = "_build" } $ do want ["short-help"] -- general purpose targets - phony "submodules" updateSubmodules - phony "cabal" installCabal - phony "short-help" shortHelpMessage - phony "all" shortHelpMessage - phony "help" helpMessage + phony "submodules" updateSubmodules + phony "cabal" installCabal + phony "short-help" shortHelpMessage + phony "all" shortHelpMessage + phony "help" helpMessage + phony "check-stack" checkStack phony "cabal-ghcs" $ do let @@ -93,6 +94,7 @@ main = do phony "build-all" (need ["build-doc", "build"]) phony "test" $ do need ["submodules"] + need ["check-stack"] need ["cabal"] forM_ hieVersions stackTest @@ -100,6 +102,7 @@ main = do phony "build-doc" $ do need ["submodules"] + need ["check-stack"] stackBuildDoc -- main targets for building hie with `stack` @@ -107,6 +110,7 @@ main = do hieVersions (\version -> phony ("hie-" ++ version) $ do need ["submodules"] + need ["check-stack"] need ["cabal"] stackBuildHie version stackInstallHie version @@ -224,8 +228,6 @@ installCabal = do return $ if parsedVersion >= makeVersion [2, 4, 1, 0] then Just cabalExe else Nothing - - -- install `cabal-install` if not already installed when (isNothing cabalExe) $ execStack_ ["install", "--stack-yaml=shake.yaml", "cabal-install"] @@ -233,8 +235,20 @@ installCabal = do ghc <- getStackGhcPath mostRecentHieVersion execCabal_ ["install", "Cabal-2.4.1.0", "--with-compiler=" ++ ghc] + +checkStack :: Action () +checkStack = do + Stdout stackVersion <- execStack ["--numeric-version"] + let (parsedVersion, "") : _ = + stackVersion & trim & readP_to_S parseVersion & filter + (("" ==) . snd) + unless (parsedVersion >= makeVersion [1, 9, 3]) $ do + liftIO $ putStrLn $ embedInStars stackExeIsOld + error stackExeIsOld + + stackBuildHie :: VersionNumber -> Action () -stackBuildHie versionNumber = do +stackBuildHie versionNumber = execStackWithYaml_ versionNumber ["build"] `actionOnException` liftIO (putStrLn stackBuildFailMsg) @@ -529,3 +543,9 @@ cabalInstallNotSuported = ++ "Unfortunately, `cabal new-install` is currently not supported on windows.\n" ++ "Please use one of the stack-based targets.\n\n" ++ "If this system has been falsely identified, please open an issue at:\n\thttps://github.com/haskell/haskell-ide-engine\n" + +-- | Error message when a windows system tries to install HIE via `cabal new-install` +stackExeIsOld :: String +stackExeIsOld = + "You The `stack` executable is outdated.\n" + ++ "Please run `stack upgrade` to upgrade you stack installation" From 0d2e6fac25e2623fab2f5eb8faa962f938dd5330 Mon Sep 17 00:00:00 2001 From: Samuel Pilz Date: Sat, 13 Apr 2019 16:08:04 +0200 Subject: [PATCH 05/13] use the compiler from shake to install Cabal --- install.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/install.hs b/install.hs index c8c46e481..18ec2a0e0 100755 --- a/install.hs +++ b/install.hs @@ -232,7 +232,7 @@ installCabal = do when (isNothing cabalExe) $ execStack_ ["install", "--stack-yaml=shake.yaml", "cabal-install"] execCabal_ ["update"] - ghc <- getStackGhcPath mostRecentHieVersion + ghc <- getStackGhcPathShake execCabal_ ["install", "Cabal-2.4.1.0", "--with-compiler=" ++ ghc] @@ -474,6 +474,11 @@ getStackGhcPath ghcVersion = do Stdout ghc <- execStackWithYaml ghcVersion ["path", "--compiler-exe"] return $ trim ghc +getStackGhcPathShake :: Action GhcPath +getStackGhcPathShake = do + Stdout ghc <- execStack ["--stack-yaml=shake.yaml", "path", "--compiler-exe"] + return $ trim ghc + -- |Get the path to a GHC that has the version specified by `VersionNumber` -- If no such GHC can be found, Nothing is returned. -- First, it is checked whether there is a GHC with the name `ghc-$VersionNumber`. From cadcfe50e729335a5cc0cff80408ff9b53e3463d Mon Sep 17 00:00:00 2001 From: Samuel Pilz Date: Sat, 13 Apr 2019 17:32:53 +0200 Subject: [PATCH 06/13] change helper functions to always use shake-yaml or specific ghc-based yaml --- install.hs | 92 ++++++++++++++++++++++++++++++------------------------ 1 file changed, 51 insertions(+), 41 deletions(-) diff --git a/install.hs b/install.hs index 18ec2a0e0..7c71ecba3 100755 --- a/install.hs +++ b/install.hs @@ -1,7 +1,7 @@ #!/usr/bin/env stack {- stack - script - --resolver nightly-2018-12-15 + runghc + --stack-yaml=shake.yaml --package shake --package directory --package extra @@ -147,7 +147,7 @@ main = do buildIcuMacosFix :: VersionNumber -> Action () -buildIcuMacosFix version = execStackWithYaml_ +buildIcuMacosFix version = execStackWithGhc_ version [ "build" , "text-icu" @@ -163,15 +163,15 @@ updateSubmodules = do validateCabalNewInstallIsSupported :: Action () validateCabalNewInstallIsSupported = when isWindowsSystem $ do - liftIO $ putStrLn $ embedInStars cabalInstallNotSuported - error cabalInstallNotSuported + liftIO $ putStrLn $ embedInStars cabalInstallNotSuportedFailMsg + error cabalInstallNotSuportedFailMsg configureCabal :: VersionNumber -> Action () configureCabal versionNumber = do ghcPath <- getGhcPath versionNumber >>= \case Nothing -> do - liftIO $ putStrLn $ embedInStars (ghcVersionNotFound versionNumber) - error (ghcVersionNotFound versionNumber) + liftIO $ putStrLn $ embedInStars (ghcVersionNotFoundFailMsg versionNumber) + error (ghcVersionNotFoundFailMsg versionNumber) Just p -> return p execCabal_ ["new-configure", "-w", ghcPath, "--write-ghc-environment-files=never"] @@ -230,7 +230,7 @@ installCabal = do else Nothing -- install `cabal-install` if not already installed when (isNothing cabalExe) $ - execStack_ ["install", "--stack-yaml=shake.yaml", "cabal-install"] + execStackShake_ ["install", "cabal-install"] execCabal_ ["update"] ghc <- getStackGhcPathShake execCabal_ ["install", "Cabal-2.4.1.0", "--with-compiler=" ++ ghc] @@ -238,24 +238,24 @@ installCabal = do checkStack :: Action () checkStack = do - Stdout stackVersion <- execStack ["--numeric-version"] + Stdout stackVersion <- execStackShake ["--numeric-version"] let (parsedVersion, "") : _ = stackVersion & trim & readP_to_S parseVersion & filter (("" ==) . snd) unless (parsedVersion >= makeVersion [1, 9, 3]) $ do - liftIO $ putStrLn $ embedInStars stackExeIsOld - error stackExeIsOld + liftIO $ putStrLn $ embedInStars stackExeIsOldFailMsg + error stackExeIsOldFailMsg stackBuildHie :: VersionNumber -> Action () stackBuildHie versionNumber = - execStackWithYaml_ versionNumber ["build"] + execStackWithGhc_ versionNumber ["build"] `actionOnException` liftIO (putStrLn stackBuildFailMsg) -- | copy the built binaries into the localBinDir stackInstallHie :: VersionNumber -> Action () stackInstallHie versionNumber = do - execStackWithYaml_ versionNumber ["install"] + execStackWithGhc_ versionNumber ["install"] localBinDir <- getLocalBin localInstallRoot <- getLocalInstallRoot versionNumber let hie = "hie" <.> exe @@ -266,15 +266,15 @@ stackInstallHie versionNumber = do buildCopyCompilerTool :: VersionNumber -> Action () buildCopyCompilerTool versionNumber = - execStackWithYaml_ versionNumber ["build", "--copy-compiler-tool"] + execStackWithGhc_ versionNumber ["build", "--copy-compiler-tool"] stackTest :: VersionNumber -> Action () -stackTest versionNumber = execStackWithYaml_ versionNumber ["test"] +stackTest versionNumber = execStackWithGhc_ versionNumber ["test"] stackBuildDoc :: Action () stackBuildDoc = do - execStack_ ["--stack-yaml=shake.yaml", "build", "hoogle"] - execStack_ ["--stack-yaml=shake.yaml", "exec", "hoogle", "generate"] + execStackShake_ ["build", "hoogle"] + execStackShake_ ["exec", "hoogle", "generate"] -- | short help message is printed by default shortHelpMessage :: Action () @@ -435,26 +435,33 @@ allVersionMessage wordList = case wordList of in concat $ (init $ init msg) ++ [" and ", lastVersion] --- TODO: more sophisticated interface to stack and cabal +-- RUN EXECUTABLES -execStackWithYaml_ :: VersionNumber -> [String] -> Action () -execStackWithYaml_ versionNumber args = do +-- |Execute a stack command for a specified ghc, discarding the output +execStackWithGhc_ :: VersionNumber -> [String] -> Action () +execStackWithGhc_ versionNumber args = do let stackFile = "stack-" ++ versionNumber ++ ".yaml" command_ [] "stack" (("--stack-yaml=" ++ stackFile) : args) -execStackWithYaml :: CmdResult r => VersionNumber -> [String] -> Action r -execStackWithYaml versionNumber args = do +-- |Execute a stack command for a specified ghc +execStackWithGhc :: CmdResult r => VersionNumber -> [String] -> Action r +execStackWithGhc versionNumber args = do let stackFile = "stack-" ++ versionNumber ++ ".yaml" command [] "stack" (("--stack-yaml=" ++ stackFile) : args) -execStack :: CmdResult r => [String] -> Action r -execStack = command [] "stack" +-- |Execute a stack command with the same resolver as the build script +execStackShake :: CmdResult r => [String] -> Action r +execStackShake args = + command [] "stack" ("--stack-yaml=shake.yaml" : args) -execStack_ :: [String] -> Action () -execStack_ = command_ [] "stack" +-- |Execute a stack command with the same resolver as the build script, discarding the output +execStackShake_ :: [String] -> Action () +execStackShake_ args = + command_ [] "stack" ("--stack-yaml=shake.yaml" : args) execCabal :: CmdResult r => [String] -> Action r -execCabal = command [] "cabal" +execCabal = + command [] "cabal" execCabal_ :: [String] -> Action () execCabal_ = command_ [] "cabal" @@ -462,6 +469,9 @@ execCabal_ = command_ [] "cabal" existsExecutable :: MonadIO m => String -> m Bool existsExecutable executable = liftIO $ isJust <$> findExecutable executable + +-- QUERY ENVIRONMENT + -- |Check if the current system is windows isWindowsSystem :: Bool isWindowsSystem = os `elem` ["mingw32", "win32"] @@ -471,12 +481,12 @@ isWindowsSystem = os `elem` ["mingw32", "win32"] -- This might install a GHC if it is not already installed, thus, might fail if stack fails to install the GHC. getStackGhcPath :: VersionNumber -> Action GhcPath getStackGhcPath ghcVersion = do - Stdout ghc <- execStackWithYaml ghcVersion ["path", "--compiler-exe"] + Stdout ghc <- execStackWithGhc ghcVersion ["path", "--compiler-exe"] return $ trim ghc getStackGhcPathShake :: Action GhcPath getStackGhcPathShake = do - Stdout ghc <- execStack ["--stack-yaml=shake.yaml", "path", "--compiler-exe"] + Stdout ghc <- execStackShake ["path", "--compiler-exe"] return $ trim ghc -- |Get the path to a GHC that has the version specified by `VersionNumber` @@ -485,7 +495,7 @@ getStackGhcPathShake = do -- If this yields no result, it is checked, whether the numeric-version of the `ghc` -- command fits to the desired version. getGhcPath :: MonadIO m => VersionNumber -> m (Maybe GhcPath) -getGhcPath ghcVersion = liftIO $ do +getGhcPath ghcVersion = liftIO $ findExecutable ("ghc-" ++ ghcVersion) >>= \case Nothing -> do findExecutable "ghc" >>= \case @@ -500,7 +510,7 @@ getGhcPath ghcVersion = liftIO $ do -- Equal to the command `stack path --local-install-root` getLocalInstallRoot :: VersionNumber -> Action FilePath getLocalInstallRoot hieVersion = do - Stdout localInstallRoot' <- execStackWithYaml + Stdout localInstallRoot' <- execStackWithGhc hieVersion ["path", "--local-install-root"] return $ trim localInstallRoot' @@ -509,8 +519,8 @@ getLocalInstallRoot hieVersion = do -- Equal to the command `stack path --local-bin` getLocalBin :: Action FilePath getLocalBin = do - Stdout stackLocalDir' <- execStack - ["path", "--stack-yaml=shake.yaml", "--local-bin"] + Stdout stackLocalDir' <- execStackShake + ["path", "--local-bin"] return $ trim stackLocalDir' -- |Trim the end of a string @@ -534,23 +544,23 @@ stackBuildFailMsg = ++ "\thttps://github.com/haskell/haskell-ide-engine" -- |No suitable ghc version has been found. Show a message. -ghcVersionNotFound :: VersionNumber -> String -ghcVersionNotFound versionNumber = +ghcVersionNotFoundFailMsg :: VersionNumber -> String +ghcVersionNotFoundFailMsg versionNumber = "No GHC with version " <> versionNumber <> " has been found.\n" <> "Either install a fitting GHC, use the stack targets or modify the PATH variable accordingly." -- | Error message when a windows system tries to install HIE via `cabal new-install` -cabalInstallNotSuported :: String -cabalInstallNotSuported = +cabalInstallNotSuportedFailMsg :: String +cabalInstallNotSuportedFailMsg = "This system has been identified as a windows system.\n" ++ "Unfortunately, `cabal new-install` is currently not supported on windows.\n" ++ "Please use one of the stack-based targets.\n\n" ++ "If this system has been falsely identified, please open an issue at:\n\thttps://github.com/haskell/haskell-ide-engine\n" -- | Error message when a windows system tries to install HIE via `cabal new-install` -stackExeIsOld :: String -stackExeIsOld = - "You The `stack` executable is outdated.\n" - ++ "Please run `stack upgrade` to upgrade you stack installation" +stackExeIsOldFailMsg :: String +stackExeIsOldFailMsg = + "The `stack` executable is outdated.\n" + ++ "Please run `stack upgrade` to upgrade your stack installation" From 7a974297cea02f4ae8734a25bfd57e4b7e33b369 Mon Sep 17 00:00:00 2001 From: Samuel Pilz Date: Sat, 13 Apr 2019 17:42:12 +0200 Subject: [PATCH 07/13] document that cabal new-build will work on windows in next release --- install.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/install.hs b/install.hs index 7c71ecba3..082834b1b 100755 --- a/install.hs +++ b/install.hs @@ -161,6 +161,7 @@ updateSubmodules = do command_ [] "git" ["submodule", "sync", "--recursive"] command_ [] "git" ["submodule", "update", "--init", "--recursive"] +-- TODO: this restriction will be gone in the next release of cabal validateCabalNewInstallIsSupported :: Action () validateCabalNewInstallIsSupported = when isWindowsSystem $ do liftIO $ putStrLn $ embedInStars cabalInstallNotSuportedFailMsg From a7bb6e987a22f04a921b17e6da7bb143b35b2463 Mon Sep 17 00:00:00 2001 From: Samuel Pilz Date: Tue, 16 Apr 2019 12:51:11 +0200 Subject: [PATCH 08/13] fix documentation comments --- install.hs | 38 +++++++++++++++++++------------------- 1 file changed, 19 insertions(+), 19 deletions(-) diff --git a/install.hs b/install.hs index 082834b1b..34f708089 100755 --- a/install.hs +++ b/install.hs @@ -41,7 +41,7 @@ import Text.ParserCombinators.ReadP ( readP_to_S ) type VersionNumber = String type GhcPath = String --- |Defines all different hie versions that are buildable. +-- | Defines all different hie versions that are buildable. -- If they are edited, make sure to maintain the order of the versions. hieVersions :: [VersionNumber] hieVersions = @@ -56,7 +56,7 @@ hieVersions = , "8.6.4" ] --- |Most recent version of hie. +-- | Most recent version of hie. -- Shown in the more concise help message. mostRecentHieVersion :: VersionNumber mostRecentHieVersion = last hieVersions @@ -155,7 +155,7 @@ buildIcuMacosFix version = execStackWithGhc_ , "--extra-include-dirs=/usr/local/opt/icu4c/include" ] --- |update the submodules that the project is in the state as required by the `stack.yaml` files +-- | update the submodules that the project is in the state as required by the `stack.yaml` files updateSubmodules :: Action () updateSubmodules = do command_ [] "git" ["submodule", "sync", "--recursive"] @@ -376,25 +376,25 @@ helpMessage = do emptyTarget :: (String, String) emptyTarget = ("", "") --- |Number of spaces the target name including whitespace should have. +-- | Number of spaces the target name including whitespace should have. -- At least twenty, maybe more if target names are long. At most the length of the longest target plus five. space :: [(String, String)] -> Int space phonyTargets = maximum (20 : map ((+ 5) . length . fst) phonyTargets) --- |Show a target. +-- | Show a target. -- Concatenates the target with its help message and inserts whitespace between them. showTarget :: Int -> (String, String) -> String showTarget spaces (target, msg) = target ++ replicate (spaces - length target) ' ' ++ msg --- |Target for a specific ghc version +-- | Target for a specific ghc version stackHieTarget :: String -> (String, String) stackHieTarget version = ( "hie-" ++ version , "Builds hie for GHC version " ++ version ++ " only with stack" ) --- |Target for a specific ghc version +-- | Target for a specific ghc version cabalHieTarget :: String -> (String, String) cabalHieTarget version = ( "cabal-hie-" ++ version @@ -438,24 +438,24 @@ allVersionMessage wordList = case wordList of -- RUN EXECUTABLES --- |Execute a stack command for a specified ghc, discarding the output +-- | Execute a stack command for a specified ghc, discarding the output execStackWithGhc_ :: VersionNumber -> [String] -> Action () execStackWithGhc_ versionNumber args = do let stackFile = "stack-" ++ versionNumber ++ ".yaml" command_ [] "stack" (("--stack-yaml=" ++ stackFile) : args) --- |Execute a stack command for a specified ghc +-- | Execute a stack command for a specified ghc execStackWithGhc :: CmdResult r => VersionNumber -> [String] -> Action r execStackWithGhc versionNumber args = do let stackFile = "stack-" ++ versionNumber ++ ".yaml" command [] "stack" (("--stack-yaml=" ++ stackFile) : args) --- |Execute a stack command with the same resolver as the build script +-- | Execute a stack command with the same resolver as the build script execStackShake :: CmdResult r => [String] -> Action r execStackShake args = command [] "stack" ("--stack-yaml=shake.yaml" : args) --- |Execute a stack command with the same resolver as the build script, discarding the output +-- | Execute a stack command with the same resolver as the build script, discarding the output execStackShake_ :: [String] -> Action () execStackShake_ args = command_ [] "stack" ("--stack-yaml=shake.yaml" : args) @@ -477,7 +477,7 @@ existsExecutable executable = liftIO $ isJust <$> findExecutable executable isWindowsSystem :: Bool isWindowsSystem = os `elem` ["mingw32", "win32"] --- |Get the path to the GHC compiler executable linked to the local `stack-$GHCVER.yaml`. +-- | Get the path to the GHC compiler executable linked to the local `stack-$GHCVER.yaml`. -- Equal to the command `stack path --stack-yaml $stack-yaml --compiler-exe`. -- This might install a GHC if it is not already installed, thus, might fail if stack fails to install the GHC. getStackGhcPath :: VersionNumber -> Action GhcPath @@ -490,7 +490,7 @@ getStackGhcPathShake = do Stdout ghc <- execStackShake ["path", "--compiler-exe"] return $ trim ghc --- |Get the path to a GHC that has the version specified by `VersionNumber` +-- | Get the path to a GHC that has the version specified by `VersionNumber` -- If no such GHC can be found, Nothing is returned. -- First, it is checked whether there is a GHC with the name `ghc-$VersionNumber`. -- If this yields no result, it is checked, whether the numeric-version of the `ghc` @@ -506,7 +506,7 @@ getGhcPath ghcVersion = liftIO $ if ghcVersion == trim version then return $ Just p else return Nothing p -> return p --- |Read the local install root of the stack project specified by the VersionNumber +-- | Read the local install root of the stack project specified by the VersionNumber -- Returns the filepath of the local install root. -- Equal to the command `stack path --local-install-root` getLocalInstallRoot :: VersionNumber -> Action FilePath @@ -516,7 +516,7 @@ getLocalInstallRoot hieVersion = do ["path", "--local-install-root"] return $ trim localInstallRoot' --- |Get the local binary path of stack. +-- | Get the local binary path of stack. -- Equal to the command `stack path --local-bin` getLocalBin :: Action FilePath getLocalBin = do @@ -524,11 +524,11 @@ getLocalBin = do ["path", "--local-bin"] return $ trim stackLocalDir' --- |Trim the end of a string +-- | Trim the end of a string trim :: String -> String trim = dropWhileEnd isSpace --- |Embed a string within two lines of stars to improve perceivability and, thus, readability. +-- | Embed a string within two lines of stars to improve perceivability and, thus, readability. embedInStars :: String -> String embedInStars str = let starsLine @@ -544,7 +544,7 @@ stackBuildFailMsg = ++ "If this does not work, open an issue at \n" ++ "\thttps://github.com/haskell/haskell-ide-engine" --- |No suitable ghc version has been found. Show a message. +-- | No suitable ghc version has been found. Show a message. ghcVersionNotFoundFailMsg :: VersionNumber -> String ghcVersionNotFoundFailMsg versionNumber = "No GHC with version " @@ -560,7 +560,7 @@ cabalInstallNotSuportedFailMsg = ++ "Please use one of the stack-based targets.\n\n" ++ "If this system has been falsely identified, please open an issue at:\n\thttps://github.com/haskell/haskell-ide-engine\n" --- | Error message when a windows system tries to install HIE via `cabal new-install` +-- | Error message when the `stack` binary is an older version stackExeIsOldFailMsg :: String stackExeIsOldFailMsg = "The `stack` executable is outdated.\n" From 1fffd94b333606ed757a271fe9c77370c3ab4cb8 Mon Sep 17 00:00:00 2001 From: Samuel Pilz Date: Tue, 16 Apr 2019 12:57:01 +0200 Subject: [PATCH 09/13] add current stack version to error about too old stack version --- install.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/install.hs b/install.hs index 34f708089..f96c14e7b 100755 --- a/install.hs +++ b/install.hs @@ -244,8 +244,8 @@ checkStack = do stackVersion & trim & readP_to_S parseVersion & filter (("" ==) . snd) unless (parsedVersion >= makeVersion [1, 9, 3]) $ do - liftIO $ putStrLn $ embedInStars stackExeIsOldFailMsg - error stackExeIsOldFailMsg + liftIO $ putStrLn $ embedInStars $ stackExeIsOldFailMsg stackVersion + error $ stackExeIsOldFailMsg stackVersion stackBuildHie :: VersionNumber -> Action () @@ -561,7 +561,8 @@ cabalInstallNotSuportedFailMsg = ++ "If this system has been falsely identified, please open an issue at:\n\thttps://github.com/haskell/haskell-ide-engine\n" -- | Error message when the `stack` binary is an older version -stackExeIsOldFailMsg :: String -stackExeIsOldFailMsg = +stackExeIsOldFailMsg :: String -> String +stackExeIsOldFailMsg stackVersion = "The `stack` executable is outdated.\n" + ++ "found version is `" ++ stackVersion ++ "`.\n" ++ "Please run `stack upgrade` to upgrade your stack installation" From 5b0d0de7348907a9382c1f3f1c820de8858925f7 Mon Sep 17 00:00:00 2001 From: Samuel Pilz Date: Tue, 16 Apr 2019 17:47:30 +0200 Subject: [PATCH 10/13] add required stack version to error message --- install.hs | 11 ++++++++--- 1 file changed, 8 insertions(+), 3 deletions(-) diff --git a/install.hs b/install.hs index f96c14e7b..c614d009a 100755 --- a/install.hs +++ b/install.hs @@ -34,6 +34,7 @@ import Data.List ( dropWhileEnd import Data.Char ( isSpace ) import Data.Version ( parseVersion , makeVersion + , showVersion ) import Data.Function ( (&) ) import Text.ParserCombinators.ReadP ( readP_to_S ) @@ -243,9 +244,9 @@ checkStack = do let (parsedVersion, "") : _ = stackVersion & trim & readP_to_S parseVersion & filter (("" ==) . snd) - unless (parsedVersion >= makeVersion [1, 9, 3]) $ do - liftIO $ putStrLn $ embedInStars $ stackExeIsOldFailMsg stackVersion - error $ stackExeIsOldFailMsg stackVersion + unless (parsedVersion >= makeVersion requiredStackVersion) $ do + liftIO $ putStrLn $ embedInStars $ stackExeIsOldFailMsg $ trim stackVersion + error $ stackExeIsOldFailMsg $ trim stackVersion stackBuildHie :: VersionNumber -> Action () @@ -565,4 +566,8 @@ stackExeIsOldFailMsg :: String -> String stackExeIsOldFailMsg stackVersion = "The `stack` executable is outdated.\n" ++ "found version is `" ++ stackVersion ++ "`.\n" + ++ "required version is `" ++ showVersion (makeVersion requiredStackVersion) ++ "`.\n" ++ "Please run `stack upgrade` to upgrade your stack installation" + +requiredStackVersion :: [Int] +requiredStackVersion = [1, 9, 3] From c28a4bec1909a1f8851020039394bb420a25cfe9 Mon Sep 17 00:00:00 2001 From: Samuel Pilz Date: Thu, 18 Apr 2019 00:38:44 +0200 Subject: [PATCH 11/13] correct the readme to match the new docs targets in install.hs --- README.md | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/README.md b/README.md index f53458261..ebb74018b 100644 --- a/README.md +++ b/README.md @@ -153,7 +153,7 @@ then it means you have the command in PATH. On Linux you will need install a couple of extra libraries (for Unicode ([ICU](http://site.icu-project.org/)) and [NCURSES](https://www.gnu.org/software/ncurses/)): -**Debian/Ubuntu**: +**Debian/Ubuntu**: ```bash sudo apt install libicu-dev libtinfo-dev libgmp-dev @@ -194,7 +194,7 @@ Available commands can be seen with: stack ./install.hs help ``` -Remember, this will take time to download a Stackage-LTS and an appropriate GHC. However, afterwards all commands should work as expected. +Remember, this will take time to download a Stackage-LTS and an appropriate GHC. However, afterwards all commands should work as expected. ##### Install specific GHC Version @@ -202,14 +202,14 @@ Install **Nightly** (and hoogle docs): ```bash stack ./install.hs hie-8.6.4 -stack ./install.hs build-doc-8.6.4 +stack ./install.hs build-docs ``` Install **LTS** (and hoogle docs): ```bash stack ./install.hs hie-8.4.4 -stack ./install.hs build-doc-8.4.4 +stack ./install.hs build-docs ``` The Haskell IDE Engine can also be built with `cabal new-build` instead of `stack build`. @@ -237,7 +237,7 @@ If your desired ghc has been found, you use it to install Haskell IDE Engine. ```bash stack install.hs cabal-hie-8.4.4 -stack install.hs cabal-build-doc-8.4.4 +stack install.hs cabal-build-docs ``` To install HIE for all GHC versions that are present on your system, use: @@ -589,11 +589,11 @@ These builds have a dependency on [homebrew](https://brew.sh)'s `gmp` library. I ### cannot satisfy -package-id \ -#### Is \ base-x? +#### Is \ base-x? Make sure that you are running the correct version of hie for your version of ghc, or check out hie-wrapper. #### Is there a hash (#) after \? Delete any `.ghc.environment*` files in your project root and try again. (At the time of writing, cabal new-style projects are not supported with ghc-mod) #### Otherwise -Try running `cabal update`. +Try running `cabal update`. From e03b5e5ae4a0cbe95f91b157df359eade24427f2 Mon Sep 17 00:00:00 2001 From: Samuel Pilz Date: Thu, 18 Apr 2019 14:21:24 +0200 Subject: [PATCH 12/13] dynamically load hie-versions and exclude `8.6.3` for windows --- install.hs | 89 +++++++++++++++++++++++++++++++++--------------------- 1 file changed, 54 insertions(+), 35 deletions(-) diff --git a/install.hs b/install.hs index c614d009a..ede8c65a5 100755 --- a/install.hs +++ b/install.hs @@ -18,7 +18,9 @@ import Control.Monad.Extra ( unlessM , mapMaybeM ) import Data.Maybe ( isJust ) -import System.Directory ( findExecutable ) +import System.Directory ( findExecutable + , listDirectory + ) import System.Environment ( getProgName , unsetEnv ) @@ -26,11 +28,14 @@ import System.Info ( os , arch ) -import Data.Maybe ( isNothing ) +import Data.Maybe ( isNothing + , mapMaybe + ) import Data.List ( dropWhileEnd , intersperse , intercalate ) +import qualified Data.Text as T import Data.Char ( isSpace ) import Data.Version ( parseVersion , makeVersion @@ -43,24 +48,27 @@ type VersionNumber = String type GhcPath = String -- | Defines all different hie versions that are buildable. --- If they are edited, make sure to maintain the order of the versions. -hieVersions :: [VersionNumber] -hieVersions = - [ "8.2.1" - , "8.2.2" - , "8.4.2" - , "8.4.3" - , "8.4.4" - , "8.6.1" - , "8.6.2" - , "8.6.3" - , "8.6.4" - ] +-- +-- The current directory is scanned for `stack-*.yaml` files. +-- On windows, `8.6.3` is excluded as this version of ghc does not work there +getHieVersions :: MonadIO m => m [VersionNumber] +getHieVersions = do + let stackYamlPrefix = T.pack "stack-" + let stackYamlSuffix = T.pack ".yaml" + files <- liftIO $ listDirectory "." + let hieVersions = files + & map T.pack + & mapMaybe + (T.stripPrefix stackYamlPrefix >=> T.stripSuffix stackYamlSuffix) + & map T.unpack + -- the following line excludes `8.6.3` on windows systems + & filter (\p -> not isWindowsSystem || p /= "8.6.3") + return hieVersions -- | Most recent version of hie. -- Shown in the more concise help message. -mostRecentHieVersion :: VersionNumber -mostRecentHieVersion = last hieVersions +mostRecentHieVersion :: MonadIO m => m VersionNumber +mostRecentHieVersion = last <$> getHieVersions main :: IO () main = do @@ -70,6 +78,8 @@ main = do ghcPaths <- findInstalledGhcs let ghcVersions = map fst ghcPaths + hieVersions <- getHieVersions + shakeArgs shakeOptions { shakeFiles = "_build" } $ do want ["short-help"] -- general purpose targets @@ -179,12 +189,14 @@ configureCabal versionNumber = do ["new-configure", "-w", ghcPath, "--write-ghc-environment-files=never"] findInstalledGhcs :: IO [(VersionNumber, GhcPath)] -findInstalledGhcs = mapMaybeM - (\version -> getGhcPath version >>= \case - Nothing -> return Nothing - Just p -> return $ Just (version, p) - ) - (reverse hieVersions) +findInstalledGhcs = do + hieVersions <- getHieVersions :: IO [VersionNumber] + mapMaybeM + (\version -> getGhcPath version >>= \case + Nothing -> return Nothing + Just p -> return $ Just (version, p) + ) + (reverse hieVersions) cabalBuildHie :: VersionNumber -> Action () cabalBuildHie versionNumber = do @@ -281,6 +293,7 @@ stackBuildDoc = do -- | short help message is printed by default shortHelpMessage :: Action () shortHelpMessage = do + hieVersions <- getHieVersions let out = liftIO . putStrLn scriptName <- liftIO getProgName out "" @@ -288,14 +301,14 @@ shortHelpMessage = do out' ("stack " <> scriptName <> " ") out "" out "Targets:" - mapM_ (out' . showTarget spaces) targets + mapM_ (out' . showTarget (spaces hieVersions)) (targets hieVersions) out "" where out = liftIO . putStrLn out' = out . (" " ++) - spaces = space targets - targets = + spaces hieVersions = space (targets hieVersions) + targets hieVersions = [ ("help", "Show help message including all targets") , emptyTarget , ( "build" @@ -304,7 +317,7 @@ shortHelpMessage = do ++ ")" ) , stackBuildAllTarget - , stackHieTarget mostRecentHieVersion + -- , stackHieTarget mostRecentHieVersion , stackBuildDocTarget , stackHieTarget "8.4.4" , emptyTarget @@ -313,7 +326,7 @@ shortHelpMessage = do ) , cabalBuildTarget , cabalBuildAllTarget - , cabalHieTarget mostRecentHieVersion + -- , cabalHieTarget mostRecentHieVersion , cabalBuildDocTarget , cabalHieTarget "8.4.4" ] @@ -321,24 +334,30 @@ shortHelpMessage = do helpMessage :: Action () helpMessage = do + + hieVersions <- getHieVersions scriptName <- liftIO getProgName out "" out "Usage:" out' ("stack " <> scriptName <> " ") out "" out "Targets:" - mapM_ (out' . showTarget spaces) targets + mapM_ (out' . showTarget (spaces hieVersions)) (targets hieVersions) out "" where out = liftIO . putStrLn out' = out . (" " ++) - spaces = space targets + spaces hieVersions = space (targets hieVersions) -- All targets the shake file supports - targets :: [(String, String)] - targets = intercalate + targets :: [VersionNumber] -> [(String, String)] + targets hieVersions = intercalate [emptyTarget] - [generalTargets, stackTargets, cabalTargets, macosTargets] + [ generalTargets + , stackTargets hieVersions + , cabalTargets hieVersions + , macosTargets + ] -- All targets with their respective help message. generalTargets = @@ -350,7 +369,7 @@ helpMessage = do macosTargets = [("icu-macos-fix", "Fixes icu related problems in MacOS")] - stackTargets = + stackTargets hieVersions = [ ( "build" , "Builds hie for all supported GHC versions (" ++ allVersionMessage hieVersions @@ -362,7 +381,7 @@ helpMessage = do ] ++ map stackHieTarget hieVersions - cabalTargets = + cabalTargets hieVersions = [ ( "cabal-ghcs" , "Show all GHC versions that can be installed via `cabal-build` and `cabal-build-all`." ) From b51def0ddcefdcf6a618dbe6503c43c2a0241e6a Mon Sep 17 00:00:00 2001 From: Samuel Pilz Date: Sun, 21 Apr 2019 00:07:08 +0200 Subject: [PATCH 13/13] sort the found supported ghc-versions --- install.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/install.hs b/install.hs index ede8c65a5..9ed87fe4e 100755 --- a/install.hs +++ b/install.hs @@ -34,6 +34,7 @@ import Data.Maybe ( isNothing import Data.List ( dropWhileEnd , intersperse , intercalate + , sort ) import qualified Data.Text as T import Data.Char ( isSpace ) @@ -63,6 +64,7 @@ getHieVersions = do & map T.unpack -- the following line excludes `8.6.3` on windows systems & filter (\p -> not isWindowsSystem || p /= "8.6.3") + & sort return hieVersions -- | Most recent version of hie. @@ -319,7 +321,7 @@ shortHelpMessage = do , stackBuildAllTarget -- , stackHieTarget mostRecentHieVersion , stackBuildDocTarget - , stackHieTarget "8.4.4" + , stackHieTarget (last hieVersions) , emptyTarget , ( "cabal-ghcs" , "Show all GHC versions that can be installed via `cabal-build` and `cabal-build-all`." @@ -328,7 +330,7 @@ shortHelpMessage = do , cabalBuildAllTarget -- , cabalHieTarget mostRecentHieVersion , cabalBuildDocTarget - , cabalHieTarget "8.4.4" + , cabalHieTarget (last hieVersions) ]