{-# LANGUAGE NoImplicitPrelude   #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings   #-}

-- | Types and functions related to Stack's @clean@ and @purge@ commands.

module Stack.Clean
  ( CleanOpts (..)
  , CleanCommand (..)
  , cleanCmd
  , clean
  ) where

import           Data.List ( (\\), intercalate )
import qualified Data.Map.Strict as Map
import           Path.IO ( ignoringAbsence, removeDirRecur )
import           Stack.Config ( withBuildConfig )
import           Stack.Constants.Config ( rootDistDirFromDir, workDirFromDir )
import           Stack.Prelude
import           Stack.Runners ( ShouldReexec (..), withConfig )
import           Stack.Types.BuildConfig
                   ( BuildConfig (..), HasBuildConfig (..), getProjectWorkDir )
import           Stack.Types.Config ( Config )
import           Stack.Types.Runner ( Runner )
import           Stack.Types.SourceMap ( SMWanted (..), ppRoot )

-- | Type representing exceptions thrown by functions exported by the

-- "Stack.Clean" module.

data CleanException
  = NonLocalPackages [PackageName]
  | DeletionFailures [(Path Abs Dir, SomeException)]
  deriving (Int -> CleanException -> ShowS
[CleanException] -> ShowS
CleanException -> FilePath
(Int -> CleanException -> ShowS)
-> (CleanException -> FilePath)
-> ([CleanException] -> ShowS)
-> Show CleanException
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CleanException -> ShowS
showsPrec :: Int -> CleanException -> ShowS
$cshow :: CleanException -> FilePath
show :: CleanException -> FilePath
$cshowList :: [CleanException] -> ShowS
showList :: [CleanException] -> ShowS
Show, Typeable)

instance Exception CleanException where
  displayException :: CleanException -> FilePath
displayException (NonLocalPackages [PackageName]
pkgs) = [FilePath] -> FilePath
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    [ FilePath
"Error: [S-9463]\n"
    , FilePath
"The following packages are not part of this project: "
    , FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate FilePath
", " ((PackageName -> FilePath) -> [PackageName] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map PackageName -> FilePath
forall a. Show a => a -> FilePath
show [PackageName]
pkgs)
    ]
  displayException (DeletionFailures [(Path Abs Dir, SomeException)]
failures) = [FilePath] -> FilePath
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
    [ FilePath
"Error: [S-6321]\n"
    , FilePath
"Exception while recursively deleting:\n"
    , ((Path Abs Dir, SomeException) -> FilePath)
-> [(Path Abs Dir, SomeException)] -> FilePath
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(Path Abs Dir
dir, SomeException
e) ->
        Path Abs Dir -> FilePath
forall b t. Path b t -> FilePath
toFilePath Path Abs Dir
dir FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
"\n" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> SomeException -> FilePath
forall e. Exception e => e -> FilePath
displayException SomeException
e FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> FilePath
"\n") [(Path Abs Dir, SomeException)]
failures
    , FilePath
"Perhaps you do not have permission to delete these files or they are in \
      \use?"
    ]

-- | Type representing command line options for the @stack clean@ command.

data CleanOpts
  = CleanShallow [PackageName]
    -- ^ Delete the "dist directories" as defined in

    -- 'Stack.Constants.Config.distRelativeDir' for the given local packages. If

    -- no packages are given, all project packages should be cleaned.

  | CleanFull
    -- ^ Delete all work directories in the project.


-- | Type representing Stack's cleaning commands.

data CleanCommand
  = Clean
  | Purge

-- | Function underlying the @stack clean@ command.

cleanCmd :: CleanOpts -> RIO Runner ()
cleanCmd :: CleanOpts -> RIO Runner ()
cleanCmd = ShouldReexec -> RIO Config () -> RIO Runner ()
forall a. ShouldReexec -> RIO Config a -> RIO Runner a
withConfig ShouldReexec
NoReexec (RIO Config () -> RIO Runner ())
-> (CleanOpts -> RIO Config ()) -> CleanOpts -> RIO Runner ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CleanOpts -> RIO Config ()
clean

