Skip to content

Commit

Permalink
Fix wordWithQuotes for a case where the string ends with an esc char
Browse files Browse the repository at this point in the history
  • Loading branch information
adithyaov committed Oct 4, 2024
1 parent 5c0a10a commit 0225f38
Show file tree
Hide file tree
Showing 2 changed files with 55 additions and 14 deletions.
27 changes: 15 additions & 12 deletions core/src/Streamly/Internal/Data/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1756,6 +1756,19 @@ wordWithQuotes keepQuotes tr escChar toRight isSep
FL.Partial s1 -> Continue 0 (WordUnquotedWord s1)
FL.Done b -> Done 0 b

{-# INLINE checkQuoteEnd #-}
checkQuoteEnd s a n ql qr =
if a == qr
then
if n == 1
then if keepQuotes
then processUnquoted s a
else return $ Continue 0 $ WordUnquotedWord s
else processQuoted s a (n - 1) ql qr
else if a == ql
then processQuoted s a (n + 1) ql qr
else processQuoted s a n ql qr

step (WordQuotedSkipPre s) a
| isEsc a = return $ Continue 0 $ WordUnquotedEsc s
| isSep a = return $ Partial 0 $ WordQuotedSkipPre s
Expand Down Expand Up @@ -1792,24 +1805,14 @@ wordWithQuotes keepQuotes tr escChar toRight isSep
b <- fextract s
return $ Partial 0 $ WordQuotedSkipPost b
-}
| otherwise = do
if a == qr
then
if n == 1
then if keepQuotes
then processUnquoted s a
else return $ Continue 0 $ WordUnquotedWord s
else processQuoted s a (n - 1) ql qr
else if a == ql
then processQuoted s a (n + 1) ql qr
else processQuoted s a n ql qr
| otherwise = checkQuoteEnd s a n ql qr
step (WordUnquotedEsc s) a = processUnquoted s a
step (WordQuotedEsc s n ql qr) a =
case tr ql a of
Nothing -> do
res <- fstep s escChar
case res of
FL.Partial s1 -> processQuoted s1 a n ql qr
FL.Partial s1 -> checkQuoteEnd s1 a n ql qr
FL.Done b -> return $ Done 0 b
Just x -> processQuoted s x n ql qr
step (WordQuotedSkipPost b) a =
Expand Down
42 changes: 40 additions & 2 deletions test/Streamly/Test/Data/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,11 +6,10 @@ module Main (main) where

import Control.Applicative ((<|>))
import Control.Exception (displayException)
import Data.Char (isSpace)
import Data.Foldable (for_)
import Data.Word (Word8, Word32, Word64)
import Streamly.Test.Common (listEquals, checkListEqual, chooseInt)
import Test.Hspec (Spec, hspec, describe)
import Test.Hspec.QuickCheck
import Test.QuickCheck
(arbitrary, forAll, elements, Property, property, listOf,
vectorOf, Gen, (.&&.))
Expand All @@ -29,6 +28,9 @@ import qualified Streamly.Internal.Data.Producer as Producer
import qualified Streamly.Internal.Data.Unfold as Unfold
import qualified Test.Hspec as H

import Test.Hspec
import Test.Hspec.QuickCheck

#if MIN_VERSION_QuickCheck(2,14,0)

import Test.QuickCheck (chooseAny)
Expand Down Expand Up @@ -1271,6 +1273,33 @@ takeStartBy_ =
where
predicate = odd
parser = P.takeStartBy_ predicate FL.toList

quotedWordTest :: String -> [String] -> IO ()
quotedWordTest inp expected = do
res <-
S.fold FL.toList
$ catRightsErr
$ S.parseMany quotedWord $ S.fromList inp
res `shouldBe` expected
where
catRightsErr = fmap (either (error . displayException) id)
quotedWord =
let toRQuote x =
case x of
'"' -> Just x
'\'' -> Just x
_ -> Nothing
-- Inside ",
-- * \\ is translated to \
-- * \" is translated to "
trEsc '"' x =
case x of
'\\' -> Just '\\'
'"' -> Just '"'
_ -> Nothing
trEsc _ _ = Nothing
in P.wordWithQuotes False trEsc '\\' toRQuote isSpace FL.toList

-------------------------------------------------------------------------------
-- Main
-------------------------------------------------------------------------------
Expand Down Expand Up @@ -1377,3 +1406,12 @@ main =
prop "takeStartBy_" takeStartBy_

takeProperties

describe "quotedWordTest" $ do
it "Single quote test" $ do
quotedWordTest "'hello\\\\\"world'" ["hello\\\\\"world"]
quotedWordTest "'hello\\'" ["hello\\"]
it "Double quote test" $ do
quotedWordTest
"\"hello\\\"\\\\w\\'orld\""
["hello\"\\w\\'orld"]

0 comments on commit 0225f38

Please sign in to comment.