Skip to content

Instantly share code, notes, and snippets.

@Lifelovinglight
Created February 7, 2017 22:23
Show Gist options
  • Save Lifelovinglight/4196070fc7cecea167c4e14256808651 to your computer and use it in GitHub Desktop.
Save Lifelovinglight/4196070fc7cecea167c4e14256808651 to your computer and use it in GitHub Desktop.
Sexp parser example
{-# LANGUAGE DataKinds #-}
module Lib
( primitiveRead
, LispType ( Nil
, LispInteger
, LispString
, LispSymbol
, LispTrue
, LispList )
) where
import Text.Parsec
import Data.Text (Text)
import qualified Data.Text as Text
data LispType = Nil
| LispInteger Integer
| LispString Text
| LispSymbol Text
| LispTrue
| LispList [LispType]
deriving (Show)
primitiveRead :: String -> Text -> Either ParseError LispType
primitiveRead source text = runParser lispParser () source text
type LispParser a = Parsec Text () a
whitespace :: LispParser ()
whitespace = skipMany space
nilParser :: LispParser LispType
nilParser = string "NIL" >> return Nil
trueParser :: LispParser LispType
trueParser = string "T" >> return LispTrue
symbolParser :: LispParser LispType
symbolParser = LispSymbol . Text.pack <$> many1 (choice [alphaNum, oneOf "!$%&*+-./:<=>?@^_~"])
integerParser :: LispParser LispType
integerParser = LispInteger . (read :: String -> Integer) <$> many1 digit
stringParser :: LispParser LispType
stringParser = LispString . Text.pack <$> between (char '"') (char '"') (many (noneOf ['"']))
listParser :: LispParser LispType
listParser = LispList <$> between (char '(') (char ')') (many1 lispParser)
lispParser :: LispParser LispType
lispParser = whitespace
>> choice [ nilParser
, trueParser
, integerParser
, stringParser
, symbolParser
, listParser ]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment