ui: simplify screen naming & importing
This commit is contained in:
parent
70d596fb38
commit
5259605e82
@ -4,7 +4,7 @@
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
|
||||
module Hledger.UI.AccountsScreen
|
||||
(screen
|
||||
(accountsScreen
|
||||
,initAccountsScreen
|
||||
,asSetSelectedAccount
|
||||
)
|
||||
@ -36,10 +36,11 @@ import Hledger.UI.UIOptions
|
||||
-- import Hledger.UI.Theme
|
||||
import Hledger.UI.UITypes
|
||||
import Hledger.UI.UIUtils
|
||||
import qualified Hledger.UI.RegisterScreen as RS (screen, rsSetCurrentAccount)
|
||||
import qualified Hledger.UI.ErrorScreen as ES (stReloadJournalIfChanged)
|
||||
import Hledger.UI.RegisterScreen
|
||||
import Hledger.UI.ErrorScreen
|
||||
|
||||
screen = AccountsScreen{
|
||||
accountsScreen :: Screen
|
||||
accountsScreen = AccountsScreen{
|
||||
asState = (list "accounts" V.empty 1, "")
|
||||
,sInitFn = initAccountsScreen
|
||||
,sDrawFn = drawAccountsScreen
|
||||
@ -256,7 +257,7 @@ handleAccountsScreen st@AppState{
|
||||
Vty.EvKey (Vty.KChar 'q') [] -> halt st'
|
||||
-- Vty.EvKey (Vty.KChar 'l') [Vty.MCtrl] -> do
|
||||
Vty.EvKey Vty.KEsc [] -> continue $ resetScreens d st'
|
||||
Vty.EvKey (Vty.KChar 'g') [] -> liftIO (ES.stReloadJournalIfChanged copts d j st') >>= continue
|
||||
Vty.EvKey (Vty.KChar 'g') [] -> liftIO (stReloadJournalIfChanged copts d j st') >>= continue
|
||||
Vty.EvKey (Vty.KChar '-') [] -> continue $ regenerateScreens j d $ decDepth st'
|
||||
Vty.EvKey (Vty.KChar '+') [] -> continue $ regenerateScreens j d $ incDepth st'
|
||||
Vty.EvKey (Vty.KChar '=') [] -> continue $ regenerateScreens j d $ incDepth st'
|
||||
@ -280,7 +281,7 @@ handleAccountsScreen st@AppState{
|
||||
Vty.EvKey (Vty.KLeft) [] -> continue $ popScreen st'
|
||||
Vty.EvKey (k) [] | k `elem` [Vty.KRight, Vty.KEnter] -> do
|
||||
let
|
||||
scr = RS.rsSetCurrentAccount selacct' RS.screen
|
||||
scr = rsSetCurrentAccount selacct' registerScreen
|
||||
st'' = screenEnter d scr st'
|
||||
scrollTopRegister
|
||||
continue st''
|
||||
|
||||
@ -3,7 +3,7 @@
|
||||
{-# LANGUAGE OverloadedStrings, FlexibleContexts #-}
|
||||
|
||||
module Hledger.UI.ErrorScreen
|
||||
(screen
|
||||
(errorScreen
|
||||
,stReloadJournalIfChanged
|
||||
)
|
||||
where
|
||||
@ -28,7 +28,8 @@ import Hledger.UI.UIOptions
|
||||
import Hledger.UI.UITypes
|
||||
import Hledger.UI.UIUtils
|
||||
|
||||
screen = ErrorScreen{
|
||||
errorScreen :: Screen
|
||||
errorScreen = ErrorScreen{
|
||||
esState = ""
|
||||
,sInitFn = initErrorScreen
|
||||
,sDrawFn = drawErrorScreen
|
||||
@ -132,5 +133,5 @@ stReloadJournalIfChanged copts d j st = do
|
||||
(ej, _) <- journalReloadIfChanged copts d j
|
||||
return $ case ej of
|
||||
Right j' -> regenerateScreens j' d st
|
||||
Left err -> screenEnter d screen{esState=err} st
|
||||
Left err -> screenEnter d errorScreen{esState=err} st
|
||||
|
||||
|
||||
@ -32,8 +32,8 @@ import Hledger.UI.UIOptions
|
||||
import Hledger.UI.UITypes
|
||||
-- import Hledger.UI.UIUtils
|
||||
import Hledger.UI.Theme
|
||||
import Hledger.UI.AccountsScreen as AS
|
||||
import Hledger.UI.RegisterScreen as RS
|
||||
import Hledger.UI.AccountsScreen
|
||||
import Hledger.UI.RegisterScreen
|
||||
|
||||
----------------------------------------------------------------------
|
||||
|
||||
@ -97,11 +97,11 @@ runBrickUi uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}} j = do
|
||||
mregister = maybestringopt "register" $ rawopts_ copts
|
||||
|
||||
(scr, prevscrs) = case mregister of
|
||||
Nothing -> (AS.screen, [])
|
||||
Nothing -> (accountsScreen, [])
|
||||
-- with --register, start on the register screen, and also put
|
||||
-- the accounts screen on the prev screens stack so you can exit
|
||||
-- to that as usual.
|
||||
Just apat -> (rsSetCurrentAccount acct RS.screen, [ascr'])
|
||||
Just apat -> (rsSetCurrentAccount acct registerScreen, [ascr'])
|
||||
where
|
||||
acct = headDef
|
||||
(error' $ "--register "++apat++" did not match any account")
|
||||
@ -109,11 +109,11 @@ runBrickUi uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}} j = do
|
||||
-- Initialising the accounts screen is awkward, requiring
|
||||
-- another temporary AppState value..
|
||||
ascr' = aScreen $
|
||||
AS.initAccountsScreen d True $
|
||||
initAccountsScreen d True $
|
||||
AppState{
|
||||
aopts=uopts'
|
||||
,ajournal=j
|
||||
,aScreen=asSetSelectedAccount acct AS.screen
|
||||
,aScreen=asSetSelectedAccount acct accountsScreen
|
||||
,aPrevScreens=[]
|
||||
,aMinibuffer=Nothing
|
||||
}
|
||||
|
||||
@ -3,7 +3,7 @@
|
||||
{-# LANGUAGE OverloadedStrings, FlexibleContexts #-}
|
||||
|
||||
module Hledger.UI.RegisterScreen
|
||||
(screen
|
||||
(registerScreen
|
||||
,rsSetCurrentAccount
|
||||
)
|
||||
where
|
||||
@ -32,10 +32,11 @@ import Hledger.UI.UIOptions
|
||||
-- import Hledger.UI.Theme
|
||||
import Hledger.UI.UITypes
|
||||
import Hledger.UI.UIUtils
|
||||
import qualified Hledger.UI.TransactionScreen as TS (screen)
|
||||
import qualified Hledger.UI.ErrorScreen as ES (stReloadJournalIfChanged)
|
||||
import Hledger.UI.TransactionScreen
|
||||
import Hledger.UI.ErrorScreen
|
||||
|
||||
screen = RegisterScreen{
|
||||
registerScreen :: Screen
|
||||
registerScreen = RegisterScreen{
|
||||
rsState = (list "register" V.empty 1, "")
|
||||
,sInitFn = initRegisterScreen
|
||||
,sDrawFn = drawRegisterScreen
|
||||
@ -231,7 +232,7 @@ handleRegisterScreen st@AppState{
|
||||
case ev of
|
||||
Vty.EvKey (Vty.KChar 'q') [] -> halt st
|
||||
Vty.EvKey Vty.KEsc [] -> continue $ resetScreens d st
|
||||
Vty.EvKey (Vty.KChar 'g') [] -> liftIO (ES.stReloadJournalIfChanged copts d j st) >>= continue
|
||||
Vty.EvKey (Vty.KChar 'g') [] -> liftIO (stReloadJournalIfChanged copts d j st) >>= continue
|
||||
Vty.EvKey (Vty.KChar 'E') [] -> scrollTop >> (continue $ regenerateScreens j d $ stToggleEmpty st)
|
||||
Vty.EvKey (Vty.KChar 'C') [] -> scrollTop >> (continue $ regenerateScreens j d $ stToggleCleared st)
|
||||
Vty.EvKey (Vty.KChar 'U') [] -> scrollTop >> (continue $ regenerateScreens j d $ stToggleUncleared st)
|
||||
@ -248,7 +249,7 @@ handleRegisterScreen st@AppState{
|
||||
numberedts = zip [1..] ts
|
||||
i = fromIntegral $ maybe 0 (+1) $ elemIndex t ts -- XXX
|
||||
in
|
||||
continue $ screenEnter d TS.screen{tsState=((i,t),numberedts,acct)} st
|
||||
continue $ screenEnter d transactionScreen{tsState=((i,t),numberedts,acct)} st
|
||||
Nothing -> continue st
|
||||
|
||||
-- fall through to the list's event handler (handles [pg]up/down)
|
||||
|
||||
@ -3,7 +3,7 @@
|
||||
{-# LANGUAGE OverloadedStrings, TupleSections #-} -- , FlexibleContexts
|
||||
|
||||
module Hledger.UI.TransactionScreen
|
||||
(screen
|
||||
(transactionScreen
|
||||
)
|
||||
where
|
||||
|
||||
@ -33,9 +33,10 @@ import Hledger.UI.UIOptions
|
||||
-- import Hledger.UI.Theme
|
||||
import Hledger.UI.UITypes
|
||||
import Hledger.UI.UIUtils
|
||||
import qualified Hledger.UI.ErrorScreen as ES (screen)
|
||||
import Hledger.UI.ErrorScreen
|
||||
|
||||
screen = TransactionScreen{
|
||||
transactionScreen :: Screen
|
||||
transactionScreen = TransactionScreen{
|
||||
tsState = ((1,nulltransaction),[(1,nulltransaction)],"")
|
||||
,sInitFn = initTransactionScreen
|
||||
,sDrawFn = drawTransactionScreen
|
||||
@ -133,7 +134,7 @@ handleTransactionScreen st@AppState{
|
||||
st' = st{aScreen=s{tsState=((i',t'),numberedts,acct)}}
|
||||
continue $ regenerateScreens j' d st'
|
||||
|
||||
Left err -> continue $ screenEnter d ES.screen{esState=err} st
|
||||
Left err -> continue $ screenEnter d errorScreen{esState=err} st
|
||||
|
||||
-- if allowing toggling here, we should refresh the txn list from the parent register screen
|
||||
-- Vty.EvKey (Vty.KChar 'E') [] -> continue $ regenerateScreens j d $ stToggleEmpty st
|
||||
|
||||
Loading…
Reference in New Issue
Block a user