Skip to content

Commit 5505ea9

Browse files
authored
Merge pull request #127 from fsoikin/noneOfCodePoints
CodePoint versions of oneOf and noneOf
2 parents c9b486e + 1be0aa1 commit 5505ea9

File tree

3 files changed

+43
-4
lines changed

3 files changed

+43
-4
lines changed

β€ŽCHANGELOG.md

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,9 @@ Breaking changes:
88

99
New features:
1010

11+
- Added primitive parsers `oneOfCodePoints` and `noneOfCodePoints` - `CodePoint`
12+
versions of `oneOf` and `noneOf` respectively. (#127 by @fsoikin)
13+
1114
Bugfixes:
1215

1316
Other improvements:

β€Žsrc/Text/Parsing/Parser/String.purs

Lines changed: 14 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -25,19 +25,23 @@ module Text.Parsing.Parser.String
2525
, whiteSpace
2626
, skipSpaces
2727
, oneOf
28+
, oneOfCodePoints
2829
, noneOf
30+
, noneOfCodePoints
2931
, match
3032
) where
3133

3234
import Prelude hiding (between)
3335

36+
import Control.Alt ((<|>))
37+
import Control.Lazy (defer)
3438
import Control.Monad.State (get, put)
3539
import Data.Array (notElem)
3640
import Data.Char (fromCharCode)
3741
import Data.CodePoint.Unicode (isSpace)
3842
import Data.Foldable (elem)
3943
import Data.Maybe (Maybe(..))
40-
import Data.String (CodePoint, Pattern(..), null, stripPrefix, uncons)
44+
import Data.String (CodePoint, Pattern(..), null, singleton, stripPrefix, uncons)
4145
import Data.String.CodeUnits as SCU
4246
import Data.Tuple (Tuple(..), fst)
4347
import Text.Parsing.Parser (ParseState(..), ParserT, fail)
@@ -121,6 +125,14 @@ oneOf ss = satisfy (flip elem ss) <?> ("one of " <> show ss)
121125
noneOf :: forall m. Monad m => Array Char -> ParserT String m Char
122126
noneOf ss = satisfy (flip notElem ss) <?> ("none of " <> show ss)
123127

128+
-- | Match one of the Unicode characters in the array.
129+
oneOfCodePoints :: forall m. Monad m => Array CodePoint -> ParserT String m CodePoint
130+
oneOfCodePoints ss = satisfyCodePoint (flip elem ss) <|> defer \_ -> fail $ "Expected one of " <> show (singleton <$> ss)
131+
132+
-- | Match any Unicode character not in the array.
133+
noneOfCodePoints :: forall m. Monad m => Array CodePoint -> ParserT String m CodePoint
134+
noneOfCodePoints ss = satisfyCodePoint (flip notElem ss) <|> defer \_ -> fail $ "Expected none of " <> show (singleton <$> ss)
135+
124136
-- | Updates a `Position` by adding the columns and lines in `String`.
125137
updatePosString :: Position -> String -> Position
126138
updatePosString pos str = case uncons str of
@@ -154,4 +166,4 @@ match p = do
154166
-- | This will break at runtime if the definition of CodePoint ever changes
155167
-- | to something other than `newtype CodePoint = CodePoint Int`.
156168
unCodePoint :: CodePoint -> Int
157-
unCodePoint = unsafeCoerce
169+
unCodePoint = unsafeCoerce

β€Žtest/Main.purs

Lines changed: 26 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ import Prelude hiding (between, when)
55
import Control.Alt ((<|>))
66
import Control.Lazy (fix)
77
import Data.Array (some)
8+
import Data.Array as Array
89
import Data.Either (Either(..))
910
import Data.List (List(..), fromFoldable, many)
1011
import Data.List.NonEmpty (cons, cons')
@@ -16,12 +17,12 @@ import Data.Tuple (Tuple(..))
1617
import Effect (Effect)
1718
import Effect.Console (logShow)
1819
import Test.Assert (assert')
19-
import Text.Parsing.Parser (ParseError(..), Parser, ParserT, parseErrorPosition, region, runParser)
20+
import Text.Parsing.Parser (ParseError(..), Parser, ParserT, parseErrorMessage, parseErrorPosition, region, runParser)
2021
import Text.Parsing.Parser.Combinators (between, chainl, endBy1, optionMaybe, sepBy1, try)
2122
import Text.Parsing.Parser.Expr (Assoc(..), Operator(..), buildExprParser)
2223
import Text.Parsing.Parser.Language (haskellDef, haskellStyle, javaStyle)
2324
import Text.Parsing.Parser.Pos (Position(..), initialPos)
24-
import Text.Parsing.Parser.String (anyChar, anyCodePoint, char, eof, satisfy, string, whiteSpace)
25+
import Text.Parsing.Parser.String (anyChar, anyCodePoint, char, eof, noneOfCodePoints, oneOfCodePoints, satisfy, string, whiteSpace)
2526
import Text.Parsing.Parser.Token (TokenParser, letter, makeTokenParser, match, token, when)
2627

2728
parens :: forall m a. Monad m => ParserT String m a -> ParserT String m a
@@ -49,6 +50,14 @@ parseErrorTestPosition p input expected = case runParser input p of
4950
assert' ("expected: " <> show expected <> ", pos: " <> show pos) (expected == pos)
5051
logShow expected
5152

53+
parseErrorTestMessage :: forall s a. Show a => Parser s a -> s -> String -> Effect Unit
54+
parseErrorTestMessage p input expected = case runParser input p of
55+
Right x -> assert' ("ParseError expected '" <> expected <> "' but parsed " <> show x) false
56+
Left err -> do
57+
let msg = parseErrorMessage err
58+
assert' ("expected: " <> expected <> ", message: " <> msg) (expected == msg)
59+
logShow expected
60+
5261
opTest :: Parser String String
5362
opTest = chainl (singleton <$> anyChar) (char '+' $> append) ""
5463

@@ -465,6 +474,21 @@ main = do
465474
sixteenth <- string "𝅑" <|> (singleton <$> char 'x')
466475
pure $ [ SCP.singleton quarter, eighth, letterx, sixteenth ]
467476

477+
parseTest "πŸ€”πŸ’―βœ…πŸ€”πŸ’―" [ "πŸ€”πŸ’―", "βœ…πŸ€”πŸ’―" ] do
478+
none <- Array.many $ noneOfCodePoints $ SCP.toCodePointArray "β“βœ…"
479+
one <- Array.many $ oneOfCodePoints $ SCP.toCodePointArray "πŸ€”πŸ’―βœ…"
480+
pure $ SCP.fromCodePointArray <$> [ none, one ]
481+
482+
parseErrorTestMessage
483+
(noneOfCodePoints $ SCP.toCodePointArray "β“βœ…")
484+
"❓"
485+
"Expected none of [\"❓\",\"βœ…\"]"
486+
487+
parseErrorTestMessage
488+
(oneOfCodePoints $ SCP.toCodePointArray "β“βœ…")
489+
"abc"
490+
"Expected one of [\"❓\",\"βœ…\"]"
491+
468492
parseTest "aa bb" [ "aa", " ", "bb" ] do
469493
aa <- SCU.fromCharArray <$> some letter
470494
w <- whiteSpace

0 commit comments

Comments
Β (0)