Use nubSort instead of nub . sort.
This commit is contained in:
		
							parent
							
								
									390cea7f7c
								
							
						
					
					
						commit
						74778efcf5
					
				| @ -41,6 +41,7 @@ module Hledger.Data.AccountName ( | ||||
| where | ||||
| 
 | ||||
| import Data.List | ||||
| import Data.List.Extra (nubSort) | ||||
| #if !(MIN_VERSION_base(4,11,0)) | ||||
| import Data.Monoid | ||||
| #endif | ||||
| @ -110,7 +111,7 @@ accountNameDrop n a | ||||
| -- ie these plus all their parent accounts up to the root. | ||||
| -- Eg: ["a:b:c","d:e"] -> ["a","a:b","a:b:c","d","d:e"] | ||||
| expandAccountNames :: [AccountName] -> [AccountName] | ||||
| expandAccountNames as = nub $ sort $ concatMap expandAccountName as | ||||
| expandAccountNames as = nubSort $ concatMap expandAccountName as | ||||
| 
 | ||||
| -- | "a:b:c" -> ["a","a:b","a:b:c"] | ||||
| expandAccountName :: AccountName -> [AccountName] | ||||
|  | ||||
| @ -95,7 +95,7 @@ import Data.Function ((&)) | ||||
| import Data.Functor.Identity (Identity(..)) | ||||
| import qualified Data.HashTable.ST.Cuckoo as H | ||||
| import Data.List | ||||
| import Data.List.Extra (groupSort) | ||||
| import Data.List.Extra (groupSort, nubSort) | ||||
| import qualified Data.Map as M | ||||
| import Data.Maybe | ||||
| #if !(MIN_VERSION_base(4,11,0)) | ||||
| @ -258,7 +258,7 @@ journalPrevTransaction j t = journalTransactionAt j (tindex t - 1) | ||||
| 
 | ||||
| -- | Unique transaction descriptions used in this journal. | ||||
| journalDescriptions :: Journal -> [Text] | ||||
| journalDescriptions = nub . sort . map tdescription . jtxns | ||||
| journalDescriptions = nubSort . map tdescription . jtxns | ||||
| 
 | ||||
| -- | All postings from this journal's transactions, in order. | ||||
| journalPostings :: Journal -> [Posting] | ||||
| @ -275,17 +275,17 @@ journalAccountNamesImplied = expandAccountNames . journalAccountNamesUsed | ||||
| 
 | ||||
| -- | Sorted unique account names declared by account directives in this journal. | ||||
| journalAccountNamesDeclared :: Journal -> [AccountName] | ||||
| journalAccountNamesDeclared = nub . sort . map fst . jdeclaredaccounts | ||||
| journalAccountNamesDeclared = nubSort . map fst . jdeclaredaccounts | ||||
| 
 | ||||
| -- | Sorted unique account names declared by account directives or posted to | ||||
| -- by transactions in this journal. | ||||
| journalAccountNamesDeclaredOrUsed :: Journal -> [AccountName] | ||||
| journalAccountNamesDeclaredOrUsed j = nub $ sort $ journalAccountNamesDeclared j ++ journalAccountNamesUsed j | ||||
| journalAccountNamesDeclaredOrUsed j = nubSort $ journalAccountNamesDeclared j ++ journalAccountNamesUsed j | ||||
| 
 | ||||
| -- | Sorted unique account names declared by account directives, or posted to | ||||
| -- or implied as parents by transactions in this journal. | ||||
| journalAccountNamesDeclaredOrImplied :: Journal -> [AccountName] | ||||
| journalAccountNamesDeclaredOrImplied j = nub $ sort $ journalAccountNamesDeclared j ++ journalAccountNamesImplied j | ||||
| journalAccountNamesDeclaredOrImplied j = nubSort $ journalAccountNamesDeclared j ++ journalAccountNamesImplied j | ||||
| 
 | ||||
| -- | Convenience/compatibility alias for journalAccountNamesDeclaredOrImplied. | ||||
| journalAccountNames :: Journal -> [AccountName] | ||||
|  | ||||
| @ -69,7 +69,7 @@ module Hledger.Data.Posting ( | ||||
| where | ||||
| 
 | ||||
| import Data.Foldable (asum) | ||||
| import Data.List | ||||
| import Data.List.Extra (nubSort) | ||||
| import qualified Data.Map as M | ||||
| import Data.Maybe | ||||
| import Data.MemoUgly (memo) | ||||
| @ -190,7 +190,7 @@ hasBalanceAssignment p = not (hasAmount p) && isJust (pbalanceassertion p) | ||||
| 
 | ||||
| -- | Sorted unique account names referenced by these postings. | ||||
| accountNamesFromPostings :: [Posting] -> [AccountName] | ||||
| accountNamesFromPostings = nub . sort . map paccount | ||||
| accountNamesFromPostings = nubSort . map paccount | ||||
| 
 | ||||
| sumPostings :: [Posting] -> MixedAmount | ||||
| sumPostings = sumStrict . map pamount | ||||
|  | ||||
| @ -11,6 +11,7 @@ where | ||||
| 
 | ||||
| import Data.Decimal | ||||
| import Data.List | ||||
| import Data.List.Extra (nubSort) | ||||
| import Data.Maybe | ||||
| #if !(MIN_VERSION_base(4,11,0)) | ||||
| import Data.Monoid ((<>)) | ||||
| @ -202,7 +203,7 @@ combineBudgetAndActual | ||||
|   (MultiBalanceReport (budgetperiods, budgetrows, (budgettots, budgetgrandtot, budgetgrandavg))) | ||||
|   (MultiBalanceReport (actualperiods, actualrows, (actualtots, actualgrandtot, actualgrandavg))) = | ||||
|   let | ||||
|     periods = nub $ sort $ filter (/= nulldatespan) $ budgetperiods ++ actualperiods | ||||
|     periods = nubSort $ filter (/= nulldatespan) $ budgetperiods ++ actualperiods | ||||
| 
 | ||||
|     -- first, combine any corresponding budget goals with actual changes | ||||
|     rows1 = | ||||
|  | ||||
| @ -24,6 +24,7 @@ where | ||||
| import GHC.Generics (Generic) | ||||
| import Control.DeepSeq (NFData) | ||||
| import Data.List | ||||
| import Data.List.Extra (nubSort) | ||||
| import qualified Data.Map as M | ||||
| import Data.Maybe | ||||
| import Data.Ord | ||||
| @ -235,7 +236,7 @@ multiBalanceReportWith ropts@ReportOpts{..} q j priceoracle = | ||||
|           (if tree_ ropts then expandAccountNames else id) $ | ||||
|           nub $ map (clipOrEllipsifyAccountName depth) $ | ||||
|           if empty_ || balancetype_ == HistoricalBalance | ||||
|           then nub $ sort $ startaccts ++ allpostedaccts | ||||
|           then nubSort $ startaccts ++ allpostedaccts | ||||
|           else allpostedaccts | ||||
|         where | ||||
|           allpostedaccts :: [AccountName] = | ||||
|  | ||||
| @ -23,8 +23,8 @@ module Hledger.Reports.PostingsReport ( | ||||
| where | ||||
| 
 | ||||
| import Data.List | ||||
| import Data.List.Extra (nubSort) | ||||
| import Data.Maybe | ||||
| import Data.Ord (comparing) | ||||
| -- import Data.Text (Text) | ||||
| import qualified Data.Text as T | ||||
| import Data.Time.Calendar | ||||
| @ -166,7 +166,7 @@ matchedPostingsBeforeAndDuring opts q j (DateSpan mstart mend) = | ||||
|   where | ||||
|     beforestartq = dbg1 "beforestartq" $ dateqtype $ DateSpan Nothing mstart | ||||
|     beforeandduringps = | ||||
|       dbg1 "ps5" $ sortBy (comparing sortdate) $                               -- sort postings by date or date2 | ||||
|       dbg1 "ps5" $ sortOn sortdate $                                           -- sort postings by date or date2 | ||||
|       dbg1 "ps4" $ (if invert_ opts then map negatePostingAmount else id) $    -- with --invert, invert amounts | ||||
|       dbg1 "ps3" $ map (filterPostingAmount symq) $                            -- remove amount parts which the query's cur: terms would exclude | ||||
|       dbg1 "ps2" $ (if related_ opts then concatMap relatedPostings else id) $ -- with -r, replace each with its sibling postings | ||||
| @ -254,7 +254,7 @@ summarisePostingsInDateSpan (DateSpan b e) wd depth showempty ps | ||||
|       summaryps | depth > 0 = [summaryp{paccount=a,pamount=balance a} | a <- clippedanames] | ||||
|                 | otherwise = [summaryp{paccount="...",pamount=sum $ map pamount ps}] | ||||
|       summarypes = map (, e') $ (if showempty then id else filter (not . isZeroMixedAmount . pamount)) summaryps | ||||
|       anames = sort $ nub $ map paccount ps | ||||
|       anames = nubSort $ map paccount ps | ||||
|       -- aggregate balances by account, like ledgerFromJournal, then do depth-clipping | ||||
|       accts = accountsFromPostings ps | ||||
|       balance a = maybe nullmixedamt bal $ lookupAccount a accts | ||||
|  | ||||
| @ -46,7 +46,7 @@ where | ||||
| 
 | ||||
| import Control.Applicative ((<|>)) | ||||
| import Data.Data (Data) | ||||
| import Data.List | ||||
| import Data.List.Extra (nubSort) | ||||
| import Data.Maybe | ||||
| import qualified Data.Text as T | ||||
| import Data.Typeable (Typeable) | ||||
| @ -337,7 +337,7 @@ simplifyStatuses l | ||||
|   | length l' >= numstatuses = [] | ||||
|   | otherwise                = l' | ||||
|   where | ||||
|     l' = nub $ sort l | ||||
|     l' = nubSort l | ||||
|     numstatuses = length [minBound .. maxBound :: Status] | ||||
| 
 | ||||
| -- | Add/remove this status from the status list. Used by hledger-ui. | ||||
|  | ||||
| @ -22,6 +22,7 @@ module Hledger.Reports.TransactionsReport ( | ||||
| where | ||||
| 
 | ||||
| import Data.List | ||||
| import Data.List.Extra (nubSort) | ||||
| import Data.Ord | ||||
| 
 | ||||
| import Hledger.Data | ||||
| @ -79,7 +80,7 @@ transactionsReportByCommodity tr = | ||||
|   [(c, filterTransactionsReportByCommodity c tr) | c <- transactionsReportCommodities tr] | ||||
|   where | ||||
|     transactionsReportCommodities (_,items) = | ||||
|       nub $ sort $ map acommodity $ concatMap (amounts . triAmount) items | ||||
|       nubSort . map acommodity $ concatMap (amounts . triAmount) items | ||||
| 
 | ||||
| -- Remove transaction report items and item amount (and running | ||||
| -- balance amount) components that don't involve the specified | ||||
|  | ||||
| @ -21,6 +21,7 @@ import Data.Default (def) | ||||
| #endif | ||||
| -- import Data.Monoid              -- | ||||
| import Data.List | ||||
| import Data.List.Extra (nubSort) | ||||
| import Data.Maybe | ||||
| -- import Data.Text (Text) | ||||
| import qualified Data.Text as T | ||||
| @ -205,7 +206,7 @@ runBrickUi uopts@UIOpts{cliopts_=copts@CliOpts{inputopts_=_iopts,reportopts_=rop | ||||
|       withManager $ \mgr -> do | ||||
|         dbg1IO "fsnotify using polling ?" $ isPollingManager mgr | ||||
|         files <- mapM (canonicalizePath . fst) $ jfiles j | ||||
|         let directories = nub $ sort $ map takeDirectory files | ||||
|         let directories = nubSort $ map takeDirectory files | ||||
|         dbg1IO "files" files | ||||
|         dbg1IO "directories to watch" directories | ||||
| 
 | ||||
|  | ||||
| @ -74,6 +74,7 @@ executable hledger-ui | ||||
|     , containers | ||||
|     , data-default | ||||
|     , directory | ||||
|     , extra >=1.6.3 | ||||
|     , filepath | ||||
|     , fsnotify >=0.2.1.2 && <0.4 | ||||
|     , hledger >=1.16.1 && <1.17 | ||||
|  | ||||
| @ -50,6 +50,7 @@ dependencies: | ||||
| - containers | ||||
| - data-default | ||||
| - directory | ||||
| - extra >=1.6.3 | ||||
| - filepath | ||||
| - fsnotify >=0.2.1.2 && <0.4 | ||||
| - microlens >=0.4 | ||||
|  | ||||
| @ -13,7 +13,8 @@ module Hledger.Web.Widget.AddForm | ||||
| 
 | ||||
| import Control.Monad.State.Strict (evalStateT) | ||||
| import Data.Bifunctor (first) | ||||
| import Data.List (dropWhileEnd, intercalate, nub, sort, unfoldr) | ||||
| import Data.List (dropWhileEnd, intercalate, unfoldr) | ||||
| import Data.List.Extra (nubSort) | ||||
| import Data.Maybe (isJust) | ||||
| #if !(MIN_VERSION_base(4,13,0)) | ||||
| import Data.Semigroup ((<>)) | ||||
| @ -71,7 +72,7 @@ addForm j today = identifyForm "add" $ \extra -> do | ||||
|   let (postRes, displayRows) = validatePostings acctRes amtRes | ||||
| 
 | ||||
|   -- bindings used in add-form.hamlet | ||||
|   let descriptions = sort $ nub $ tdescription <$> jtxns j | ||||
|   let descriptions = nubSort $ tdescription <$> jtxns j | ||||
|       journals = fst <$> jfiles j | ||||
| 
 | ||||
|   pure (validateTransaction dateRes descRes postRes, $(widgetFile "add-form")) | ||||
|  | ||||
| @ -166,6 +166,7 @@ library | ||||
|     , containers | ||||
|     , data-default | ||||
|     , directory | ||||
|     , extra >=1.6.3 | ||||
|     , filepath | ||||
|     , hjsmin | ||||
|     , hledger >=1.16.1 && <1.17 | ||||
|  | ||||
| @ -112,6 +112,7 @@ library: | ||||
|   - data-default | ||||
|   - Decimal | ||||
|   - directory | ||||
|   - extra >=1.6.3 | ||||
|   - filepath | ||||
|   - hjsmin | ||||
|   - http-conduit | ||||
|  | ||||
| @ -75,6 +75,7 @@ import Data.Char | ||||
| import Data.Default | ||||
| import Data.Functor.Identity (Identity) | ||||
| import "base-compat-batteries" Data.List.Compat | ||||
| import Data.List.Extra (nubSort) | ||||
| import Data.List.Split (splitOneOf) | ||||
| import Data.Ord | ||||
| import Data.Maybe | ||||
| @ -661,7 +662,7 @@ likelyExecutablesInPath :: IO [String] | ||||
| likelyExecutablesInPath = do | ||||
|   pathdirs <- splitOneOf "[:;]" `fmap` getEnvSafe "PATH" | ||||
|   pathfiles <- concat `fmap` mapM getDirectoryContentsSafe pathdirs | ||||
|   return $ nub $ sort pathfiles | ||||
|   return $ nubSort pathfiles | ||||
|   -- exclude directories and files without execute permission. | ||||
|   -- These will do a stat for each hledger-*, probably ok. | ||||
|   -- But they need paths, not just filenames | ||||
|  | ||||
| @ -8,6 +8,7 @@ where | ||||
| 
 | ||||
| import Data.Function | ||||
| import Data.List | ||||
| import Data.List.Extra (nubSort) | ||||
| import qualified Data.Text as T | ||||
| import Hledger | ||||
| import Hledger.Cli.CliOptions | ||||
| @ -28,7 +29,7 @@ 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 | ||||
|         as = nubSort $ map paccount ps | ||||
| 
 | ||||
| checkdupes' :: (Ord k, Eq k) => [(k, v)] -> [(k, [v])] | ||||
| checkdupes' l = zip dupLeafs dupAccountNames | ||||
|  | ||||
| @ -13,7 +13,7 @@ module Hledger.Cli.Commands.Commodities ( | ||||
| ) where | ||||
| 
 | ||||
| import Control.Monad | ||||
| import Data.List | ||||
| import Data.List.Extra (nubSort) | ||||
| import qualified Data.Map as M | ||||
| import qualified Data.Text.IO as T | ||||
| 
 | ||||
| @ -32,5 +32,5 @@ commoditiesmode = hledgerCommandMode | ||||
| commodities :: CliOpts -> Journal -> IO () | ||||
| commodities _copts j = do | ||||
|   let cs = filter (/= "AUTO") $ | ||||
|            nub $ sort $ M.keys (jcommodities j) ++ M.keys (jinferredcommodities j) | ||||
|            nubSort $ M.keys (jcommodities j) ++ M.keys (jinferredcommodities j) | ||||
|   forM_ cs T.putStrLn | ||||
|  | ||||
| @ -14,7 +14,7 @@ module Hledger.Cli.Commands.Descriptions ( | ||||
|  ,descriptions | ||||
| ) where | ||||
| 
 | ||||
| import Data.List | ||||
| import Data.List.Extra (nubSort) | ||||
| import qualified Data.Text.IO as T | ||||
| 
 | ||||
| import Hledger | ||||
| @ -35,6 +35,6 @@ descriptions CliOpts{reportopts_=ropts} j = do | ||||
|   d <- getCurrentDay | ||||
|   let q  = queryFromOpts d ropts | ||||
|       ts = entriesReport ropts q j | ||||
|       descriptions = nub $ sort $ map tdescription ts | ||||
|       descriptions = nubSort $ map tdescription ts | ||||
| 
 | ||||
|   mapM_ T.putStrLn descriptions | ||||
|  | ||||
| @ -15,7 +15,7 @@ module Hledger.Cli.Commands.Notes ( | ||||
|  ,notes | ||||
| ) where | ||||
| 
 | ||||
| import Data.List | ||||
| import Data.List.Extra (nubSort) | ||||
| import qualified Data.Text.IO as T | ||||
| 
 | ||||
| import Hledger | ||||
| @ -36,6 +36,6 @@ notes CliOpts{reportopts_=ropts} j = do | ||||
|   d <- getCurrentDay | ||||
|   let q  = queryFromOpts d ropts | ||||
|       ts = entriesReport ropts q j | ||||
|       notes = nub $ sort $ map transactionNote ts | ||||
|       notes = nubSort $ map transactionNote ts | ||||
| 
 | ||||
|   mapM_ T.putStrLn notes | ||||
|  | ||||
| @ -15,7 +15,7 @@ module Hledger.Cli.Commands.Payees ( | ||||
|  ,payees | ||||
| ) where | ||||
| 
 | ||||
| import Data.List | ||||
| import Data.List.Extra (nubSort) | ||||
| import qualified Data.Text.IO as T | ||||
| 
 | ||||
| import Hledger | ||||
| @ -36,6 +36,6 @@ payees CliOpts{reportopts_=ropts} j = do | ||||
|   d <- getCurrentDay | ||||
|   let q  = queryFromOpts d ropts | ||||
|       ts = entriesReport ropts q j | ||||
|       payees = nub $ sort $ map transactionPayee ts | ||||
|       payees = nubSort $ map transactionPayee ts | ||||
| 
 | ||||
|   mapM_ T.putStrLn payees | ||||
|  | ||||
| @ -6,7 +6,7 @@ module Hledger.Cli.Commands.Printunique ( | ||||
| ) | ||||
| where | ||||
| 
 | ||||
| import Data.List | ||||
| import Data.List.Extra (nubSortOn) | ||||
| import Hledger | ||||
| import Hledger.Cli.CliOptions | ||||
| import Hledger.Cli.Commands.Print | ||||
| @ -21,6 +21,6 @@ printuniquemode = hledgerCommandMode | ||||
| printunique opts j@Journal{jtxns=ts} = do | ||||
|   print' opts j{jtxns=uniquify ts} | ||||
|   where | ||||
|     uniquify = nubBy (\t1 t2 -> thingToCompare t1 == thingToCompare t2) . sortOn thingToCompare | ||||
|     uniquify = nubSortOn thingToCompare | ||||
|     thingToCompare = tdescription | ||||
|     -- thingToCompare = tdate | ||||
|  | ||||
| @ -14,6 +14,7 @@ module Hledger.Cli.Commands.Stats ( | ||||
| where | ||||
| 
 | ||||
| import Data.List | ||||
| import Data.List.Extra (nubSort) | ||||
| import Data.Maybe | ||||
| import Data.Ord | ||||
| import Data.HashSet (size, fromList) | ||||
| @ -108,4 +109,4 @@ showLedgerStats l today span = | ||||
|              acctdepth | null as = 0 | ||||
|                        | otherwise = maximum $ map accountNameLevel as | ||||
|              mktprices = jpricedirectives j | ||||
|              mktpricecommodities = nub $ sort $ map pdcommodity mktprices | ||||
|              mktpricecommodities = nubSort $ map pdcommodity mktprices | ||||
|  | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user