module Darcs.Util.IsoDate
( getIsoDateTime, readUTCDate, readUTCDateOldFashioned
, parseDate, getLocalTz
, englishDateTime, englishInterval, englishLast
, iso8601Interval, iso8601Duration
, cleanLocalDate, resetCalendar
, MCalendarTime(..), subtractFromMCal, addToMCal
, toMCalendarTime, unsafeToCalendarTime
, unsetTime, TimeInterval
, showIsoDateTime
, theBeginning
) where
import Darcs.Prelude
import Prelude ( (^) )
import Text.ParserCombinators.Parsec
import System.Time
import System.IO.Unsafe ( unsafePerformIO )
import Data.Char ( toUpper, isDigit )
import Data.Maybe ( fromMaybe )
import Control.Monad ( liftM, liftM2 )
import qualified Data.ByteString.Char8 as BC
type TimeInterval = (Maybe CalendarTime, Maybe CalendarTime)
readUTCDate :: String -> CalendarTime
readUTCDate = readDate 0
cleanLocalDate :: String -> IO String
cleanLocalDate str =
do tz <- getLocalTz
return . showIsoDateTime . resetCalendar . readDate tz $ str
getLocalTz :: IO Int
getLocalTz = ctTZ `liftM` (getClockTime >>= toCalendarTime)
readDate :: Int -> String -> CalendarTime
readDate tz d =
case parseDate tz d of
Left e -> error $ "bad date: "++d++" - "++show e
Right ct -> resetCalendar $ unsafeToCalendarTime ct
readUTCDateOldFashioned :: String -> CalendarTime
readUTCDateOldFashioned d =
case parseDate 0 d of
Left e -> error $ "bad date: "++d++" - "++show e
Right ct -> (unsafeToCalendarTime ct) { ctTZ = 0 }
parseDate :: Int -> String -> Either ParseError MCalendarTime
parseDate tz d =
if length d >= 14 && BC.all isDigit bd
then Right $ toMCalendarTime $
CalendarTime (readI $ BC.take 4 bd)
(toEnum $ (+ (-1)) $ readI $ BC.take 2 $ BC.drop 4 bd)
(readI $ BC.take 2 $ BC.drop 6 bd)
(readI $ BC.take 2 $ BC.drop 8 bd)
(readI $ BC.take 2 $ BC.drop 10 bd)
(readI $ BC.take 2 $ BC.drop 12 bd)
0 Sunday 0
"GMT" 0 False
else let dt = do { x <- dateTime tz; eof; return x }
in parse dt "" d
where bd = BC.pack (take 14 d)
readI s = fst $ fromMaybe (error "parseDate: invalid date") (BC.readInt s)
showIsoDateTime :: CalendarTime -> String
showIsoDateTime ct = concat [ show $ ctYear ct
, twoDigit . show . (+1) . fromEnum $ ctMonth ct
, twoDigit . show $ ctDay ct
, twoDigit . show $ ctHour ct
, twoDigit . show $ ctMin ct
, twoDigit . show $ ctSec ct
]
where twoDigit [] = undefined
twoDigit x@(_:[]) = '0' : x
twoDigit x@(_:_:[]) = x
twoDigit _ = undefined
getIsoDateTime :: IO String
getIsoDateTime = (showIsoDateTime . toUTCTime) `liftM` getClockTime
caseChar :: Char -> GenParser Char a Char
caseChar c = satisfy (\x -> toUpper x == toUpper c)
caseString :: String -> GenParser Char a ()
caseString cs = mapM_ caseChar cs <?> cs
caseStrings :: [String] -> GenParser Char a ()
caseStrings xs = foldl1 (<|>) $ map caseString xs
manyN :: Int -> GenParser a b c -> GenParser a b [c]
manyN n p
| n <= 0 = return []
| otherwise = liftM2 (++) (count n p) (many p)
manyNtoM :: Int -> Int -> GenParser a b c -> GenParser a b [c]
manyNtoM n m p
| n < 0 = return []
| n > m = return []
| n == m = count n p
| n == 0 = foldr ((<|>) . (\x -> try $ count x p)) (return []) (reverse [1..m])
| otherwise = liftM2 (++) (count n p) (manyNtoM 0 (m-n) p)
dateTime :: Int -> CharParser a MCalendarTime
dateTime tz =
choice [try $ toMCalendarTime `fmap` cvsDateTime tz,
try $ iso8601DateTime tz,
try $ toMCalendarTime `fmap` oldDateTime,
toMCalendarTime `fmap` rfc2822DateTime]
parseDHMS :: CharParser a (Int, Int, Int, Int)
parseDHMS = do
d <- day
_ <- mySpaces
(h, m, s) <- parseHMS
return (d, h, m, s)
parseHMS :: CharParser a (Int, Int, Int)
parseHMS = do
h <- hour
_ <- char ':'
m <- minute
_ <- char ':'
s <- second
return (h, m, s)
parseSpacesMonthName :: CharParser a Month
parseSpacesMonthName = do
_ <- mySpaces
mon <- monthName
_ <- mySpaces
return mon
cvsDateTime :: Int -> CharParser a CalendarTime
cvsDateTime tz =
do y <- year
_ <- char '/'
mon <- monthNum
_ <- char '/'
(d, h, m, s) <- parseDHMS
z <- option tz $ mySpaces >> zone
return (CalendarTime y mon d h m s 0 Monday 0 "" z False)
oldDateTime :: CharParser a CalendarTime
oldDateTime = do wd <- dayName
mon <- parseSpacesMonthName
(d, h, m , s) <- parseDHMS
_ <- mySpaces
z <- zone
_ <- mySpaces
y <- year
return (CalendarTime y mon d h m s 0 wd 0 "" z False)
rfc2822DateTime :: CharParser a CalendarTime
rfc2822DateTime = do wd <- dayName
_ <- char ','
_ <- mySpaces
d <- day
mon <- parseSpacesMonthName
y <- year
_ <- mySpaces
(h, m, s) <- parseHMS
_ <- mySpaces
z <- zone
return (CalendarTime y mon d h m s 0 wd 0 "" z False)
iso8601DateTime :: Int -> CharParser a MCalendarTime
iso8601DateTime localTz = try $
do d <- iso8601Date
t <- option id $ try $ do optional $ oneOf " T"
iso8601Time
return $ t $ d { mctTZ = Just localTz }
iso8601Date :: CharParser a MCalendarTime
iso8601Date =
do d <- calendar_date <|> week_date <|> ordinal_date
return $ foldr ($) nullMCalendar d
where
calendar_date =
try $ do d <- optchain year_ [ (dash, month_), (dash, day_) ]
notFollowedBy (digit <|> char 'W')
return d
week_date =
try $ do yfn <- year_
optional dash
_ <- char 'W'
w' <- (\x -> x-1) `liftM` twoDigits
mwd <- option Nothing $ do { optional dash; Just `fmap` nDigits 1 }
let y = resetCalendar . unsafeToCalendarTime . yfn $ nullMCalendar { mctDay = Just 1 }
firstDay = ctWDay y
let afterThursday = firstDay == Sunday || firstDay > Thursday
w = if afterThursday then w'+1 else w'
yday = (7 * w) + fromMaybe 1 mwd
diff c = c { mctWeek = True
, mctWDay = toEnum `fmap` mwd
, mctDay = Just yday }
return [diff.yfn]
ordinal_date =
try $ optchain year_ [ (dash, yearDay_) ]
year_ = try $ do y <- fourDigits <?> "year (0000-9999)"
return $ \c -> c { mctYear = Just y }
month_ = try $ do m <- twoDigits <?> "month (1 to 12)"
return $ \c -> c { mctMonth = Just $ intToMonth m }
day_ = try $ do d <- twoDigits <?> "day in month (1 to 31)"
return $ \c -> c { mctDay = Just d }
yearDay_ = try $ do d <- nDigits 3 <?> "day in year (001 to 366)"
return $ \c -> c { mctDay = Just d
, mctYDay = Just (d - 1) }
dash = char '-'
iso8601Time :: CharParser a (MCalendarTime -> MCalendarTime)
iso8601Time = try $
do ts <- optchain hour_ [ (colon , min_)
, (colon , sec_)
, (oneOf ",.", pico_) ]
z <- option id $ choice [ zulu , offset ]
return $ foldr (.) id (z:ts)
where
hour_ = do h <- twoDigits
return $ \c -> c { mctHour = Just h }
min_ = do m <- twoDigits
return $ \c -> c { mctMin = Just m }
sec_ = do s <- twoDigits
return $ \c -> c { mctSec = Just s }
pico_ = do digs <- many digit
let picoExp = 12
digsExp = length digs
let frac | null digs = 0
| digsExp > picoExp = read $ take picoExp digs
| otherwise = 10 ^ (picoExp - digsExp) * read digs
return $ \c -> c { mctPicosec = Just frac }
zulu = do { _ <- char 'Z'; return (\c -> c { mctTZ = Just 0 }) }
offset = do sign <- choice [ char '+' >> return 1
, char '-' >> return (-1) ]
h <- twoDigits
m <- option 0 $ do { optional colon; twoDigits }
return $ \c -> c { mctTZ = Just $ sign * 60 * ((h*60)+m) }
colon = char ':'
iso8601Interval :: Int -> CharParser a (Either TimeDiff (MCalendarTime, MCalendarTime))
iso8601Interval localTz = leftDur <|> rightDur where
leftDur =
do dur <- iso8601Duration
end <- option Nothing $ do { _ <- char '/'; Just `liftM` isoDt }
return $ case end of
Nothing -> Left dur
Just e -> Right (dur `subtractFromMCal` e, e)
rightDur =
do start <- isoDt
_ <- char '/'
durOrEnd <- Left `liftM` iso8601Duration <|> Right `liftM` isoDt
return $ case durOrEnd of
Left dur -> Right (start, dur `addToMCal` start)
Right end -> Right (start, end)
isoDt = iso8601DateTime localTz
iso8601Duration :: CharParser a TimeDiff
iso8601Duration =
do _ <- char 'P'
y <- block 0 'Y'
mon <- block 0 'M'
d <- block 0 'D'
(h,m,s) <- option (0,0,0) $
do _ <- char 'T'
h' <- block (-1) 'H'
m' <- block (-1) 'M'
s' <- block (-1) 'S'
let unset = (== (-1))
if all unset [h',m',s']
then fail "T should be omitted if time is unspecified"
else let clear x = if unset x then 0 else x
in return (clear h', clear m', clear s')
return $ TimeDiff y mon d h m s 0
where block d c = option d $ try $
do n <- many1 digit
_ <- char c
return $ read n
optchain :: CharParser a b -> [(CharParser a c, CharParser a b)] -> CharParser a [b]
optchain p next = try $
do r1 <- p
r2 <- case next of
[] -> return []
((sep,p2):next2) -> option [] $ do { optional sep; optchain p2 next2 }
return (r1:r2)
nDigits :: Int -> CharParser a Int
nDigits n = read `liftM` count n digit
twoDigits, fourDigits :: CharParser a Int
twoDigits = nDigits 2
fourDigits = nDigits 4
mySpaces :: CharParser a String
mySpaces = manyN 1 $ char ' '
dayName :: CharParser a Day
dayName = choice
[ caseString "Mon" >> return Monday
, try (caseString "Tue") >> return Tuesday
, caseString "Wed" >> return Wednesday
, caseString "Thu" >> return Thursday
, caseString "Fri" >> return Friday
, try (caseString "Sat") >> return Saturday
, caseString "Sun" >> return Sunday
]
year :: CharParser a Int
year = fourDigits
monthNum :: CharParser a Month
monthNum = do mn <- manyNtoM 1 2 digit
return $ intToMonth (read mn :: Int)
intToMonth :: Int -> Month
intToMonth 1 = January
intToMonth 2 = February
intToMonth 3 = March
intToMonth 4 = April
intToMonth 5 = May
intToMonth 6 = June
intToMonth 7 = July
intToMonth 8 = August
intToMonth 9 = September
intToMonth 10 = October
intToMonth 11 = November
intToMonth 12 = December
intToMonth _ = error "invalid month!"
monthName :: CharParser a Month
monthName = choice
[ try (caseString "Jan") >> return January
, caseString "Feb" >> return February
, try (caseString "Mar") >> return March
, try (caseString "Apr") >> return April
, caseString "May" >> return May
, try (caseString "Jun") >> return June
, caseString "Jul" >> return July
, caseString "Aug" >> return August
, caseString "Sep" >> return September
, caseString "Oct" >> return October
, caseString "Nov" >> return November
, caseString "Dec" >> return December
]
day :: CharParser a Int
day = do d <- manyNtoM 1 2 digit
return (read d :: Int)
hour :: CharParser a Int
hour = twoDigits
minute :: CharParser a Int
minute = twoDigits
second :: CharParser a Int
second = twoDigits
zone :: CharParser a Int
zone = choice
[ do { _ <- char '+'; h <- hour; m <- minute; return (((h*60)+m)*60) }
, do { _ <- char '-'; h <- hour; m <- minute; return (-((h*60)+m)*60) }
, mkZone "UTC" 0
, mkZone "UT" 0
, mkZone "GMT" 0
, mkZone "WET" 0
, mkZone "WEST" 1
, mkZone "BST" 1
, mkZone "ART" (-3)
, mkZone "BRT" (-3)
, mkZone "BRST" (-2)
, mkZone "AST" (-4)
, mkZone "ADT" (-3)
, mkZone "CLT" (-4)
, mkZone "CLST" (-3)
, mkZone "EST" (-5)
, mkZone "EDT" (-4)
, mkZone "CST" (-6)
, mkZone "CDT" (-5)
, mkZone "MST" (-7)
, mkZone "MDT" (-6)
, mkZone "PST" (-8)
, mkZone "PDT" (-7)
, mkZone "AKST" (-9)
, mkZone "AKDT" (-8)
, mkZone "HST" (-10)
, mkZone "HAST" (-10)
, mkZone "HADT" (-9)
, mkZone "SST" (-12)
, mkZone "WAT" 1
, mkZone "CET" 1
, mkZone "CEST" 2
, mkZone "MET" 1
, mkZone "MEZ" 1
, mkZone "MEST" 2
, mkZone "MESZ" 2
, mkZone "EET" 2
, mkZone "EEST" 3
, mkZone "CAT" 2
, mkZone "SAST" 2
, mkZone "EAT" 3
, mkZone "MSK" 3
, mkZone "MSD" 4
, mkZone "SGT" 8
, mkZone "KST" 9
, mkZone "JST" 9
, mkZone "GST" 10
, mkZone "NZST" 12
, mkZone "NZDT" 13
, do { _ <- manyTill (oneOf $ ' ' : ['a'..'z']++['A'..'Z'])
(lookAhead space_digit);
return 0 }
]
where mkZone n o = try $ do { caseString n; return (o*60*60) }
space_digit = try $ do { _ <- char ' '; oneOf ['0'..'9'] }
englishDateTime :: CalendarTime -> CharParser a CalendarTime
englishDateTime now =
try $ dateMaybeAtTime <|> timeThenDate
where
dateMaybeAtTime = try $
do ed <- englishDate now
t <- option Nothing $ try $
do { _ <- space; optional $ caseString "at "; Just `liftM` englishTime }
return $ fromMaybe id t ed
timeThenDate = try $
do t <- englishTime
optional $ char ','
_ <- space
ed <- englishDate now
return $ t $ unsetTime ed
englishDate :: CalendarTime -> CharParser a CalendarTime
englishDate now = try $
(caseString "today" >> return (resetCalendar now))
<|> (caseString "yesterday" >> return (oneDay `subtractFromCal` now))
<|> fst `fmap` englishLast now
<|> englishAgo now
where oneDay = TimeDiff 0 0 1 0 0 0 0
englishAgo :: CalendarTime -> CharParser a CalendarTime
englishAgo now =
try $ do p <- englishDuration
_ <- try space
(m,ref) <- try (caseString "ago" >> return (-1, now))
<|> do m <- beforeMod <|> afterMod
_ <- space
d <- englishDate now
<|> fst `fmap` englishLast now
<|> unsafeToCalendarTime `fmap` iso8601DateTime (ctTZ now)
return (m,d)
return $ multiplyDiff m p `addToCal` ref
where
beforeMod = try $ caseString "before" >> return (-1)
afterMod = try $ caseStrings ["after","since"] >> return 1
englishInterval :: CalendarTime -> CharParser a TimeInterval
englishInterval now = twixt <|> before <|> after <|> inTheLast <|> lastetc
where
englishDT = unsafeToCalendarTime `fmap` iso8601DateTime (ctTZ now)
<|> englishDateTime now
before = try $
do caseString "before"
_ <- space
end <- englishDT
return (Just theBeginning, Just end)
after = try $
do caseStrings ["after","since"]
_ <- space
start <- englishDT
return (Just start, Nothing)
twixt = try $
do caseString "between"
_ <- space
start <- englishDT
_ <- space
caseString "and"
_ <- space
end <- englishDT
return (Just start, Just end)
inTheLast = try $
do caseString "in the last"
_ <- space
dur <- englishDuration
return (Just $ dur `subtractFromCal` now, Just now)
lastetc =
do l <- englishAgo now
return (Just l, Just now)
englishLast :: CalendarTime -> CharParser a (CalendarTime, CalendarTime)
englishLast now =
try $ do caseString "last"
_ <- space
d <- englishDuration
return (d `subtractFromCal` now, now)
englishTime :: CharParser a (CalendarTime->CalendarTime)
englishTime = try $
choice [ wrapM `fmap` iso8601Time
, namedTime "noon" 12 0
, namedTime "midnight" 0 0
, namedTime "tea time" 16 30
, namedTime "bed time" 2 30
, namedTime "proper bed time" 21 30 ]
where namedTime name h m = try $
do caseString name
return $ \c -> c { ctHour = h, ctMin = m }
wrapM f = unsafeToCalendarTime . f . toMCalendarTime
englishDuration :: CharParser a TimeDiff
englishDuration = try $
do n <- option 1 $ do x <- many1 digit
_ <- space
return $ read x
b <- base
optional (caseStrings ["es","s"])
let current = multiplyDiff n b
next <- option noTimeDiff $ try $ do
{ optional space; _ <- char ',' ; optional space ; englishDuration }
return $ addDiff current next
where
base = choice
[ try $ caseString "score" >> return (TimeDiff 20 0 0 0 0 0 0)
, caseString "year" >> return (TimeDiff 1 0 0 0 0 0 0)
, try $ caseString "month" >> return (TimeDiff 0 1 0 0 0 0 0)
, caseString "fortnight" >> return (TimeDiff 0 0 14 0 0 0 0)
, caseString "week" >> return (TimeDiff 0 0 7 0 0 0 0)
, caseString "day" >> return (TimeDiff 0 0 1 0 0 0 0)
, caseString "hour" >> return (TimeDiff 0 0 0 1 0 0 0)
, caseString "minute" >> return (TimeDiff 0 0 0 0 1 0 0)
, caseString "second" >> return (TimeDiff 0 0 0 0 0 1 0) ]
theBeginning :: CalendarTime
theBeginning = unsafePerformIO $ toCalendarTime $ TOD 0 0
data MCalendarTime = MCalendarTime
{ mctYear :: Maybe Int
, mctMonth :: Maybe Month
, mctDay :: Maybe Int
, mctHour :: Maybe Int
, mctMin :: Maybe Int
, mctSec :: Maybe Int
, mctPicosec :: Maybe Integer
, mctWDay :: Maybe Day
, mctYDay :: Maybe Int
, mctTZName :: Maybe String
, mctTZ :: Maybe Int
, mctIsDST :: Maybe Bool
, mctWeek :: Bool
} deriving Show
toMCalendarTime :: CalendarTime -> MCalendarTime
toMCalendarTime (CalendarTime a b c d e f g h i j k l) =
MCalendarTime (Just a) (Just b) (Just c) (Just d) (Just e) (Just f)
(Just g) (Just h) (Just i) (Just j) (Just k) (Just l)
False
unsafeToCalendarTime :: MCalendarTime -> CalendarTime
unsafeToCalendarTime m =
CalendarTime
{ ctYear = fromMaybe 0 $ mctYear m
, ctMonth = fromMaybe January $ mctMonth m
, ctDay = fromMaybe 1 $ mctDay m
, ctHour = fromMaybe 0 $ mctHour m
, ctMin = fromMaybe 0 $ mctMin m
, ctSec = fromMaybe 0 $ mctSec m
, ctPicosec = fromMaybe 0 $ mctPicosec m
, ctWDay = fromMaybe Sunday $ mctWDay m
, ctYDay = fromMaybe 0 $ mctYDay m
, ctTZName = fromMaybe "" $ mctTZName m
, ctTZ = fromMaybe 0 $ mctTZ m
, ctIsDST = fromMaybe False $ mctIsDST m
}
addToCal :: TimeDiff -> CalendarTime -> CalendarTime
addToCal td = toUTCTime . addToClockTime td . toClockTime
subtractFromCal :: TimeDiff -> CalendarTime -> CalendarTime
subtractFromCal = addToCal . multiplyDiff (-1)
addToMCal :: TimeDiff -> MCalendarTime -> MCalendarTime
addToMCal td mc =
copyCalendar (addToCal td $ unsafeToCalendarTime mc) mc
subtractFromMCal :: TimeDiff -> MCalendarTime -> MCalendarTime
subtractFromMCal = addToMCal . multiplyDiff (-1)
addDiff :: TimeDiff -> TimeDiff -> TimeDiff
addDiff (TimeDiff a1 a2 a3 a4 a5 a6 a7) (TimeDiff b1 b2 b3 b4 b5 b6 b7) =
TimeDiff (a1+b1) (a2+b2) (a3+b3) (a4+b4) (a5+b5) (a6+b6) (a7 + b7)
multiplyDiff :: Int -> TimeDiff -> TimeDiff
multiplyDiff m (TimeDiff a1 a2 a3 a4 a5 a6 a7) =
TimeDiff (a1*m) (a2*m) (a3*m) (a4*m) (a5*m) (a6*m) (a7 * toInteger m)
nullMCalendar :: MCalendarTime
nullMCalendar = MCalendarTime Nothing Nothing Nothing Nothing Nothing Nothing
Nothing Nothing Nothing Nothing Nothing Nothing
False
resetCalendar :: CalendarTime -> CalendarTime
resetCalendar = toUTCTime . toClockTime
copyCalendar :: CalendarTime -> MCalendarTime -> MCalendarTime
copyCalendar c mc = mc
{ mctYear = mctYear mc >> Just (ctYear c)
, mctMonth = mctMonth mc >> Just (ctMonth c)
, mctDay = mctDay mc >> Just (ctDay c)
, mctHour = mctHour mc >> Just (ctHour c)
, mctMin = mctMin mc >> Just (ctMin c)
, mctSec = mctSec mc >> Just (ctSec c)
, mctPicosec = mctPicosec mc >> Just (ctPicosec c)
, mctWDay = mctWDay mc >> Just (ctWDay c)
, mctYDay = mctYDay mc >> Just (ctYDay c)
, mctTZName = mctTZName mc >> Just (ctTZName c)
, mctTZ = mctTZ mc >> Just (ctTZ c)
, mctIsDST = mctIsDST mc >> Just (ctIsDST c)
}
unsetTime :: CalendarTime -> CalendarTime
unsetTime mc = mc
{ ctHour = 0
, ctMin = 0
, ctSec = 0
, ctPicosec = 0
}