Skip to content

Commit 8f78cf8

Browse files
committed
takeWhile
1 parent 66b5222 commit 8f78cf8

File tree

4 files changed

+49
-8
lines changed

4 files changed

+49
-8
lines changed

CHANGELOG.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,8 @@ Breaking changes:
1010

1111
New features:
1212

13+
- Add `Parsing.String.Basic.takeWhile` (#218 by @jamesdbrock)
14+
1315
Other improvements:
1416

1517
## [v10.1.0](https://github.com/purescript-contrib/purescript-parsing/releases/tag/v10.1.0) - 2022-11-10

src/Parsing.purs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -430,8 +430,7 @@ failWithPosition message pos = throwError (ParseError message pos)
430430
-- |
431431
-- | lmap (parseErrorHuman input 30) $ runParser input do
432432
-- | inContext ("Megacity list: " <> _) do
433-
-- | cityname <- inContext ("city name: " <> _) do
434-
-- | fst <$> match (skipMany letter)
433+
-- | cityname <- inContext ("city name: " <> _) (takeWhile isLetter)
435434
-- | skipSpaces
436435
-- | population <- inContext ("population: " <> _) intDecimal
437436
-- | pure $ Tuple cityname population

src/Parsing/String/Basic.purs

Lines changed: 37 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,9 @@
22
-- |
33
-- | #### unicode dependency
44
-- |
5-
-- | Some of the parsers in this module depend on the __unicode__ package.
5+
-- | Some of the parsers in this module depend on the
6+
-- | [__unicode__](https://pursuit.purescript.org/packages/purescript-unicode)
7+
-- | package.
68
-- | The __unicode__ package is large; about half a megabyte unminified.
79
-- | If code which depends on __parsing__ is “tree-shaken”
810
-- | “dead-code-eliminated,” then
@@ -24,6 +26,7 @@ module Parsing.String.Basic
2426
, alphaNum
2527
, intDecimal
2628
, number
29+
, takeWhile
2730
, whiteSpace
2831
, skipSpaces
2932
, oneOf
@@ -41,9 +44,11 @@ import Data.Int as Data.Int
4144
import Data.Maybe (Maybe(..))
4245
import Data.Number (infinity, nan)
4346
import Data.Number as Data.Number
44-
import Data.String (CodePoint, singleton, takeWhile)
47+
import Data.String (CodePoint, singleton)
48+
import Data.String as String
4549
import Data.String.CodePoints (codePointFromChar)
4650
import Data.String.CodeUnits as SCU
51+
import Data.String.CodeUnits as String.CodeUnits
4752
import Data.Tuple (fst)
4853
import Parsing (ParserT, fail)
4954
import Parsing.Combinators (choice, tryRethrow, (<?>), (<|>), (<~?>))
@@ -161,7 +166,7 @@ whiteSpace = fst <$> match skipSpaces
161166
-- | Always succeeds. Will only consume when some characters are skipped.
162167
skipSpaces :: forall m. ParserT String m Unit
163168
skipSpaces = consumeWith \input -> do
164-
let consumed = takeWhile isSpace input
169+
let consumed = String.takeWhile isSpace input
165170
let remainder = SCU.drop (SCU.length consumed) input
166171
Right { value: unit, consumed, remainder }
167172

@@ -180,3 +185,32 @@ oneOfCodePoints ss = satisfyCodePoint (flip elem ss) <~?> \_ -> "one of " <> sho
180185
-- | Match any Unicode character not in the array.
181186
noneOfCodePoints :: forall m. Array CodePoint -> ParserT String m CodePoint
182187
noneOfCodePoints ss = satisfyCodePoint (flip notElem ss) <~?> \_ -> "none of " <> show (singleton <$> ss)
188+
189+
-- | Take the longest `String` for which the characters satisfy the
190+
-- | predicate.
191+
-- |
192+
-- | See [__`Data.CodePoint.Unicode`__](https://pursuit.purescript.org/packages/purescript-unicode/docs/Data.CodePoint.Unicode)
193+
-- | for useful predicates.
194+
-- |
195+
-- | Example:
196+
-- |
197+
-- | ```
198+
-- | runParser "Tackling the Awkward Squad" do
199+
-- | takeWhile Data.CodePoint.Unicode.isLetter
200+
-- | ```
201+
-- | ---
202+
-- | ```
203+
-- | Right "Tackling"
204+
-- | ```
205+
takeWhile :: forall m. (CodePoint -> Boolean) -> ParserT String m String
206+
takeWhile predicate =
207+
consumeWith \s ->
208+
let
209+
value = String.takeWhile predicate s
210+
in
211+
Right
212+
{ consumed: value
213+
, remainder: SCU.drop (SCU.length value) s
214+
, value
215+
}
216+

test/Main.purs

Lines changed: 9 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ import Control.Monad.State (State, lift, modify, runState)
1313
import Data.Array (some, toUnfoldable)
1414
import Data.Array as Array
1515
import Data.Bifunctor (lmap, rmap)
16+
import Data.CodePoint.Unicode as CodePoint.Unicode
1617
import Data.Either (Either(..), either, fromLeft, hush)
1718
import Data.Foldable (oneOf)
1819
import Data.List (List(..), fromFoldable, (:))
@@ -41,7 +42,7 @@ import Parsing.Combinators.Array as Combinators.Array
4142
import Parsing.Expr (Assoc(..), Operator(..), buildExprParser)
4243
import Parsing.Language (haskellDef, haskellStyle, javaStyle)
4344
import Parsing.String (anyChar, anyCodePoint, anyTill, char, eof, match, parseErrorHuman, regex, rest, satisfy, string, takeN)
44-
import Parsing.String.Basic (intDecimal, letter, noneOfCodePoints, number, oneOfCodePoints, skipSpaces, whiteSpace)
45+
import Parsing.String.Basic (intDecimal, letter, noneOfCodePoints, number, oneOfCodePoints, skipSpaces, takeWhile, whiteSpace)
4546
import Parsing.String.Basic as String.Basic
4647
import Parsing.String.Replace (breakCap, replace, replaceT, splitCap, splitCapT)
4748
import Parsing.Token (TokenParser, makeTokenParser, token, when)
@@ -712,8 +713,7 @@ main = do
712713
assertEqual' "region 1"
713714
{ actual: runParser input do
714715
inContext ("Megacity list: " <> _) do
715-
cityname <- inContext ("city name: " <> _) do
716-
fst <$> match (Combinators.skipMany letter)
716+
cityname <- inContext ("city name: " <> _) (takeWhile CodePoint.Unicode.isLetter)
717717
skipSpaces
718718
population <- inContext ("population: " <> _) intDecimal
719719
pure $ Tuple cityname population
@@ -725,6 +725,12 @@ main = do
725725
, expected: Left $ ParseError "Expected 'c'" (Position { index: 1, column: 2, line: 1 })
726726
}
727727

728+
assertEqual' "takeWhile 1"
729+
{ actual: runParser "Tackling the Awkward" do
730+
takeWhile CodePoint.Unicode.isLetter <* string " the Awkward"
731+
, expected: Right "Tackling"
732+
}
733+
728734
log "\nTESTS number\n"
729735

730736
-- assert' "Number.fromString" $ Just infinity == Data.Number.fromString "Infinity"

0 commit comments

Comments
 (0)