-- | Deletes build artifacts in the current project.

clean :: CleanOpts -> RIO Config ()
clean :: CleanOpts -> RIO Config ()
clean CleanOpts
cleanOpts = do
  [Path Abs Dir]
toDelete <- RIO BuildConfig [Path Abs Dir] -> RIO Config [Path Abs Dir]
forall a. RIO BuildConfig a -> RIO Config a
withBuildConfig (RIO BuildConfig [Path Abs Dir] -> RIO Config [Path Abs Dir])
-> RIO BuildConfig [Path Abs Dir] -> RIO Config [Path Abs Dir]
forall a b. (a -> b) -> a -> b
$ CleanOpts -> RIO BuildConfig [Path Abs Dir]
dirsToDelete CleanOpts
cleanOpts
  Utf8Builder -> RIO Config ()
forall (m :: * -> *) env.
(MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) =>
Utf8Builder -> m ()
logDebug (Utf8Builder -> RIO Config ()) -> Utf8Builder -> RIO Config ()
forall a b. (a -> b) -> a -> b
$ Utf8Builder
"Need to delete: " Utf8Builder -> Utf8Builder -> Utf8Builder
forall a. Semigroup a => a -> a -> a
<> FilePath -> Utf8Builder
forall a. IsString a => FilePath -> a
fromString ([FilePath] -> FilePath
forall a. Show a => a -> FilePath
show ((Path Abs Dir -> FilePath) -> [Path Abs Dir] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Path Abs Dir -> FilePath
forall b t. Path b t -> FilePath
toFilePath [Path Abs Dir]
toDelete))
  [(Path Abs Dir, SomeException)]
failures <- [Maybe (Path Abs Dir, SomeException)]
-> [(Path Abs Dir, SomeException)]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe (Path Abs Dir, SomeException)]
 -> [(Path Abs Dir, SomeException)])
-> RIO Config [Maybe (Path Abs Dir, SomeException)]
-> RIO Config [(Path Abs Dir, SomeException)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Path Abs Dir -> RIO Config (Maybe (Path Abs Dir, SomeException)))
-> [Path Abs Dir]
-> RIO Config [Maybe (Path Abs Dir, SomeException)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Path Abs Dir -> RIO Config (Maybe (Path Abs Dir, SomeException))
cleanDir [Path Abs Dir]
toDelete
  case [(Path Abs Dir, SomeException)]
failures of
    [] -> () -> RIO Config ()
forall a. a -> RIO Config a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
    [(Path Abs Dir, SomeException)]
_  -> CleanException -> RIO Config ()
forall (m :: * -> *) e a. (MonadIO m, Exception e) => e -> m a
throwIO (CleanException -> RIO Config ())
-> CleanException -> RIO Config ()
forall a b. (a -> b) -> a -> b
$ [(Path Abs Dir, SomeException)] -> CleanException
DeletionFailures [(Path Abs Dir, SomeException)]
failures

cleanDir :: Path Abs Dir -> RIO Config (Maybe (Path Abs Dir, SomeException))
cleanDir :: Path Abs Dir -> RIO Config (Maybe (Path Abs Dir, SomeException))
cleanDir Path Abs Dir
dir = do
  Utf8Builder -> RIO Config ()
forall (m :: * -> *) env.
(MonadIO m, MonadReader env m, HasLogFunc env, HasCallStack) =>
Utf8Builder -> m ()
logDebug (Utf8Builder -> RIO Config ()) -> Utf8Builder -> RIO Config ()
forall a b. (a -> b) -> a -> b
$ Utf8Builder
"Deleting directory: " Utf8Builder -> Utf8Builder -> Utf8Builder
forall a. Semigroup a => a -> a -> a
<> FilePath -> Utf8Builder
forall a. IsString a => FilePath -> a
fromString (Path Abs Dir -> FilePath
forall b t. Path b t -> FilePath
toFilePath Path Abs Dir
dir)
  IO (Maybe (Path Abs Dir, SomeException))
-> RIO Config (Maybe (Path Abs Dir, SomeException))
forall a. IO a -> RIO Config a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> IO ()
forall (m :: * -> *) a. (MonadIO m, MonadCatch m) => m a -> m ()
ignoringAbsence (Path Abs Dir -> IO ()
forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
removeDirRecur Path Abs Dir
dir) IO ()
-> IO (Maybe (Path Abs Dir, SomeException))
-> IO (Maybe (Path Abs Dir, SomeException))
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe (Path Abs Dir, SomeException)
-> IO (Maybe (Path Abs Dir, SomeException))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (Path Abs Dir, SomeException)
forall a. Maybe a
Nothing) RIO Config (Maybe (Path Abs Dir, SomeException))
-> (SomeException
    -> RIO Config (Maybe (Path Abs Dir, SomeException)))
