2017-06-27 16:47:54 +03:00
|
|
|
{-# LANGUAGE CPP #-}
|
2016-06-11 03:30:45 +03:00
|
|
|
{- | UIState operations. -}
|
|
|
|
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# LANGUAGE RecordWildCards #-}
|
|
|
|
|
|
|
|
module Hledger.UI.UIState
|
|
|
|
where
|
|
|
|
|
2017-06-27 16:47:54 +03:00
|
|
|
#if !MIN_VERSION_brick(0,19,0)
|
2016-06-11 03:30:45 +03:00
|
|
|
import Brick
|
2017-06-27 16:47:54 +03:00
|
|
|
#endif
|
2016-06-11 03:30:45 +03:00
|
|
|
import Brick.Widgets.Edit
|
|
|
|
import Data.List
|
|
|
|
import Data.Text.Zipper (gotoEOL)
|
|
|
|
import Data.Time.Calendar (Day)
|
|
|
|
|
|
|
|
import Hledger
|
|
|
|
import Hledger.Cli.CliOptions
|
|
|
|
import Hledger.UI.UITypes
|
|
|
|
import Hledger.UI.UIOptions
|
|
|
|
|
2017-06-16 02:48:03 +03:00
|
|
|
-- | Toggle between showing only unmarked items or all items.
|
|
|
|
toggleUnmarked :: UIState -> UIState
|
|
|
|
toggleUnmarked ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
2017-06-19 02:11:18 +03:00
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=reportOptsToggleStatusSomehow Unmarked copts ropts}}}
|
2016-06-11 03:30:45 +03:00
|
|
|
|
|
|
|
-- | Toggle between showing only pending items or all items.
|
|
|
|
togglePending :: UIState -> UIState
|
|
|
|
togglePending ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
2017-06-19 02:11:18 +03:00
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=reportOptsToggleStatusSomehow Pending copts ropts}}}
|
2016-06-11 03:30:45 +03:00
|
|
|
|
2017-06-16 02:48:03 +03:00
|
|
|
-- | Toggle between showing only cleared items or all items.
|
|
|
|
toggleCleared :: UIState -> UIState
|
|
|
|
toggleCleared ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
2017-06-19 02:11:18 +03:00
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=reportOptsToggleStatusSomehow Cleared copts ropts}}}
|
|
|
|
|
2019-07-15 13:28:52 +03:00
|
|
|
-- TODO testing different status toggle styles
|
2017-06-19 02:11:18 +03:00
|
|
|
|
2019-07-15 13:28:52 +03:00
|
|
|
-- | Generate zero or more indicators of the status filters currently active,
|
2017-06-19 02:11:18 +03:00
|
|
|
-- which will be shown comma-separated as part of the indicators list.
|
|
|
|
uiShowStatus :: CliOpts -> [Status] -> [String]
|
|
|
|
uiShowStatus copts ss =
|
|
|
|
case style of
|
2019-07-15 13:28:52 +03:00
|
|
|
-- in style 2, instead of "Y, Z" show "not X"
|
|
|
|
Just 2 | length ss == numstatuses-1
|
2017-06-19 02:11:18 +03:00
|
|
|
-> map (("not "++). showstatus) $ sort $ complement ss -- should be just one
|
|
|
|
_ -> map showstatus $ sort ss
|
|
|
|
where
|
|
|
|
numstatuses = length [minBound..maxBound::Status]
|
|
|
|
style = maybeintopt "status-toggles" $ rawopts_ copts
|
|
|
|
showstatus Cleared = "cleared"
|
|
|
|
showstatus Pending = "pending"
|
|
|
|
showstatus Unmarked = "unmarked"
|
|
|
|
|
|
|
|
reportOptsToggleStatusSomehow :: Status -> CliOpts -> ReportOpts -> ReportOpts
|
|
|
|
reportOptsToggleStatusSomehow s copts ropts =
|
2019-07-15 13:28:52 +03:00
|
|
|
case maybeintopt "status-toggles" $ rawopts_ copts of
|
2017-06-19 02:11:18 +03:00
|
|
|
Just 2 -> reportOptsToggleStatus2 s ropts
|
|
|
|
Just 3 -> reportOptsToggleStatus3 s ropts
|
|
|
|
-- Just 4 -> reportOptsToggleStatus4 s ropts
|
|
|
|
-- Just 5 -> reportOptsToggleStatus5 s ropts
|
|
|
|
_ -> reportOptsToggleStatus1 s ropts
|
|
|
|
|
|
|
|
-- 1 UPC toggles only X/all
|
|
|
|
reportOptsToggleStatus1 s ropts@ReportOpts{statuses_=ss}
|
|
|
|
| ss == [s] = ropts{statuses_=[]}
|
|
|
|
| otherwise = ropts{statuses_=[s]}
|
|
|
|
|
|
|
|
-- 2 UPC cycles X/not-X/all
|
|
|
|
-- repeatedly pressing X cycles:
|
|
|
|
-- [] U [u]
|
|
|
|
-- [u] U [pc]
|
|
|
|
-- [pc] U []
|
|
|
|
-- pressing Y after first or second step starts new cycle:
|
|
|
|
-- [u] P [p]
|
|
|
|
-- [pc] P [p]
|
|
|
|
reportOptsToggleStatus2 s ropts@ReportOpts{statuses_=ss}
|
|
|
|
| ss == [s] = ropts{statuses_=complement [s]}
|
|
|
|
| ss == complement [s] = ropts{statuses_=[]}
|
2019-07-15 13:28:52 +03:00
|
|
|
| otherwise = ropts{statuses_=[s]} -- XXX assume only three values
|
2017-06-19 02:11:18 +03:00
|
|
|
|
|
|
|
-- 3 UPC toggles each X
|
|
|
|
reportOptsToggleStatus3 s ropts@ReportOpts{statuses_=ss}
|
|
|
|
| s `elem` ss = ropts{statuses_=filter (/= s) ss}
|
|
|
|
| otherwise = ropts{statuses_=simplifyStatuses (s:ss)}
|
|
|
|
|
|
|
|
-- 4 upc sets X, UPC sets not-X
|
|
|
|
--reportOptsToggleStatus4 s ropts@ReportOpts{statuses_=ss}
|
|
|
|
-- | s `elem` ss = ropts{statuses_=filter (/= s) ss}
|
|
|
|
-- | otherwise = ropts{statuses_=simplifyStatuses (s:ss)}
|
|
|
|
--
|
|
|
|
-- 5 upc toggles X, UPC toggles not-X
|
|
|
|
--reportOptsToggleStatus5 s ropts@ReportOpts{statuses_=ss}
|
|
|
|
-- | s `elem` ss = ropts{statuses_=filter (/= s) ss}
|
|
|
|
-- | otherwise = ropts{statuses_=simplifyStatuses (s:ss)}
|
|
|
|
|
|
|
|
-- | Given a list of unique enum values, list the other possible values of that enum.
|
|
|
|
complement :: (Bounded a, Enum a, Eq a) => [a] -> [a]
|
|
|
|
complement = ([minBound..maxBound] \\)
|
|
|
|
|
|
|
|
--
|
2017-06-10 23:30:48 +03:00
|
|
|
|
2016-06-11 03:30:45 +03:00
|
|
|
-- | Toggle between showing all and showing only nonempty (more precisely, nonzero) items.
|
|
|
|
toggleEmpty :: UIState -> UIState
|
|
|
|
toggleEmpty ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=toggleEmpty ropts}}}
|
|
|
|
where
|
|
|
|
toggleEmpty ropts = ropts{empty_=not $ empty_ ropts}
|
|
|
|
|
2019-10-20 17:12:14 +03:00
|
|
|
-- | Show primary amounts, not cost or value.
|
|
|
|
clearCostValue :: UIState -> UIState
|
|
|
|
clearCostValue ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{value_ = plog "clearing value mode" Nothing}}}}
|
|
|
|
|
|
|
|
-- | Toggle between showing the primary amounts or costs.
|
|
|
|
toggleCost :: UIState -> UIState
|
|
|
|
toggleCost ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{value_ = valuationToggleCost $ value_ ropts}}}}
|
|
|
|
|
|
|
|
-- | Toggle between showing primary amounts or default valuation.
|
|
|
|
toggleValue :: UIState -> UIState
|
|
|
|
toggleValue ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{
|
|
|
|
value_ = plog "toggling value mode to" $ valuationToggleValue $ value_ ropts}}}}
|
|
|
|
|
|
|
|
-- | Basic toggling of -B/cost, for hledger-ui.
|
|
|
|
valuationToggleCost :: Maybe ValuationType -> Maybe ValuationType
|
|
|
|
valuationToggleCost (Just (AtCost _)) = Nothing
|
|
|
|
valuationToggleCost _ = Just $ AtCost Nothing
|
|
|
|
|
|
|
|
-- | Basic toggling of -V, for hledger-ui.
|
|
|
|
valuationToggleValue :: Maybe ValuationType -> Maybe ValuationType
|
|
|
|
valuationToggleValue (Just (AtDefault _)) = Nothing
|
|
|
|
valuationToggleValue _ = Just $ AtDefault Nothing
|
|
|
|
|
2018-10-15 23:41:41 +03:00
|
|
|
-- | Toggle between flat and tree mode. If current mode is unspecified/default, assume it's flat.
|
|
|
|
toggleTree :: UIState -> UIState
|
|
|
|
toggleTree ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=toggleTreeMode ropts}}}
|
2016-06-11 03:30:45 +03:00
|
|
|
where
|
2018-10-16 04:30:57 +03:00
|
|
|
toggleTreeMode ropts
|
|
|
|
| accountlistmode_ ropts == ALTree = ropts{accountlistmode_=ALFlat}
|
|
|
|
| otherwise = ropts{accountlistmode_=ALTree}
|
2016-06-11 03:30:45 +03:00
|
|
|
|
2016-08-13 03:44:55 +03:00
|
|
|
-- | Toggle between historical balances and period balances.
|
|
|
|
toggleHistorical :: UIState -> UIState
|
|
|
|
toggleHistorical ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{balancetype_=b}}}}
|
|
|
|
where
|
|
|
|
b | balancetype_ ropts == HistoricalBalance = PeriodChange
|
|
|
|
| otherwise = HistoricalBalance
|
|
|
|
|
2020-02-16 16:27:09 +03:00
|
|
|
-- | Toggle hledger-ui's "forecast mode". In forecast mode, periodic
|
|
|
|
-- transactions (generated by periodic rules) are enabled (as with
|
|
|
|
-- hledger --forecast), and also future transactions in general
|
|
|
|
-- (including non-periodic ones) are displayed. In normal mode, all
|
|
|
|
-- future transactions (periodic or not) are suppressed (unlike
|
|
|
|
-- command-line hledger).
|
|
|
|
--
|
|
|
|
-- After toggling this, we do a full reload of the journal from disk
|
|
|
|
-- to make it take effect; currently that's done in the callers (cf
|
|
|
|
-- AccountsScreen, RegisterScreen) where it's easier. This is
|
|
|
|
-- overkill, probably we should just hide/show the periodic
|
|
|
|
-- transactions with a query for their special tag.
|
|
|
|
--
|
|
|
|
toggleForecast :: UIState -> UIState
|
|
|
|
toggleForecast ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts'}}
|
2018-10-16 01:11:22 +03:00
|
|
|
where
|
2020-02-16 16:27:09 +03:00
|
|
|
copts' = copts{reportopts_=ropts{forecast_=not $ forecast_ ropts}}
|
2018-10-16 01:11:22 +03:00
|
|
|
|
2016-06-11 03:30:45 +03:00
|
|
|
-- | Toggle between showing all and showing only real (non-virtual) items.
|
|
|
|
toggleReal :: UIState -> UIState
|
|
|
|
toggleReal ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=toggleReal ropts}}}
|
|
|
|
where
|
|
|
|
toggleReal ropts = ropts{real_=not $ real_ ropts}
|
|
|
|
|
2016-07-07 01:08:57 +03:00
|
|
|
-- | Toggle the ignoring of balance assertions.
|
|
|
|
toggleIgnoreBalanceAssertions :: UIState -> UIState
|
2017-09-15 03:41:42 +03:00
|
|
|
toggleIgnoreBalanceAssertions ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{inputopts_=iopts}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{inputopts_=iopts{ignore_assertions_=not $ ignore_assertions_ iopts}}}}
|
2016-07-07 01:08:57 +03:00
|
|
|
|
2016-08-10 17:17:35 +03:00
|
|
|
-- | Step through larger report periods, up to all.
|
|
|
|
growReportPeriod :: Day -> UIState -> UIState
|
|
|
|
growReportPeriod _d ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{period_=periodGrow $ period_ ropts}}}}
|
|
|
|
|
|
|
|
-- | Step through smaller report periods, down to a day.
|
|
|
|
shrinkReportPeriod :: Day -> UIState -> UIState
|
|
|
|
shrinkReportPeriod d ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{period_=periodShrink d $ period_ ropts}}}}
|
2016-08-10 01:31:35 +03:00
|
|
|
|
2016-12-02 06:26:17 +03:00
|
|
|
-- | Step the report start/end dates to the next period of same duration,
|
|
|
|
-- remaining inside the given enclosing span.
|
2016-08-13 18:08:43 +03:00
|
|
|
nextReportPeriod :: DateSpan -> UIState -> UIState
|
2016-12-02 06:26:17 +03:00
|
|
|
nextReportPeriod enclosingspan ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts@ReportOpts{period_=p}}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{period_=periodNextIn enclosingspan p}}}}
|
2016-08-02 18:22:21 +03:00
|
|
|
|
2016-12-02 06:26:17 +03:00
|
|
|
-- | Step the report start/end dates to the next period of same duration,
|
|
|
|
-- remaining inside the given enclosing span.
|
2016-08-13 18:08:43 +03:00
|
|
|
previousReportPeriod :: DateSpan -> UIState -> UIState
|
2016-12-02 06:26:17 +03:00
|
|
|
previousReportPeriod enclosingspan ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts@ReportOpts{period_=p}}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{period_=periodPreviousIn enclosingspan p}}}}
|
|
|
|
|
|
|
|
-- | If a standard report period is set, step it forward/backward if needed so that
|
|
|
|
-- it encloses the given date.
|
|
|
|
moveReportPeriodToDate :: Day -> UIState -> UIState
|
|
|
|
moveReportPeriodToDate d ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts@ReportOpts{period_=p}}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{period_=periodMoveTo d p}}}}
|
2016-08-02 18:22:21 +03:00
|
|
|
|
2016-12-03 02:36:23 +03:00
|
|
|
-- | Get the report period.
|
|
|
|
reportPeriod :: UIState -> Period
|
|
|
|
reportPeriod UIState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=ReportOpts{period_=p}}}} =
|
|
|
|
p
|
|
|
|
|
2016-08-10 01:31:35 +03:00
|
|
|
-- | Set the report period.
|
|
|
|
setReportPeriod :: Period -> UIState -> UIState
|
|
|
|
setReportPeriod p ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{period_=p}}}}
|
|
|
|
|
2016-06-11 03:30:45 +03:00
|
|
|
-- | Apply a new filter query.
|
|
|
|
setFilter :: String -> UIState -> UIState
|
|
|
|
setFilter s ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{query_=s}}}}
|
|
|
|
|
2016-06-18 18:46:08 +03:00
|
|
|
-- | Clear all filters/flags.
|
2016-06-11 03:30:45 +03:00
|
|
|
resetFilter :: UIState -> UIState
|
|
|
|
resetFilter ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{
|
2018-10-17 00:02:09 +03:00
|
|
|
accountlistmode_=ALFlat
|
2016-06-18 18:46:08 +03:00
|
|
|
,empty_=True
|
2017-06-16 02:54:34 +03:00
|
|
|
,statuses_=[]
|
2016-06-11 03:30:45 +03:00
|
|
|
,real_=False
|
|
|
|
,query_=""
|
2016-08-13 18:08:43 +03:00
|
|
|
--,period_=PeriodAll
|
2016-06-11 03:30:45 +03:00
|
|
|
}}}}
|
|
|
|
|
|
|
|
resetDepth :: UIState -> UIState
|
|
|
|
resetDepth ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}} =
|
|
|
|
ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{depth_=Nothing}}}}
|
|
|
|
|
|
|
|
-- | Get the maximum account depth in the current journal.
|
|
|
|
maxDepth :: UIState -> Int
|
|
|
|
maxDepth UIState{ajournal=j} = maximum $ map accountNameLevel $ journalAccountNames j
|
|
|
|
|
|
|
|
-- | Decrement the current depth limit towards 0. If there was no depth limit,
|
|
|
|
-- set it to one less than the maximum account depth.
|
|
|
|
decDepth :: UIState -> UIState
|
|
|
|
decDepth ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts@ReportOpts{..}}}}
|
|
|
|
= ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{depth_=dec depth_}}}}
|
|
|
|
where
|
|
|
|
dec (Just d) = Just $ max 0 (d-1)
|
|
|
|
dec Nothing = Just $ maxDepth ui - 1
|
|
|
|
|
|
|
|
-- | Increment the current depth limit. If this makes it equal to the
|
|
|
|
-- the maximum account depth, remove the depth limit.
|
|
|
|
incDepth :: UIState -> UIState
|
|
|
|
incDepth ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts@ReportOpts{..}}}}
|
|
|
|
= ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{depth_=inc depth_}}}}
|
|
|
|
where
|
|
|
|
inc (Just d) | d < (maxDepth ui - 1) = Just $ d+1
|
|
|
|
inc _ = Nothing
|
|
|
|
|
|
|
|
-- | Set the current depth limit to the specified depth, or remove the depth limit.
|
|
|
|
-- Also remove the depth limit if the specified depth is greater than the current
|
|
|
|
-- maximum account depth. If the specified depth is negative, reset the depth limit
|
|
|
|
-- to whatever was specified at uiartup.
|
|
|
|
setDepth :: Maybe Int -> UIState -> UIState
|
|
|
|
setDepth mdepth ui@UIState{aopts=uopts@UIOpts{cliopts_=copts@CliOpts{reportopts_=ropts}}}
|
|
|
|
= ui{aopts=uopts{cliopts_=copts{reportopts_=ropts{depth_=mdepth'}}}}
|
|
|
|
where
|
|
|
|
mdepth' = case mdepth of
|
|
|
|
Nothing -> Nothing
|
|
|
|
Just d | d < 0 -> depth_ ropts
|
|
|
|
| d >= maxDepth ui -> Nothing
|
|
|
|
| otherwise -> mdepth
|
|
|
|
|
2016-07-27 03:28:29 +03:00
|
|
|
getDepth :: UIState -> Maybe Int
|
|
|
|
getDepth UIState{aopts=UIOpts{cliopts_=CliOpts{reportopts_=ropts}}} = depth_ ropts
|
|
|
|
|
2016-06-11 03:30:45 +03:00
|
|
|
-- | Open the minibuffer, setting its content to the current query with the cursor at the end.
|
|
|
|
showMinibuffer :: UIState -> UIState
|
|
|
|
showMinibuffer ui = setMode (Minibuffer e) ui
|
|
|
|
where
|
2017-06-27 16:47:54 +03:00
|
|
|
#if MIN_VERSION_brick(0,19,0)
|
|
|
|
e = applyEdit gotoEOL $ editor MinibufferEditor (Just 1) oldq
|
|
|
|
#else
|
2016-07-25 04:06:49 +03:00
|
|
|
e = applyEdit gotoEOL $ editor MinibufferEditor (str . unlines) (Just 1) oldq
|
2017-06-27 16:47:54 +03:00
|
|
|
#endif
|
2016-06-11 03:30:45 +03:00
|
|
|
oldq = query_ $ reportopts_ $ cliopts_ $ aopts ui
|
|
|
|
|
|
|
|
-- | Close the minibuffer, discarding any edit in progress.
|
|
|
|
closeMinibuffer :: UIState -> UIState
|
|
|
|
closeMinibuffer = setMode Normal
|
|
|
|
|
|
|
|
setMode :: Mode -> UIState -> UIState
|
|
|
|
setMode m ui = ui{aMode=m}
|
|
|
|
|
|
|
|
-- | Regenerate the content for the current and previous screens, from a new journal and current date.
|
|
|
|
regenerateScreens :: Journal -> Day -> UIState -> UIState
|
|
|
|
regenerateScreens j d ui@UIState{aScreen=s,aPrevScreens=ss} =
|
|
|
|
-- XXX clumsy due to entanglement of UIState and Screen.
|
|
|
|
-- sInit operates only on an appstate's current screen, so
|
|
|
|
-- remove all the screens from the appstate and then add them back
|
|
|
|
-- one at a time, regenerating as we go.
|
|
|
|
let
|
|
|
|
first:rest = reverse $ s:ss :: [Screen]
|
|
|
|
ui0 = ui{ajournal=j, aScreen=first, aPrevScreens=[]} :: UIState
|
|
|
|
|
|
|
|
ui1 = (sInit first) d False ui0 :: UIState
|
|
|
|
ui2 = foldl' (\ui s -> (sInit s) d False $ pushScreen s ui) ui1 rest :: UIState
|
|
|
|
in
|
|
|
|
ui2
|
|
|
|
|
|
|
|
pushScreen :: Screen -> UIState -> UIState
|
|
|
|
pushScreen scr ui = ui{aPrevScreens=(aScreen ui:aPrevScreens ui)
|
|
|
|
,aScreen=scr
|
|
|
|
}
|
|
|
|
|
|
|
|
popScreen :: UIState -> UIState
|
|
|
|
popScreen ui@UIState{aPrevScreens=s:ss} = ui{aScreen=s, aPrevScreens=ss}
|
|
|
|
popScreen ui = ui
|
|
|
|
|
|
|
|
resetScreens :: Day -> UIState -> UIState
|
|
|
|
resetScreens d ui@UIState{aScreen=s,aPrevScreens=ss} =
|
|
|
|
(sInit topscreen) d True $ resetDepth $ resetFilter $ closeMinibuffer ui{aScreen=topscreen, aPrevScreens=[]}
|
|
|
|
where
|
|
|
|
topscreen = case ss of _:_ -> last ss
|
|
|
|
[] -> s
|
|
|
|
|
|
|
|
-- | Enter a new screen, saving the old screen & state in the
|
|
|
|
-- navigation history and initialising the new screen's state.
|
|
|
|
screenEnter :: Day -> Screen -> UIState -> UIState
|
|
|
|
screenEnter d scr ui = (sInit scr) d True $
|
|
|
|
pushScreen scr
|
|
|
|
ui
|
|
|
|
|