cli: make check-dupes a builtin command

This commit is contained in:
Simon Michael 2017-09-12 19:09:00 -07:00
parent 44e3d72926
commit fe9cd2a186
7 changed files with 57 additions and 64 deletions

View File

@ -1,59 +0,0 @@
#!/usr/bin/env stack
{- stack runghc --verbosity info
--package hledger-lib
--package hledger
--package here
--package text
-}
{-# OPTIONS_GHC -Wno-missing-signatures -Wno-name-shadowing #-}
{-# LANGUAGE QuasiQuotes #-}
import Hledger
import Hledger.Cli
import Text.Printf (printf)
-- import System.Environment (getArgs)
import Data.List
import Data.Function
import Data.String.Here
import qualified Data.Text as T
------------------------------------------------------------------------------
cmdmode = hledgerCommandMode
[here| check-dupes
Reports duplicates in the account tree: account names having the same leaf
but different prefixes. In other words, two or more leaves that are
categorized differently.
Reads the default journal file, or another specified as an argument.
http://stefanorodighiero.net/software/hledger-dupes.html
|]
[]
[generalflagsgroup1]
[]
([], Nothing)
------------------------------------------------------------------------------
main = do
opts <- getHledgerCliOpts cmdmode
withJournalDo opts $ \CliOpts{rawopts_=_opts,reportopts_=_ropts} j -> do
mapM_ render $ checkdupes $ accountsNames j
accountsNames :: Journal -> [(String, AccountName)]
accountsNames j = map leafAndAccountName as
where leafAndAccountName a = (T.unpack $ accountLeafName a, a)
ps = journalPostings j
as = nub $ sort $ map paccount ps
checkdupes :: (Ord k, Eq k) => [(k, v)] -> [(k, [v])]
checkdupes l = zip dupLeafs dupAccountNames
where dupLeafs = map (fst . head) d
dupAccountNames = map (map snd) d
d = dupes' l
dupes' = filter ((> 1) . length)
. groupBy ((==) `on` fst)
. sortBy (compare `on` fst)
render :: (String, [AccountName]) -> IO ()
render (leafName, accountNameL) = printf "%s as %s\n" leafName (concat $ intersperse ", " (map T.unpack accountNameL))

View File

@ -19,6 +19,7 @@ module Hledger.Cli.Commands (
,module Hledger.Cli.Commands.Balancesheetequity ,module Hledger.Cli.Commands.Balancesheetequity
,module Hledger.Cli.Commands.Cashflow ,module Hledger.Cli.Commands.Cashflow
,module Hledger.Cli.Commands.Checkdates ,module Hledger.Cli.Commands.Checkdates
,module Hledger.Cli.Commands.Checkdupes
,module Hledger.Cli.Commands.Help ,module Hledger.Cli.Commands.Help
,module Hledger.Cli.Commands.Incomestatement ,module Hledger.Cli.Commands.Incomestatement
,module Hledger.Cli.Commands.Print ,module Hledger.Cli.Commands.Print
@ -49,6 +50,7 @@ import Hledger.Cli.Commands.Balancesheet
import Hledger.Cli.Commands.Balancesheetequity import Hledger.Cli.Commands.Balancesheetequity
import Hledger.Cli.Commands.Cashflow import Hledger.Cli.Commands.Cashflow
import Hledger.Cli.Commands.Checkdates import Hledger.Cli.Commands.Checkdates
import Hledger.Cli.Commands.Checkdupes
import Hledger.Cli.Commands.Help import Hledger.Cli.Commands.Help
import Hledger.Cli.Commands.Incomestatement import Hledger.Cli.Commands.Incomestatement
import Hledger.Cli.Commands.Print import Hledger.Cli.Commands.Print

View File

@ -0,0 +1,49 @@
{-# LANGUAGE QuasiQuotes #-}
module Hledger.Cli.Commands.Checkdupes (
checkdupesmode
,checkdupes
)
where
import Data.Function
import Data.List
import Data.String.Here
import qualified Data.Text as T
import Hledger
import Hledger.Cli.CliOptions
import System.Console.CmdArgs.Explicit
import Text.Printf
checkdupesmode :: Mode RawOpts
checkdupesmode = hledgerCommandMode
[here| check-dupes
Reports account names having the same leaf but different prefixes.
In other words, two or more leaves that are categorized differently.
Reads the default journal file, or another specified as an argument.
An example: http://stefanorodighiero.net/software/hledger-dupes.html
|]
[]
[generalflagsgroup1]
[]
([], Nothing)
checkdupes _opts j = mapM_ render $ checkdupes' $ accountsNames j
accountsNames :: Journal -> [(String, AccountName)]
accountsNames j = map leafAndAccountName as
where leafAndAccountName a = (T.unpack $ accountLeafName a, a)
ps = journalPostings j
as = nub $ sort $ map paccount ps
checkdupes' :: (Ord k, Eq k) => [(k, v)] -> [(k, [v])]
checkdupes' l = zip dupLeafs dupAccountNames
where dupLeafs = map (fst . head) d
dupAccountNames = map (map snd) d
d = dupes' l
dupes' = filter ((> 1) . length)
. groupBy ((==) `on` fst)
. sortBy (compare `on` fst)
render :: (String, [AccountName]) -> IO ()
render (leafName, accountNameL) = printf "%s as %s\n" leafName (concat $ intersperse ", " (map T.unpack accountNameL))

View File

@ -89,11 +89,6 @@ is an old pie chart generator, in need of some love.
[hledger-check.hs](https://github.com/simonmichael/hledger/blob/master/bin/hledger-check.hs) [hledger-check.hs](https://github.com/simonmichael/hledger/blob/master/bin/hledger-check.hs)
checks more powerful account balance assertions. checks more powerful account balance assertions.
### check-dupes
[hledger-check-dupes.hs](https://github.com/simonmichael/hledger/blob/master/bin/hledger-check-dupes.hs#L21)
checks for account names sharing the same leaf name.
### equity ### equity
[hledger-equity.hs](https://github.com/simonmichael/hledger/blob/master/bin/hledger-equity.hs#L17) [hledger-equity.hs](https://github.com/simonmichael/hledger/blob/master/bin/hledger-equity.hs#L17)

View File

@ -345,6 +345,10 @@ you can alter the report mode with `--change`/`--cumulative`/`--historical`.
Check that transactions are sorted by increasing date. Check that transactions are sorted by increasing date.
With a query, only matched transactions' dates are checked. With a query, only matched transactions' dates are checked.
## check-dupes
Reports account names having the same leaf but different prefixes.
An example: http://stefanorodighiero.net/software/hledger-dupes.html
## help ## help
Show any of the hledger manuals. Show any of the hledger manuals.

View File

@ -130,6 +130,7 @@ library
Hledger.Cli.Commands.Balancesheetequity Hledger.Cli.Commands.Balancesheetequity
Hledger.Cli.Commands.Cashflow Hledger.Cli.Commands.Cashflow
Hledger.Cli.Commands.Checkdates Hledger.Cli.Commands.Checkdates
Hledger.Cli.Commands.Checkdupes
Hledger.Cli.Commands.Help Hledger.Cli.Commands.Help
Hledger.Cli.Commands.Incomestatement Hledger.Cli.Commands.Incomestatement
Hledger.Cli.Commands.Print Hledger.Cli.Commands.Print

View File

@ -111,6 +111,7 @@ library:
- Hledger.Cli.Commands.Balancesheetequity - Hledger.Cli.Commands.Balancesheetequity
- Hledger.Cli.Commands.Cashflow - Hledger.Cli.Commands.Cashflow
- Hledger.Cli.Commands.Checkdates - Hledger.Cli.Commands.Checkdates
- Hledger.Cli.Commands.Checkdupes
- Hledger.Cli.Commands.Help - Hledger.Cli.Commands.Help
- Hledger.Cli.Commands.Incomestatement - Hledger.Cli.Commands.Incomestatement
- Hledger.Cli.Commands.Print - Hledger.Cli.Commands.Print