Skip to content

Instantly share code, notes, and snippets.

@hrb90
Created December 2, 2017 03:35
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save hrb90/b7d37bd4ffc4b4af2ad83942102d87d6 to your computer and use it in GitHub Desktop.
Save hrb90/b7d37bd4ffc4b4af2ad83942102d87d6 to your computer and use it in GitHub Desktop.
module Main where
import Prelude hiding (between)
import Control.Monad.Eff (Eff)
import Data.Array (foldr, many, reverse, some, uncons)
import Data.Bifunctor (lmap)
import Data.Either (Either)
import Data.Functor (voidRight)
import Data.Maybe (Maybe(..))
import Partial.Unsafe (unsafePartial)
import Text.Parsing.Parser (Parser, runParser)
import Text.Parsing.Parser.Combinators (between)
import Text.Parsing.Parser.Expr (Assoc(..), Operator(..), buildExprParser)
import Text.Parsing.Parser.String (char, string, whiteSpace)
import Text.Parsing.Parser.Token (digit)
data Expr = Lit Int | Add Expr Expr
eval :: Expr -> Int
eval (Lit i) = i
eval (Add x1 x2) = eval x1 + eval x2
instance showExpr :: Show Expr where
show (Lit i) = show i
show (Add x1 x2) = "(" <> show x1 <> "+" <> show x2 <> ")"
decimal :: Parser String Expr
decimal = some digit
# map makeLit
where makeLit x = x # reverse # toInt # Lit
toInt arr = case (uncons arr) of
Just { head: x, tail: xs } -> charToInt x + 10 * toInt xs
Nothing -> 0
charToInt x = unsafePartial $ case x of
'0' -> 0
'1' -> 1
'2' -> 2
'3' -> 3
'4' -> 4
'5' -> 5
'6' -> 6
'7' -> 7
'8' -> 8
'9' -> 9
-- Parses strings like " + 1"
plusNumber :: Parser String (Expr -> Expr)
plusNumber = do
_ <- whiteSpace
_ <- char '+'
_ <- whiteSpace
n <- decimal
pure $ flip Add n
-- Parses strings like "1 + 2 + 3+ 4" into expressions
additionString :: Parser String Expr
additionString = do
n <- decimal
plusses <- many plusNumber
pure $ foldr ($) n $ reverse plusses
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment