Parser++
This commit is contained in:
parent
96103ea665
commit
fbfa7c7d48
3 changed files with 128 additions and 81 deletions
|
|
@ -12,7 +12,7 @@ to generate this file without the comments in this block.
|
||||||
-}
|
-}
|
||||||
{ name = "parser"
|
{ name = "parser"
|
||||||
, dependencies =
|
, dependencies =
|
||||||
[ "console", "effect", "maybe", "prelude", "strings", "tuples" ]
|
[ "arrays", "console", "effect", "maybe", "prelude", "strings", "tuples" ]
|
||||||
, packages = ./packages.dhall
|
, packages = ./packages.dhall
|
||||||
, sources = [ "src/**/*.purs", "test/**/*.purs" ]
|
, sources = [ "src/**/*.purs", "test/**/*.purs" ]
|
||||||
}
|
}
|
||||||
|
|
|
||||||
132
src/Main.purs
132
src/Main.purs
|
|
@ -1,99 +1,51 @@
|
||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
import Prelude
|
import Parser
|
||||||
|
|
||||||
|
import Prelude (Unit, discard, show, ($), (==), (<>))
|
||||||
|
|
||||||
import Effect (Effect)
|
import Effect (Effect)
|
||||||
import Effect.Console (log)
|
import Effect.Console (log)
|
||||||
|
|
||||||
import Data.Maybe (Maybe(..))
|
import Data.Maybe (Maybe(..))
|
||||||
import Data.Tuple (Tuple(..))
|
import Data.Tuple (Tuple(..))
|
||||||
import Data.String.CodeUnits (uncons)
|
|
||||||
|
|
||||||
newtype Parser v = Parser (String -> Maybe (Tuple v String))
|
-- isf :: Parser Boolean
|
||||||
parse :: forall a. Parser a -> (String -> Maybe (Tuple a String))
|
-- isf = (_ == 'f') <$> itemP
|
||||||
parse (Parser p) = p
|
--
|
||||||
|
-- isf2 :: Parser Boolean
|
||||||
itemP :: Parser Char
|
-- isf2 = (==) <$> itemP <*> pure 'f'
|
||||||
itemP = Parser p
|
--
|
||||||
where p str = case uncons str of
|
-- isf3 :: Parser Boolean
|
||||||
Nothing -> Nothing
|
-- isf3 = charP 'f'
|
||||||
Just { head: x, tail: xs } -> Just (Tuple x xs)
|
--
|
||||||
|
-- ishi :: Parser (Tuple Boolean Boolean)
|
||||||
instance functorParser :: Functor Parser where
|
-- ishi = Tuple <$> ((_ == 'h') <$> itemP) <*> ((_ == 'i') <$> itemP)
|
||||||
map f (Parser p) =
|
--
|
||||||
Parser $ \s0 -> do
|
-- ishi2 :: Parser (Tuple Boolean Boolean)
|
||||||
(Tuple x s1) <- p s0
|
-- ishi2 = ado
|
||||||
pure (Tuple (f x) s1)
|
-- h <- itemP
|
||||||
|
-- i <- itemP
|
||||||
instance applyParser :: Apply Parser where
|
-- in Tuple (h == 'h') (i == 'i')
|
||||||
apply (Parser p1) (Parser p2)
|
--
|
||||||
= Parser $ \str -> case p1 str of
|
-- isffound :: Maybe (Tuple Boolean String) -> Effect Unit
|
||||||
Nothing -> Nothing
|
-- isffound maybe = case maybe of
|
||||||
Just (Tuple x1 xs1) -> case p2 xs1 of
|
-- Nothing -> log "no more data"
|
||||||
Nothing -> Nothing
|
-- Just (Tuple b str) -> do
|
||||||
Just (Tuple x2 xs2) -> Just (Tuple (x1 x2) xs2)
|
-- let toprint = if b then "FOUND IT" else "not found"
|
||||||
|
-- log $ toprint <> ", rest: " <> str
|
||||||
instance applicativeParser :: Applicative Parser where
|
|
||||||
pure a = Parser $ \str -> Just (Tuple a str)
|
|
||||||
|
|
||||||
instance bindParser :: Bind Parser where
|
|
||||||
bind (Parser p) f = Parser $ \str -> case p str of
|
|
||||||
Nothing -> Nothing
|
|
||||||
Just (Tuple x xs) ->
|
|
||||||
let (Parser p2) = f x
|
|
||||||
in p2 xs
|
|
||||||
|
|
||||||
charP :: Char -> Parser Boolean
|
|
||||||
charP c = (_ == c) <$> itemP
|
|
||||||
|
|
||||||
isf :: Parser Boolean
|
|
||||||
isf = (_ == 'f') <$> itemP
|
|
||||||
|
|
||||||
isf2 :: Parser Boolean
|
|
||||||
isf2 = (==) <$> itemP <*> pure 'f'
|
|
||||||
|
|
||||||
isf3 :: Parser Boolean
|
|
||||||
isf3 = charP 'f'
|
|
||||||
|
|
||||||
ishi :: Parser (Tuple Boolean Boolean)
|
|
||||||
ishi = Tuple <$> ((_ == 'h') <$> itemP) <*> ((_ == 'i') <$> itemP)
|
|
||||||
|
|
||||||
ishi2 :: Parser (Tuple Boolean Boolean)
|
|
||||||
ishi2 = ado
|
|
||||||
h <- itemP
|
|
||||||
i <- itemP
|
|
||||||
in Tuple (h == 'h') (i == 'i')
|
|
||||||
|
|
||||||
isffound :: Maybe (Tuple Boolean String) -> Effect Unit
|
|
||||||
isffound maybe = case maybe of
|
|
||||||
Nothing -> log "no more data"
|
|
||||||
Just (Tuple b str) -> do
|
|
||||||
let toprint = if b then "FOUND IT" else "not found"
|
|
||||||
log $ toprint <> ", rest: " <> str
|
|
||||||
|
|
||||||
main :: Effect Unit
|
main :: Effect Unit
|
||||||
main = do
|
main = do
|
||||||
log "🍝"
|
log "🍝"
|
||||||
|
|
||||||
log $ "parsing 'hi': " <> case parse ishi2 "hi" of
|
log $ "parsing 'hello': " <> case parse (stringP "hello") "hello" of
|
||||||
Just (Tuple x y) -> show x <> " " <> show y
|
Just (Tuple x y) -> show x <> " " <> show y
|
||||||
Nothing -> "coudn't parse two letters"
|
Nothing -> "failed"
|
||||||
|
|
||||||
log $ "parsing 'no': " <> case parse ishi2 "no" 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 -> "coudn't parse two letters"
|
Nothing -> "failed"
|
||||||
|
|
||||||
log $ "parsing 'ho': " <> case parse ishi2 "ho" of
|
|
||||||
Just (Tuple x y) -> show x <> " " <> show y
|
|
||||||
Nothing -> "coudn't parse two letters"
|
|
||||||
|
|
||||||
log $ "parsing 'ni': " <> case parse ishi2 "ni" of
|
|
||||||
Just (Tuple x y) -> show x <> " " <> show y
|
|
||||||
Nothing -> "coudn't parse two letters"
|
|
||||||
|
|
||||||
log $ "parsing '': " <> case parse ishi2 "" of
|
|
||||||
Just (Tuple x y) -> show x <> " " <> show y
|
|
||||||
Nothing -> "coudn't parse two letters"
|
|
||||||
|
|
||||||
|
|
||||||
-- JUST WORKS
|
-- JUST WORKS
|
||||||
-- isffound $ parse isf "fable"
|
-- isffound $ parse isf "fable"
|
||||||
|
|
@ -106,4 +58,24 @@ main = do
|
||||||
-- isffound $ parse isf2 "n"
|
-- isffound $ parse isf2 "n"
|
||||||
-- isffound $ parse isf2 ""
|
-- isffound $ parse isf2 ""
|
||||||
|
|
||||||
|
-- log $ "parsing 'hi': " <> case parse ishi2 "hi" of
|
||||||
|
-- Just (Tuple x y) -> show x <> " " <> show y
|
||||||
|
-- Nothing -> "coudn't parse two letters"
|
||||||
|
--
|
||||||
|
-- log $ "parsing 'no': " <> case parse ishi2 "no" of
|
||||||
|
-- Just (Tuple x y) -> show x <> " " <> show y
|
||||||
|
-- Nothing -> "coudn't parse two letters"
|
||||||
|
--
|
||||||
|
-- log $ "parsing 'ho': " <> case parse ishi2 "ho" of
|
||||||
|
-- Just (Tuple x y) -> show x <> " " <> show y
|
||||||
|
-- Nothing -> "coudn't parse two letters"
|
||||||
|
--
|
||||||
|
-- log $ "parsing 'ni': " <> case parse ishi2 "ni" of
|
||||||
|
-- Just (Tuple x y) -> show x <> " " <> show y
|
||||||
|
-- Nothing -> "coudn't parse two letters"
|
||||||
|
--
|
||||||
|
-- log $ "parsing '': " <> case parse ishi2 "" of
|
||||||
|
-- Just (Tuple x y) -> show x <> " " <> show y
|
||||||
|
-- Nothing -> "coudn't parse two letters"
|
||||||
|
|
||||||
log "end"
|
log "end"
|
||||||
|
|
|
||||||
75
src/Parser.purs
Normal file
75
src/Parser.purs
Normal file
|
|
@ -0,0 +1,75 @@
|
||||||
|
module Parser where
|
||||||
|
|
||||||
|
import Prelude
|
||||||
|
|
||||||
|
import Data.Array as A
|
||||||
|
import Data.Maybe (Maybe(..))
|
||||||
|
import Data.Tuple (Tuple(..))
|
||||||
|
import Data.String.CodeUnits (uncons, toCharArray, fromCharArray)
|
||||||
|
|
||||||
|
newtype Parser v = Parser (String -> Maybe (Tuple v String))
|
||||||
|
parse :: forall a. Parser a -> (String -> Maybe (Tuple a String))
|
||||||
|
parse (Parser p) = p
|
||||||
|
|
||||||
|
itemP :: Parser Char
|
||||||
|
itemP = Parser p
|
||||||
|
where p str = case uncons str of
|
||||||
|
Nothing -> Nothing
|
||||||
|
Just { head: x, tail: xs } -> Just (Tuple x xs)
|
||||||
|
|
||||||
|
instance functorParser :: Functor Parser where
|
||||||
|
map f (Parser p) =
|
||||||
|
Parser $ \s0 -> do
|
||||||
|
(Tuple x s1) <- p s0
|
||||||
|
pure (Tuple (f x) s1)
|
||||||
|
|
||||||
|
instance applyParser :: Apply Parser where
|
||||||
|
apply (Parser p1) (Parser p2)
|
||||||
|
= Parser $ \str -> case p1 str of
|
||||||
|
Nothing -> Nothing
|
||||||
|
Just (Tuple x1 xs1) -> case p2 xs1 of
|
||||||
|
Nothing -> Nothing
|
||||||
|
Just (Tuple x2 xs2) -> Just (Tuple (x1 x2) xs2)
|
||||||
|
|
||||||
|
instance applicativeParser :: Applicative Parser where
|
||||||
|
pure a = Parser $ \str -> Just (Tuple a str)
|
||||||
|
|
||||||
|
instance bindParser :: Bind Parser where
|
||||||
|
bind (Parser p) f = Parser $ \str -> case p str of
|
||||||
|
Nothing -> Nothing
|
||||||
|
Just (Tuple x xs) ->
|
||||||
|
let (Parser p2) = f x
|
||||||
|
in p2 xs
|
||||||
|
|
||||||
|
charP :: Char -> Parser Boolean
|
||||||
|
charP c = (_ == c) <$> itemP
|
||||||
|
|
||||||
|
-- Next steps.
|
||||||
|
sat :: (Char -> Boolean) -> Parser Char
|
||||||
|
sat f = Parser p
|
||||||
|
where
|
||||||
|
p stream = case uncons stream of
|
||||||
|
Nothing -> Nothing
|
||||||
|
Just { head: x, tail: xs } -> if f x then Just (Tuple x xs)
|
||||||
|
else Nothing
|
||||||
|
|
||||||
|
emptyP :: forall a. Parser a
|
||||||
|
emptyP = Parser \_ -> Nothing
|
||||||
|
|
||||||
|
sat2 :: (Char -> Boolean) -> Parser Char
|
||||||
|
sat2 p = do x <- itemP
|
||||||
|
if p x then pure x else emptyP
|
||||||
|
|
||||||
|
--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
|
||||||
|
|
||||||
|
stringP :: String -> Parser Boolean
|
||||||
|
stringP str = case A.uncons (toCharArray str) of
|
||||||
|
Nothing -> Parser \stream -> Just (Tuple true stream)
|
||||||
|
Just { head: x, tail: xs } -> do _ <- charP x
|
||||||
|
stringP (fromCharArray xs)
|
||||||
Loading…
Add table
Reference in a new issue