]> gitweb @ CieloNegro.org - time-http.git/commitdiff
Rename Asctime -> C
authorPHO <pho@cielonegro.org>
Thu, 15 Dec 2011 09:30:18 +0000 (18:30 +0900)
committerPHO <pho@cielonegro.org>
Thu, 15 Dec 2011 09:30:18 +0000 (18:30 +0900)
Ditz-issue: 0a3272772c73cf31486eb2b6691fa38232d3c4c5

Data/Time/Format/C.hs [moved from Data/Time/Format/Asctime.hs with 80% similarity]
Data/Time/Format/HTTP.hs
Data/Time/Format/RFC1123.hs
Data/Time/Format/RFC733.hs
Data/Time/Format/RFC822.hs
Test/Time/Format/HTTP.hs
time-http.cabal

similarity index 80%
rename from Data/Time/Format/Asctime.hs
rename to Data/Time/Format/C.hs
index 8e280b54f4cf1e860b07604ecb53e912f22d3b4b..0c204d5d387177c01e51023dca6e5723e4f48441 100644 (file)
 -- > 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
@@ -33,6 +34,7 @@ import qualified Data.Ascii as A
 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
@@ -40,27 +42,33 @@ import Data.Time.Format.HTTP.Common
 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
@@ -101,6 +109,6 @@ toAsciiBuilder localTime
         ⊕ 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 |])
                ]
index 2dd3aad7e93db660cc6efc2e0690a0029480999e..2c44147295cbe03ce0d0668600a3b13fce0f6492 100644 (file)
@@ -46,6 +46,7 @@
 -- >              | "Sep" | "Oct" | "Nov" | "Dec"
 module Data.Time.Format.HTTP
     ( HTTP
+    , http
     , httpDateAndTime
     )
     where
@@ -57,7 +58,7 @@ import Data.Convertible.Base
 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
@@ -71,6 +72,12 @@ import Prelude.Unicode
 -- 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
@@ -96,17 +103,13 @@ httpDateAndTime
     = 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
index 6d81035b61aafdd9fa7732b96459fba921a0e975..1d4f28eb99c5d328d8d8dc5357d0d8a43ba19231 100644 (file)
@@ -18,6 +18,7 @@
 -- > year ::= 4DIGIT
 module Data.Time.Format.RFC1123
     ( RFC1123
+    , rfc1123
     , rfc1123DateAndTime
     )
     where
@@ -27,6 +28,7 @@ import qualified Data.Ascii as A
 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
@@ -41,6 +43,12 @@ import Prelude.Unicode
 -- 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
index e800310e77976905298800e28c2ff8ae6699e5aa..58dec8dfde636aed9b79bd24eb0335df331c0ab3 100644 (file)
@@ -46,6 +46,7 @@
 -- >               | ("+" | "-") 4DIGIT ; Local diff: HHMM
 module Data.Time.Format.RFC733
     ( RFC733
+    , rfc733
     , rfc733DateAndTime
     )
     where
@@ -55,6 +56,7 @@ import qualified Data.Ascii as A
 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
@@ -69,6 +71,12 @@ import Prelude.Unicode
 -- 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
index 803d040fb901f65df3f1f7dc755c86cdff1b13f2..0d8fcacdacae3b7db0546fcc2498677fbb68803a 100644 (file)
@@ -1,3 +1,6 @@
+{-# 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
index 6555cdbbd01d18c49626c1cdfcf2d9ddb2297370..b443e86919a0dd2dce09579a61e28c9d82e2b453 100644 (file)
@@ -12,7 +12,7 @@ import Data.Convertible.Base
 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
@@ -89,15 +89,15 @@ instance Arbitrary (Tagged Cent20 UTCTime) where
 
 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))
@@ -137,7 +137,7 @@ tests = [ -- Asctime
                      ≡ 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)))
index 678a36bd58048b1cb8902374b7f8231e45e2c557..d30a68a90e325199c4be99c43ea4e95d129a3284 100644 (file)
@@ -27,7 +27,7 @@ Source-Repository head
 
 Library
     Exposed-modules:
-        Data.Time.Format.Asctime
+        Data.Time.Format.C
         Data.Time.Format.RFC733
         Data.Time.Format.RFC822
         Data.Time.Format.RFC1123