2008-10-03 06:04:15 +04:00
|
|
|
|
{-|
|
|
|
|
|
|
2010-05-27 07:58:47 +04:00
|
|
|
|
Standard imports and utilities which are useful everywhere, or needed low
|
|
|
|
|
in the module hierarchy. This is the bottom of hledger's module graph.
|
2008-10-03 06:04:15 +04:00
|
|
|
|
|
|
|
|
|
-}
|
2021-01-29 15:34:18 +03:00
|
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
{-# LANGUAGE LambdaCase #-}
|
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2008-10-03 06:04:15 +04:00
|
|
|
|
|
2011-05-28 08:11:44 +04:00
|
|
|
|
module Hledger.Utils (---- provide these frequently used modules - or not, for clearer api:
|
|
|
|
|
-- module Control.Monad,
|
|
|
|
|
-- module Data.List,
|
|
|
|
|
-- module Data.Maybe,
|
|
|
|
|
-- module Data.Time.Calendar,
|
|
|
|
|
-- module Data.Time.Clock,
|
|
|
|
|
-- module Data.Time.LocalTime,
|
|
|
|
|
-- module Data.Tree,
|
|
|
|
|
-- module Text.RegexPR,
|
|
|
|
|
-- module Text.Printf,
|
|
|
|
|
---- all of this one:
|
2011-08-08 05:34:00 +04:00
|
|
|
|
module Hledger.Utils,
|
2014-10-29 03:21:33 +03:00
|
|
|
|
module Hledger.Utils.Debug,
|
2015-08-19 23:47:26 +03:00
|
|
|
|
module Hledger.Utils.Parse,
|
2014-07-06 21:11:02 +04:00
|
|
|
|
module Hledger.Utils.Regex,
|
2015-08-19 23:47:26 +03:00
|
|
|
|
module Hledger.Utils.String,
|
lib: textification begins! account names
The first of several conversions from String to (strict) Text, hopefully
reducing space and time usage.
This one shows a small improvement, with GHC 7.10.3 and text-1.2.2.1:
hledger -f data/100x100x10.journal stats
string: <<ghc: 39471064 bytes, 77 GCs, 198421/275048 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.015 MUT (0.020 elapsed), 0.010 GC (0.014 elapsed) :ghc>>
text: <<ghc: 39268024 bytes, 77 GCs, 197018/270840 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.002 elapsed), 0.016 MUT (0.022 elapsed), 0.009 GC (0.011 elapsed) :ghc>>
hledger -f data/1000x100x10.journal stats
string: <<ghc: 318555920 bytes, 617 GCs, 2178997/7134472 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.001 elapsed), 0.129 MUT (0.136 elapsed), 0.067 GC (0.077 elapsed) :ghc>>
text: <<ghc: 314248496 bytes, 612 GCs, 2074045/6617960 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.003 elapsed), 0.137 MUT (0.145 elapsed), 0.067 GC (0.079 elapsed) :ghc>>
hledger -f data/10000x100x10.journal stats
string: <<ghc: 3114763608 bytes, 6026 GCs, 18858950/75552024 avg/max bytes residency (11 samples), 201M in use, 0.000 INIT (0.000 elapsed), 1.331 MUT (1.372 elapsed), 0.699 GC (0.812 elapsed) :ghc>>
text: <<ghc: 3071468920 bytes, 5968 GCs, 14120344/62951360 avg/max bytes residency (9 samples), 124M in use, 0.000 INIT (0.003 elapsed), 1.272 MUT (1.349 elapsed), 0.513 GC (0.578 elapsed) :ghc>>
hledger -f data/100000x100x10.journal stats
string: <<ghc: 31186579432 bytes, 60278 GCs, 135332581/740228992 avg/max bytes residency (13 samples), 1697M in use, 0.000 INIT (0.008 elapsed), 14.677 MUT (15.508 elapsed), 7.081 GC (8.074 elapsed) :ghc>>
text: <<ghc: 30753427672 bytes, 59763 GCs, 117595958/666457240 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.008 elapsed), 13.713 MUT (13.966 elapsed), 6.220 GC (7.108 elapsed) :ghc>>
2016-05-24 04:16:21 +03:00
|
|
|
|
module Hledger.Utils.Text,
|
2015-08-19 23:47:26 +03:00
|
|
|
|
module Hledger.Utils.Test,
|
2017-04-26 04:27:25 +03:00
|
|
|
|
module Hledger.Utils.Color,
|
2015-08-19 23:47:26 +03:00
|
|
|
|
module Hledger.Utils.Tree,
|
2014-10-29 03:21:33 +03:00
|
|
|
|
-- Debug.Trace.trace,
|
2014-03-20 03:11:46 +04:00
|
|
|
|
-- module Data.PPrint,
|
2012-03-29 23:06:31 +04:00
|
|
|
|
-- module Hledger.Utils.UTF8IOCompat
|
2019-10-20 01:21:42 +03:00
|
|
|
|
error',userError',usageError,
|
2012-03-29 23:06:31 +04:00
|
|
|
|
-- the rest need to be done in each module I think
|
2011-05-28 08:11:44 +04:00
|
|
|
|
)
|
2007-02-16 12:00:17 +03:00
|
|
|
|
where
|
2018-04-12 20:47:03 +03:00
|
|
|
|
|
2018-01-05 03:29:23 +03:00
|
|
|
|
import Control.Monad (liftM, when)
|
2019-02-03 03:34:10 +03:00
|
|
|
|
import Data.FileEmbed (makeRelativeToProject, embedStringFile)
|
2021-01-29 15:34:18 +03:00
|
|
|
|
import Data.List (foldl', foldl1')
|
2019-02-03 03:34:10 +03:00
|
|
|
|
-- import Data.String.Here (hereFile)
|
lib: textification: parse stream
10% more allocation, but 35% lower maximum residency, and slightly quicker.
hledger -f data/100x100x10.journal stats
<<ghc: 39327768 bytes, 77 GCs, 196834/269496 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.010 elapsed), 0.020 MUT (0.092 elapsed), 0.014 GC (0.119 elapsed) :ghc>>
<<ghc: 42842136 bytes, 84 GCs, 194010/270912 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.009 elapsed), 0.016 MUT (0.029 elapsed), 0.012 GC (0.120 elapsed) :ghc>>
hledger -f data/1000x1000x10.journal stats
<<ghc: 314291440 bytes, 612 GCs, 2070776/6628048 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.000 elapsed), 0.128 MUT (0.144 elapsed), 0.059 GC (0.070 elapsed) :ghc>>
<<ghc: 349558872 bytes, 681 GCs, 1397597/4106384 avg/max bytes residency (7 samples), 11M in use, 0.000 INIT (0.004 elapsed), 0.124 MUT (0.133 elapsed), 0.047 GC (0.053 elapsed) :ghc>>
hledger -f data/10000x1000x10.journal stats
<<ghc: 3070026824 bytes, 5973 GCs, 12698030/62951784 avg/max bytes residency (10 samples), 124M in use, 0.000 INIT (0.002 elapsed), 1.268 MUT (1.354 elapsed), 0.514 GC (0.587 elapsed) :ghc>>
<<ghc: 3424013128 bytes, 6658 GCs, 11405501/41071624 avg/max bytes residency (11 samples), 111M in use, 0.000 INIT (0.001 elapsed), 1.343 MUT (1.406 elapsed), 0.511 GC (0.573 elapsed) :ghc>>
hledger -f data/100000x1000x10.journal stats
<<ghc: 30753387392 bytes, 59811 GCs, 117615462/666703600 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.000 elapsed), 12.068 MUT (12.238 elapsed), 6.015 GC (7.190 elapsed) :ghc>>
<<ghc: 34306530696 bytes, 66727 GCs, 76806196/414629312 avg/max bytes residency (14 samples), 1009M in use, 0.000 INIT (0.010 elapsed), 14.357 MUT (16.370 elapsed), 5.298 GC (6.534 elapsed) :ghc>>
2016-05-25 01:58:23 +03:00
|
|
|
|
import Data.Text (Text)
|
|
|
|
|
import qualified Data.Text.IO as T
|
2021-01-29 15:34:18 +03:00
|
|
|
|
import Data.Time.Clock (getCurrentTime)
|
|
|
|
|
import Data.Time.LocalTime (LocalTime, ZonedTime, getCurrentTimeZone,
|
|
|
|
|
utcToLocalTime, utcToZonedTime)
|
2019-02-03 03:34:10 +03:00
|
|
|
|
-- import Language.Haskell.TH.Quote (QuasiQuoter(..))
|
2019-01-27 02:52:58 +03:00
|
|
|
|
import Language.Haskell.TH.Syntax (Q, Exp)
|
2012-03-24 22:08:11 +04:00
|
|
|
|
import System.Directory (getHomeDirectory)
|
2021-01-29 15:34:18 +03:00
|
|
|
|
import System.FilePath (isRelative, (</>))
|
2013-03-29 22:46:10 +04:00
|
|
|
|
import System.IO
|
2021-01-29 15:34:18 +03:00
|
|
|
|
(Handle, IOMode (..), hGetEncoding, hSetEncoding, hSetNewlineMode,
|
|
|
|
|
openFile, stdin, universalNewlineMode, utf8_bom)
|
2014-07-06 21:11:02 +04:00
|
|
|
|
|
2014-10-29 03:21:33 +03:00
|
|
|
|
import Hledger.Utils.Debug
|
2015-08-19 23:47:26 +03:00
|
|
|
|
import Hledger.Utils.Parse
|
2014-07-06 21:11:02 +04:00
|
|
|
|
import Hledger.Utils.Regex
|
2015-08-19 23:47:26 +03:00
|
|
|
|
import Hledger.Utils.String
|
lib: textification begins! account names
The first of several conversions from String to (strict) Text, hopefully
reducing space and time usage.
This one shows a small improvement, with GHC 7.10.3 and text-1.2.2.1:
hledger -f data/100x100x10.journal stats
string: <<ghc: 39471064 bytes, 77 GCs, 198421/275048 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.015 MUT (0.020 elapsed), 0.010 GC (0.014 elapsed) :ghc>>
text: <<ghc: 39268024 bytes, 77 GCs, 197018/270840 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.002 elapsed), 0.016 MUT (0.022 elapsed), 0.009 GC (0.011 elapsed) :ghc>>
hledger -f data/1000x100x10.journal stats
string: <<ghc: 318555920 bytes, 617 GCs, 2178997/7134472 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.001 elapsed), 0.129 MUT (0.136 elapsed), 0.067 GC (0.077 elapsed) :ghc>>
text: <<ghc: 314248496 bytes, 612 GCs, 2074045/6617960 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.003 elapsed), 0.137 MUT (0.145 elapsed), 0.067 GC (0.079 elapsed) :ghc>>
hledger -f data/10000x100x10.journal stats
string: <<ghc: 3114763608 bytes, 6026 GCs, 18858950/75552024 avg/max bytes residency (11 samples), 201M in use, 0.000 INIT (0.000 elapsed), 1.331 MUT (1.372 elapsed), 0.699 GC (0.812 elapsed) :ghc>>
text: <<ghc: 3071468920 bytes, 5968 GCs, 14120344/62951360 avg/max bytes residency (9 samples), 124M in use, 0.000 INIT (0.003 elapsed), 1.272 MUT (1.349 elapsed), 0.513 GC (0.578 elapsed) :ghc>>
hledger -f data/100000x100x10.journal stats
string: <<ghc: 31186579432 bytes, 60278 GCs, 135332581/740228992 avg/max bytes residency (13 samples), 1697M in use, 0.000 INIT (0.008 elapsed), 14.677 MUT (15.508 elapsed), 7.081 GC (8.074 elapsed) :ghc>>
text: <<ghc: 30753427672 bytes, 59763 GCs, 117595958/666457240 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.008 elapsed), 13.713 MUT (13.966 elapsed), 6.220 GC (7.108 elapsed) :ghc>>
2016-05-24 04:16:21 +03:00
|
|
|
|
import Hledger.Utils.Text
|
2015-08-19 23:47:26 +03:00
|
|
|
|
import Hledger.Utils.Test
|
2017-04-26 04:27:25 +03:00
|
|
|
|
import Hledger.Utils.Color
|
2015-08-19 23:47:26 +03:00
|
|
|
|
import Hledger.Utils.Tree
|
2012-03-29 23:06:31 +04:00
|
|
|
|
-- import Prelude hiding (readFile,writeFile,appendFile,getContents,putStr,putStrLn)
|
|
|
|
|
-- import Hledger.Utils.UTF8IOCompat (readFile,writeFile,appendFile,getContents,putStr,putStrLn)
|
2019-10-20 01:21:42 +03:00
|
|
|
|
import Hledger.Utils.UTF8IOCompat (error',userError',usageError)
|
2008-10-10 11:39:20 +04:00
|
|
|
|
|
2008-12-06 10:15:19 +03:00
|
|
|
|
|
2014-03-26 22:15:04 +04:00
|
|
|
|
-- tuples
|
|
|
|
|
|
|
|
|
|
first3 (x,_,_) = x
|
|
|
|
|
second3 (_,x,_) = x
|
|
|
|
|
third3 (_,_,x) = x
|
|
|
|
|
|
|
|
|
|
first4 (x,_,_,_) = x
|
|
|
|
|
second4 (_,x,_,_) = x
|
|
|
|
|
third4 (_,_,x,_) = x
|
|
|
|
|
fourth4 (_,_,_,x) = x
|
|
|
|
|
|
|
|
|
|
first5 (x,_,_,_,_) = x
|
|
|
|
|
second5 (_,x,_,_,_) = x
|
|
|
|
|
third5 (_,_,x,_,_) = x
|
|
|
|
|
fourth5 (_,_,_,x,_) = x
|
|
|
|
|
fifth5 (_,_,_,_,x) = x
|
|
|
|
|
|
2015-08-23 03:42:19 +03:00
|
|
|
|
first6 (x,_,_,_,_,_) = x
|
|
|
|
|
second6 (_,x,_,_,_,_) = x
|
|
|
|
|
third6 (_,_,x,_,_,_) = x
|
|
|
|
|
fourth6 (_,_,_,x,_,_) = x
|
|
|
|
|
fifth6 (_,_,_,_,x,_) = x
|
|
|
|
|
sixth6 (_,_,_,_,_,x) = x
|
|
|
|
|
|
2019-08-19 04:09:27 +03:00
|
|
|
|
-- currying
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
curry2 :: ((a, b) -> c) -> a -> b -> c
|
|
|
|
|
curry2 f x y = f (x, y)
|
|
|
|
|
|
|
|
|
|
uncurry2 :: (a -> b -> c) -> (a, b) -> c
|
|
|
|
|
uncurry2 f (x, y) = f x y
|
|
|
|
|
|
|
|
|
|
curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d
|
|
|
|
|
curry3 f x y z = f (x, y, z)
|
|
|
|
|
|
|
|
|
|
uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
|
|
|
|
|
uncurry3 f (x, y, z) = f x y z
|
|
|
|
|
|
|
|
|
|
curry4 :: ((a, b, c, d) -> e) -> a -> b -> c -> d -> e
|
|
|
|
|
curry4 f w x y z = f (w, x, y, z)
|
|
|
|
|
|
|
|
|
|
uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e
|
|
|
|
|
uncurry4 f (w, x, y, z) = f w x y z
|
|
|
|
|
|
2007-07-03 03:54:17 +04:00
|
|
|
|
-- lists
|
|
|
|
|
|
2007-02-16 12:00:17 +03:00
|
|
|
|
splitAtElement :: Eq a => a -> [a] -> [[a]]
|
2014-10-25 01:29:34 +04:00
|
|
|
|
splitAtElement x l =
|
|
|
|
|
case l of
|
|
|
|
|
[] -> []
|
|
|
|
|
e:es | e==x -> split es
|
|
|
|
|
es -> split es
|
|
|
|
|
where
|
|
|
|
|
split es = let (first,rest) = break (x==) es
|
|
|
|
|
in first : splitAtElement x rest
|
2007-02-16 12:00:17 +03:00
|
|
|
|
|
lib: textification begins! account names
The first of several conversions from String to (strict) Text, hopefully
reducing space and time usage.
This one shows a small improvement, with GHC 7.10.3 and text-1.2.2.1:
hledger -f data/100x100x10.journal stats
string: <<ghc: 39471064 bytes, 77 GCs, 198421/275048 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.015 MUT (0.020 elapsed), 0.010 GC (0.014 elapsed) :ghc>>
text: <<ghc: 39268024 bytes, 77 GCs, 197018/270840 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.002 elapsed), 0.016 MUT (0.022 elapsed), 0.009 GC (0.011 elapsed) :ghc>>
hledger -f data/1000x100x10.journal stats
string: <<ghc: 318555920 bytes, 617 GCs, 2178997/7134472 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.001 elapsed), 0.129 MUT (0.136 elapsed), 0.067 GC (0.077 elapsed) :ghc>>
text: <<ghc: 314248496 bytes, 612 GCs, 2074045/6617960 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.003 elapsed), 0.137 MUT (0.145 elapsed), 0.067 GC (0.079 elapsed) :ghc>>
hledger -f data/10000x100x10.journal stats
string: <<ghc: 3114763608 bytes, 6026 GCs, 18858950/75552024 avg/max bytes residency (11 samples), 201M in use, 0.000 INIT (0.000 elapsed), 1.331 MUT (1.372 elapsed), 0.699 GC (0.812 elapsed) :ghc>>
text: <<ghc: 3071468920 bytes, 5968 GCs, 14120344/62951360 avg/max bytes residency (9 samples), 124M in use, 0.000 INIT (0.003 elapsed), 1.272 MUT (1.349 elapsed), 0.513 GC (0.578 elapsed) :ghc>>
hledger -f data/100000x100x10.journal stats
string: <<ghc: 31186579432 bytes, 60278 GCs, 135332581/740228992 avg/max bytes residency (13 samples), 1697M in use, 0.000 INIT (0.008 elapsed), 14.677 MUT (15.508 elapsed), 7.081 GC (8.074 elapsed) :ghc>>
text: <<ghc: 30753427672 bytes, 59763 GCs, 117595958/666457240 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.008 elapsed), 13.713 MUT (13.966 elapsed), 6.220 GC (7.108 elapsed) :ghc>>
2016-05-24 04:16:21 +03:00
|
|
|
|
-- text
|
|
|
|
|
|
2009-01-25 09:47:05 +03:00
|
|
|
|
-- time
|
|
|
|
|
|
|
|
|
|
getCurrentLocalTime :: IO LocalTime
|
|
|
|
|
getCurrentLocalTime = do
|
|
|
|
|
t <- getCurrentTime
|
|
|
|
|
tz <- getCurrentTimeZone
|
|
|
|
|
return $ utcToLocalTime tz t
|
2016-10-21 21:47:07 +03:00
|
|
|
|
|
|
|
|
|
getCurrentZonedTime :: IO ZonedTime
|
|
|
|
|
getCurrentZonedTime = do
|
|
|
|
|
t <- getCurrentTime
|
|
|
|
|
tz <- getCurrentTimeZone
|
|
|
|
|
return $ utcToZonedTime tz t
|
2009-04-01 12:55:46 +04:00
|
|
|
|
|
2009-04-08 09:30:26 +04:00
|
|
|
|
-- misc
|
2009-04-01 12:55:46 +04:00
|
|
|
|
|
2018-07-30 13:04:33 +03:00
|
|
|
|
-- | Apply a function the specified number of times,
|
|
|
|
|
-- which should be > 0 (otherwise does nothing).
|
|
|
|
|
-- Possibly uses O(n) stack ?
|
2011-01-14 07:32:08 +03:00
|
|
|
|
applyN :: Int -> (a -> a) -> a -> a
|
2018-07-30 13:04:33 +03:00
|
|
|
|
applyN n f | n < 1 = id
|
|
|
|
|
| otherwise = (!! n) . iterate f
|
2016-12-29 22:23:22 +03:00
|
|
|
|
-- from protolude, compare
|
|
|
|
|
-- applyN :: Int -> (a -> a) -> a -> a
|
|
|
|
|
-- applyN n f = X.foldr (.) identity (X.replicate n f)
|
2012-03-24 22:08:11 +04:00
|
|
|
|
|
2012-05-30 12:36:01 +04:00
|
|
|
|
-- | Convert a possibly relative, possibly tilde-containing file path to an absolute one,
|
2014-09-11 00:07:53 +04:00
|
|
|
|
-- given the current directory. ~username is not supported. Leave "-" unchanged.
|
2016-05-23 10:32:55 +03:00
|
|
|
|
-- Can raise an error.
|
|
|
|
|
expandPath :: FilePath -> FilePath -> IO FilePath -- general type sig for use in reader parsers
|
2012-05-30 12:36:01 +04:00
|
|
|
|
expandPath _ "-" = return "-"
|
2018-10-10 02:12:57 +03:00
|
|
|
|
expandPath curdir p = (if isRelative p then (curdir </>) else id) `liftM` expandHomePath p
|
2020-08-06 02:05:56 +03:00
|
|
|
|
-- PARTIAL:
|
2021-01-29 15:34:18 +03:00
|
|
|
|
|
2018-10-10 02:12:57 +03:00
|
|
|
|
-- | Expand user home path indicated by tilde prefix
|
|
|
|
|
expandHomePath :: FilePath -> IO FilePath
|
|
|
|
|
expandHomePath = \case
|
|
|
|
|
('~':'/':p) -> (</> p) <$> getHomeDirectory
|
|
|
|
|
('~':'\\':p) -> (</> p) <$> getHomeDirectory
|
|
|
|
|
('~':_) -> ioError $ userError "~USERNAME in paths is not supported"
|
|
|
|
|
p -> return p
|
2012-04-16 20:44:41 +04:00
|
|
|
|
|
2019-07-15 13:28:52 +03:00
|
|
|
|
-- | Read text from a file,
|
2020-02-25 01:04:44 +03:00
|
|
|
|
-- converting any \r\n line endings to \n,,
|
2018-01-05 03:29:23 +03:00
|
|
|
|
-- using the system locale's text encoding,
|
2019-07-15 13:28:52 +03:00
|
|
|
|
-- ignoring any utf8 BOM prefix (as seen in paypal's 2018 CSV, eg) if that encoding is utf8.
|
2018-01-05 03:17:25 +03:00
|
|
|
|
readFilePortably :: FilePath -> IO Text
|
|
|
|
|
readFilePortably f = openFile f ReadMode >>= readHandlePortably
|
|
|
|
|
|
2019-07-15 13:28:52 +03:00
|
|
|
|
-- | Like readFilePortably, but read from standard input if the path is "-".
|
2018-01-05 03:17:25 +03:00
|
|
|
|
readFileOrStdinPortably :: String -> IO Text
|
|
|
|
|
readFileOrStdinPortably f = openFileOrStdin f ReadMode >>= readHandlePortably
|
|
|
|
|
where
|
|
|
|
|
openFileOrStdin :: String -> IOMode -> IO Handle
|
|
|
|
|
openFileOrStdin "-" _ = return stdin
|
|
|
|
|
openFileOrStdin f m = openFile f m
|
lib: textification: parse stream
10% more allocation, but 35% lower maximum residency, and slightly quicker.
hledger -f data/100x100x10.journal stats
<<ghc: 39327768 bytes, 77 GCs, 196834/269496 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.010 elapsed), 0.020 MUT (0.092 elapsed), 0.014 GC (0.119 elapsed) :ghc>>
<<ghc: 42842136 bytes, 84 GCs, 194010/270912 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.009 elapsed), 0.016 MUT (0.029 elapsed), 0.012 GC (0.120 elapsed) :ghc>>
hledger -f data/1000x1000x10.journal stats
<<ghc: 314291440 bytes, 612 GCs, 2070776/6628048 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.000 elapsed), 0.128 MUT (0.144 elapsed), 0.059 GC (0.070 elapsed) :ghc>>
<<ghc: 349558872 bytes, 681 GCs, 1397597/4106384 avg/max bytes residency (7 samples), 11M in use, 0.000 INIT (0.004 elapsed), 0.124 MUT (0.133 elapsed), 0.047 GC (0.053 elapsed) :ghc>>
hledger -f data/10000x1000x10.journal stats
<<ghc: 3070026824 bytes, 5973 GCs, 12698030/62951784 avg/max bytes residency (10 samples), 124M in use, 0.000 INIT (0.002 elapsed), 1.268 MUT (1.354 elapsed), 0.514 GC (0.587 elapsed) :ghc>>
<<ghc: 3424013128 bytes, 6658 GCs, 11405501/41071624 avg/max bytes residency (11 samples), 111M in use, 0.000 INIT (0.001 elapsed), 1.343 MUT (1.406 elapsed), 0.511 GC (0.573 elapsed) :ghc>>
hledger -f data/100000x1000x10.journal stats
<<ghc: 30753387392 bytes, 59811 GCs, 117615462/666703600 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.000 elapsed), 12.068 MUT (12.238 elapsed), 6.015 GC (7.190 elapsed) :ghc>>
<<ghc: 34306530696 bytes, 66727 GCs, 76806196/414629312 avg/max bytes residency (14 samples), 1009M in use, 0.000 INIT (0.010 elapsed), 14.357 MUT (16.370 elapsed), 5.298 GC (6.534 elapsed) :ghc>>
2016-05-25 01:58:23 +03:00
|
|
|
|
|
2018-01-05 03:17:25 +03:00
|
|
|
|
readHandlePortably :: Handle -> IO Text
|
|
|
|
|
readHandlePortably h = do
|
lib: textification: parse stream
10% more allocation, but 35% lower maximum residency, and slightly quicker.
hledger -f data/100x100x10.journal stats
<<ghc: 39327768 bytes, 77 GCs, 196834/269496 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.010 elapsed), 0.020 MUT (0.092 elapsed), 0.014 GC (0.119 elapsed) :ghc>>
<<ghc: 42842136 bytes, 84 GCs, 194010/270912 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.009 elapsed), 0.016 MUT (0.029 elapsed), 0.012 GC (0.120 elapsed) :ghc>>
hledger -f data/1000x1000x10.journal stats
<<ghc: 314291440 bytes, 612 GCs, 2070776/6628048 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.000 elapsed), 0.128 MUT (0.144 elapsed), 0.059 GC (0.070 elapsed) :ghc>>
<<ghc: 349558872 bytes, 681 GCs, 1397597/4106384 avg/max bytes residency (7 samples), 11M in use, 0.000 INIT (0.004 elapsed), 0.124 MUT (0.133 elapsed), 0.047 GC (0.053 elapsed) :ghc>>
hledger -f data/10000x1000x10.journal stats
<<ghc: 3070026824 bytes, 5973 GCs, 12698030/62951784 avg/max bytes residency (10 samples), 124M in use, 0.000 INIT (0.002 elapsed), 1.268 MUT (1.354 elapsed), 0.514 GC (0.587 elapsed) :ghc>>
<<ghc: 3424013128 bytes, 6658 GCs, 11405501/41071624 avg/max bytes residency (11 samples), 111M in use, 0.000 INIT (0.001 elapsed), 1.343 MUT (1.406 elapsed), 0.511 GC (0.573 elapsed) :ghc>>
hledger -f data/100000x1000x10.journal stats
<<ghc: 30753387392 bytes, 59811 GCs, 117615462/666703600 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.000 elapsed), 12.068 MUT (12.238 elapsed), 6.015 GC (7.190 elapsed) :ghc>>
<<ghc: 34306530696 bytes, 66727 GCs, 76806196/414629312 avg/max bytes residency (14 samples), 1009M in use, 0.000 INIT (0.010 elapsed), 14.357 MUT (16.370 elapsed), 5.298 GC (6.534 elapsed) :ghc>>
2016-05-25 01:58:23 +03:00
|
|
|
|
hSetNewlineMode h universalNewlineMode
|
2018-01-05 03:29:23 +03:00
|
|
|
|
menc <- hGetEncoding h
|
|
|
|
|
when (fmap show menc == Just "UTF-8") $ -- XXX no Eq instance, rely on Show
|
|
|
|
|
hSetEncoding h utf8_bom
|
lib: textification: parse stream
10% more allocation, but 35% lower maximum residency, and slightly quicker.
hledger -f data/100x100x10.journal stats
<<ghc: 39327768 bytes, 77 GCs, 196834/269496 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.010 elapsed), 0.020 MUT (0.092 elapsed), 0.014 GC (0.119 elapsed) :ghc>>
<<ghc: 42842136 bytes, 84 GCs, 194010/270912 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.009 elapsed), 0.016 MUT (0.029 elapsed), 0.012 GC (0.120 elapsed) :ghc>>
hledger -f data/1000x1000x10.journal stats
<<ghc: 314291440 bytes, 612 GCs, 2070776/6628048 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.000 elapsed), 0.128 MUT (0.144 elapsed), 0.059 GC (0.070 elapsed) :ghc>>
<<ghc: 349558872 bytes, 681 GCs, 1397597/4106384 avg/max bytes residency (7 samples), 11M in use, 0.000 INIT (0.004 elapsed), 0.124 MUT (0.133 elapsed), 0.047 GC (0.053 elapsed) :ghc>>
hledger -f data/10000x1000x10.journal stats
<<ghc: 3070026824 bytes, 5973 GCs, 12698030/62951784 avg/max bytes residency (10 samples), 124M in use, 0.000 INIT (0.002 elapsed), 1.268 MUT (1.354 elapsed), 0.514 GC (0.587 elapsed) :ghc>>
<<ghc: 3424013128 bytes, 6658 GCs, 11405501/41071624 avg/max bytes residency (11 samples), 111M in use, 0.000 INIT (0.001 elapsed), 1.343 MUT (1.406 elapsed), 0.511 GC (0.573 elapsed) :ghc>>
hledger -f data/100000x1000x10.journal stats
<<ghc: 30753387392 bytes, 59811 GCs, 117615462/666703600 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.000 elapsed), 12.068 MUT (12.238 elapsed), 6.015 GC (7.190 elapsed) :ghc>>
<<ghc: 34306530696 bytes, 66727 GCs, 76806196/414629312 avg/max bytes residency (14 samples), 1009M in use, 0.000 INIT (0.010 elapsed), 14.357 MUT (16.370 elapsed), 5.298 GC (6.534 elapsed) :ghc>>
2016-05-25 01:58:23 +03:00
|
|
|
|
T.hGetContents h
|
|
|
|
|
|
2015-08-20 06:28:24 +03:00
|
|
|
|
-- | Total version of maximum, for integral types, giving 0 for an empty list.
|
|
|
|
|
maximum' :: Integral a => [a] -> a
|
|
|
|
|
maximum' [] = 0
|
2017-01-13 03:24:53 +03:00
|
|
|
|
maximum' xs = maximumStrict xs
|
|
|
|
|
|
|
|
|
|
-- | Strict version of sum that doesn’t leak space
|
|
|
|
|
{-# INLINABLE sumStrict #-}
|
|
|
|
|
sumStrict :: Num a => [a] -> a
|
|
|
|
|
sumStrict = foldl' (+) 0
|
|
|
|
|
|
|
|
|
|
-- | Strict version of maximum that doesn’t leak space
|
|
|
|
|
{-# INLINABLE maximumStrict #-}
|
|
|
|
|
maximumStrict :: Ord a => [a] -> a
|
|
|
|
|
maximumStrict = foldl1' max
|
|
|
|
|
|
|
|
|
|
-- | Strict version of minimum that doesn’t leak space
|
|
|
|
|
{-# INLINABLE minimumStrict #-}
|
|
|
|
|
minimumStrict :: Ord a => [a] -> a
|
|
|
|
|
minimumStrict = foldl1' min
|
|
|
|
|
|
|
|
|
|
-- | This is a version of sequence based on difference lists. It is
|
|
|
|
|
-- slightly faster but we mostly use it because it uses the heap
|
|
|
|
|
-- instead of the stack. This has the advantage that Neil Mitchell’s
|
|
|
|
|
-- trick of limiting the stack size to discover space leaks doesn’t
|
|
|
|
|
-- show this as a false positive.
|
|
|
|
|
{-# INLINABLE sequence' #-}
|
|
|
|
|
sequence' :: Monad f => [f a] -> f [a]
|
|
|
|
|
sequence' ms = do
|
|
|
|
|
h <- go id ms
|
|
|
|
|
return (h [])
|
|
|
|
|
where
|
|
|
|
|
go h [] = return h
|
|
|
|
|
go h (m:ms) = do
|
|
|
|
|
x <- m
|
|
|
|
|
go (h . (x :)) ms
|
|
|
|
|
|
2019-02-17 02:57:29 +03:00
|
|
|
|
-- | Like mapM but uses sequence'.
|
2017-01-13 03:24:53 +03:00
|
|
|
|
{-# INLINABLE mapM' #-}
|
|
|
|
|
mapM' :: Monad f => (a -> f b) -> [a] -> f [b]
|
|
|
|
|
mapM' f = sequence' . map f
|
2018-04-12 20:47:03 +03:00
|
|
|
|
|
2019-01-27 02:52:58 +03:00
|
|
|
|
-- | Like embedFile, but takes a path relative to the package directory.
|
|
|
|
|
-- Similar to embedFileRelative ?
|
2019-02-03 03:34:10 +03:00
|
|
|
|
embedFileRelative :: FilePath -> Q Exp
|
|
|
|
|
embedFileRelative f = makeRelativeToProject f >>= embedStringFile
|
|
|
|
|
|
|
|
|
|
-- -- | Like hereFile, but takes a path relative to the package directory.
|
|
|
|
|
-- -- Similar to embedFileRelative ?
|
|
|
|
|
-- hereFileRelative :: FilePath -> Q Exp
|
|
|
|
|
-- hereFileRelative f = makeRelativeToProject f >>= hereFileExp
|
|
|
|
|
-- where
|
|
|
|
|
-- QuasiQuoter{quoteExp=hereFileExp} = hereFile
|
2019-07-15 13:28:52 +03:00
|
|
|
|
|
2018-09-06 23:08:26 +03:00
|
|
|
|
tests_Utils = tests "Utils" [
|
|
|
|
|
tests_Text
|
2018-09-04 01:54:29 +03:00
|
|
|
|
]
|