ui: Esc (outside minibuffer) resets, jumps to top

This commit is contained in:
Simon Michael 2016-06-07 09:26:16 -07:00
parent 579ab45d0a
commit bbcbaf6080
7 changed files with 64 additions and 32 deletions

View File

@ -49,8 +49,8 @@ screen = AccountsScreen{
asSetSelectedAccount a scr@AccountsScreen{asState=(l,_)} = scr{asState=(l,a)} asSetSelectedAccount a scr@AccountsScreen{asState=(l,_)} = scr{asState=(l,a)}
asSetSelectedAccount _ scr = scr asSetSelectedAccount _ scr = scr
initAccountsScreen :: Day -> AppState -> AppState initAccountsScreen :: Day -> Bool -> AppState -> AppState
initAccountsScreen d st@AppState{ initAccountsScreen d reset st@AppState{
aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}, aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}},
ajournal=j, ajournal=j,
aScreen=s@AccountsScreen{asState=(oldl,selacct)} aScreen=s@AccountsScreen{asState=(oldl,selacct)}
@ -63,9 +63,10 @@ initAccountsScreen d st@AppState{
-- (may need to move to the next leaf account when entering flat mode) -- (may need to move to the next leaf account when entering flat mode)
newl' = listMoveTo selidx newl newl' = listMoveTo selidx newl
where where
selidx = case listSelectedElement oldl of selidx = case (reset, listSelectedElement oldl) of
Nothing -> 0 (True, _) -> 0
Just (_,(_,a,_,_)) -> fromMaybe (fromMaybe 0 mprefixmatch) mexactmatch (_, Nothing) -> 0
(_, Just (_,(_,a,_,_))) -> fromMaybe (fromMaybe 0 mprefixmatch) mexactmatch
where where
mexactmatch = findIndex ((a ==) . second4) displayitems mexactmatch = findIndex ((a ==) . second4) displayitems
mprefixmatch = findIndex ((a `isAccountNamePrefixOf`) . second4) displayitems mprefixmatch = findIndex ((a `isAccountNamePrefixOf`) . second4) displayitems
@ -99,7 +100,7 @@ initAccountsScreen d st@AppState{
displayitems = map displayitem items displayitems = map displayitem items
initAccountsScreen _ _ = error "init function called with wrong screen type, should not happen" initAccountsScreen _ _ _ = error "init function called with wrong screen type, should not happen"
drawAccountsScreen :: AppState -> [Widget] drawAccountsScreen :: AppState -> [Widget]
drawAccountsScreen AppState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=ropts}} drawAccountsScreen AppState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=ropts}}
@ -153,6 +154,7 @@ drawAccountsScreen AppState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=ropts}}
,("/", "filter") ,("/", "filter")
,("DEL", "unfilter") ,("DEL", "unfilter")
,("right/enter", "register") ,("right/enter", "register")
,("ESC", "cancel/top")
,("g", "reload") ,("g", "reload")
,("q", "quit") ,("q", "quit")
] ]
@ -253,6 +255,7 @@ handleAccountsScreen st@AppState{
case ev of case ev of
Vty.EvKey (Vty.KChar 'q') [] -> halt st' Vty.EvKey (Vty.KChar 'q') [] -> halt st'
-- Vty.EvKey (Vty.KChar 'l') [Vty.MCtrl] -> do -- Vty.EvKey (Vty.KChar 'l') [Vty.MCtrl] -> do
Vty.EvKey Vty.KEsc [] -> continue $ resetScreens d st'
Vty.EvKey (Vty.KChar 'g') [] -> do Vty.EvKey (Vty.KChar 'g') [] -> do
(ej, _) <- liftIO $ journalReloadIfChanged copts d j (ej, _) <- liftIO $ journalReloadIfChanged copts d j

View File

@ -33,9 +33,9 @@ screen = ErrorScreen{
,sHandleFn = handleErrorScreen ,sHandleFn = handleErrorScreen
} }
initErrorScreen :: Day -> AppState -> AppState initErrorScreen :: Day -> Bool -> AppState -> AppState
initErrorScreen _ st@AppState{aScreen=ErrorScreen{}} = st initErrorScreen _ _ st@AppState{aScreen=ErrorScreen{}} = st
initErrorScreen _ _ = error "init function called with wrong screen type, should not happen" initErrorScreen _ _ _ = error "init function called with wrong screen type, should not happen"
drawErrorScreen :: AppState -> [Widget] drawErrorScreen :: AppState -> [Widget]
drawErrorScreen AppState{ -- aopts=_uopts@UIOpts{cliopts_=_copts@CliOpts{reportopts_=_ropts@ReportOpts{query_=querystr}}}, drawErrorScreen AppState{ -- aopts=_uopts@UIOpts{cliopts_=_copts@CliOpts{reportopts_=_ropts@ReportOpts{query_=querystr}}},
@ -103,12 +103,12 @@ handleErrorScreen st@AppState{
,aopts=UIOpts{cliopts_=copts} ,aopts=UIOpts{cliopts_=copts}
,ajournal=j ,ajournal=j
} e = do } e = do
d <- liftIO getCurrentDay
case e of case e of
Vty.EvKey Vty.KEsc [] -> halt st
Vty.EvKey (Vty.KChar 'q') [] -> halt st Vty.EvKey (Vty.KChar 'q') [] -> halt st
Vty.EvKey Vty.KEsc [] -> continue $ resetScreens d st
Vty.EvKey (Vty.KChar 'g') [] -> do Vty.EvKey (Vty.KChar 'g') [] -> do
d <- liftIO getCurrentDay
(ej, _) <- liftIO $ journalReloadIfChanged copts d j (ej, _) <- liftIO $ journalReloadIfChanged copts d j
case ej of case ej of
Left err -> continue st{aScreen=s{esState=err}} -- show latest parse error Left err -> continue st{aScreen=s{esState=err}} -- show latest parse error

View File

@ -109,7 +109,7 @@ runBrickUi uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}} j = do
-- Initialising the accounts screen is awkward, requiring -- Initialising the accounts screen is awkward, requiring
-- another temporary AppState value.. -- another temporary AppState value..
ascr' = aScreen $ ascr' = aScreen $
AS.initAccountsScreen d $ AS.initAccountsScreen d True $
AppState{ AppState{
aopts=uopts' aopts=uopts'
,ajournal=j ,ajournal=j
@ -118,7 +118,7 @@ runBrickUi uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}} j = do
,aMinibuffer=Nothing ,aMinibuffer=Nothing
} }
st = (sInitFn scr) d st = (sInitFn scr) d True
AppState{ AppState{
aopts=uopts' aopts=uopts'
,ajournal=j ,ajournal=j

View File

@ -45,8 +45,8 @@ screen = RegisterScreen{
rsSetCurrentAccount a scr@RegisterScreen{rsState=(l,_)} = scr{rsState=(l,a)} rsSetCurrentAccount a scr@RegisterScreen{rsState=(l,_)} = scr{rsState=(l,a)}
rsSetCurrentAccount _ scr = scr rsSetCurrentAccount _ scr = scr
initRegisterScreen :: Day -> AppState -> AppState initRegisterScreen :: Day -> Bool -> AppState -> AppState
initRegisterScreen d st@AppState{aopts=opts, ajournal=j, aScreen=s@RegisterScreen{rsState=(oldl,acct)}} = initRegisterScreen d reset st@AppState{aopts=opts, ajournal=j, aScreen=s@RegisterScreen{rsState=(oldl,acct)}} =
st{aScreen=s{rsState=(newl',acct)}} st{aScreen=s{rsState=(newl',acct)}}
where where
-- gather arguments and queries -- gather arguments and queries
@ -86,12 +86,13 @@ initRegisterScreen d st@AppState{aopts=opts, ajournal=j, aScreen=s@RegisterScree
-- (eg after toggling nonzero mode), otherwise select the last element. -- (eg after toggling nonzero mode), otherwise select the last element.
newl' = listMoveTo newselidx newl newl' = listMoveTo newselidx newl
where where
newselidx = case listSelectedElement oldl of newselidx = case (reset, listSelectedElement oldl) of
Nothing -> endidx (True, _) -> 0
Just (_,(_,_,_,_,_,Transaction{tindex=ti})) -> fromMaybe endidx $ findIndex ((==ti) . tindex . sixth6) displayitems (_, Nothing) -> endidx
(_, Just (_,(_,_,_,_,_,Transaction{tindex=ti}))) -> fromMaybe endidx $ findIndex ((==ti) . tindex . sixth6) displayitems
endidx = length displayitems endidx = length displayitems
initRegisterScreen _ _ = error "init function called with wrong screen type, should not happen" initRegisterScreen _ _ _ = error "init function called with wrong screen type, should not happen"
drawRegisterScreen :: AppState -> [Widget] drawRegisterScreen :: AppState -> [Widget]
drawRegisterScreen AppState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=ropts}} drawRegisterScreen AppState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=ropts}}
@ -182,6 +183,7 @@ drawRegisterScreen AppState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=ropts}}
,("/", "filter") ,("/", "filter")
,("DEL", "unfilter") ,("DEL", "unfilter")
,("right/enter", "transaction") ,("right/enter", "transaction")
,("ESC", "cancel/top")
,("g", "reload") ,("g", "reload")
,("q", "quit") ,("q", "quit")
] ]
@ -228,6 +230,7 @@ handleRegisterScreen st@AppState{
case ev of case ev of
Vty.EvKey (Vty.KChar 'q') [] -> halt st Vty.EvKey (Vty.KChar 'q') [] -> halt st
Vty.EvKey Vty.KEsc [] -> continue $ resetScreens d st
Vty.EvKey (Vty.KChar 'g') [] -> do Vty.EvKey (Vty.KChar 'g') [] -> do
(ej, _) <- liftIO $ journalReloadIfChanged copts d j (ej, _) <- liftIO $ journalReloadIfChanged copts d j

View File

@ -42,13 +42,13 @@ screen = TransactionScreen{
,sHandleFn = handleTransactionScreen ,sHandleFn = handleTransactionScreen
} }
initTransactionScreen :: Day -> AppState -> AppState initTransactionScreen :: Day -> Bool -> AppState -> AppState
initTransactionScreen _d st@AppState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=_ropts}} initTransactionScreen _d _reset st@AppState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=_ropts}}
,ajournal=_j ,ajournal=_j
,aScreen=s@TransactionScreen{tsState=((n,t),nts,a)}} = ,aScreen=s@TransactionScreen{tsState=((n,t),nts,a)}} =
st{aScreen=s{tsState=((n,t),nts,a)}} st{aScreen=s{tsState=((n,t),nts,a)}}
initTransactionScreen _ _ = error "init function called with wrong screen type, should not happen" initTransactionScreen _ _ _ = error "init function called with wrong screen type, should not happen"
drawTransactionScreen :: AppState -> [Widget] drawTransactionScreen :: AppState -> [Widget]
drawTransactionScreen AppState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=ropts}} drawTransactionScreen AppState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=ropts}}
@ -104,8 +104,8 @@ handleTransactionScreen st@AppState{
(iprev,tprev) = maybe (i,t) ((i-1),) $ lookup (i-1) nts (iprev,tprev) = maybe (i,t) ((i-1),) $ lookup (i-1) nts
(inext,tnext) = maybe (i,t) ((i+1),) $ lookup (i+1) nts (inext,tnext) = maybe (i,t) ((i+1),) $ lookup (i+1) nts
case e of case e of
Vty.EvKey Vty.KEsc [] -> halt st
Vty.EvKey (Vty.KChar 'q') [] -> halt st Vty.EvKey (Vty.KChar 'q') [] -> halt st
Vty.EvKey Vty.KEsc [] -> continue $ resetScreens d st
Vty.EvKey (Vty.KChar 'g') [] -> do Vty.EvKey (Vty.KChar 'g') [] -> do
d <- liftIO getCurrentDay d <- liftIO getCurrentDay

View File

@ -70,7 +70,8 @@ data Screen =
) )
,AccountName -- full name of the currently selected account (or "") ,AccountName -- full name of the currently selected account (or "")
) )
,sInitFn :: Day -> AppState -> AppState -- ^ function to generate the screen's state on entry or change ,sInitFn :: Day -> Bool -> AppState -> AppState -- ^ function to generate/update the screen's state,
-- takes the current date and whether to reset the selection.
,sDrawFn :: AppState -> [Widget] -- ^ brick renderer to use for this screen ,sDrawFn :: AppState -> [Widget] -- ^ brick renderer to use for this screen
,sHandleFn :: AppState -> V.Event -> EventM (Next AppState) -- ^ brick event handler to use for this screen ,sHandleFn :: AppState -> V.Event -> EventM (Next AppState) -- ^ brick event handler to use for this screen
} }
@ -85,22 +86,22 @@ data Screen =
) )
,AccountName -- full name of the acct we are showing a register for ,AccountName -- full name of the acct we are showing a register for
) )
,sInitFn :: Day -> AppState -> AppState -- ^ function to generate the screen's state on entry or change ,sInitFn :: Day -> Bool -> AppState -> AppState
,sDrawFn :: AppState -> [Widget] -- ^ brick renderer to use for this screen ,sDrawFn :: AppState -> [Widget]
,sHandleFn :: AppState -> V.Event -> EventM (Next AppState) -- ^ brick event handler to use for this screen ,sHandleFn :: AppState -> V.Event -> EventM (Next AppState)
} }
| TransactionScreen { | TransactionScreen {
tsState :: ((Integer, Transaction) -- the (numbered) transaction we are currently viewing tsState :: ((Integer, Transaction) -- the (numbered) transaction we are currently viewing
,[(Integer, Transaction)] -- the list of numbered transactions we can step through ,[(Integer, Transaction)] -- the list of numbered transactions we can step through
,AccountName -- the account whose register we entered this screen from ,AccountName -- the account whose register we entered this screen from
) )
,sInitFn :: Day -> AppState -> AppState ,sInitFn :: Day -> Bool -> AppState -> AppState
,sDrawFn :: AppState -> [Widget] ,sDrawFn :: AppState -> [Widget]
,sHandleFn :: AppState -> V.Event -> EventM (Next AppState) ,sHandleFn :: AppState -> V.Event -> EventM (Next AppState)
} }
| ErrorScreen { | ErrorScreen {
esState :: String -- error message to display esState :: String -- error message to display
,sInitFn :: Day -> AppState -> AppState ,sInitFn :: Day -> Bool -> AppState -> AppState
,sDrawFn :: AppState -> [Widget] ,sDrawFn :: AppState -> [Widget]
,sHandleFn :: AppState -> V.Event -> EventM (Next AppState) ,sHandleFn :: AppState -> V.Event -> EventM (Next AppState)
} }

