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

-- | Function related to Stack's @uninstall@ command.

module Stack.Uninstall
  ( uninstallCmd
  ) where

import          Stack.Constants ( osIsWindows )
import          Stack.Prelude
import          Stack.Runners ( ShouldReexec (..), withConfig )
import          Stack.Types.Config
                  ( configL, configLocalBin, configLocalProgramsBase
                  , stackGlobalConfigL, stackRootL
                  )
import          Stack.Types.Runner ( Runner )

-- | Function underlying the @stack uninstall@ command. Display help for the

-- command.

uninstallCmd :: () -> RIO Runner ()
uninstallCmd :: () -> RIO Runner ()
uninstallCmd () = forall a. ShouldReexec -> RIO Config a -> RIO Runner a
withConfig ShouldReexec
NoReexec forall a b. (a -> b) -> a -> b
$ do
  Path Abs Dir
stackRoot <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall s. HasConfig s => Lens' s (Path Abs Dir)
stackRootL
  Path Abs File
globalConfig <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall s. HasConfig s => Lens' s (Path Abs File)
stackGlobalConfigL
  Path Abs Dir
programsDir <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall a b. (a -> b) -> a -> b
$ forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to Config -> Path Abs Dir
configLocalProgramsBase
  Path Abs Dir
localBinDir <- forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view forall a b. (a -> b) -> a -> b
$ forall env. HasConfig env => Lens' env Config
configLforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s a. (s -> a) -> SimpleGetter s a
to Config -> Path Abs Dir
configLocalBin
  let toStyleDoc :: Path b t -> StyleDoc
toStyleDoc = Style -> StyleDoc -> StyleDoc
style Style
Dir forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b t. Path b t -> String
toFilePath
      stackRoot' :: StyleDoc
stackRoot' = forall {b} {t}. Path b t -> StyleDoc
toStyleDoc Path Abs Dir
stackRoot
      globalConfig' :: StyleDoc
globalConfig' = forall {b} {t}. Path b t -> StyleDoc
toStyleDoc Path Abs File
globalConfig
      programsDir' :: StyleDoc
programsDir' = forall {b} {t}. Path b t -> StyleDoc
toStyleDoc Path Abs Dir
programsDir
      localBinDir' :: StyleDoc
localBinDir' = forall {b} {t}. Path b t -> StyleDoc
toStyleDoc Path Abs Dir
localBinDir
  forall env (m :: * -> *).
(HasCallStack, HasTerm env, MonadReader env m, MonadIO m) =>
StyleDoc -> m ()
prettyInfo forall a b. (a -> b) -> a -> b
$
       [StyleDoc] -> StyleDoc
