Lacks Control.Lazy and our parser will be full-featured.

This commit is contained in:
Philippe Pittoli 2024-01-09 08:44:39 +01:00
parent 51fe35c60f
commit c9cf7815de
3 changed files with 54 additions and 8 deletions

View File

@ -12,7 +12,15 @@ to generate this file without the comments in this block.
-} -}
{ name = "parser" { name = "parser"
, dependencies = , dependencies =
[ "arrays", "console", "effect", "maybe", "prelude", "strings", "tuples" ] [ "arrays"
, "console"
, "control"
, "effect"
, "maybe"
, "prelude"
, "strings"
, "tuples"
]
, packages = ./packages.dhall , packages = ./packages.dhall
, sources = [ "src/**/*.purs", "test/**/*.purs" ] , sources = [ "src/**/*.purs", "test/**/*.purs" ]
} }

View File

@ -39,10 +39,6 @@ main :: Effect Unit
main = do main = do
log "🍝" log "🍝"
log $ "parsing 'hello': " <> case parse (stringP "hello") "hello" of
Just (Tuple x y) -> show x <> " " <> show y
Nothing -> "failed"
log $ "parsing the first 'f' in 'fiction' (sat): " <> case parse (sat (\x -> x == 'f')) "fiction" of log $ "parsing the first 'f' in 'fiction' (sat): " <> case parse (sat (\x -> x == 'f')) "fiction" of
Just (Tuple x y) -> show x <> " " <> show y Just (Tuple x y) -> show x <> " " <> show y
Nothing -> "failed" Nothing -> "failed"

View File

@ -2,6 +2,11 @@ module Parser where
import Prelude import Prelude
import Control.Alt (class Alt)
import Control.Plus (class Plus, empty)
import Control.Alternative (class Alternative)
-- TODO: import Control.Lazy (class Lazy)
import Data.Array as A import Data.Array as A
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
@ -41,10 +46,26 @@ instance bindParser :: Bind Parser where
let (Parser p2) = f x let (Parser p2) = f x
in p2 xs in p2 xs
-- Next steps. instance altParser :: Alt Parser where
alt :: forall a. Parser a -> Parser a -> Parser a
alt (Parser p1) (Parser p2) = Parser p
where
p stream = case p1 stream of
Nothing -> p2 stream
Just x -> Just x
instance plusParser :: Plus Parser where
empty :: forall a. Parser a empty :: forall a. Parser a
empty = Parser \_ -> Nothing empty = Parser \_ -> Nothing
instance alternativeParser :: Alternative Parser
-- TODO: Control.Lazy instance
--instance lazyParser :: Lazy Parser (Array a) where
-- defer
-- Generic parsing functions.
sat :: (Char -> Boolean) -> Parser Char sat :: (Char -> Boolean) -> Parser Char
sat p = do x <- item sat p = do x <- item
if p x then pure x else empty if p x then pure x else empty
@ -73,6 +94,12 @@ isAlpha c = A.any (\f -> f c) [isLower, isUpper]
letter :: Parser Char letter :: Parser Char
letter = sat isAlpha letter = sat isAlpha
isAlphaNum :: Char -> Boolean
isAlphaNum c = A.any (\f -> f c) [isAlpha, isDigit]
alphanum :: Parser Char
alphanum = sat isAlphaNum
char :: Char -> Parser Char char :: Char -> Parser Char
char x = sat (_ == x) char x = sat (_ == x)
@ -85,3 +112,18 @@ string str = case A.uncons (toCharArray str) of
Just { head: x, tail: xs } -> do c <- char x Just { head: x, tail: xs } -> do c <- char x
rest <- string (fromCharArray xs) rest <- string (fromCharArray xs)
pure (concat c rest) pure (concat c rest)
-- TODO: A.many requires an instance of Control.Lazy class.
--ident :: Parser String
--ident = do x <- lower
-- xs <- A.many alphanum
-- pure (fromCharArray $ A.cons x xs)
-- TODO: try orElse
--try :: Parser a -> Parser a
--try p = Parser p'
-- where
-- p' = case parse p of
-- Nothing -> p
-- Just
-- orElse, (<|>) :: Parser a -> Parser a -> Parser a