ghcup-0.1.18.0: ghc toolchain installer
Copyright(c) Julian Ospald 2020
LicenseLGPL-3.0
Maintainerhasufell@hasufell.de
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

GHCup.Utils

Description

This module contains GHCup helpers specific to installation and introspection of files/versions etc.

Synopsis

Documentation

binarySymLinkDestination Source #

Arguments

:: (MonadThrow m, MonadIO m) 
=> FilePath

binary dir

-> FilePath

the full toolpath

-> m FilePath 

Create a relative symlink destination for the binary directory, given a target toolpath.

rmMinorGHCSymlinks :: (MonadReader env m, HasDirs env, MonadIO m, HasLog env, MonadThrow m, MonadFail m, MonadMask m) => GHCTargetVersion -> Excepts '[NotInstalled] m () Source #

Removes the minor GHC symlinks, e.g. ghc-8.6.5.

rmPlainGHC Source #

Arguments

:: (MonadReader env m, HasDirs env, HasLog env, MonadThrow m, MonadFail m, MonadIO m, MonadMask m) 
=> Maybe Text

target

-> Excepts '[NotInstalled] m () 

Removes the set ghc version for the given target, if any.

rmMajorGHCSymlinks :: (MonadReader env m, HasDirs env, MonadIO m, HasLog env, MonadThrow m, MonadFail m, MonadMask m) => GHCTargetVersion -> Excepts '[NotInstalled] m () Source #

Remove the major GHC symlink, e.g. ghc-8.6.

rmMinorHLSSymlinks :: (MonadReader env m, HasDirs env, MonadIO m, HasLog env, MonadThrow m, MonadFail m, MonadMask m) => Version -> Excepts '[NotInstalled] m () Source #

Removes the minor HLS files, e.g. 'haskell-language-server-8.10.7~1.6.1.0' and 'haskell-language-server-wrapper-1.6.1.0'.

rmPlainHLS :: (MonadReader env m, HasDirs env, HasLog env, MonadThrow m, MonadFail m, MonadIO m, MonadMask m) => Excepts '[NotInstalled] m () Source #

Removes the set HLS version, if any.

ghcInstalled :: (MonadIO m, MonadReader env m, HasDirs env, MonadThrow m) => GHCTargetVersion -> m Bool Source #

Whether the given GHC versin is installed.

ghcSrcInstalled :: (MonadIO m, MonadReader env m, HasDirs env, MonadThrow m) => GHCTargetVersion -> m Bool Source #

Whether the given GHC version is installed from source.

ghcSet Source #

Arguments

:: (MonadReader env m, HasDirs env, MonadThrow m, MonadIO m) 
=> Maybe Text

the target of the GHC version, if any (e.g. armv7-unknown-linux-gnueabihf)

-> m (Maybe GHCTargetVersion) 

Whether the given GHC version is set as the current.

getInstalledGHCs :: (MonadReader env m, HasDirs env, MonadIO m) => m [Either FilePath GHCTargetVersion] Source #

Get all installed GHCs by reading ~.ghcupghc/dir. If a dir cannot be parsed, returns left.

getInstalledCabals :: (MonadReader env m, HasDirs env, MonadIO m, MonadCatch m) => m [Either FilePath Version] Source #

Get all installed cabals, by matching on ~/.ghcup/bin/cabal-*.

cabalInstalled :: (MonadIO m, MonadReader env m, HasDirs env, MonadCatch m) => Version -> m Bool Source #

Whether the given cabal version is installed.

getInstalledHLSs :: (MonadReader env m, HasDirs env, MonadIO m, MonadCatch m) => m [Either FilePath Version] Source #

Get all installed hls, by matching on ~/.ghcup/bin/haskell-language-server-wrapper-hlsver, as well as ~/.ghcup/hls/hlsver

getInstalledStacks :: (MonadReader env m, HasDirs env, MonadIO m, MonadCatch m) => m [Either FilePath Version] Source #

Get all installed stacks, by matching on ~/.ghcup/bin/stack-stackver.

stackInstalled :: (MonadIO m, MonadReader env m, HasDirs env, MonadCatch m) => Version -> m Bool Source #

Whether the given Stack version is installed.

hlsInstalled :: (MonadIO m, MonadReader env m, HasDirs env, MonadCatch m) => Version -> m Bool Source #

Whether the given HLS version is installed.

hlsGHCVersions :: (MonadReader env m, HasDirs env, MonadIO m, MonadThrow m, MonadCatch m) => m [Version] Source #

Return the GHC versions the currently selected HLS supports.

hlsServerBinaries Source #

Arguments

:: (MonadReader env m, HasDirs env, MonadIO m) 
=> Version 
-> Maybe Version

optional GHC version

-> m [FilePath] 

Get all server binaries for an hls version from the ~.ghcupbin directory, if any.

hlsInternalServerScripts Source #

Arguments

