{-# LANGUAGE FlexibleContexts #-}
module StateManagement where
import Brick
import Control.Monad.IO.Class
import Control.Monad.State.Class
import Control.Monad.State.Lazy (execState)
import Control.Monad (when, (<=<))
import Data.Maybe (fromJust)
import Lens.Micro.Platform
import Recents
import States hiding (cardState)
import Stack hiding (head)
import qualified Brick.Widgets.List as L
import qualified Data.Vector as Vec
import qualified Data.Map.Strict as M
import qualified Stack
getMode :: State -> Mode
getMode :: State -> Mode
getMode (MainMenuState MMS
_) = Mode
MainMenu
getMode (SettingsState SS
_) = Mode
Settings
getMode (InfoState IS
_) = Mode
Info
getMode (CardSelectorState CSS
_) = Mode
CardSelector
getMode (FileBrowserState FBS
_) = Mode
FileBrowser
getMode (CardsState CS
_) = Mode
Cards
getMode (ParameterState PS
_) = Mode
Parameter
getState :: MonadState GlobalState m => m State
getState :: forall (m :: * -> *). MonadState GlobalState m => m State
getState = Maybe State -> State
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe State -> State) -> m (Maybe State) -> m State
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m (Maybe State)
forall (m :: * -> *). MonadState GlobalState m => m (Maybe State)
safeGetState
mms :: Lens' GlobalState MMS
mms :: Lens' GlobalState MMS
mms = (GlobalState -> MMS)
-> (GlobalState -> MMS -> GlobalState) -> Lens' GlobalState MMS
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\GlobalState
gs -> State -> MMS
mmsCast (State -> MMS) -> (Maybe State -> State) -> Maybe State -> MMS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe State -> State
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe State -> MMS) -> Maybe State -> MMS
forall a b. (a -> b) -> a -> b
$ Mode -> Map Mode State -> Maybe State
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Mode
MainMenu (GlobalState
gs GlobalState
-> Getting (Map Mode State) GlobalState (Map Mode State)
-> Map Mode State
forall s a. s -> Getting a s a -> a
^. Getting (Map Mode State) GlobalState (Map Mode State)
Lens' GlobalState (Map Mode State)
states)) (\GlobalState
gs MMS
s -> GlobalState
gs GlobalState -> (GlobalState -> GlobalState) -> GlobalState
forall a b. a -> (a -> b) -> b
& (Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState
Lens' GlobalState (Map Mode State)
states ((Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState)
-> (Map Mode State -> Map Mode State) -> GlobalState -> GlobalState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Mode -> State -> Map Mode State -> Map Mode State
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Mode
MainMenu (MMS -> State
MainMenuState MMS
s))
where mmsCast :: State -> MMS
mmsCast s :: State
s@(MainMenuState MMS
mms) = MMS
mms
mmsCast State
_ = [Char] -> MMS
forall a. HasCallStack => [Char] -> a
error [Char]
"impossible"
ss :: Lens' GlobalState SS
ss :: Lens' GlobalState SS
ss = (GlobalState -> SS)
-> (GlobalState -> SS -> GlobalState) -> Lens' GlobalState SS
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\GlobalState
gs -> State -> SS
ssCast (State -> SS) -> (Maybe State -> State) -> Maybe State -> SS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe State -> State
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe State -> SS) -> Maybe State -> SS
forall a b. (a -> b) -> a -> b
$ Mode -> Map Mode State -> Maybe State
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Mode
Settings (GlobalState
gs GlobalState
-> Getting (Map Mode State) GlobalState (Map Mode State)
-> Map Mode State
forall s a. s -> Getting a s a -> a
^. Getting (Map Mode State) GlobalState (Map Mode State)
Lens' GlobalState (Map Mode State)
states)) (\GlobalState
gs SS
s -> GlobalState
gs GlobalState -> (GlobalState -> GlobalState) -> GlobalState
forall a b. a -> (a -> b) -> b
& (Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState
Lens' GlobalState (Map Mode State)
states ((Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState)
-> (Map Mode State -> Map Mode State) -> GlobalState -> GlobalState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Mode -> State -> Map Mode State -> Map Mode State
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Mode
Settings (SS -> State
SettingsState SS
s))
where ssCast :: State -> SS
ssCast s :: State
s@(SettingsState SS
ss) = SS
ss
ssCast State
_ = [Char] -> SS
forall a. HasCallStack => [Char] -> a
error [Char]
"impossible"
is :: Lens' GlobalState IS
is :: Lens' GlobalState IS
is = (GlobalState -> IS)
-> (GlobalState -> IS -> GlobalState) -> Lens' GlobalState IS
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\GlobalState
gs -> State -> IS
isCast (State -> IS) -> (Maybe State -> State) -> Maybe State -> IS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe State -> State
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe State -> IS) -> Maybe State -> IS
forall a b. (a -> b) -> a -> b
$ Mode -> Map Mode State -> Maybe State
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Mode
Info (GlobalState
gs GlobalState
-> Getting (Map Mode State) GlobalState (Map Mode State)
-> Map Mode State
forall s a. s -> Getting a s a -> a
^. Getting (Map Mode State) GlobalState (Map Mode State)
Lens' GlobalState (Map Mode State)
states)) (\GlobalState
gs IS
s -> GlobalState
gs GlobalState -> (GlobalState -> GlobalState) -> GlobalState
forall a b. a -> (a -> b) -> b
& (Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState
Lens' GlobalState (Map Mode State)
states ((Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState)
-> (Map Mode State -> Map Mode State) -> GlobalState -> GlobalState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Mode -> State -> Map Mode State -> Map Mode State
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Mode
Info (IS -> State
InfoState IS
s))
where isCast :: State -> IS
isCast s :: State
s@(InfoState IS
ss) = IS
ss
isCast State
_ = [Char] -> IS
forall a. HasCallStack => [Char] -> a
error [Char]
"impossible"
cs :: Lens' GlobalState CS
cs :: Lens' GlobalState CS
cs = (GlobalState -> CS)
-> (GlobalState -> CS -> GlobalState) -> Lens' GlobalState CS
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\GlobalState
gs -> State -> CS
csCast (State -> CS) -> (Maybe State -> State) -> Maybe State -> CS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe State -> State
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe State -> CS) -> Maybe State -> CS
forall a b. (a -> b) -> a -> b
$ Mode -> Map Mode State -> Maybe State
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Mode
Cards (GlobalState
gs GlobalState
-> Getting (Map Mode State) GlobalState (Map Mode State)
-> Map Mode State
forall s a. s -> Getting a s a -> a
^. Getting (Map Mode State) GlobalState (Map Mode State)
Lens' GlobalState (Map Mode State)
states)) (\GlobalState
gs CS
s -> GlobalState
gs GlobalState -> (GlobalState -> GlobalState) -> GlobalState
forall a b. a -> (a -> b) -> b
& (Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState
Lens' GlobalState (Map Mode State)
states ((Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState)
-> (Map Mode State -> Map Mode State) -> GlobalState -> GlobalState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Mode -> State -> Map Mode State -> Map Mode State
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Mode
Cards (CS -> State
CardsState CS
s))
where csCast :: State -> CS
csCast s :: State
s@(CardsState CS
cs) = CS
cs
csCast State
_ = [Char] -> CS
forall a. HasCallStack => [Char] -> a
error [Char]
"impossible"
css :: Lens' GlobalState CSS
css :: Lens' GlobalState CSS
css = (GlobalState -> CSS)
-> (GlobalState -> CSS -> GlobalState) -> Lens' GlobalState CSS
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\GlobalState
gs -> State -> CSS
cssCast (State -> CSS) -> (Maybe State -> State) -> Maybe State -> CSS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe State -> State
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe State -> CSS) -> Maybe State -> CSS
forall a b. (a -> b) -> a -> b
$ Mode -> Map Mode State -> Maybe State
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Mode
CardSelector (GlobalState
gs GlobalState
-> Getting (Map Mode State) GlobalState (Map Mode State)
-> Map Mode State
forall s a. s -> Getting a s a -> a
^. Getting (Map Mode State) GlobalState (Map Mode State)
Lens' GlobalState (Map Mode State)
states)) (\GlobalState
gs CSS
s -> GlobalState
gs GlobalState -> (GlobalState -> GlobalState) -> GlobalState
forall a b. a -> (a -> b) -> b
& (Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState
Lens' GlobalState (Map Mode State)
states ((Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState)
-> (Map Mode State -> Map Mode State) -> GlobalState -> GlobalState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Mode -> State -> Map Mode State -> Map Mode State
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Mode
CardSelector (CSS -> State
CardSelectorState CSS
s))
where cssCast :: State -> CSS
cssCast s :: State
s@(CardSelectorState CSS
css) = CSS
css
cssCast State
_ = [Char] -> CSS
forall a. HasCallStack => [Char] -> a
error [Char]
"impossible"
fbs :: Lens' GlobalState FBS
fbs :: Lens' GlobalState FBS
fbs = (GlobalState -> FBS)
-> (GlobalState -> FBS -> GlobalState) -> Lens' GlobalState FBS
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\GlobalState
gs -> State -> FBS
fbsCast (State -> FBS) -> (Maybe State -> State) -> Maybe State -> FBS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe State -> State
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe State -> FBS) -> Maybe State -> FBS
forall a b. (a -> b) -> a -> b
$ Mode -> Map Mode State -> Maybe State
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Mode
FileBrowser (GlobalState
gs GlobalState
-> Getting (Map Mode State) GlobalState (Map Mode State)
-> Map Mode State
forall s a. s -> Getting a s a -> a
^. Getting (Map Mode State) GlobalState (Map Mode State)
Lens' GlobalState (Map Mode State)
states)) (\GlobalState
gs FBS
s -> GlobalState
gs GlobalState -> (GlobalState -> GlobalState) -> GlobalState
forall a b. a -> (a -> b) -> b
& (Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState
Lens' GlobalState (Map Mode State)
states ((Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState)
-> (Map Mode State -> Map Mode State) -> GlobalState -> GlobalState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Mode -> State -> Map Mode State -> Map Mode State
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Mode
FileBrowser (FBS -> State
FileBrowserState FBS
s))
where fbsCast :: State -> FBS
fbsCast s :: State
s@(FileBrowserState FBS
fbs) = FBS
fbs
fbsCast State
_ = [Char] -> FBS
forall a. HasCallStack => [Char] -> a
error [Char]
"impossible"
ps :: Lens' GlobalState PS
ps :: Lens' GlobalState PS
ps = (GlobalState -> PS)
-> (GlobalState -> PS -> GlobalState) -> Lens' GlobalState PS
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\GlobalState
gs -> State -> PS
psCast (State -> PS) -> (Maybe State -> State) -> Maybe State -> PS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe State -> State
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe State -> PS) -> Maybe State -> PS
forall a b. (a -> b) -> a -> b
$ Mode -> Map Mode State -> Maybe State
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Mode
Parameter (GlobalState
gs GlobalState
-> Getting (Map Mode State) GlobalState (Map Mode State)
-> Map Mode State
forall s a. s -> Getting a s a -> a
^. Getting (Map Mode State) GlobalState (Map Mode State)
Lens' GlobalState (Map Mode State)
states)) (\GlobalState
gs PS
s -> GlobalState
gs GlobalState -> (GlobalState -> GlobalState) -> GlobalState
forall a b. a -> (a -> b) -> b
& (Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState
Lens' GlobalState (Map Mode State)
states ((Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState)
-> (Map Mode State -> Map Mode State) -> GlobalState -> GlobalState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Mode -> State -> Map Mode State -> Map Mode State
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Mode
Parameter (PS -> State
ParameterState PS
s))
where psCast :: State -> PS
psCast s :: State
s@(ParameterState PS
ps) = PS
ps
psCast State
_ = [Char] -> PS
forall a. HasCallStack => [Char] -> a
error [Char]
"impossible"
goToState_ :: GlobalState -> State -> GlobalState
goToState_ :: GlobalState -> State -> GlobalState
goToState_ GlobalState
gs State
s = State GlobalState IS -> GlobalState -> GlobalState
forall s a. State s a -> s -> s
execState (State -> State GlobalState IS
forall (m :: * -> *). MonadState GlobalState m => State -> m IS
goToState State
s) GlobalState
gs
goToState :: MonadState GlobalState m => State -> m ()
goToState :: forall (m :: * -> *). MonadState GlobalState m => State -> m IS
goToState State
s = do (Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState
Lens' GlobalState (Map Mode State)
states ((Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState)
-> (Map Mode State -> Map Mode State) -> m IS
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m IS
%= Mode -> State -> Map Mode State -> Map Mode State
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (State -> Mode
getMode State
s) State
s
(Stack Mode -> Identity (Stack Mode))
-> GlobalState -> Identity GlobalState
Lens' GlobalState (Stack Mode)
stack ((Stack Mode -> Identity (Stack Mode))
-> GlobalState -> Identity GlobalState)
-> (Stack Mode -> Stack Mode) -> m IS
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m IS
%= Mode -> Stack Mode -> Stack Mode
forall a. Ord a => a -> Stack a -> Stack a
insert (State -> Mode
getMode State
s)
moveToState :: MonadState GlobalState m => State -> m ()
moveToState :: forall (m :: * -> *). MonadState GlobalState m => State -> m IS
moveToState State
s = do
m IS
forall (m :: * -> *). MonadState GlobalState m => m IS
popState
State -> m IS
forall (m :: * -> *). MonadState GlobalState m => State -> m IS
goToState State
s
removeToState :: MonadState GlobalState m => State -> m ()
removeToState :: forall (m :: * -> *). MonadState GlobalState m => State -> m IS
removeToState State
s = do
m IS
forall (m :: * -> *). MonadState GlobalState m => m IS
popState
Mode
current <- Stack Mode -> Mode
forall a. Stack a -> a
Stack.head (Stack Mode -> Mode) -> m (Stack Mode) -> m Mode
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Getting (Stack Mode) GlobalState (Stack Mode) -> m (Stack Mode)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting (Stack Mode) GlobalState (Stack Mode)
Lens' GlobalState (Stack Mode)
stack
if Mode
current Mode -> Mode -> Bool
forall a. Eq a => a -> a -> Bool
== State -> Mode
getMode State
s
then State -> m IS
forall (m :: * -> *). MonadState GlobalState m => State -> m IS
moveToState State
s
else State -> m IS
forall (m :: * -> *). MonadState GlobalState m => State -> m IS
removeToState State
s
popState :: MonadState GlobalState m => m ()
popState :: forall (m :: * -> *). MonadState GlobalState m => m IS
popState = do
Stack Mode
s <- Getting (Stack Mode) GlobalState (Stack Mode) -> m (Stack Mode)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting (Stack Mode) GlobalState (Stack Mode)
Lens' GlobalState (Stack Mode)
stack
let top :: Mode
top = Stack Mode -> Mode
forall a. Stack a -> a
Stack.head Stack Mode
s
s' :: Stack Mode
s' = Stack Mode -> Stack Mode
forall a. Ord a => Stack a -> Stack a
Stack.pop Stack Mode
s
(Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState
Lens' GlobalState (Map Mode State)
states ((Map Mode State -> Identity (Map Mode State))
-> GlobalState -> Identity GlobalState)
-> (Map Mode State -> Map Mode State) -> m IS
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m IS
%= Mode -> Map Mode State -> Map Mode State
forall k a. Ord k => k -> Map k a -> Map k a
M.delete Mode
top
(Stack Mode -> Identity (Stack Mode))
-> GlobalState -> Identity GlobalState
Lens' GlobalState (Stack Mode)
stack ((Stack Mode -> Identity (Stack Mode))
-> GlobalState -> Identity GlobalState)
-> Stack Mode -> m IS
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m IS
.= Stack Mode
s'
popStateOrQuit :: EventM n GlobalState ()
popStateOrQuit :: forall n. EventM n GlobalState IS
popStateOrQuit =
do EventM n GlobalState IS
forall (m :: * -> *). MonadState GlobalState m => m IS
popState
Stack Mode
s <- Getting (Stack Mode) GlobalState (Stack Mode)
-> EventM n GlobalState (Stack Mode)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting (Stack Mode) GlobalState (Stack Mode)
Lens' GlobalState (Stack Mode)
stack
Bool -> EventM n GlobalState IS -> EventM n GlobalState IS
forall (f :: * -> *). Applicative f => Bool -> f IS -> f IS
when (Stack Mode -> Int
forall a. Stack a -> Int
Stack.size Stack Mode
s Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) EventM n GlobalState IS
forall n s. EventM n s IS
halt
safeGetState :: MonadState GlobalState m => m (Maybe State)
safeGetState :: forall (m :: * -> *). MonadState GlobalState m => m (Maybe State)
safeGetState = do
GlobalState
gs <- m GlobalState
forall s (m :: * -> *). MonadState s m => m s
get
Maybe State -> m (Maybe State)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe State -> m (Maybe State)) -> Maybe State -> m (Maybe State)
forall a b. (a -> b) -> a -> b
$ do
Mode
key <- Stack Mode -> Maybe Mode
forall a. Stack a -> Maybe a
safeHead (GlobalState
gs GlobalState
-> Getting (Stack Mode) GlobalState (Stack Mode) -> Stack Mode
forall s a. s -> Getting a s a -> a
^. Getting (Stack Mode) GlobalState (Stack Mode)
Lens' GlobalState (Stack Mode)
stack)
Mode -> Map Mode State -> Maybe State
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Mode
key (GlobalState
gs GlobalState
-> Getting (Map Mode State) GlobalState (Map Mode State)
-> Map Mode State
forall s a. s -> Getting a s a -> a
^. Getting (Map Mode State) GlobalState (Map Mode State)
Lens' GlobalState (Map Mode State)
states)
goToModeOrQuit :: Mode -> EventM n GlobalState ()
goToModeOrQuit :: forall n. Mode -> EventM n GlobalState IS
goToModeOrQuit Mode
mode = do
Maybe State
mMode <- Mode -> Map Mode State -> Maybe State
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Mode
mode (Map Mode State -> Maybe State)
-> EventM n GlobalState (Map Mode State)
-> EventM n GlobalState (Maybe State)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Getting (Map Mode State) GlobalState (Map Mode State)
-> EventM n GlobalState (Map Mode State)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting (Map Mode State) GlobalState (Map Mode State)
Lens' GlobalState (Map Mode State)
states
EventM n GlobalState IS
-> (State -> EventM n GlobalState IS)
-> Maybe State
-> EventM n GlobalState IS
forall b a. b -> (a -> b) -> Maybe a -> b
maybe EventM n GlobalState IS
forall n s. EventM n s IS
halt State -> EventM n GlobalState IS
forall (m :: * -> *). MonadState GlobalState m => State -> m IS
goToState Maybe State
mMode
removeToMode :: MonadState GlobalState m => Mode -> m ()
removeToMode :: forall (m :: * -> *). MonadState GlobalState m => Mode -> m IS
removeToMode Mode
m = do
m IS
forall (m :: * -> *). MonadState GlobalState m => m IS
popState
Mode
current <- Stack Mode -> Mode
forall a. Stack a -> a
Stack.head (Stack Mode -> Mode) -> m (Stack Mode) -> m Mode
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Getting (Stack Mode) GlobalState (Stack Mode) -> m (Stack Mode)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting (Stack Mode) GlobalState (Stack Mode)
Lens' GlobalState (Stack Mode)
stack
if Mode
current Mode -> Mode -> Bool
forall a. Eq a => a -> a -> Bool
== Mode
m
then IS -> m IS
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else Mode -> m IS
forall (m :: * -> *). MonadState GlobalState m => Mode -> m IS
removeToMode Mode
m
removeToModeOrQuit :: Mode -> EventM n GlobalState ()
removeToModeOrQuit :: forall n. Mode -> EventM n GlobalState IS
removeToModeOrQuit = EventM n GlobalState IS -> Mode -> EventM n GlobalState IS
forall n.
EventM n GlobalState IS -> Mode -> EventM n GlobalState IS
removeToModeOrQuit' (EventM n GlobalState IS -> Mode -> EventM n GlobalState IS)
-> EventM n GlobalState IS -> Mode -> EventM n GlobalState IS
forall a b. (a -> b) -> a -> b
$ IS -> EventM n GlobalState IS
forall a. a -> EventM n GlobalState a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
removeToModeOrQuit' :: EventM n GlobalState () -> Mode -> EventM n GlobalState ()
removeToModeOrQuit' :: forall n.
EventM n GlobalState IS -> Mode -> EventM n GlobalState IS
removeToModeOrQuit' EventM n GlobalState IS
beforeMoving Mode
mode = do
Maybe State
mState <- Mode -> Map Mode State -> Maybe State
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Mode
mode (Map Mode State -> Maybe State)
-> EventM n GlobalState (Map Mode State)
-> EventM n GlobalState (Maybe State)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Getting (Map Mode State) GlobalState (Map Mode State)
-> EventM n GlobalState (Map Mode State)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting (Map Mode State) GlobalState (Map Mode State)
Lens' GlobalState (Map Mode State)
states
case Maybe State
mState of
Maybe State
Nothing -> EventM n GlobalState IS
forall n s. EventM n s IS
halt
Just State
m -> do
GlobalState
gs <- EventM n GlobalState GlobalState
forall s (m :: * -> *). MonadState s m => m s
get
EventM n GlobalState IS
beforeMoving
Mode -> EventM n GlobalState IS
forall (m :: * -> *). MonadState GlobalState m => Mode -> m IS
removeToMode Mode
mode
refreshRecents :: (MonadState CSS m, MonadIO m) => m ()
refreshRecents :: forall (m :: * -> *). (MonadState CSS m, MonadIO m) => m IS
refreshRecents = do
Stack [Char]
rs <- IO (Stack [Char]) -> m (Stack [Char])
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO (Stack [Char])
getRecents
let prettyRecents :: [[Char]]
prettyRecents = [[Char]] -> [[Char]]
shortenFilepaths (Stack [Char] -> [[Char]]
forall a. OSet a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Stack [Char]
rs)
options :: Vector [Char]
options = [[Char]] -> Vector [Char]
forall a. [a] -> Vector a
Vec.fromList ([[Char]]
prettyRecents [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ [[Char]
"Select file from system"])
(Stack [Char] -> Identity (Stack [Char])) -> CSS -> Identity CSS
Lens' CSS (Stack [Char])
recents ((Stack [Char] -> Identity (Stack [Char])) -> CSS -> Identity CSS)
-> Stack [Char] -> m IS
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m IS
.= Stack [Char]
rs
(List Name [Char] -> Identity (List Name [Char]))
-> CSS -> Identity CSS
Lens' CSS (List Name [Char])
list ((List Name [Char] -> Identity (List Name [Char]))
-> CSS -> Identity CSS)
-> List Name [Char] -> m IS
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m IS
.= Name -> Vector [Char] -> Int -> List Name [Char]
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
L.list Name
RecentsList Vector [Char]
options Int
1