module Text.XML.XSD.DateTime
( DateTime(..)
, isZoned
, isUnzoned
, dateTime'
, dateTime
, toText
, fromZonedTime
, toUTCTime
, fromUTCTime
, toLocalTime
, fromLocalTime
, utcTime'
, utcTime
, localTime'
, localTime
) where
import Control.Applicative (pure, (<$>), (*>), (<|>))
import Control.Monad (when)
import Data.Attoparsec.Text (Parser, char, digit)
import qualified Data.Attoparsec.Text as A
import Data.Char (isDigit, ord)
import Data.Fixed (Pico, showFixed)
import Data.Maybe (maybeToList)
import Data.Monoid ((<>))
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TB
import qualified Data.Text.Lazy.Builder.Int as TBI
import qualified Data.Text.Read as TR
import Data.Time
import Data.Time.Calendar.MonthDay (monthLength)
data DateTime = DtZoned UTCTime
| DtUnzoned LocalTime
deriving (Eq)
mkDateTime :: Integer
-> Int
-> Int
-> Int
-> Int
-> Pico
-> Maybe Pico
-> DateTime
mkDateTime y m d hh mm ss mz =
case mz of
Just z -> DtZoned $ addUTCTime (negate $ realToFrac z) uTime
Nothing -> DtUnzoned lTime
where
day = addDays (if hh == 24 then 1 else 0) (fromGregorian y m d)
tod = TimeOfDay (if hh == 24 then 0 else hh) mm ss
lTime = LocalTime day tod
uTime = UTCTime day (timeOfDayToTime tod)
instance Show DateTime where
show = T.unpack . toText
instance Read DateTime where
readList s = [(maybeToList (dateTime . T.pack $ s), [])]
dateTime' :: Text -> Either String DateTime
dateTime' = A.parseOnly (parseDateTime <|> fail "bad date time")
dateTime :: Text -> Maybe DateTime
dateTime = either (const Nothing) Just . dateTime'
toText :: DateTime -> Text
toText = TL.toStrict . TB.toLazyText . dtBuilder
where
dtBuilder (DtZoned uTime) = ltBuilder (utcToLocalTime utc uTime) <> "Z"
dtBuilder (DtUnzoned lTime) = ltBuilder lTime
ltBuilder (LocalTime day (TimeOfDay hh mm sss)) =
let (y, m, d) = toGregorian day
in buildInt4 y
<> "-"
<> buildUInt2 m
<> "-"
<> buildUInt2 d
<> "T"
<> buildUInt2 hh
<> ":"
<> buildUInt2 mm
<> ":"
<> buildSeconds sss
buildInt4 :: Integer -> TB.Builder
buildInt4 year =
let absYear = abs year
k x = if absYear < x then ("0" <>) else id
in k 1000 . k 100 . k 10 $ TBI.decimal year
buildUInt2 :: Int -> TB.Builder
buildUInt2 x = (if x < 10 then ("0" <>) else id) $ TBI.decimal x
buildSeconds :: Pico -> TB.Builder
buildSeconds secs = (if secs < 10 then ("0" <>) else id)
$ TB.fromString (showFixed True secs)
fromZonedTime :: ZonedTime -> DateTime
fromZonedTime = fromUTCTime . zonedTimeToUTC
isZoned :: DateTime -> Bool
isZoned (DtZoned _) = True
isZoned (DtUnzoned _) = False
isUnzoned :: DateTime -> Bool
isUnzoned = not . isZoned
toUTCTime :: DateTime -> Maybe UTCTime
toUTCTime (DtZoned time) = Just time
toUTCTime _ = Nothing
fromUTCTime :: UTCTime -> DateTime
fromUTCTime = DtZoned
toLocalTime :: DateTime -> Maybe LocalTime
toLocalTime (DtUnzoned time) = Just time
toLocalTime _ = Nothing
fromLocalTime :: LocalTime -> DateTime
fromLocalTime = DtUnzoned
utcTime' :: Text -> Either String UTCTime
utcTime' txt = dateTime' txt >>= maybe (Left err) Right . toUTCTime
where
err = "input time is non-timezoned"
utcTime :: Text -> Maybe UTCTime
utcTime txt = dateTime txt >>= toUTCTime
localTime' :: Text -> Either String LocalTime
localTime' txt = dateTime' txt >>= maybe (Left err) Right . toLocalTime
where
err = "input time is non-timezoned"
localTime :: Text -> Maybe LocalTime
localTime txt = dateTime txt >>= toLocalTime
parseDateTime :: Parser DateTime
parseDateTime = do yy <- yearParser
_ <- char '-'
mm <- p2imax 12
_ <- char '-'
dd <- p2imax (monthLength (isLeapYear $ fromIntegral yy) mm)
_ <- char 'T'
hhh <- p2imax 24
_ <- char ':'
mmm <- p2imax 59
_ <- char ':'
sss <- secondParser
when (hhh == 24 && (mmm /= 0 || sss /= 0))
$ fail "invalid time, past 24:00:00"
o <- parseOffset
return $ mkDateTime yy mm dd hhh mmm sss o
parseOffset :: Parser (Maybe Pico)
parseOffset = (A.endOfInput *> pure Nothing)
<|>
(char 'Z' *> pure (Just 0))
<|>
(do sign <- (char '+' *> pure 1) <|> (char '-' *> pure (1))
hh <- fromIntegral <$> p2imax 14
_ <- char ':'
mm <- fromIntegral <$> p2imax (if hh == 14 then 0 else 59)
return . Just $ sign * (hh * 3600 + mm * 60))
yearParser :: Parser Integer
yearParser = do sign <- (char '-' *> pure (1)) <|> pure 1
ds <- A.takeWhile isDigit
when (T.length ds < 4)
$ fail "need at least four digits in year"
when (T.length ds > 4 && T.head ds == '0')
$ fail "leading zero in year"
let Right (absyear, _) = TR.decimal ds
when (absyear == 0)
$ fail "year zero disallowed"
return $ sign * absyear
secondParser :: Parser Pico
secondParser = do d1 <- digit
d2 <- digit
frac <- readFrac <$> (char '.' *> A.takeWhile isDigit)
<|> pure 0
return (read [d1, d2] + frac)
where
readFrac ds = read $ '0' : '.' : T.unpack ds
p2imax :: Int -> Parser Int
p2imax m = do a <- digit
b <- digit
let n = 10 * val a + val b
if n > m
then fail $ "value " ++ show n ++ " exceeded maximum " ++ show m
else return n
where
val c = ord c ord '0'