{-# LANGUAGE CPP                   #-}
{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE ViewPatterns          #-}
{-# LANGUAGE QuasiQuotes           #-}

{-|
Module      : GHCup.Utils.Dirs
Description : Definition of GHCup directories
Copyright   : (c) Julian Ospald, 2020
License     : LGPL-3.0
Maintainer  : hasufell@hasufell.de
Stability   : experimental
Portability : portable
-}
module GHCup.Utils.Dirs
  ( getAllDirs
  , ghcupBaseDir
  , ghcupConfigFile
  , ghcupCacheDir
  , ghcupGHCBaseDir
  , ghcupGHCDir
  , ghcupHLSBaseDir
  , ghcupHLSDir
  , mkGhcupTmpDir
  , parseGHCupGHCDir
  , parseGHCupHLSDir
  , relativeSymlink
  , withGHCupTmpDir
  , getConfigFilePath
  , useXDG
  , cleanupTrash

  , GHCupPath
  , appendGHCupPath
  , fromGHCupPath
  , createTempGHCupDirectory
  , getGHCupTmpDirs

  , removeDirectory
  , removeDirectoryRecursive
  , removePathForcibly

  -- System.Directory re-exports
  , createDirectory
  , createDirectoryIfMissing
  , renameDirectory
  , listDirectory
  , getDirectoryContents
  , getCurrentDirectory
  , setCurrentDirectory
  , withCurrentDirectory
  , getHomeDirectory
  , XdgDirectory(..)
  , getXdgDirectory
  , XdgDirectoryList(..)
  , getXdgDirectoryList
  , getAppUserDataDirectory
  , getUserDocumentsDirectory
  , getTemporaryDirectory
  , removeFile
  , renameFile
  , renamePath
  , getFileSize
  , canonicalizePath
  , makeAbsolute
  , makeRelativeToCurrentDirectory
  , doesPathExist
  , doesFileExist
  , doesDirectoryExist
  , findExecutable
  , findExecutables
  , findExecutablesInDirectories
  , findFile
  , findFileWith
  , findFilesWith
  , exeExtension
  , createFileLink
  , createDirectoryLink
  , removeDirectoryLink
  , pathIsSymbolicLink
  , getSymbolicLinkTarget
  , Permissions
  , emptyPermissions
  , readable
  , writable
  , executable
  , searchable
  , setOwnerReadable
  , setOwnerWritable
  , setOwnerExecutable
  , setOwnerSearchable
  , getPermissions
  , setPermissions
  , copyPermissions
  , getAccessTime
  , getModificationTime
  , setAccessTime
  , setModificationTime
  , isSymbolicLink
  )
where


import           GHCup.Errors
import           GHCup.Types
import           GHCup.Types.JSON               ( )
import           GHCup.Types.Optics
import           GHCup.Prelude.MegaParsec
import           GHCup.Prelude.File.Search
import           GHCup.Prelude.String.QQ
import           GHCup.Prelude.Logger.Internal (logWarn, logDebug)
#if defined(IS_WINDOWS)
import           GHCup.Prelude.Windows ( isWindows )
#else
import           GHCup.Prelude.Posix   ( isWindows )
#endif

import           Control.DeepSeq (NFData, rnf)
import           Control.Exception.Safe
import           Control.Monad
import           Control.Monad.IO.Unlift
import           Control.Monad.Reader
import           Control.Monad.Trans.Resource hiding (throwM)
import           Data.List
import           Data.ByteString                ( ByteString )
import           Data.Bifunctor
import           Data.Maybe
import           Data.Versions
import           GHC.IO.Exception               ( IOErrorType(NoSuchThing) )
import           Haskus.Utils.Variant.Excepts
import           Optics
import           Safe
import           System.Directory hiding ( removeDirectory
                                         , removeDirectoryRecursive
                                         , removePathForcibly
                                         , findFiles
                                         )
import qualified System.Directory              as SD

import           System.Environment
import           System.FilePath
import           System.IO.Temp
import           Text.Regex.Posix

import qualified Data.ByteString               as BS
import qualified Data.Text                     as T
import qualified Data.Yaml.Aeson               as Y
import qualified Text.Megaparsec               as MP
import System.IO.Error (ioeGetErrorType)



    ---------------------------
    --[ GHCupPath utilities ]--
    ---------------------------

-- | A 'GHCupPath' is a safe sub-path that can be recursively deleted.
--
-- The constructor is not exported.
newtype GHCupPath = GHCupPath FilePath
  deriving (Int -> GHCupPath -> ShowS
[GHCupPath] -> ShowS
GHCupPath -> String
(Int -> GHCupPath -> ShowS)
-> (GHCupPath -> String)
-> ([GHCupPath] -> ShowS)
-> Show GHCupPath
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GHCupPath] -> ShowS
$cshowList :: [GHCupPath] -> ShowS
show :: GHCupPath -> String
$cshow :: GHCupPath -> String
showsPrec :: Int -> GHCupPath -> ShowS
$cshowsPrec :: Int -> GHCupPath -> ShowS
Show, GHCupPath -> GHCupPath -> Bool
(GHCupPath -> GHCupPath -> Bool)
-> (GHCupPath -> GHCupPath -> Bool) -> Eq GHCupPath
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GHCupPath -> GHCupPath -> Bool
$c/= :: GHCupPath -> GHCupPath -> Bool
== :: GHCupPath -> GHCupPath -> Bool
$c== :: GHCupPath -> GHCupPath -> Bool
Eq, Eq GHCupPath
Eq GHCupPath
-> (GHCupPath -> GHCupPath -> Ordering)
-> (GHCupPath -> GHCupPath -> Bool)
-> (GHCupPath -> GHCupPath -> Bool)
-> (GHCupPath -> GHCupPath -> Bool)
-> (GHCupPath -> GHCupPath -> Bool)
-> (GHCupPath -> GHCupPath -> GHCupPath)
-> (GHCupPath -> GHCupPath -> GHCupPath)
-> Ord GHCupPath
GHCupPath -> GHCupPath -> Bool
GHCupPath -> GHCupPath -> Ordering
GHCupPath -> GHCupPath -> GHCupPath
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GHCupPath -> GHCupPath -> GHCupPath
$cmin :: GHCupPath -> GHCupPath -> GHCupPath
max :: GHCupPath -> GHCupPath -> GHCupPath
$cmax :: GHCupPath -> GHCupPath -> GHCupPath
>= :: GHCupPath -> GHCupPath -> Bool
$c>= :: GHCupPath -> GHCupPath -> Bool
> :: GHCupPath -> GHCupPath -> Bool
$c> :: GHCupPath -> GHCupPath -> Bool
<= :: GHCupPath -> GHCupPath -> Bool
$c<= :: GHCupPath -> GHCupPath -> Bool
< :: GHCupPath -> GHCupPath -> Bool
$c< :: GHCupPath -> GHCupPath -> Bool
compare :: GHCupPath -> GHCupPath -> Ordering
$ccompare :: GHCupPath -> GHCupPath -> Ordering
$cp1Ord :: Eq GHCupPath
Ord)

instance NFData GHCupPath where
  rnf :: GHCupPath -> ()
rnf (GHCupPath String
fp) = String -> ()
forall a. NFData a => a -> ()
rnf String
fp

appendGHCupPath :: GHCupPath -> FilePath -> GHCupPath
appendGHCupPath :: GHCupPath -> String -> GHCupPath
appendGHCupPath (GHCupPath String
gp) String
fp = String -> GHCupPath
GHCupPath (String
gp String -> ShowS
</> String
fp)

fromGHCupPath :: GHCupPath -> FilePath
fromGHCupPath :: GHCupPath -> String
fromGHCupPath (GHCupPath String
gp) = String
gp

createTempGHCupDirectory :: GHCupPath -> FilePath -> IO GHCupPath
createTempGHCupDirectory :: GHCupPath -> String -> IO GHCupPath
createTempGHCupDirectory (GHCupPath String
gp) String
d = String -> GHCupPath
GHCupPath (String -> GHCupPath) -> IO String -> IO GHCupPath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> String -> IO String
createTempDirectory String
gp String
d


getGHCupTmpDirs :: IO [GHCupPath]
getGHCupTmpDirs :: IO [GHCupPath]
getGHCupTmpDirs = do
  String
tmpdir <- GHCupPath -> String
fromGHCupPath (GHCupPath -> String) -> IO GHCupPath -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO GHCupPath
ghcupTMPDir
  [String]
ghcup_dirs <- (IOException -> IO [String]) -> IO [String] -> IO [String]
forall (m :: * -> *) a.
MonadCatch m =>
(IOException -> m a) -> m a -> m a
handleIO (\IOException
_ -> [String] -> IO [String]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []) (IO [String] -> IO [String]) -> IO [String] -> IO [String]
forall a b. (a -> b) -> a -> b
$ String -> Regex -> IO [String]
findFiles
    String
tmpdir
    (CompOption -> ExecOption -> ByteString -> Regex
forall regex compOpt execOpt source.
RegexMaker regex compOpt execOpt source =>
compOpt -> execOpt -> source -> regex
makeRegexOpts CompOption
compExtended
                   ExecOption
execBlank
                   ([s|^ghcup-.*$|] :: ByteString)
    )
  [GHCupPath] -> IO [GHCupPath]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((String -> GHCupPath) -> [String] -> [GHCupPath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\String
p -> String -> GHCupPath
GHCupPath (String
tmpdir String -> ShowS
</> String
p)) ([String] -> [GHCupPath]) -> [String] -> [GHCupPath]
forall a b. (a -> b) -> a -> b
$ (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> (String -> Bool) -> Maybe String -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (String
"ghcup-" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf`) (Maybe String -> Bool)
-> (String -> Maybe String) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> Maybe String
forall a. [a] -> Maybe a
lastMay ([String] -> Maybe String)
-> (String -> [String]) -> String -> Maybe String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
splitPath) [String]
ghcup_dirs)


    ------------------------------
    --[ GHCup base directories ]--
    ------------------------------


-- | ~/.ghcup by default
--
-- If 'GHCUP_USE_XDG_DIRS' is set (to anything),
-- then uses 'XDG_DATA_HOME/ghcup' as per xdg spec.
ghcupBaseDir :: IO GHCupPath
ghcupBaseDir :: IO GHCupPath
ghcupBaseDir
  | Bool
isWindows = do
      String
bdir <- String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"C:\\" (Maybe String -> String) -> IO (Maybe String) -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO (Maybe String)
lookupEnv String
"GHCUP_INSTALL_BASE_PREFIX"
      GHCupPath -> IO GHCupPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> GHCupPath
GHCupPath (String
bdir String -> ShowS
</> String
"ghcup"))
  | Bool
otherwise = do
      Bool
xdg <- IO Bool
useXDG
      if Bool
xdg
        then do
          String
bdir <- String -> IO (Maybe String)
lookupEnv String
"XDG_DATA_HOME" IO (Maybe String) -> (Maybe String -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            Just String
r  -> String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
r
            Maybe String
Nothing -> do
              String
home <- IO String -> IO String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO String
getHomeDirectory
              String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String
home String -> ShowS
</> String
".local" String -> ShowS
</> String
"share")
          GHCupPath -> IO GHCupPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> GHCupPath
GHCupPath (String
bdir String -> ShowS
</> String
"ghcup"))
        else do
          String
bdir <- String -> IO (Maybe String)
lookupEnv String
"GHCUP_INSTALL_BASE_PREFIX" IO (Maybe String) -> (Maybe String -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            Just String
r  -> String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
r
            Maybe String
Nothing -> IO String -> IO String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO String
getHomeDirectory
          GHCupPath -> IO GHCupPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> GHCupPath
GHCupPath (String
bdir String -> ShowS
</> String
".ghcup"))


-- | ~/.ghcup by default
--
-- If 'GHCUP_USE_XDG_DIRS' is set (to anything),
-- then uses 'XDG_CONFIG_HOME/ghcup' as per xdg spec.
ghcupConfigDir :: IO GHCupPath
ghcupConfigDir :: IO GHCupPath
ghcupConfigDir
  | Bool
isWindows = IO GHCupPath
ghcupBaseDir
  | Bool
otherwise = do
      Bool
xdg <- IO Bool
useXDG
      if Bool
xdg
        then do
          String
bdir <- String -> IO (Maybe String)
lookupEnv String
"XDG_CONFIG_HOME" IO (Maybe String) -> (Maybe String -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            Just String
r  -> String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
r
            Maybe String
Nothing -> do
              String
home <- IO String -> IO String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO String
getHomeDirectory
              String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String
home String -> ShowS
</> String
".config")
          GHCupPath -> IO GHCupPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> GHCupPath
GHCupPath (String
bdir String -> ShowS
</> String
"ghcup"))
        else do
          String
bdir <- String -> IO (Maybe String)
lookupEnv String
"GHCUP_INSTALL_BASE_PREFIX" IO (Maybe String) -> (Maybe String -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            Just String
r  -> String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
r
            Maybe String
Nothing -> IO String -> IO String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO String
getHomeDirectory
          GHCupPath -> IO GHCupPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> GHCupPath
GHCupPath (String
bdir String -> ShowS
</> String
".ghcup"))


-- | If 'GHCUP_USE_XDG_DIRS' is set (to anything),
-- then uses 'XDG_BIN_HOME' env var or defaults to '~/.local/bin'
-- (which, sadly is not strictly xdg spec).
ghcupBinDir :: IO FilePath
ghcupBinDir :: IO String
ghcupBinDir
  | Bool
isWindows = (GHCupPath -> String
fromGHCupPath (GHCupPath -> String) -> IO GHCupPath -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO GHCupPath
ghcupBaseDir) IO String -> ShowS -> IO String
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (String -> ShowS
</> String
"bin")
  | Bool
otherwise = do
      Bool
xdg <- IO Bool
useXDG
      if Bool
xdg
        then do
          String -> IO (Maybe String)
lookupEnv String
"XDG_BIN_HOME" IO (Maybe String) -> (Maybe String -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            Just String
r  -> String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
r
            Maybe String
Nothing -> do
              String
home <- IO String -> IO String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO String
getHomeDirectory
              String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String
home String -> ShowS
</> String
".local" String -> ShowS
</> String
"bin")
        else (GHCupPath -> String
fromGHCupPath (GHCupPath -> String) -> IO GHCupPath -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO GHCupPath
ghcupBaseDir) IO String -> ShowS -> IO String
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (String -> ShowS
</> String
"bin")


-- | Defaults to '~/.ghcup/cache'.
--
-- If 'GHCUP_USE_XDG_DIRS' is set (to anything),
-- then uses 'XDG_CACHE_HOME/ghcup' as per xdg spec.
ghcupCacheDir :: IO GHCupPath
ghcupCacheDir :: IO GHCupPath
ghcupCacheDir
  | Bool
isWindows = IO GHCupPath
ghcupBaseDir IO GHCupPath -> (GHCupPath -> GHCupPath) -> IO GHCupPath
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (\(GHCupPath String
gp) -> String -> GHCupPath
GHCupPath (String
gp String -> ShowS
</> String
"cache"))
  | Bool
otherwise = do
      Bool
xdg <- IO Bool
useXDG
      if Bool
xdg
        then do
          String
bdir <- String -> IO (Maybe String)
lookupEnv String
"XDG_CACHE_HOME" IO (Maybe String) -> (Maybe String -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            Just String
r  -> String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
r
            Maybe String
Nothing -> do
              String
home <- IO String -> IO String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO String
getHomeDirectory
              String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String
home String -> ShowS
</> String
".cache")
          GHCupPath -> IO GHCupPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> GHCupPath
GHCupPath (String
bdir String -> ShowS
</> String
"ghcup"))
        else IO GHCupPath
ghcupBaseDir IO GHCupPath -> (GHCupPath -> GHCupPath) -> IO GHCupPath
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (\(GHCupPath String
gp) -> String -> GHCupPath
GHCupPath (String
gp String -> ShowS
</> String
"cache"))


-- | Defaults to '~/.ghcup/logs'.
--
-- If 'GHCUP_USE_XDG_DIRS' is set (to anything),
-- then uses 'XDG_CACHE_HOME/ghcup/logs' as per xdg spec.
ghcupLogsDir :: IO GHCupPath
ghcupLogsDir :: IO GHCupPath
ghcupLogsDir
  | Bool
isWindows = IO GHCupPath
ghcupBaseDir IO GHCupPath -> (GHCupPath -> GHCupPath) -> IO GHCupPath
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (\(GHCupPath String
gp) -> String -> GHCupPath
GHCupPath (String
gp String -> ShowS
</> String
"logs"))
  | Bool
otherwise = do
      Bool
xdg <- IO Bool
useXDG
      if Bool
xdg
        then do
          String
bdir <- String -> IO (Maybe String)
lookupEnv String
"XDG_CACHE_HOME" IO (Maybe String) -> (Maybe String -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            Just String
r  -> String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
r
            Maybe String
Nothing -> do
              String
home <- IO String -> IO String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO String
getHomeDirectory
              String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String
home String -> ShowS
</> String
".cache")
          GHCupPath -> IO GHCupPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> GHCupPath
GHCupPath (String
bdir String -> ShowS
</> String
"ghcup" String -> ShowS
</> String
"logs"))
        else IO GHCupPath
ghcupBaseDir IO GHCupPath -> (GHCupPath -> GHCupPath) -> IO GHCupPath
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (\(GHCupPath String
gp) -> String -> GHCupPath
GHCupPath (String
gp String -> ShowS
</> String
"logs"))


-- | Defaults to '~/.ghcup/db.
--
-- If 'GHCUP_USE_XDG_DIRS' is set (to anything),
-- then uses 'XDG_CACHE_HOME/ghcup/db as per xdg spec.
ghcupDbDir :: IO GHCupPath
ghcupDbDir :: IO GHCupPath
ghcupDbDir
  | Bool
isWindows = IO GHCupPath
ghcupBaseDir IO GHCupPath -> (GHCupPath -> GHCupPath) -> IO GHCupPath
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (\(GHCupPath String
gp) -> String -> GHCupPath
GHCupPath (String
gp String -> ShowS
</> String
"db"))
  | Bool
otherwise = do
      Bool
xdg <- IO Bool
useXDG
      if Bool
xdg
        then do
          String
bdir <- String -> IO (Maybe String)
lookupEnv String
"XDG_CACHE_HOME" IO (Maybe String) -> (Maybe String -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            Just String
r  -> String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
r
            Maybe String
Nothing -> do
              String
home <- IO String -> IO String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO String
getHomeDirectory
              String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String
home String -> ShowS
</> String
".cache")
          GHCupPath -> IO GHCupPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> GHCupPath
GHCupPath (String
bdir String -> ShowS
</> String
"ghcup" String -> ShowS
</> String
"db"))
        else IO GHCupPath
ghcupBaseDir IO GHCupPath -> (GHCupPath -> GHCupPath) -> IO GHCupPath
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (\(GHCupPath String
gp) -> String -> GHCupPath
GHCupPath (String
gp String -> ShowS
</> String
"db"))


-- | '~/.ghcup/trash'.
-- Mainly used on windows to improve file removal operations
ghcupRecycleDir :: IO GHCupPath
ghcupRecycleDir :: IO GHCupPath
ghcupRecycleDir = IO GHCupPath
ghcupBaseDir IO GHCupPath -> (GHCupPath -> GHCupPath) -> IO GHCupPath
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (\(GHCupPath String
gp) -> String -> GHCupPath
GHCupPath (String
gp String -> ShowS
</> String
"trash"))


-- | Defaults to '~/.ghcup/tmp.
--
-- If 'GHCUP_USE_XDG_DIRS' is set (to anything),
-- then uses 'XDG_CACHE_HOME/ghcup/tmp as per xdg spec.
ghcupTMPDir :: IO GHCupPath
ghcupTMPDir :: IO GHCupPath
ghcupTMPDir
  | Bool
isWindows = IO GHCupPath
ghcupBaseDir IO GHCupPath -> (GHCupPath -> GHCupPath) -> IO GHCupPath
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (\(GHCupPath String
gp) -> String -> GHCupPath
GHCupPath (String
gp String -> ShowS
</> String
"tmp"))
  | Bool
otherwise = do
      Bool
xdg <- IO Bool
useXDG
      if Bool
xdg
        then do
          String
bdir <- String -> IO (Maybe String)
lookupEnv String
"XDG_CACHE_HOME" IO (Maybe String) -> (Maybe String -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            Just String
r  -> String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
r
            Maybe String
Nothing -> do
              String
home <- IO String -> IO String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO String
getHomeDirectory
              String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String
home String -> ShowS
</> String
".cache")
          GHCupPath -> IO GHCupPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> GHCupPath
GHCupPath (String
bdir String -> ShowS
</> String
"ghcup" String -> ShowS
</> String
"tmp"))
        else IO GHCupPath
ghcupBaseDir IO GHCupPath -> (GHCupPath -> GHCupPath) -> IO GHCupPath
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (\(GHCupPath String
gp) -> String -> GHCupPath
GHCupPath (String
gp String -> ShowS
</> String
"tmp"))


getAllDirs :: IO Dirs
getAllDirs :: IO Dirs
getAllDirs = do
  GHCupPath
baseDir    <- IO GHCupPath
ghcupBaseDir
  String
binDir     <- IO String
ghcupBinDir
  GHCupPath
cacheDir   <- IO GHCupPath
ghcupCacheDir
  GHCupPath
logsDir    <- IO GHCupPath
ghcupLogsDir
  GHCupPath
confDir    <- IO GHCupPath
ghcupConfigDir
  GHCupPath
recycleDir <- IO GHCupPath
ghcupRecycleDir
  GHCupPath
tmpDir     <- IO GHCupPath
ghcupTMPDir
  GHCupPath
dbDir      <- IO GHCupPath
ghcupDbDir
  Dirs -> IO Dirs
forall (f :: * -> *) a. Applicative f => a -> f a
pure Dirs :: GHCupPath
-> String
-> GHCupPath
-> GHCupPath
-> GHCupPath
-> GHCupPath
-> GHCupPath
-> GHCupPath
-> Dirs
Dirs { String
GHCupPath
$sel:tmpDir:Dirs :: GHCupPath
$sel:recycleDir:Dirs :: GHCupPath
$sel:dbDir:Dirs :: GHCupPath
$sel:confDir:Dirs :: GHCupPath
$sel:logsDir:Dirs :: GHCupPath
$sel:cacheDir:Dirs :: GHCupPath
$sel:binDir:Dirs :: String
$sel:baseDir:Dirs :: GHCupPath
dbDir :: GHCupPath
tmpDir :: GHCupPath
recycleDir :: GHCupPath
confDir :: GHCupPath
logsDir :: GHCupPath
cacheDir :: GHCupPath
binDir :: String
baseDir :: GHCupPath
.. }



    -------------------
    --[ GHCup files ]--
    -------------------

getConfigFilePath :: (MonadIO m) => m FilePath
getConfigFilePath :: m String
getConfigFilePath = do
  GHCupPath
confDir <- IO GHCupPath -> m GHCupPath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO GHCupPath
ghcupConfigDir
  String -> m String
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> m String) -> String -> m String
forall a b. (a -> b) -> a -> b
$ GHCupPath -> String
fromGHCupPath GHCupPath
confDir String -> ShowS
</> String
"config.yaml"

ghcupConfigFile :: (MonadIO m)
                => Excepts '[JSONError] m UserSettings
ghcupConfigFile :: Excepts '[JSONError] m UserSettings
ghcupConfigFile = do
  String
filepath <- Excepts '[JSONError] m String
forall (m :: * -> *). MonadIO m => m String
getConfigFilePath
  Maybe ByteString
contents <- IO (Maybe ByteString) -> Excepts '[JSONError] m (Maybe ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ByteString)
 -> Excepts '[JSONError] m (Maybe ByteString))
-> IO (Maybe ByteString)
-> Excepts '[JSONError] m (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ (IOException -> IO (Maybe ByteString))
-> IO (Maybe ByteString) -> IO (Maybe ByteString)
forall (m :: * -> *) a.
MonadCatch m =>
(IOException -> m a) -> m a -> m a
handleIO (\IOException
e -> if IOErrorType
NoSuchThing IOErrorType -> IOErrorType -> Bool
forall a. Eq a => a -> a -> Bool
== IOException -> IOErrorType
ioeGetErrorType IOException
e then Maybe ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe ByteString
forall a. Maybe a
Nothing else IO (Maybe ByteString) -> IO (Maybe ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ByteString) -> IO (Maybe ByteString))
-> IO (Maybe ByteString) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ IOException -> IO (Maybe ByteString)
forall a. IOException -> IO a
ioError IOException
e) (IO (Maybe ByteString) -> IO (Maybe ByteString))
-> IO (Maybe ByteString) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO ByteString
BS.readFile String
filepath
  case Maybe ByteString
contents of
      Maybe ByteString
Nothing -> UserSettings -> Excepts '[JSONError] m UserSettings
forall (f :: * -> *) a. Applicative f => a -> f a
pure UserSettings
defaultUserSettings
      Just ByteString
contents' -> Excepts '[JSONError] m UserSettings
-> Excepts '[JSONError] m UserSettings
forall (es' :: [*]) (es :: [*]) a (m :: * -> *).
(Monad m, VEitherLift es es') =>
Excepts es m a -> Excepts es' m a
liftE
        (Excepts '[JSONError] m UserSettings
 -> Excepts '[JSONError] m UserSettings)
-> (ByteString -> Excepts '[JSONError] m UserSettings)
-> ByteString
-> Excepts '[JSONError] m UserSettings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Monad m =>
VEither '[JSONError] a -> Excepts '[JSONError] m a
forall (m :: * -> *) (es :: [*]) a.
Monad m =>
VEither es a -> Excepts es m a
veitherToExcepts @_ @'[JSONError]
        (VEither '[JSONError] UserSettings
 -> Excepts '[JSONError] m UserSettings)
-> (ByteString -> VEither '[JSONError] UserSettings)
-> ByteString
-> Excepts '[JSONError] m UserSettings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (JSONError -> VEither '[JSONError] UserSettings)
-> (UserSettings -> VEither '[JSONError] UserSettings)
-> Either JSONError UserSettings
-> VEither '[JSONError] UserSettings
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (V '[JSONError] -> VEither '[JSONError] UserSettings
forall x (xs :: [*]). V xs -> VEither xs x
VLeft (V '[JSONError] -> VEither '[JSONError] UserSettings)
-> (JSONError -> V '[JSONError])
-> JSONError
-> VEither '[JSONError] UserSettings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JSONError -> V '[JSONError]
forall c (cs :: [*]). (c :< cs) => c -> V cs
V) UserSettings -> VEither '[JSONError] UserSettings
forall x (xs :: [*]). x -> VEither xs x
VRight
        (Either JSONError UserSettings
 -> VEither '[JSONError] UserSettings)
-> (ByteString -> Either JSONError UserSettings)
-> ByteString
-> VEither '[JSONError] UserSettings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParseException -> JSONError)
-> Either ParseException UserSettings
-> Either JSONError UserSettings
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (String -> JSONError
JSONDecodeError (String -> JSONError)
-> (ParseException -> String) -> ParseException -> JSONError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseException -> String
forall e. Exception e => e -> String
displayException)
        (Either ParseException UserSettings
 -> Either JSONError UserSettings)
-> (ByteString -> Either ParseException UserSettings)
-> ByteString
-> Either JSONError UserSettings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either ParseException UserSettings
forall a. FromJSON a => ByteString -> Either ParseException a
Y.decodeEither'
        (ByteString -> Excepts '[JSONError] m UserSettings)
-> ByteString -> Excepts '[JSONError] m UserSettings
forall a b. (a -> b) -> a -> b
$ ByteString
contents'


    -------------------------
    --[ GHCup directories ]--
    -------------------------


-- | ~/.ghcup/ghc by default.
ghcupGHCBaseDir :: (MonadReader env m, HasDirs env) => m GHCupPath
ghcupGHCBaseDir :: m GHCupPath
ghcupGHCBaseDir = do
  Dirs {String
GHCupPath
tmpDir :: GHCupPath
recycleDir :: GHCupPath
dbDir :: GHCupPath
confDir :: GHCupPath
logsDir :: GHCupPath
cacheDir :: GHCupPath
binDir :: String
baseDir :: GHCupPath
$sel:tmpDir:Dirs :: Dirs -> GHCupPath
$sel:recycleDir:Dirs :: Dirs -> GHCupPath
$sel:dbDir:Dirs :: Dirs -> GHCupPath
$sel:confDir:Dirs :: Dirs -> GHCupPath
$sel:logsDir:Dirs :: Dirs -> GHCupPath
$sel:cacheDir:Dirs :: Dirs -> GHCupPath
$sel:binDir:Dirs :: Dirs -> String
$sel:baseDir:Dirs :: Dirs -> GHCupPath
..}  <- m Dirs
forall env (m :: * -> *).
(MonadReader env m, LabelOptic' "dirs" A_Lens env Dirs) =>
m Dirs
getDirs
  GHCupPath -> m GHCupPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GHCupPath
baseDir GHCupPath -> String -> GHCupPath
`appendGHCupPath` String
"ghc")


-- | Gets '~/.ghcup/ghc/<ghcupGHCDir>'.
-- The dir may be of the form
--   * armv7-unknown-linux-gnueabihf-8.8.3
--   * 8.8.4
ghcupGHCDir :: (MonadReader env m, HasDirs env, MonadThrow m)
            => GHCTargetVersion
            -> m GHCupPath
ghcupGHCDir :: GHCTargetVersion -> m GHCupPath
ghcupGHCDir GHCTargetVersion
ver = do
  GHCupPath
ghcbasedir <- m GHCupPath
forall env (m :: * -> *).
(MonadReader env m, HasDirs env) =>
m GHCupPath
ghcupGHCBaseDir
  let verdir :: String
verdir = Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ GHCTargetVersion -> Text
tVerToText GHCTargetVersion
ver
  GHCupPath -> m GHCupPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GHCupPath
ghcbasedir GHCupPath -> String -> GHCupPath
`appendGHCupPath` String
verdir)


-- | See 'ghcupToolParser'.
parseGHCupGHCDir :: MonadThrow m => FilePath -> m GHCTargetVersion
parseGHCupGHCDir :: String -> m GHCTargetVersion
parseGHCupGHCDir (String -> Text
T.pack -> Text
fp) =
  Either (ParseErrorBundle Text Void) GHCTargetVersion
-> m GHCTargetVersion
forall a (m :: * -> *) b.
(Exception a, MonadThrow m) =>
Either a b -> m b
throwEither (Either (ParseErrorBundle Text Void) GHCTargetVersion
 -> m GHCTargetVersion)
-> Either (ParseErrorBundle Text Void) GHCTargetVersion
-> m GHCTargetVersion
forall a b. (a -> b) -> a -> b
$ Parsec Void Text GHCTargetVersion
-> String
-> Text
-> Either (ParseErrorBundle Text Void) GHCTargetVersion
forall e s a.
Parsec e s a -> String -> s -> Either (ParseErrorBundle s e) a
MP.parse Parsec Void Text GHCTargetVersion
ghcTargetVerP String
"" Text
fp

parseGHCupHLSDir :: MonadThrow m => FilePath -> m Version
parseGHCupHLSDir :: String -> m Version
parseGHCupHLSDir (String -> Text
T.pack -> Text
fp) =
  Either (ParseErrorBundle Text Void) Version -> m Version
forall a (m :: * -> *) b.
(Exception a, MonadThrow m) =>
Either a b -> m b
throwEither (Either (ParseErrorBundle Text Void) Version -> m Version)
-> Either (ParseErrorBundle Text Void) Version -> m Version
forall a b. (a -> b) -> a -> b
$ Parsec Void Text Version
-> String -> Text -> Either (ParseErrorBundle Text Void) Version
forall e s a.
Parsec e s a -> String -> s -> Either (ParseErrorBundle s e) a
MP.parse Parsec Void Text Version
version' String
"" Text
fp

-- TODO: inlined from GHCup.Prelude
throwEither :: (Exception a, MonadThrow m) => Either a b -> m b
throwEither :: Either a b -> m b
throwEither Either a b
a = case Either a b
a of
  Left  a
e -> a -> m b
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM a
e
  Right b
r -> b -> m b
forall (f :: * -> *) a. Applicative f => a -> f a
pure b
r

-- | ~/.ghcup/hls by default, for new-style installs.
ghcupHLSBaseDir :: (MonadReader env m, HasDirs env) => m GHCupPath
ghcupHLSBaseDir :: m GHCupPath
ghcupHLSBaseDir = do
  Dirs {String
GHCupPath
tmpDir :: GHCupPath
recycleDir :: GHCupPath
dbDir :: GHCupPath
confDir :: GHCupPath
logsDir :: GHCupPath
cacheDir :: GHCupPath
binDir :: String
baseDir :: GHCupPath
$sel:tmpDir:Dirs :: Dirs -> GHCupPath
$sel:recycleDir:Dirs :: Dirs -> GHCupPath
$sel:dbDir:Dirs :: Dirs -> GHCupPath
$sel:confDir:Dirs :: Dirs -> GHCupPath
$sel:logsDir:Dirs :: Dirs -> GHCupPath
$sel:cacheDir:Dirs :: Dirs -> GHCupPath
$sel:binDir:Dirs :: Dirs -> String
$sel:baseDir:Dirs :: Dirs -> GHCupPath
..}  <- m Dirs
forall env (m :: * -> *).
(MonadReader env m, LabelOptic' "dirs" A_Lens env Dirs) =>
m Dirs
getDirs
  GHCupPath -> m GHCupPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GHCupPath
baseDir GHCupPath -> String -> GHCupPath
`appendGHCupPath` String
"hls")

-- | Gets '~/.ghcup/hls/<hls-ver>' for new-style installs.
ghcupHLSDir :: (MonadReader env m, HasDirs env, MonadThrow m)
            => Version
            -> m GHCupPath
ghcupHLSDir :: Version -> m GHCupPath
ghcupHLSDir Version
ver = do
  GHCupPath
basedir <- m GHCupPath
forall env (m :: * -> *).
(MonadReader env m, HasDirs env) =>
m GHCupPath
ghcupHLSBaseDir
  let verdir :: String
verdir = Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Version -> Text
prettyVer Version
ver
  GHCupPath -> m GHCupPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GHCupPath
basedir GHCupPath -> String -> GHCupPath
`appendGHCupPath` String
verdir)


mkGhcupTmpDir :: ( MonadReader env m
                 , HasDirs env
                 , MonadUnliftIO m
                 , HasLog env
                 , MonadCatch m
                 , MonadThrow m
                 , MonadMask m
                 , MonadIO m)
              => m GHCupPath
mkGhcupTmpDir :: m GHCupPath
mkGhcupTmpDir = String -> GHCupPath
GHCupPath (String -> GHCupPath) -> m String -> m GHCupPath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
  Dirs { GHCupPath
tmpDir :: GHCupPath
$sel:tmpDir:Dirs :: Dirs -> GHCupPath
tmpDir } <- m Dirs
forall env (m :: * -> *).
(MonadReader env m, LabelOptic' "dirs" A_Lens env Dirs) =>
m Dirs
getDirs
  IO String -> m String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ String -> String -> IO String
createTempDirectory (GHCupPath -> String
fromGHCupPath GHCupPath
tmpDir) String
"ghcup"


withGHCupTmpDir :: ( MonadReader env m
                   , HasDirs env
                   , HasLog env
                   , HasSettings env
                   , MonadUnliftIO m
                   , MonadCatch m
                   , MonadResource m
                   , MonadThrow m
                   , MonadMask m
                   , MonadIO m)
                => m GHCupPath
withGHCupTmpDir :: m GHCupPath
withGHCupTmpDir = (ReleaseKey, GHCupPath) -> GHCupPath
forall a b. (a, b) -> b
snd ((ReleaseKey, GHCupPath) -> GHCupPath)
-> m (ReleaseKey, GHCupPath) -> m GHCupPath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((forall a. m a -> IO a) -> IO (ReleaseKey, GHCupPath))
-> m (ReleaseKey, GHCupPath)
forall (m :: * -> *) b.
MonadUnliftIO m =>
((forall a. m a -> IO a) -> IO b) -> m b
withRunInIO (\forall a. m a -> IO a
run ->
  m (ReleaseKey, GHCupPath) -> IO (ReleaseKey, GHCupPath)
forall a. m a -> IO a
run
    (m (ReleaseKey, GHCupPath) -> IO (ReleaseKey, GHCupPath))
-> m (ReleaseKey, GHCupPath) -> IO (ReleaseKey, GHCupPath)
forall a b. (a -> b) -> a -> b
$ IO GHCupPath -> (GHCupPath -> IO ()) -> m (ReleaseKey, GHCupPath)
forall (m :: * -> *) a.
MonadResource m =>
IO a -> (a -> IO ()) -> m (ReleaseKey, a)
allocate
        (m GHCupPath -> IO GHCupPath
forall a. m a -> IO a
run m GHCupPath
forall env (m :: * -> *).
(MonadReader env m, HasDirs env, MonadUnliftIO m, HasLog env,
 MonadCatch m, MonadThrow m, MonadMask m, MonadIO m) =>
m GHCupPath
mkGhcupTmpDir)
        (\GHCupPath
fp ->
            (IOException -> IO ()) -> IO () -> IO ()
forall (m :: * -> *) a.
MonadCatch m =>
(IOException -> m a) -> m a -> m a
handleIO (\IOException
e -> m () -> IO ()
forall a. m a -> IO a
run
                (m () -> IO ()) -> m () -> IO ()
forall a b. (a -> b) -> a -> b
$ Text -> m ()
forall env (m :: * -> *).
(MonadReader env m,
 LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logDebug (Text
"Resource cleanup failed for " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (GHCupPath -> String
fromGHCupPath GHCupPath
fp) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
", error was: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (IOException -> String
forall e. Exception e => e -> String
displayException IOException
e)))
            (IO () -> IO ()) -> (GHCupPath -> IO ()) -> GHCupPath -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GHCupPath -> IO ()
removePathForcibly
            (GHCupPath -> IO ()) -> GHCupPath -> IO ()
forall a b. (a -> b) -> a -> b
$ GHCupPath
fp))




    --------------
    --[ Others ]--
    --------------


useXDG :: IO Bool
useXDG :: IO Bool
useXDG = Maybe String -> Bool
forall a. Maybe a -> Bool
isJust (Maybe String -> Bool) -> IO (Maybe String) -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO (Maybe String)
lookupEnv String
"GHCUP_USE_XDG_DIRS"


-- | Like 'relpath'. Assumes the inputs are resolved in case of symlinks.
relativeSymlink :: FilePath  -- ^ the path in which to create the symlink
                -> FilePath  -- ^ the symlink destination
                -> FilePath
relativeSymlink :: String -> ShowS
relativeSymlink String
p1 String
p2
  | Bool
isWindows = String
p2 -- windows quickly gets into MAX_PATH issues so we don't care about relative symlinks
  | Bool
otherwise =
    let d1 :: [String]
d1      = String -> [String]
splitDirectories String
p1
        d2 :: [String]
d2      = String -> [String]
splitDirectories String
p2
        common :: [(String, String)]
common  = ((String, String) -> Bool)
-> [(String, String)] -> [(String, String)]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (\(String
x, String
y) -> String
x String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
y) ([(String, String)] -> [(String, String)])
-> [(String, String)] -> [(String, String)]
forall a b. (a -> b) -> a -> b
$ [String] -> [String] -> [(String, String)]
forall a b. [a] -> [b] -> [(a, b)]
zip [String]
d1 [String]
d2
        cPrefix :: [String]
cPrefix = Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop ([(String, String)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(String, String)]
common) [String]
d1
    in  [String] -> String
joinPath (Int -> String -> [String]
forall a. Int -> a -> [a]
replicate ([String] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
cPrefix) String
"..")
          String -> ShowS
forall a. Semigroup a => a -> a -> a
<> [String] -> String
joinPath ([Char
pathSeparator] String -> [String] -> [String]
forall a. a -> [a] -> [a]
: Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop ([(String, String)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(String, String)]
common) [String]
d2)


cleanupTrash :: ( MonadIO m
                , MonadMask m
                , MonadReader env m
                , HasLog env
                , HasDirs env
                , HasSettings env
                )
             => m ()
cleanupTrash :: m ()
cleanupTrash = do
  Dirs { GHCupPath
recycleDir :: GHCupPath
$sel:recycleDir:Dirs :: Dirs -> GHCupPath
recycleDir } <- m Dirs
forall env (m :: * -> *).
(MonadReader env m, LabelOptic' "dirs" A_Lens env Dirs) =>
m Dirs
getDirs
  [String]
contents <- IO [String] -> m [String]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [String] -> m [String]) -> IO [String] -> m [String]
forall a b. (a -> b) -> a -> b
$ String -> IO [String]
listDirectory (GHCupPath -> String
fromGHCupPath GHCupPath
recycleDir)
  if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
contents
  then () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
  else do
    Text -> m ()
forall env (m :: * -> *).
(MonadReader env m,
 LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logWarn (Text
"Removing leftover files in " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (GHCupPath -> String
fromGHCupPath GHCupPath
recycleDir))
    [String] -> (String -> m ()) -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [String]
contents (\String
fp -> (IOException -> m ()) -> m () -> m ()
forall (m :: * -> *) a.
MonadCatch m =>
(IOException -> m a) -> m a -> m a
handleIO (\IOException
e ->
        Text -> m ()
forall env (m :: * -> *).
(MonadReader env m,
 LabelOptic' "loggerConfig" A_Lens env LoggerConfig, MonadIO m) =>
Text -> m ()
logDebug (Text
"Resource cleanup failed for " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
fp Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
", error was: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (IOException -> String
forall e. Exception e => e -> String
displayException IOException
e))
      ) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GHCupPath -> IO ()
removePathForcibly (GHCupPath
recycleDir GHCupPath -> String -> GHCupPath
`appendGHCupPath` String
fp))



-- System.Directory re-exports with GHCupPath

removeDirectory :: GHCupPath -> IO ()
removeDirectory :: GHCupPath -> IO ()
removeDirectory (GHCupPath String
fp) = String -> IO ()
SD.removeDirectory String
fp

removeDirectoryRecursive :: GHCupPath -> IO ()
removeDirectoryRecursive :: GHCupPath -> IO ()
removeDirectoryRecursive (GHCupPath String
fp) = String -> IO ()
SD.removeDirectoryRecursive String
fp

removePathForcibly :: GHCupPath -> IO ()
removePathForcibly :: GHCupPath -> IO ()
removePathForcibly (GHCupPath String
fp) = String -> IO ()
SD.removePathForcibly String
fp