Add an option to preserve quotes in wordQuotedBy

This commit is contained in:
Adithya Kumar 2022-06-07 21:53:34 +05:30
parent c5e0ee5a0c
commit f3b07c2922
3 changed files with 88 additions and 10 deletions

View File

@ -909,21 +909,26 @@ wordFramedBy isEsc isBegin isEnd isSpc =
-- as it encounters any of the closing quotes.
--
-- >>> q = (`elem` ['"', '\''])
-- >>> p = Parser.wordQuotedBy (== '\\') q q id isSpace Fold.toList
-- >>> Stream.parse p $ Stream.fromList "a\"b'c\";'d\"e'f"
-- >>> p kQ = Parser.wordQuotedBy kQ (== '\\') q q id isSpace Fold.toList
--
-- >>> Stream.parse (p False) $ Stream.fromList "a\"b'c\";'d\"e'f ghi"
-- "ab'c;d\"ef"
--
-- >>> Stream.parse (p True) $ Stream.fromList "a\"b'c\";'d\"e'f ghi"
-- "a\"b'c\";'d\"e'f"
--
{-# INLINE wordQuotedBy #-}
wordQuotedBy :: (MonadCatch m, Eq a) =>
(a -> Bool) -- ^ Escape
Bool -- ^ keep the quotes in the output
-> (a -> Bool) -- ^ Escape
-> (a -> Bool) -- ^ left quote
-> (a -> Bool) -- ^ right quote
-> (a -> a) -- ^ get right quote from left quote
-> (a -> Bool) -- ^ word seperator
-> Fold m a b
-> Parser m a b
wordQuotedBy isEsc isBegin isEnd toRight isSpc =
D.toParserK . D.wordQuotedBy isEsc isBegin isEnd toRight isSpc
wordQuotedBy keepQuotes isEsc isBegin isEnd toRight isSpc =
D.toParserK . D.wordQuotedBy keepQuotes isEsc isBegin isEnd toRight isSpc
-- | Given an input stream @[a,b,c,...]@ and a comparison function @cmp@, the
-- parser assigns the element @a@ to the first group, then if @a \`cmp` b@ is

View File

@ -1182,14 +1182,15 @@ data WordQuotedState s b a =
{-# INLINE wordQuotedBy #-}
wordQuotedBy :: (MonadCatch m, Eq a) =>
(a -> Bool) -- ^ Escape
Bool -- ^ keep the quotes in the output
-> (a -> Bool) -- ^ Escape
-> (a -> Bool) -- ^ left quote
-> (a -> Bool) -- ^ right quote
-> (a -> a) -- ^ get right quote from the left quote
-> (a -> Bool) -- ^ word seperator
-> Fold m a b
-> Parser m a b
wordQuotedBy isEsc isBegin isEnd toRight isSep
wordQuotedBy keepQuotes isEsc isBegin isEnd toRight isSep
(Fold fstep finitial fextract) =
Parser step initial extract
@ -1222,7 +1223,10 @@ wordQuotedBy isEsc isBegin isEnd toRight isSep
step (WordQuotedSkipPre s) a
| isEsc a = return $ Continue 0 $ WordUnquotedEsc s
| isSep a = return $ Partial 0 $ WordQuotedSkipPre s
| isBegin a = return $ Continue 0 $ WordQuotedWord s 1 a
| isBegin a =
if keepQuotes
then process s a 1 a
else return $ Continue 0 $ WordQuotedWord s 1 a
| isEnd a =
return $ Error "wordQuotedBy: missing frame start"
| otherwise = processUnquoted s a
@ -1233,12 +1237,15 @@ wordQuotedBy isEsc isBegin isEnd toRight isSep
return $ Partial 0 $ WordQuotedSkipPost b
| otherwise = do
if isBegin a
then return $ Continue 0 $ WordQuotedWord s 1 a
then if keepQuotes
then process s a 1 a
else return $ Continue 0 $ WordQuotedWord s 1 a
else if isEnd a
then return $ Error "wordQuotedBy: missing frame start"
else processUnquoted s a
step (WordQuotedWord s n q) a
| isEsc a = return $ Continue 0 $ WordQuotedEsc s n q
-- XXX Will this ever occur? Will n ever be 0?
| n == 0 && isSep a = do
b <- fextract s
return $ Partial 0 $ WordQuotedSkipPost b
@ -1246,7 +1253,9 @@ wordQuotedBy isEsc isBegin isEnd toRight isSep
if a == toRight q
then
if n == 1
then return $ Continue 0 $ WordUnquotedWord s
then if keepQuotes
then processUnquoted s a
else return $ Continue 0 $ WordUnquotedWord s
else process s a (n - 1) q
else if a == q
then process s a (n + 1) q

View File

@ -1,6 +1,7 @@
module Main (main) where
import Control.Exception (SomeException(..), displayException)
import Data.Foldable (for_)
import Data.Word (Word8, Word32, Word64)
import Streamly.Test.Common (listEquals, checkListEqual, chooseInt)
import Test.Hspec (Spec, hspec, describe)
@ -467,6 +468,68 @@ wordBy =
let wrds = words lst
in if wrds == [] && length lst > 0 then [""] else wrds
parseManyWordQuotedBy :: H.SpecWith ()
parseManyWordQuotedBy =
describe "parseMany wordQuotedBy"
$ for_ testCases
$ \c@(kQ, lQ, rQ, fromLQ, input, expected) -> do
let inpStrm = S.fromList input
esc '\\' = True
esc _ = False
spc ' ' = True
spc _ = False
parser = P.wordQuotedBy kQ esc lQ rQ fromLQ spc FL.toList
result <- H.runIO $ S.toList $ S.parseMany parser inpStrm
H.it (showCase c) $ result `H.shouldBe` expected
where
showCase (kQ, _, _, _, input, expected) =
show kQ ++ ", " ++ input ++ " -> " ++ show expected
testCases =
[ ( True
, (== '\'')
, (== '\'')
, id
, "The quick brown fox"
, ["The", "quick", "brown", "fox"])
, ( True
, (== '\'')
, (== '\'')
, id
, "The' quick brown' fox"
, ["The' quick brown'", "fox"])
, ( False
, (== '\'')
, (== '\'')
, id
, "The' quick brown' fox"
, ["The quick brown", "fox"])
, ( True
, (== '[')
, (== '[')
, \x -> if x == '[' then ']' else error "Not an opening quote."
, "The[ quick brown] fox"
, ["The[ quick brown]", "fox"])
, ( True
, (== '[')
, (== '[')
, \x -> if x == '[' then ']' else error "Not an opening quote."
, "The[ qui[ck] brown] \\ f[ ox]"
, ["The[ qui[ck] brown]", " f[ ox]"])
, ( False
, (== '[')
, (== '[')
, \x -> if x == '[' then ']' else error "Not an opening quote."
, "The[ qui[ck] brown] fox"
, ["The qui[ck] brown", "fox"])
]
-- splitWithPass :: Property
-- splitWithPass =
-- forAll (listOf (chooseInt (0, 1))) $ \ls ->
@ -1106,6 +1169,7 @@ main =
prop ("P.takeP = Prelude.take") takeP
prop "P.groupBy = Prelude.head . Prelude.groupBy" groupBy
prop "many (P.wordBy ' ') = words'" wordBy
parseManyWordQuotedBy
prop "choice" choice
-- prop "" splitWithPass
-- prop "" splitWithFailLeft