X-Git-Url: http://git.cielonegro.org/gitweb.cgi?p=time-http.git;a=blobdiff_plain;f=Data%2FTime%2FHTTP%2FCommon.hs;h=84beeb3665cd9439f66f85bb5bae18197dfbe187;hp=cf5412c28b093eca5844e8286cec529f78f4a6e8;hb=127b8db;hpb=d82d61b7f6627c026d0a61209a6cceda5e572214 diff --git a/Data/Time/HTTP/Common.hs b/Data/Time/HTTP/Common.hs index cf5412c..84beeb3 100644 --- a/Data/Time/HTTP/Common.hs +++ b/Data/Time/HTTP/Common.hs @@ -15,11 +15,13 @@ module Data.Time.HTTP.Common , longMonthName , longMonthNameP - , show2 , show4 + , show2 + , show2' - , read2 , read4 + , read2 + , read2' , show4digitsTZ , read4digitsTZ @@ -29,15 +31,24 @@ module Data.Time.HTTP.Common , assertTimeOfDayIsGood , optionMaybe + , finishOff + + , parseAttempt + , parseAttempt' ) where import Blaze.ByteString.Builder.ByteString as B import Blaze.Text.Int as BT import Control.Applicative +import Control.Exception.Base import Control.Monad -import Data.Ascii (AsciiBuilder) +import Control.Monad.Unicode +import Data.Ascii (Ascii, AsciiBuilder) import qualified Data.Ascii as A +import Data.Attempt import Data.Attoparsec.Char8 as P +import Data.ByteString (ByteString) +import Data.Char import Data.Monoid.Unicode import Data.Fixed import Data.Time @@ -211,6 +222,14 @@ show2 = A.unsafeFromBuilder ∘ go | 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' @@ -225,21 +244,18 @@ read2 = 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 - -fromC ∷ Num n ⇒ Char → n -fromC '0' = 0 -fromC '1' = 1 -fromC '2' = 2 -fromC '3' = 3 -fromC '4' = 4 -fromC '5' = 5 -fromC '6' = 6 -fromC '7' = 7 -fromC '8' = 8 -fromC '9' = 9 -fromC _ = undefined +{-# INLINE digit' #-} +digit' = fromIntegral <$> fromC <$> P.digit + where + {-# INLINE fromC #-} + fromC c = ord c - ord '0' show4digitsTZ ∷ TimeZone → AsciiBuilder show4digitsTZ tz @@ -274,7 +290,7 @@ assertWeekDayIsGood givenWD gregDay (year, month, day) = toGregorian gregDay in unless (givenWD ≡ correctWD) - $ fail + ∘ fail $ concat [ "Gregorian day " , show year , "-" @@ -324,3 +340,28 @@ optionMaybe ∷ Alternative f ⇒ f a → f (Maybe a) {-# INLINE optionMaybe #-} optionMaybe p = option Nothing (Just <$> p) + +finishOff ∷ Parser α → Parser α +{-# INLINE finishOff #-} +finishOff = ((endOfInput *>) ∘ return =≪) + +parseAttempt ∷ Exception e + ⇒ (String → e) + → Parser α + → ByteString + → Attempt α +{-# INLINEABLE parseAttempt #-} +parseAttempt f p bs + = case parseOnly (finishOff p) bs of + Right α → Success α + Left e → Failure $ f e + +parseAttempt' ∷ Parser α → Ascii → Attempt α +{-# INLINE parseAttempt' #-} +parseAttempt' p a = parseAttempt h p bs + where + h ∷ String → StringException + h _ = StringException $ A.toString a + + bs ∷ ByteString + bs = A.toByteString a