module Mit.Undo
( Undo (..),
showUndos,
parseUndos,
applyUndo,
undosStash,
)
where
import Data.Text qualified as Text
import Mit.Env (Env)
import Mit.Git
import Mit.Monad
import Mit.Prelude
data Undo
= Apply Text
| Reset Text
| Revert Text
deriving stock (Undo -> Undo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Undo -> Undo -> Bool
$c/= :: Undo -> Undo -> Bool
== :: Undo -> Undo -> Bool
$c== :: Undo -> Undo -> Bool
Eq, Int -> Undo -> ShowS
[Undo] -> ShowS
Undo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Undo] -> ShowS
$cshowList :: [Undo] -> ShowS
show :: Undo -> String
$cshow :: Undo -> String
showsPrec :: Int -> Undo -> ShowS
$cshowsPrec :: Int -> Undo -> ShowS
Show)
showUndos :: [Undo] -> Text
showUndos :: [Undo] -> Text
showUndos =
Text -> [Text] -> Text
Text.intercalate Text
" " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map Undo -> Text
showUndo
where
showUndo :: Undo -> Text
showUndo :: Undo -> Text
showUndo = \case
Apply Text
commit -> Text
"apply/" forall a. Semigroup a => a -> a -> a
<> Text
commit
Reset Text
commit -> Text
"reset/" forall a. Semigroup a => a -> a -> a
<> Text
commit
Revert Text
commit -> Text
"revert/" forall a. Semigroup a => a -> a -> a
<> Text
commit
parseUndos :: Text -> Maybe [Undo]
parseUndos :: Text -> Maybe [Undo]
parseUndos = do
Text -> [Text]
Text.words forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Text -> Maybe Undo
parseUndo
where
parseUndo :: Text -> Maybe Undo
parseUndo :: Text -> Maybe Undo
parseUndo Text
text =
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum
[ Text -> Undo
Apply forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> Maybe Text
Text.stripPrefix Text
"apply/" Text
text,
Text -> Undo
Reset forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> Maybe Text
Text.stripPrefix Text
"reset/" Text
text,
Text -> Undo
Revert forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> Maybe Text
Text.stripPrefix Text
"revert/" Text
text,
forall a. HasCallStack => String -> a
error (forall a. Show a => a -> String
show Text
text)
]
applyUndo :: Undo -> Mit Env x ()
applyUndo :: forall x. Undo -> Mit Env x ()
applyUndo = \case
Apply Text
commit -> do
forall x. [Text] -> Mit Env x ()
git_ [Text
"stash", Text
"apply", Text
"--quiet", Text
commit]
forall x. Mit Env x ()
gitUnstageChanges
Reset Text
commit -> do
forall x. [Text] -> Mit Env x ()
git_ [Text
"clean", Text
"-d", Text
"--force"]
forall a x. ProcessOutput a => [Text] -> Mit Env x a
git [Text
"reset", Text
"--hard", Text
commit]
Revert Text
commit -> forall x. [Text] -> Mit Env x ()
git_ [Text
"revert", Text
commit]
undosStash :: [Undo] -> Maybe Text
undosStash :: [Undo] -> Maybe Text
undosStash [Undo]
undos =
forall a. [a] -> Maybe a
listToMaybe [Text
commit | Apply Text
commit <- [Undo]
undos]