{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module View
( viewState
, viewQuestion
, viewContext
, viewSuggestion
, viewMessage
) where
import Brick
import Brick.Widgets.List
import Brick.Widgets.WrappedText
import Data.Semigroup ((<>))
import Data.Text (Text)
import qualified Data.Text as T
import qualified Hledger as HL
#if !MIN_VERSION_hledger_lib(1,16,99)
import Data.Time hiding (parseTime)
#endif
import Model
viewState :: Step -> Widget n
viewState :: Step -> Widget n
viewState (DateQuestion Comment
comment) = Comment -> Widget n
forall n. Comment -> Widget n
txt (Comment -> Widget n) -> Comment -> Widget n
forall a b. (a -> b) -> a -> b
$
if Comment -> Bool
T.null Comment
comment then Comment
" " else Comment -> Comment
viewComment Comment
comment
viewState (DescriptionQuestion Day
date Comment
comment) = Comment -> Widget n
forall n. Comment -> Widget n
txt (Comment -> Widget n) -> Comment -> Widget n
forall a b. (a -> b) -> a -> b
$
#if MIN_VERSION_hledger_lib(1,16,99)
String -> Comment
T.pack (Day -> String
forall a. Show a => a -> String
show Day
date)
#else
T.pack (formatTime defaultTimeLocale "%Y/%m/%d" date)
#endif
Comment -> Comment -> Comment
forall a. Semigroup a => a -> a -> a
<> Comment -> Comment
viewComment Comment
comment
viewState (AccountQuestion Transaction
trans Comment
comment) = Comment -> Widget n
forall n. Comment -> Widget n
txt (Comment -> Widget n) -> Comment -> Widget n
forall a b. (a -> b) -> a -> b
$
Transaction -> Comment
showTransaction Transaction
trans Comment -> Comment -> Comment
forall a. Semigroup a => a -> a -> a
<> Comment -> Comment
viewComment Comment
comment
viewState (AmountQuestion Comment
acc Transaction
trans Comment
comment) = Comment -> Widget n
forall n. Comment -> Widget n
txt (Comment -> Widget n) -> Comment -> Widget n
forall a b. (a -> b) -> a -> b
$
Transaction -> Comment
showTransaction Transaction
trans Comment -> Comment -> Comment
forall a. Semigroup a => a -> a -> a
<> Comment
"\n " Comment -> Comment -> Comment
forall a. Semigroup a => a -> a -> a
<> Comment
acc Comment -> Comment -> Comment
forall a. Semigroup a => a -> a -> a
<> Comment -> Comment
viewComment Comment
comment
viewState (FinalQuestion Transaction
trans Bool
_) = Comment -> Widget n
forall n. Comment -> Widget n
txt (Comment -> Widget n) -> Comment -> Widget n
forall a b. (a -> b) -> a -> b
$
Transaction -> Comment
showTransaction Transaction
trans
viewQuestion :: Step -> Widget n
viewQuestion :: Step -> Widget n
viewQuestion (DateQuestion Comment
_) = Comment -> Widget n
forall n. Comment -> Widget n
txt Comment
"Date"
viewQuestion (DescriptionQuestion Day
_ Comment
_) = Comment -> Widget n
forall n. Comment -> Widget n
txt Comment
"Description"
viewQuestion (AccountQuestion Transaction
trans Comment
_) = String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$
String
"Account " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Transaction -> Int
numPostings Transaction
trans Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
viewQuestion (AmountQuestion Comment
_ Transaction
trans Comment
_) = String -> Widget n
forall n. String -> Widget n
str (String -> Widget n) -> String -> Widget n
forall a b. (a -> b) -> a -> b
$
String
"Amount " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Transaction -> Int
numPostings Transaction
trans Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
viewQuestion (FinalQuestion Transaction
_ Bool
duplicate) = Comment -> Widget n
forall n. Comment -> Widget n
txt (Comment -> Widget n) -> Comment -> Widget n
forall a b. (a -> b) -> a -> b
$
Comment
"Add this transaction to the journal?"
Comment -> Comment -> Comment
forall a. Semigroup a => a -> a -> a
<> (if Bool
duplicate then Comment
" (warning: duplicate)" else Comment
"")
Comment -> Comment -> Comment
forall a. Semigroup a => a -> a -> a
<> Comment
" Y/n"
viewContext :: (Ord n, Show n) => List n Text -> Widget n
viewContext :: List n Comment -> Widget n
viewContext = (Bool -> Comment -> Widget n) -> Bool -> List n Comment -> Widget n
forall (t :: * -> *) n e.
(Traversable t, Splittable t, Ord n, Show n) =>
(Bool -> e -> Widget n) -> Bool -> GenericList n t e -> Widget n
renderList Bool -> Comment -> Widget n
forall n. Bool -> Comment -> Widget n
renderItem Bool
True
viewSuggestion :: Maybe Text -> Widget n
viewSuggestion :: Maybe Comment -> Widget n
viewSuggestion Maybe Comment
Nothing = Comment -> Widget n
forall n. Comment -> Widget n
txt Comment
""
viewSuggestion (Just Comment
t) = Comment -> Widget n
forall n. Comment -> Widget n
txt (Comment -> Widget n) -> Comment -> Widget n
forall a b. (a -> b) -> a -> b
$ Comment
" (" Comment -> Comment -> Comment
forall a. Semigroup a => a -> a -> a
<> Comment
t Comment -> Comment -> Comment
forall a. Semigroup a => a -> a -> a
<> Comment
")"
renderItem :: Bool -> Text -> Widget n
renderItem :: Bool -> Comment -> Widget n
renderItem Bool
True = AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
listSelectedAttr (Widget n -> Widget n)
-> (Comment -> Widget n) -> Comment -> Widget n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Padding -> Widget n -> Widget n
forall n. Padding -> Widget n -> Widget n
padRight Padding
Max (Widget n -> Widget n)
-> (Comment -> Widget n) -> Comment -> Widget n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Comment -> Widget n
forall n. Comment -> Widget n
txt
renderItem Bool
False = Comment -> Widget n
forall n. Comment -> Widget n
txt
numPostings :: HL.Transaction -> Int
numPostings :: Transaction -> Int
numPostings = [Posting] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Posting] -> Int)
-> (Transaction -> [Posting]) -> Transaction -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> [Posting]
HL.tpostings
viewMessage :: Text -> Widget n
viewMessage :: Comment -> Widget n
viewMessage Comment
msg = Comment -> Widget n
forall n. Comment -> Widget n
wrappedText (if Comment -> Bool
T.null Comment
msg then Comment
" " else Comment
msg)
viewComment :: Text -> Text
Comment
comment
| Comment -> Bool
T.null Comment
comment = Comment
""
| Bool
otherwise = [Comment] -> Comment
T.unlines ([Comment] -> Comment) -> [Comment] -> Comment
forall a b. (a -> b) -> a -> b
$ (Comment -> Comment) -> [Comment] -> [Comment]
forall a b. (a -> b) -> [a] -> [b]
map (Comment
" ; " Comment -> Comment -> Comment
forall a. Semigroup a => a -> a -> a
<>) ([Comment] -> [Comment]) -> [Comment] -> [Comment]
forall a b. (a -> b) -> a -> b
$ Comment -> [Comment]
T.lines Comment
comment
showTransaction :: HL.Transaction -> Text
showTransaction :: Transaction -> Comment
showTransaction = Comment -> Comment
T.stripEnd (Comment -> Comment)
-> (Transaction -> Comment) -> Transaction -> Comment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> Comment
HL.showTransaction