git-annex/Utility/TimeStamp.hs
Joey Hess 3ba6e9bb96
use attoparsec parser for String parsing, 10x speedup
This is not as efficient as using ByteStrings throughout, but converting
the String to ByteString is actually significantly faster than the old
parser.

    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)

    benchmarking parse/new
    time                 834.6 ns   (797.1 ns .. 886.9 ns)
                         0.987 R²   (0.976 R² .. 0.999 R²)
    mean                 816.4 ns   (802.7 ns .. 845.1 ns)
    std dev              62.39 ns   (37.66 ns .. 108.4 ns)
    variance introduced by outliers: 82% (severely inflated)

There is a small behavior change from the old parsePOSIXTime,
which accepted any amount of trailing whitespace after the timestamp.
That behavior was not documented, and it doesn't seem anything relied on it.
2019-01-02 13:28:44 -04:00

59 lines
1.7 KiB
Haskell

{- timestamp parsing and formatting
-
- Copyright 2015-2019 Joey Hess <id@joeyh.name>
-
- License: BSD-2-clause
-}
{-# LANGUAGE CPP #-}
module Utility.TimeStamp where
import Utility.Data
import Data.Time.Clock.POSIX
import Data.Time
import Data.Ratio
import Control.Applicative
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
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)
parsePOSIXTime :: String -> Maybe POSIXTime
parsePOSIXTime s = eitherToMaybe $
A.parseOnly (parserPOSIXTime <* A.endOfInput) (B8.pack s)
{- 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)