hledger/hledger-lib/Hledger/Utils/Parse.hs
Simon Michael c89c33b36e 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-24 19:00:57 -07:00

48 lines
1.4 KiB
Haskell

{-# LANGUAGE FlexibleContexts #-}
module Hledger.Utils.Parse where
import Data.Char
import Data.List
-- import Data.Text (Text)
-- import qualified Data.Text as T
import Text.Parsec
import Text.Printf
import Hledger.Utils.UTF8IOCompat (error')
-- | Backtracking choice, use this when alternatives share a prefix.
-- Consumes no input if all choices fail.
choice' :: Stream s m t => [ParsecT s u m a] -> ParsecT s u m a
choice' = choice . map Text.Parsec.try
parsewith :: Parsec [Char] () a -> String -> Either ParseError a
parsewith p = runParser p () ""
parseWithState :: Stream s m t => u -> ParsecT s u m a -> s -> m (Either ParseError a)
parseWithState jps p = runParserT p jps ""
fromparse :: Either ParseError a -> a
fromparse = either parseerror id
parseerror :: ParseError -> a
parseerror e = error' $ showParseError e
showParseError :: ParseError -> String
showParseError e = "parse error at " ++ show e
showDateParseError :: ParseError -> String
showDateParseError e = printf "date parse error (%s)" (intercalate ", " $ tail $ lines $ show e)
nonspace :: (Stream s m Char) => ParsecT s st m Char
nonspace = satisfy (not . isSpace)
spacenonewline :: (Stream s m Char) => ParsecT s st m Char
spacenonewline = satisfy (`elem` " \v\f\t")
restofline :: (Stream s m Char) => ParsecT s st m String
restofline = anyChar `manyTill` newline
eolof :: (Stream s m Char) => ParsecT s st m ()
eolof = (newline >> return ()) <|> eof