lib: Account, AccountName: hlint
This commit is contained in:
parent
6d94eed6fd
commit
b231d99e38
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE RecordWildCards, StandaloneDeriving, OverloadedStrings #-}
|
||||
{-# LANGUAGE RecordWildCards, OverloadedStrings #-}
|
||||
{-|
|
||||
|
||||
|
||||
@ -93,7 +93,7 @@ tieAccountParents = tie Nothing
|
||||
|
||||
-- | Look up an account's numeric code, if any, from the Journal and set it.
|
||||
accountSetCodeFrom :: Journal -> Account -> Account
|
||||
accountSetCodeFrom j a = a{acode=fromMaybe Nothing $ (lookup (aname a) $ jaccounts j)}
|
||||
accountSetCodeFrom j a = a{acode=fromMaybe Nothing $ lookup (aname a) (jaccounts j)}
|
||||
|
||||
-- | Get this account's parent accounts, from the nearest up to the root.
|
||||
parentAccounts :: Account -> [Account]
|
||||
@ -200,7 +200,7 @@ sortAccountTreeByAmount :: NormalSign -> Account -> Account
|
||||
sortAccountTreeByAmount normalsign a
|
||||
| null $ asubs a = a
|
||||
| otherwise = a{asubs=
|
||||
sortBy (maybeflip $ comparing aibalance) $
|
||||
sortBy (maybeflip $ comparing aibalance) $
|
||||
map (sortAccountTreeByAmount normalsign) $ asubs a}
|
||||
where
|
||||
maybeflip | normalsign==NormallyNegative = id
|
||||
|
||||
@ -43,7 +43,7 @@ accountLeafName = last . accountNameComponents
|
||||
accountSummarisedName :: AccountName -> Text
|
||||
accountSummarisedName a
|
||||
-- length cs > 1 = take 2 (head cs) ++ ":" ++ a'
|
||||
| length cs > 1 = (T.intercalate ":" (map (T.take 2) $ init cs)) <> ":" <> a'
|
||||
| length cs > 1 = T.intercalate ":" (map (T.take 2) $ init cs) <> ":" <> a'
|
||||
| otherwise = a'
|
||||
where
|
||||
cs = accountNameComponents a
|
||||
@ -125,11 +125,11 @@ elideAccountName width s
|
||||
| " (split)" `T.isSuffixOf` s =
|
||||
let
|
||||
names = T.splitOn ", " $ T.take (T.length s - 8) s
|
||||
widthpername = (max 0 (width - 8 - 2 * (max 1 (length names) - 1))) `div` length names
|
||||
widthpername = max 0 (width - 8 - 2 * (max 1 (length names) - 1)) `div` length names
|
||||
in
|
||||
fitText Nothing (Just width) True False $
|
||||
(<>" (split)") $
|
||||
T.intercalate ", " $
|
||||
T.intercalate ", "
|
||||
[accountNameFromComponents $ elideparts widthpername [] $ accountNameComponents s' | s' <- names]
|
||||
| otherwise =
|
||||
fitText Nothing (Just width) True False $ accountNameFromComponents $ elideparts width [] $ accountNameComponents s
|
||||
@ -174,7 +174,7 @@ accountRegexToAccountName = T.pack . regexReplace "^\\^(.*?)\\(:\\|\\$\\)$" "\\1
|
||||
|
||||
-- | Does this string look like an exact account-matching regular expression ?
|
||||
isAccountRegex :: String -> Bool
|
||||
isAccountRegex s = take 1 s == "^" && (take 5 $ reverse s) == ")$|:("
|
||||
isAccountRegex s = take 1 s == "^" && take 5 (reverse s) == ")$|:("
|
||||
|
||||
tests_Hledger_Data_AccountName = TestList
|
||||
[
|
||||
|
||||
Loading…
Reference in New Issue
Block a user