vsep
         [ String -> StyleDoc
flow String
"To uninstall Stack, it should be sufficient to delete:"
         , Int -> StyleDoc -> StyleDoc
hang Int
4 forall a b. (a -> b) -> a -> b
$ [StyleDoc] -> StyleDoc
fillSep
             [ String -> StyleDoc
flow String
"(1) the directory containing Stack's tools"
             , StyleDoc
"(" forall a. Semigroup a => a -> a -> a
<> StyleDoc
softbreak forall a. Semigroup a => a -> a -> a
<> StyleDoc
programsDir' forall a. Semigroup a => a -> a -> a
<> StyleDoc
softbreak forall a. Semigroup a => a -> a -> a
<> StyleDoc
");"
             ]
         , Int -> StyleDoc -> StyleDoc
hang Int
4 forall a b. (a -> b) -> a -> b
$ [StyleDoc] -> StyleDoc
fillSep
             [ String -> StyleDoc
flow String
"(2) the Stack root directory"
             , StyleDoc
"(" forall a. Semigroup a => a -> a -> a
<> StyleDoc
softbreak forall a. Semigroup a => a -> a -> a
<> StyleDoc
stackRoot' forall a. Semigroup a => a -> a -> a
<> StyleDoc
softbreak forall a. Semigroup a => a -> a -> a
<> StyleDoc
");"
             ]
         , Int -> StyleDoc -> StyleDoc
hang Int
4 forall a b. (a -> b) -> a -> b
$ [StyleDoc] -> StyleDoc
fillSep
             [ String -> StyleDoc
flow String
"(3) if different, the directory containing "
             , String -> StyleDoc
flow String
"Stack's global YAML configuration file"
             , StyleDoc -> StyleDoc
parens StyleDoc
globalConfig' forall a. Semigroup a => a -> a -> a
<> StyleDoc
";"
             , StyleDoc
"and"
             ]
         , Int -> StyleDoc -> StyleDoc
hang Int
4 forall a b. (a -> b) -> a -> b
$ [StyleDoc] -> StyleDoc
fillSep
             [ String -> StyleDoc
flow String
"(4) the 'stack' executable file (see the output"
             , String -> StyleDoc
flow String
"of command"
             , StyleDoc
howToFindStack forall a. Semigroup a => a -> a -> a
<> StyleDoc
","
             , String -> StyleDoc
flow String
"if Stack is on the PATH;"
             , String -> StyleDoc
flow String
"Stack is often installed in"
             , StyleDoc
localBinDir' forall a. Semigroup a => a -> a -> a
<> StyleDoc
softbreak forall a. Semigroup a => a -> a -> a
<> StyleDoc
")."
             ]
         , [StyleDoc] -> StyleDoc
fillSep
             [String -> StyleDoc
flow String
"You may also want to delete"
             , Style -> StyleDoc -> StyleDoc
style Style
File StyleDoc
".stack-work"
             , String -> StyleDoc
flow String
"directories in any Haskell projects that you have built."
             ]
         ]
      forall a. Semigroup a => a -> a -> a
<> StyleDoc
blankLine
      forall a. Semigroup a => a -> a -> a
<> [StyleDoc] -> StyleDoc
vsep
           [ [StyleDoc] -> StyleDoc
fillSep
               [ String -> StyleDoc
flow String
"To uninstall completely a Stack-supplied tool (such as \
                      \GHC or, on Windows, MSYS2), delete from Stack's tools \
                      \directory"
               , StyleDoc -> StyleDoc
parens StyleDoc
programsDir' forall a. Semigroup a => a -> a -> a
<> StyleDoc
":"
               ]
           , Int -> StyleDoc -> StyleDoc
hang Int
4 forall a b. (a -> b) -> a -> b
$ [StyleDoc] -> StyleDoc
fillSep
               [ String -> StyleDoc
flow String
"(1) the tool's subdirectory;"
               ]
           , Int -> StyleDoc -> StyleDoc
hang Int
4 forall a b. (a -> b) -> a -> b
$ [StyleDoc] -> StyleDoc
fillSep
               [ String -> StyleDoc
flow String
"(2) the tool's archive file"
               , StyleDoc -> StyleDoc
parens (Style -> StyleDoc -> StyleDoc
style Style
File StyleDoc
"<tool>.tar.xz") forall a. Semigroup a => a -> a -> a
<> StyleDoc
"; and"
               ]
           , Int -> StyleDoc -> StyleDoc
hang Int
4 forall a b. (a -> b) -> a -> b
$ [StyleDoc] -> StyleDoc
fillSep
               [ String -> StyleDoc
flow String
"(3) the file marking that the tool is installed"
               , StyleDoc -> StyleDoc
parens (Style -> StyleDoc -> StyleDoc
style Style
File StyleDoc
"<tool>.installed") forall a. Semigroup a => a -> a -> a
<> StyleDoc
"."
               ]
           ]
 where
  styleShell :: StyleDoc -> StyleDoc
styleShell = Style -> StyleDoc -> StyleDoc
style Style
Shell
  howToFindStack :: StyleDoc
howToFindStack
    | Bool
osIsWindows = StyleDoc -> StyleDoc
styleShell StyleDoc
"where.exe stack"
    | Bool
otherwise   = StyleDoc -> StyleDoc
styleShell StyleDoc
"which stack"