[Haskell-cafe] Converting string to System.Time.ClockTime

dokondr dokondr at gmail.com
Thu Dec 8 16:01:22 CET 2011


Now, when I have managed to convert UTCTime to seconds (see code below) I
got stuck trying to convert from UTCTime to CalendarTime, how to do this?

import Data.Time.Format
import Data.Time.Clock
import Locale
import Data.Maybe
import Data.Time.Clock.POSIX

s1 = "Wed, 07 Dec 2011 10:09:21 +0000"
s2 = "Wed, 07 Dec 2011 10:11:00 +0000"
t1 = fromJust $ tryParseTime s1
t2 = fromJust $ tryParseTime s2
pt1 = utcTimeToPOSIXSeconds t1  -- :: UTCTime -> POSIXTime
pt2 = utcTimeToPOSIXSeconds t2
pt3 = pt1 + (pt2 - pt1) / 2
t3 = posixSecondsToUTCTime pt3

t = compare t1 t2

tryParseTime :: String -> Maybe UTCTime
tryParseTime timeStr = tryFormat (parseTime defaultTimeLocale timeFormat1
timeStr :: Maybe UTCTime)
   where
     tryFormat time
        | time == Nothing = parseTime defaultTimeLocale timeFormat2 timeStr
:: Maybe UTCTime
        | otherwise = time

     timeFormat1 = "%a, %d %b %Y %T %z"
     timeFormat2 = "%m/%e/%Y %l:%M:%S %p"
-- timeFormat1 = "%m/%d/%Y %l:%M:%S %p"


On Thu, Dec 8, 2011 at 6:30 PM, dokondr <dokondr at gmail.com> wrote:

> I need to parse time strings like "Wed, 07 Dec 2011 10:09:21 +0000" to a
> type that:
> 1) implements Eq, Ord
> 2) is numerical, so I could subtract one value from another to find the
> difference or interval length
>
> To answer 1) requirement I wrote the following snippet. Yet I could not
> subtract  UTCTime values. How can I convert them to milliseconds?
>
> import Data.Time.Format
> import Data.Time.Clock
> import Locale
> import Data.Maybe
>
> s1 = "Wed, 07 Dec 2011 10:09:21 +0000"
> s2 = "Wed, 07 Dec 2011 10:11:00 +0000"
> t1 = fromJust $ tryParseTime s1
> t2 = fromJust $ tryParseTime s2
>
> t = compare t1 t2
>
> tryParseTime :: String -> Maybe UTCTime
> tryParseTime timeStr = tryFormat (parseTime defaultTimeLocale timeFormat1
> timeStr :: Maybe UTCTime)
>    where
>      tryFormat time
>         | time == Nothing = parseTime defaultTimeLocale timeFormat2
> timeStr :: Maybe UTCTime
>         | otherwise = time
>
>      timeFormat1 = "%a, %d %b %Y %T %z"
>      timeFormat2 = "%m/%e/%Y %l:%M:%S %p"
>
>
>
>
> On Thu, Dec 8, 2011 at 6:12 PM, Erik Hesselink <hesselink at gmail.com>wrote:
>
>> I'm not sure if you really need ClockTime (from old-time), but if you
>> don't, the types from the 'time' package are all parseable with
>> `parseTime` [1].
>>
>> Erik
>>
> [1]
>> http://hackage.haskell.org/packages/archive/time/latest/doc/html/Data-Time-Format.html#v:parseTime
>>
>> On Thu, Dec 8, 2011 at 14:16, dokondr <dokondr at gmail.com> wrote:
>> > Hi,
>> > What would be the simplest way to convert strings like "Wed, 07 Dec 2011
>> > 10:09:21 +0000" to System.Time.ClockTime ?
>> >
>> > Thanks!
>> >
>> >
>> >
>> > _______________________________________________
>> > Haskell-Cafe mailing list
>> > Haskell-Cafe at haskell.org
>> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>> >
>>
>
>
>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20111208/0fddf3b6/attachment.htm>


More information about the Haskell-Cafe mailing list