Any way to read in a time?

John Meacham john@repetae.net
Fri, 18 Oct 2002 15:47:14 -0700


I have come across this problem in a couple places, here are my
solutions

a parser based on Parsec (this parses RFC2822 email style dates)

parseDate :: Parser ClockTime
parseDate = token $ do
    skipOption (word >> skipOption (token $ char ','))
    day <- number
    month <- ml
    year <- liftM (\n -> if n < 100 then n + 1900 else n)number
    hour <- number
    token $ char ':'
    minute <- number
    second <- option 0 ((token $ char ':') >> number)
    tz <- timezone
    spaces
    option () comments
    return $ toClockTime calendarTime { ctYear = year, ctDay = day,
ctMonth = month, ctHour = hour, ctMin = minute, ctSec= second, ctTZ = tz}

timezone = token $ do
    pm <- (char '-' >> return negate) <|> (char '+' >> return id)
    h1 <- liftM digitToInt digit
    h2 <- liftM digitToInt digit
    m1 <- liftM digitToInt digit
    m2 <- liftM digitToInt digit
    return $ 60 * (pm $ (h1 * 10 + h2) * 60 + m1 * 10 + m2)



another solution when I just wanted to serialize times, was this
instance of Binary I wrote

instance Binary ClockTime where
    put bh ct = do
        let t = toUTCTime ct
        put bh (ctYear t)
        put bh (fromEnum $ ctMonth t)
        put bh (ctDay t)
        put bh (ctHour t)
        put bh (ctMin t)
        put bh (ctSec t)
    get bh = do
        year <- get bh
        month <- fmap toEnum $ get bh
        day <- get bh
        hour <- get bh
        min <- get bh
        sec <- get bh
        return $ toClockTime $ (toUTCTime epoch) {ctYear = year, ctDay =
day, ctMonth = month, ctHour = hour, ctMin = min, ctSec = sec}

epoch = toClockTime $ CalendarTime { ctYear = 1970, ctMonth = January,
  ctDay = 0, ctHour = 0, ctMin = 0, ctSec = 0, ctTZ = 0, ctPicosec = 0,
  ctWDay = undefined, ctYDay = undefined, ctTZName = undefined, ctIsDST =
  undefined}


perhaps one might be useful to you...
	John


On Fri, Oct 18, 2002 at 03:15:44PM -0400, David Roundy wrote:
> I've been looking at the standard Time module, and it seems pretty easy to
> convert a date into a string (using either calendarTimeToString or
> formatCalendarTime), but there doesn't seem to be any way to reverse the
> process.
> 
> I understand that there are so many date and time formats that it may be
> hard to parse, and that for many formats there may be no unambiguous
> translation back into a CalendarTime (e.g. if the time zone isn't included
> in the string), but it seems like a pretty fundamental (and commonly
> needed) ability to be able to output a human-readable date and then read it
> back in.
> 
> Does anyone have a suggestion how best to go about this? I guess the
> easiest way might be to just convert to UTC and then use formatCalendarTime
> to choose what formatting I want and then write my own parser to reverse
> the process.  But this seems like a process with a relatively high
> probability of introducing rarely seen bugs, which ought to be dealt with
> by a standard library.
> 
> Of course, there are also a couple of other workarounds I could use.
> CalendarTime derives from Show, so I could just output the result of show,
> but that's an awfully verbose format.  I could also give up on comparing
> dates (which I don't necesarily need, although it is nice) and just treat
> dates as strings.
> 
> Any ideas or commentary would be welcome.
> -- 
> David Roundy
> http://civet.berkeley.edu/droundy/
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 

-- 
---------------------------------------------------------------------------
John Meacham - California Institute of Technology, Alum. - john@foo.net
---------------------------------------------------------------------------