--
-- ANSI C's asctime() format looks like:
--
--- @Wdy Mon DD HH:MM:SS YYYY@
+-- @Wdy Mon [D]D HH:MM:SS YYYY@
--
-- The exact syntax is as follows:
--
-- > month ::= "Jan" | "Feb" | "Mar" | "Apr"
-- > | "May" | "Jun" | "Jul" | "Aug"
-- > | "Sep" | "Oct" | "Nov" | "Dec"
--- > day ::= 2DIGIT
+-- > day ::= 2DIGIT | SP 1DIGIT
-- > time ::= 2DIGIT ':' 2DIGIT [':' 2DIGIT]
-- > year ::= 4DIGIT
--
-- |Parse an ANSI C's @asctime()@ string.
asctime ∷ Parser LocalTime
asctime = do weekDay ← shortWeekDayNameP
- _ ← string ", "
+ _ ← char ' '
month ← shortMonthNameP
_ ← char ' '
- day ← read2
+ day ← read2'
_ ← char ' '
hour ← read2
_ ← char ':'
timeOfDay = localTimeOfDay localTime
in
shortWeekDayName week
- ⊕ A.toAsciiBuilder "⊕ "
+ ⊕ A.toAsciiBuilder " "
⊕ shortMonthName month
⊕ A.toAsciiBuilder " "
- ⊕ show2 day
+ ⊕ show2' day
⊕ A.toAsciiBuilder " "
⊕ show2 (todHour timeOfDay)
⊕ A.toAsciiBuilder ":"
, longMonthName
, longMonthNameP
- , show2
, show4
+ , show2
+ , show2'
- , read2
, read4
+ , read2
+ , read2'
, show4digitsTZ
, read4digitsTZ
| i ≥ 0 ∧ i < 100 = BT.integral i
| otherwise = error ("show2: the integer i must satisfy 0 <= i < 100: " ⧺ show i)
+show2' ∷ Integral i ⇒ i → AsciiBuilder
+{-# INLINE show2' #-}
+show2' = A.unsafeFromBuilder ∘ go
+ where
+ go i | i ≥ 0 ∧ i < 10 = B.fromByteString " " ⊕ BT.digit i
+ | i ≥ 0 ∧ i < 100 = BT.integral i
+ | otherwise = error ("show2': the integer i must satisfy 0 <= i < 100: " ⧺ show i)
+
read4 ∷ Num n ⇒ Parser n
{-# INLINEABLE read4 #-}
read4 = do n1 ← digit'
n2 ← digit'
return (n1 * 10 + n2)
+read2' ∷ Num n ⇒ Parser n
+{-# INLINEABLE read2' #-}
+read2' = do n1 ← (char ' ' *> pure 0) <|> digit'
+ n2 ← digit'
+ return (n1 * 10 + n2)
+
digit' ∷ Num n ⇒ Parser n
digit' = fromC <$> P.digit
CONFIGURE_ARGS = -O2 --enable-tests
+RUN_COMMAND = time ./dist/build/test-time-http/test-time-http
include cabal-package.mk
{-# LANGUAGE
- UnicodeSyntax
+ OverloadedStrings
+ , UnicodeSyntax
+ , ViewPatterns
#-}
module Main (main) where
+import Control.Applicative
+import Control.Applicative.Unicode
+import Data.Time
+import qualified Data.Time.Asctime as Asctime
import System.Exit
+import Prelude.Unicode
import Test.QuickCheck
main ∷ IO ()
Failure {} → exitFailure
NoExpectedFailure {} → exitFailure
+instance Arbitrary Day where
+ arbitrary = ModifiedJulianDay <$> arbitrary
+
+instance Arbitrary TimeOfDay where
+ arbitrary
+ = do h ← choose (0, 23)
+ m ← choose (0, 59)
+ s ← choose (0, 60)
+ return $ TimeOfDay h m (fromIntegral (s ∷ Int))
+
+instance Arbitrary LocalTime where
+ arbitrary = LocalTime <$> arbitrary ⊛ arbitrary
+
tests ∷ [Property]
-tests = [
+tests = [ -- Asctime
+ property ( Asctime.fromAscii "Sun Nov 6 08:49:37 1994"
+ ≡ Right (LocalTime (ModifiedJulianDay 49662) (TimeOfDay 8 49 37)) )
+ , property ( Asctime.toAscii (LocalTime (ModifiedJulianDay 49662) (TimeOfDay 8 49 37))
+ ≡ "Sun Nov 6 08:49:37 1994" )
+ , property $ \lt → Right lt ≡ Asctime.fromAscii (Asctime.toAscii lt)
]
Build-depends:
ascii == 0.0.*,
+ attoparsec == 0.9.*,
blaze-builder == 0.3.*,
blaze-textual == 0.2.*,
- attoparsec == 0.9.*,
base == 4.*,
base-unicode-symbols == 0.2.*,
time == 1.2.*
Build-depends:
QuickCheck == 2.4.*,
ascii == 0.0.*,
+ attoparsec == 0.9.*,
blaze-builder == 0.3.*,
blaze-textual == 0.2.*,
- attoparsec == 0.9.*,
base == 4.*,
base-unicode-symbols == 0.2.*,
time == 1.2.*