-> RIO Config (Maybe (Path Abs Dir, SomeException))
forall (m :: * -> *) a.
MonadUnliftIO m =>
m a -> (SomeException -> m a) -> m a
`catchAny` \SomeException
ex ->
    Maybe (Path Abs Dir, SomeException)
-> RIO Config (Maybe (Path Abs Dir, SomeException))
forall a. a -> RIO Config a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (Path Abs Dir, SomeException)
 -> RIO Config (Maybe (Path Abs Dir, SomeException)))
-> Maybe (Path Abs Dir, SomeException)
-> RIO Config (Maybe (Path Abs Dir, SomeException))
forall a b. (a -> b) -> a -> b
$ (Path Abs Dir, SomeException)
-> Maybe (Path Abs Dir, SomeException)
forall a. a -> Maybe a
Just (Path Abs Dir
dir, SomeException
ex)

dirsToDelete :: CleanOpts -> RIO BuildConfig [Path Abs Dir]
dirsToDelete :: CleanOpts -> RIO BuildConfig [Path Abs Dir]
dirsToDelete CleanOpts
cleanOpts = do
  Map PackageName ProjectPackage
packages <- Getting
  (Map PackageName ProjectPackage)
  BuildConfig
  (Map PackageName ProjectPackage)
-> RIO BuildConfig (Map PackageName ProjectPackage)
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view (Getting
   (Map PackageName ProjectPackage)
   BuildConfig
   (Map PackageName ProjectPackage)
 -> RIO BuildConfig (Map PackageName ProjectPackage))
-> Getting
     (Map PackageName ProjectPackage)
     BuildConfig
     (Map PackageName ProjectPackage)
-> RIO BuildConfig (Map PackageName ProjectPackage)
forall a b. (a -> b) -> a -> b
$ (BuildConfig -> Const (Map PackageName ProjectPackage) BuildConfig)
-> BuildConfig
-> Const (Map PackageName ProjectPackage) BuildConfig
forall env. HasBuildConfig env => Lens' env BuildConfig
Lens' BuildConfig BuildConfig
buildConfigL ((BuildConfig
  -> Const (Map PackageName ProjectPackage) BuildConfig)
 -> BuildConfig
 -> Const (Map PackageName ProjectPackage) BuildConfig)
-> Getting
     (Map PackageName ProjectPackage)
     BuildConfig
     (Map PackageName ProjectPackage)
-> Getting
     (Map PackageName ProjectPackage)
     BuildConfig
     (Map PackageName ProjectPackage)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BuildConfig -> Map PackageName ProjectPackage)
-> SimpleGetter BuildConfig (Map PackageName ProjectPackage)
forall s a. (s -> a) -> SimpleGetter s a
to (.smWanted.project)
  case CleanOpts
cleanOpts of
    CleanShallow [] ->
      -- Filter out packages listed as extra-deps

      (ProjectPackage -> RIO BuildConfig (Path Abs Dir))
