buchhaltung-0.0.5: Automates most of your plain text accounting data entry in ledger format.

Safe HaskellNone
LanguageHaskell2010

Buchhaltung.Add

Contents

Synopsis

Types

type AddT' env m = RWST (FullOptions env) () Journal (ErrorT m) Source #

type AddOptions = FullOptions [Partner] Source #

Monad Transformer used to describe the add program

The add specific environment, that can contain a partner user

type AddT m = AddT' [Partner] m Source #

data Partner Source #

Constructors

Partner 

Fields

partners :: (MonadReader AddOptions m, MonadError Msg m) => m [Partner] Source #

Extract partner information from the env and throw errors if there are any readPartner :: (MonadReader AddOptions m, MonadError Msg m) => (Partner -> a) -> m (Maybe a) readPartner f = reader $ fmap f . oEnv

Entry point

toPartner :: Monad m => User -> AddT' env m Partner Source #

Convert given Username to Partner.

hello :: Monad m => AddT' env m String Source #

Welcome message

mainLoop :: AddT IO () Source #

main user interaction loop

saveAndClear Source #

Arguments

:: Maybe Transaction

matching transaction for clearing

-> Bool

clear the matching transactions

-> (Maybe Transaction, [(Partner, Transaction)])

transactioons to be saved: ((user's,other's),

-> AddT IO () 

Saves transaction into the designated ledgers files of each user, and clears the transaction tht was matched (conditional on a Bool argument)

clearSecondPosting :: Transaction -> (Transaction, Transaction) Source #

infoNewTx

split :: [EditablePosting] -> ([Posting], [(Partner, E.NonEmpty Posting, MixedAmount)]) Source #

Split EditablePostings in User's Postings and (Partner, Postings, Open Balance)

finishTransaction Source #

Arguments

:: (MonadIO m, MonadReader AddOptions m) 
=> Bool

require balanced transactions

-> Maybe (Transaction, [EditablePosting])

the transaction and postings to be combined

-> m (Maybe Transaction, [(Partner, Transaction)])

(user's, partners') transactions

generate the main and possibly the other users' transactions

myJournalAddTransaction :: FilePath -> [Transaction] -> AddT IO Journal Source #

add transaction to ledger file

clearNthPosting :: Int -> Transaction -> Transaction Source #

Transaction suggestions

data Asserted a Source #

Constructors

AA 

Fields

type AssertedAmount = Asserted MixedAmount Source #

fromPosting :: Posting -> Asserted MixedAmount Source #

sugTrans :: AddT IO (AssertedAmount, Maybe Transaction) Source #

Ask an amount, and return transactions matching the entered amount

data Choice Source #

Constructors

Reenter 
Manual 
Choose Int 

choose Source #

Arguments

:: [String]

choices

-> IO Choice 

user input: choose one from a list of choices

stripP

Main editing loop

myEd :: EditorConf (AddT IO) EditablePosting Transaction Source #

combines everything into an EditorConf

mainPrompt :: (ListLike m item, IsString m) => m Source #

quiet :: Monad m => a -> m (Maybe a) Source #

nextNotFirst :: EditablePosting -> EditablePosting Source #

change user of current posting, but not for the first posting ReferenceA

balanceTransactionIfRequired :: Transaction -> Either String Transaction Source #

data Balancing Source #

Constructors

B 

Fields

balanceRequirement :: MonadError String m => [Posting] -> m Balancing Source #

check, if the transaction should be passed through balanceTransaction to infer missing amounts

checkDone :: LState EditablePosting Transaction -> AddT IO (Maybe (LState EditablePosting Transaction)) Source #

Try to balance the transactions and present the final transactions

Asking (with completion)

askDescription Source #

Arguments

:: Maybe T.Text

default

-> IO T.Text 

askDate Source #

Arguments

:: Maybe Day

default

-> IO (Day, T.Text) 

dateandcodep :: MP.Parser (SmartDate, T.Text) Source #

HLedger's smartdate and code

myAskAccount

askAmount Source #

Arguments

:: Maybe AssertedAmount

default value, if "" is entered

-> T.Text

prompt

-> Maybe T.Text

initial

-> AddT IO AssertedAmount 

parseAmount :: Journal -> T.Text -> Either (ParseError Char Dec) AssertedAmount Source #

_amountp2

nosymbolamountp2 :: Monad m => JournalStateParser m Amount Source #

getDefaultCommodityAndStyle2 :: Journal -> Maybe (CommoditySymbol, AmountStyle) Source #

askPercent :: IO Decimal Source #

Posting and Suggestions

data EditablePosting Source #

Type holding suggested or temporary postings

Constructors

EditablePosting 

Fields

editablePosting

addPosting :: AccountName -> Maybe AssertedAmount -> EditablePosting -> EditablePosting Source #

generate and add new Posting to EditablePosting

jumpTo :: Int -> Zipper a -> Zipper a Source #

jump to a certain element in a zipper

editDate :: LState a Transaction -> AddT IO (LState a Transaction) Source #

editDescription :: LState a Transaction -> AddT IO (LState a Transaction) Source #

editCurAmount :: EditablePostings -> AddT IO EditablePostings Source #

edit the amount of the selected posting

modifyCurAmount Source #

Arguments

:: (AssertedAmount -> AssertedAmount -> AssertedAmount)

oldAmout -> enteredAmount -> newAmount

-> Bool

Show old amound

-> EditablePostings 
-> AddT IO EditablePostings 

modfiy current amount by asking for a new amount, that is combined with the old to get a new amount (e.g. with (+))

replaceMissing :: MixedAmount -> MixedAmount Source #

defNumSuggestedAccounts :: Int Source #

Hardcoded default number of suggested accounts

suggestedPostings :: MonadIO m => AccountName -> Maybe AssertedAmount -> AddT m (E.NonEmpty EditablePosting) Source #

retrieve a number of suggested contra postings for a given account, sort frequency of that contra account for the given account.

duplicate each posting for both users, but only if the other user's account is present in the suggestions.

next :: EditablePosting -> EditablePosting Source #

change posting's user to the next user

assignOpenBalance :: Decimal -> EditablePostings -> EditablePostings Source #

assign the Transaction's open balance to an empty EditablePosting

totalBalance :: [EditablePosting] -> MixedAmount Source #

showAmount2 :: Amount -> T.Text Source #

showMixedAmount2 :: MixedAmount -> T.Text Source #

addNewPosting Source #

Arguments

:: Bool

for next partner

-> EditablePostings 
-> AddT IO EditablePostings 

ask for new account (display old as default) and use existing posting, if same account without a posting/amount already exists or append.

moveToNextEmpty :: EditablePostings -> EditablePostings Source #

move the focus to the next empty posting

Pretty Table Printer

fillLeft

fillRight

fillCenter