{-# LANGUAGE MultiWayIf, ViewPatterns, TupleSections #-}
{-# LANGUAGE FlexibleContexts, MonoLocalBinds #-}
module Aura.Commands.B
( saveState
, restoreState
, cleanStates
, listStates
) where
import Aura.Core (warn)
import Aura.Languages
import Aura.Settings
import Aura.State
import Aura.Utils (optionalPrompt)
import BasePrelude
import qualified Data.Text as T
import System.Path (toFilePath, takeFileName, toUnrootedFilePath)
import System.Path.IO (removeFile)
cleanStates :: Settings -> Word -> IO ()
cleanStates ss (fromIntegral -> n) = do
stfs <- reverse <$> getStateFiles
(pinned, others) <- partition p <$> traverse (\sf -> (sf,) <$> readState sf) stfs
warn ss . cleanStates_4 (length stfs) $ langOf ss
unless (null pinned) . warn ss . cleanStates_6 (length pinned) $ langOf ss
unless (null stfs) . warn ss . cleanStates_5 (T.pack . toUnrootedFilePath . takeFileName $ head stfs) $ langOf ss
okay <- optionalPrompt ss $ cleanStates_2 n
if | not okay -> warn ss . cleanStates_3 $ langOf ss
| otherwise -> traverse_ (removeFile . fst) . drop n $ others
where p = maybe False pinnedOf . snd
listStates :: IO ()
listStates = getStateFiles >>= traverse_ (putStrLn . toFilePath)