check: uniqueleafnames: fancy error message like the others
This commit is contained in:
parent
e82e1db464
commit
b96713a584
@ -1,4 +1,5 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
module Hledger.Cli.Commands.Check.Uniqueleafnames (
|
module Hledger.Cli.Commands.Check.Uniqueleafnames (
|
||||||
@ -15,30 +16,43 @@ import Data.Semigroup ((<>))
|
|||||||
#endif
|
#endif
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import Hledger
|
import Hledger
|
||||||
|
import Text.Printf (printf)
|
||||||
|
|
||||||
|
-- | Check that all the journal's postings are to accounts with a unique leaf name.
|
||||||
|
-- Otherwise, return an error message for the first offending posting.
|
||||||
journalCheckUniqueleafnames :: Journal -> Either String ()
|
journalCheckUniqueleafnames :: Journal -> Either String ()
|
||||||
journalCheckUniqueleafnames j = do
|
journalCheckUniqueleafnames j = do
|
||||||
let dupes = checkdupes' $ accountsNames j
|
-- find all duplicate leafnames, and the full account names they appear in
|
||||||
if null dupes
|
let dupes = finddupes $ journalLeafAndFullAccountNames j
|
||||||
then Right ()
|
-- report the first posting that references one of them (and its position), for now
|
||||||
else Left . T.unpack $
|
sequence_ $ map (checkposting dupes) $ journalPostings j
|
||||||
-- XXX make output more like Checkdates.hs, Check.hs etc.
|
|
||||||
foldMap render dupes
|
|
||||||
where
|
|
||||||
render (leafName, accountNameL) =
|
|
||||||
leafName <> " as " <> T.intercalate ", " accountNameL
|
|
||||||
|
|
||||||
checkdupes' :: (Ord k, Eq k) => [(k, v)] -> [(k, [v])]
|
finddupes :: (Ord leaf, Eq full) => [(leaf, full)] -> [(leaf, [full])]
|
||||||
checkdupes' l = zip dupLeafs dupAccountNames
|
finddupes leafandfullnames = zip dupLeafs dupAccountNames
|
||||||
where dupLeafs = map (fst . head) d
|
where dupLeafs = map (fst . head) d
|
||||||
dupAccountNames = map (map snd) d
|
dupAccountNames = map (map snd) d
|
||||||
d = dupes' l
|
d = dupes' leafandfullnames
|
||||||
dupes' = filter ((> 1) . length)
|
dupes' = filter ((> 1) . length)
|
||||||
. groupBy ((==) `on` fst)
|
. groupBy ((==) `on` fst)
|
||||||
. sortBy (compare `on` fst)
|
. sortBy (compare `on` fst)
|
||||||
|
|
||||||
accountsNames :: Journal -> [(Text, AccountName)]
|
journalLeafAndFullAccountNames :: Journal -> [(Text, AccountName)]
|
||||||
accountsNames j = map leafAndAccountName as
|
journalLeafAndFullAccountNames j = map leafAndAccountName as
|
||||||
where leafAndAccountName a = (accountLeafName a, a)
|
where leafAndAccountName a = (accountLeafName a, a)
|
||||||
ps = journalPostings j
|
ps = journalPostings j
|
||||||
as = nubSort $ map paccount ps
|
as = nubSort $ map paccount ps
|
||||||
|
|
||||||
|
checkposting :: [(Text,[AccountName])] -> Posting -> Either String ()
|
||||||
|
checkposting leafandfullnames Posting{paccount,ptransaction} =
|
||||||
|
case [lf | lf@(_,fs) <- leafandfullnames, paccount `elem` fs] of
|
||||||
|
[] -> Right ()
|
||||||
|
(leaf,fulls):_ -> Left $ printf
|
||||||
|
"account leaf names are not unique\nleaf name \"%s\" appears in account names: %s%s"
|
||||||
|
leaf
|
||||||
|
(T.intercalate ", " $ map (("\""<>).(<>"\"")) fulls)
|
||||||
|
(case ptransaction of
|
||||||
|
Nothing -> ""
|
||||||
|
Just t -> printf "\nseen in \"%s\" in transaction at: %s\n\n%s"
|
||||||
|
paccount
|
||||||
|
(showGenericSourcePos $ tsourcepos t)
|
||||||
|
(linesPrepend "> " . (<>"\n") . textChomp $ showTransaction t) :: String)
|
||||||
|
|||||||
@ -11,11 +11,5 @@ $ hledger -f- check uniqueleafnames
|
|||||||
(a) 1
|
(a) 1
|
||||||
(b:a) 1
|
(b:a) 1
|
||||||
$ hledger -f- check uniqueleafnames
|
$ hledger -f- check uniqueleafnames
|
||||||
>2 /a as a, b:a/
|
>2 /account leaf names are not unique/
|
||||||
>=1
|
>=1
|
||||||
# XXX
|
|
||||||
# improve message
|
|
||||||
# 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>
|
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user