:: (MonadReader env m, HasDirs env, MonadIO m, MonadThrow m) 
=> Version 
-> Maybe Version

optional GHC version

-> m [FilePath] 

Get all scripts for a hls version from the ~.ghcuphlsverbin directory, if any. Returns the full path.

hlsInternalServerBinaries Source #

Arguments

:: (MonadReader env m, HasDirs env, MonadIO m, MonadThrow m, MonadFail m) 
=> Version 
-> Maybe Version

optional GHC version

-> m [FilePath] 

Get all binaries for a hls version from the ~.ghcuphlsverlibhaskell-language-server-verbin directory, if any. Returns the full path.

hlsInternalServerLibs Source #

Arguments

:: (MonadReader env m, HasDirs env, MonadIO m, MonadThrow m, MonadFail m) 
=> Version 
-> Version

GHC version

-> m [FilePath] 

Get all libraries for a hls version from the ~.ghcuphlsverlibhaskell-language-server-verlibghc-ver directory, if any. Returns the full path.

hlsWrapperBinary :: (MonadReader env m, HasDirs env, MonadThrow m, MonadIO m) => Version -> m (Maybe FilePath) Source #

Get the wrapper binary for an hls version, if any.

hlsAllBinaries :: (MonadReader env m, HasDirs env, MonadIO m, MonadThrow m) => Version -> m [FilePath] Source #

Get all binaries for an hls version, if any.

getMajorMinorV :: MonadThrow m => Version -> m (Int, Int) Source #

Extract (major, minor) from any version.

matchPVPrefix :: PVP -> PVP -> Bool Source #

Match PVP prefix.

>>> matchPVPrefix [pver|8.8|] [pver|8.8.4|]
True
>>> matchPVPrefix [pver|8|] [pver|8.8.4|]
True
>>> matchPVPrefix [pver|8.10|] [pver|8.8.4|]
False
>>> matchPVPrefix [pver|8.10|] [pver|8.10.7|]
True

toL :: PVP -> [Int] Source #

getGHCForPVP Source #

Arguments

:: (MonadReader env m, HasDirs env, MonadIO m, MonadThrow m) 
=> PVP 
-> Maybe Text

the target triple

-> m (Maybe GHCTargetVersion) 

Get the latest installed full GHC version that satisfies the given (possibly partial) PVP version.

getGHCForPVP' Source #

Arguments

:: MonadThrow m 
=> PVP 
-> [(PVP, Text, Maybe Text)]

installed GHCs

-> Maybe Text

the target triple

-> m (Maybe GHCTargetVersion) 

Like getGHCForPVP, except with explicit input parameter.

>>> getGHCForPVP' [pver|8|] installedVersions Nothing
Just (GHCTargetVersion {_tvTarget = Nothing, _tvVersion = Version {_vEpoch = Nothing, _vChunks = (Digits 8 :| []) :| [Digits 10 :| [],Digits 7 :| []], _vRel = [Str "debug" :| []], _vMeta = Just "lol"}})
>>> fmap prettyShow $ getGHCForPVP' [pver|8.8|] installedVersions Nothing
"Just 8.8.4"
>>> fmap prettyShow $ getGHCForPVP' [pver|8.10.4|] installedVersions Nothing
"Just 8.10.4"

getLatestToolFor :: MonadThrow m => Tool -> PVP -> GHCupDownloads -> m (Maybe (PVP, VersionInfo)) Source #

Get the latest available ghc for the given PVP version, which may only contain parts.

>>> (fmap . fmap) fst $ getLatestToolFor GHC [pver|8|] r
Just (PVP {_pComponents = 8 :| [10,7]})
>>> (fmap . fmap) fst $ getLatestToolFor GHC [pver|8.8|] r
Just (PVP {_pComponents = 8 :| [8,4]})
>>> (fmap . fmap) fst $ getLatestToolFor GHC [pver|8.8.4|] r
Just (PVP {_pComponents = 8 :| [8,4]})

unpackToDir Source #

Arguments

:: (MonadReader env m, HasLog env, MonadIO m, MonadThrow m) 
=> FilePath

destination dir

-> FilePath

archive path

-> Excepts '[UnknownArchive, ArchiveResult] m () 

Unpack an archive to a temporary directory and return that path.

intoSubdir Source #

Arguments

:: (MonadReader env m, HasLog env, MonadIO m, MonadThrow m, MonadCatch m) 
=> GHCupPath

unpacked tar dir

-> TarDir

how to descend

-> Excepts '[TarDirDoesNotExist] m GHCupPath 

getTagged :: Tag -> Fold (Map Version VersionInfo) (Version, VersionInfo) Source #

Get the tool version that has this tag. If multiple have it, picks the greatest version.

getLatestBaseVersion :: GHCupDownloads -> PVP -> Maybe (Version, VersionInfo) Source #

Gets the latest GHC with a given base version.

