Merge remote-tracking branch 'origin/merge-requests/70'
This commit is contained in:
@@ -137,30 +137,8 @@ getDownloadsF urlSource = do
|
||||
bsExt <- reThrowAll DownloadFailed $ downloadBS uri
|
||||
ext <- lE' JSONDecodeError $ bimap show id $ Y.decodeEither' (L.toStrict bsExt)
|
||||
pure (mergeGhcupInfo base ext)
|
||||
where
|
||||
readFromCache :: (MonadIO m, MonadCatch m, MonadLogger m, MonadReader AppState m)
|
||||
=> Excepts '[JSONError, FileDoesNotExistError] m GHCupInfo
|
||||
readFromCache = do
|
||||
AppState {dirs = Dirs {..}} <- lift ask
|
||||
lift $ $(logWarn)
|
||||
[i|Could not get download info, trying cached version (this may not be recent!)|]
|
||||
let path = view pathL' ghcupURL
|
||||
yaml_file <- (cacheDir </>) <$> urlBaseName path
|
||||
bs <-
|
||||
handleIO' NoSuchThing
|
||||
(\_ -> throwE $ FileDoesNotExistError (toFilePath yaml_file))
|
||||
$ liftIO
|
||||
$ readFile yaml_file
|
||||
lE' JSONDecodeError $ bimap show id $ Y.decodeEither' (L.toStrict bs)
|
||||
|
||||
getBase :: (MonadFail m, MonadIO m, MonadCatch m, MonadLogger m, MonadReader AppState m)
|
||||
=> Excepts '[JSONError , FileDoesNotExistError] m GHCupInfo
|
||||
getBase =
|
||||
handleIO (\_ -> readFromCache)
|
||||
$ catchE @_ @'[JSONError, FileDoesNotExistError]
|
||||
(\(DownloadFailed _) -> readFromCache)
|
||||
$ ((reThrowAll @_ @_ @'[JSONError, DownloadFailed] DownloadFailed $ smartDl ghcupURL)
|
||||
>>= (liftE . lE' @_ @_ @'[JSONError] JSONDecodeError . bimap show id . Y.decodeEither' . L.toStrict))
|
||||
where
|
||||
|
||||
mergeGhcupInfo :: GHCupInfo -- ^ base to merge with
|
||||
-> GHCupInfo -- ^ extension overwriting the base
|
||||
@@ -172,6 +150,32 @@ getDownloadsF urlSource = do
|
||||
) base
|
||||
in GHCupInfo tr new
|
||||
|
||||
|
||||
readFromCache :: (MonadIO m, MonadCatch m, MonadLogger m, MonadReader AppState m)
|
||||
=> Excepts '[JSONError, FileDoesNotExistError] m GHCupInfo
|
||||
readFromCache = do
|
||||
AppState {dirs = Dirs {..}} <- lift ask
|
||||
lift $ $(logWarn)
|
||||
[i|Could not get download info, trying cached version (this may not be recent!)|]
|
||||
let path = view pathL' ghcupURL
|
||||
yaml_file <- (cacheDir </>) <$> urlBaseName path
|
||||
bs <-
|
||||
handleIO' NoSuchThing
|
||||
(\_ -> throwE $ FileDoesNotExistError (toFilePath yaml_file))
|
||||
$ liftIO
|
||||
$ readFile yaml_file
|
||||
lE' JSONDecodeError $ bimap show id $ Y.decodeEither' (L.toStrict bs)
|
||||
|
||||
|
||||
getBase :: (MonadFail m, MonadIO m, MonadCatch m, MonadLogger m, MonadReader AppState m)
|
||||
=> Excepts '[JSONError , FileDoesNotExistError] m GHCupInfo
|
||||
getBase =
|
||||
handleIO (\_ -> readFromCache)
|
||||
$ catchE @_ @'[JSONError, FileDoesNotExistError]
|
||||
(\(DownloadFailed _) -> readFromCache)
|
||||
$ ((reThrowAll @_ @_ @'[JSONError, DownloadFailed] DownloadFailed $ smartDl ghcupURL)
|
||||
>>= (liftE . lE' @_ @_ @'[JSONError] JSONDecodeError . bimap show id . Y.decodeEither' . L.toStrict))
|
||||
where
|
||||
-- First check if the json file is in the ~/.ghcup/cache dir
|
||||
-- and check it's access time. If it has been accessed within the
|
||||
-- last 5 minutes, just reuse it.
|
||||
@@ -209,8 +213,8 @@ getDownloadsF urlSource = do
|
||||
then do
|
||||
accessTime <-
|
||||
PF.accessTimeHiRes
|
||||
<$> (liftIO $ PF.getFileStatus (toFilePath json_file))
|
||||
currentTime <- liftIO $ getPOSIXTime
|
||||
<$> liftIO (PF.getFileStatus (toFilePath json_file))
|
||||
currentTime <- liftIO getPOSIXTime
|
||||
|
||||
-- access time won't work on most linuxes, but we can try regardless
|
||||
if (currentTime - accessTime) > 300
|
||||
|
||||
@@ -808,3 +808,12 @@ getVersionInfo v' tool dls =
|
||||
% _head
|
||||
)
|
||||
dls
|
||||
|
||||
|
||||
-- Gathering monoidal values
|
||||
traverseFold :: (Foldable t, Applicative m, Monoid b) => (a -> m b) -> t a -> m b
|
||||
traverseFold f = foldl (\mb a -> (<>) <$> mb <*> f a) (pure mempty)
|
||||
|
||||
-- | Gathering monoidal values
|
||||
forFold :: (Foldable t, Applicative m, Monoid b) => t a -> (a -> m b) -> m b
|
||||
forFold = flip traverseFold
|
||||
|
||||
@@ -185,9 +185,9 @@ getDirs = do
|
||||
ghcupConfigFile :: (MonadIO m)
|
||||
=> Excepts '[JSONError] m UserSettings
|
||||
ghcupConfigFile = do
|
||||
confDir <- liftIO $ ghcupConfigDir
|
||||
confDir <- liftIO ghcupConfigDir
|
||||
let file = confDir </> [rel|config.yaml|]
|
||||
bs <- liftIO $ handleIO' NoSuchThing (\_ -> pure $ Nothing) $ fmap Just $ readFile file
|
||||
bs <- liftIO $ handleIO' NoSuchThing (\_ -> pure Nothing) $ Just <$> readFile file
|
||||
case bs of
|
||||
Nothing -> pure defaultUserSettings
|
||||
Just bs' -> lE' JSONDecodeError . bimap show id . Y.decodeEither' . L.toStrict $ bs'
|
||||
|
||||
Reference in New Issue
Block a user