{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Data.Attoparsec.Time
(
day
, localTime
, timeOfDay
, timeZone
, utcTime
, zonedTime
) where
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
day :: Parser Day
day = do
absOrNeg <- negate <$ char '-' <|> id <$ char '+' <|> pure id
y <- (decimal <* char '-') <|> fail "date must be of form [+,-]YYYY-MM-DD"
m <- (twoDigits <* char '-') <|> fail "date must be of form [+,-]YYYY-MM-DD"
d <- twoDigits <|> fail "date must be of form [+,-]YYYY-MM-DD"
maybe (fail "invalid date") return (fromGregorianValid (absOrNeg y) m d)
twoDigits :: Parser Int
twoDigits = do
a <- digit
b <- digit
let c2d c = ord c .&. 15
return $! c2d a * 10 + c2d b
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
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)
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)
localTime :: Parser Local.LocalTime
localTime = Local.LocalTime <$> day <* daySep <*> timeOfDay
where daySep = satisfy (\c -> c == 'T' || c == ' ')
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
zonedTime :: Parser Local.ZonedTime
zonedTime = Local.ZonedTime <$> localTime <*> (fromMaybe utc <$> timeZone)
utc :: Local.TimeZone
utc = Local.TimeZone 0 False ""