module Main where import Data.Foldable import Data.List import System.Environment import System.Directory -- | Bundles the information for directory deletion while retaining the contents data Direm = Direm { del :: FilePath, targetDir :: FilePath, copy :: [FilePath] } deriving (Show, Eq) -- | Gathers the information direm :: FilePath -> IO Direm direm dir' = do dir <- canonicalizePath dir' target <- canonicalizePath $ dir ++ "/../" files <- listDirectory dir pure $ Direm dir target files -- | Copies all files to the parent directory and then deletes the directory runDirem :: Direm -> IO () runDirem (Direm dir target files) = do traverse_ (\file -> renamePath (dir ++ "/" ++ file) (target ++ "/" ++ file)) files removeDirectory dir -- | Generates the report of what will happen when running the operation showDirem :: Direm -> String showDirem (Direm dir target files) = "Deleting\n\t" ++ dir ++ "\n" ++ "while retaining\n" ++ unlines ["\t" ++ file | file <- files] ++ "in\n\t" ++ target main :: IO () main = do dir : flags <- getArgs actions <- direm dir putStrLn $ showDirem actions putStrLn "OK? y/n" answer <- if "-y" `elem` flags then pure "y" else getLine if "y" `isPrefixOf` answer then runDirem actions else putStrLn "Ok, quitting"