dev: ui: rename hledger-ui debug helpers

This commit is contained in:
Simon Michael 2022-10-31 12:32:57 -10:00
parent 603fae70c0
commit 9a9ebfc0e3
9 changed files with 80 additions and 81 deletions

View File

@ -50,7 +50,7 @@ import Control.Arrow ((>>>))
asDraw :: UIState -> [Widget Name]
asDraw ui = dlogUiTrace "asDraw" $ asDrawHelper ui ropts' scrname showbalchgkey
asDraw ui = dbgui "asDraw" $ asDrawHelper ui ropts' scrname showbalchgkey
where
ropts' = _rsReportOpts $ reportspec_ $ uoCliOpts $ aopts ui
scrname = "account " ++ if ishistorical then "balances" else "changes"
@ -63,9 +63,9 @@ asDraw ui = dlogUiTrace "asDraw" $ asDrawHelper ui ropts' scrname showbalchgkey
-- for toggling between end balance and balance change mode.
asDrawHelper :: UIState -> ReportOpts -> String -> Bool -> [Widget Name]
asDrawHelper UIState{aScreen=scr, aopts=uopts, ajournal=j, aMode=mode} ropts scrname showbalchgkey =
dlogUiTrace "asDrawHelper" $
dbgui "asDrawHelper" $
case toAccountsLikeScreen scr of
Nothing -> dlogUiTrace "asDrawHelper" $ errorWrongScreenType "draw helper" -- PARTIAL:
Nothing -> dbgui "asDrawHelper" $ errorWrongScreenType "draw helper" -- PARTIAL:
Just (ALS _ ass) -> case mode of
Help -> [helpDialog, maincontent]
_ -> [maincontent]
@ -178,10 +178,10 @@ asDrawItem (acctwidth, balwidth) selected AccountsScreenItem{..} =
-- | Handle events on any accounts-like screen (all accounts, balance sheet, income statement..).
asHandle :: BrickEvent Name AppEvent -> EventM Name UIState ()
asHandle ev = do
dlogUiTraceM "asHandle"
dbguiEv "asHandle"
ui0@UIState{aScreen=scr, aMode=mode} <- get'
case toAccountsLikeScreen scr of
Nothing -> dlogUiTrace "asHandle" $ errorWrongScreenType "event handler" -- PARTIAL:
Nothing -> dbgui "asHandle" $ errorWrongScreenType "event handler" -- PARTIAL:
Just als@(ALS scons ass) -> do
-- save the currently selected account, in case we leave this screen and lose the selection
put' ui0{aScreen=scons ass{_assSelectedAccount=asSelectedAccount ass}}
@ -194,7 +194,7 @@ asHandle ev = do
-- The provided AccountsLikeScreen should correspond to the ui state's current screen.
asHandleNormalMode :: AccountsLikeScreen -> BrickEvent Name AppEvent -> EventM Name UIState ()
asHandleNormalMode (ALS scons ass) ev = do
dlogUiTraceM "asHandleNormalMode"
dbguiEv "asHandleNormalMode"
ui@UIState{aopts=UIOpts{uoCliOpts=copts}, ajournal=j} <- get'
d <- liftIO getCurrentDay
@ -353,7 +353,7 @@ handleHelpMode ev = do
enterRegisterScreen :: Day -> AccountName -> UIState -> EventM Name UIState ()
enterRegisterScreen d acct ui@UIState{ajournal=j, aopts=uopts} = do
dlogUiTraceM "enterRegisterScreen"
dbguiEv "enterRegisterScreen"
let
regscr = rsNew uopts d j acct isdepthclipped
where

View File

@ -20,11 +20,11 @@ import Hledger.UI.AccountsScreen (asHandle, asDrawHelper)
bsDraw :: UIState -> [Widget Name]
bsDraw ui = dlogUiTrace "bsDraw" $ asDrawHelper ui ropts' scrname showbalchgkey
bsDraw ui = dbgui "bsDraw" $ asDrawHelper ui ropts' scrname showbalchgkey
where
scrname = "balance sheet"
ropts' = (_rsReportOpts $ reportspec_ $ uoCliOpts $ aopts ui){balanceaccum_=Historical}
showbalchgkey = False
bsHandle :: BrickEvent Name AppEvent -> EventM Name UIState ()
bsHandle = asHandle . dlogUiTrace "bsHandle"
bsHandle = asHandle . dbgui "bsHandle"

