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>>
		
			
				
	
	
		
			148 lines
		
	
	
		
			4.6 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
			
		
		
	
	
			148 lines
		
	
	
		
			4.6 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.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 whatever newline convention it may contain.
 | |
| readFile' :: FilePath -> IO String
 | |
| readFile' name =  do
 | |
|   h <- openFile name ReadMode
 | |
|   hSetNewlineMode h universalNewlineMode
 | |
|   hGetContents h
 | |
| 
 | |
| -- | Total version of maximum, for integral types, giving 0 for an empty list.
 | |
| maximum' :: Integral a => [a] -> a
 | |
| maximum' [] = 0
 | |
| maximum' xs = maximum xs
 |