Skip to content

Instantly share code, notes, and snippets.

@hypernormal
Last active October 24, 2019 14:40
Show Gist options
  • Save hypernormal/38b4f571d4297d31a5813c6baba70662 to your computer and use it in GitHub Desktop.
Save hypernormal/38b4f571d4297d31a5813c6baba70662 to your computer and use it in GitHub Desktop.
LispParser pairing task in Haskell using Parser Combinators
module LispParser where
import Test.Hspec
import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Error
data Expr =
List [Expr]
| Number Integer
| String String
deriving (Show, Eq)
leftParen :: Parser Char
leftParen = char '('
rightParen :: Parser Char
rightParen = char ')'
parseString :: Parser Expr
parseString = String <$> many1 (noneOf "() ")
parseNumber :: Parser Expr
parseNumber = Number . read <$> many1 digit
parseList :: Parser Expr
parseList = List <$> sepBy parseExpr spaces
parseParensExpr :: Parser Expr
parseParensExpr = do
_ <- leftParen
list <- try parseList
_ <- rightParen
return list
parseExpr :: Parser Expr
parseExpr = parseNumber
<|> parseString
<|> parseParensExpr
main :: IO ()
main = hspec $
describe "parser" $ do
it "parses parentheses in pairs into a List" $
testParse "()" `shouldBe` (Right $ List [])
it "parses nested parentheses in pairs into nested Lists" $
testParse "((()))" `shouldBe` (Right $ List [List [List []]])
it "parses list of lists" $
testParse "(() ())" `shouldBe` (Right$ List [List [], List[]])
it "fails when parentheses don't match" $ do
let Left err = testParse "("
errorIsUnknown err `shouldBe` False
it "fails when nested parentheses don't match" $ do
let Left err = testParse "((())"
errorIsUnknown err `shouldBe` False
it "parses numbers" $
testParse "33" `shouldBe` (Right $ Number 33)
it "parses numbers nested in lists" $
testParse "(25)" `shouldBe` (Right $ List [Number 25])
it "parses listed numbers" $
testParse "(32 24)" `shouldBe` (Right $ List [Number 32, Number 24])
it "parses strings" $
testParse "first" `shouldBe` (Right $ String "first")
it "parses strings nested in lists" $
testParse "(first)" `shouldBe` (Right $ List [String "first"])
it "parses listed strings" $
testParse "(first second)" `shouldBe` (Right $ List [String "first", String "second"])
it "parses the provided example from RC" $
testParse "(first (list 1 (+ 2 3) 9))" `shouldBe` (Right $ List [String "first", List [String "list", Number 1, List [String "+", Number 2, Number 3], Number 9]])
it "parses another complex example" $
testParse "(+ 2 (+ 3 (+ 4 5)))" `shouldBe` (Right $ List [String "+", Number 2, List [String "+", Number 3, List [String "+", Number 4, Number 5]]])
testParse :: String -> Either ParseError Expr
testParse = parse parseExpr ""
@hypernormal
Copy link
Author

Dependencies: HSpec and Parsec
To install:

stack install parsec
stack install hspec

To run:
stack runghc LispParser.hs

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment