| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Hledger.Cli.Add
Description
A history-aware add command to help with data entry. |
- addmode :: Mode RawOpts
- data EntryState = EntryState {- esOpts :: CliOpts
- esArgs :: [String]
- esToday :: Day
- esDefDate :: Day
- esJournal :: Journal
- esSimilarTransaction :: Maybe Transaction
- esPostings :: [Posting]
 
- defEntryState :: EntryState
- data RestartTransactionException = RestartTransactionException
- add :: CliOpts -> Journal -> IO ()
- showHelp :: IO ()
- getAndAddTransactions :: EntryState -> IO ()
- confirmedTransactionWizard :: EntryState -> Wizard Haskeline Transaction
- transactionWizard :: EntryState -> Wizard Haskeline Transaction
- similarTransaction :: EntryState -> Text -> Maybe Transaction
- dateAndCodeWizard :: EntryState -> Wizard Haskeline (Day, Text)
- descriptionAndCommentWizard :: EntryState -> Wizard Haskeline (Text, Text)
- postingsWizard :: EntryState -> Wizard Haskeline [Posting]
- postingWizard :: EntryState -> Wizard Haskeline (Maybe Posting)
- postingsBalanced :: [Posting] -> Bool
- accountWizard :: EntryState -> Wizard Haskeline String
- amountAndCommentWizard :: EntryState -> Wizard Haskeline (Amount, Text)
- maybeExit :: Wizard Haskeline String -> Wizard Haskeline String
- maybeRestartTransaction :: Wizard Haskeline String -> Wizard Haskeline String
- dateCompleter :: String -> CompletionFunc IO
- descriptionCompleter :: Journal -> String -> CompletionFunc IO
- accountCompleter :: Journal -> String -> CompletionFunc IO
- amountCompleter :: String -> CompletionFunc IO
- completer :: [String] -> String -> CompletionFunc IO
- defaultTo' :: a -> Wizard Haskeline a -> Wizard Haskeline a
- withCompletion :: (:<:) WithSettings b => CompletionFunc IO -> Wizard b a -> Wizard b a
- green :: [Char] -> [Char]
- showDefault :: [Char] -> [Char]
- journalAddTransaction :: Journal -> CliOpts -> Transaction -> IO Journal
- appendToJournalFileOrStdout :: FilePath -> String -> IO ()
- ensureOneNewlineTerminated :: String -> String
- registerFromString :: String -> IO String
- capitalize :: String -> String
- transactionsSimilarTo :: Journal -> Query -> Text -> [(Double, Transaction)]
- compareDescriptions :: Text -> Text -> Double
- compareStrings :: String -> String -> Double
- wordLetterPairs :: String -> [[Char]]
- letterPairs :: [a] -> [[a]]
Documentation
data EntryState Source #
State used while entering transactions.
Constructors
| EntryState | |
| Fields 
 | |
Instances
data RestartTransactionException Source #
Constructors
| RestartTransactionException | 
add :: CliOpts -> Journal -> IO () Source #
Read multiple transactions from the console, prompting for each field, and append them to the journal file. If the journal came from stdin, this command has no effect.
getAndAddTransactions :: EntryState -> IO () Source #
Loop reading transactions from the console, prompting, validating and appending each one to the journal file, until end of input or ctrl-c (then raise an EOF exception). If provided, command-line arguments are used as defaults; otherwise defaults come from the most similar recent transaction in the journal.
similarTransaction :: EntryState -> Text -> Maybe Transaction Source #
dateAndCodeWizard :: EntryState -> Wizard Haskeline (Day, Text) Source #
postingsWizard :: EntryState -> Wizard Haskeline [Posting] Source #
postingWizard :: EntryState -> Wizard Haskeline (Maybe Posting) Source #
postingsBalanced :: [Posting] -> Bool Source #
amountAndCommentWizard :: EntryState -> Wizard Haskeline (Amount, Text) Source #
dateCompleter :: String -> CompletionFunc IO Source #
descriptionCompleter :: Journal -> String -> CompletionFunc IO Source #
accountCompleter :: Journal -> String -> CompletionFunc IO Source #
amountCompleter :: String -> CompletionFunc IO Source #
completer :: [String] -> String -> CompletionFunc IO Source #
Generate a haskeline completion function from the given completions and default, that case insensitively completes with prefix matches, or infix matches above a minimum length, or completes the null string with the default.
withCompletion :: (:<:) WithSettings b => CompletionFunc IO -> Wizard b a -> Wizard b a Source #
showDefault :: [Char] -> [Char] Source #
journalAddTransaction :: Journal -> CliOpts -> Transaction -> IO Journal Source #
Append this transaction to the journal's file and transaction list.
appendToJournalFileOrStdout :: FilePath -> String -> IO () Source #
Append a string, typically one or more transactions, to a journal file, or if the file is "-", dump it to stdout. Tries to avoid excess whitespace.
ensureOneNewlineTerminated :: String -> String Source #
Replace a string's 0 or more terminating newlines with exactly one.
registerFromString :: String -> IO String Source #
Convert a string of journal data into a register report.
capitalize :: String -> String Source #
transactionsSimilarTo :: Journal -> Query -> Text -> [(Double, Transaction)] Source #
Find the most similar and recent transactions matching the given transaction description and report query. Transactions are listed with their "relevancy" score, most relevant first.
compareDescriptions :: Text -> Text -> Double Source #
Return a similarity measure, from 0 to 1, for two transaction descriptions. This is like compareStrings, but first strips out any numbers, to improve accuracy eg when there are bank transaction ids from imported data.
compareStrings :: String -> String -> Double Source #
Return a similarity measure, from 0 to 1, for two strings. This was based on Simon White's string similarity algorithm (http:/www.catalysoft.comarticles/StrikeAMatch.html), later found to be https://en.wikipedia.org/wiki/S%C3%B8rensen%E2%80%93Dice_coefficient, modified to handle short strings better. Todo: check out http://nlp.fi.muni.cz/raslan/2008/raslan08.pdf#page=14 .
wordLetterPairs :: String -> [[Char]] Source #
letterPairs :: [a] -> [[a]] Source #