Skip to content

Commit

Permalink
Merge pull request haskell#1035 from haskell/issue-1013-space-before-…
Browse files Browse the repository at this point in the history
…zulu

Resolves haskell#1013: Don't accept space before Zulu/TZ offset
  • Loading branch information
phadej authored Jun 9, 2023
2 parents 14d796e + 64d4c5f commit 212c324
Show file tree
Hide file tree
Showing 2 changed files with 20 additions and 12 deletions.
5 changes: 1 addition & 4 deletions attoparsec-iso8601/src/Data/Attoparsec/Time.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,8 +24,7 @@ module Data.Attoparsec.Time
) where

import Control.Applicative ((<|>))
import Control.Monad (void, when)
import Data.Attoparsec.Text (Parser, char, digit, option, anyChar, peekChar, peekChar', takeWhile1, satisfy)
import Data.Attoparsec.Text (Parser, char, digit, option, anyChar, peekChar, takeWhile1, satisfy)
import Data.Bits ((.&.))
import Data.Char (isDigit, ord)
import Data.Fixed (Pico, Fixed (..))
Expand Down Expand Up @@ -136,8 +135,6 @@ seconds = do
-- zero. (This makes some speedups possible.)
timeZone :: Parser (Maybe Local.TimeZone)
timeZone = do
let maybeSkip c = do ch <- peekChar'; when (ch == c) (void anyChar)
maybeSkip ' '
ch <- satisfy $ \c -> c == 'Z' || c == '+' || c == '-'
if ch == 'Z'
then return Nothing
Expand Down
27 changes: 19 additions & 8 deletions tests/UnitTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -54,14 +54,14 @@ import Data.Maybe (fromMaybe)
import Data.Scientific (Scientific, scientific)
import Data.Tagged (Tagged(..))
import Data.Text (Text)
import Data.Time (UTCTime)
import Data.Time (UTCTime, ZonedTime)
import Data.Time.Format.Compat (parseTimeM, defaultTimeLocale)
import GHC.Generics (Generic)
import GHC.Generics.Generically (Generically (..))
import Instances ()
import Numeric.Natural (Natural)
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.HUnit (Assertion, assertFailure, assertEqual, testCase, (@?=))
import Test.Tasty.HUnit (Assertion, assertFailure, assertEqual, testCase, testCaseSteps, (@?=))
import Text.Printf (printf)
import UnitTests.NullaryConstructors (nullaryConstructors)
import qualified Data.ByteString as S
Expand Down Expand Up @@ -188,8 +188,8 @@ utcTimeGood = do

-- Test that a few non-timezone qualified timestamp formats get
-- rejected if decoding to UTCTime.
utcTimeBad :: Assertion
utcTimeBad = do
utcTimeBad :: (String -> IO ()) -> Assertion
utcTimeBad info = do
verifyFailParse "2000-01-01T12:13:00" -- missing Zulu time not allowed (some TZ required)
verifyFailParse "2000-01-01 12:13:00" -- missing Zulu time not allowed (some TZ required)
verifyFailParse "2000-01-01" -- date only not OK
Expand All @@ -199,10 +199,21 @@ utcTimeBad = do
verifyFailParse "2015-01-03 12:13:00.Z" -- decimal at the end but no digits
verifyFailParse "2015-01-03 12:13.000Z" -- decimal at the end, but no seconds
verifyFailParse "2015-01-03 23:59:61Z" -- exceeds allowed seconds per day
verifyFailParse "2015-01-03 12:13:00 Z" -- space before Zulu
verifyFailParse "2015-01-03 12:13:00 +00:00" -- space before offset
where
verifyFailParse (s :: LT.Text) =
let (dec :: Maybe UTCTime) = decode . LT.encodeUtf8 $ LT.concat ["\"", s, "\""] in
assertEqual "verify failure" Nothing dec
verifyFailParse :: LT.Text -> Assertion
verifyFailParse s = do
info (LT.unpack s)
let bs = LT.encodeUtf8 $ LT.concat ["\"", s, "\""]
let decU = decode bs :: Maybe UTCTime
let decZ = decode bs :: Maybe ZonedTime
assertIsNothing "verify failure UTCTime" decU
assertIsNothing "verify failure ZonedTime" decZ

assertIsNothing :: Show a => String -> Maybe a -> Assertion
assertIsNothing _ Nothing = return ()
assertIsNothing err (Just a) = assertFailure $ err ++ " " ++ show a

-- Non identifier keys should be escaped & enclosed in brackets
formatErrorExample :: Assertion
Expand Down Expand Up @@ -787,7 +798,7 @@ tests = testGroup "unit" [
]
, testGroup "utctime" [
testCase "good" utcTimeGood
, testCase "bad" utcTimeBad
, testCaseSteps "bad" utcTimeBad
]
, testGroup "formatError" [
testCase "example 1" formatErrorExample
Expand Down

0 comments on commit 212c324

Please sign in to comment.