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>>
168 lines
5.3 KiB
Haskell
168 lines
5.3 KiB
Haskell
{-|
|
|
|
|
Standard imports and utilities which are useful everywhere, or needed low
|
|
in the module hierarchy. This is the bottom of hledger's module graph.
|
|
|
|
-}
|
|
|
|
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 Test.HUnit,
|
|
-- module Text.Printf,
|
|
---- all of this one:
|
|
module Hledger.Utils,
|
|
module Hledger.Utils.Debug,
|
|
module Hledger.Utils.Parse,
|
|
module Hledger.Utils.Regex,
|
|
module Hledger.Utils.String,
|
|
module Hledger.Utils.Text,
|
|
module Hledger.Utils.Test,
|
|
module Hledger.Utils.Tree,
|
|
-- Debug.Trace.trace,
|
|
-- module Data.PPrint,
|
|
-- module Hledger.Utils.UTF8IOCompat
|
|
SystemString,fromSystemString,toSystemString,error',userError',
|
|
-- the rest need to be done in each module I think
|
|
)
|
|
where
|
|
import Control.Monad (liftM)
|
|
-- import Data.Char
|
|
-- import Data.List
|
|
-- import Data.Maybe
|
|
-- import Data.PPrint
|
|
import Data.Text (Text)
|
|
import qualified Data.Text.IO as T
|
|
import Data.Time.Clock
|
|
import Data.Time.LocalTime
|
|
-- import Data.Text (Text)
|
|
-- import qualified Data.Text as T
|
|
import System.Directory (getHomeDirectory)
|
|
import System.FilePath((</>), isRelative)
|
|
import System.IO
|
|
-- import Text.Printf
|
|
-- import qualified Data.Map as Map
|
|
|
|
import Hledger.Utils.Debug
|
|
import Hledger.Utils.Parse
|
|
import Hledger.Utils.Regex
|
|
import Hledger.Utils.String
|
|
import Hledger.Utils.Text
|
|
import Hledger.Utils.Test
|
|
import Hledger.Utils.Tree
|
|
-- import Prelude hiding (readFile,writeFile,appendFile,getContents,putStr,putStrLn)
|
|
-- import Hledger.Utils.UTF8IOCompat (readFile,writeFile,appendFile,getContents,putStr,putStrLn)
|
|
import Hledger.Utils.UTF8IOCompat (SystemString,fromSystemString,toSystemString,error',userError')
|
|
|
|
|
|
-- 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
|
|
|
|
first6 (x,_,_,_,_,_) = x
|
|
second6 (_,x,_,_,_,_) = x
|
|
third6 (_,_,x,_,_,_) = x
|
|
fourth6 (_,_,_,x,_,_) = x
|
|
fifth6 (_,_,_,_,x,_) = x
|
|
sixth6 (_,_,_,_,_,x) = x
|
|
|
|
-- lists
|
|
|
|
splitAtElement :: Eq a => a -> [a] -> [[a]]
|
|
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
|
|
|
|
-- text
|
|
|
|
-- time
|
|
|
|
getCurrentLocalTime :: IO LocalTime
|
|
getCurrentLocalTime = do
|
|
t <- getCurrentTime
|
|
tz <- getCurrentTimeZone
|
|
return $ utcToLocalTime tz t
|
|
|
|
-- misc
|
|
|
|
isLeft :: Either a b -> Bool
|
|
isLeft (Left _) = True
|
|
isLeft _ = False
|
|
|
|
isRight :: Either a b -> Bool
|
|
isRight = not . isLeft
|
|
|
|
-- | Apply a function the specified number of times. Possibly uses O(n) stack ?
|
|
applyN :: Int -> (a -> a) -> a -> a
|
|
applyN n f = (!! n) . iterate f
|
|
|
|
-- | Convert a possibly relative, possibly tilde-containing file path to an absolute one,
|
|
-- given the current directory. ~username is not supported. Leave "-" unchanged.
|
|
-- Can raise an error.
|
|
expandPath :: FilePath -> FilePath -> IO FilePath -- general type sig for use in reader parsers
|
|
expandPath _ "-" = return "-"
|
|
expandPath curdir p = (if isRelative p then (curdir </>) else id) `liftM` expandPath' p
|
|
where
|
|
expandPath' ('~':'/':p) = (</> p) <$> getHomeDirectory
|
|
expandPath' ('~':'\\':p) = (</> p) <$> getHomeDirectory
|
|
expandPath' ('~':_) = ioError $ userError "~USERNAME in paths is not supported"
|
|
expandPath' p = return p
|
|
|
|
firstJust ms = case dropWhile (==Nothing) ms of
|
|
[] -> Nothing
|
|
(md:_) -> md
|
|
|
|
-- | Read a file in universal newline mode, handling any of the usual line ending conventions.
|
|
readFile' :: FilePath -> IO String
|
|
readFile' name = do
|
|
h <- openFile name ReadMode
|
|
hSetNewlineMode h universalNewlineMode
|
|
hGetContents h
|
|
|
|
-- | Read a file in universal newline mode, handling any of the usual line ending conventions.
|
|
readFileAnyLineEnding :: FilePath -> IO Text
|
|
readFileAnyLineEnding path = do
|
|
h <- openFile path ReadMode
|
|
hSetNewlineMode h universalNewlineMode
|
|
T.hGetContents h
|
|
|
|
-- | Read the given file, or standard input if the path is "-", using
|
|
-- universal newline mode.
|
|
readFileOrStdinAnyLineEnding :: String -> IO Text
|
|
readFileOrStdinAnyLineEnding f = do
|
|
h <- fileHandle f
|
|
hSetNewlineMode h universalNewlineMode
|
|
T.hGetContents h
|
|
where
|
|
fileHandle "-" = return stdin
|
|
fileHandle f = openFile f ReadMode
|
|
|
|
-- | Total version of maximum, for integral types, giving 0 for an empty list.
|
|
maximum' :: Integral a => [a] -> a
|
|
maximum' [] = 0
|
|
maximum' xs = maximum xs
|