Most of the parser just got implemented!
parent
46469bb8f4
commit
f5c552adf7
|
@ -16,6 +16,7 @@ to generate this file without the comments in this block.
|
||||||
, "console"
|
, "console"
|
||||||
, "control"
|
, "control"
|
||||||
, "effect"
|
, "effect"
|
||||||
|
, "integers"
|
||||||
, "maybe"
|
, "maybe"
|
||||||
, "prelude"
|
, "prelude"
|
||||||
, "strings"
|
, "strings"
|
||||||
|
|
|
@ -47,6 +47,11 @@ main = do
|
||||||
Just (Tuple x y) -> show x <> " " <> show y
|
Just (Tuple x y) -> show x <> " " <> show y
|
||||||
Nothing -> "failed"
|
Nothing -> "failed"
|
||||||
|
|
||||||
|
log $ "parsing ident (all first alphanum) in 'ab123-blah' (ident): " <>
|
||||||
|
case parse ident "ab123-blah" of
|
||||||
|
Just (Tuple x y) -> show x <> " " <> show y
|
||||||
|
Nothing -> "failed"
|
||||||
|
|
||||||
-- JUST WORKS
|
-- JUST WORKS
|
||||||
-- isffound $ parse isf "fable"
|
-- isffound $ parse isf "fable"
|
||||||
-- isffound $ parse isf "f"
|
-- isffound $ parse isf "f"
|
||||||
|
|
|
@ -2,10 +2,12 @@ module Parser where
|
||||||
|
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
import Control.Alt (class Alt)
|
import Data.Int as Int
|
||||||
|
|
||||||
|
import Control.Alt (class Alt, (<|>))
|
||||||
import Control.Plus (class Plus, empty)
|
import Control.Plus (class Plus, empty)
|
||||||
import Control.Alternative (class Alternative)
|
import Control.Alternative (class Alternative)
|
||||||
-- TODO: import Control.Lazy (class Lazy)
|
import Control.Lazy (class Lazy)
|
||||||
|
|
||||||
import Data.Array as A
|
import Data.Array as A
|
||||||
import Data.Maybe (Maybe(..))
|
import Data.Maybe (Maybe(..))
|
||||||
|
@ -61,8 +63,8 @@ instance plusParser :: Plus Parser where
|
||||||
instance alternativeParser :: Alternative Parser
|
instance alternativeParser :: Alternative Parser
|
||||||
|
|
||||||
-- TODO: Control.Lazy instance
|
-- TODO: Control.Lazy instance
|
||||||
--instance lazyParser :: Lazy Parser (Array a) where
|
instance lazyParser :: Lazy (Parser a) where
|
||||||
-- defer
|
defer f = Parser \str -> parse (f unit) str
|
||||||
|
|
||||||
-- Generic parsing functions.
|
-- Generic parsing functions.
|
||||||
|
|
||||||
|
@ -113,11 +115,49 @@ string str = case A.uncons (toCharArray str) of
|
||||||
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 :: Parser String
|
ident = do x <- lower
|
||||||
--ident = do x <- lower
|
xs <- A.many alphanum
|
||||||
-- xs <- A.many alphanum
|
pure (fromCharArray $ A.cons x xs)
|
||||||
-- pure (fromCharArray $ A.cons x xs)
|
|
||||||
|
nat :: Parser Int
|
||||||
|
nat = do xs <- A.some digit
|
||||||
|
case Int.fromString (fromCharArray xs) of
|
||||||
|
Nothing -> empty
|
||||||
|
Just x -> pure x
|
||||||
|
|
||||||
|
int :: Parser Int
|
||||||
|
int = do _ <- char '-'
|
||||||
|
n <- nat
|
||||||
|
pure (-n)
|
||||||
|
<|> nat
|
||||||
|
|
||||||
|
-- Handling spacing
|
||||||
|
|
||||||
|
isSpace :: Char -> Boolean
|
||||||
|
isSpace c = A.any (\v -> v == c) [' ', '\t', ' ', '\r', '\n']
|
||||||
|
|
||||||
|
space :: Parser Unit
|
||||||
|
space = do _ <- A.many (sat isSpace)
|
||||||
|
pure unit
|
||||||
|
|
||||||
|
token :: forall a. Parser a -> Parser a
|
||||||
|
token p = do space
|
||||||
|
v <- p
|
||||||
|
_ <- space
|
||||||
|
pure v
|
||||||
|
|
||||||
|
identifier :: Parser String
|
||||||
|
identifier = token ident
|
||||||
|
|
||||||
|
natural :: Parser Int
|
||||||
|
natural = token nat
|
||||||
|
|
||||||
|
integer :: Parser Int
|
||||||
|
integer = token int
|
||||||
|
|
||||||
|
symbol :: String -> Parser String
|
||||||
|
symbol xs = token (string xs)
|
||||||
|
|
||||||
-- TODO: try orElse
|
-- TODO: try orElse
|
||||||
--try :: Parser a -> Parser a
|
--try :: Parser a -> Parser a
|
||||||
|
|
Loading…
Reference in New Issue