try to make the add command a bit more usable
This commit is contained in:
parent
c0c9c7a070
commit
e2d14aebb7
185
AddCommand.hs
185
AddCommand.hs
@ -6,7 +6,6 @@ An add command to help with data entry.
|
|||||||
|
|
||||||
module AddCommand
|
module AddCommand
|
||||||
where
|
where
|
||||||
-- import Data.List.Utils (replace)
|
|
||||||
import Prelude hiding (putStr, putStrLn, getLine, appendFile)
|
import Prelude hiding (putStr, putStrLn, getLine, appendFile)
|
||||||
import Ledger
|
import Ledger
|
||||||
import Options
|
import Options
|
||||||
@ -18,73 +17,93 @@ import Text.ParserCombinators.Parsec
|
|||||||
import Utils (ledgerFromStringWithOpts)
|
import Utils (ledgerFromStringWithOpts)
|
||||||
|
|
||||||
|
|
||||||
-- | Read ledger transactions from the command line, prompting for each
|
-- | Read ledger transactions from the terminal, prompting for each field,
|
||||||
-- field, and append them to the ledger file. If the ledger came from
|
-- and append them to the ledger file. If the ledger came from stdin, this
|
||||||
-- stdin, this command has no effect.
|
-- command has no effect.
|
||||||
add :: [Opt] -> [String] -> Ledger -> IO ()
|
add :: [Opt] -> [String] -> Ledger -> IO ()
|
||||||
add opts args l
|
add opts args l
|
||||||
| filepath (rawledger l) == "-" = return ()
|
| filepath (rawledger l) == "-" = return ()
|
||||||
| otherwise = do
|
| otherwise = do
|
||||||
hPutStrLn stderr ("Enter one or more transactions, which will be added to your ledger file.\n\
|
hPutStrLn stderr
|
||||||
\A blank account or amount ends a transaction, control-d to finish.")
|
"Enter one or more transactions, which will be added to your ledger file.\n\
|
||||||
ts <- getAndAddTransactions l args
|
\To complete a transaction, enter . as account name.\n\
|
||||||
hPutStrLn stderr $ printf "\nAdded %d transactions to %s" (length ts) (filepath $ rawledger l)
|
\To finish input, enter control-d (discards any transaction in progress)."
|
||||||
|
getAndAddTransactions l args
|
||||||
|
return ()
|
||||||
|
|
||||||
-- | Read a number of ledger transactions from the command line,
|
-- | Read a number of ledger transactions from the command line,
|
||||||
-- prompting, validating, displaying and appending them to the ledger
|
-- prompting, validating, displaying and appending them to the ledger
|
||||||
-- file, until EOF.
|
-- file, until end of input.
|
||||||
getAndAddTransactions :: Ledger -> [String] -> IO [LedgerTransaction]
|
getAndAddTransactions :: Ledger -> [String] -> IO [LedgerTransaction]
|
||||||
getAndAddTransactions l args = (do
|
getAndAddTransactions l args = do
|
||||||
t <- getTransaction l args >>= addTransaction l
|
-- for now, thread the eoi flag throughout rather than muck about with monads
|
||||||
liftM (t:) (getAndAddTransactions l args)
|
(t, eoi) <- getTransaction l args
|
||||||
) `catch` (\e -> if isEOFError e then return [] else ioError e)
|
l <- if isJust t then addTransaction l (fromJust t) else return l
|
||||||
|
if eoi then return $ maybe [] (:[]) t
|
||||||
|
else liftM (fromJust t:) (getAndAddTransactions l args)
|
||||||
|
|
||||||
-- | Read a transaction from the command line.
|
-- | Get a transaction from the command line, if possible, and a flag
|
||||||
getTransaction :: Ledger -> [String] -> IO LedgerTransaction
|
-- indicating end of input.
|
||||||
|
getTransaction :: Ledger -> [String] -> IO (Maybe LedgerTransaction, Bool)
|
||||||
getTransaction l args = do
|
getTransaction l args = do
|
||||||
today <- getCurrentDay
|
today <- getCurrentDay
|
||||||
datestr <- askFor "date" (Just $ showDate today)
|
(datestr, eoi) <- askFor "date"
|
||||||
(Just $ \s -> null s ||
|
(Just $ showDate today)
|
||||||
(isRight $ parse (smartdate >> many spacenonewline >> eof) "" $ lowercase s))
|
(Just $ \s -> null s ||
|
||||||
let date = fixSmartDate today $ fromparse $ (parse smartdate "" . lowercase) datestr
|
(isRight $ parse (smartdate >> many spacenonewline >> eof) "" $ lowercase s))
|
||||||
description <- if null args
|
if eoi
|
||||||
then askFor "description" Nothing (Just $ not . null)
|
then return (Nothing, True)
|
||||||
else (do
|
|
||||||
hPutStrLn stderr $ "description: " ++ unwords args
|
|
||||||
return $ unwords args)
|
|
||||||
let historymatches = transactionsSimilarTo l description
|
|
||||||
when (not $ null historymatches) (do
|
|
||||||
hPutStrLn stderr "Similar past transactions:"
|
|
||||||
hPutStr stderr $ concatMap (\(n,t) -> printf "[%3d%%] %s" (round $ n*100 :: Int) (show t)) $ take 3 historymatches)
|
|
||||||
let bestmatch | null historymatches = Nothing
|
|
||||||
| otherwise = Just $ snd $ head $ historymatches
|
|
||||||
let bestmatchpostings = maybe Nothing (Just . ltpostings) bestmatch
|
|
||||||
let getpostingsandvalidate = do
|
|
||||||
ps <- getPostings bestmatchpostings []
|
|
||||||
let t = nullledgertxn{ltdate=date
|
|
||||||
,ltstatus=False
|
|
||||||
,ltdescription=description
|
|
||||||
,ltpostings=ps
|
|
||||||
}
|
|
||||||
either (const retry) (return) $ balanceLedgerTransaction t
|
|
||||||
retry = do
|
|
||||||
hPutStrLn stderr $ nonzerobalanceerror ++ ". Re-enter:"
|
|
||||||
getpostingsandvalidate
|
|
||||||
getpostingsandvalidate
|
|
||||||
|
|
||||||
-- | Read two or more postings from the command line.
|
|
||||||
getPostings :: Maybe [Posting] -> [Posting] -> IO [Posting]
|
|
||||||
getPostings bestmatchps enteredps = do
|
|
||||||
account <- askFor (printf "account %d" n) defaultaccount validateaccount
|
|
||||||
if null account
|
|
||||||
then return enteredps
|
|
||||||
else do
|
else do
|
||||||
amountstr <- askFor (printf "amount %d" n) defaultamount validateamount
|
(description, eoi) <- if null args
|
||||||
|
then askFor "description" Nothing (Just $ not . null)
|
||||||
|
else (do
|
||||||
|
let description = unwords args
|
||||||
|
hPutStrLn stderr $ "description: " ++ description
|
||||||
|
return (description, False))
|
||||||
|
if eoi
|
||||||
|
then return (Nothing, True)
|
||||||
|
else do
|
||||||
|
let historymatches = transactionsSimilarTo l description
|
||||||
|
when (not $ null historymatches) (do
|
||||||
|
hPutStrLn stderr "Similar past transactions found:"
|
||||||
|
hPutStr stderr $ concatMap (\(n,t) -> printf "[%3d%%] %s" (round $ n*100 :: Int) (show t)) $ take 3 historymatches)
|
||||||
|
let bestmatch | null historymatches = Nothing
|
||||||
|
| otherwise = Just $ snd $ head $ historymatches
|
||||||
|
bestmatchpostings = maybe Nothing (Just . ltpostings) bestmatch
|
||||||
|
date = fixSmartDate today $ fromparse $ (parse smartdate "" . lowercase) datestr
|
||||||
|
getpostingsandvalidate = do
|
||||||
|
(ps, eoi) <- getPostings bestmatchpostings []
|
||||||
|
let t = nullledgertxn{ltdate=date
|
||||||
|
,ltstatus=False
|
||||||
|
,ltdescription=description
|
||||||
|
,ltpostings=ps
|
||||||
|
}
|
||||||
|
if eoi && null ps
|
||||||
|
then return (Nothing, eoi)
|
||||||
|
else either (const retry) (return . flip (,) eoi . Just) $ balanceLedgerTransaction t
|
||||||
|
retry = do
|
||||||
|
hPutStrLn stderr $ "\n" ++ nonzerobalanceerror ++ ". Re-enter:"
|
||||||
|
getpostingsandvalidate
|
||||||
|
getpostingsandvalidate
|
||||||
|
|
||||||
|
-- | Get two or more postings from the command line, if possible, and a
|
||||||
|
-- flag indicating end of input.
|
||||||
|
getPostings :: Maybe [Posting] -> [Posting] -> IO ([Posting], Bool)
|
||||||
|
getPostings bestmatchps enteredps = do
|
||||||
|
(account, eoi) <- askFor (printf "account %d" n) defaultaccount validateaccount
|
||||||
|
if account=="." || eoi
|
||||||
|
then return (enteredps, eoi)
|
||||||
|
else do
|
||||||
|
(amountstr, eoi) <- askFor (printf "amount %d" n) defaultamount validateamount
|
||||||
let amount = fromparse $ parse (someamount <|> return missingamt) "" amountstr
|
let amount = fromparse $ parse (someamount <|> return missingamt) "" amountstr
|
||||||
let p = nullrawposting{paccount=account,pamount=amount}
|
let p = nullrawposting{paccount=account,pamount=amount}
|
||||||
if amount == missingamt
|
if eoi
|
||||||
then return $ enteredps ++ [p]
|
then if null enteredps
|
||||||
else getPostings bestmatchps $ enteredps ++ [p]
|
then return ([], True)
|
||||||
|
else return (enteredps ++ [p], True)
|
||||||
|
else if amount == missingamt
|
||||||
|
then return $ (enteredps ++ [p], eoi)
|
||||||
|
else getPostings bestmatchps $ enteredps ++ [p]
|
||||||
where
|
where
|
||||||
n = length enteredps + 1
|
n = length enteredps + 1
|
||||||
bestmatch | isNothing bestmatchps = Nothing
|
bestmatch | isNothing bestmatchps = Nothing
|
||||||
@ -92,32 +111,44 @@ getPostings bestmatchps enteredps = do
|
|||||||
| otherwise = Nothing
|
| otherwise = Nothing
|
||||||
where Just ps = bestmatchps
|
where Just ps = bestmatchps
|
||||||
defaultaccount = maybe Nothing (Just . paccount) bestmatch
|
defaultaccount = maybe Nothing (Just . paccount) bestmatch
|
||||||
validateaccount = Just $ \s -> not $ null s && (length enteredps < 2)
|
validateaccount = Just $ \s -> not $ null s
|
||||||
defaultamount = maybe Nothing (Just . show . pamount) bestmatch
|
defaultamount = maybe Nothing (Just . show . pamount) bestmatch
|
||||||
validateamount = Just $ \s ->
|
validateamount = Just $ \s ->
|
||||||
(null s && (not $ null enteredps)) ||
|
(null s && (not $ null enteredps)) ||
|
||||||
(isRight $ parse (someamount>>many spacenonewline>>eof) "" s)
|
(isRight $ parse (someamount>>many spacenonewline>>eof) "" s)
|
||||||
|
|
||||||
|
|
||||||
-- | Prompt and read a string value, possibly with a default and a validator.
|
-- | Prompt for and read a string value and a flag indicating whether
|
||||||
-- A validator will cause the prompt to repeat until the input is valid.
|
-- input has ended (control-d was pressed), optionally with a default
|
||||||
askFor :: String -> Maybe String -> Maybe (String -> Bool) -> IO String
|
-- value and a validator. A validator will cause the prompt to repeat
|
||||||
|
-- until the input is valid (unless the input is just ctrl-d).
|
||||||
|
askFor :: String -> Maybe String -> Maybe (String -> Bool) -> IO (String, Bool)
|
||||||
askFor prompt def validator = do
|
askFor prompt def validator = do
|
||||||
hPutStr stderr $ prompt ++ (maybe "" showdef def) ++ ": "
|
hPutStr stderr $ prompt ++ (maybe "" showdef def) ++ ": "
|
||||||
hFlush stderr
|
hFlush stderr
|
||||||
l <- getLine
|
-- ugly
|
||||||
let input = if null l then fromMaybe l def else l
|
l <- getLine `catch` (\e -> if isEOFError e then return "*EOF*" else ioError e)
|
||||||
|
let (l', eoi) = case l of "*EOF*" -> ("", True)
|
||||||
|
_ -> (l, False)
|
||||||
|
let input = if null l' then fromMaybe l' def else l'
|
||||||
case validator of
|
case validator of
|
||||||
Just valid -> if valid input then return input else askFor prompt def validator
|
Just valid -> if valid input || (null input && eoi)
|
||||||
Nothing -> return input
|
then return (input, eoi)
|
||||||
|
else askFor prompt def validator
|
||||||
|
Nothing -> return (input, eoi)
|
||||||
where showdef s = " [" ++ s ++ "]"
|
where showdef s = " [" ++ s ++ "]"
|
||||||
|
|
||||||
-- | Append this transaction to the ledger's file.
|
-- | Append this transaction to the ledger's file. Also, to the ledger's
|
||||||
addTransaction :: Ledger -> LedgerTransaction -> IO LedgerTransaction
|
-- transaction list, but we don't bother updating the other fields - this
|
||||||
|
-- is enough to include new transactions in the history matching.
|
||||||
|
addTransaction :: Ledger -> LedgerTransaction -> IO Ledger
|
||||||
addTransaction l t = do
|
addTransaction l t = do
|
||||||
putStrLn =<< registerFromString (show t)
|
|
||||||
appendToLedgerFile l $ show t
|
appendToLedgerFile l $ show t
|
||||||
return t
|
putStrLn $ printf "\nAdded transaction to %s:" (filepath $ rawledger l)
|
||||||
|
putStrLn =<< registerFromString (show t)
|
||||||
|
return l{rawledger=rl{ledger_txns=ts}}
|
||||||
|
where rl = rawledger l
|
||||||
|
ts = ledger_txns rl ++ [t]
|
||||||
|
|
||||||
-- | Append data to the ledger's file, ensuring proper separation from any
|
-- | Append data to the ledger's file, ensuring proper separation from any
|
||||||
-- existing data; or if the file is "-", dump it to stdout.
|
-- existing data; or if the file is "-", dump it to stdout.
|
||||||
@ -138,16 +169,23 @@ registerFromString :: String -> IO String
|
|||||||
registerFromString s = do
|
registerFromString s = do
|
||||||
now <- getCurrentLocalTime
|
now <- getCurrentLocalTime
|
||||||
l <- ledgerFromStringWithOpts [] [] now s
|
l <- ledgerFromStringWithOpts [] [] now s
|
||||||
return $ showRegisterReport [] [] l
|
return $ showRegisterReport [Empty] [] l
|
||||||
|
|
||||||
-- | Simon White's letter pairs algorithm from
|
-- | Return a similarity measure, from 0 to 1, for two strings.
|
||||||
|
-- This is Simon White's letter pairs algorithm from
|
||||||
-- http://www.catalysoft.com/articles/StrikeAMatch.html
|
-- http://www.catalysoft.com/articles/StrikeAMatch.html
|
||||||
compareStrings s t = 2.0 * (fromIntegral i) / (fromIntegral u)
|
-- with a modification for short strings.
|
||||||
|
compareStrings :: String -> String -> Float
|
||||||
|
compareStrings "" "" = 1
|
||||||
|
compareStrings (a:[]) "" = 0
|
||||||
|
compareStrings "" (b:[]) = 0
|
||||||
|
compareStrings (a:[]) (b:[]) = if toUpper a == toUpper b then 1 else 0
|
||||||
|
compareStrings s1 s2 = 2.0 * (fromIntegral i) / (fromIntegral u)
|
||||||
where
|
where
|
||||||
pairs1 = wordLetterPairs $ uppercase s
|
|
||||||
pairs2 = wordLetterPairs $ uppercase t
|
|
||||||
u = length pairs1 + length pairs2
|
|
||||||
i = length $ intersect pairs1 pairs2
|
i = length $ intersect pairs1 pairs2
|
||||||
|
u = length pairs1 + length pairs2
|
||||||
|
pairs1 = wordLetterPairs $ uppercase s1
|
||||||
|
pairs2 = wordLetterPairs $ uppercase s2
|
||||||
wordLetterPairs = concatMap letterPairs . words
|
wordLetterPairs = concatMap letterPairs . words
|
||||||
letterPairs (a:b:rest) = [a,b]:(letterPairs (b:rest))
|
letterPairs (a:b:rest) = [a,b]:(letterPairs (b:rest))
|
||||||
letterPairs _ = []
|
letterPairs _ = []
|
||||||
@ -160,12 +198,13 @@ compareLedgerDescriptions s t = compareStrings s' t'
|
|||||||
transactionsSimilarTo :: Ledger -> String -> [(Float,LedgerTransaction)]
|
transactionsSimilarTo :: Ledger -> String -> [(Float,LedgerTransaction)]
|
||||||
transactionsSimilarTo l s =
|
transactionsSimilarTo l s =
|
||||||
sortBy compareRelevanceAndRecency
|
sortBy compareRelevanceAndRecency
|
||||||
$ filter ((/=0).fst)
|
$ filter ((> threshold).fst)
|
||||||
$ [(compareLedgerDescriptions s $ ltdescription t, t) | t <- ts]
|
$ [(compareLedgerDescriptions s $ ltdescription t, t) | t <- ts]
|
||||||
-- $ [(compareLedgerDescriptions s $ (strace $ unwords $ [ltdescription t] ++ (map (replace ":" " " . paccount) $ ltpostings t)), t) | t <- ts]
|
-- $ [(compareLedgerDescriptions s $ (strace $ unwords $ [ltdescription t] ++ (map (replace ":" " " . paccount) $ ltpostings t)), t) | t <- ts]
|
||||||
where
|
where
|
||||||
compareRelevanceAndRecency (n1,t1) (n2,t2) = compare (n2,ltdate t2) (n1,ltdate t1)
|
compareRelevanceAndRecency (n1,t1) (n2,t2) = compare (n2,ltdate t2) (n1,ltdate t1)
|
||||||
ts = ledger_txns $ rawledger l
|
ts = ledger_txns $ rawledger l
|
||||||
|
threshold = 0
|
||||||
|
|
||||||
{- doctests
|
{- doctests
|
||||||
|
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user