View File

@ -149,10 +149,10 @@ uiReloadJournal copts d ui = do
ej <-
let copts' = enableForecastPreservingPeriod ui copts
in runExceptT $ journalReload copts'
-- dlogUiTraceIO $ ("uiReloadJournal before reload: "++) $ pshow' $ map tdescription $ jtxns $ ajournal ui
-- dbguiIO $ ("uiReloadJournal before reload: "++) $ pshow' $ map tdescription $ jtxns $ ajournal ui
return $ case ej of
Right j ->
-- dlogUiTrace (("uiReloadJournal after reload: "++) $ pshow' $ map tdescription $ jtxns j) $
-- dbgui (("uiReloadJournal after reload: "++) $ pshow' $ map tdescription $ jtxns j) $
regenerateScreens j d ui
Left err ->
case ui of

View File

@ -20,11 +20,11 @@ import Hledger.UI.AccountsScreen (asHandle, asDrawHelper)
isDraw :: UIState -> [Widget Name]
isDraw ui = dlogUiTrace "isDraw" $ asDrawHelper ui ropts' scrname showbalchgkey
isDraw ui = dbgui "isDraw" $ asDrawHelper ui ropts' scrname showbalchgkey
where
scrname = "income statement"
ropts' = (_rsReportOpts $ reportspec_ $ uoCliOpts $ aopts ui){balanceaccum_=PerPeriod}
showbalchgkey = False
isHandle :: BrickEvent Name AppEvent -> EventM Name UIState ()
isHandle = asHandle . dlogUiTrace "isHandle"
isHandle = asHandle . dbgui "isHandle"

View File

@ -33,7 +33,7 @@ import Hledger.UI.Theme
import Hledger.UI.UIOptions
import Hledger.UI.UITypes
import Hledger.UI.UIState (uiState, getDepth)
import Hledger.UI.UIUtils (dlogUiTraceM, dlogUiTraceIO)
import Hledger.UI.UIUtils (dbguiEv, dbguiIO)
import Hledger.UI.MenuScreen
import Hledger.UI.AccountsScreen
import Hledger.UI.BalancesheetScreen
@ -167,7 +167,7 @@ runBrickUi uopts0@UIOpts{uoCliOpts=copts@CliOpts{inputopts_=_iopts,reportspec_=r
setMode (outputIface v) Mouse True
return v
dlogUiTraceIO "\n\n==== hledger-ui start"
dbguiIO "\n\n==== hledger-ui start"
if not (uoWatch uopts)
then do
@ -244,7 +244,7 @@ brickApp mtheme = App {
uiHandle :: BrickEvent Name AppEvent -> EventM Name UIState ()
uiHandle ev = do
dlogUiTraceM $ "\n==== " ++ show ev
dbguiEv $ "\n==== " ++ show ev
ui <- get
case aScreen ui of
MS _ -> msHandle ev

View File

@ -42,7 +42,7 @@ msDraw UIState{aopts=_uopts@UIOpts{uoCliOpts=copts@CliOpts{reportspec_=_rspec}}
,ajournal=j
,aScreen=MS sst
,aMode=mode
} = dlogUiTrace "msDraw" $
} = dbgui "msDraw" $
case mode of
Help -> [helpDialog, maincontent]
_ -> [maincontent]
@ -83,7 +83,7 @@ msDraw UIState{aopts=_uopts@UIOpts{uoCliOpts=copts@CliOpts{reportspec_=_rspec}}
,("q", str "quit")
]
msDraw _ = dlogUiTrace "msDraw" $ errorWrongScreenType "draw function" -- PARTIAL:
msDraw _ = dbgui "msDraw" $ errorWrongScreenType "draw function" -- PARTIAL:
-- msDrawItem :: (Int,Int) -> Bool -> MenuScreenItem -> Widget Name
-- msDrawItem (_acctwidth, _balwidth) _selected MenuScreenItem{..} =
@ -96,7 +96,7 @@ msDrawItem _selected MenuScreenItem{..} =
msHandle :: BrickEvent Name AppEvent -> EventM Name UIState ()
msHandle ev = do
ui0 <- get'
dlogUiTraceM "msHandle"
dbguiEv "msHandle"
case ui0 of
ui@UIState{
aopts=UIOpts{uoCliOpts=copts}
@ -249,11 +249,11 @@ msHandle ev = do
MouseUp{} -> return ()
AppEvent _ -> return ()
_ -> dlogUiTraceM "msHandle" >> errorWrongScreenType "event handler"
_ -> dbguiEv "msHandle" >> errorWrongScreenType "event handler"
msEnterScreen :: Day -> ScreenName -> UIState -> EventM Name UIState ()
msEnterScreen d scrname ui@UIState{ajournal=j, aopts=uopts} = do
dlogUiTraceM "msEnterScreen"
dbguiEv "msEnterScreen"
let
scr = case scrname of
Accounts -> asNew uopts d j Nothing

View File

@ -45,7 +45,7 @@ rsDraw :: UIState -> [Widget Name]
rsDraw UIState{aopts=_uopts@UIOpts{uoCliOpts=copts@CliOpts{reportspec_=rspec}}
,aScreen=RS RSS{..}
,aMode=mode
} = dlogUiTrace "rsDraw 1" $
} = dbgui "rsDraw 1" $
case mode of
Help -> [helpDialog, maincontent]
_ -> [maincontent]
@ -152,7 +152,7 @@ rsDraw UIState{aopts=_uopts@UIOpts{uoCliOpts=copts@CliOpts{reportspec_=rspec}}
-- ,("q", "quit")
]
rsDraw _ = dlogUiTrace "rsDraw 2" $ errorWrongScreenType "draw function" -- PARTIAL:
rsDraw _ = dbgui "rsDraw 2" $ errorWrongScreenType "draw function" -- PARTIAL:
rsDrawItem :: (Int,Int,Int,Int,Int) -> Bool -> RegisterScreenItem -> Widget Name
rsDrawItem (datewidth,descwidth,acctswidth,changewidth,balwidth) selected RegisterScreenItem{..} =
@ -183,7 +183,7 @@ rsDrawItem (datewidth,descwidth,acctswidth,changewidth,balwidth) selected Regist
rsHandle :: BrickEvent Name AppEvent -> EventM Name UIState ()
rsHandle ev = do
ui0 <- get'
dlogUiTraceM "rsHandle 1"
dbguiEv "rsHandle 1"
case ui0 of
ui@UIState{
aScreen=RS sst@RSS{..}
@ -328,7 +328,7 @@ rsHandle ev = do
MouseUp{} -> return ()
AppEvent _ -> return ()
_ -> dlogUiTrace "rsHandle 2" $ errorWrongScreenType "event handler"
_ -> dbgui "rsHandle 2" $ errorWrongScreenType "event handler"
isBlankElement mel = ((rsItemDate . snd) <$> mel) == Just ""
@ -349,7 +349,7 @@ rsCenterSelection ui = return ui
rsEnterTransactionScreen :: AccountName -> [NumberedTransaction] -> NumberedTransaction -> UIState -> EventM Name UIState ()
rsEnterTransactionScreen acct nts nt ui = do
dlogUiTraceM "rsEnterTransactionScreen"
dbguiEv "rsEnterTransactionScreen"
put' $
pushScreen (tsNew acct nts nt)
ui

View File

@ -62,7 +62,7 @@ screenUpdate opts d j = \case
-- Screen-specific arguments: the error message to show.
esNew :: String -> Screen
esNew msg =
dlogUiTrace "esNew" $
dbgui "esNew" $
ES ESS {
_essError = msg
,_essUnused = ()
@ -71,13 +71,13 @@ esNew msg =
-- | Update an error screen. Currently a no-op since error screen
-- depends only on its screen-specific state.
esUpdate :: ErrorScreenState -> ErrorScreenState
esUpdate = dlogUiTrace "esUpdate`"
esUpdate = dbgui "esUpdate`"
-- | Construct a menu screen.
-- Screen-specific arguments: none.
msNew :: Screen
msNew =
dlogUiTrace "msNew" $
dbgui "msNew" $
MS MSS {
_mssList = list MenuList (V.fromList [
MenuScreenItem "All accounts" Accounts
@ -90,7 +90,7 @@ msNew =
-- | Update a menu screen. Currently a no-op since menu screen
-- has unchanging content.
msUpdate :: MenuScreenState -> MenuScreenState
msUpdate = dlogUiTrace "msUpdate"
msUpdate = dbgui "msUpdate"
nullass macct = ASS {
_assSelectedAccount = fromMaybe "" macct
@ -101,11 +101,11 @@ nullass macct = ASS {
-- with the appropriate one selected.
-- Screen-specific arguments: the account to select if any.
asNew :: UIOpts -> Day -> Journal -> Maybe AccountName -> Screen
asNew uopts d j macct = dlogUiTrace "asNew" $ AS $ asUpdate uopts d j $ nullass macct
asNew uopts d j macct = dbgui "asNew" $ AS $ asUpdate uopts d j $ nullass macct
-- | Update an accounts screen's state from these options, reporting date, and journal.
asUpdate :: UIOpts -> Day -> Journal -> AccountsScreenState -> AccountsScreenState
asUpdate uopts d = dlogUiTrace "asUpdate" .
asUpdate uopts d = dbgui "asUpdate" .
asUpdateHelper rspec d copts roptsmod extraquery
where
UIOpts{uoCliOpts=copts@CliOpts{reportspec_=rspec}} = uopts
@ -115,7 +115,7 @@ asUpdate uopts d = dlogUiTrace "asUpdate" .
-- | Update an accounts-like screen's state from this report spec, reporting date,
-- cli options, report options modifier, extra query, and journal.
asUpdateHelper :: ReportSpec -> Day -> CliOpts -> (ReportOpts -> ReportOpts) -> Query -> Journal -> AccountsScreenState -> AccountsScreenState
asUpdateHelper rspec0 d copts roptsModify extraquery j ass = dlogUiTrace "asUpdateHelper"
asUpdateHelper rspec0 d copts roptsModify extraquery j ass = dbgui "asUpdateHelper"
ass{_assList=l}
where
ropts = roptsModify $ _rsReportOpts rspec0
@ -171,11 +171,11 @@ asUpdateHelper rspec0 d copts roptsModify extraquery j ass = dlogUiTrace "asUpda
-- with the appropriate one selected.
-- Screen-specific arguments: the account to select if any.
bsNew :: UIOpts -> Day -> Journal -> Maybe AccountName -> Screen
bsNew uopts d j macct = dlogUiTrace "bsNew" $ BS $ bsUpdate uopts d j $ nullass macct
bsNew uopts d j macct = dbgui "bsNew" $ BS $ bsUpdate uopts d j $ nullass macct
-- | Update a balance sheet screen's state from these options, reporting date, and journal.
bsUpdate :: UIOpts -> Day -> Journal -> AccountsScreenState -> AccountsScreenState
bsUpdate uopts d = dlogUiTrace "bsUpdate" .
bsUpdate uopts d = dbgui "bsUpdate" .
asUpdateHelper rspec d copts roptsmod extraquery
where
UIOpts{uoCliOpts=copts@CliOpts{reportspec_=rspec}} = uopts
@ -186,11 +186,11 @@ bsUpdate uopts d = dlogUiTrace "bsUpdate" .
-- with the appropriate one selected.
-- Screen-specific arguments: the account to select if any.
isNew :: UIOpts -> Day -> Journal -> Maybe AccountName -> Screen
isNew uopts d j macct = dlogUiTrace "isNew" $ IS $ isUpdate uopts d j $ nullass macct
isNew uopts d j macct = dbgui "isNew" $ IS $ isUpdate uopts d j $ nullass macct
-- | Update an income statement screen's state from these options, reporting date, and journal.
isUpdate :: UIOpts -> Day -> Journal -> AccountsScreenState -> AccountsScreenState
isUpdate uopts d = dlogUiTrace "isUpdate" .
isUpdate uopts d = dbgui "isUpdate" .
asUpdateHelper rspec d copts roptsmod extraquery
where
UIOpts{uoCliOpts=copts@CliOpts{reportspec_=rspec}} = uopts
@ -203,7 +203,7 @@ isUpdate uopts d = dlogUiTrace "isUpdate" .
-- whether to force inclusive balances.
rsNew :: UIOpts -> Day -> Journal -> AccountName -> Bool -> Screen
rsNew uopts d j acct forceinclusive = -- XXX forcedefaultselection - whether to force selecting the last transaction.
dlogUiTrace "rsNew" $
dbgui "rsNew" $
RS $
rsUpdate uopts d j $
RSS {
@ -215,7 +215,7 @@ rsNew uopts d j acct forceinclusive = -- XXX forcedefaultselection - whether to
-- | Update a register screen from these options, reporting date, and journal.
rsUpdate :: UIOpts -> Day -> Journal -> RegisterScreenState -> RegisterScreenState
rsUpdate uopts d j rss@RSS{_rssAccount, _rssForceInclusive, _rssList=oldlist} =
dlogUiTrace "rsUpdate"
dbgui "rsUpdate"
rss{_rssList=l'}
where
UIOpts{uoCliOpts=copts@CliOpts{reportspec_=rspec@ReportSpec{_rsReportOpts=ropts}}} = uopts
@ -320,7 +320,7 @@ rsUpdate uopts d j rss@RSS{_rssAccount, _rssForceInclusive, _rssList=oldlist} =
-- the list of showable transactions, the currently shown transaction.
tsNew :: AccountName -> [NumberedTransaction] -> NumberedTransaction -> Screen
tsNew acct nts nt =
dlogUiTrace "tsNew" $
dbgui "tsNew" $
TS TSS{
_tssAccount = acct
,_tssTransactions = nts
@ -330,5 +330,5 @@ tsNew acct nts nt =
-- | Update a transaction screen. Currently a no-op since transaction screen
-- depends only on its screen-specific state.
tsUpdate :: TransactionScreenState -> TransactionScreenState
tsUpdate = dlogUiTrace "tsUpdate"
tsUpdate = dbgui "tsUpdate"

View File

@ -32,14 +32,13 @@ module Hledger.UI.UIUtils (
,reportSpecAddQuery
,reportSpecSetFutureAndForecast
,listScrollPushingSelection
,dlogUiTrace
,dlogUiTraceIO
,dlogUiTraceM
,dlogUiScreenStack
,dbgui
,dbguiIO
,dbguiEv
,dbguiScreensEv
,screenRegisterDescriptions
,screenId
,mapScreens
,uiDebugLevel
,uiNumBlankItems
)
where
@ -87,32 +86,32 @@ suspendSignal = raiseSignal sigSTOP
get' = do
x <- get
dlogUiTraceM $ "getting state: " ++ (head $ lines $ pshow $ aScreen x)
dbguiEv $ "getting state: " ++ (head $ lines $ pshow $ aScreen x)
-- ++ " " ++ (show $ map tdescription $ jtxns $ ajournal x)
-- dlogUiTraceM $ ("query: "++) $ pshow' $ x & aopts & uoCliOpts & reportspec_ & _rsQuery
-- dlogUiScreenStack "getting" screenId x
-- dlogUiScreenStack "getting, with register descriptions" screenRegisterDescriptions x
-- dbguiEv $ ("query: "++) $ pshow' $ x & aopts & uoCliOpts & reportspec_ & _rsQuery
-- dbguiScreensEv "getting" screenId x
-- dbguiScreensEv "getting, with register descriptions" screenRegisterDescriptions x
return x
put' x = do
dlogUiTraceM $ "putting state: " ++ (head $ lines $ pshow $ aScreen x)
dbguiEv $ "putting state: " ++ (head $ lines $ pshow $ aScreen x)
-- ++ " " ++ (show $ map tdescription $ jtxns $ ajournal x)
-- dlogUiTraceM $ ("query: "++) $ pshow' $ x & aopts & uoCliOpts & reportspec_ & _rsQuery
-- dlogUiScreenStack "putting" screenId x
-- dlogUiScreenStack "putting, with register descriptions" screenRegisterDescriptions x
-- dbguiEv $ ("query: "++) $ pshow' $ x & aopts & uoCliOpts & reportspec_ & _rsQuery
-- dbguiScreensEv "putting" screenId x
-- dbguiScreensEv "putting, with register descriptions" screenRegisterDescriptions x
put x
modify' f = do
x <- get
let x' = f x
dlogUiTraceM $ "modifying state: " ++ (head $ lines $ pshow $ aScreen x')
dbguiEv $ "modifying state: " ++ (head $ lines $ pshow $ aScreen x')
-- ++ " " ++ (show $ map tdescription $ jtxns $ ajournal x')
-- dlogUiTraceM $ ("from: "++) $ pshow' $ x & aopts & uoCliOpts & reportspec_ & _rsQuery
-- dlogUiTraceM $ ("to: "++) $ pshow' $ x' & aopts & uoCliOpts & reportspec_ & _rsQuery
-- dlogUiScreenStack "getting" screenId x
-- dlogUiScreenStack "putting" screenId x'
-- dlogUiScreenStack "getting, with register descriptions" screenRegisterDescriptions x
-- dlogUiScreenStack "putting, with register descriptions" screenRegisterDescriptions x'
-- dbguiEv $ ("from: "++) $ pshow' $ x & aopts & uoCliOpts & reportspec_ & _rsQuery
-- dbguiEv $ ("to: "++) $ pshow' $ x' & aopts & uoCliOpts & reportspec_ & _rsQuery
-- dbguiScreensEv "getting" screenId x
-- dbguiScreensEv "putting" screenId x'
-- dbguiScreensEv "getting, with register descriptions" screenRegisterDescriptions x
-- dbguiScreensEv "putting, with register descriptions" screenRegisterDescriptions x'
modify f
-- | On posix platforms, suspend the program using the STOP signal,
@ -439,29 +438,33 @@ listScrollPushingSelection name listheight scrollamt = do
_ -> return list
_ -> return list
-- | Log a string to ./debug.log before returning the second argument,
-- if the global debug level is at or above a standard hledger-ui debug level.
-- Uses unsafePerformIO.
dlogUiTrace :: String -> a -> a
dlogUiTrace = traceLogAt uiDebugLevel
-- Log hledger-ui events at this debug level and above.
uiDebugLevel :: Int
uiDebugLevel = 1
-- | Like dlogUiTrace, but convenient in IO.
dlogUiTraceIO :: String -> IO ()
dlogUiTraceIO s = dlogUiTrace s $ return ()
-- | A debug logging helper to use in hledger-ui code:
-- at any debug level >= 1, logs the string to ./debug.log before returning the second argument.
-- Like traceLogAt 1. Uses unsafePerformIO.
dbgui :: String -> a -> a
dbgui = traceLogAt uiDebugLevel
-- | Like dlogUiTrace, but convenient in event handlers.
dlogUiTraceM :: String -> EventM Name UIState ()
dlogUiTraceM s = dlogUiTrace s $ return ()
-- | Like dbgui, but convenient in IO.
dbguiIO :: String -> IO ()
dbguiIO s = dbgui s $ return ()
-- | Like dlogUiTraceM, but log a compact view of the current screen stack,
-- | Like dbgui, but convenient in hledger EventM handlers.
dbguiEv :: String -> EventM Name s ()
dbguiEv s = dbgui s $ return ()
-- | Like dbguiEv, but log a compact view of the current screen stack,
-- from topmost screen to currently-viewed screen,
-- with each screen rendered by the given rendering function
-- (and with the given extra label if any).
-- Useful for inspecting states across the whole screen stack.
-- To just show the stack: @dlogUiScreenStack "" screenId ui@
dlogUiScreenStack :: String -> (Screen -> String) -> UIState -> EventM Name UIState ()
dlogUiScreenStack postfix showscr ui =
dlogUiTraceM $ concat [
-- To just show the stack: @dbguiScreensEv "" screenId ui@
dbguiScreensEv :: String -> (Screen -> String) -> UIState -> EventM Name UIState ()
dbguiScreensEv postfix showscr ui =
dbguiEv $ concat [
"screen stack"
,if null postfix then "" else " (" ++ postfix ++ ")"
,": "
@ -492,10 +495,6 @@ screenId = \case
TS _ -> "T" -- transaction
ES _ -> "E" -- error
-- | Log hledger-ui events at this debug level.
uiDebugLevel :: Int
uiDebugLevel = 2
-- | How many blank items to add to lists to fill the full window height.
uiNumBlankItems :: Int
uiNumBlankItems