diff --git a/Data/Aeson/Internal/Time.hs b/Data/Aeson/Internal/Time.hs index 714609006..462d7a8f6 100644 --- a/Data/Aeson/Internal/Time.hs +++ b/Data/Aeson/Internal/Time.hs @@ -17,45 +17,4 @@ module Data.Aeson.Internal.Time , toTimeOfDay64 ) where -import Prelude () -import Prelude.Compat - -import Data.Int (Int64) -import Data.Time -import Unsafe.Coerce (unsafeCoerce) - -#if MIN_VERSION_base(4,7,0) - -import Data.Fixed (Pico, Fixed(MkFixed)) - -toPico :: Integer -> Pico -toPico = MkFixed - -fromPico :: Pico -> Integer -fromPico (MkFixed i) = i - -#else - -import Data.Fixed (Pico) - -toPico :: Integer -> Pico -toPico = unsafeCoerce - -fromPico :: Pico -> Integer -fromPico = unsafeCoerce - -#endif - --- | Like TimeOfDay, but using a fixed-width integer for seconds. -data TimeOfDay64 = TOD {-# UNPACK #-} !Int - {-# UNPACK #-} !Int - {-# UNPACK #-} !Int64 - -diffTimeOfDay64 :: DiffTime -> TimeOfDay64 -diffTimeOfDay64 t = TOD (fromIntegral h) (fromIntegral m) s - where (h,mp) = fromIntegral pico `quotRem` 3600000000000000 - (m,s) = mp `quotRem` 60000000000000 - pico = unsafeCoerce t :: Integer - -toTimeOfDay64 :: TimeOfDay -> TimeOfDay64 -toTimeOfDay64 (TimeOfDay h m s) = TOD h m (fromIntegral (fromPico s)) +import Data.Attoparsec.Time.Internal diff --git a/Data/Aeson/Parser/Time.hs b/Data/Aeson/Parser/Time.hs index 800bab60b..dd6e0a5b7 100644 --- a/Data/Aeson/Parser/Time.hs +++ b/Data/Aeson/Parser/Time.hs @@ -1,16 +1,3 @@ -{-# LANGUAGE BangPatterns #-} -{-# LANGUAGE ScopedTypeVariables #-} - --- | --- Module: Data.Aeson.Parser.Time --- Copyright: (c) 2015-2016 Bryan O'Sullivan --- License: BSD3 --- Maintainer: Bryan O'Sullivan --- Stability: experimental --- Portability: portable --- --- Parsers for parsing dates and times. - module Data.Aeson.Parser.Time ( run @@ -25,120 +12,49 @@ module Data.Aeson.Parser.Time import Prelude () import Prelude.Compat -import Control.Applicative ((<|>)) -import Control.Monad (void, when) -import Data.Aeson.Internal.Time (toPico) -import Data.Attoparsec.Text as A -import Data.Bits ((.&.)) -import Data.Char (isDigit, ord) -import Data.Fixed (Pico) -import Data.Int (Int64) -import Data.Maybe (fromMaybe) +import Data.Attoparsec.Text (Parser) import Data.Text (Text) -import Data.Time.Calendar (Day, fromGregorianValid) +import Data.Time.Calendar (Day) import Data.Time.Clock (UTCTime(..)) import qualified Data.Aeson.Types.Internal as Aeson -import qualified Data.Text as T +import qualified Data.Attoparsec.Text as A +import qualified Data.Attoparsec.Time as T import qualified Data.Time.LocalTime as Local -- | Run an attoparsec parser as an aeson parser. run :: Parser a -> Text -> Aeson.Parser a -run p t = case A.parseOnly (p <* endOfInput) t of +run p t = case A.parseOnly (p <* A.endOfInput) t of Left err -> fail $ "could not parse date: " ++ err Right r -> return r -- | Parse a date of the form @[+,-]YYYY-MM-DD@. day :: Parser Day -day = do - absOrNeg <- negate <$ char '-' <|> id <$ char '+' <|> pure id - y <- decimal <* char '-' - m <- twoDigits <* char '-' - d <- twoDigits - maybe (fail "invalid date") return (fromGregorianValid (absOrNeg y) m d) - --- | Parse a two-digit integer (e.g. day of month, hour). -twoDigits :: Parser Int -twoDigits = do - a <- digit - b <- digit - let c2d c = ord c .&. 15 - return $! c2d a * 10 + c2d b +day = T.day +{-# INLINE day #-} -- | Parse a time of the form @HH:MM[:SS[.SSS]]@. timeOfDay :: Parser Local.TimeOfDay -timeOfDay = do - h <- twoDigits - m <- char ':' *> twoDigits - s <- option 0 (char ':' *> seconds) - if h < 24 && m < 60 && s < 61 - then return (Local.TimeOfDay h m s) - else fail "invalid time" - -data T = T {-# UNPACK #-} !Int {-# UNPACK #-} !Int64 - --- | Parse a count of seconds, with the integer part being two digits --- long. -seconds :: Parser Pico -seconds = do - real <- twoDigits - mc <- peekChar - case mc of - Just '.' -> do - t <- anyChar *> takeWhile1 isDigit - return $! parsePicos real t - _ -> return $! fromIntegral real - where - parsePicos a0 t = toPico (fromIntegral (t' * 10^n)) - where T n t' = T.foldl' step (T 12 (fromIntegral a0)) t - step ma@(T m a) c - | m <= 0 = ma - | otherwise = T (m-1) (10 * a + fromIntegral (ord c) .&. 15) +timeOfDay = T.timeOfDay +{-# INLINE timeOfDay #-} -- | Parse a time zone, and return 'Nothing' if the offset from UTC is -- zero. (This makes some speedups possible.) timeZone :: Parser (Maybe Local.TimeZone) -timeZone = do - let maybeSkip c = do ch <- peekChar'; when (ch == c) (void anyChar) - maybeSkip ' ' - ch <- satisfy $ \c -> c == 'Z' || c == '+' || c == '-' - if ch == 'Z' - then return Nothing - else do - h <- twoDigits - mm <- peekChar - m <- case mm of - Just ':' -> anyChar *> twoDigits - Just d | isDigit d -> twoDigits - _ -> return 0 - let off | ch == '-' = negate off0 - | otherwise = off0 - off0 = h * 60 + m - case undefined of - _ | off == 0 -> - return Nothing - | off < -720 || off > 840 || m > 59 -> - fail "invalid time zone offset" - | otherwise -> - let !tz = Local.minutesToTimeZone off - in return (Just tz) +timeZone = T.timeZone +{-# INLINE timeZone #-} -- | Parse a date and time, of the form @YYYY-MM-DD HH:MM[:SS[.SSS]]@. -- The space may be replaced with a @T@. The number of seconds is optional -- and may be followed by a fractional component. localTime :: Parser Local.LocalTime -localTime = Local.LocalTime <$> day <* daySep <*> timeOfDay - where daySep = satisfy (\c -> c == 'T' || c == ' ') +localTime = T.localTime +{-# INLINE localTime #-} -- | Behaves as 'zonedTime', but converts any time zone offset into a -- UTC time. utcTime :: Parser UTCTime -utcTime = do - lt@(Local.LocalTime d t) <- localTime - mtz <- timeZone - case mtz of - Nothing -> let !tt = Local.timeOfDayToTime t - in return (UTCTime d tt) - Just tz -> return $! Local.localTimeToUTC tz lt +utcTime = T.utcTime +{-# INLINE utcTime #-} -- | Parse a date with time zone info. Acceptable formats: -- @@ -152,7 +68,5 @@ utcTime = do -- two digits are hours, the @:@ is optional and the second two digits -- (also optional) are minutes. zonedTime :: Parser Local.ZonedTime -zonedTime = Local.ZonedTime <$> localTime <*> (fromMaybe utc <$> timeZone) - -utc :: Local.TimeZone -utc = Local.TimeZone 0 False "" +zonedTime = T.zonedTime +{-# INLINE zonedTime #-} diff --git a/aeson.cabal b/aeson.cabal index 8438a9243..49ed770e3 100644 --- a/aeson.cabal +++ b/aeson.cabal @@ -80,7 +80,7 @@ flag cffi library default-language: Haskell2010 - hs-source-dirs: . + hs-source-dirs: . attoparsec-iso8601/ exposed-modules: Data.Aeson @@ -109,6 +109,8 @@ library Data.Aeson.Types.ToJSON Data.Aeson.Types.Class Data.Aeson.Types.Internal + Data.Attoparsec.Time + Data.Attoparsec.Time.Internal build-depends: attoparsec >= 0.13.0.1, diff --git a/attoparsec-iso8601/Data/Attoparsec/Time.hs b/attoparsec-iso8601/Data/Attoparsec/Time.hs new file mode 100644 index 000000000..f5a3ccbeb --- /dev/null +++ b/attoparsec-iso8601/Data/Attoparsec/Time.hs @@ -0,0 +1,149 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE ScopedTypeVariables #-} + +-- | +-- Module: Data.Aeson.Parser.Time +-- Copyright: (c) 2015-2016 Bryan O'Sullivan +-- License: BSD3 +-- Maintainer: Bryan O'Sullivan +-- Stability: experimental +-- Portability: portable +-- +-- Parsers for parsing dates and times. + +module Data.Attoparsec.Time + ( + day + , localTime + , timeOfDay + , timeZone + , utcTime + , zonedTime + ) where + +import Prelude () +import Prelude.Compat + +import Control.Applicative ((<|>)) +import Control.Monad (void, when) +import Data.Attoparsec.Text as A +import Data.Attoparsec.Time.Internal (toPico) +import Data.Bits ((.&.)) +import Data.Char (isDigit, ord) +import Data.Fixed (Pico) +import Data.Int (Int64) +import Data.Maybe (fromMaybe) +import Data.Time.Calendar (Day, fromGregorianValid) +import Data.Time.Clock (UTCTime(..)) +import qualified Data.Text as T +import qualified Data.Time.LocalTime as Local + +-- | Parse a date of the form @[+,-]YYYY-MM-DD@. +day :: Parser Day +day = do + absOrNeg <- negate <$ char '-' <|> id <$ char '+' <|> pure id + y <- decimal <* char '-' + m <- twoDigits <* char '-' + d <- twoDigits + maybe (fail "invalid date") return (fromGregorianValid (absOrNeg y) m d) + +-- | Parse a two-digit integer (e.g. day of month, hour). +twoDigits :: Parser Int +twoDigits = do + a <- digit + b <- digit + let c2d c = ord c .&. 15 + return $! c2d a * 10 + c2d b + +-- | Parse a time of the form @HH:MM[:SS[.SSS]]@. +timeOfDay :: Parser Local.TimeOfDay +timeOfDay = do + h <- twoDigits + m <- char ':' *> twoDigits + s <- option 0 (char ':' *> seconds) + if h < 24 && m < 60 && s < 61 + then return (Local.TimeOfDay h m s) + else fail "invalid time" + +data T = T {-# UNPACK #-} !Int {-# UNPACK #-} !Int64 + +-- | Parse a count of seconds, with the integer part being two digits +-- long. +seconds :: Parser Pico +seconds = do + real <- twoDigits + mc <- peekChar + case mc of + Just '.' -> do + t <- anyChar *> takeWhile1 isDigit + return $! parsePicos real t + _ -> return $! fromIntegral real + where + parsePicos a0 t = toPico (fromIntegral (t' * 10^n)) + where T n t' = T.foldl' step (T 12 (fromIntegral a0)) t + step ma@(T m a) c + | m <= 0 = ma + | otherwise = T (m-1) (10 * a + fromIntegral (ord c) .&. 15) + +-- | Parse a time zone, and return 'Nothing' if the offset from UTC is +-- zero. (This makes some speedups possible.) +timeZone :: Parser (Maybe Local.TimeZone) +timeZone = do + let maybeSkip c = do ch <- peekChar'; when (ch == c) (void anyChar) + maybeSkip ' ' + ch <- satisfy $ \c -> c == 'Z' || c == '+' || c == '-' + if ch == 'Z' + then return Nothing + else do + h <- twoDigits + mm <- peekChar + m <- case mm of + Just ':' -> anyChar *> twoDigits + Just d | isDigit d -> twoDigits + _ -> return 0 + let off | ch == '-' = negate off0 + | otherwise = off0 + off0 = h * 60 + m + case undefined of + _ | off == 0 -> + return Nothing + | off < -720 || off > 840 || m > 59 -> + fail "invalid time zone offset" + | otherwise -> + let !tz = Local.minutesToTimeZone off + in return (Just tz) + +-- | Parse a date and time, of the form @YYYY-MM-DD HH:MM[:SS[.SSS]]@. +-- The space may be replaced with a @T@. The number of seconds is optional +-- and may be followed by a fractional component. +localTime :: Parser Local.LocalTime +localTime = Local.LocalTime <$> day <* daySep <*> timeOfDay + where daySep = satisfy (\c -> c == 'T' || c == ' ') + +-- | Behaves as 'zonedTime', but converts any time zone offset into a +-- UTC time. +utcTime :: Parser UTCTime +utcTime = do + lt@(Local.LocalTime d t) <- localTime + mtz <- timeZone + case mtz of + Nothing -> let !tt = Local.timeOfDayToTime t + in return (UTCTime d tt) + Just tz -> return $! Local.localTimeToUTC tz lt + +-- | Parse a date with time zone info. Acceptable formats: +-- +-- @YYYY-MM-DD HH:MM Z@ +-- @YYYY-MM-DD HH:MM:SS Z@ +-- @YYYY-MM-DD HH:MM:SS.SSS Z@ +-- +-- The first space may instead be a @T@, and the second space is +-- optional. The @Z@ represents UTC. The @Z@ may be replaced with a +-- time zone offset of the form @+0000@ or @-08:00@, where the first +-- two digits are hours, the @:@ is optional and the second two digits +-- (also optional) are minutes. +zonedTime :: Parser Local.ZonedTime +zonedTime = Local.ZonedTime <$> localTime <*> (fromMaybe utc <$> timeZone) + +utc :: Local.TimeZone +utc = Local.TimeZone 0 False "" diff --git a/attoparsec-iso8601/Data/Attoparsec/Time/Internal.hs b/attoparsec-iso8601/Data/Attoparsec/Time/Internal.hs new file mode 100644 index 000000000..0f51acabd --- /dev/null +++ b/attoparsec-iso8601/Data/Attoparsec/Time/Internal.hs @@ -0,0 +1,61 @@ +{-# LANGUAGE CPP #-} + +-- | +-- Module: Data.Aeson.Internal.Time +-- Copyright: (c) 2015-2016 Bryan O'Sullivan +-- License: BSD3 +-- Maintainer: Bryan O'Sullivan +-- Stability: experimental +-- Portability: portable + +module Data.Attoparsec.Time.Internal + ( + TimeOfDay64(..) + , fromPico + , toPico + , diffTimeOfDay64 + , toTimeOfDay64 + ) where + +import Prelude () +import Prelude.Compat + +import Data.Int (Int64) +import Data.Time +import Unsafe.Coerce (unsafeCoerce) + +#if MIN_VERSION_base(4,7,0) + +import Data.Fixed (Pico, Fixed(MkFixed)) + +toPico :: Integer -> Pico +toPico = MkFixed + +fromPico :: Pico -> Integer +fromPico (MkFixed i) = i + +#else + +import Data.Fixed (Pico) + +toPico :: Integer -> Pico +toPico = unsafeCoerce + +fromPico :: Pico -> Integer +fromPico = unsafeCoerce + +#endif + +-- | Like TimeOfDay, but using a fixed-width integer for seconds. +data TimeOfDay64 = TOD {-# UNPACK #-} !Int + {-# UNPACK #-} !Int + {-# UNPACK #-} !Int64 + +diffTimeOfDay64 :: DiffTime -> TimeOfDay64 +diffTimeOfDay64 t = TOD (fromIntegral h) (fromIntegral m) s + where (h,mp) = fromIntegral pico `quotRem` 3600000000000000 + (m,s) = mp `quotRem` 60000000000000 + pico = unsafeCoerce t :: Integer + +toTimeOfDay64 :: TimeOfDay -> TimeOfDay64 +toTimeOfDay64 (TimeOfDay h m s) = TOD h m (fromIntegral (fromPico s)) diff --git a/attoparsec-iso8601/LICENSE b/attoparsec-iso8601/LICENSE new file mode 100644 index 000000000..a6fb08ada --- /dev/null +++ b/attoparsec-iso8601/LICENSE @@ -0,0 +1,30 @@ +Copyright (c) 2011, MailRank, Inc. + +All rights reserved. + +Redistribution and use in source and binary forms, with or without +modification, are permitted provided that the following conditions +are met: + +1. Redistributions of source code must retain the above copyright + notice, this list of conditions and the following disclaimer. + +2. Redistributions in binary form must reproduce the above copyright + notice, this list of conditions and the following disclaimer in the + documentation and/or other materials provided with the distribution. + +3. Neither the name of the author nor the names of his contributors + may be used to endorse or promote products derived from this software + without specific prior written permission. + +THIS SOFTWARE IS PROVIDED BY THE CONTRIBUTORS ``AS IS'' AND ANY EXPRESS +OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED +WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE +DISCLAIMED. IN NO EVENT SHALL THE AUTHORS OR CONTRIBUTORS BE LIABLE FOR +ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL +DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS +OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) +HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, +STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN +ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +POSSIBILITY OF SUCH DAMAGE. diff --git a/attoparsec-iso8601/README.md b/attoparsec-iso8601/README.md new file mode 100644 index 000000000..1dab22a35 --- /dev/null +++ b/attoparsec-iso8601/README.md @@ -0,0 +1,19 @@ +Parsing of ISO 8601 dates. + +This package is used to parse dates in aeson. It is split into a +separate package to be shared by other projects that want to parse +dates like aeson does. + +For now, this project is located in the aeson repository and aeson +itself uses the source of this package without pulling in the package +as a dependency. + +## Stability + +Since aeson depends on this package we want to be very careful about +changing the format. + +There may be breaking changes if we find that the format is +incorrectly too lenient. We consider widening of the allowed input a +non-breaking addition since all previously valid input will still +parse correctly. diff --git a/attoparsec-iso8601/attoparsec-iso8601.cabal b/attoparsec-iso8601/attoparsec-iso8601.cabal new file mode 100644 index 000000000..76014f812 --- /dev/null +++ b/attoparsec-iso8601/attoparsec-iso8601.cabal @@ -0,0 +1,55 @@ +name: attoparsec-iso8601 +version: 1.0.0.0 +synopsis: Parsing of ISO 8601 dates, originally from aeson. +description: Parsing of ISO 8601 dates, originally from aeson. +license: BSD3 +license-file: LICENSE +category: Parsing +copyright: (c) 2011-2016 Bryan O'Sullivan + (c) 2011 MailRank, Inc. +author: Bryan O'Sullivan +maintainer: Adam Bergmark +stability: experimental +cabal-version: >=1.10 +homepage: https://github.com/bos/aeson +bug-reports: https://github.com/bos/aeson/issues +build-type: Simple +extra-source-files: + README.md + +flag developer + description: operate in developer mode + default: False + manual: True + +flag fast + description: compile without optimizations + default: False + manual: True + +library + hs-source-dirs: . + default-language: Haskell2010 + ghc-options: -Wall + exposed-modules: + Data.Attoparsec.Time.Internal + Data.Attoparsec.Time + build-depends: + attoparsec >= 0.13.0.1, + base >= 4.5 && < 5, + base-compat >= 0.9.1 && < 0.10, + text >= 1.1.1.0, + time >= 1.1.1.4 + + if flag(fast) + ghc-options: -O0 + else + ghc-options: -O2 + + if flag(developer) + ghc-options: -Werror + ghc-prof-options: -auto-all + +source-repository head + type: git + location: git://github.com/bos/aeson.git diff --git a/benchmarks/aeson-benchmarks.cabal b/benchmarks/aeson-benchmarks.cabal index a2617367a..8c6840a2a 100644 --- a/benchmarks/aeson-benchmarks.cabal +++ b/benchmarks/aeson-benchmarks.cabal @@ -10,7 +10,7 @@ flag bytestring-builder manual: False library - hs-source-dirs: .. . ../ffi ../pure + hs-source-dirs: .. . ../ffi ../pure ../attoparsec-iso8601 c-sources: ../cbits/unescape_string.c exposed-modules: Data.Aeson @@ -34,6 +34,8 @@ library Data.Aeson.Types.Generic Data.Aeson.Types.Internal Data.Aeson.Types.ToJSON + Data.Attoparsec.Time + Data.Attoparsec.Time.Internal build-depends: attoparsec >= 0.13.0.1, diff --git a/stack-lts6.yaml b/stack-lts6.yaml index b9e6be2c0..9c764f22a 100644 --- a/stack-lts6.yaml +++ b/stack-lts6.yaml @@ -1,11 +1,14 @@ resolver: lts-6.30 packages: - '.' +- attoparsec-iso8601 extra-deps: - semigroups-0.18.2 - integer-logarithms-1 flags: aeson: fast: true + attoparsec-iso8601: + fast: true semigroups: bytestring-builder: false diff --git a/stack-lts7.yaml b/stack-lts7.yaml index f25a81001..4a25d38ce 100644 --- a/stack-lts7.yaml +++ b/stack-lts7.yaml @@ -1,8 +1,11 @@ resolver: lts-7.19 packages: - '.' +- attoparsec-iso8601 extra-deps: - integer-logarithms-1 flags: aeson: fast: true + attoparsec-iso8601: + fast: true diff --git a/stack-lts8.yaml b/stack-lts8.yaml index a56ce502b..ad193bb17 100644 --- a/stack-lts8.yaml +++ b/stack-lts8.yaml @@ -1,6 +1,9 @@ resolver: lts-8.1 packages: - '.' +- attoparsec-iso8601 flags: aeson: fast: true + attoparsec-iso8601: + fast: true diff --git a/stack-nightly.yaml b/stack-nightly.yaml index 1e32aaab7..f14437ec8 100644 --- a/stack-nightly.yaml +++ b/stack-nightly.yaml @@ -1,8 +1,9 @@ -resolver: nightly-2017-02-29 +resolver: nightly-2017-03-25 packages: - '.' -extra-deps: -- integer-logarithms-1 +- attoparsec-iso8601 flags: aeson: fast: true + attoparsec-iso8601: + fast: true