, TemplateHaskell
, UnicodeSyntax
#-}
--- |This module provides functions for ANSI C's asctime() format.
+-- |This module provides functions for ANSI C's date and time strings.
--
--- ANSI C's asctime() format looks like:
+-- ANSI C's @ctime(3)@/@asctime(3)@ format looks like:
--
-- @Wdy Mon [D]D HH:MM:SS YYYY@
--
-- > day ::= 2DIGIT | SP 1DIGIT
-- > time ::= 2DIGIT ':' 2DIGIT [':' 2DIGIT]
-- > year ::= 4DIGIT
---
--- As you can see, it has no time zone info. "Data.Time.HTTP" will
--- treat it as UTC.
-module Data.Time.Asctime
+module Data.Time.Format.Asctime
( Asctime
, asctime
)
import Data.Tagged
import Data.Time
import Data.Time.Calendar.WeekDate
-import Data.Time.HTTP.Common
+import Data.Time.Format.HTTP.Common
import Prelude.Unicode
--- |The phantom type for conversion between ANSI C's @asctime()@
+-- |The phantom type for conversions between ANSI C's date and time
-- string and 'LocalTime'.
--
-- >>> convertSuccess (LocalTime (ModifiedJulianDay 49662) (TimeOfDay 8 49 37))
{-# INLINE convertAttempt #-}
convertAttempt = parseAttempt' asctime ∘ untag
--- |Parse an ANSI C's @asctime()@ string.
+-- |Parse an ANSI C's date and time string.
asctime ∷ Parser LocalTime
-asctime = do weekDay ← shortWeekDayNameP
- _ ← char ' '
- month ← shortMonthNameP
- _ ← char ' '
- day ← read2'
- _ ← char ' '
- hour ← read2
- _ ← char ':'
- minute ← read2
- _ ← char ':'
- second ← read2
- _ ← char ' '
- year ← read4
+asctime
+ = do weekDay ← shortWeekDayNameP
+ _ ← char ' '
+ month ← shortMonthNameP
+ _ ← char ' '
+ day ← read2'
+ _ ← char ' '
+ hour ← read2
+ _ ← char ':'
+ minute ← read2
+ _ ← char ':'
+ second ← read2
+ _ ← char ' '
+ year ← read4
- gregDay ← assertGregorianDateIsGood year month day
- _ ← assertWeekDayIsGood weekDay gregDay
- tod ← assertTimeOfDayIsGood hour minute second
+ gregDay ← assertGregorianDateIsGood year month day
+ _ ← assertWeekDayIsGood weekDay gregDay
+ tod ← assertTimeOfDayIsGood hour minute second
- return (LocalTime gregDay tod)
+ return (LocalTime gregDay tod)
toAsciiBuilder ∷ LocalTime → AsciiBuilder
toAsciiBuilder localTime
, UnicodeSyntax
#-}
-- |This module provides functions to parse and format HTTP\/1.1 date
--- and time formats.
+-- and time strings
+-- (<http://tools.ietf.org/html/rfc2616#section-3.3>).
--
-- The HTTP\/1.1 specification (RFC 2616) says that HTTP\/1.1 clients
-- and servers which parse the date value MUST accept all the
-- > month = "Jan" | "Feb" | "Mar" | "Apr"
-- > | "May" | "Jun" | "Jul" | "Aug"
-- > | "Sep" | "Oct" | "Nov" | "Dec"
-module Data.Time.HTTP
+module Data.Time.Format.HTTP
( HTTP
, httpDateAndTime
)
import Data.Convertible.Base
import Data.Tagged
import Data.Time
-import Data.Time.Asctime
-import Data.Time.RFC1123
-import Data.Time.RFC733
-import Data.Time.RFC822
-import Data.Time.HTTP.Common
+import Data.Time.Format.Asctime
+import Data.Time.Format.HTTP.Common
+import Data.Time.Format.RFC733
+import Data.Time.Format.RFC822
+import Data.Time.Format.RFC1123
import Prelude.Unicode
--- |FIXME: doc
+-- |The phantom type for conversions between HTTP/1.1 date and time
+-- strings and 'UTCTime'.
+--
+-- >>> convertSuccess (UTCTime (ModifiedJulianDay 49662) 31777)
+-- Tagged "Sun, 06 Nov 1994 08:49:37 GMT"
data HTTP
instance ConvertSuccess UTCTime (Tagged HTTP Ascii) where
OverloadedStrings
, UnicodeSyntax
#-}
-module Data.Time.HTTP.Common
+module Data.Time.Format.HTTP.Common
( shortWeekDayName
, shortWeekDayNameP
, UnicodeSyntax
#-}
-- |This module provides functions to parse and format RFC 1123 date
--- and time formats.
+-- and time strings (<http://tools.ietf.org/html/rfc1123#page-55>).
--
-- The format is basically same as RFC 822, but the syntax for @date@
-- is changed from:
-- to:
--
-- > year ::= 4DIGIT
-module Data.Time.RFC1123
+module Data.Time.Format.RFC1123
( RFC1123
, rfc1123DateAndTime
)
import Data.Tagged
import Data.Time
import Data.Time.Calendar.WeekDate
-import Data.Time.HTTP.Common
-import Data.Time.RFC822.Internal
+import Data.Time.Format.HTTP.Common
+import Data.Time.Format.RFC822.Internal
import Prelude.Unicode
--- FIXME: doc
+-- |The phantom type for conversions between RFC 1123 date and time
+-- strings and 'ZonedTime'.
+--
+-- >>> convertSuccess (ZonedTime (LocalTime (ModifiedJulianDay 49662) (TimeOfDay 8 49 37)) utc)
+-- Tagged "Sun, 06 Nov 1994 08:49:37 GMT"
data RFC1123
instance ConvertSuccess ZonedTime (Tagged RFC1123 Ascii) where
, UnicodeSyntax
#-}
-- |This module provides functions to parse and format RFC 733 date
--- and time formats.
+-- and time strings (<http://tools.ietf.org/html/rfc733#appendix-E>).
--
-- The syntax is as follows:
--
-- > | "N" ; +1
-- > | "Y" ; +12
-- > | ("+" | "-") 4DIGIT ; Local diff: HHMM
-module Data.Time.RFC733
+module Data.Time.Format.RFC733
( RFC733
, rfc733DateAndTime
)
import Data.Tagged
import Data.Time
import Data.Time.Calendar.WeekDate
-import Data.Time.RFC822.Internal
-import Data.Time.HTTP.Common
+import Data.Time.Format.HTTP.Common
+import Data.Time.Format.RFC822.Internal
import Prelude.Unicode
--- FIXME: docs
+-- |The phantom type for conversions between RFC 733 date and time
+-- strings and 'ZonedTime'.
+--
+-- >>> convertSuccess (ZonedTime (LocalTime (ModifiedJulianDay 49662) (TimeOfDay 8 49 37)) utc)
+-- Tagged "Sunday, 06-Nov-1994 08:49:37 GMT"
data RFC733
instance ConvertSuccess ZonedTime (Tagged RFC733 Ascii) where
{-# INLINE convertAttempt #-}
convertAttempt = parseAttempt' rfc733DateAndTime ∘ untag
+-- |Parse an RFC 733 date and time string.
rfc733DateAndTime ∷ Parser ZonedTime
rfc733DateAndTime = dateTime
-- |This module provides functions to parse and format RFC 822 date
--- and time formats.
+-- and time strings (<http://tools.ietf.org/html/rfc822#section-5>).
--
-- The syntax is as follows:
--
-- > | "N" ; +1
-- > | "Y" ; +12
-- > | ("+" | "-") 4DIGIT ; Local diff: HHMM
-module Data.Time.RFC822
+module Data.Time.Format.RFC822
( RFC822
, rfc822DateAndTime
)
where
-import Data.Time.RFC822.Internal
+import Data.Time.Format.RFC822.Internal
, TemplateHaskell
, UnicodeSyntax
#-}
-module Data.Time.RFC822.Internal
+module Data.Time.Format.RFC822.Internal
( RFC822
, rfc822DateAndTime
, rfc822Time
import Data.Tagged
import Data.Time
import Data.Time.Calendar.WeekDate
-import Data.Time.HTTP.Common
+import Data.Time.Format.HTTP.Common
import Prelude.Unicode
--- |FIXME: docs
+-- |The phantom type for conversions between RFC 822 date and time
+-- strings and 'ZonedTime'.
+--
+-- >>> convertSuccess (ZonedTime (LocalTime (ModifiedJulianDay 49662) (TimeOfDay 8 49 37)) utc)
+-- Tagged "Sun, 06 Nov 94 08:49:37 GMT"
data RFC822
instance ConvertSuccess ZonedTime (Tagged RFC822 Ascii) where
import Data.Proxy
import Data.Tagged
import Data.Time
-import Data.Time.Asctime
-import Data.Time.HTTP
-import Data.Time.RFC733
-import Data.Time.RFC822
-import Data.Time.RFC1123
+import Data.Time.Format.Asctime
+import Data.Time.Format.HTTP
+import Data.Time.Format.RFC733
+import Data.Time.Format.RFC822
+import Data.Time.Format.RFC1123
import System.Exit
import Prelude.Unicode
import Test.QuickCheck
≡ cs referenceLocalTime
)
- , property $ \lt → Just lt ≡ fromAttempt (ca (cs (lt ∷ LocalTime)
- ∷ Tagged Asctime Ascii))
+ , property $ \lt → Just lt ≡ fromAttempt (ca (cs (lt ∷ LocalTime) ∷ Tagged Asctime Ascii))
-- RFC733
, property ( fromAttempt (ca (Tagged "Sunday, 06-Nov-94 08:49:37 GMT" ∷ Tagged RFC733 Ascii))
≡ cs referenceZonedTime
)
- , property $ \zt → Just zt ≡ fromAttempt (ca (cs (zt ∷ ZonedTime)
- ∷ Tagged RFC733 Ascii))
+ , property $ \zt → Just zt ≡ fromAttempt (ca (cs (zt ∷ ZonedTime) ∷ Tagged RFC733 Ascii))
-- RFC822
, property ( fromAttempt (ca (Tagged "Sun, 06 Nov 94 08:49:37 GMT" ∷ Tagged RFC822 Ascii))
≡ cs referenceZonedTime
)
- , property $ \zt → Just zt ≡ fromAttempt (ca (cs (zt ∷ ZonedTime)
- ∷ Tagged RFC1123 Ascii))
+ , property $ \zt → Just zt ≡ fromAttempt (ca (cs (zt ∷ ZonedTime) ∷ Tagged RFC1123 Ascii))
-- HTTP
, property ( (Tagged "Sun, 06 Nov 1994 08:49:37 GMT" ∷ Tagged HTTP Ascii)
)
, property $ \ut → Just ut ≡ fromAttempt (ca (cs ut ∷ Tagged HTTP Ascii) ∷ Attempt UTCTime)
, property $ \ut → Just ut ≡ fromAttempt (ca (retagHTTP (cs (ut2lt ut) ∷ Tagged Asctime Ascii)))
- , property $ \ut → Just ut ≡ fromAttempt (ca (retagHTTP (cs (ut2zt ut) ∷ Tagged RFC733 Ascii)))
+ , property $ \ut → Just ut ≡ fromAttempt (ca (retagHTTP (cs (ut2zt ut) ∷ Tagged RFC733 Ascii)))
, property $ \ut → Just (untag ut) ≡ fromAttempt (ca (retagHTTP (cs (ut2zt (untag (ut ∷ Tagged Cent20 UTCTime)))
∷ Tagged RFC822 Ascii)))
, property $ \ut → Just ut ≡ fromAttempt (ca (retagHTTP (cs (ut2zt ut) ∷ Tagged RFC1123 Ascii)))
Synopsis: Parse and format HTTP/1.1 Date and Time strings
Description:
This package provides functionalities to parse and format
- various Date and Time formats allowed in HTTP\/1.1 (RFC 2616).
+ various Date and Time formats allowed in HTTP\/1.1
+ (<http://tools.ietf.org/html/rfc2616#section-3.3>).
Homepage: http://cielonegro.org/HTTPDateTime.html
Bug-Reports: http://static.cielonegro.org/ditz/time-http/
Library
Exposed-modules:
- Data.Time.Asctime
- Data.Time.HTTP
- Data.Time.RFC1123
- Data.Time.RFC733
- Data.Time.RFC822
+ Data.Time.Format.Asctime
+ Data.Time.Format.RFC733
+ Data.Time.Format.RFC822
+ Data.Time.Format.RFC1123
+ Data.Time.Format.HTTP
Other-modules:
- Data.Time.HTTP.Common
- Data.Time.RFC822.Internal
+ Data.Time.Format.HTTP.Common
+ Data.Time.Format.RFC822.Internal
Build-depends:
ascii == 0.0.*,
Test-Suite test-time-http
Type: exitcode-stdio-1.0
- Main-Is: Test/Time/HTTP.hs
+ Main-Is: Test/Time/Format/HTTP.hs
Default-Language: Haskell2010
Build-depends:
QuickCheck == 2.4.*,