attoparsec parser for POSIXTime

(Not yet used anywhere.)

Benchmarking

{-# LANGUAGE OverloadedStrings #-}

import Criterion.Main
import Utility.TimeStamp
import Data.Attoparsec.ByteString

main = defaultMain
	[ bgroup "parse"
		[ bench "new" $ whnf (parseOnly (parserPOSIXTime <* endOfInput)) "1431286201.113452s"
		, bench "old" $ whnf parsePOSIXTime "1431286201.113452s"
		]
	]

benchmarking parse/new
time                 643.6 ns   (640.2 ns .. 646.7 ns)
                     1.000 R²   (0.999 R² .. 1.000 R²)
mean                 645.3 ns   (642.1 ns .. 650.9 ns)
std dev              14.59 ns   (9.194 ns .. 22.07 ns)
variance introduced by outliers: 29% (moderately inflated)

benchmarking parse/old
time                 9.657 μs   (9.600 μs .. 9.732 μs)
                     1.000 R²   (0.999 R² .. 1.000 R²)
mean                 9.703 μs   (9.645 μs .. 9.785 μs)
std dev              231.6 ns   (161.5 ns .. 323.7 ns)
variance introduced by outliers: 25% (moderately inflated)

So old took 9703 ns to parse, and new 643 ns.
This commit is contained in:
Joey Hess 2019-01-02 12:26:07 -04:00
parent ba2c0663f9
commit 3c74dcd4e1
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38

View file

@ -1,6 +1,6 @@
{- timestamp parsing and formatting
-
- Copyright 2015-2016 Joey Hess <id@joeyh.name>
- Copyright 2015-2019 Joey Hess <id@joeyh.name>
-
- License: BSD-2-clause
-}
@ -15,10 +15,32 @@ import Utility.Misc
import Data.Time.Clock.POSIX
import Data.Time
import Data.Ratio
import Control.Applicative
import qualified Data.ByteString as B
import qualified Data.Attoparsec.ByteString as A
import Data.Attoparsec.ByteString.Char8 (char, decimal, signed, isDigit_w8)
#if ! MIN_VERSION_time(1,5,0)
import System.Locale
#endif
{- Parses how POSIXTime shows itself: "1431286201.113452s"
- (The "s" is included for historical reasons and is optional.)
- Also handles the format with no decimal seconds. -}
parserPOSIXTime :: A.Parser POSIXTime
parserPOSIXTime = mkPOSIXTime
<$> signed decimal
<*> (declen <|> pure (0, 0))
<* optional (char 's')
where
declen :: A.Parser (Integer, Int)
declen = do
_ <- char '.'
b <- A.takeWhile isDigit_w8
let len = B.length b
d <- either fail pure $
A.parseOnly (decimal <* A.endOfInput) b
return (d, len)
{- Parses how POSIXTime shows itself: "1431286201.113452s"
- Also handles the format with no fractional seconds. -}
parsePOSIXTime :: String -> Maybe POSIXTime
@ -27,19 +49,26 @@ parsePOSIXTime = uncurry parsePOSIXTime' . separate (== '.')
{- Parses the integral and decimal part of a POSIXTime -}
parsePOSIXTime' :: String -> String -> Maybe POSIXTime
parsePOSIXTime' sn sd = do
n <- fromIntegral <$> readi sn
n <- readi sn
let sd' = takeWhile (/= 's') sd
if null sd'
then return n
then return (fromIntegral n)
else do
d <- readi sd'
let r = d % (10 ^ (length sd'))
return $ if n < 0
then n - fromRational r
else n + fromRational r
return $ mkPOSIXTime n (d, length sd')
where
readi :: String -> Maybe Integer
readi = readish
{- This implementation allows for higher precision in a POSIXTime than
- supported by the system's Double, and avoids the complications of
- floating point. -}
mkPOSIXTime :: Integer -> (Integer, Int) -> POSIXTime
mkPOSIXTime n (d, dlen)
| n < 0 = fromIntegral n - fromRational r
| otherwise = fromIntegral n + fromRational r
where
r = d % (10 ^ dlen)
formatPOSIXTime :: String -> POSIXTime -> String
formatPOSIXTime fmt t = formatTime defaultTimeLocale fmt (posixSecondsToUTCTime t)