First cross try
This commit is contained in:
		
							parent
							
								
									d7a6935a1a
								
							
						
					
					
						commit
						f46700e1cc
					
				@ -55,3 +55,10 @@ Anything dealing with ghcup specific directories is in
 | 
				
			|||||||
Download information on where to fetch bindists from is in
 | 
					Download information on where to fetch bindists from is in
 | 
				
			||||||
`GHCup.Data.GHCupDownloads`.
 | 
					`GHCup.Data.GHCupDownloads`.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					## Major refactors
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					1. First major refactor included adding cross support. This added
 | 
				
			||||||
 | 
					   `GHCTargetVersion`, which includes the target in addition to the version.
 | 
				
			||||||
 | 
					   Most of the `Version` parameters to functions had to be replaced with
 | 
				
			||||||
 | 
					   that and ensured the logic is consistent for cross and non-cross
 | 
				
			||||||
 | 
					   installs.
 | 
				
			||||||
 | 
				
			|||||||
							
								
								
									
										13
									
								
								README.md
									
									
									
									
									
								
							
							
						
						
									
										13
									
								
								README.md
									
									
									
									
									
								
							@ -11,6 +11,8 @@ Similar in scope to [rustup](https://github.com/rust-lang-nursery/rustup.rs), [p
 | 
				
			|||||||
   * [Installation](#installation)
 | 
					   * [Installation](#installation)
 | 
				
			||||||
   * [Usage](#usage)
 | 
					   * [Usage](#usage)
 | 
				
			||||||
     * [Manpages](#manpages)
 | 
					     * [Manpages](#manpages)
 | 
				
			||||||
 | 
					     * [Shell-completion](#shell-completion)
 | 
				
			||||||
 | 
					     * [Cross support](#cross-support)
 | 
				
			||||||
   * [Design goals](#design-goals)
 | 
					   * [Design goals](#design-goals)
 | 
				
			||||||
   * [How](#how)
 | 
					   * [How](#how)
 | 
				
			||||||
   * [Known users](#known-users)
 | 
					   * [Known users](#known-users)
 | 
				
			||||||
@ -77,6 +79,17 @@ as e.g. `/etc/bash_completion.d/ghcup` (depending on distro)
 | 
				
			|||||||
and make sure your bashrc sources the startup script
 | 
					and make sure your bashrc sources the startup script
 | 
				
			||||||
(`/usr/share/bash-completion/bash_completion` on some distros).
 | 
					(`/usr/share/bash-completion/bash_completion` on some distros).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					### Cross support
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					ghcup can compile and install a cross GHC for any target. However, this
 | 
				
			||||||
 | 
					requires that the build host has a complete cross toolchain and various
 | 
				
			||||||
 | 
					libraries installed for the target platform.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					Consult the GHC documentation on the [prerequisites](https://gitlab.haskell.org/ghc/ghc/-/wikis/building/cross-compiling#tools-to-install).
 | 
				
			||||||
 | 
					For distributions with non-standard locations of cross toolchain and
 | 
				
			||||||
 | 
					libraries, this may need some tweaking of `build.mk` or configure args.
 | 
				
			||||||
 | 
					See `ghcup compile ghc --help` for further information.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
## Design goals
 | 
					## Design goals
 | 
				
			||||||
 | 
					
 | 
				
			||||||
1. simplicity
 | 
					1. simplicity
 | 
				
			||||||
 | 
				
			|||||||
@ -27,9 +27,12 @@ import           Haskus.Utils.Variant.Excepts
 | 
				
			|||||||
import           Optics
 | 
					import           Optics
 | 
				
			||||||
import           System.Exit
 | 
					import           System.Exit
 | 
				
			||||||
import           System.IO
 | 
					import           System.IO
 | 
				
			||||||
 | 
					import           Text.ParserCombinators.ReadP
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import qualified Data.ByteString               as B
 | 
					import qualified Data.ByteString               as B
 | 
				
			||||||
import qualified Data.Map.Strict               as M
 | 
					import qualified Data.Map.Strict               as M
 | 
				
			||||||
 | 
					import qualified Data.Text                     as T
 | 
				
			||||||
 | 
					import qualified Data.Version                  as V
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
data ValidationError = InternalError String
 | 
					data ValidationError = InternalError String
 | 
				
			||||||
@ -61,7 +64,7 @@ validate dls = do
 | 
				
			|||||||
        forM_ (M.toList $ _viArch vi) $ \(arch, pspecs) -> do
 | 
					        forM_ (M.toList $ _viArch vi) $ \(arch, pspecs) -> do
 | 
				
			||||||
          checkHasRequiredPlatforms t v arch (M.keys pspecs)
 | 
					          checkHasRequiredPlatforms t v arch (M.keys pspecs)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    checkGHCisSemver
 | 
					    checkGHCVerIsValid
 | 
				
			||||||
    forM_ (M.toList dls) $ \(t, _) -> checkMandatoryTags t
 | 
					    forM_ (M.toList dls) $ \(t, _) -> checkMandatoryTags t
 | 
				
			||||||
    _ <- checkGHCHasBaseVersion
 | 
					    _ <- checkGHCHasBaseVersion
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -111,13 +114,14 @@ validate dls = do
 | 
				
			|||||||
    isUniqueTag (Base       _) = False
 | 
					    isUniqueTag (Base       _) = False
 | 
				
			||||||
    isUniqueTag (UnknownTag _) = False
 | 
					    isUniqueTag (UnknownTag _) = False
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  checkGHCisSemver = do
 | 
					  checkGHCVerIsValid = do
 | 
				
			||||||
    let ghcVers = toListOf (ix GHC % to M.keys % folded) dls
 | 
					    let ghcVers = toListOf (ix GHC % to M.keys % folded) dls
 | 
				
			||||||
    forM_ ghcVers $ \v -> case semver (prettyVer v) of
 | 
					    forM_ ghcVers $ \v ->
 | 
				
			||||||
      Left _ -> do
 | 
					      case [ x | (x,"") <- readP_to_S V.parseVersion (T.unpack . prettyVer $ v) ] of
 | 
				
			||||||
        lift $ $(logError) [i|GHC version #{v} is not valid semver|]
 | 
					        [_] -> pure ()
 | 
				
			||||||
        addError
 | 
					        _   -> do
 | 
				
			||||||
      Right _ -> pure ()
 | 
					          lift $ $(logError) [i|GHC version #{v} is not valid |]
 | 
				
			||||||
 | 
					          addError
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  -- a tool must have at least one of each mandatory tags
 | 
					  -- a tool must have at least one of each mandatory tags
 | 
				
			||||||
  checkMandatoryTags tool = do
 | 
					  checkMandatoryTags tool = do
 | 
				
			||||||
 | 
				
			|||||||
@ -19,6 +19,7 @@ import           GHCup.Types
 | 
				
			|||||||
import           GHCup.Utils
 | 
					import           GHCup.Utils
 | 
				
			||||||
import           GHCup.Utils.File
 | 
					import           GHCup.Utils.File
 | 
				
			||||||
import           GHCup.Utils.Logger
 | 
					import           GHCup.Utils.Logger
 | 
				
			||||||
 | 
					import           GHCup.Utils.MegaParsec
 | 
				
			||||||
import           GHCup.Utils.Prelude
 | 
					import           GHCup.Utils.Prelude
 | 
				
			||||||
import           GHCup.Version
 | 
					import           GHCup.Version
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -37,7 +38,7 @@ import           Data.List.NonEmpty             (NonEmpty ((:|)))
 | 
				
			|||||||
import           Data.Maybe
 | 
					import           Data.Maybe
 | 
				
			||||||
import           Data.String.Interpolate
 | 
					import           Data.String.Interpolate
 | 
				
			||||||
import           Data.Text                      ( Text )
 | 
					import           Data.Text                      ( Text )
 | 
				
			||||||
import           Data.Versions
 | 
					import           Data.Versions           hiding ( str )
 | 
				
			||||||
import           Data.Void
 | 
					import           Data.Void
 | 
				
			||||||
import           GHC.IO.Encoding
 | 
					import           GHC.IO.Encoding
 | 
				
			||||||
import           Haskus.Utils.Variant.Excepts
 | 
					import           Haskus.Utils.Variant.Excepts
 | 
				
			||||||
@ -92,11 +93,11 @@ data Command
 | 
				
			|||||||
  | ToolRequirements
 | 
					  | ToolRequirements
 | 
				
			||||||
  | ChangeLog ChangeLogOptions
 | 
					  | ChangeLog ChangeLogOptions
 | 
				
			||||||
 | 
					
 | 
				
			||||||
data ToolVersion = ToolVersion Version
 | 
					data ToolVersion = ToolVersion GHCTargetVersion -- target is ignored for cabal
 | 
				
			||||||
                 | ToolTag Tag
 | 
					                 | ToolTag Tag
 | 
				
			||||||
 | 
					
 | 
				
			||||||
prettyToolVer :: ToolVersion -> String
 | 
					prettyToolVer :: ToolVersion -> String
 | 
				
			||||||
prettyToolVer (ToolVersion v') = T.unpack $ prettyVer v'
 | 
					prettyToolVer (ToolVersion v') = T.unpack $ prettyTVer v'
 | 
				
			||||||
prettyToolVer (ToolTag t) = show t
 | 
					prettyToolVer (ToolTag t) = show t
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -116,15 +117,25 @@ data ListOptions = ListOptions
 | 
				
			|||||||
  }
 | 
					  }
 | 
				
			||||||
 | 
					
 | 
				
			||||||
data RmOptions = RmOptions
 | 
					data RmOptions = RmOptions
 | 
				
			||||||
  { ghcVer :: Version
 | 
					  { ghcVer :: GHCTargetVersion
 | 
				
			||||||
  }
 | 
					  }
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
data CompileCommand = CompileGHC CompileOptions
 | 
					data CompileCommand = CompileGHC GHCCompileOptions
 | 
				
			||||||
                    | CompileCabal CompileOptions
 | 
					                    | CompileCabal CabalCompileOptions
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
data CompileOptions = CompileOptions
 | 
					data GHCCompileOptions = GHCCompileOptions
 | 
				
			||||||
 | 
					  { targetVer    :: Version
 | 
				
			||||||
 | 
					  , bootstrapGhc :: Either Version (Path Abs)
 | 
				
			||||||
 | 
					  , jobs         :: Maybe Int
 | 
				
			||||||
 | 
					  , buildConfig  :: Maybe (Path Abs)
 | 
				
			||||||
 | 
					  , patchDir     :: Maybe (Path Abs)
 | 
				
			||||||
 | 
					  , crossTarget  :: Maybe Text
 | 
				
			||||||
 | 
					  , addConfArgs  :: [Text]
 | 
				
			||||||
 | 
					  }
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					data CabalCompileOptions = CabalCompileOptions
 | 
				
			||||||
  { targetVer    :: Version
 | 
					  { targetVer    :: Version
 | 
				
			||||||
  , bootstrapGhc :: Either Version (Path Abs)
 | 
					  , bootstrapGhc :: Either Version (Path Abs)
 | 
				
			||||||
  , jobs         :: Maybe Int
 | 
					  , jobs         :: Maybe Int
 | 
				
			||||||
@ -377,7 +388,7 @@ compileP = subparser
 | 
				
			|||||||
      "ghc"
 | 
					      "ghc"
 | 
				
			||||||
      (   CompileGHC
 | 
					      (   CompileGHC
 | 
				
			||||||
      <$> (info
 | 
					      <$> (info
 | 
				
			||||||
            (compileOpts <**> helper)
 | 
					            (ghcCompileOpts <**> helper)
 | 
				
			||||||
            (  progDesc "Compile GHC from source"
 | 
					            (  progDesc "Compile GHC from source"
 | 
				
			||||||
            <> footerDoc (Just $ text compileFooter)
 | 
					            <> footerDoc (Just $ text compileFooter)
 | 
				
			||||||
            )
 | 
					            )
 | 
				
			||||||
@ -387,7 +398,7 @@ compileP = subparser
 | 
				
			|||||||
       "cabal"
 | 
					       "cabal"
 | 
				
			||||||
       (   CompileCabal
 | 
					       (   CompileCabal
 | 
				
			||||||
       <$> (info
 | 
					       <$> (info
 | 
				
			||||||
             (compileOpts <**> helper)
 | 
					             (cabalCompileOpts <**> helper)
 | 
				
			||||||
             (  progDesc "Compile Cabal from source"
 | 
					             (  progDesc "Compile Cabal from source"
 | 
				
			||||||
             <> footerDoc (Just $ text compileCabalFooter)
 | 
					             <> footerDoc (Just $ text compileCabalFooter)
 | 
				
			||||||
             )
 | 
					             )
 | 
				
			||||||
@ -400,9 +411,19 @@ compileP = subparser
 | 
				
			|||||||
  a self-contained "~/.ghcup/ghc/<ghcver>" directory
 | 
					  a self-contained "~/.ghcup/ghc/<ghcver>" directory
 | 
				
			||||||
  and symlinks the ghc binaries to "~/.ghcup/bin/<binary>-<ghcver>".
 | 
					  and symlinks the ghc binaries to "~/.ghcup/bin/<binary>-<ghcver>".
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  This also allows building a cross-compiler. Consult the documentation
 | 
				
			||||||
 | 
					  first: <https://gitlab.haskell.org/ghc/ghc/-/wikis/building/cross-compiling#configuring-the-build>
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					ENV variables:
 | 
				
			||||||
 | 
					  Various toolchain variables will be passed onto the ghc build system,
 | 
				
			||||||
 | 
					  such as: CC, LD, OBJDUMP, NM, AR, RANLIB.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
Examples:
 | 
					Examples:
 | 
				
			||||||
  ghcup compile ghc -j 4 -v 8.4.2 -b 8.2.2
 | 
					  ghcup compile ghc -j 4 -v 8.4.2 -b 8.2.2
 | 
				
			||||||
  ghcup compile ghc -j 4 -v 8.4.2 -b /usr/bin/ghc-8.2.2|]
 | 
					  # specify path to bootstrap ghc
 | 
				
			||||||
 | 
					  ghcup compile ghc -j 4 -v 8.4.2 -b /usr/bin/ghc-8.2.2
 | 
				
			||||||
 | 
					  # build cross compiler
 | 
				
			||||||
 | 
					  ghcup compile ghc -j 4 -v 8.4.2 -b 8.2.2 -x armv7-unknown-linux-gnueabihf --config $(pwd)/build.mk -- --enable-unregisterised|]
 | 
				
			||||||
  compileCabalFooter = [i|Discussion:
 | 
					  compileCabalFooter = [i|Discussion:
 | 
				
			||||||
  Compiles and installs the specified Cabal version
 | 
					  Compiles and installs the specified Cabal version
 | 
				
			||||||
  into "~/.ghcup/bin".
 | 
					  into "~/.ghcup/bin".
 | 
				
			||||||
@ -412,10 +433,24 @@ Examples:
 | 
				
			|||||||
  ghcup compile cabal -j 4 -v 3.2.0.0 -b /usr/bin/ghc-8.6.5|]
 | 
					  ghcup compile cabal -j 4 -v 3.2.0.0 -b /usr/bin/ghc-8.6.5|]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					ghcCompileOpts :: Parser GHCCompileOptions
 | 
				
			||||||
 | 
					ghcCompileOpts =
 | 
				
			||||||
 | 
					  (\CabalCompileOptions {..} crossTarget addConfArgs -> GHCCompileOptions { .. }
 | 
				
			||||||
 | 
					    )
 | 
				
			||||||
 | 
					    <$> cabalCompileOpts
 | 
				
			||||||
 | 
					    <*> (optional
 | 
				
			||||||
 | 
					          (option
 | 
				
			||||||
 | 
					            str
 | 
				
			||||||
 | 
					            (short 'x' <> long "cross-target" <> metavar "CROSS_TARGET" <> help
 | 
				
			||||||
 | 
					              "Build cross-compiler for this platform"
 | 
				
			||||||
 | 
					            )
 | 
				
			||||||
 | 
					          )
 | 
				
			||||||
 | 
					        )
 | 
				
			||||||
 | 
					    <*> many (argument str (metavar "CONFIGURE_ARGS" <> help "Additional arguments to configure, prefix with '-- ' (longopts)"))
 | 
				
			||||||
 | 
					
 | 
				
			||||||
compileOpts :: Parser CompileOptions
 | 
					cabalCompileOpts :: Parser CabalCompileOptions
 | 
				
			||||||
compileOpts =
 | 
					cabalCompileOpts =
 | 
				
			||||||
  CompileOptions
 | 
					  CabalCompileOptions
 | 
				
			||||||
    <$> (option
 | 
					    <$> (option
 | 
				
			||||||
          (eitherReader
 | 
					          (eitherReader
 | 
				
			||||||
            (bimap (const "Not a valid version") id . version . T.pack)
 | 
					            (bimap (const "Not a valid version") id . version . T.pack)
 | 
				
			||||||
@ -490,12 +525,12 @@ toolVersionArgument =
 | 
				
			|||||||
  argument (eitherReader toolVersionEither) (metavar "VERSION|TAG")
 | 
					  argument (eitherReader toolVersionEither) (metavar "VERSION|TAG")
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
versionArgument :: Parser Version
 | 
					versionArgument :: Parser GHCTargetVersion
 | 
				
			||||||
versionArgument = argument (eitherReader versionEither) (metavar "VERSION")
 | 
					versionArgument = argument (eitherReader tVersionEither) (metavar "VERSION")
 | 
				
			||||||
 | 
					
 | 
				
			||||||
versionParser :: Parser Version
 | 
					versionParser :: Parser GHCTargetVersion
 | 
				
			||||||
versionParser = option
 | 
					versionParser = option
 | 
				
			||||||
  (eitherReader versionEither)
 | 
					  (eitherReader tVersionEither)
 | 
				
			||||||
  (short 'v' <> long "version" <> metavar "VERSION" <> help "The target version"
 | 
					  (short 'v' <> long "version" <> metavar "VERSION" <> help "The target version"
 | 
				
			||||||
  )
 | 
					  )
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -508,16 +543,15 @@ tagEither s' = case fmap toLower s' of
 | 
				
			|||||||
                                  Left  _ -> Left [i|Invalid PVP version for base #{ver'}|]
 | 
					                                  Left  _ -> Left [i|Invalid PVP version for base #{ver'}|]
 | 
				
			||||||
  other         -> Left ([i|Unknown tag #{other}|])
 | 
					  other         -> Left ([i|Unknown tag #{other}|])
 | 
				
			||||||
 | 
					
 | 
				
			||||||
versionEither :: String -> Either String Version
 | 
					
 | 
				
			||||||
versionEither s' =
 | 
					tVersionEither :: String -> Either String GHCTargetVersion
 | 
				
			||||||
  -- 'version' is a bit too lax and will parse typoed tags
 | 
					tVersionEither =
 | 
				
			||||||
                   case readMaybe ((: []) . head $ s') :: Maybe Int of
 | 
					  bimap (const "Not a valid version") id . MP.parse ghcTargetVerP "" . T.pack
 | 
				
			||||||
  Just _  -> bimap (const "Not a valid version") id . version . T.pack $ s'
 | 
					
 | 
				
			||||||
  Nothing -> Left "Not a valid version"
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
toolVersionEither :: String -> Either String ToolVersion
 | 
					toolVersionEither :: String -> Either String ToolVersion
 | 
				
			||||||
toolVersionEither s' =
 | 
					toolVersionEither s' =
 | 
				
			||||||
  bimap id ToolTag (tagEither s') <|> bimap id ToolVersion (versionEither s')
 | 
					  bimap id ToolTag (tagEither s') <|> bimap id ToolVersion (tVersionEither s')
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
toolParser :: String -> Either String Tool
 | 
					toolParser :: String -> Either String Tool
 | 
				
			||||||
@ -611,18 +645,7 @@ platformParser s' = case MP.parse (platformP <* MP.eof) "" (T.pack s') of
 | 
				
			|||||||
        MP.setInput rest
 | 
					        MP.setInput rest
 | 
				
			||||||
        pure v
 | 
					        pure v
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  choice' []       = fail "Empty list"
 | 
					 | 
				
			||||||
  choice' [x     ] = x
 | 
					 | 
				
			||||||
  choice' (x : xs) = MP.try x <|> choice' xs
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
  parseUntil :: MP.Parsec Void Text Text -> MP.Parsec Void Text Text
 | 
					 | 
				
			||||||
  parseUntil p = do
 | 
					 | 
				
			||||||
    (MP.try (MP.lookAhead p) $> mempty)
 | 
					 | 
				
			||||||
      <|> (do
 | 
					 | 
				
			||||||
            c  <- T.singleton <$> MP.anySingle
 | 
					 | 
				
			||||||
            c2 <- parseUntil p
 | 
					 | 
				
			||||||
            pure (c `mappend` c2)
 | 
					 | 
				
			||||||
          )
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
toSettings :: Options -> Settings
 | 
					toSettings :: Options -> Settings
 | 
				
			||||||
@ -834,7 +857,7 @@ Report bugs at <https://gitlab.haskell.org/haskell/ghcup-hs/issues>|]
 | 
				
			|||||||
            Install (InstallOptions {..}) ->
 | 
					            Install (InstallOptions {..}) ->
 | 
				
			||||||
              (runInstTool $ do
 | 
					              (runInstTool $ do
 | 
				
			||||||
                  v <- liftE $ fromVersion dls instVer GHC
 | 
					                  v <- liftE $ fromVersion dls instVer GHC
 | 
				
			||||||
                  liftE $ installGHCBin dls v instPlatform
 | 
					                  liftE $ installGHCBin dls (_tvVersion v) instPlatform -- FIXME: ugly sharing of tool version
 | 
				
			||||||
                )
 | 
					                )
 | 
				
			||||||
                >>= \case
 | 
					                >>= \case
 | 
				
			||||||
                      VRight _ -> do
 | 
					                      VRight _ -> do
 | 
				
			||||||
@ -866,7 +889,7 @@ Make sure to clean up #{tmpdir} afterwards.|])
 | 
				
			|||||||
            InstallCabal (InstallOptions {..}) ->
 | 
					            InstallCabal (InstallOptions {..}) ->
 | 
				
			||||||
              (runInstTool $ do
 | 
					              (runInstTool $ do
 | 
				
			||||||
                  v <- liftE $ fromVersion dls instVer Cabal
 | 
					                  v <- liftE $ fromVersion dls instVer Cabal
 | 
				
			||||||
                  liftE $ installCabalBin dls v instPlatform
 | 
					                  liftE $ installCabalBin dls (_tvVersion v) instPlatform -- FIXME: ugly sharing of tool version
 | 
				
			||||||
                )
 | 
					                )
 | 
				
			||||||
                >>= \case
 | 
					                >>= \case
 | 
				
			||||||
                      VRight _ -> do
 | 
					                      VRight _ -> do
 | 
				
			||||||
@ -895,10 +918,10 @@ Make sure to clean up #{tmpdir} afterwards.|])
 | 
				
			|||||||
                  liftE $ setGHC v SetGHCOnly
 | 
					                  liftE $ setGHC v SetGHCOnly
 | 
				
			||||||
                )
 | 
					                )
 | 
				
			||||||
                >>= \case
 | 
					                >>= \case
 | 
				
			||||||
                      VRight v -> do
 | 
					                      VRight (GHCTargetVersion{..}) -> do
 | 
				
			||||||
                        runLogger
 | 
					                        runLogger
 | 
				
			||||||
                          $ $(logInfo)
 | 
					                          $ $(logInfo)
 | 
				
			||||||
                              [i|GHC #{prettyVer v} successfully set as default version|]
 | 
					                              [i|GHC #{prettyVer _tvVersion} successfully set as default version#{maybe "" (" for cross target " <>) _tvTarget}|]
 | 
				
			||||||
                        pure ExitSuccess
 | 
					                        pure ExitSuccess
 | 
				
			||||||
                      VLeft e -> do
 | 
					                      VLeft e -> do
 | 
				
			||||||
                        runLogger ($(logError) [i|#{e}|])
 | 
					                        runLogger ($(logError) [i|#{e}|])
 | 
				
			||||||
@ -938,13 +961,14 @@ Make sure to clean up #{tmpdir} afterwards.|])
 | 
				
			|||||||
                        runLogger ($(logError) [i|#{e}|])
 | 
					                        runLogger ($(logError) [i|#{e}|])
 | 
				
			||||||
                        pure $ ExitFailure 8
 | 
					                        pure $ ExitFailure 8
 | 
				
			||||||
 | 
					
 | 
				
			||||||
            Compile (CompileGHC CompileOptions {..}) ->
 | 
					            Compile (CompileGHC GHCCompileOptions {..}) ->
 | 
				
			||||||
              (runCompileGHC $ liftE $ compileGHC dls
 | 
					              (runCompileGHC $ liftE $ compileGHC dls
 | 
				
			||||||
                                                  targetVer
 | 
					                                                  (GHCTargetVersion crossTarget targetVer)
 | 
				
			||||||
                                                  bootstrapGhc
 | 
					                                                  bootstrapGhc
 | 
				
			||||||
                                                  jobs
 | 
					                                                  jobs
 | 
				
			||||||
                                                  buildConfig
 | 
					                                                  buildConfig
 | 
				
			||||||
                                                  patchDir
 | 
					                                                  patchDir
 | 
				
			||||||
 | 
					                                                  addConfArgs
 | 
				
			||||||
                )
 | 
					                )
 | 
				
			||||||
                >>= \case
 | 
					                >>= \case
 | 
				
			||||||
                      VRight _ -> do
 | 
					                      VRight _ -> do
 | 
				
			||||||
@ -957,7 +981,8 @@ Make sure to clean up #{tmpdir} afterwards.|])
 | 
				
			|||||||
                        pure ExitSuccess
 | 
					                        pure ExitSuccess
 | 
				
			||||||
                      VLeft (V (BuildFailed tmpdir e)) -> do
 | 
					                      VLeft (V (BuildFailed tmpdir e)) -> do
 | 
				
			||||||
                        case keepDirs of
 | 
					                        case keepDirs of
 | 
				
			||||||
                          Never -> runLogger ($(logError) [i|Build failed with #{e}|])
 | 
					                          Never -> runLogger ($(logError) [i|Build failed with #{e}
 | 
				
			||||||
 | 
					Check the logs at ~/.ghcup/logs|])
 | 
				
			||||||
                          _ -> runLogger ($(logError) [i|Build failed with #{e}
 | 
					                          _ -> runLogger ($(logError) [i|Build failed with #{e}
 | 
				
			||||||
Check the logs at ~/.ghcup/logs and the build directory #{tmpdir} for more clues.
 | 
					Check the logs at ~/.ghcup/logs and the build directory #{tmpdir} for more clues.
 | 
				
			||||||
Make sure to clean up #{tmpdir} afterwards.|])
 | 
					Make sure to clean up #{tmpdir} afterwards.|])
 | 
				
			||||||
@ -966,7 +991,7 @@ Make sure to clean up #{tmpdir} afterwards.|])
 | 
				
			|||||||
                        runLogger ($(logError) [i|#{e}|])
 | 
					                        runLogger ($(logError) [i|#{e}|])
 | 
				
			||||||
                        pure $ ExitFailure 9
 | 
					                        pure $ ExitFailure 9
 | 
				
			||||||
 | 
					
 | 
				
			||||||
            Compile (CompileCabal CompileOptions {..}) ->
 | 
					            Compile (CompileCabal CabalCompileOptions {..}) ->
 | 
				
			||||||
              (runCompileCabal $ do
 | 
					              (runCompileCabal $ do
 | 
				
			||||||
                  liftE $ compileCabal dls targetVer bootstrapGhc jobs patchDir
 | 
					                  liftE $ compileCabal dls targetVer bootstrapGhc jobs patchDir
 | 
				
			||||||
                )
 | 
					                )
 | 
				
			||||||
@ -1037,7 +1062,7 @@ Make sure to clean up #{tmpdir} afterwards.|])
 | 
				
			|||||||
                  ver' = maybe
 | 
					                  ver' = maybe
 | 
				
			||||||
                    (Right Latest)
 | 
					                    (Right Latest)
 | 
				
			||||||
                    (\case
 | 
					                    (\case
 | 
				
			||||||
                      ToolVersion tv -> Left tv
 | 
					                      ToolVersion tv -> Left (_tvVersion tv) -- FIXME: ugly sharing of ToolVersion
 | 
				
			||||||
                      ToolTag     t  -> Right t
 | 
					                      ToolTag     t  -> Right t
 | 
				
			||||||
                    )
 | 
					                    )
 | 
				
			||||||
                    clToolVer
 | 
					                    clToolVer
 | 
				
			||||||
@ -1074,23 +1099,23 @@ fromVersion :: Monad m
 | 
				
			|||||||
            => GHCupDownloads
 | 
					            => GHCupDownloads
 | 
				
			||||||
            -> Maybe ToolVersion
 | 
					            -> Maybe ToolVersion
 | 
				
			||||||
            -> Tool
 | 
					            -> Tool
 | 
				
			||||||
            -> Excepts '[TagNotFound] m Version
 | 
					            -> Excepts '[TagNotFound] m GHCTargetVersion
 | 
				
			||||||
fromVersion av Nothing tool =
 | 
					fromVersion av Nothing tool =
 | 
				
			||||||
  getRecommended av tool ?? TagNotFound Recommended tool
 | 
					  mkTVer <$> getRecommended av tool ?? TagNotFound Recommended tool
 | 
				
			||||||
fromVersion av (Just (ToolVersion v)) _ = do
 | 
					fromVersion av (Just (ToolVersion v)) _ = do
 | 
				
			||||||
  case pvp $ prettyVer v of
 | 
					  case pvp $ prettyVer (_tvVersion v) of
 | 
				
			||||||
    Left _ -> pure v
 | 
					    Left _ -> pure v
 | 
				
			||||||
    Right (PVP (major' :|[minor'])) ->
 | 
					    Right (PVP (major' :|[minor'])) ->
 | 
				
			||||||
      case getLatestGHCFor (fromIntegral major') (fromIntegral minor') av of
 | 
					      case getLatestGHCFor (fromIntegral major') (fromIntegral minor') av of
 | 
				
			||||||
        Just v' -> pure v'
 | 
					        Just v' -> pure $ GHCTargetVersion (_tvTarget v) v'
 | 
				
			||||||
        Nothing -> pure v
 | 
					        Nothing -> pure v
 | 
				
			||||||
    Right _ -> pure v
 | 
					    Right _ -> pure v
 | 
				
			||||||
fromVersion av (Just (ToolTag Latest)) tool =
 | 
					fromVersion av (Just (ToolTag Latest)) tool =
 | 
				
			||||||
  getLatest av tool ?? TagNotFound Latest tool
 | 
					  mkTVer <$> getLatest av tool ?? TagNotFound Latest tool
 | 
				
			||||||
fromVersion av (Just (ToolTag Recommended)) tool =
 | 
					fromVersion av (Just (ToolTag Recommended)) tool =
 | 
				
			||||||
  getRecommended av tool ?? TagNotFound Recommended tool
 | 
					  mkTVer <$> getRecommended av tool ?? TagNotFound Recommended tool
 | 
				
			||||||
fromVersion av (Just (ToolTag (Base pvp''))) GHC =
 | 
					fromVersion av (Just (ToolTag (Base pvp''))) GHC =
 | 
				
			||||||
  getLatestBaseVersion av pvp'' ?? TagNotFound (Base pvp'') GHC
 | 
					  mkTVer <$> getLatestBaseVersion av pvp'' ?? TagNotFound (Base pvp'') GHC
 | 
				
			||||||
fromVersion _ (Just (ToolTag t')) tool =
 | 
					fromVersion _ (Just (ToolTag t')) tool =
 | 
				
			||||||
  throwE $ TagNotFound t' tool
 | 
					  throwE $ TagNotFound t' tool
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -1122,7 +1147,9 @@ printListResult raw lr = do
 | 
				
			|||||||
                    | otherwise  -> (color Red "✗")
 | 
					                    | otherwise  -> (color Red "✗")
 | 
				
			||||||
              in  (if raw then [] else [marks])
 | 
					              in  (if raw then [] else [marks])
 | 
				
			||||||
                    ++ [ fmap toLower . show $ lTool
 | 
					                    ++ [ fmap toLower . show $ lTool
 | 
				
			||||||
                       , T.unpack . prettyVer $ lVer
 | 
					                       , case lCross of
 | 
				
			||||||
 | 
					                           Nothing -> T.unpack . prettyVer $ lVer
 | 
				
			||||||
 | 
					                           Just c  -> T.unpack (c <> "-" <> prettyVer lVer)
 | 
				
			||||||
                       , intercalate "," $ (fmap printTag $ sort lTag)
 | 
					                       , intercalate "," $ (fmap printTag $ sort lTag)
 | 
				
			||||||
                       , intercalate ","
 | 
					                       , intercalate ","
 | 
				
			||||||
                       $  (if fromSrc then [color' Blue "compiled"] else mempty)
 | 
					                       $  (if fromSrc then [color' Blue "compiled"] else mempty)
 | 
				
			||||||
 | 
				
			|||||||
@ -41,9 +41,6 @@ common ascii-string
 | 
				
			|||||||
common async
 | 
					common async
 | 
				
			||||||
  build-depends: async >=0.8
 | 
					  build-depends: async >=0.8
 | 
				
			||||||
 | 
					
 | 
				
			||||||
common attoparsec
 | 
					 | 
				
			||||||
  build-depends: attoparsec >=0.13
 | 
					 | 
				
			||||||
 | 
					 | 
				
			||||||
common base
 | 
					common base
 | 
				
			||||||
  build-depends: base >=4.12 && <5
 | 
					  build-depends: base >=4.12 && <5
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -230,7 +227,6 @@ library
 | 
				
			|||||||
    , aeson
 | 
					    , aeson
 | 
				
			||||||
    , ascii-string
 | 
					    , ascii-string
 | 
				
			||||||
    , async
 | 
					    , async
 | 
				
			||||||
    , attoparsec
 | 
					 | 
				
			||||||
    , binary
 | 
					    , binary
 | 
				
			||||||
    , bytestring
 | 
					    , bytestring
 | 
				
			||||||
    , bz2
 | 
					    , bz2
 | 
				
			||||||
@ -248,6 +244,7 @@ library
 | 
				
			|||||||
    , hpath-posix
 | 
					    , hpath-posix
 | 
				
			||||||
    , language-bash
 | 
					    , language-bash
 | 
				
			||||||
    , lzma
 | 
					    , lzma
 | 
				
			||||||
 | 
					    , megaparsec
 | 
				
			||||||
    , monad-logger
 | 
					    , monad-logger
 | 
				
			||||||
    , mtl
 | 
					    , mtl
 | 
				
			||||||
    , optics
 | 
					    , optics
 | 
				
			||||||
@ -295,6 +292,7 @@ library
 | 
				
			|||||||
    GHCup.Utils.Dirs
 | 
					    GHCup.Utils.Dirs
 | 
				
			||||||
    GHCup.Utils.File
 | 
					    GHCup.Utils.File
 | 
				
			||||||
    GHCup.Utils.Logger
 | 
					    GHCup.Utils.Logger
 | 
				
			||||||
 | 
					    GHCup.Utils.MegaParsec
 | 
				
			||||||
    GHCup.Utils.Prelude
 | 
					    GHCup.Utils.Prelude
 | 
				
			||||||
    GHCup.Utils.String.QQ
 | 
					    GHCup.Utils.String.QQ
 | 
				
			||||||
    GHCup.Utils.Version.QQ
 | 
					    GHCup.Utils.Version.QQ
 | 
				
			||||||
 | 
				
			|||||||
							
								
								
									
										209
									
								
								lib/GHCup.hs
									
									
									
									
									
								
							
							
						
						
									
										209
									
								
								lib/GHCup.hs
									
									
									
									
									
								
							@ -41,6 +41,7 @@ import           Data.ByteString                ( ByteString )
 | 
				
			|||||||
import           Data.List
 | 
					import           Data.List
 | 
				
			||||||
import           Data.Maybe
 | 
					import           Data.Maybe
 | 
				
			||||||
import           Data.String.Interpolate
 | 
					import           Data.String.Interpolate
 | 
				
			||||||
 | 
					import           Data.Text                      ( Text )
 | 
				
			||||||
import           Data.Versions
 | 
					import           Data.Versions
 | 
				
			||||||
import           Data.Word8
 | 
					import           Data.Word8
 | 
				
			||||||
import           GHC.IO.Exception
 | 
					import           GHC.IO.Exception
 | 
				
			||||||
@ -53,11 +54,14 @@ import           Prelude                 hiding ( abs
 | 
				
			|||||||
                                                , writeFile
 | 
					                                                , writeFile
 | 
				
			||||||
                                                )
 | 
					                                                )
 | 
				
			||||||
import           System.IO.Error
 | 
					import           System.IO.Error
 | 
				
			||||||
 | 
					import           System.Posix.Env.ByteString    ( getEnvironment )
 | 
				
			||||||
import           System.Posix.FilePath          ( getSearchPath )
 | 
					import           System.Posix.FilePath          ( getSearchPath )
 | 
				
			||||||
import           System.Posix.Files.ByteString
 | 
					import           System.Posix.Files.ByteString
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import qualified Data.ByteString               as B
 | 
					import qualified Data.ByteString               as B
 | 
				
			||||||
 | 
					import qualified Data.ByteString.Lazy          as BL
 | 
				
			||||||
import qualified Data.Map.Strict               as Map
 | 
					import qualified Data.Map.Strict               as Map
 | 
				
			||||||
 | 
					import qualified Data.Text                     as T
 | 
				
			||||||
import qualified Data.Text.Encoding            as E
 | 
					import qualified Data.Text.Encoding            as E
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -94,8 +98,9 @@ installGHCBin :: ( MonadFail m
 | 
				
			|||||||
                   m
 | 
					                   m
 | 
				
			||||||
                   ()
 | 
					                   ()
 | 
				
			||||||
installGHCBin bDls ver mpfReq = do
 | 
					installGHCBin bDls ver mpfReq = do
 | 
				
			||||||
 | 
					  let tver = (mkTVer ver)
 | 
				
			||||||
  lift $ $(logDebug) [i|Requested to install GHC with #{ver}|]
 | 
					  lift $ $(logDebug) [i|Requested to install GHC with #{ver}|]
 | 
				
			||||||
  whenM (liftIO $ toolAlreadyInstalled GHC ver)
 | 
					  whenM (liftIO $ ghcInstalled tver)
 | 
				
			||||||
    $ (throwE $ AlreadyInstalled GHC ver)
 | 
					    $ (throwE $ AlreadyInstalled GHC ver)
 | 
				
			||||||
  Settings {..}                <- lift ask
 | 
					  Settings {..}                <- lift ask
 | 
				
			||||||
  pfreq@(PlatformRequest {..}) <- maybe (liftE $ platformRequest) pure mpfReq
 | 
					  pfreq@(PlatformRequest {..}) <- maybe (liftE $ platformRequest) pure mpfReq
 | 
				
			||||||
@ -110,14 +115,14 @@ installGHCBin bDls ver mpfReq = do
 | 
				
			|||||||
  void $ liftIO $ darwinNotarization _rPlatform tmpUnpack
 | 
					  void $ liftIO $ darwinNotarization _rPlatform tmpUnpack
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  -- prepare paths
 | 
					  -- prepare paths
 | 
				
			||||||
  ghcdir <- liftIO $ ghcupGHCDir ver
 | 
					  ghcdir <- liftIO $ ghcupGHCDir tver
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  -- the subdir of the archive where we do the work
 | 
					  -- the subdir of the archive where we do the work
 | 
				
			||||||
  let workdir = maybe tmpUnpack (tmpUnpack </>) (view dlSubdir dlinfo)
 | 
					  let workdir = maybe tmpUnpack (tmpUnpack </>) (view dlSubdir dlinfo)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  liftE $ runBuildAction tmpUnpack (Just ghcdir) (installGHC' workdir ghcdir)
 | 
					  liftE $ runBuildAction tmpUnpack (Just ghcdir) (installGHC' workdir ghcdir)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  liftE $ postGHCInstall ver
 | 
					  liftE $ postGHCInstall tver
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 where
 | 
					 where
 | 
				
			||||||
  -- | Install an unpacked GHC distribution. This only deals with the GHC build system and nothing else.
 | 
					  -- | Install an unpacked GHC distribution. This only deals with the GHC build system and nothing else.
 | 
				
			||||||
@ -161,15 +166,15 @@ installCabalBin :: ( MonadMask m
 | 
				
			|||||||
                     ()
 | 
					                     ()
 | 
				
			||||||
installCabalBin bDls ver mpfReq = do
 | 
					installCabalBin bDls ver mpfReq = do
 | 
				
			||||||
  lift $ $(logDebug) [i|Requested to install cabal version #{ver}|]
 | 
					  lift $ $(logDebug) [i|Requested to install cabal version #{ver}|]
 | 
				
			||||||
  Settings {..} <- lift ask
 | 
					  Settings {..}                <- lift ask
 | 
				
			||||||
  pfreq@(PlatformRequest {..}) <- maybe (liftE $ platformRequest) pure mpfReq
 | 
					  pfreq@(PlatformRequest {..}) <- maybe (liftE $ platformRequest) pure mpfReq
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  -- download (or use cached version)
 | 
					  -- download (or use cached version)
 | 
				
			||||||
  dlinfo        <- lE $ getDownloadInfo Cabal ver pfreq bDls
 | 
					  dlinfo                       <- lE $ getDownloadInfo Cabal ver pfreq bDls
 | 
				
			||||||
  dl            <- liftE $ downloadCached dlinfo Nothing
 | 
					  dl                           <- liftE $ downloadCached dlinfo Nothing
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  -- unpack
 | 
					  -- unpack
 | 
				
			||||||
  tmpUnpack     <- lift withGHCupTmpDir
 | 
					  tmpUnpack                    <- lift withGHCupTmpDir
 | 
				
			||||||
  liftE $ unpackToDir tmpUnpack dl
 | 
					  liftE $ unpackToDir tmpUnpack dl
 | 
				
			||||||
  void $ liftIO $ darwinNotarization _rPlatform tmpUnpack
 | 
					  void $ liftIO $ darwinNotarization _rPlatform tmpUnpack
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -215,11 +220,11 @@ installCabalBin bDls ver mpfReq = do
 | 
				
			|||||||
-- Additionally creates a ~/.ghcup/share -> ~/.ghcup/ghc/<ver>/share symlink
 | 
					-- Additionally creates a ~/.ghcup/share -> ~/.ghcup/ghc/<ver>/share symlink
 | 
				
			||||||
-- for `SetGHCOnly` constructor.
 | 
					-- for `SetGHCOnly` constructor.
 | 
				
			||||||
setGHC :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
 | 
					setGHC :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
 | 
				
			||||||
       => Version
 | 
					       => GHCTargetVersion
 | 
				
			||||||
       -> SetGHC
 | 
					       -> SetGHC
 | 
				
			||||||
       -> Excepts '[NotInstalled] m Version
 | 
					       -> Excepts '[NotInstalled] m GHCTargetVersion
 | 
				
			||||||
setGHC ver sghc = do
 | 
					setGHC ver sghc = do
 | 
				
			||||||
  let verBS = verToBS ver
 | 
					  let verBS = verToBS (_tvVersion ver)
 | 
				
			||||||
  ghcdir <- liftIO $ ghcupGHCDir ver
 | 
					  ghcdir <- liftIO $ ghcupGHCDir ver
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  -- symlink destination
 | 
					  -- symlink destination
 | 
				
			||||||
@ -229,7 +234,7 @@ setGHC ver sghc = do
 | 
				
			|||||||
  -- first delete the old symlinks (this fixes compatibility issues
 | 
					  -- first delete the old symlinks (this fixes compatibility issues
 | 
				
			||||||
  -- with old ghcup)
 | 
					  -- with old ghcup)
 | 
				
			||||||
  case sghc of
 | 
					  case sghc of
 | 
				
			||||||
    SetGHCOnly -> liftE $ rmPlain ver
 | 
					    SetGHCOnly -> liftE $ rmPlain (_tvTarget ver)
 | 
				
			||||||
    SetGHC_XY  -> lift $ rmMajorSymlinks ver
 | 
					    SetGHC_XY  -> lift $ rmMajorSymlinks ver
 | 
				
			||||||
    SetGHC_XYZ -> lift $ rmMinorSymlinks ver
 | 
					    SetGHC_XYZ -> lift $ rmMinorSymlinks ver
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -239,9 +244,8 @@ setGHC ver sghc = do
 | 
				
			|||||||
    targetFile <- case sghc of
 | 
					    targetFile <- case sghc of
 | 
				
			||||||
      SetGHCOnly -> pure file
 | 
					      SetGHCOnly -> pure file
 | 
				
			||||||
      SetGHC_XY  -> do
 | 
					      SetGHC_XY  -> do
 | 
				
			||||||
        major' <-
 | 
					        major' <- (\(mj, mi) -> E.encodeUtf8 $ intToText mj <> "." <> intToText mi)
 | 
				
			||||||
          (\(mj, mi) -> E.encodeUtf8 $ intToText mj <> "." <> intToText mi)
 | 
					                     <$> getMajorMinorV (_tvVersion ver)
 | 
				
			||||||
            <$> getGHCMajor ver
 | 
					 | 
				
			||||||
        parseRel (toFilePath file <> B.singleton _hyphen <> major')
 | 
					        parseRel (toFilePath file <> B.singleton _hyphen <> major')
 | 
				
			||||||
      SetGHC_XYZ -> parseRel (toFilePath file <> B.singleton _hyphen <> verBS)
 | 
					      SetGHC_XYZ -> parseRel (toFilePath file <> B.singleton _hyphen <> verBS)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -252,7 +256,7 @@ setGHC ver sghc = do
 | 
				
			|||||||
    liftIO $ createSymlink fullF destL
 | 
					    liftIO $ createSymlink fullF destL
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  -- create symlink for share dir
 | 
					  -- create symlink for share dir
 | 
				
			||||||
  lift $ symlinkShareDir ghcdir verBS
 | 
					  when (isNothing . _tvTarget $ ver) $ lift $ symlinkShareDir ghcdir verBS
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  pure ver
 | 
					  pure ver
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -292,6 +296,7 @@ data ListCriteria = ListInstalled
 | 
				
			|||||||
data ListResult = ListResult
 | 
					data ListResult = ListResult
 | 
				
			||||||
  { lTool      :: Tool
 | 
					  { lTool      :: Tool
 | 
				
			||||||
  , lVer       :: Version
 | 
					  , lVer       :: Version
 | 
				
			||||||
 | 
					  , lCross     :: Maybe Text -- ^ currently only for GHC
 | 
				
			||||||
  , lTag       :: [Tag]
 | 
					  , lTag       :: [Tag]
 | 
				
			||||||
  , lInstalled :: Bool
 | 
					  , lInstalled :: Bool
 | 
				
			||||||
  , lSet       :: Bool -- ^ currently active version
 | 
					  , lSet       :: Bool -- ^ currently active version
 | 
				
			||||||
@ -309,7 +314,7 @@ availableToolVersions av tool = view
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
-- | List all versions from the download info, as well as stray
 | 
					-- | List all versions from the download info, as well as stray
 | 
				
			||||||
-- versions.
 | 
					-- versions.
 | 
				
			||||||
listVersions :: (MonadLogger m, MonadIO m)
 | 
					listVersions :: (MonadThrow m, MonadLogger m, MonadIO m)
 | 
				
			||||||
             => GHCupDownloads
 | 
					             => GHCupDownloads
 | 
				
			||||||
             -> Maybe Tool
 | 
					             -> Maybe Tool
 | 
				
			||||||
             -> Maybe ListCriteria
 | 
					             -> Maybe ListCriteria
 | 
				
			||||||
@ -333,44 +338,58 @@ listVersions av lt criteria = case lt of
 | 
				
			|||||||
    pure (ghcvers <> cabalvers <> ghcupvers)
 | 
					    pure (ghcvers <> cabalvers <> ghcupvers)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 where
 | 
					 where
 | 
				
			||||||
  strayGHCs :: (MonadLogger m, MonadIO m)
 | 
					  strayGHCs :: (MonadThrow m, MonadLogger m, MonadIO m)
 | 
				
			||||||
            => Map.Map Version [Tag]
 | 
					            => Map.Map Version [Tag]
 | 
				
			||||||
            -> m [ListResult]
 | 
					            -> m [ListResult]
 | 
				
			||||||
  strayGHCs avTools = do
 | 
					  strayGHCs avTools = do
 | 
				
			||||||
    ghcdir <- liftIO $ ghcupGHCBaseDir
 | 
					    ghcs <- getInstalledGHCs
 | 
				
			||||||
    fs     <- liftIO $ liftIO $ hideErrorDef [NoSuchThing] [] $ getDirsFiles' ghcdir
 | 
					    fmap catMaybes $ forM ghcs $ \case
 | 
				
			||||||
    fmap catMaybes $ forM fs $ \(toFilePath -> f) -> do
 | 
					      Right tver@GHCTargetVersion{ _tvTarget = Nothing, .. } -> do
 | 
				
			||||||
      case version . decUTF8Safe $ f of
 | 
					        case Map.lookup _tvVersion avTools of
 | 
				
			||||||
        Right v' -> do
 | 
					          Just _  -> pure Nothing
 | 
				
			||||||
          case Map.lookup v' avTools of
 | 
					          Nothing -> do
 | 
				
			||||||
            Just _  -> pure Nothing
 | 
					            lSet    <- fmap (maybe False (\(GHCTargetVersion _ v ) -> v == _tvVersion)) $ ghcSet Nothing
 | 
				
			||||||
            Nothing -> do
 | 
					            fromSrc <- liftIO $ ghcSrcInstalled tver
 | 
				
			||||||
              lSet    <- fmap (maybe False (== v')) $ ghcSet
 | 
					            pure $ Just $ ListResult
 | 
				
			||||||
              fromSrc <- liftIO $ ghcSrcInstalled v'
 | 
					              { lTool      = GHC
 | 
				
			||||||
              pure $ Just $ ListResult
 | 
					              , lVer       = _tvVersion
 | 
				
			||||||
                { lTool      = GHC
 | 
					              , lCross     = Nothing
 | 
				
			||||||
                , lVer       = v'
 | 
					              , lTag       = []
 | 
				
			||||||
                , lTag       = []
 | 
					              , lInstalled = True
 | 
				
			||||||
                , lInstalled = True
 | 
					              , lStray     = maybe True (const False) (Map.lookup _tvVersion avTools)
 | 
				
			||||||
                , lStray     = maybe True (const False) (Map.lookup v' avTools)
 | 
					              , ..
 | 
				
			||||||
                , ..
 | 
					              }
 | 
				
			||||||
                }
 | 
					      Right tver@GHCTargetVersion{ .. } -> do
 | 
				
			||||||
        Left e -> do
 | 
					        lSet    <- fmap (maybe False (\(GHCTargetVersion _ v ) -> v == _tvVersion)) $ ghcSet _tvTarget
 | 
				
			||||||
          $(logWarn)
 | 
					        fromSrc <- liftIO $ ghcSrcInstalled tver
 | 
				
			||||||
            [i|Could not parse version of stray directory #{toFilePath ghcdir}/#{f}: #{e}|]
 | 
					        pure $ Just $ ListResult
 | 
				
			||||||
          pure Nothing
 | 
					          { lTool      = GHC
 | 
				
			||||||
 | 
					          , lVer       = _tvVersion
 | 
				
			||||||
 | 
					          , lCross     = _tvTarget
 | 
				
			||||||
 | 
					          , lTag       = []
 | 
				
			||||||
 | 
					          , lInstalled = True
 | 
				
			||||||
 | 
					          , lStray     = True -- NOTE: cross currently cannot be installed via bindist
 | 
				
			||||||
 | 
					          , ..
 | 
				
			||||||
 | 
					          }
 | 
				
			||||||
 | 
					      Left e -> do
 | 
				
			||||||
 | 
					        $(logWarn)
 | 
				
			||||||
 | 
					          [i|Could not parse version of stray directory #{toFilePath e}|]
 | 
				
			||||||
 | 
					        pure Nothing
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  -- NOTE: this are not cross ones, because no bindists
 | 
				
			||||||
  toListResult :: Tool -> (Version, [Tag]) -> IO ListResult
 | 
					  toListResult :: Tool -> (Version, [Tag]) -> IO ListResult
 | 
				
			||||||
  toListResult t (v, tags) = case t of
 | 
					  toListResult t (v, tags) = case t of
 | 
				
			||||||
    GHC -> do
 | 
					    GHC -> do
 | 
				
			||||||
      lSet       <- fmap (maybe False (== v)) $ ghcSet
 | 
					      let tver = mkTVer v
 | 
				
			||||||
      lInstalled <- ghcInstalled v
 | 
					      lSet       <- fmap (maybe False (\(GHCTargetVersion _ v') -> v' == v)) $ ghcSet Nothing
 | 
				
			||||||
      fromSrc    <- ghcSrcInstalled v
 | 
					      lInstalled <- ghcInstalled tver
 | 
				
			||||||
      pure ListResult { lVer = v, lTag = tags, lTool = t, lStray = False, .. }
 | 
					      fromSrc    <- ghcSrcInstalled tver
 | 
				
			||||||
 | 
					      pure ListResult { lVer = v, lCross = Nothing , lTag = tags, lTool = t, lStray = False, .. }
 | 
				
			||||||
    Cabal -> do
 | 
					    Cabal -> do
 | 
				
			||||||
      lSet <- fmap (== v) $ cabalSet
 | 
					      lSet <- fmap (== v) $ cabalSet
 | 
				
			||||||
      let lInstalled = lSet
 | 
					      let lInstalled = lSet
 | 
				
			||||||
      pure ListResult { lVer    = v
 | 
					      pure ListResult { lVer    = v
 | 
				
			||||||
 | 
					                      , lCross  = Nothing
 | 
				
			||||||
                      , lTag    = tags
 | 
					                      , lTag    = tags
 | 
				
			||||||
                      , lTool   = t
 | 
					                      , lTool   = t
 | 
				
			||||||
                      , fromSrc = False
 | 
					                      , fromSrc = False
 | 
				
			||||||
@ -382,6 +401,7 @@ listVersions av lt criteria = case lt of
 | 
				
			|||||||
      let lInstalled = lSet
 | 
					      let lInstalled = lSet
 | 
				
			||||||
      pure ListResult { lVer    = v
 | 
					      pure ListResult { lVer    = v
 | 
				
			||||||
                      , lTag    = tags
 | 
					                      , lTag    = tags
 | 
				
			||||||
 | 
					                      , lCross  = Nothing
 | 
				
			||||||
                      , lTool   = t
 | 
					                      , lTool   = t
 | 
				
			||||||
                      , fromSrc = False
 | 
					                      , fromSrc = False
 | 
				
			||||||
                      , lStray  = False
 | 
					                      , lStray  = False
 | 
				
			||||||
@ -404,10 +424,10 @@ listVersions av lt criteria = case lt of
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
-- | This function may throw and crash in various ways.
 | 
					-- | This function may throw and crash in various ways.
 | 
				
			||||||
rmGHCVer :: (MonadThrow m, MonadLogger m, MonadIO m, MonadFail m)
 | 
					rmGHCVer :: (MonadThrow m, MonadLogger m, MonadIO m, MonadFail m)
 | 
				
			||||||
         => Version
 | 
					         => GHCTargetVersion
 | 
				
			||||||
         -> Excepts '[NotInstalled] m ()
 | 
					         -> Excepts '[NotInstalled] m ()
 | 
				
			||||||
rmGHCVer ver = do
 | 
					rmGHCVer ver = do
 | 
				
			||||||
  isSetGHC <- fmap (maybe False (== ver)) $ ghcSet
 | 
					  isSetGHC <- fmap (maybe False (== ver)) $ ghcSet (_tvTarget ver)
 | 
				
			||||||
  dir      <- liftIO $ ghcupGHCDir ver
 | 
					  dir      <- liftIO $ ghcupGHCDir ver
 | 
				
			||||||
  let d' = toFilePath dir
 | 
					  let d' = toFilePath dir
 | 
				
			||||||
  exists <- liftIO $ doesDirectoryExist dir
 | 
					  exists <- liftIO $ doesDirectoryExist dir
 | 
				
			||||||
@ -418,7 +438,7 @@ rmGHCVer ver = do
 | 
				
			|||||||
      -- this isn't atomic, order matters
 | 
					      -- this isn't atomic, order matters
 | 
				
			||||||
      when isSetGHC $ do
 | 
					      when isSetGHC $ do
 | 
				
			||||||
        lift $ $(logInfo) [i|Removing ghc symlinks|]
 | 
					        lift $ $(logInfo) [i|Removing ghc symlinks|]
 | 
				
			||||||
        liftE $ rmPlain ver
 | 
					        liftE $ rmPlain (_tvTarget ver)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
      lift $ $(logInfo) [i|Removing directory recursively: #{d'}|]
 | 
					      lift $ $(logInfo) [i|Removing directory recursively: #{d'}|]
 | 
				
			||||||
      liftIO $ deleteDirRecursive dir
 | 
					      liftIO $ deleteDirRecursive dir
 | 
				
			||||||
@ -430,15 +450,15 @@ rmGHCVer ver = do
 | 
				
			|||||||
      -- first remove
 | 
					      -- first remove
 | 
				
			||||||
      lift $ rmMajorSymlinks ver
 | 
					      lift $ rmMajorSymlinks ver
 | 
				
			||||||
      -- then fix them (e.g. with an earlier version)
 | 
					      -- then fix them (e.g. with an earlier version)
 | 
				
			||||||
      (mj, mi) <- getGHCMajor ver
 | 
					      (mj, mi) <- getMajorMinorV (_tvVersion ver)
 | 
				
			||||||
      getGHCForMajor mj mi >>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
 | 
					      getGHCForMajor mj mi (_tvTarget ver) >>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
      liftIO
 | 
					      liftIO
 | 
				
			||||||
        $   ghcupBaseDir
 | 
					        $   ghcupBaseDir
 | 
				
			||||||
        >>= hideError doesNotExistErrorType
 | 
					        >>= hideError doesNotExistErrorType
 | 
				
			||||||
        .   deleteFile
 | 
					        .   deleteFile
 | 
				
			||||||
        .   (</> [rel|share|])
 | 
					        .   (</> [rel|share|])
 | 
				
			||||||
    else throwE (NotInstalled GHC ver)
 | 
					    else throwE (NotInstalled GHC (ver ^. tvVersion % to prettyVer))
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -479,11 +499,12 @@ compileGHC :: ( MonadMask m
 | 
				
			|||||||
              , MonadFail m
 | 
					              , MonadFail m
 | 
				
			||||||
              )
 | 
					              )
 | 
				
			||||||
           => GHCupDownloads
 | 
					           => GHCupDownloads
 | 
				
			||||||
           -> Version                    -- ^ version to install
 | 
					           -> GHCTargetVersion           -- ^ version to install
 | 
				
			||||||
           -> Either Version (Path Abs)  -- ^ version to bootstrap with
 | 
					           -> Either Version (Path Abs)  -- ^ version to bootstrap with
 | 
				
			||||||
           -> Maybe Int                  -- ^ jobs
 | 
					           -> Maybe Int                  -- ^ jobs
 | 
				
			||||||
           -> Maybe (Path Abs)           -- ^ build config
 | 
					           -> Maybe (Path Abs)           -- ^ build config
 | 
				
			||||||
           -> Maybe (Path Abs)
 | 
					           -> Maybe (Path Abs)           -- ^ patch directory
 | 
				
			||||||
 | 
					           -> [Text]                     -- ^ additional args to ./configure
 | 
				
			||||||
           -> Excepts
 | 
					           -> Excepts
 | 
				
			||||||
                '[ AlreadyInstalled
 | 
					                '[ AlreadyInstalled
 | 
				
			||||||
                 , BuildFailed
 | 
					                 , BuildFailed
 | 
				
			||||||
@ -500,13 +521,15 @@ compileGHC :: ( MonadMask m
 | 
				
			|||||||
                 ]
 | 
					                 ]
 | 
				
			||||||
                m
 | 
					                m
 | 
				
			||||||
                ()
 | 
					                ()
 | 
				
			||||||
compileGHC dls tver bstrap jobs mbuildConfig patchdir = do
 | 
					compileGHC dls tver bstrap jobs mbuildConfig patchdir aargs = do
 | 
				
			||||||
  lift $ $(logDebug) [i|Requested to compile: #{tver} with #{bstrap}|]
 | 
					  lift $ $(logDebug) [i|Requested to compile: #{tver} with #{bstrap}|]
 | 
				
			||||||
  whenM (liftIO $ toolAlreadyInstalled GHC tver)
 | 
					  whenM (liftIO $ ghcInstalled tver)
 | 
				
			||||||
        (throwE $ AlreadyInstalled GHC tver)
 | 
					        (throwE $ AlreadyInstalled GHC (tver ^. tvVersion))
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  -- download source tarball
 | 
					  -- download source tarball
 | 
				
			||||||
  dlInfo    <- preview (ix GHC % ix tver % viSourceDL % _Just) dls ?? NoDownload
 | 
					  dlInfo <-
 | 
				
			||||||
 | 
					    preview (ix GHC % ix (tver ^. tvVersion) % viSourceDL % _Just) dls
 | 
				
			||||||
 | 
					      ?? NoDownload
 | 
				
			||||||
  dl        <- liftE $ downloadCached dlInfo Nothing
 | 
					  dl        <- liftE $ downloadCached dlInfo Nothing
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  -- unpack
 | 
					  -- unpack
 | 
				
			||||||
@ -530,13 +553,20 @@ compileGHC dls tver bstrap jobs mbuildConfig patchdir = do
 | 
				
			|||||||
  pure ()
 | 
					  pure ()
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 where
 | 
					 where
 | 
				
			||||||
  defaultConf = [s|
 | 
					  defaultConf = case _tvTarget tver of
 | 
				
			||||||
 | 
					                  Nothing -> [s|
 | 
				
			||||||
V=0
 | 
					V=0
 | 
				
			||||||
BUILD_MAN = NO
 | 
					BUILD_MAN = NO
 | 
				
			||||||
BUILD_SPHINX_HTML = NO
 | 
					BUILD_SPHINX_HTML = NO
 | 
				
			||||||
BUILD_SPHINX_PDF = NO
 | 
					BUILD_SPHINX_PDF = NO
 | 
				
			||||||
HADDOCK_DOCS = YES
 | 
					HADDOCK_DOCS = YES|]
 | 
				
			||||||
GhcWithLlvmCodeGen = YES|]
 | 
					                  Just _ -> [s|
 | 
				
			||||||
 | 
					V=0
 | 
				
			||||||
 | 
					BUILD_MAN = NO
 | 
				
			||||||
 | 
					BUILD_SPHINX_HTML = NO
 | 
				
			||||||
 | 
					BUILD_SPHINX_PDF = NO
 | 
				
			||||||
 | 
					HADDOCK_DOCS = NO
 | 
				
			||||||
 | 
					Stage1Only = YES|]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  compile :: (MonadCatch m, MonadLogger m, MonadIO m)
 | 
					  compile :: (MonadCatch m, MonadLogger m, MonadIO m)
 | 
				
			||||||
          => Either (Path Rel) (Path Abs)
 | 
					          => Either (Path Rel) (Path Abs)
 | 
				
			||||||
@ -544,6 +574,7 @@ GhcWithLlvmCodeGen = YES|]
 | 
				
			|||||||
          -> Path Abs
 | 
					          -> Path Abs
 | 
				
			||||||
          -> Excepts
 | 
					          -> Excepts
 | 
				
			||||||
               '[ FileDoesNotExistError
 | 
					               '[ FileDoesNotExistError
 | 
				
			||||||
 | 
					                , InvalidBuildConfig
 | 
				
			||||||
                , PatchFailed
 | 
					                , PatchFailed
 | 
				
			||||||
                , ProcessError
 | 
					                , ProcessError
 | 
				
			||||||
                , NotFoundInPATH
 | 
					                , NotFoundInPATH
 | 
				
			||||||
@ -552,14 +583,14 @@ GhcWithLlvmCodeGen = YES|]
 | 
				
			|||||||
               ()
 | 
					               ()
 | 
				
			||||||
  compile bghc ghcdir workdir = do
 | 
					  compile bghc ghcdir workdir = do
 | 
				
			||||||
    lift $ $(logInfo) [i|configuring build|]
 | 
					    lift $ $(logInfo) [i|configuring build|]
 | 
				
			||||||
 | 
					    liftE $ checkBuildConfig
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    forM_ patchdir $ \dir -> liftE $ applyPatches dir workdir
 | 
					    forM_ patchdir $ \dir -> liftE $ applyPatches dir workdir
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    -- force ld.bfd for build (others seem to misbehave, like lld from FreeBSD)
 | 
					    cEnv <- liftIO $ getEnvironment
 | 
				
			||||||
    newEnv <- addToCurrentEnv [("LD", "ld.bfd")]
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
    if
 | 
					    if
 | 
				
			||||||
      | tver >= [vver|8.8.0|] -> do
 | 
					      | (_tvVersion tver) >= [vver|8.8.0|] -> do
 | 
				
			||||||
        bghcPath <- case bghc of
 | 
					        bghcPath <- case bghc of
 | 
				
			||||||
          Right ghc' -> pure ghc'
 | 
					          Right ghc' -> pure ghc'
 | 
				
			||||||
          Left  bver -> do
 | 
					          Left  bver -> do
 | 
				
			||||||
@ -568,20 +599,32 @@ GhcWithLlvmCodeGen = YES|]
 | 
				
			|||||||
        lEM $ liftIO $ execLogged
 | 
					        lEM $ liftIO $ execLogged
 | 
				
			||||||
          "./configure"
 | 
					          "./configure"
 | 
				
			||||||
          False
 | 
					          False
 | 
				
			||||||
          ["--prefix=" <> toFilePath ghcdir]
 | 
					          (  ["--prefix=" <> toFilePath ghcdir]
 | 
				
			||||||
 | 
					          ++ (maybe mempty
 | 
				
			||||||
 | 
					                    (\x -> ["--target=" <> E.encodeUtf8 x])
 | 
				
			||||||
 | 
					                    (_tvTarget tver)
 | 
				
			||||||
 | 
					             )
 | 
				
			||||||
 | 
					          ++ fmap E.encodeUtf8 aargs
 | 
				
			||||||
 | 
					          )
 | 
				
			||||||
          [rel|ghc-conf|]
 | 
					          [rel|ghc-conf|]
 | 
				
			||||||
          (Just workdir)
 | 
					          (Just workdir)
 | 
				
			||||||
          (Just (("GHC", toFilePath bghcPath) : newEnv))
 | 
					          (Just (("GHC", toFilePath bghcPath) : cEnv))
 | 
				
			||||||
      | otherwise -> do
 | 
					      | otherwise -> do
 | 
				
			||||||
        lEM $ liftIO $ execLogged
 | 
					        lEM $ liftIO $ execLogged
 | 
				
			||||||
          "./configure"
 | 
					          "./configure"
 | 
				
			||||||
          False
 | 
					          False
 | 
				
			||||||
          [ "--prefix=" <> toFilePath ghcdir
 | 
					          (  [ "--prefix=" <> toFilePath ghcdir
 | 
				
			||||||
          , "--with-ghc=" <> either toFilePath toFilePath bghc
 | 
					             , "--with-ghc=" <> either toFilePath toFilePath bghc
 | 
				
			||||||
          ]
 | 
					             ]
 | 
				
			||||||
 | 
					          ++ (maybe mempty
 | 
				
			||||||
 | 
					                    (\x -> ["--target=" <> E.encodeUtf8 x])
 | 
				
			||||||
 | 
					                    (_tvTarget tver)
 | 
				
			||||||
 | 
					             )
 | 
				
			||||||
 | 
					          ++ fmap E.encodeUtf8 aargs
 | 
				
			||||||
 | 
					          )
 | 
				
			||||||
          [rel|ghc-conf|]
 | 
					          [rel|ghc-conf|]
 | 
				
			||||||
          (Just workdir)
 | 
					          (Just workdir)
 | 
				
			||||||
          (Just newEnv)
 | 
					          (Just cEnv)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    case mbuildConfig of
 | 
					    case mbuildConfig of
 | 
				
			||||||
      Just bc -> liftIOException
 | 
					      Just bc -> liftIOException
 | 
				
			||||||
@ -604,6 +647,30 @@ GhcWithLlvmCodeGen = YES|]
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
  build_mk workdir = workdir </> [rel|mk/build.mk|]
 | 
					  build_mk workdir = workdir </> [rel|mk/build.mk|]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  checkBuildConfig :: (MonadCatch m, MonadIO m)
 | 
				
			||||||
 | 
					                   => Excepts
 | 
				
			||||||
 | 
					                        '[FileDoesNotExistError , InvalidBuildConfig]
 | 
				
			||||||
 | 
					                        m
 | 
				
			||||||
 | 
					                        ()
 | 
				
			||||||
 | 
					  checkBuildConfig = do
 | 
				
			||||||
 | 
					    c <- case mbuildConfig of
 | 
				
			||||||
 | 
					      Just bc -> do
 | 
				
			||||||
 | 
					        BL.toStrict <$> liftIOException doesNotExistErrorType
 | 
				
			||||||
 | 
					                                        (FileDoesNotExistError $ toFilePath bc)
 | 
				
			||||||
 | 
					                                        (liftIO $ readFile bc)
 | 
				
			||||||
 | 
					      Nothing -> pure defaultConf
 | 
				
			||||||
 | 
					    let lines' = fmap T.strip . T.lines $ decUTF8Safe c
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					   -- for cross, we need Stage1Only
 | 
				
			||||||
 | 
					    case _tvTarget tver of
 | 
				
			||||||
 | 
					      Just _ -> when (not $ elem "Stage1Only = YES" lines') $ throwE
 | 
				
			||||||
 | 
					        (InvalidBuildConfig
 | 
				
			||||||
 | 
					          [s|Cross compiling needs to be a Stage1 build, add "Stage1Only = YES" to your config!|]
 | 
				
			||||||
 | 
					        )
 | 
				
			||||||
 | 
					      Nothing -> pure ()
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
compileCabal :: ( MonadReader Settings m
 | 
					compileCabal :: ( MonadReader Settings m
 | 
				
			||||||
                , MonadResource m
 | 
					                , MonadResource m
 | 
				
			||||||
@ -763,12 +830,12 @@ upgradeGHCup dls mtarget force = do
 | 
				
			|||||||
-- | Creates ghc-x.y.z and ghc-x.y symlinks. This is used for
 | 
					-- | Creates ghc-x.y.z and ghc-x.y symlinks. This is used for
 | 
				
			||||||
-- both installing from source and bindist.
 | 
					-- both installing from source and bindist.
 | 
				
			||||||
postGHCInstall :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
 | 
					postGHCInstall :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
 | 
				
			||||||
               => Version
 | 
					               => GHCTargetVersion
 | 
				
			||||||
               -> Excepts '[NotInstalled] m ()
 | 
					               -> Excepts '[NotInstalled] m ()
 | 
				
			||||||
postGHCInstall ver = do
 | 
					postGHCInstall ver@GHCTargetVersion{..} = do
 | 
				
			||||||
  void $ liftE $ setGHC ver SetGHC_XYZ
 | 
					  void $ liftE $ setGHC ver SetGHC_XYZ
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  -- Create ghc-x.y symlinks. This may not be the current
 | 
					  -- Create ghc-x.y symlinks. This may not be the current
 | 
				
			||||||
  -- version, create it regardless.
 | 
					  -- version, create it regardless.
 | 
				
			||||||
  (mj, mi) <- liftIO $ getGHCMajor ver
 | 
					  (mj, mi) <- getMajorMinorV _tvVersion
 | 
				
			||||||
  getGHCForMajor mj mi >>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
 | 
					  getGHCForMajor mj mi _tvTarget >>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
 | 
				
			||||||
 | 
				
			|||||||
@ -64,7 +64,7 @@ data AlreadyInstalled = AlreadyInstalled Tool Version
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
-- | The tool is not installed. Some operations rely on a tool
 | 
					-- | The tool is not installed. Some operations rely on a tool
 | 
				
			||||||
-- to be installed (such as setting the current GHC version).
 | 
					-- to be installed (such as setting the current GHC version).
 | 
				
			||||||
data NotInstalled = NotInstalled Tool Version
 | 
					data NotInstalled = NotInstalled Tool Text
 | 
				
			||||||
  deriving Show
 | 
					  deriving Show
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | An executable was expected to be in PATH, but was not found.
 | 
					-- | An executable was expected to be in PATH, but was not found.
 | 
				
			||||||
@ -104,6 +104,9 @@ data PatchFailed = PatchFailed
 | 
				
			|||||||
data NoToolRequirements = NoToolRequirements
 | 
					data NoToolRequirements = NoToolRequirements
 | 
				
			||||||
  deriving Show
 | 
					  deriving Show
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					data InvalidBuildConfig = InvalidBuildConfig Text
 | 
				
			||||||
 | 
					  deriving Show
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
    -------------------------
 | 
					    -------------------------
 | 
				
			||||||
    --[ High-level errors ]--
 | 
					    --[ High-level errors ]--
 | 
				
			||||||
 | 
				
			|||||||
@ -1,5 +1,6 @@
 | 
				
			|||||||
{-# LANGUAGE CPP           #-}
 | 
					{-# LANGUAGE CPP               #-}
 | 
				
			||||||
{-# LANGUAGE DeriveGeneric #-}
 | 
					{-# LANGUAGE DeriveGeneric     #-}
 | 
				
			||||||
 | 
					{-# LANGUAGE OverloadedStrings #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
module GHCup.Types where
 | 
					module GHCup.Types where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -190,3 +191,23 @@ data PlatformRequest = PlatformRequest
 | 
				
			|||||||
  , _rVersion  :: Maybe Versioning
 | 
					  , _rVersion  :: Maybe Versioning
 | 
				
			||||||
  }
 | 
					  }
 | 
				
			||||||
  deriving (Eq, Show)
 | 
					  deriving (Eq, Show)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | A GHC identified by the target platform triple
 | 
				
			||||||
 | 
					-- and the version.
 | 
				
			||||||
 | 
					data GHCTargetVersion = GHCTargetVersion
 | 
				
			||||||
 | 
					  { _tvTarget  :: Maybe Text
 | 
				
			||||||
 | 
					  , _tvVersion :: Version
 | 
				
			||||||
 | 
					  }
 | 
				
			||||||
 | 
					  deriving (Ord, Eq, Show)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					mkTVer :: Version -> GHCTargetVersion
 | 
				
			||||||
 | 
					mkTVer = GHCTargetVersion Nothing
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Assembles a path of the form: <target-triple>-<version>
 | 
				
			||||||
 | 
					prettyTVer :: GHCTargetVersion -> Text
 | 
				
			||||||
 | 
					prettyTVer (GHCTargetVersion (Just t) v') = t <> "-" <> prettyVer v'
 | 
				
			||||||
 | 
					prettyTVer (GHCTargetVersion Nothing  v') = prettyVer v'
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
				
			|||||||
@ -42,18 +42,18 @@ deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''GHCupI
 | 
				
			|||||||
deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''Requirements
 | 
					deriveJSON defaultOptions { fieldLabelModifier = removeLensFieldLabel } ''Requirements
 | 
				
			||||||
 | 
					
 | 
				
			||||||
instance ToJSON Tag where
 | 
					instance ToJSON Tag where
 | 
				
			||||||
  toJSON Latest = String "Latest"
 | 
					  toJSON Latest             = String "Latest"
 | 
				
			||||||
  toJSON Recommended = String "Recommended"
 | 
					  toJSON Recommended        = String "Recommended"
 | 
				
			||||||
  toJSON (Base pvp'') = String ("base-" <> prettyPVP pvp'')
 | 
					  toJSON (Base       pvp'') = String ("base-" <> prettyPVP pvp'')
 | 
				
			||||||
  toJSON (UnknownTag x) = String (T.pack x)
 | 
					  toJSON (UnknownTag x    ) = String (T.pack x)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
instance FromJSON Tag where
 | 
					instance FromJSON Tag where
 | 
				
			||||||
  parseJSON = withText "Tag" $ \t -> case T.unpack t of
 | 
					  parseJSON = withText "Tag" $ \t -> case T.unpack t of
 | 
				
			||||||
    "Latest" -> pure Latest
 | 
					    "Latest"                             -> pure Latest
 | 
				
			||||||
    "Recommended" -> pure Recommended
 | 
					    "Recommended"                        -> pure Recommended
 | 
				
			||||||
    ('b':'a':'s':'e':'-':ver') -> case pvp (T.pack ver') of
 | 
					    ('b' : 'a' : 's' : 'e' : '-' : ver') -> case pvp (T.pack ver') of
 | 
				
			||||||
                                    Right x -> pure $ Base x
 | 
					      Right x -> pure $ Base x
 | 
				
			||||||
                                    Left e -> fail . show $ e
 | 
					      Left  e -> fail . show $ e
 | 
				
			||||||
    x -> pure (UnknownTag x)
 | 
					    x -> pure (UnknownTag x)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
instance ToJSON URI where
 | 
					instance ToJSON URI where
 | 
				
			||||||
 | 
				
			|||||||
@ -19,6 +19,8 @@ makeLenses ''DownloadInfo
 | 
				
			|||||||
makeLenses ''Tag
 | 
					makeLenses ''Tag
 | 
				
			||||||
makeLenses ''VersionInfo
 | 
					makeLenses ''VersionInfo
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					makeLenses ''GHCTargetVersion
 | 
				
			||||||
 | 
					
 | 
				
			||||||
makeLenses ''GHCupInfo
 | 
					makeLenses ''GHCupInfo
 | 
				
			||||||
 | 
					
 | 
				
			||||||
uriSchemeL' :: Lens' (URIRef Absolute) Scheme
 | 
					uriSchemeL' :: Lens' (URIRef Absolute) Scheme
 | 
				
			||||||
 | 
				
			|||||||
@ -4,6 +4,7 @@
 | 
				
			|||||||
{-# LANGUAGE OverloadedStrings     #-}
 | 
					{-# LANGUAGE OverloadedStrings     #-}
 | 
				
			||||||
{-# LANGUAGE QuasiQuotes           #-}
 | 
					{-# LANGUAGE QuasiQuotes           #-}
 | 
				
			||||||
{-# LANGUAGE TemplateHaskell       #-}
 | 
					{-# LANGUAGE TemplateHaskell       #-}
 | 
				
			||||||
 | 
					{-# LANGUAGE ViewPatterns          #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
module GHCup.Utils
 | 
					module GHCup.Utils
 | 
				
			||||||
@ -19,7 +20,9 @@ import           GHCup.Types.Optics
 | 
				
			|||||||
import           GHCup.Types.JSON               ( )
 | 
					import           GHCup.Types.JSON               ( )
 | 
				
			||||||
import           GHCup.Utils.Dirs
 | 
					import           GHCup.Utils.Dirs
 | 
				
			||||||
import           GHCup.Utils.File
 | 
					import           GHCup.Utils.File
 | 
				
			||||||
 | 
					import           GHCup.Utils.MegaParsec
 | 
				
			||||||
import           GHCup.Utils.Prelude
 | 
					import           GHCup.Utils.Prelude
 | 
				
			||||||
 | 
					import           GHCup.Utils.String.QQ
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import           Control.Applicative
 | 
					import           Control.Applicative
 | 
				
			||||||
import           Control.Exception.Safe
 | 
					import           Control.Exception.Safe
 | 
				
			||||||
@ -29,11 +32,12 @@ import           Control.Monad.Fail             ( MonadFail )
 | 
				
			|||||||
#endif
 | 
					#endif
 | 
				
			||||||
import           Control.Monad.Logger
 | 
					import           Control.Monad.Logger
 | 
				
			||||||
import           Control.Monad.Reader
 | 
					import           Control.Monad.Reader
 | 
				
			||||||
import           Data.Attoparsec.ByteString
 | 
					 | 
				
			||||||
import           Data.ByteString                ( ByteString )
 | 
					import           Data.ByteString                ( ByteString )
 | 
				
			||||||
 | 
					import           Data.Either
 | 
				
			||||||
import           Data.List
 | 
					import           Data.List
 | 
				
			||||||
import           Data.Maybe
 | 
					import           Data.Maybe
 | 
				
			||||||
import           Data.String.Interpolate
 | 
					import           Data.String.Interpolate
 | 
				
			||||||
 | 
					import           Data.Text                      ( Text )
 | 
				
			||||||
import           Data.Versions
 | 
					import           Data.Versions
 | 
				
			||||||
import           Data.Word8
 | 
					import           Data.Word8
 | 
				
			||||||
import           GHC.IO.Exception
 | 
					import           GHC.IO.Exception
 | 
				
			||||||
@ -51,6 +55,7 @@ import           System.Posix.FilePath          ( getSearchPath
 | 
				
			|||||||
                                                , takeFileName
 | 
					                                                , takeFileName
 | 
				
			||||||
                                                )
 | 
					                                                )
 | 
				
			||||||
import           System.Posix.Files.ByteString  ( readSymbolicLink )
 | 
					import           System.Posix.Files.ByteString  ( readSymbolicLink )
 | 
				
			||||||
 | 
					import           Text.Regex.Posix
 | 
				
			||||||
import           URI.ByteString
 | 
					import           URI.ByteString
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import qualified Codec.Archive.Tar             as Tar
 | 
					import qualified Codec.Archive.Tar             as Tar
 | 
				
			||||||
@ -60,7 +65,7 @@ import qualified Codec.Compression.Lzma        as Lzma
 | 
				
			|||||||
import qualified Data.ByteString               as B
 | 
					import qualified Data.ByteString               as B
 | 
				
			||||||
import qualified Data.Map.Strict               as Map
 | 
					import qualified Data.Map.Strict               as Map
 | 
				
			||||||
import qualified Data.Text.Encoding            as E
 | 
					import qualified Data.Text.Encoding            as E
 | 
				
			||||||
 | 
					import qualified Text.Megaparsec               as MP
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -73,64 +78,69 @@ import qualified Data.Text.Encoding            as E
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
-- | The symlink destination of a ghc tool.
 | 
					-- | The symlink destination of a ghc tool.
 | 
				
			||||||
ghcLinkDestination :: ByteString -- ^ the tool, such as 'ghc', 'haddock' etc.
 | 
					ghcLinkDestination :: ByteString -- ^ the tool, such as 'ghc', 'haddock' etc.
 | 
				
			||||||
                   -> Version
 | 
					                   -> GHCTargetVersion
 | 
				
			||||||
                   -> ByteString
 | 
					                   -> ByteString
 | 
				
			||||||
ghcLinkDestination tool ver = "../ghc/" <> verToBS ver <> "/bin/" <> tool
 | 
					ghcLinkDestination tool ver =
 | 
				
			||||||
 | 
					  "../ghc/" <> E.encodeUtf8 (prettyTVer ver) <> "/bin/" <> tool
 | 
				
			||||||
 | 
					 | 
				
			||||||
-- | Extract the version part of the result of `ghcLinkDestination`.
 | 
					 | 
				
			||||||
ghcLinkVersion :: MonadThrow m => ByteString -> m Version
 | 
					 | 
				
			||||||
ghcLinkVersion = either (throwM . ParseError) pure . parseOnly parser
 | 
					 | 
				
			||||||
 where
 | 
					 | 
				
			||||||
  parser    = string "../ghc/" *> verParser <* string "/bin/ghc"
 | 
					 | 
				
			||||||
  verParser = many1' (notWord8 _slash) >>= \t ->
 | 
					 | 
				
			||||||
    case
 | 
					 | 
				
			||||||
        version (decUTF8Safe $ B.pack t)
 | 
					 | 
				
			||||||
      of
 | 
					 | 
				
			||||||
        Left  e -> fail $ show e
 | 
					 | 
				
			||||||
        Right r -> pure r
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- e.g. ghc-8.6.5
 | 
					-- e.g. ghc-8.6.5
 | 
				
			||||||
rmMinorSymlinks :: (MonadIO m, MonadLogger m) => Version -> m ()
 | 
					rmMinorSymlinks :: (MonadIO m, MonadLogger m) => GHCTargetVersion -> m ()
 | 
				
			||||||
rmMinorSymlinks ver = do
 | 
					rmMinorSymlinks GHCTargetVersion {..} = do
 | 
				
			||||||
  bindir <- liftIO $ ghcupBinDir
 | 
					  bindir <- liftIO $ ghcupBinDir
 | 
				
			||||||
  files  <- liftIO $ getDirsFiles' bindir
 | 
					
 | 
				
			||||||
  let myfiles =
 | 
					  files  <- liftIO $ findFiles'
 | 
				
			||||||
        filter (\x -> ("-" <> verToBS ver) `B.isSuffixOf` toFilePath x) files
 | 
					    bindir
 | 
				
			||||||
  forM_ myfiles $ \f -> do
 | 
					    (  maybe mempty (\x -> MP.chunk (x <> "-")) _tvTarget
 | 
				
			||||||
 | 
					    *> parseUntil1 (MP.chunk $ prettyVer _tvVersion)
 | 
				
			||||||
 | 
					    *> (MP.chunk $ prettyVer _tvVersion)
 | 
				
			||||||
 | 
					    *> MP.eof
 | 
				
			||||||
 | 
					    )
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  forM_ files $ \f -> do
 | 
				
			||||||
    let fullF = (bindir </> f)
 | 
					    let fullF = (bindir </> f)
 | 
				
			||||||
    $(logDebug) [i|rm -f #{toFilePath fullF}|]
 | 
					    $(logDebug) [i|rm -f #{toFilePath fullF}|]
 | 
				
			||||||
    liftIO $ hideError doesNotExistErrorType $ deleteFile fullF
 | 
					    liftIO $ hideError doesNotExistErrorType $ deleteFile fullF
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- E.g. ghc, if this version is the set one.
 | 
					
 | 
				
			||||||
-- This reads `ghcupGHCDir`.
 | 
					-- Removes the set ghc version for the given target, if any.
 | 
				
			||||||
rmPlain :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
 | 
					rmPlain :: (MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
 | 
				
			||||||
        => Version
 | 
					  => Maybe Text -- ^ target
 | 
				
			||||||
        -> Excepts '[NotInstalled] m ()
 | 
					        -> Excepts '[NotInstalled] m ()
 | 
				
			||||||
rmPlain ver = do
 | 
					rmPlain target = do
 | 
				
			||||||
  files  <- liftE $ ghcToolFiles ver
 | 
					  mtv <- ghcSet target
 | 
				
			||||||
  bindir <- liftIO $ ghcupBinDir
 | 
					  forM_ mtv $ \tv -> do
 | 
				
			||||||
  forM_ files $ \f -> do
 | 
					    files  <- liftE $ ghcToolFiles tv
 | 
				
			||||||
    let fullF = (bindir </> f)
 | 
					    bindir <- liftIO $ ghcupBinDir
 | 
				
			||||||
    lift $ $(logDebug) [i|rm -f #{toFilePath fullF}|]
 | 
					    forM_ files $ \f -> do
 | 
				
			||||||
    liftIO $ hideError doesNotExistErrorType $ deleteFile fullF
 | 
					      let fullF = (bindir </> f)
 | 
				
			||||||
  -- old ghcup
 | 
					      lift $ $(logDebug) [i|rm -f #{toFilePath fullF}|]
 | 
				
			||||||
  let hdc_file = (bindir </> [rel|haddock-ghc|])
 | 
					      liftIO $ hideError doesNotExistErrorType $ deleteFile fullF
 | 
				
			||||||
  lift $ $(logDebug) [i|rm -f #{toFilePath hdc_file}|]
 | 
					    -- old ghcup
 | 
				
			||||||
  liftIO $ hideError doesNotExistErrorType $ deleteFile hdc_file
 | 
					    let hdc_file = (bindir </> [rel|haddock-ghc|])
 | 
				
			||||||
 | 
					    lift $ $(logDebug) [i|rm -f #{toFilePath hdc_file}|]
 | 
				
			||||||
 | 
					    liftIO $ hideError doesNotExistErrorType $ deleteFile hdc_file
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- e.g. ghc-8.6
 | 
					-- e.g. ghc-8.6
 | 
				
			||||||
rmMajorSymlinks :: (MonadLogger m, MonadIO m) => Version -> m ()
 | 
					rmMajorSymlinks :: (MonadThrow m, MonadLogger m, MonadIO m)
 | 
				
			||||||
rmMajorSymlinks ver = do
 | 
					                => GHCTargetVersion
 | 
				
			||||||
  (mj, mi) <- liftIO $ getGHCMajor ver
 | 
					                -> m ()
 | 
				
			||||||
  let v' = E.encodeUtf8 $ intToText mj <> "." <> intToText mi
 | 
					rmMajorSymlinks GHCTargetVersion {..} = do
 | 
				
			||||||
 | 
					  (mj, mi) <- getMajorMinorV _tvVersion
 | 
				
			||||||
 | 
					  let v' = intToText mj <> "." <> intToText mi
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  bindir <- liftIO ghcupBinDir
 | 
					  bindir <- liftIO ghcupBinDir
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  files  <- liftIO $ getDirsFiles' bindir
 | 
					  files  <- liftIO $ findFiles'
 | 
				
			||||||
  let myfiles = filter (\x -> ("-" <> v') `B.isSuffixOf` toFilePath x) files
 | 
					    bindir
 | 
				
			||||||
  forM_ myfiles $ \f -> do
 | 
					    (  maybe mempty (\x -> MP.chunk (x <> "-")) _tvTarget
 | 
				
			||||||
 | 
					    *> parseUntil1 (MP.chunk v')
 | 
				
			||||||
 | 
					    *> MP.chunk v'
 | 
				
			||||||
 | 
					    *> MP.eof
 | 
				
			||||||
 | 
					    )
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  forM_ files $ \f -> do
 | 
				
			||||||
    let fullF = (bindir </> f)
 | 
					    let fullF = (bindir </> f)
 | 
				
			||||||
    $(logDebug) [i|rm -f #{toFilePath fullF}|]
 | 
					    $(logDebug) [i|rm -f #{toFilePath fullF}|]
 | 
				
			||||||
    liftIO $ hideError doesNotExistErrorType $ deleteFile fullF
 | 
					    liftIO $ hideError doesNotExistErrorType $ deleteFile fullF
 | 
				
			||||||
@ -143,33 +153,61 @@ rmMajorSymlinks ver = do
 | 
				
			|||||||
    -----------------------------------
 | 
					    -----------------------------------
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
toolAlreadyInstalled :: Tool -> Version -> IO Bool
 | 
					ghcInstalled :: GHCTargetVersion -> IO Bool
 | 
				
			||||||
toolAlreadyInstalled tool ver = case tool of
 | 
					 | 
				
			||||||
  GHC   -> ghcInstalled ver
 | 
					 | 
				
			||||||
  Cabal -> cabalInstalled ver
 | 
					 | 
				
			||||||
  GHCup -> pure True
 | 
					 | 
				
			||||||
 | 
					 | 
				
			||||||
 | 
					 | 
				
			||||||
ghcInstalled :: Version -> IO Bool
 | 
					 | 
				
			||||||
ghcInstalled ver = do
 | 
					ghcInstalled ver = do
 | 
				
			||||||
  ghcdir <- ghcupGHCDir ver
 | 
					  ghcdir <- ghcupGHCDir ver
 | 
				
			||||||
  doesDirectoryExist ghcdir
 | 
					  doesDirectoryExist ghcdir
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
ghcSrcInstalled :: Version -> IO Bool
 | 
					ghcSrcInstalled :: GHCTargetVersion -> IO Bool
 | 
				
			||||||
ghcSrcInstalled ver = do
 | 
					ghcSrcInstalled ver = do
 | 
				
			||||||
  ghcdir <- ghcupGHCDir ver
 | 
					  ghcdir <- ghcupGHCDir ver
 | 
				
			||||||
  doesFileExist (ghcdir </> ghcUpSrcBuiltFile)
 | 
					  doesFileExist (ghcdir </> ghcUpSrcBuiltFile)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
ghcSet :: (MonadIO m) => m (Maybe Version)
 | 
					ghcSet :: (MonadThrow m, MonadIO m)
 | 
				
			||||||
ghcSet = do
 | 
					       => Maybe Text   -- ^ the target of the GHC version, if any
 | 
				
			||||||
  ghcBin <- (</> [rel|ghc|]) <$> liftIO ghcupBinDir
 | 
					                       --  (e.g. armv7-unknown-linux-gnueabihf)
 | 
				
			||||||
 | 
					       -> m (Maybe GHCTargetVersion)
 | 
				
			||||||
 | 
					ghcSet mtarget = do
 | 
				
			||||||
 | 
					  ghc    <- parseRel $ E.encodeUtf8 (maybe "ghc" (<> "-ghc") mtarget)
 | 
				
			||||||
 | 
					  ghcBin <- (</> ghc) <$> liftIO ghcupBinDir
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  -- link destination is of the form ../ghc/<ver>/bin/ghc
 | 
					  -- link destination is of the form ../ghc/<ver>/bin/ghc
 | 
				
			||||||
 | 
					  -- for old ghcup, it is ../ghc/<ver>/bin/ghc-<ver>
 | 
				
			||||||
  liftIO $ handleIO' NoSuchThing (\_ -> pure $ Nothing) $ do
 | 
					  liftIO $ handleIO' NoSuchThing (\_ -> pure $ Nothing) $ do
 | 
				
			||||||
    link <- readSymbolicLink $ toFilePath ghcBin
 | 
					    link <- readSymbolicLink $ toFilePath ghcBin
 | 
				
			||||||
    Just <$> ghcLinkVersion link
 | 
					    Just <$> ghcLinkVersion link
 | 
				
			||||||
 | 
					 where
 | 
				
			||||||
 | 
					  ghcLinkVersion :: MonadThrow m => ByteString -> m GHCTargetVersion
 | 
				
			||||||
 | 
					  ghcLinkVersion bs = do
 | 
				
			||||||
 | 
					    t <- throwEither $ E.decodeUtf8' bs
 | 
				
			||||||
 | 
					    throwEither $ MP.parse parser "" t
 | 
				
			||||||
 | 
					   where
 | 
				
			||||||
 | 
					    parser =
 | 
				
			||||||
 | 
					      MP.chunk "../ghc/"
 | 
				
			||||||
 | 
					        *> (do
 | 
				
			||||||
 | 
					             r    <- parseUntil1 (MP.chunk "/")
 | 
				
			||||||
 | 
					             rest <- MP.getInput
 | 
				
			||||||
 | 
					             MP.setInput r
 | 
				
			||||||
 | 
					             x <- ghcTargetVerP
 | 
				
			||||||
 | 
					             MP.setInput rest
 | 
				
			||||||
 | 
					             pure x
 | 
				
			||||||
 | 
					           )
 | 
				
			||||||
 | 
					        <* MP.chunk "/"
 | 
				
			||||||
 | 
					        <* MP.takeRest
 | 
				
			||||||
 | 
					        <* MP.eof
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Get all installed GHCs by reading ~/.ghcup/ghc/<dir>.
 | 
				
			||||||
 | 
					-- If a dir cannot be parsed, returns left.
 | 
				
			||||||
 | 
					getInstalledGHCs :: MonadIO m => m [Either (Path Rel) GHCTargetVersion]
 | 
				
			||||||
 | 
					getInstalledGHCs = do
 | 
				
			||||||
 | 
					  ghcdir <- liftIO $ ghcupGHCBaseDir
 | 
				
			||||||
 | 
					  fs     <- liftIO $ hideErrorDef [NoSuchThing] [] $ getDirsFiles' ghcdir
 | 
				
			||||||
 | 
					  forM fs $ \f -> case parseGHCupGHCDir f of
 | 
				
			||||||
 | 
					    Right r -> pure $ Right r
 | 
				
			||||||
 | 
					    Left  _ -> pure $ Left f
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
cabalInstalled :: Version -> IO Bool
 | 
					cabalInstalled :: Version -> IO Bool
 | 
				
			||||||
@ -193,33 +231,36 @@ cabalSet = do
 | 
				
			|||||||
    -----------------------------------------
 | 
					    -----------------------------------------
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | We assume GHC is in semver format. I hope it is.
 | 
					getMajorMinorV :: MonadThrow m => Version -> m (Int, Int)
 | 
				
			||||||
getGHCMajor :: MonadThrow m => Version -> m (Int, Int)
 | 
					getMajorMinorV Version {..} = case _vChunks of
 | 
				
			||||||
getGHCMajor ver = do
 | 
					  ([Digits x] : [Digits y] : _) -> pure (fromIntegral x, fromIntegral y)
 | 
				
			||||||
  SemVer {..} <- throwEither (semver $ prettyVer ver)
 | 
					  _ -> throwM $ ParseError "Could not parse X.Y from version"
 | 
				
			||||||
  pure (fromIntegral _svMajor, fromIntegral _svMinor)
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					matchMajor :: Version -> Int -> Int -> Bool
 | 
				
			||||||
 | 
					matchMajor v' major' minor' = case getMajorMinorV v' of
 | 
				
			||||||
 | 
					  Just (x, y) -> x == major' && y == minor'
 | 
				
			||||||
 | 
					  Nothing     -> False
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Get the latest installed full GHC version that satisfies X.Y.
 | 
					-- | Get the latest installed full GHC version that satisfies X.Y.
 | 
				
			||||||
-- This reads `ghcupGHCBaseDir`.
 | 
					-- This reads `ghcupGHCBaseDir`.
 | 
				
			||||||
getGHCForMajor :: (MonadIO m, MonadThrow m)
 | 
					getGHCForMajor :: (MonadIO m, MonadThrow m)
 | 
				
			||||||
               => Int -- ^ major version component
 | 
					               => Int        -- ^ major version component
 | 
				
			||||||
               -> Int -- ^ minor version component
 | 
					               -> Int        -- ^ minor version component
 | 
				
			||||||
               -> m (Maybe Version)
 | 
					               -> Maybe Text -- ^ the target triple
 | 
				
			||||||
getGHCForMajor major' minor' = do
 | 
					               -> m (Maybe GHCTargetVersion)
 | 
				
			||||||
  p       <- liftIO $ ghcupGHCBaseDir
 | 
					getGHCForMajor major' minor' mt = do
 | 
				
			||||||
  ghcs    <- liftIO $ getDirsFiles' p
 | 
					  ghcs <- rights <$> getInstalledGHCs
 | 
				
			||||||
  semvers <- forM ghcs $ \ghc ->
 | 
					
 | 
				
			||||||
    throwEither . semver =<< (throwEither . E.decodeUtf8' . toFilePath $ ghc)
 | 
					  pure
 | 
				
			||||||
  mapM (throwEither . version)
 | 
					 | 
				
			||||||
    . fmap prettySemVer
 | 
					 | 
				
			||||||
    . lastMay
 | 
					    . lastMay
 | 
				
			||||||
    . sort
 | 
					    . sortBy (\x y -> compare (_tvVersion x) (_tvVersion y))
 | 
				
			||||||
    . filter
 | 
					    . filter
 | 
				
			||||||
        (\SemVer {..} ->
 | 
					        (\GHCTargetVersion {..} ->
 | 
				
			||||||
          fromIntegral _svMajor == major' && fromIntegral _svMinor == minor'
 | 
					          _tvTarget == mt && matchMajor _tvVersion major' minor'
 | 
				
			||||||
        )
 | 
					        )
 | 
				
			||||||
    $ semvers
 | 
					    $ ghcs
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Get the latest available ghc for X.Y major version.
 | 
					-- | Get the latest available ghc for X.Y major version.
 | 
				
			||||||
@ -228,14 +269,10 @@ getLatestGHCFor :: Int -- ^ major version component
 | 
				
			|||||||
                -> GHCupDownloads
 | 
					                -> GHCupDownloads
 | 
				
			||||||
                -> Maybe Version
 | 
					                -> Maybe Version
 | 
				
			||||||
getLatestGHCFor major' minor' dls = do
 | 
					getLatestGHCFor major' minor' dls = do
 | 
				
			||||||
  join . fmap
 | 
					  join
 | 
				
			||||||
      (lastMay . filter
 | 
					    . fmap (lastMay . filter (\v -> matchMajor v major' minor'))
 | 
				
			||||||
        (\v -> case semver $ prettyVer v of
 | 
					    . preview (ix GHC % to Map.keys)
 | 
				
			||||||
                 Right SemVer{..} -> fromIntegral _svMajor == major' && fromIntegral _svMinor == minor'
 | 
					    $ dls
 | 
				
			||||||
                 Left _ -> False
 | 
					 | 
				
			||||||
        )
 | 
					 | 
				
			||||||
      )
 | 
					 | 
				
			||||||
    . preview (ix GHC % to Map.keys) $ dls
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -282,7 +319,8 @@ unpackToDir dest av = do
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
-- | Get the tool version that has this tag. If multiple have it,
 | 
					-- | Get the tool version that has this tag. If multiple have it,
 | 
				
			||||||
-- picks the greatest version.
 | 
					-- picks the greatest version.
 | 
				
			||||||
getTagged :: Tag -> AffineFold (Map.Map Version VersionInfo) (Version, VersionInfo)
 | 
					getTagged :: Tag
 | 
				
			||||||
 | 
					          -> AffineFold (Map.Map Version VersionInfo) (Version, VersionInfo)
 | 
				
			||||||
getTagged tag =
 | 
					getTagged tag =
 | 
				
			||||||
  ( to (Map.filter (\VersionInfo {..} -> elem tag _viTags))
 | 
					  ( to (Map.filter (\VersionInfo {..} -> elem tag _viTags))
 | 
				
			||||||
  % to Map.toDescList
 | 
					  % to Map.toDescList
 | 
				
			||||||
@ -298,7 +336,8 @@ getRecommended av tool = headOf (ix tool % getTagged Recommended % to fst) $ av
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
-- | Gets the latest GHC with a given base version.
 | 
					-- | Gets the latest GHC with a given base version.
 | 
				
			||||||
getLatestBaseVersion :: GHCupDownloads -> PVP -> Maybe Version
 | 
					getLatestBaseVersion :: GHCupDownloads -> PVP -> Maybe Version
 | 
				
			||||||
getLatestBaseVersion av pvpVer = headOf (ix GHC % getTagged (Base pvpVer) % to fst) av
 | 
					getLatestBaseVersion av pvpVer =
 | 
				
			||||||
 | 
					  headOf (ix GHC % getTagged (Base pvpVer) % to fst) av
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -328,12 +367,12 @@ urlBaseName = parseRel . snd . B.breakEnd (== _slash) . urlDecode False
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- Get tool files from '~/.ghcup/bin/ghc/<ver>/bin/*'
 | 
					-- Get tool files from '~/.ghcup/bin/ghc/<ver>/bin/*'
 | 
				
			||||||
-- while ignoring *-<ver> symlinks.
 | 
					-- while ignoring *-<ver> symlinks and accounting for cross triple prefix.
 | 
				
			||||||
--
 | 
					--
 | 
				
			||||||
-- Returns unversioned relative files, e.g.:
 | 
					-- Returns unversioned relative files, e.g.:
 | 
				
			||||||
--   ["hsc2hs","haddock","hpc","runhaskell","ghc","ghc-pkg","ghci","runghc","hp2ps"]
 | 
					--   ["hsc2hs","haddock","hpc","runhaskell","ghc","ghc-pkg","ghci","runghc","hp2ps"]
 | 
				
			||||||
ghcToolFiles :: (MonadThrow m, MonadFail m, MonadIO m)
 | 
					ghcToolFiles :: (MonadThrow m, MonadFail m, MonadIO m)
 | 
				
			||||||
             => Version
 | 
					             => GHCTargetVersion
 | 
				
			||||||
             -> Excepts '[NotInstalled] m [Path Rel]
 | 
					             -> Excepts '[NotInstalled] m [Path Rel]
 | 
				
			||||||
ghcToolFiles ver = do
 | 
					ghcToolFiles ver = do
 | 
				
			||||||
  ghcdir <- liftIO $ ghcupGHCDir ver
 | 
					  ghcdir <- liftIO $ ghcupGHCDir ver
 | 
				
			||||||
@ -341,18 +380,28 @@ ghcToolFiles ver = do
 | 
				
			|||||||
 | 
					
 | 
				
			||||||
  -- fail if ghc is not installed
 | 
					  -- fail if ghc is not installed
 | 
				
			||||||
  whenM (fmap not $ liftIO $ doesDirectoryExist ghcdir)
 | 
					  whenM (fmap not $ liftIO $ doesDirectoryExist ghcdir)
 | 
				
			||||||
        (throwE (NotInstalled GHC ver))
 | 
					        (throwE (NotInstalled GHC (prettyTVer ver)))
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  files         <- liftIO $ getDirsFiles' bindir
 | 
					  files    <- liftIO $ getDirsFiles' bindir
 | 
				
			||||||
  -- figure out the <ver> suffix, because this might not be `Version` for
 | 
					  -- figure out the <ver> suffix, because this might not be `Version` for
 | 
				
			||||||
  -- alpha/rc releases, but x.y.a.somedate.
 | 
					  -- alpha/rc releases, but x.y.a.somedate.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  -- for cross, this won't be "ghc", but e.g.
 | 
				
			||||||
 | 
					  -- "armv7-unknown-linux-gnueabihf-ghc"
 | 
				
			||||||
 | 
					  [ghcbin] <- liftIO $ findFiles
 | 
				
			||||||
 | 
					    bindir
 | 
				
			||||||
 | 
					    (makeRegexOpts compExtended
 | 
				
			||||||
 | 
					                   execBlank
 | 
				
			||||||
 | 
					                   ([s|^([a-zA-Z0-9_-]*[a-zA-Z0-9_]-)?ghc$|] :: ByteString)
 | 
				
			||||||
 | 
					    )
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  (Just symver) <-
 | 
					  (Just symver) <-
 | 
				
			||||||
    (B.stripPrefix "ghc-" . takeFileName)
 | 
					    (B.stripPrefix (toFilePath ghcbin <> "-") . takeFileName)
 | 
				
			||||||
      <$> (liftIO $ readSymbolicLink $ toFilePath (bindir </> [rel|ghc|]))
 | 
					      <$> (liftIO $ readSymbolicLink $ toFilePath (bindir </> ghcbin))
 | 
				
			||||||
  when (B.null symver)
 | 
					  when (B.null symver)
 | 
				
			||||||
       (throwIO $ userError $ "Fatal: ghc symlink target is broken")
 | 
					       (throwIO $ userError $ "Fatal: ghc symlink target is broken")
 | 
				
			||||||
 | 
					
 | 
				
			||||||
  pure $ filter (\x -> not $ symver `B.isSuffixOf` toFilePath x) files
 | 
					  pure . filter (\x -> not $ symver `B.isSuffixOf` toFilePath x) $ files
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | This file, when residing in ~/.ghcup/ghc/<ver>/ signals that
 | 
					-- | This file, when residing in ~/.ghcup/ghc/<ver>/ signals that
 | 
				
			||||||
@ -403,13 +452,8 @@ darwinNotarization _ _ = pure $ Right ()
 | 
				
			|||||||
getChangeLog :: GHCupDownloads -> Tool -> Either Version Tag -> Maybe URI
 | 
					getChangeLog :: GHCupDownloads -> Tool -> Either Version Tag -> Maybe URI
 | 
				
			||||||
getChangeLog dls tool (Left v') =
 | 
					getChangeLog dls tool (Left v') =
 | 
				
			||||||
  preview (ix tool % ix v' % viChangeLog % _Just) dls
 | 
					  preview (ix tool % ix v' % viChangeLog % _Just) dls
 | 
				
			||||||
getChangeLog dls tool (Right tag) = preview
 | 
					getChangeLog dls tool (Right tag) =
 | 
				
			||||||
  ( ix tool
 | 
					  preview (ix tool % getTagged tag % to snd % viChangeLog % _Just) dls
 | 
				
			||||||
  % getTagged tag
 | 
					 | 
				
			||||||
  % to snd
 | 
					 | 
				
			||||||
  % viChangeLog
 | 
					 | 
				
			||||||
  % _Just
 | 
					 | 
				
			||||||
  ) dls
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Execute a build action while potentially cleaning up:
 | 
					-- | Execute a build action while potentially cleaning up:
 | 
				
			||||||
 | 
				
			|||||||
@ -1,10 +1,13 @@
 | 
				
			|||||||
{-# LANGUAGE OverloadedStrings     #-}
 | 
					{-# LANGUAGE OverloadedStrings     #-}
 | 
				
			||||||
{-# LANGUAGE QuasiQuotes           #-}
 | 
					{-# LANGUAGE QuasiQuotes           #-}
 | 
				
			||||||
 | 
					{-# LANGUAGE ViewPatterns          #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
module GHCup.Utils.Dirs where
 | 
					module GHCup.Utils.Dirs where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					import           GHCup.Types
 | 
				
			||||||
import           GHCup.Types.JSON               ( )
 | 
					import           GHCup.Types.JSON               ( )
 | 
				
			||||||
 | 
					import           GHCup.Utils.MegaParsec
 | 
				
			||||||
import           GHCup.Utils.Prelude
 | 
					import           GHCup.Utils.Prelude
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import           Control.Applicative
 | 
					import           Control.Applicative
 | 
				
			||||||
@ -13,7 +16,6 @@ import           Control.Monad
 | 
				
			|||||||
import           Control.Monad.Reader
 | 
					import           Control.Monad.Reader
 | 
				
			||||||
import           Control.Monad.Trans.Resource
 | 
					import           Control.Monad.Trans.Resource
 | 
				
			||||||
import           Data.Maybe
 | 
					import           Data.Maybe
 | 
				
			||||||
import           Data.Versions
 | 
					 | 
				
			||||||
import           HPath
 | 
					import           HPath
 | 
				
			||||||
import           HPath.IO
 | 
					import           HPath.IO
 | 
				
			||||||
import           Optics
 | 
					import           Optics
 | 
				
			||||||
@ -27,8 +29,10 @@ import           System.Posix.Env.ByteString    ( getEnv
 | 
				
			|||||||
import           System.Posix.Temp.ByteString   ( mkdtemp )
 | 
					import           System.Posix.Temp.ByteString   ( mkdtemp )
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import qualified Data.ByteString.UTF8          as UTF8
 | 
					import qualified Data.ByteString.UTF8          as UTF8
 | 
				
			||||||
 | 
					import qualified Data.Text.Encoding            as E
 | 
				
			||||||
import qualified System.Posix.FilePath         as FP
 | 
					import qualified System.Posix.FilePath         as FP
 | 
				
			||||||
import qualified System.Posix.User             as PU
 | 
					import qualified System.Posix.User             as PU
 | 
				
			||||||
 | 
					import qualified Text.Megaparsec               as MP
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
@ -37,6 +41,7 @@ import qualified System.Posix.User             as PU
 | 
				
			|||||||
    -------------------------
 | 
					    -------------------------
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | ~/.ghcup by default
 | 
				
			||||||
ghcupBaseDir :: IO (Path Abs)
 | 
					ghcupBaseDir :: IO (Path Abs)
 | 
				
			||||||
ghcupBaseDir = do
 | 
					ghcupBaseDir = do
 | 
				
			||||||
  bdir <- getEnv "GHCUP_INSTALL_BASE_PREFIX" >>= \case
 | 
					  bdir <- getEnv "GHCUP_INSTALL_BASE_PREFIX" >>= \case
 | 
				
			||||||
@ -44,16 +49,30 @@ ghcupBaseDir = do
 | 
				
			|||||||
    Nothing -> liftIO getHomeDirectory
 | 
					    Nothing -> liftIO getHomeDirectory
 | 
				
			||||||
  pure (bdir </> [rel|.ghcup|])
 | 
					  pure (bdir </> [rel|.ghcup|])
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | ~/.ghcup/ghc by default.
 | 
				
			||||||
ghcupGHCBaseDir :: IO (Path Abs)
 | 
					ghcupGHCBaseDir :: IO (Path Abs)
 | 
				
			||||||
ghcupGHCBaseDir = ghcupBaseDir <&> (</> [rel|ghc|])
 | 
					ghcupGHCBaseDir = ghcupBaseDir <&> (</> [rel|ghc|])
 | 
				
			||||||
 | 
					
 | 
				
			||||||
ghcupGHCDir :: Version -> IO (Path Abs)
 | 
					
 | 
				
			||||||
 | 
					-- | Gets '~/.ghcup/ghc/<ghcupGHCDir>'.
 | 
				
			||||||
 | 
					-- The dir may be of the form
 | 
				
			||||||
 | 
					--   * armv7-unknown-linux-gnueabihf-8.8.3
 | 
				
			||||||
 | 
					--   * 8.8.4
 | 
				
			||||||
 | 
					ghcupGHCDir :: GHCTargetVersion -> IO (Path Abs)
 | 
				
			||||||
ghcupGHCDir ver = do
 | 
					ghcupGHCDir ver = do
 | 
				
			||||||
  ghcbasedir <- ghcupGHCBaseDir
 | 
					  ghcbasedir <- ghcupGHCBaseDir
 | 
				
			||||||
  verdir     <- parseRel (verToBS ver)
 | 
					  verdir     <- parseRel $ E.encodeUtf8 (prettyTVer ver)
 | 
				
			||||||
  pure (ghcbasedir </> verdir)
 | 
					  pure (ghcbasedir </> verdir)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | See 'ghcupToolParser'.
 | 
				
			||||||
 | 
					parseGHCupGHCDir :: MonadThrow m => Path Rel -> m GHCTargetVersion
 | 
				
			||||||
 | 
					parseGHCupGHCDir (toFilePath -> f) = do
 | 
				
			||||||
 | 
					  fp <- throwEither $ E.decodeUtf8' f
 | 
				
			||||||
 | 
					  throwEither $ MP.parse ghcTargetVerP "" fp
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
ghcupBinDir :: IO (Path Abs)
 | 
					ghcupBinDir :: IO (Path Abs)
 | 
				
			||||||
ghcupBinDir = ghcupBaseDir <&> (</> [rel|bin|])
 | 
					ghcupBinDir = ghcupBaseDir <&> (</> [rel|bin|])
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
				
			|||||||
@ -18,6 +18,8 @@ import           Data.Foldable
 | 
				
			|||||||
import           Data.Functor
 | 
					import           Data.Functor
 | 
				
			||||||
import           Data.IORef
 | 
					import           Data.IORef
 | 
				
			||||||
import           Data.Maybe
 | 
					import           Data.Maybe
 | 
				
			||||||
 | 
					import           Data.Text                      ( Text )
 | 
				
			||||||
 | 
					import           Data.Void
 | 
				
			||||||
import           GHC.Foreign                    ( peekCStringLen )
 | 
					import           GHC.Foreign                    ( peekCStringLen )
 | 
				
			||||||
import           GHC.IO.Encoding                ( getLocaleEncoding )
 | 
					import           GHC.IO.Encoding                ( getLocaleEncoding )
 | 
				
			||||||
import           GHC.IO.Exception
 | 
					import           GHC.IO.Exception
 | 
				
			||||||
@ -39,10 +41,12 @@ import "unix"    System.Posix.IO.ByteString
 | 
				
			|||||||
                                         hiding ( openFd )
 | 
					                                         hiding ( openFd )
 | 
				
			||||||
import           System.Posix.Process           ( ProcessStatus(..) )
 | 
					import           System.Posix.Process           ( ProcessStatus(..) )
 | 
				
			||||||
import           System.Posix.Types
 | 
					import           System.Posix.Types
 | 
				
			||||||
 | 
					import           Text.Regex.Posix
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import qualified Control.Exception             as EX
 | 
					import qualified Control.Exception             as EX
 | 
				
			||||||
import qualified Data.Text                     as T
 | 
					import qualified Data.Text                     as T
 | 
				
			||||||
 | 
					import qualified Data.Text.Encoding            as E
 | 
				
			||||||
import qualified System.Posix.Process.ByteString
 | 
					import qualified System.Posix.Process.ByteString
 | 
				
			||||||
                                               as SPPB
 | 
					                                               as SPPB
 | 
				
			||||||
import           Streamly.External.Posix.DirStream
 | 
					import           Streamly.External.Posix.DirStream
 | 
				
			||||||
@ -51,12 +55,14 @@ import qualified Streamly.Internal.Memory.ArrayStream
 | 
				
			|||||||
import qualified Streamly.FileSystem.Handle    as FH
 | 
					import qualified Streamly.FileSystem.Handle    as FH
 | 
				
			||||||
import qualified Streamly.Internal.Data.Unfold as SU
 | 
					import qualified Streamly.Internal.Data.Unfold as SU
 | 
				
			||||||
import qualified Streamly.Prelude              as S
 | 
					import qualified Streamly.Prelude              as S
 | 
				
			||||||
 | 
					import qualified Text.Megaparsec               as MP
 | 
				
			||||||
import qualified Data.ByteString               as BS
 | 
					import qualified Data.ByteString               as BS
 | 
				
			||||||
import qualified Data.ByteString.Lazy          as L
 | 
					import qualified Data.ByteString.Lazy          as L
 | 
				
			||||||
import qualified "unix-bytestring" System.Posix.IO.ByteString
 | 
					import qualified "unix-bytestring" System.Posix.IO.ByteString
 | 
				
			||||||
                                               as SPIB
 | 
					                                               as SPIB
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Bool signals whether the regions should be cleaned.
 | 
					-- | Bool signals whether the regions should be cleaned.
 | 
				
			||||||
data StopThread = StopThread Bool
 | 
					data StopThread = StopThread Bool
 | 
				
			||||||
  deriving Show
 | 
					  deriving Show
 | 
				
			||||||
@ -379,3 +385,27 @@ searchPath paths needle = go paths
 | 
				
			|||||||
    if p == toFilePath needle
 | 
					    if p == toFilePath needle
 | 
				
			||||||
      then isExecutable (basedir </> needle)
 | 
					      then isExecutable (basedir </> needle)
 | 
				
			||||||
      else pure False
 | 
					      else pure False
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					findFiles :: Path Abs -> Regex -> IO [Path Rel]
 | 
				
			||||||
 | 
					findFiles path regex = do
 | 
				
			||||||
 | 
					  dirStream <- openDirStream (toFilePath path)
 | 
				
			||||||
 | 
					  f         <-
 | 
				
			||||||
 | 
					    (fmap . fmap) snd
 | 
				
			||||||
 | 
					    . S.toList
 | 
				
			||||||
 | 
					    . S.filter (\(_, p) -> match regex p)
 | 
				
			||||||
 | 
					    $ dirContentsStream dirStream
 | 
				
			||||||
 | 
					  pure $ join $ fmap parseRel f
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					findFiles' :: Path Abs -> MP.Parsec Void Text () -> IO [Path Rel]
 | 
				
			||||||
 | 
					findFiles' path parser = do
 | 
				
			||||||
 | 
					  dirStream <- openDirStream (toFilePath path)
 | 
				
			||||||
 | 
					  f         <-
 | 
				
			||||||
 | 
					    (fmap . fmap) snd
 | 
				
			||||||
 | 
					    . S.toList
 | 
				
			||||||
 | 
					    . S.filter (\(_, p) -> case E.decodeUtf8' p of
 | 
				
			||||||
 | 
					                             Left _ -> False
 | 
				
			||||||
 | 
					                             Right p' -> isJust $ MP.parseMaybe parser p')
 | 
				
			||||||
 | 
					    $ dirContentsStream dirStream
 | 
				
			||||||
 | 
					  pure $ join $ fmap parseRel f
 | 
				
			||||||
 | 
				
			|||||||
							
								
								
									
										87
									
								
								lib/GHCup/Utils/MegaParsec.hs
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										87
									
								
								lib/GHCup/Utils/MegaParsec.hs
									
									
									
									
									
										Normal file
									
								
							@ -0,0 +1,87 @@
 | 
				
			|||||||
 | 
					{-# LANGUAGE CPP                  #-}
 | 
				
			||||||
 | 
					{-# LANGUAGE OverloadedStrings    #-}
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					module GHCup.Utils.MegaParsec where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					import           GHCup.Types
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					import           Control.Applicative
 | 
				
			||||||
 | 
					import           Control.Monad
 | 
				
			||||||
 | 
					#if !MIN_VERSION_base(4,13,0)
 | 
				
			||||||
 | 
					import           Control.Monad.Fail             ( MonadFail )
 | 
				
			||||||
 | 
					#endif
 | 
				
			||||||
 | 
					import           Data.Functor
 | 
				
			||||||
 | 
					import           Data.Maybe
 | 
				
			||||||
 | 
					import           Data.Text                      ( Text )
 | 
				
			||||||
 | 
					import           Data.Versions
 | 
				
			||||||
 | 
					import           Data.Void
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					import qualified Data.Text                     as T
 | 
				
			||||||
 | 
					import qualified Text.Megaparsec               as MP
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					choice' :: (MonadFail f, MP.MonadParsec e s f) => [f a] -> f a
 | 
				
			||||||
 | 
					choice' []       = fail "Empty list"
 | 
				
			||||||
 | 
					choice' [x     ] = x
 | 
				
			||||||
 | 
					choice' (x : xs) = MP.try x <|> choice' xs
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					parseUntil :: MP.Parsec Void Text a -> MP.Parsec Void Text Text
 | 
				
			||||||
 | 
					parseUntil p = do
 | 
				
			||||||
 | 
					  (MP.try (MP.lookAhead p) $> mempty)
 | 
				
			||||||
 | 
					    <|> (do
 | 
				
			||||||
 | 
					          c  <- T.singleton <$> MP.anySingle
 | 
				
			||||||
 | 
					          c2 <- parseUntil p
 | 
				
			||||||
 | 
					          pure (c `mappend` c2)
 | 
				
			||||||
 | 
					        )
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					parseUntil1 :: MP.Parsec Void Text a -> MP.Parsec Void Text Text
 | 
				
			||||||
 | 
					parseUntil1 p = do
 | 
				
			||||||
 | 
					  i1 <- MP.getOffset
 | 
				
			||||||
 | 
					  t <- parseUntil p
 | 
				
			||||||
 | 
					  i2 <- MP.getOffset
 | 
				
			||||||
 | 
					  if i1 == i2 then fail "empty parse" else pure t
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Parses e.g.
 | 
				
			||||||
 | 
					--   * armv7-unknown-linux-gnueabihf-ghc
 | 
				
			||||||
 | 
					--   * armv7-unknown-linux-gnueabihf-ghci
 | 
				
			||||||
 | 
					ghcTargetBinP :: Text -> MP.Parsec Void Text (Maybe Text, Text)
 | 
				
			||||||
 | 
					ghcTargetBinP t =
 | 
				
			||||||
 | 
					  (,)
 | 
				
			||||||
 | 
					    <$> (   MP.try
 | 
				
			||||||
 | 
					            (Just <$> (parseUntil1 (MP.chunk "-" *> MP.chunk t)) <* MP.chunk "-"
 | 
				
			||||||
 | 
					            )
 | 
				
			||||||
 | 
					        <|> (flip const Nothing <$> mempty)
 | 
				
			||||||
 | 
					        )
 | 
				
			||||||
 | 
					    <*> (MP.chunk t <* MP.eof)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Extracts target triple and version from e.g.
 | 
				
			||||||
 | 
					--   * armv7-unknown-linux-gnueabihf-8.8.3
 | 
				
			||||||
 | 
					--   * armv7-unknown-linux-gnueabihf-8.8.3
 | 
				
			||||||
 | 
					ghcTargetVerP :: MP.Parsec Void Text GHCTargetVersion
 | 
				
			||||||
 | 
					ghcTargetVerP =
 | 
				
			||||||
 | 
					  (\x y -> GHCTargetVersion x y)
 | 
				
			||||||
 | 
					    <$> (MP.try (Just <$> (parseUntil1 (MP.chunk "-" *> verP)) <* MP.chunk "-")
 | 
				
			||||||
 | 
					        <|> (flip const Nothing <$> mempty)
 | 
				
			||||||
 | 
					        )
 | 
				
			||||||
 | 
					    <*> (version' <* MP.eof)
 | 
				
			||||||
 | 
					 where
 | 
				
			||||||
 | 
					  verP :: MP.Parsec Void Text Text
 | 
				
			||||||
 | 
					  verP = do
 | 
				
			||||||
 | 
					    v <- version'
 | 
				
			||||||
 | 
					    let startsWithDigists =
 | 
				
			||||||
 | 
					          and
 | 
				
			||||||
 | 
					            . take 3
 | 
				
			||||||
 | 
					            . join
 | 
				
			||||||
 | 
					            . (fmap . fmap)
 | 
				
			||||||
 | 
					                (\case
 | 
				
			||||||
 | 
					                  (Digits _) -> True
 | 
				
			||||||
 | 
					                  (Str    _) -> False
 | 
				
			||||||
 | 
					                )
 | 
				
			||||||
 | 
					            $ (_vChunks v)
 | 
				
			||||||
 | 
					    if startsWithDigists && not (isJust (_vEpoch v))
 | 
				
			||||||
 | 
					      then pure $ prettyVer v
 | 
				
			||||||
 | 
					      else fail "Oh"
 | 
				
			||||||
@ -218,6 +218,12 @@ throwEither a = case a of
 | 
				
			|||||||
  Right r -> pure r
 | 
					  Right r -> pure r
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					throwEither' :: (Exception a, MonadThrow m) => a -> Either x b -> m b
 | 
				
			||||||
 | 
					throwEither' e eth = case eth of
 | 
				
			||||||
 | 
					  Left  _ -> throwM e
 | 
				
			||||||
 | 
					  Right r -> pure r
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
verToBS :: Version -> ByteString
 | 
					verToBS :: Version -> ByteString
 | 
				
			||||||
verToBS = E.encodeUtf8 . prettyVer
 | 
					verToBS = E.encodeUtf8 . prettyVer
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
				
			|||||||
		Loading…
	
		Reference in New Issue
	
	Block a user