ghcInternalBinDir :: (MonadReader env m, HasDirs env, MonadThrow m, MonadFail m, MonadIO m) => GHCTargetVersion -> m FilePath Source #

Usually ~/.ghcup/ghc/<ver>/bin/

ghcToolFiles :: (MonadReader env m, HasDirs env, MonadThrow m, MonadFail m, MonadIO m) => GHCTargetVersion -> Excepts '[NotInstalled] m [FilePath] Source #

Get tool files from ~/.ghcup/ghc/<ver>/bin/* while ignoring *-<ver> symlinks and accounting for cross triple prefix.

Returns unversioned relative files without extension, e.g.:

  • ["hsc2hs","haddock","hpc","runhaskell","ghc","ghc-pkg","ghci","runghc","hp2ps"]

ghcUpSrcBuiltFile :: FilePath Source #

This file, when residing in ~/.ghcup/ghc/<ver>/ signals that this GHC was built from source. It contains the build config.

make :: (MonadThrow m, MonadIO m, MonadReader env m, HasDirs env, HasLog env, HasSettings env) => [String] -> Maybe FilePath -> m (Either ProcessError ()) Source #

Calls gmake if it exists in PATH, otherwise make.

applyPatches Source #

Arguments

:: (MonadReader env m, HasDirs env, HasLog env, MonadIO m) 
=> FilePath

dir containing patches

-> FilePath

dir to apply patches in

-> Excepts '[PatchFailed] m () 

Try to apply patches in order. The order is determined by a quilt series file (in the patch directory) if one exists, else the patches are applied in lexicographical order. Fails with PatchFailed on first failure.

applyPatch Source #

Arguments

:: (MonadReader env m, HasDirs env, HasLog env, MonadIO m) 
=> FilePath

Patch

-> FilePath

dir to apply patches in

-> Excepts '[PatchFailed] m () 

runBuildAction Source #

Arguments

:: (MonadReader env m, HasDirs env, HasSettings env, MonadIO m, MonadMask m, HasLog env, MonadUnliftIO m, MonadFail m, MonadCatch m) 
=> GHCupPath

build directory (cleaned up depending on Settings)

-> Excepts e m a 
-> Excepts e m a 

Execute a build action while potentially cleaning up:

  1. the build directory, depending on the KeepDirs setting

cleanUpOnError Source #

Arguments

:: forall e m a env. (MonadReader env m, HasDirs env, HasSettings env, MonadIO m, MonadMask m, HasLog env, MonadUnliftIO m, MonadFail m, MonadCatch m) 
=> GHCupPath

build directory (cleaned up depending on Settings)

-> Excepts e m a 
-> Excepts e m a 

Clean up the given directory if the action fails, depending on the Settings.

cleanFinally Source #

Arguments

:: (MonadReader env m, HasDirs env, HasSettings env, MonadIO m, MonadMask m, HasLog env, MonadUnliftIO m, MonadFail m, MonadCatch m) 
=> GHCupPath

build directory (cleaned up depending on Settings)

-> Excepts e m a 
-> Excepts e m a 

Clean up the given directory if the action fails, depending on the Settings.

rmBDir :: (MonadReader env m, HasLog env, MonadUnliftIO m, MonadIO m) => GHCupPath -> m () Source #

Remove a build directory, ignoring if it doesn't exist and gracefully printing other errors without crashing.

ensureDirectories :: Dirs -> IO () Source #

Ensure ghcup directory structure exists.

ghcBinaryName :: GHCTargetVersion -> String Source #

For ghc without arch triple, this is:

  • ghc

For ghc with arch triple:

  • triple-ghc (e.g. arm-linux-gnueabihf-ghc)

installDestSanityCheck :: (MonadIO m, MonadCatch m, MonadMask m) => InstallDirResolved -> Excepts '[DirNotEmpty] m () Source #

Does basic checks for isolated installs Isolated Directory: 1. if it doesn't exist -> proceed 2. if it exists and is empty -> proceed 3. if it exists and is non-empty -> panic and leave the house

getInstalledFiles :: (MonadIO m, MonadCatch m, MonadReader env m, HasDirs env, MonadFail m) => Tool -> GHCTargetVersion -> m (Maybe [FilePath]) Source #

Returns Nothing for legacy installs.

warnAboutHlsCompatibility :: (MonadReader env m, HasDirs env, HasLog env, MonadThrow m, MonadCatch m, MonadIO m) => m () Source #

Warn if the installed and set HLS is not compatible with the installed and set GHC version.

enableAnsiSupport :: IO (Either String Bool) Source #

Enables ANSI support on windows, does nothing on unix.

Returns 'Left str' on errors and 'Right bool' on success, where bool markes whether ansi support was already enabled.

This function never crashes.

Rip-off of https://docs.rs/ansi_term/0.12.1/x86_64-pc-windows-msvc/src/ansi_term/windows.rs.html#10-61