Skip to content

Instantly share code, notes, and snippets.

@pete-murphy
Last active October 27, 2021 22:37
Show Gist options
  • Save pete-murphy/1289ae1cdc4aabf2383d1004822c0279 to your computer and use it in GitHub Desktop.
Save pete-murphy/1289ae1cdc4aabf2383d1004822c0279 to your computer and use it in GitHub Desktop.
module Main where
import Prelude
import Control.Alt ((<|>))
import Control.Lazy as Lazy
import Data.Either (Either(..))
import Data.Int as Int
import Data.Maybe (Maybe(..))
import Effect (Effect)
import Effect.Console as Console
import Text.Parsing.StringParser (Parser)
import Text.Parsing.StringParser as StringParser
import Text.Parsing.StringParser.CodePoints as CodePoints
import Text.Parsing.StringParser.Combinators as Combinators
-- expr ::= term + expr | term
-- term ::= factor * term | factor
-- factor ::= power ** factor | power
-- power ::= (expr) | a
data Expr
= Add Expr Expr
| Mul Expr Expr
| Pow Expr Expr
| Lit Int
instance Show Expr where
show = case _ of
Add x y -> "(Add " <> show x <> " " <> show y <> ")"
Mul x y -> "(Mul " <> show x <> " " <> show y <> ")"
Pow x y -> "(Pow " <> show x <> " " <> show y <> ")"
Lit x -> show x
expr :: Unit -> Parser Expr
expr _ = StringParser.try (do
x <- Lazy.defer term
_ <- CodePoints.string "+"
y <- Lazy.defer expr
pure (Add x y))
<|> Lazy.defer term
term :: Unit -> Parser Expr
term _ = StringParser.try (do
x <- Lazy.defer factor
_ <- CodePoints.string "*"
y <- Lazy.defer term
pure (Mul x y))
<|> Lazy.defer factor
factor :: Unit -> Parser Expr
factor _ = StringParser.try (do
x <- Lazy.defer power
_ <- CodePoints.string "**"
y <- Lazy.defer factor
pure (Pow x y))
<|> Lazy.defer power
power :: Unit -> Parser Expr
power _ = StringParser.try
(Combinators.between
(CodePoints.string "(")
(CodePoints.string ")")
(Lazy.defer expr))
<|> lit
lit :: Parser Expr
lit = do
d <- CodePoints.regex "\\d+"
case Int.fromString d of
Just d' -> pure (Lit d')
_ -> StringParser.fail "Not an Int"
doUnParser :: forall a. Show a => String -> Parser a -> String -> Effect Unit
doUnParser parserName parser content = do
Console.log ("(unParser) Parsing content with '" <> parserName <> "'")
case StringParser.unParser parser { str: content, pos: 0 } of
Left rec -> Console.log $
"Position: " <> show rec.pos
<> "\nError: " <> show rec.error
Right rec -> Console.log $
"Result was: " <> show rec.result
<> "\nSuffix was: " <> show rec.suffix
Console.log "-----"
main :: Effect Unit
main = do
doUnParser "expr" (expr unit) "2*3**2"
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment