{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Data.Time.Parsers
( day
, month
, localTime
, timeOfDay
, timeZone
, utcTime
, zonedTime
, DateParsing
) where
import Control.Applicative (optional, some, (<|>))
import Control.Monad (void, when)
import Data.Bits ((.&.))
import Data.Char (isDigit, ord)
import Data.Fixed (Pico)
import Data.Int (Int64)
import Data.List (foldl')
import Data.Maybe (fromMaybe)
import Data.Time.Calendar (Day, fromGregorianValid)
import Data.Time.Clock (UTCTime (..))
import Text.Parser.Char (CharParsing (..), digit)
import Text.Parser.Combinators (unexpected)
import Text.Parser.LookAhead (LookAheadParsing (..))
import Unsafe.Coerce (unsafeCoerce)
import qualified Data.Time.LocalTime as Local
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((*>), (<$), (<$>), (<*), (<*>))
#endif
type DateParsing m = (CharParsing m, LookAheadParsing m, Monad m)
toPico :: Integer -> Pico
toPico = unsafeCoerce
month :: DateParsing m => m (Integer, Int)
month = do
s <- negate <$ char '-' <|> id <$ char '+' <|> return id
y <- decimal
_ <- char '-'
m <- twoDigits
if (1 <= m && m <= 12)
then return (s y, m)
else unexpected "Invalid month"
{-# INLINE month #-}
day :: DateParsing m => m Day
day = do
s <- negate <$ char '-' <|> id <$ char '+' <|> return id
y <- decimal
_ <- char '-'
m <- twoDigits
_ <- char '-'
d <- twoDigits
maybe (unexpected "invalid date") return (fromGregorianValid (s y) m d)
twoDigits :: DateParsing m => m Int
twoDigits = do
a <- digit
b <- digit
let c2d c = ord c .&. 15
return $! c2d a * 10 + c2d b
timeOfDay :: DateParsing m => m Local.TimeOfDay
timeOfDay = do
h <- twoDigits <* char ':'
m <- twoDigits <* char ':'
s <- seconds
if h < 24 && m < 60 && s < 61
then return (Local.TimeOfDay h m s)
else unexpected "invalid time"
data T = T {-# UNPACK #-} !Int {-# UNPACK #-} !Int64
seconds :: DateParsing m => m Pico
seconds = do
real <- twoDigits
mc <- peekChar
case mc of
Just '.' -> do
t <- anyChar *> some digit
return $! parsePicos real t
_ -> return $! fromIntegral real
where
parsePicos a0 t = toPico (fromIntegral (t' * 10^n))
where T n 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)
timeZone :: DateParsing m => m (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 ->
unexpected "invalid time zone offset"
| otherwise ->
let !tz = Local.minutesToTimeZone off
in return (Just tz)
localTime :: DateParsing m => m Local.LocalTime
localTime = Local.LocalTime <$> day <* daySep <*> timeOfDay
where daySep = satisfy (\c -> c == 'T' || c == ' ')
utcTime :: DateParsing m => m UTCTime
utcTime = f <$> localTime <*> timeZone
where
f :: Local.LocalTime -> Maybe Local.TimeZone -> UTCTime
f (Local.LocalTime d t) Nothing =
let !tt = Local.timeOfDayToTime t
in UTCTime d tt
f lt (Just tz) = Local.localTimeToUTC tz lt
zonedTime :: DateParsing m => m Local.ZonedTime
zonedTime = Local.ZonedTime <$> localTime <*> (fromMaybe utc <$> timeZone)
utc :: Local.TimeZone
utc = Local.TimeZone 0 False ""
decimal :: (DateParsing m, Integral a) => m a
decimal = foldl' step 0 `fmap` some digit
where step a w = a * 10 + fromIntegral (ord w - 48)
peekChar :: DateParsing m => m (Maybe Char)
peekChar = optional peekChar'
peekChar' :: DateParsing m => m Char
peekChar' = lookAhead anyChar