-- > day ::= 2DIGIT | SP 1DIGIT
-- > time ::= 2DIGIT ':' 2DIGIT [':' 2DIGIT]
-- > year ::= 4DIGIT
-module Data.Time.Format.Asctime
- ( Asctime
- , asctime
+module Data.Time.Format.C
+ ( C
+ , c
+ , cDateAndTime
)
where
import Control.Applicative
import Data.Attoparsec.Char8
import Data.Convertible.Base
import Data.Monoid.Unicode
+import Data.Proxy
import Data.Tagged
import Data.Time
import Data.Time.Calendar.WeekDate
import Prelude.Unicode
-- |The phantom type for conversions between ANSI C's date and time
--- string and 'LocalTime'.
+-- strings and 'LocalTime'.
--
-- >>> convertSuccess (LocalTime (ModifiedJulianDay 49662) (TimeOfDay 8 49 37))
-- Tagged "Sun Nov 6 08:49:37 1994"
-data Asctime
+data C
-instance ConvertSuccess LocalTime (Tagged Asctime Ascii) where
+-- |The proxy for conversions between ANSI C's date and time strings
+-- and 'LocalTime'.
+c ∷ Proxy C
+{-# INLINE CONLIKE c #-}
+c = Proxy
+
+instance ConvertSuccess LocalTime (Tagged C Ascii) where
{-# INLINE convertSuccess #-}
convertSuccess = (A.fromAsciiBuilder <$>) ∘ cs
-instance ConvertSuccess LocalTime (Tagged Asctime AsciiBuilder) where
+instance ConvertSuccess LocalTime (Tagged C AsciiBuilder) where
{-# INLINE convertSuccess #-}
convertSuccess = Tagged ∘ toAsciiBuilder
-instance ConvertAttempt (Tagged Asctime Ascii) LocalTime where
+instance ConvertAttempt (Tagged C Ascii) LocalTime where
{-# INLINE convertAttempt #-}
- convertAttempt = parseAttempt' asctime ∘ untag
+ convertAttempt = parseAttempt' cDateAndTime ∘ untag
-- |Parse an ANSI C's date and time string.
-asctime ∷ Parser LocalTime
-asctime
+cDateAndTime ∷ Parser LocalTime
+cDateAndTime
= do weekDay ← shortWeekDayNameP
_ ← char ' '
month ← shortMonthNameP
⊕ A.toAsciiBuilder " "
⊕ show4 year
-deriveAttempts [ ([t| LocalTime |], [t| Tagged Asctime Ascii |])
- , ([t| LocalTime |], [t| Tagged Asctime AsciiBuilder |])
+deriveAttempts [ ([t| LocalTime |], [t| Tagged C Ascii |])
+ , ([t| LocalTime |], [t| Tagged C AsciiBuilder |])
]
-- > | "Sep" | "Oct" | "Nov" | "Dec"
module Data.Time.Format.HTTP
( HTTP
+ , http
, httpDateAndTime
)
where
import Data.Proxy
import Data.Tagged
import Data.Time
-import Data.Time.Format.Asctime
+import Data.Time.Format.C
import Data.Time.Format.HTTP.Common
import Data.Time.Format.RFC733
import Data.Time.Format.RFC822
-- Tagged "Sun, 06 Nov 1994 08:49:37 GMT"
data HTTP
+-- |The proxy for conversions between ANSI HTTP/1.1 date and time
+-- strings and 'UTCTime'.
+http ∷ Proxy HTTP
+{-# INLINE CONLIKE http #-}
+http = Proxy
+
instance ConvertSuccess UTCTime (Tagged HTTP Ascii) where
{-# INLINE convertSuccess #-}
convertSuccess = (A.fromAsciiBuilder <$>) ∘ cs
= choice [ zonedTimeToUTC <$> try rfc1123DateAndTime
, zonedTimeToUTC <$> try rfc733DateAndTime
, zonedTimeToUTC <$> try rfc822DateAndTime
- , localTimeToUTC utc <$> asctime
+ , localTimeToUTC utc <$> cDateAndTime
]
toAsciiBuilder ∷ UTCTime → AsciiBuilder
{-# INLINE toAsciiBuilder #-}
toAsciiBuilder = flip proxy rfc1123 ∘ cs ∘ ut2zt
where
- rfc1123 ∷ Proxy RFC1123
- {-# INLINE CONLIKE rfc1123 #-}
- rfc1123 = Proxy
-
ut2zt ∷ UTCTime → ZonedTime
{-# INLINE ut2zt #-}
ut2zt = utcToZonedTime gmt
-- > year ::= 4DIGIT
module Data.Time.Format.RFC1123
( RFC1123
+ , rfc1123
, rfc1123DateAndTime
)
where
import Data.Attoparsec.Char8
import Data.Convertible.Base
import Data.Monoid.Unicode
+import Data.Proxy
import Data.Tagged
import Data.Time
import Data.Time.Calendar.WeekDate
-- Tagged "Sun, 06 Nov 1994 08:49:37 GMT"
data RFC1123
+-- |The proxy for conversions between RFC 1123 date and time strings
+-- and 'ZonedTime'.
+rfc1123 ∷ Proxy RFC1123
+{-# INLINE CONLIKE rfc1123 #-}
+rfc1123 = Proxy
+
instance ConvertSuccess ZonedTime (Tagged RFC1123 Ascii) where
{-# INLINE convertSuccess #-}
convertSuccess = (A.fromAsciiBuilder <$>) ∘ cs
-- > | ("+" | "-") 4DIGIT ; Local diff: HHMM
module Data.Time.Format.RFC733
( RFC733
+ , rfc733
, rfc733DateAndTime
)
where
import Data.Attoparsec.Char8
import Data.Convertible.Base
import Data.Monoid.Unicode
+import Data.Proxy
import Data.Tagged
import Data.Time
import Data.Time.Calendar.WeekDate
-- Tagged "Sunday, 06-Nov-1994 08:49:37 GMT"
data RFC733
+-- |The proxy for conversions between RFC 733 date and time strings
+-- and 'ZonedTime'.
+rfc733 ∷ Proxy RFC733
+{-# INLINE CONLIKE rfc733 #-}
+rfc733 = Proxy
+
instance ConvertSuccess ZonedTime (Tagged RFC733 Ascii) where
{-# INLINE convertSuccess #-}
convertSuccess = (A.fromAsciiBuilder <$>) ∘ cs
+{-# LANGUAGE
+ UnicodeSyntax
+ #-}
-- |This module provides functions to parse and format RFC 822 date
-- and time strings (<http://tools.ietf.org/html/rfc822#section-5>).
--
-- > | ("+" | "-") 4DIGIT ; Local diff: HHMM
module Data.Time.Format.RFC822
( RFC822
+ , rfc822
, rfc822DateAndTime
)
where
+import Data.Proxy
import Data.Time.Format.RFC822.Internal
+
+-- |The proxy for conversions between RFC 822 date and time strings
+-- and 'ZonedTime'.
+rfc822 ∷ Proxy RFC822
+{-# INLINE CONLIKE rfc822 #-}
+rfc822 = Proxy
import Data.Proxy
import Data.Tagged
import Data.Time
-import Data.Time.Format.Asctime
+import Data.Time.Format.C
import Data.Time.Format.HTTP
import Data.Time.Format.RFC733
import Data.Time.Format.RFC822
tests ∷ [Property]
tests = [ -- Asctime
- property ( fromAttempt (ca (Tagged "Sun Nov 6 08:49:37 1994" ∷ Tagged Asctime Ascii))
+ property ( fromAttempt (ca (Tagged "Sun Nov 6 08:49:37 1994" ∷ Tagged C Ascii))
≡ Just referenceLocalTime
)
- , property ( (Tagged "Sun Nov 6 08:49:37 1994" ∷ Tagged Asctime Ascii)
+ , property ( (Tagged "Sun Nov 6 08:49:37 1994" ∷ Tagged C Ascii)
≡ cs referenceLocalTime
)
- , property $ \lt → Just lt ≡ fromAttempt (ca (cs (lt ∷ LocalTime) ∷ Tagged Asctime Ascii))
+ , property $ \lt → Just lt ≡ fromAttempt (ca (cs (lt ∷ LocalTime) ∷ Tagged C Ascii))
-- RFC733
, property ( fromAttempt (ca (Tagged "Sunday, 06-Nov-94 08:49:37 GMT" ∷ Tagged RFC733 Ascii))
≡ cs referenceUTCTime
)
, 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 (ut2lt ut) ∷ Tagged C 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)))
Library
Exposed-modules:
- Data.Time.Format.Asctime
+ Data.Time.Format.C
Data.Time.Format.RFC733
Data.Time.Format.RFC822
Data.Time.Format.RFC1123