View File

@ -3,6 +3,7 @@
module Hledger.UI.UIUtils ( module Hledger.UI.UIUtils (
pushScreen pushScreen
,popScreen ,popScreen
,resetScreens
,screenEnter ,screenEnter
,reload ,reload
,getViewportSize ,getViewportSize
@ -23,6 +24,7 @@ module Hledger.UI.UIUtils (
,stToggleFlat ,stToggleFlat
,stToggleReal ,stToggleReal
,stFilter ,stFilter
,stResetFilter
,stShowMinibuffer ,stShowMinibuffer
,stHideMinibuffer ,stHideMinibuffer
) where ) where
@ -98,6 +100,22 @@ stFilter :: String -> AppState -> AppState
stFilter s st@AppState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} = stFilter s st@AppState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
st{aopts=uopts{cliopts_=copts{reportopts_=ropts{query_=s}}}} st{aopts=uopts{cliopts_=copts{reportopts_=ropts{query_=s}}}}
-- | Clear all filter queries/flags.
stResetFilter :: AppState -> AppState
stResetFilter st@AppState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
st{aopts=uopts{cliopts_=copts{reportopts_=ropts{
empty_=True
,cleared_=False
,pending_=False
,uncleared_=False
,real_=False
,query_=""
}}}}
stResetDepth :: AppState -> AppState
stResetDepth st@AppState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
st{aopts=uopts{cliopts_=copts{reportopts_=ropts{depth_=Nothing}}}}
-- | Enable the minibuffer, setting its content to the current query with the cursor at the end. -- | Enable the minibuffer, setting its content to the current query with the cursor at the end.
stShowMinibuffer st = st{aMinibuffer=Just e} stShowMinibuffer st = st{aMinibuffer=Just e}
where where
@ -117,8 +135,8 @@ reload j d st@AppState{aScreen=s,aPrevScreens=ss} =
let let
first:rest = reverse $ s:ss first:rest = reverse $ s:ss
st0 = st{ajournal=j, aScreen=first, aPrevScreens=[]} st0 = st{ajournal=j, aScreen=first, aPrevScreens=[]}
st1 = (sInitFn first) d st0 st1 = (sInitFn first) d False st0
st2 = foldl' (\st s -> (sInitFn s) d $ pushScreen s st) st1 rest st2 = foldl' (\st s -> (sInitFn s) d False $ pushScreen s st) st1 rest
in in
st2 st2
@ -131,13 +149,20 @@ popScreen :: AppState -> AppState
popScreen st@AppState{aPrevScreens=s:ss} = st{aScreen=s, aPrevScreens=ss} popScreen st@AppState{aPrevScreens=s:ss} = st{aScreen=s, aPrevScreens=ss}
popScreen st = st popScreen st = st
resetScreens :: Day -> AppState -> AppState
resetScreens d st@AppState{aScreen=s,aPrevScreens=ss} =
(sInitFn topscreen) d True $ stResetDepth $ stResetFilter $ stHideMinibuffer st{aScreen=topscreen, aPrevScreens=[]}
where
topscreen = case ss of _:_ -> last ss
[] -> s
-- clearScreens :: AppState -> AppState -- clearScreens :: AppState -> AppState
-- clearScreens st = st{aPrevScreens=[]} -- clearScreens st = st{aPrevScreens=[]}
-- | Enter a new screen, saving the old screen & state in the -- | Enter a new screen, saving the old screen & state in the
-- navigation history and initialising the new screen's state. -- navigation history and initialising the new screen's state.
screenEnter :: Day -> Screen -> AppState -> AppState screenEnter :: Day -> Screen -> AppState -> AppState
screenEnter d scr st = (sInitFn scr) d $ screenEnter d scr st = (sInitFn scr) d True $
pushScreen scr pushScreen scr
st st