Compare commits

..

No commits in common. "6144fcd4c9c352672fd5ce705d95eeee9ea3cd12" and "61019ecd49d7b3f89f83fcb872967af4598c5cda" have entirely different histories.

4 changed files with 88 additions and 88 deletions

View File

@ -1,9 +1,5 @@
# Revision history for ghcup # Revision history for ghcup
## 0.1.16 -- ????-??-??
* Add 'nuke' subcommand wrt [#135](https://gitlab.haskell.org/haskell/ghcup-hs/-/issues/135), implemented by Arjun Kathuria
## 0.1.15.2 -- 2021-06-13 ## 0.1.15.2 -- 2021-06-13
* Remove legacy handling of cabal binary and be more graceful about binaries not installed by ghcup (e.g. stack) * Remove legacy handling of cabal binary and be more graceful about binaries not installed by ghcup (e.g. stack)

View File

@ -1113,10 +1113,7 @@ Report bugs at <https://gitlab.haskell.org/haskell/ghcup-hs/issues>|]
let loggerConfig = LoggerConfig let loggerConfig = LoggerConfig
{ lcPrintDebug = verbose settings { lcPrintDebug = verbose settings
, colorOutter = B.hPut stderr , colorOutter = B.hPut stderr
, rawOutter = , rawOutter = B.appendFile logfile
case optCommand of
Nuke -> \_ -> pure ()
_ -> B.appendFile logfile
} }
let runLogger = myLoggerT loggerConfig let runLogger = myLoggerT loggerConfig
let siletRunLogger = myLoggerT loggerConfig { colorOutter = \_ -> pure () } let siletRunLogger = myLoggerT loggerConfig { colorOutter = \_ -> pure () }
@ -1706,27 +1703,31 @@ Make sure to clean up #{tmpdir} afterwards.|])
Nuke -> Nuke ->
runRm (do runRm (do
lift $ $logWarn "WARNING: This will remove GHCup and all installed components from your system." lift $ runLogger $ $logWarn "WARNING: This will remove GHCup and all installed components from your system."
lift $ $logWarn "Waiting 10 seconds before commencing, if you want to cancel it, now would be the time." lift $ runLogger $ $logWarn "Waiting 10 seconds before commencing, if you want to cancel it, now would be the time."
liftIO $ threadDelay 10000000 -- wait 10s liftIO $ threadDelay 10000000 -- wait 10s
lift $ $logInfo "Initiating Nuclear Sequence 🚀🚀🚀" lift $ runLogger $ $logInfo "Initiating Nuclear Sequence 🚀🚀🚀"
lift $ $logInfo "Nuking in 3...2...1" lift $ runLogger $ $logInfo "Nuking in 3...2...1"
lInstalled <- lift $ listVersions Nothing (Just ListInstalled)
lInstalled <- lift $ runLogger . flip runReaderT appstate $ listVersions Nothing (Just ListInstalled)
forM_ lInstalled (liftE . rmTool) forM_ lInstalled (liftE . rmTool)
lift rmGhcupDirs leftOverFiles <- lift $ runLogger $ runReaderT rmGhcupDirs appstate
pure leftOverFiles
) >>= \case ) >>= \case
VRight leftOverFiles VRight leftOverFiles -> do
| null leftOverFiles -> do
case length leftOverFiles of
0 -> do
runLogger $ $logInfo "Nuclear Annihilation complete!" runLogger $ $logInfo "Nuclear Annihilation complete!"
pure ExitSuccess pure ExitSuccess
| otherwise -> do _ -> do
runLogger $ $logWarn "These Files have survived Nuclear Annihilation, you may remove them manually." runLogger $ $logWarn "These Directories/Files have survived Nuclear Annihilation, you may remove them manually."
forM_ leftOverFiles putStrLn forM_ leftOverFiles (runLogger . $logDebug . T.pack)
pure ExitSuccess pure ExitSuccess
VLeft e -> do VLeft e -> do

View File

@ -1305,26 +1305,29 @@ rmGhcup = do
(liftIO $ canonicalizePath currentRunningExecPath) (liftIO $ canonicalizePath currentRunningExecPath)
p2 <- handleIO' doesNotExistErrorType p2 <- handleIO' doesNotExistErrorType
(handlePathNotPresent ghcupFilepath) (handlePathNotPresent ghcupFilename)
(liftIO $ canonicalizePath ghcupFilepath) (liftIO $ canonicalizePath ghcupFilename)
let areEqualPaths = equalFilePath p1 p2 let areEqualPaths = equalFilePath p1 p2
when (not areEqualPaths) $ do if areEqualPaths
$logWarn $ nonStandardInstallLocationMsg currentRunningExecPath then
do
#if defined(IS_WINDOWS) #if defined(IS_WINDOWS)
-- since it doesn't seem possible to delete a running exec in windows -- since it doesn't seem possible to delete a running exec in windows
-- we move it to temp dir, to be deleted at next reboot -- we move it to temp dir, to be deleted at next reboot
tempDir <- liftIO $ getTemporaryDirectory tempDir <- liftIO $ getTemporaryDirectory
let tempFilepath = tempDir </> ghcupFilename let tempFilepath = tempDir </> ghcupFilename
hideError UnsupportedOperation $ hideError UnsupportedOperation $
liftIO $ hideError NoSuchThing $ liftIO $ hideError NoSuchThing $
Win32.moveFileEx ghcupFilepath (Just tempFilepath) Win32.mOVEFILE_REPLACE_EXISTING Win32.moveFileEx ghcupFilepath (Just tempFilepath) 1
#else #else
-- delete it. -- delete it.
hideError doesNotExistErrorType $ liftIO $ rmFile ghcupFilepath hideError doesNotExistErrorType $ liftIO $ rmFile ghcupFilepath
#endif #endif
else
$logWarn $
nonStandardInstallLocationMsg currentRunningExecPath
where where
handlePathNotPresent fp _err = do handlePathNotPresent fp _err = do
@ -1345,74 +1348,83 @@ rmTool :: ( MonadReader AppState m
-> Excepts '[NotInstalled ] m () -> Excepts '[NotInstalled ] m ()
rmTool ListResult {lVer, lTool, lCross} = do rmTool ListResult {lVer, lTool, lCross} = do
case lTool of -- appstate <- ask
GHC ->
let ghcTargetVersion = GHCTargetVersion lCross lVer
in rmGHCVer ghcTargetVersion
HLS -> rmHLSVer lVer
Cabal -> rmCabalVer lVer
Stack -> rmStackVer lVer
GHCup -> lift rmGhcup
case lTool of
GHC -> do
let ghcTargetVersion = GHCTargetVersion lCross lVer
rmGHCVer ghcTargetVersion
HLS -> do
rmHLSVer lVer
Cabal -> do
rmCabalVer lVer
Stack -> do
rmStackVer lVer
GHCup -> do
lift rmGhcup
rmGhcupDirs :: ( MonadReader AppState m rmGhcupDirs :: ( MonadReader AppState m
, MonadIO m , MonadIO m
, MonadLogger m , MonadLogger m
, MonadCatch m , MonadCatch m
, MonadMask m ) , MonadMask m )
=> m [FilePath] => m [FilePath]
rmGhcupDirs = do rmGhcupDirs = do
Dirs dirs@Dirs
{ baseDir { baseDir
, binDir , binDir
, logsDir , logsDir
, cacheDir , cacheDir
} <- asks dirs , confDir } <- asks dirs
let envFilePath = baseDir </> "env" let envFilePath = baseDir </> "env"
confFilePath <- getConfigFilePath confFilePath <- getConfigFilePath
rmEnvFile envFilePath -- remove env File
rmEnvFile envFilePath
-- remove the configFile file
rmConfFile confFilePath rmConfFile confFilePath
-- remove entire cache Dir
rmCacheDir cacheDir rmCacheDir cacheDir
rmLogsDir logsDir
rmBinDir binDir
#if defined(IS_WINDOWS)
rmPath (baseDir </> "msys64")
#endif
liftIO $ removeEmptyDirsRecursive baseDir -- remove entire logs Dir
rmLogsDir logsDir
-- report files in baseDir that are left-over after -- remove bin directory conditionally
-- the standard location deletions above rmBinDir binDir
hideErrorDef [doesNotExistErrorType] [] $ reportRemainingFiles baseDir
-- report files in baseDir that are left-over after the standard location deletions above
reportRemainingFiles baseDir
where where
rmEnvFile :: (MonadCatch m, MonadLogger m, MonadIO m) => FilePath -> m ()
rmEnvFile enFilePath = do rmEnvFile enFilePath = do
$logInfo "Removing Ghcup Environment File" $logInfo "Removing Ghcup Environment File"
hideError doesNotExistErrorType $ liftIO $ deleteFile enFilePath hideError doesNotExistErrorType $ liftIO $ deleteFile enFilePath
rmConfFile :: (MonadCatch m, MonadLogger m, MonadIO m) => FilePath -> m ()
rmConfFile confFilePath = do rmConfFile confFilePath = do
$logInfo "removing Ghcup Config File" $logInfo "removing Ghcup Config File"
hideError doesNotExistErrorType $ liftIO $ deleteFile confFilePath hideError doesNotExistErrorType $ liftIO $ deleteFile confFilePath
rmCacheDir :: (MonadLogger m, MonadIO m) => FilePath -> m ()
rmCacheDir cacheDir = do rmCacheDir cacheDir = do
$logInfo "removing ghcup cache Dir" $logInfo "removing ghcup cache Dir"
contents <- liftIO $ getDirectoryContentsRecursive cacheDir contents <- liftIO $ listDirectory cacheDir
forM_ contents (liftIO . deleteFile . (cacheDir </>)) forM_ contents deleteFile
removeDirIfEmptyOrIsSymlink cacheDir
rmLogsDir :: (MonadLogger m, MonadIO m) => FilePath -> m ()
rmLogsDir logsDir = do rmLogsDir logsDir = do
$logInfo "removing ghcup logs Dir" $logInfo "removing ghcup logs Dir"
contents <- liftIO $ getDirectoryContentsRecursive logsDir contents <- liftIO $ listDirectory logsDir
forM_ contents (liftIO . deleteFile . (logsDir </>)) forM_ contents deleteFile
removeDirIfEmptyOrIsSymlink logsDir
rmBinDir :: (MonadCatch m, MonadIO m) => FilePath -> m ()
rmBinDir binDir = do rmBinDir binDir = do
#if !defined(IS_WINDOWS) #if !defined(IS_WINDOWS)
isXDGStyle <- liftIO $ useXDG isXDGStyle <- liftIO $ useXDG
@ -1423,12 +1435,11 @@ rmGhcupDirs = do
removeDirIfEmptyOrIsSymlink binDir removeDirIfEmptyOrIsSymlink binDir
#endif #endif
reportRemainingFiles :: MonadIO m => FilePath -> m [FilePath] reportRemainingFiles ghcupDir = do
reportRemainingFiles dir = do remainingFiles <- liftIO $ getDirectoryContentsRecursive ghcupDir
remainingFiles <- liftIO $ getDirectoryContentsRecursive dir
let normalizedFilePaths = fmap normalise remainingFiles let normalizedFilePaths = fmap normalise remainingFiles
let sortedByDepthRemainingFiles = reverse $ sortBy compareFn normalizedFilePaths let sortedByDepthRemainingFiles = reverse $ sortBy compareFn normalizedFilePaths
let remainingFilesAbsolute = fmap (dir </>) sortedByDepthRemainingFiles remainingFilesAbsolute <- makePathsAbsolute sortedByDepthRemainingFiles
pure remainingFilesAbsolute pure remainingFilesAbsolute
@ -1439,22 +1450,17 @@ rmGhcupDirs = do
compareFn :: FilePath -> FilePath -> Ordering compareFn :: FilePath -> FilePath -> Ordering
compareFn fp1 fp2 = compare (calcDepth fp1) (calcDepth fp2) compareFn fp1 fp2 = compare (calcDepth fp1) (calcDepth fp2)
removeEmptyDirsRecursive :: FilePath -> IO () makePathsAbsolute :: (MonadIO m) => [FilePath] -> m [FilePath]
removeEmptyDirsRecursive fp = do makePathsAbsolute paths = liftIO $
cs <- listDirectory fp >>= filterM doesDirectoryExist . fmap (fp </>) traverse (makeAbsolute . normalise) paths
forM_ cs removeEmptyDirsRecursive
hideError InappropriateType $ removeDirIfEmptyOrIsSymlink fp
-- we expect only files inside cache/log dir -- we expect only files inside cache/log dir
-- we report remaining files/dirs later, -- we report remaining files/dirs later,
-- hence the force/quiet mode in these delete functions below. -- hence the force/quiet mode in these delete functions below.
deleteFile :: FilePath -> IO ()
deleteFile filepath = do deleteFile filepath = do
hideError InappropriateType $ rmFile filepath hideError InappropriateType $ rmFile filepath
removeDirIfEmptyOrIsSymlink :: (MonadCatch m, MonadIO m) => FilePath -> m ()
removeDirIfEmptyOrIsSymlink filepath = removeDirIfEmptyOrIsSymlink filepath =
hideError UnsatisfiedConstraints $ hideError UnsatisfiedConstraints $
handleIO' InappropriateType handleIO' InappropriateType
@ -1467,8 +1473,6 @@ rmGhcupDirs = do
then liftIO $ deleteFile fp then liftIO $ deleteFile fp
else liftIO $ ioError e else liftIO $ ioError e
------------------ ------------------
--[ Debug info ]-- --[ Debug info ]--
------------------ ------------------

View File

@ -190,14 +190,14 @@ hideError :: (MonadIO m, MonadCatch m) => IOErrorType -> m () -> m ()
hideError err = handleIO (\e -> if err == ioeGetErrorType e then pure () else liftIO . ioError $ e) hideError err = handleIO (\e -> if err == ioeGetErrorType e then pure () else liftIO . ioError $ e)
hideErrorDef :: (MonadIO m, MonadCatch m) => [IOErrorType] -> a -> m a -> m a hideErrorDef :: [IOErrorType] -> a -> IO a -> IO a
hideErrorDef errs def = hideErrorDef errs def =
handleIO (\e -> if ioeGetErrorType e `elem` errs then pure def else liftIO $ ioError e) handleIO (\e -> if ioeGetErrorType e `elem` errs then pure def else ioError e)
hideErrorDefM :: (MonadIO m, MonadCatch m) => [IOErrorType] -> m a -> m a -> m a hideErrorDefM :: [IOErrorType] -> IO a -> IO a -> IO a
hideErrorDefM errs def = hideErrorDefM errs def =
handleIO (\e -> if ioeGetErrorType e `elem` errs then def else liftIO $ ioError e) handleIO (\e -> if ioeGetErrorType e `elem` errs then def else ioError e)
-- TODO: does this work? -- TODO: does this work?
@ -334,13 +334,12 @@ copyDirectoryRecursive srcDir destDir = do
in doCopy src dest in doCopy src dest
| (srcBase, srcFile) <- srcFiles ] | (srcBase, srcFile) <- srcFiles ]
-- | List all the files in a directory and all subdirectories.
-- | List all the files in a directory and all subdirectories. --
-- -- The order places files in sub-directories after all the files in their
-- The order places files in sub-directories after all the files in their -- parent directories. The list is generated lazily so is not well defined if
-- parent directories. The list is generated lazily so is not well defined if -- the source directory structure changes before the list is used.
-- the source directory structure changes before the list is used. --
--
getDirectoryContentsRecursive :: FilePath -> IO [FilePath] getDirectoryContentsRecursive :: FilePath -> IO [FilePath]
getDirectoryContentsRecursive topdir = recurseDirectories [""] getDirectoryContentsRecursive topdir = recurseDirectories [""]
where where