hledger/hledger-ui/Hledger/UI/Main.hs
Simon Michael 866414a528 ui: provide a more useful transaction register
The register screen is now like the register view in hledger-web (and
other accounting systems), rather than hledger's register command.
This means:

- it shows transactions affecting a particular current account, rather
  than postings matching a pattern.

- Each line represents a whole transaction.

- The account field shows the *other* account being transacted with.
  When there is more than one, they are all listed, abbreviated and
  marked with "(split)".

- The amount field shows the effect of the transaction on the current
  account; positive for an inflow to this account, negative for an
  outflow.

- The balance field should usually show the current account's historic
  balance as of the transaction date, even when you change the report
  start date. (Not working yet - currently it always shows the running
  total).

- Transactions are listed most recent first, currently.
2015-08-24 16:24:11 -07:00

113 lines
3.2 KiB
Haskell

{-|
hledger-ui - a hledger add-on providing a curses-style interface.
Copyright (c) 2007-2015 Simon Michael <simon@joyful.com>
Released under GPL version 3 or later.
TODO:
show journal entries
--
switch to next brick release
reg: use full width
home/end
keep cursor at bottom of screen if jumping to end
reg2: find subaccounts' transactions better
reg2: track current account better
reg2: track current query better
--
-H
--drop
search
filter
depth adjustment
add
edit
options adjustment
reload on screen change
reload on redraw
reload on file change
-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Hledger.UI.Main where
-- import Control.Applicative
-- import Control.Lens ((^.))
import Control.Monad
-- import Data.Default
-- import Data.Monoid --
-- import Data.List
-- import Data.Maybe
-- import Data.Time.Calendar
-- import Safe
import System.Exit
import qualified Graphics.Vty as V
import Brick
import Hledger
import Hledger.Cli hiding (progname,prognameandversion,green)
import Hledger.UI.Options
import Hledger.UI.UITypes
import Hledger.UI.UIUtils
import Hledger.UI.AccountsScreen as AS
-- import Hledger.UI.RegisterScreen as RS
import Hledger.UI.RegisterScreen2 as RS2
----------------------------------------------------------------------
-- | The available screens.
appScreens = [
AS.screen
,RS2.screen
]
main :: IO ()
main = do
opts <- getHledgerUIOpts
-- when (debug_ $ cliopts_ opts) $ printf "%s\n" prognameandversion >> printf "opts: %s\n" (show opts)
run opts
where
run opts
| "help" `inRawOpts` (rawopts_ $ cliopts_ opts) = putStr (showModeHelp uimode) >> exitSuccess
| "version" `inRawOpts` (rawopts_ $ cliopts_ opts) = putStrLn prognameandversion >> exitSuccess
| "binary-filename" `inRawOpts` (rawopts_ $ cliopts_ opts) = putStrLn (binaryfilename progname)
| otherwise = withJournalDo' opts runBrickUi
withJournalDo' :: UIOpts -> (UIOpts -> Journal -> IO ()) -> IO ()
withJournalDo' opts cmd = do
-- journalFilePathFromOpts (cliopts_ opts) >>= readJournalFile Nothing >>=
-- either error' (cmd opts . journalApplyAliases (aliasesFromOpts $ cliopts_ opts))
-- XXX head should be safe for now
(head `fmap` journalFilePathFromOpts (cliopts_ opts)) >>= readJournalFile Nothing Nothing True >>=
either error' (cmd opts . journalApplyAliases (aliasesFromOpts $ cliopts_ opts))
runBrickUi :: UIOpts -> Journal -> IO ()
runBrickUi opts j = do
d <- getCurrentDay
let
args = words' $ query_ $ reportopts_ $ cliopts_ opts
scr = head appScreens
st = (sInitFn scr) d args
AppState{
aopts=opts
,aargs=args
,ajournal=j
,aScreen=scr
,aPrevScreens=[]
}
app :: App (AppState) V.Event
app = App {
appLiftVtyEvent = id
, appStartEvent = return
, appAttrMap = const customAttrMap
, appChooseCursor = showFirstCursor
, appHandleEvent = \st ev -> (sHandleFn $ aScreen st) st ev
, appDraw = \st -> (sDrawFn $ aScreen st) st
}
void $ defaultMain app st