Allow to specify regex for subdir
This commit is contained in:
parent
cafedd73a2
commit
5c45884f5f
@ -57,7 +57,7 @@ variables:
|
|||||||
script:
|
script:
|
||||||
- ./.gitlab/script/ghcup_version.sh
|
- ./.gitlab/script/ghcup_version.sh
|
||||||
variables:
|
variables:
|
||||||
JSON_VERSION: "0.0.2"
|
JSON_VERSION: "0.0.3"
|
||||||
|
|
||||||
.test_ghcup_version:linux:
|
.test_ghcup_version:linux:
|
||||||
extends:
|
extends:
|
||||||
|
@ -214,7 +214,9 @@ install' AppState {..} (_, ListResult {..}) = do
|
|||||||
, TagNotFound
|
, TagNotFound
|
||||||
, DigestError
|
, DigestError
|
||||||
, DownloadFailed
|
, DownloadFailed
|
||||||
, NoUpdate]
|
, NoUpdate
|
||||||
|
, TarDirDoesNotExist
|
||||||
|
]
|
||||||
|
|
||||||
(run $ do
|
(run $ do
|
||||||
case lTool of
|
case lTool of
|
||||||
|
@ -404,7 +404,11 @@ installParser =
|
|||||||
installGHCFooter = [s|Discussion:
|
installGHCFooter = [s|Discussion:
|
||||||
Installs the specified GHC version (or a recommended default one) into
|
Installs the specified GHC version (or a recommended default one) into
|
||||||
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>".
|
||||||
|
|
||||||
|
Examples:
|
||||||
|
# install GHC head
|
||||||
|
ghcup -n install ghc -u '{"dlHash": "", "dlSubdir": { "RegexDir": "ghc-.*"}, "dlUri": "https://gitlab.haskell.org/api/v4/projects/1/jobs/artifacts/master/raw/ghc-x86_64-fedora27-linux.tar.xz?job=validate-x86_64-linux-fedora27" }' head|]
|
||||||
|
|
||||||
|
|
||||||
installOpts :: Parser InstallOptions
|
installOpts :: Parser InstallOptions
|
||||||
@ -428,7 +432,7 @@ installOpts =
|
|||||||
<> long "url"
|
<> long "url"
|
||||||
<> metavar "BINDIST_URL"
|
<> metavar "BINDIST_URL"
|
||||||
<> help
|
<> help
|
||||||
"Provide DownloadInfo as json string, e.g.: '{ \"dlHash\": \"<sha256 hash>\", \"dlSubdir\": \"ghc-<ver>\", \"dlUri\": \"<uri>\" }'"
|
"Provide DownloadInfo as json string, e.g.: '{ \"dlHash\": \"<sha256 hash>\", \"dlSubdir\": { \"RegexDir\": \"ghc-.*\"}, \"dlUri\": \"<uri>\" }'"
|
||||||
)
|
)
|
||||||
)
|
)
|
||||||
)
|
)
|
||||||
@ -940,6 +944,7 @@ Report bugs at <https://gitlab.haskell.org/haskell/ghcup-hs/issues>|]
|
|||||||
, TagNotFound
|
, TagNotFound
|
||||||
, DigestError
|
, DigestError
|
||||||
, DownloadFailed
|
, DownloadFailed
|
||||||
|
, TarDirDoesNotExist
|
||||||
]
|
]
|
||||||
|
|
||||||
let
|
let
|
||||||
@ -986,6 +991,7 @@ Report bugs at <https://gitlab.haskell.org/haskell/ghcup-hs/issues>|]
|
|||||||
, NotFoundInPATH
|
, NotFoundInPATH
|
||||||
, PatchFailed
|
, PatchFailed
|
||||||
, UnknownArchive
|
, UnknownArchive
|
||||||
|
, TarDirDoesNotExist
|
||||||
#if !defined(TAR)
|
#if !defined(TAR)
|
||||||
, ArchiveResult
|
, ArchiveResult
|
||||||
#endif
|
#endif
|
||||||
@ -1005,6 +1011,7 @@ Report bugs at <https://gitlab.haskell.org/haskell/ghcup-hs/issues>|]
|
|||||||
, NotInstalled
|
, NotInstalled
|
||||||
, PatchFailed
|
, PatchFailed
|
||||||
, UnknownArchive
|
, UnknownArchive
|
||||||
|
, TarDirDoesNotExist
|
||||||
#if !defined(TAR)
|
#if !defined(TAR)
|
||||||
, ArchiveResult
|
, ArchiveResult
|
||||||
#endif
|
#endif
|
||||||
|
@ -153,6 +153,9 @@ common safe
|
|||||||
common safe-exceptions
|
common safe-exceptions
|
||||||
build-depends: safe-exceptions >=0.1
|
build-depends: safe-exceptions >=0.1
|
||||||
|
|
||||||
|
common split
|
||||||
|
build-depends: split >=0.2.3.4
|
||||||
|
|
||||||
common streamly
|
common streamly
|
||||||
build-depends: streamly >=0.7.1
|
build-depends: streamly >=0.7.1
|
||||||
|
|
||||||
@ -276,6 +279,7 @@ library
|
|||||||
, resourcet
|
, resourcet
|
||||||
, safe
|
, safe
|
||||||
, safe-exceptions
|
, safe-exceptions
|
||||||
|
, split
|
||||||
, streamly
|
, streamly
|
||||||
, streamly-posix
|
, streamly-posix
|
||||||
, streamly-bytestring
|
, streamly-bytestring
|
||||||
|
77
lib/GHCup.hs
77
lib/GHCup.hs
@ -112,6 +112,7 @@ installGHCBindist :: ( MonadFail m
|
|||||||
, NoDownload
|
, NoDownload
|
||||||
, NotInstalled
|
, NotInstalled
|
||||||
, UnknownArchive
|
, UnknownArchive
|
||||||
|
, TarDirDoesNotExist
|
||||||
#if !defined(TAR)
|
#if !defined(TAR)
|
||||||
, ArchiveResult
|
, ArchiveResult
|
||||||
#endif
|
#endif
|
||||||
@ -136,7 +137,7 @@ installGHCBindist dlinfo ver (PlatformRequest {..}) = do
|
|||||||
ghcdir <- lift $ ghcupGHCDir tver
|
ghcdir <- lift $ 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)
|
workdir <- maybe (pure tmpUnpack) (liftE . intoSubdir tmpUnpack) (view dlSubdir dlinfo)
|
||||||
|
|
||||||
liftE $ runBuildAction tmpUnpack (Just ghcdir) (installGHC' workdir ghcdir)
|
liftE $ runBuildAction tmpUnpack (Just ghcdir) (installGHC' workdir ghcdir)
|
||||||
|
|
||||||
@ -189,6 +190,7 @@ installGHCBin :: ( MonadFail m
|
|||||||
, NoDownload
|
, NoDownload
|
||||||
, NotInstalled
|
, NotInstalled
|
||||||
, UnknownArchive
|
, UnknownArchive
|
||||||
|
, TarDirDoesNotExist
|
||||||
#if !defined(TAR)
|
#if !defined(TAR)
|
||||||
, ArchiveResult
|
, ArchiveResult
|
||||||
#endif
|
#endif
|
||||||
@ -221,6 +223,7 @@ installCabalBindist :: ( MonadMask m
|
|||||||
, NoDownload
|
, NoDownload
|
||||||
, NotInstalled
|
, NotInstalled
|
||||||
, UnknownArchive
|
, UnknownArchive
|
||||||
|
, TarDirDoesNotExist
|
||||||
#if !defined(TAR)
|
#if !defined(TAR)
|
||||||
, ArchiveResult
|
, ArchiveResult
|
||||||
#endif
|
#endif
|
||||||
@ -250,7 +253,7 @@ installCabalBindist dlinfo ver (PlatformRequest {..}) = do
|
|||||||
void $ liftIO $ darwinNotarization _rPlatform tmpUnpack
|
void $ liftIO $ darwinNotarization _rPlatform tmpUnpack
|
||||||
|
|
||||||
-- 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)
|
workdir <- maybe (pure tmpUnpack) (liftE . intoSubdir tmpUnpack) (view dlSubdir dlinfo)
|
||||||
|
|
||||||
liftE $ installCabal' workdir binDir
|
liftE $ installCabal' workdir binDir
|
||||||
|
|
||||||
@ -300,6 +303,7 @@ installCabalBin :: ( MonadMask m
|
|||||||
, NoDownload
|
, NoDownload
|
||||||
, NotInstalled
|
, NotInstalled
|
||||||
, UnknownArchive
|
, UnknownArchive
|
||||||
|
, TarDirDoesNotExist
|
||||||
#if !defined(TAR)
|
#if !defined(TAR)
|
||||||
, ArchiveResult
|
, ArchiveResult
|
||||||
#endif
|
#endif
|
||||||
@ -328,7 +332,13 @@ installCabalBin bDls ver pfreq = 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 :: (MonadReader Settings m, MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
|
setGHC :: ( MonadReader Settings m
|
||||||
|
, MonadLogger m
|
||||||
|
, MonadThrow m
|
||||||
|
, MonadFail m
|
||||||
|
, MonadIO m
|
||||||
|
, MonadCatch m
|
||||||
|
)
|
||||||
=> GHCTargetVersion
|
=> GHCTargetVersion
|
||||||
-> SetGHC
|
-> SetGHC
|
||||||
-> Excepts '[NotInstalled] m GHCTargetVersion
|
-> Excepts '[NotInstalled] m GHCTargetVersion
|
||||||
@ -350,15 +360,22 @@ setGHC ver sghc = do
|
|||||||
-- for ghc tools (ghc, ghci, haddock, ...)
|
-- for ghc tools (ghc, ghci, haddock, ...)
|
||||||
verfiles <- ghcToolFiles ver
|
verfiles <- ghcToolFiles ver
|
||||||
forM_ verfiles $ \file -> do
|
forM_ verfiles $ \file -> do
|
||||||
targetFile <- case sghc of
|
mTargetFile <- case sghc of
|
||||||
SetGHCOnly -> pure file
|
SetGHCOnly -> pure $ Just file
|
||||||
SetGHC_XY -> do
|
SetGHC_XY -> do
|
||||||
major' <- (\(mj, mi) -> E.encodeUtf8 $ intToText mj <> "." <> intToText mi)
|
v' <-
|
||||||
<$> getMajorMinorV (_tvVersion ver)
|
handle
|
||||||
parseRel (toFilePath file <> B.singleton _hyphen <> major')
|
(\(e :: ParseError) -> lift $ $(logWarn) [i|#{e}|] >> pure Nothing)
|
||||||
SetGHC_XYZ -> parseRel (toFilePath file <> B.singleton _hyphen <> verBS)
|
$ fmap Just
|
||||||
|
$ getMajorMinorV (_tvVersion ver)
|
||||||
|
forM v' $ \(mj, mi) ->
|
||||||
|
let major' = E.encodeUtf8 $ intToText mj <> "." <> intToText mi
|
||||||
|
in parseRel (toFilePath file <> B.singleton _hyphen <> major')
|
||||||
|
SetGHC_XYZ ->
|
||||||
|
fmap Just $ parseRel (toFilePath file <> B.singleton _hyphen <> verBS)
|
||||||
|
|
||||||
-- create symlink
|
-- create symlink
|
||||||
|
forM mTargetFile $ \targetFile -> do
|
||||||
let fullF = binDir </> targetFile
|
let fullF = binDir </> targetFile
|
||||||
destL <- lift $ ghcLinkDestination (toFilePath file) ver
|
destL <- lift $ ghcLinkDestination (toFilePath file) ver
|
||||||
lift $ $(logDebug) [i|ln -s #{destL} #{toFilePath fullF}|]
|
lift $ $(logDebug) [i|ln -s #{destL} #{toFilePath fullF}|]
|
||||||
@ -589,7 +606,13 @@ listVersions av lt criteria pfreq = do
|
|||||||
-- This may leave GHCup without a "set" version.
|
-- This may leave GHCup without a "set" version.
|
||||||
-- Will try to fix the ghc-x.y symlink after removal (e.g. to an
|
-- Will try to fix the ghc-x.y symlink after removal (e.g. to an
|
||||||
-- older version).
|
-- older version).
|
||||||
rmGHCVer :: (MonadReader Settings m, MonadThrow m, MonadLogger m, MonadIO m, MonadFail m)
|
rmGHCVer :: ( MonadReader Settings m
|
||||||
|
, MonadThrow m
|
||||||
|
, MonadLogger m
|
||||||
|
, MonadIO m
|
||||||
|
, MonadFail m
|
||||||
|
, MonadCatch m
|
||||||
|
)
|
||||||
=> GHCTargetVersion
|
=> GHCTargetVersion
|
||||||
-> Excepts '[NotInstalled] m ()
|
-> Excepts '[NotInstalled] m ()
|
||||||
rmGHCVer ver = do
|
rmGHCVer ver = do
|
||||||
@ -614,10 +637,15 @@ rmGHCVer ver = do
|
|||||||
|
|
||||||
lift $ $(logInfo) [i|Removing/rewiring ghc-x.y symlinks|]
|
lift $ $(logInfo) [i|Removing/rewiring ghc-x.y symlinks|]
|
||||||
-- first remove
|
-- first remove
|
||||||
lift $ rmMajorSymlinks ver
|
handle (\(_ :: ParseError) -> pure ()) $ lift $ rmMajorSymlinks ver
|
||||||
-- then fix them (e.g. with an earlier version)
|
-- then fix them (e.g. with an earlier version)
|
||||||
(mj, mi) <- getMajorMinorV (_tvVersion ver)
|
v' <-
|
||||||
lift (getGHCForMajor mj mi (_tvTarget ver)) >>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
|
handle
|
||||||
|
(\(e :: ParseError) -> lift $ $(logWarn) [i|#{e}|] >> pure Nothing)
|
||||||
|
$ fmap Just
|
||||||
|
$ getMajorMinorV (_tvVersion ver)
|
||||||
|
forM_ v' $ \(mj, mi) -> lift (getGHCForMajor mj mi (_tvTarget ver))
|
||||||
|
>>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
|
||||||
|
|
||||||
Settings { dirs = Dirs {..} } <- lift ask
|
Settings { dirs = Dirs {..} } <- lift ask
|
||||||
|
|
||||||
@ -708,6 +736,7 @@ compileGHC :: ( MonadMask m
|
|||||||
, NotFoundInPATH
|
, NotFoundInPATH
|
||||||
, PatchFailed
|
, PatchFailed
|
||||||
, UnknownArchive
|
, UnknownArchive
|
||||||
|
, TarDirDoesNotExist
|
||||||
#if !defined(TAR)
|
#if !defined(TAR)
|
||||||
, ArchiveResult
|
, ArchiveResult
|
||||||
#endif
|
#endif
|
||||||
@ -733,7 +762,7 @@ compileGHC dls tver bstrap jobs mbuildConfig patchdir aargs PlatformRequest {..}
|
|||||||
bghc <- case bstrap of
|
bghc <- case bstrap of
|
||||||
Right g -> pure $ Right g
|
Right g -> pure $ Right g
|
||||||
Left bver -> Left <$> parseRel ("ghc-" <> verToBS bver)
|
Left bver -> Left <$> parseRel ("ghc-" <> verToBS bver)
|
||||||
let workdir = maybe id (flip (</>)) (view dlSubdir dlInfo) $ tmpUnpack
|
workdir <- maybe (pure tmpUnpack) (liftE . intoSubdir tmpUnpack) (view dlSubdir dlInfo)
|
||||||
ghcdir <- lift $ ghcupGHCDir tver
|
ghcdir <- lift $ ghcupGHCDir tver
|
||||||
|
|
||||||
liftE $ runBuildAction
|
liftE $ runBuildAction
|
||||||
@ -888,6 +917,7 @@ compileCabal :: ( MonadReader Settings m
|
|||||||
, NotInstalled
|
, NotInstalled
|
||||||
, PatchFailed
|
, PatchFailed
|
||||||
, UnknownArchive
|
, UnknownArchive
|
||||||
|
, TarDirDoesNotExist
|
||||||
#if !defined(TAR)
|
#if !defined(TAR)
|
||||||
, ArchiveResult
|
, ArchiveResult
|
||||||
#endif
|
#endif
|
||||||
@ -917,7 +947,7 @@ compileCabal dls tver bghc jobs patchdir PlatformRequest{..} = do
|
|||||||
liftE $ unpackToDir tmpUnpack dl
|
liftE $ unpackToDir tmpUnpack dl
|
||||||
void $ liftIO $ darwinNotarization _rPlatform tmpUnpack
|
void $ liftIO $ darwinNotarization _rPlatform tmpUnpack
|
||||||
|
|
||||||
let workdir = maybe id (flip (</>)) (view dlSubdir dlInfo) $ tmpUnpack
|
workdir <- maybe (pure tmpUnpack) (liftE . intoSubdir tmpUnpack) (view dlSubdir dlInfo)
|
||||||
|
|
||||||
cbin <- liftE $ runBuildAction tmpUnpack Nothing (compile workdir)
|
cbin <- liftE $ runBuildAction tmpUnpack Nothing (compile workdir)
|
||||||
|
|
||||||
@ -1039,7 +1069,13 @@ upgradeGHCup dls mtarget force pfreq = 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 :: (MonadReader Settings m, MonadLogger m, MonadThrow m, MonadFail m, MonadIO m)
|
postGHCInstall :: ( MonadReader Settings m
|
||||||
|
, MonadLogger m
|
||||||
|
, MonadThrow m
|
||||||
|
, MonadFail m
|
||||||
|
, MonadIO m
|
||||||
|
, MonadCatch m
|
||||||
|
)
|
||||||
=> GHCTargetVersion
|
=> GHCTargetVersion
|
||||||
-> Excepts '[NotInstalled] m ()
|
-> Excepts '[NotInstalled] m ()
|
||||||
postGHCInstall ver@GHCTargetVersion {..} = do
|
postGHCInstall ver@GHCTargetVersion {..} = do
|
||||||
@ -1047,5 +1083,10 @@ postGHCInstall ver@GHCTargetVersion{..} = do
|
|||||||
|
|
||||||
-- 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) <- getMajorMinorV _tvVersion
|
v' <-
|
||||||
lift (getGHCForMajor mj mi _tvTarget) >>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
|
handle (\(e :: ParseError) -> lift $ $(logWarn) [i|#{e}|] >> pure Nothing)
|
||||||
|
$ fmap Just
|
||||||
|
$ getMajorMinorV _tvVersion
|
||||||
|
forM_ v' $ \(mj, mi) -> lift (getGHCForMajor mj mi _tvTarget)
|
||||||
|
>>= mapM_ (\v -> liftE $ setGHC v SetGHC_XY)
|
||||||
|
|
||||||
|
@ -89,6 +89,9 @@ data JSONError = JSONDecodeError String
|
|||||||
data FileDoesNotExistError = FileDoesNotExistError ByteString
|
data FileDoesNotExistError = FileDoesNotExistError ByteString
|
||||||
deriving Show
|
deriving Show
|
||||||
|
|
||||||
|
data TarDirDoesNotExist = TarDirDoesNotExist TarDir
|
||||||
|
deriving Show
|
||||||
|
|
||||||
-- | File digest verification failed.
|
-- | File digest verification failed.
|
||||||
data DigestError = DigestError Text Text
|
data DigestError = DigestError Text Text
|
||||||
deriving Show
|
deriving Show
|
||||||
|
@ -137,7 +137,7 @@ data LinuxDistro = Debian
|
|||||||
-- to download, extract and install a tool.
|
-- to download, extract and install a tool.
|
||||||
data DownloadInfo = DownloadInfo
|
data DownloadInfo = DownloadInfo
|
||||||
{ _dlUri :: URI
|
{ _dlUri :: URI
|
||||||
, _dlSubdir :: Maybe (Path Rel)
|
, _dlSubdir :: Maybe TarDir
|
||||||
, _dlHash :: Text
|
, _dlHash :: Text
|
||||||
}
|
}
|
||||||
deriving (Eq, Show)
|
deriving (Eq, Show)
|
||||||
@ -150,6 +150,12 @@ data DownloadInfo = DownloadInfo
|
|||||||
--------------
|
--------------
|
||||||
|
|
||||||
|
|
||||||
|
-- | How to descend into a tar archive.
|
||||||
|
data TarDir = RealDir (Path Rel)
|
||||||
|
| RegexDir String -- ^ will be compiled to regex, the first match will "win"
|
||||||
|
deriving (Eq, Show)
|
||||||
|
|
||||||
|
|
||||||
-- | Where to fetch GHCupDownloads from.
|
-- | Where to fetch GHCupDownloads from.
|
||||||
data URLSource = GHCupURL
|
data URLSource = GHCupURL
|
||||||
| OwnSource URI
|
| OwnSource URI
|
||||||
|
@ -193,3 +193,7 @@ instance FromJSON (Path Rel) where
|
|||||||
case parseRel d of
|
case parseRel d of
|
||||||
Right x -> pure x
|
Right x -> pure x
|
||||||
Left e -> fail $ "Failure in HPath Rel (FromJSON)" <> show e
|
Left e -> fail $ "Failure in HPath Rel (FromJSON)" <> show e
|
||||||
|
|
||||||
|
|
||||||
|
deriveJSON defaultOptions{ sumEncoding = ObjectWithSingleField } ''TarDir
|
||||||
|
|
||||||
|
@ -48,7 +48,9 @@ import Control.Monad.Logger
|
|||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
import Data.ByteString ( ByteString )
|
import Data.ByteString ( ByteString )
|
||||||
import Data.Either
|
import Data.Either
|
||||||
|
import Data.Foldable
|
||||||
import Data.List
|
import Data.List
|
||||||
|
import Data.List.Split
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.String.Interpolate
|
import Data.String.Interpolate
|
||||||
import Data.Text ( Text )
|
import Data.Text ( Text )
|
||||||
@ -403,6 +405,28 @@ unpackToDir dest av = do
|
|||||||
| otherwise -> throwE $ UnknownArchive fn
|
| otherwise -> throwE $ UnknownArchive fn
|
||||||
|
|
||||||
|
|
||||||
|
intoSubdir :: (MonadLogger m, MonadIO m, MonadThrow m, MonadCatch m)
|
||||||
|
=> Path Abs -- ^ unpacked tar dir
|
||||||
|
-> TarDir -- ^ how to descend
|
||||||
|
-> Excepts '[TarDirDoesNotExist] m (Path Abs)
|
||||||
|
intoSubdir bdir tardir = case tardir of
|
||||||
|
RealDir pr -> do
|
||||||
|
whenM (fmap not . liftIO . doesDirectoryExist $ (bdir </> pr))
|
||||||
|
(throwE $ TarDirDoesNotExist tardir)
|
||||||
|
pure (bdir </> pr)
|
||||||
|
RegexDir r -> do
|
||||||
|
let rs = splitOn "/" r
|
||||||
|
foldlM
|
||||||
|
(\y x ->
|
||||||
|
(fmap sort . handleIO (\_ -> pure []) . liftIO . findFiles y . regex $ x) >>= \case
|
||||||
|
[] -> throwE $ TarDirDoesNotExist tardir
|
||||||
|
(p : _) -> pure (y </> p)
|
||||||
|
)
|
||||||
|
bdir
|
||||||
|
rs
|
||||||
|
where regex = makeRegexOpts compIgnoreCase execBlank
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
------------
|
------------
|
||||||
|
@ -166,7 +166,6 @@ ghcupGHCDir :: (MonadReader Settings m, MonadThrow m)
|
|||||||
=> GHCTargetVersion
|
=> GHCTargetVersion
|
||||||
-> m (Path Abs)
|
-> m (Path Abs)
|
||||||
ghcupGHCDir ver = do
|
ghcupGHCDir ver = do
|
||||||
Settings {..} <- ask
|
|
||||||
ghcbasedir <- ghcupGHCBaseDir
|
ghcbasedir <- ghcupGHCBaseDir
|
||||||
verdir <- parseRel $ E.encodeUtf8 (prettyTVer ver)
|
verdir <- parseRel $ E.encodeUtf8 (prettyTVer ver)
|
||||||
pure (ghcbasedir </> verdir)
|
pure (ghcbasedir </> verdir)
|
||||||
|
Loading…
Reference in New Issue
Block a user