cli: add diff command
This merges the external hledger-diff addon, which is now deprecated. https://github.com/gebner/hledger-diff/
This commit is contained in:
		
							parent
							
								
									f9aa71caf1
								
							
						
					
					
						commit
						ceb193f85e
					
				| @ -69,6 +69,7 @@ import Hledger.Cli.Commands.Checkdates | ||||
| import Hledger.Cli.Commands.Checkdupes | ||||
| import Hledger.Cli.Commands.Close | ||||
| import Hledger.Cli.Commands.Commodities | ||||
| import Hledger.Cli.Commands.Diff | ||||
| import Hledger.Cli.Commands.Files | ||||
| import Hledger.Cli.Commands.Help | ||||
| import Hledger.Cli.Commands.Import | ||||
| @ -102,6 +103,7 @@ builtinCommands = [ | ||||
|   ,(helpmode               , help') | ||||
|   ,(importmode             , importcmd) | ||||
|   ,(filesmode              , files) | ||||
|   ,(diffmode               , diff) | ||||
|   ,(incomestatementmode    , incomestatement) | ||||
|   ,(pricesmode             , prices) | ||||
|   ,(printmode              , print') | ||||
|  | ||||
							
								
								
									
										126
									
								
								hledger/Hledger/Cli/Commands/Diff.hs
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										126
									
								
								hledger/Hledger/Cli/Commands/Diff.hs
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,126 @@ | ||||
| {-| | ||||
| 
 | ||||
| The @diff@ command compares two diff. | ||||
| 
 | ||||
| -} | ||||
| 
 | ||||
| {-# LANGUAGE OverloadedStrings #-} | ||||
| {-# LANGUAGE TemplateHaskell #-} | ||||
| 
 | ||||
| module Hledger.Cli.Commands.Diff ( | ||||
|   diffmode | ||||
|  ,diff | ||||
| ) where | ||||
| 
 | ||||
| import Data.List | ||||
| import Data.Function | ||||
| import Data.Ord | ||||
| import Data.Maybe | ||||
| import Data.Time | ||||
| import Data.Either | ||||
| import qualified Data.Text as T | ||||
| import System.Exit | ||||
| 
 | ||||
| import Hledger | ||||
| import Prelude hiding (putStrLn) | ||||
| import Hledger.Utils.UTF8IOCompat (putStrLn) | ||||
| import Hledger.Cli.CliOptions | ||||
| 
 | ||||
| -- | Command line options for this command. | ||||
| diffmode = hledgerCommandMode | ||||
|   $(embedFileRelative "Hledger/Cli/Commands/Diff.txt") | ||||
|   [] | ||||
|   [generalflagsgroup2] | ||||
|   [] | ||||
|   ([], Just $ argsFlag "[ACCOUNT] -f [JOURNAL1] -f [JOURNAL2]") | ||||
| 
 | ||||
| data PostingWithPath = PostingWithPath { | ||||
|                      ppposting :: Posting, | ||||
|                      pptxnidx :: Int, | ||||
|                      pppidx :: Int } | ||||
|                  deriving (Show) | ||||
| 
 | ||||
| instance Eq PostingWithPath where | ||||
|     a == b = pptxnidx a == pptxnidx b | ||||
|           && pppidx a == pppidx b | ||||
| 
 | ||||
| pptxn :: PostingWithPath -> Transaction | ||||
| pptxn = fromJust . ptransaction . ppposting | ||||
| 
 | ||||
| ppamountqty :: PostingWithPath -> Quantity | ||||
| ppamountqty = aquantity . head . amounts . pamount . ppposting | ||||
| 
 | ||||
| allPostingsWithPath :: Journal -> [PostingWithPath] | ||||
| allPostingsWithPath j = do | ||||
|     (txnidx, txn) <- zip [0..] $ jtxns j | ||||
|     (pidx, p) <- zip [0..] $ tpostings txn | ||||
|     return PostingWithPath { ppposting = p, pptxnidx = txnidx, pppidx = pidx } | ||||
| 
 | ||||
| binBy :: Ord b => (a -> b) -> [a] -> [[a]] | ||||
| binBy f = groupBy ((==) `on` f) . sortBy (comparing f) | ||||
| 
 | ||||
| combine :: ([a], [b]) -> [Either a b] | ||||
| combine (ls, rs) = map Left ls ++ map Right rs | ||||
| 
 | ||||
| combinedBinBy :: Ord b => (a -> b) -> ([a], [a]) -> [([a], [a])] | ||||
| combinedBinBy f = map partitionEithers . binBy (either f f) . combine | ||||
| 
 | ||||
| greedyMaxMatching :: (Eq a, Eq b) => [(a,b)] -> [(a,b)] | ||||
| greedyMaxMatching = greedyMaxMatching' [] | ||||
| 
 | ||||
| greedyMaxMatching' :: (Eq a, Eq b) => [Either a b] -> [(a,b)] -> [(a,b)] | ||||
| greedyMaxMatching' alreadyUsed ((l,r):rest) | ||||
|   | Left l `elem` alreadyUsed || Right r `elem` alreadyUsed | ||||
|       = greedyMaxMatching' alreadyUsed rest | ||||
|   | otherwise = (l,r) : greedyMaxMatching' (Left l : Right r : alreadyUsed) rest | ||||
| greedyMaxMatching' _ [] = [] | ||||
| 
 | ||||
| dateCloseness :: (PostingWithPath, PostingWithPath) -> Integer | ||||
| dateCloseness = negate . uncurry (diffDays `on` tdate.pptxn) | ||||
| 
 | ||||
| type Matching = [(PostingWithPath, PostingWithPath)] | ||||
| 
 | ||||
| matching :: [PostingWithPath] -> [PostingWithPath] -> Matching | ||||
| matching ppl ppr = do | ||||
|     (left, right) <- combinedBinBy ppamountqty (ppl, ppr) -- TODO: probably not a correct choice of bins | ||||
|     greedyMaxMatching $ sortBy (comparing dateCloseness) [ (l,r) | l <- left, r <- right ] | ||||
| 
 | ||||
| readJournalFile' :: FilePath -> IO Journal | ||||
| readJournalFile' fn = | ||||
|     readJournalFile definputopts {ignore_assertions_ = True} fn >>= either error' return | ||||
| 
 | ||||
| matchingPostings :: AccountName -> Journal -> [PostingWithPath] | ||||
| matchingPostings acct j = filter ((== acct) . paccount . ppposting) $ allPostingsWithPath j | ||||
| 
 | ||||
| pickSide :: Side -> (a,a) -> a | ||||
| pickSide L (l,_) = l | ||||
| pickSide R (_,r) = r | ||||
| 
 | ||||
| unmatchedtxns :: Side -> [PostingWithPath] -> Matching -> [Transaction] | ||||
| unmatchedtxns s pp m = | ||||
|     map pptxn $ nubBy ((==) `on` pptxnidx) $ pp \\ map (pickSide s) m | ||||
| 
 | ||||
| -- | The diff command. | ||||
| diff :: CliOpts -> Journal -> IO () | ||||
| diff CliOpts{file_=[f1, f2], reportopts_=ReportOpts{query_=acctName}} _ = do | ||||
|   j1 <- readJournalFile' f1 | ||||
|   j2 <- readJournalFile' f2 | ||||
| 
 | ||||
|   let acct = T.pack acctName | ||||
|   let pp1 = matchingPostings acct j1 | ||||
|   let pp2 = matchingPostings acct j2 | ||||
| 
 | ||||
|   let m = matching pp1 pp2 | ||||
| 
 | ||||
|   let unmatchedtxn1 = unmatchedtxns L pp1 m | ||||
|   let unmatchedtxn2 = unmatchedtxns R pp2 m | ||||
| 
 | ||||
|   putStrLn "Unmatched transactions in the first journal:\n" | ||||
|   mapM_ (putStr . showTransaction) unmatchedtxn1 | ||||
| 
 | ||||
|   putStrLn "Unmatched transactions in the second journal:\n" | ||||
|   mapM_ (putStr . showTransaction) unmatchedtxn2 | ||||
| 
 | ||||
| diff _ _ = do | ||||
|   putStrLn "Specifiy exactly two journal files" | ||||
|   exitFailure | ||||
							
								
								
									
										35
									
								
								hledger/Hledger/Cli/Commands/Diff.md
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										35
									
								
								hledger/Hledger/Cli/Commands/Diff.md
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,35 @@ | ||||
| diff\ | ||||
| Compares two journal files.  It looks at the transactions of a single | ||||
| account and prints out the transactions which are in one journal file but not | ||||
| in the other. | ||||
| 
 | ||||
| This is particularly useful for reconciling existing journals with bank | ||||
| statements.  Many banks provide a way to export the transactions between two | ||||
| given dates, which can be converted to ledger files using custom scripts or | ||||
| read directly as CSV files.  With the diff command you can make sure that these | ||||
| transactions from bank match up exactly with the transactions in your ledger | ||||
| file, and that the resulting balance is correct.  (One possible concrete | ||||
| workflow is to have one ledger file per year and export the transactions for | ||||
| the current year, starting on January 1.) | ||||
| 
 | ||||
| This command compares the postings of a single account (which needs to have the | ||||
| same name in both files), and only checks the amount of the postings (not the | ||||
| name or the date of the transactions).  Postings are compared (instead of | ||||
| transactions) so that you can combine multiple transactions from the bank | ||||
| statement in a single transaction in the ledger file. | ||||
| 
 | ||||
| _FLAGS_ | ||||
| 
 | ||||
| Examples: | ||||
| 
 | ||||
| ```shell | ||||
| $ hledger diff assets:bank:giro -f 2014.journal -f bank.journal | ||||
| Unmatched transactions in the first journal: | ||||
| 
 | ||||
| 2014/01/01 Opening Balances | ||||
|     assets:bank:giro              EUR ... | ||||
|     ... | ||||
|     equity:opening balances       EUR -... | ||||
| 
 | ||||
| Unmatched transactions in the second journal: | ||||
| ``` | ||||
							
								
								
									
										35
									
								
								hledger/Hledger/Cli/Commands/Diff.txt
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										35
									
								
								hledger/Hledger/Cli/Commands/Diff.txt
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,35 @@ | ||||
| diff | ||||
| Compares two journal files. It looks at the transactions of a single | ||||
| account and prints out the transactions which are in one journal file | ||||
| but not in the other. | ||||
| 
 | ||||
| This is particularly useful for reconciling existing journals with bank | ||||
| statements. Many banks provide a way to export the transactions between | ||||
| two given dates, which can be converted to ledger files using custom | ||||
| scripts or read directly as CSV files. With the diff command you can | ||||
| make sure that these transactions from bank match up exactly with the | ||||
| transactions in your ledger file, and that the resulting balance is | ||||
| correct. (One possible concrete workflow is to have one ledger file per | ||||
| year and export the transactions for the current year, starting on | ||||
| January 1.) | ||||
| 
 | ||||
| This command compares the postings of a single account (which needs to | ||||
| have the same name in both files), and only checks the amount of the | ||||
| postings (not the name or the date of the transactions). Postings are | ||||
| compared (instead of transactions) so that you can combine multiple | ||||
| transactions from the bank statement in a single transaction in the | ||||
| ledger file. | ||||
| 
 | ||||
| _FLAGS_ | ||||
| 
 | ||||
| Examples: | ||||
| 
 | ||||
| $ hledger diff assets:bank:giro -f 2014.journal -f bank.journal | ||||
| Unmatched transactions in the first journal: | ||||
| 
 | ||||
| 2014/01/01 Opening Balances | ||||
|     assets:bank:giro              EUR ... | ||||
|     ... | ||||
|     equity:opening balances       EUR -... | ||||
| 
 | ||||
| Unmatched transactions in the second journal: | ||||
| @ -4,7 +4,7 @@ cabal-version: 1.12 | ||||
| -- | ||||
| -- see: https://github.com/sol/hpack | ||||
| -- | ||||
| -- hash: 0682613dd00c2d6d52d5a9079bb63755cc25a0a09be9c996f55a0c0ad60fbafa | ||||
| -- hash: c936fb07d9099bcceeb59ad6e75b91aae6928718a53608affb3d9e7b6c4fe89d | ||||
| 
 | ||||
| name:           hledger | ||||
| version:        1.14.1 | ||||
| @ -72,6 +72,7 @@ extra-source-files: | ||||
|     Hledger/Cli/Commands/Checkdupes.txt | ||||
|     Hledger/Cli/Commands/Close.txt | ||||
|     Hledger/Cli/Commands/Commodities.txt | ||||
|     Hledger/Cli/Commands/Diff.txt | ||||
|     Hledger/Cli/Commands/Files.txt | ||||
|     Hledger/Cli/Commands/Help.txt | ||||
|     Hledger/Cli/Commands/Import.txt | ||||
| @ -121,6 +122,7 @@ library | ||||
|       Hledger.Cli.Commands.Checkdupes | ||||
|       Hledger.Cli.Commands.Close | ||||
|       Hledger.Cli.Commands.Commodities | ||||
|       Hledger.Cli.Commands.Diff | ||||
|       Hledger.Cli.Commands.Help | ||||
|       Hledger.Cli.Commands.Files | ||||
|       Hledger.Cli.Commands.Import | ||||
|  | ||||
| @ -65,6 +65,7 @@ extra-source-files: | ||||
| - Hledger/Cli/Commands/Checkdupes.txt | ||||
| - Hledger/Cli/Commands/Close.txt | ||||
| - Hledger/Cli/Commands/Commodities.txt | ||||
| - Hledger/Cli/Commands/Diff.txt | ||||
| - Hledger/Cli/Commands/Files.txt | ||||
| - Hledger/Cli/Commands/Help.txt | ||||
| - Hledger/Cli/Commands/Import.txt | ||||
| @ -165,6 +166,7 @@ library: | ||||
|   - Hledger.Cli.Commands.Checkdupes | ||||
|   - Hledger.Cli.Commands.Close | ||||
|   - Hledger.Cli.Commands.Commodities | ||||
|   - Hledger.Cli.Commands.Diff | ||||
|   - Hledger.Cli.Commands.Help | ||||
|   - Hledger.Cli.Commands.Files | ||||
|   - Hledger.Cli.Commands.Import | ||||
|  | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user