-> [ProjectPackage] -> RIO BuildConfig [Path Abs Dir]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Path Abs Dir -> RIO BuildConfig (Path Abs Dir)
forall env (m :: * -> *).
(HasConfig env, MonadReader env m) =>
Path Abs Dir -> m (Path Abs Dir)
rootDistDirFromDir (Path Abs Dir -> RIO BuildConfig (Path Abs Dir))
-> (ProjectPackage -> Path Abs Dir)
-> ProjectPackage
-> RIO BuildConfig (Path Abs Dir)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProjectPackage -> Path Abs Dir
ppRoot) ([ProjectPackage] -> RIO BuildConfig [Path Abs Dir])
-> [ProjectPackage] -> RIO BuildConfig [Path Abs Dir]
forall a b. (a -> b) -> a -> b
$ Map PackageName ProjectPackage -> [ProjectPackage]
forall k a. Map k a -> [a]
Map.elems Map PackageName ProjectPackage
packages
    CleanShallow [PackageName]
targets -> do
      let localPkgNames :: [PackageName]
localPkgNames = Map PackageName ProjectPackage -> [PackageName]
forall k a. Map k a -> [k]
Map.keys Map PackageName ProjectPackage
packages
          getPkgDir :: PackageName -> Maybe (Path Abs Dir)
getPkgDir PackageName
pkgName' = (ProjectPackage -> Path Abs Dir)
-> Maybe ProjectPackage -> Maybe (Path Abs Dir)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ProjectPackage -> Path Abs Dir
ppRoot (PackageName
-> Map PackageName ProjectPackage -> Maybe ProjectPackage
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup PackageName
pkgName' Map PackageName ProjectPackage
packages)
      case [PackageName]
targets [PackageName] -> [PackageName] -> [PackageName]
forall a. Eq a => [a] -> [a] -> [a]
\\ [PackageName]
localPkgNames of
        [] -> (Path Abs Dir -> RIO BuildConfig (Path Abs Dir))
-> [Path Abs Dir] -> RIO BuildConfig [Path Abs Dir]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Path Abs Dir -> RIO BuildConfig (Path Abs Dir)
forall env (m :: * -> *).
(HasConfig env, MonadReader env m) =>
Path Abs Dir -> m (Path Abs Dir)
rootDistDirFromDir ((PackageName -> Maybe (Path Abs Dir))
-> [PackageName] -> [Path Abs Dir]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe PackageName -> Maybe (Path Abs Dir)
getPkgDir [PackageName]
targets)
        [PackageName]
xs -> CleanException -> RIO BuildConfig [Path Abs Dir]
forall e a. (HasCallStack, Exception e) => e -> RIO BuildConfig a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM ([PackageName] -> CleanException
NonLocalPackages [PackageName]
xs)
    CleanOpts
CleanFull -> do
      [Path Abs Dir]
pkgWorkDirs <- (ProjectPackage -> RIO BuildConfig (Path Abs Dir))
-> [ProjectPackage] -> RIO BuildConfig [Path Abs Dir]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Path Abs Dir -> RIO BuildConfig (Path Abs Dir)
forall env (m :: * -> *).
(HasConfig env, MonadReader env m) =>
Path Abs Dir -> m (Path Abs Dir)
workDirFromDir (Path Abs Dir -> RIO BuildConfig (Path Abs Dir))
-> (ProjectPackage -> Path Abs Dir)
-> ProjectPackage
-> RIO BuildConfig (Path Abs Dir)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProjectPackage -> Path Abs Dir
ppRoot) ([ProjectPackage] -> RIO BuildConfig [Path Abs Dir])
-> [ProjectPackage] -> RIO BuildConfig [Path Abs Dir]
forall a b. (a -> b) -> a -> b
$ Map PackageName ProjectPackage -> [ProjectPackage]
forall k a. Map k a -> [a]
Map.elems Map PackageName ProjectPackage
packages
      Path Abs Dir
projectWorkDir <- RIO BuildConfig (Path Abs Dir)
forall env (m :: * -> *).
(HasBuildConfig env, MonadReader env m) =>
m (Path Abs Dir)
getProjectWorkDir
      [Path Abs Dir] -> RIO BuildConfig [Path Abs Dir]
forall a. a -> RIO BuildConfig a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Path Abs Dir
projectWorkDir Path Abs Dir -> [Path Abs Dir] -> [Path Abs Dir]
forall a. a -> [a] -> [a]
: [Path Abs Dir]
pkgWorkDirs)