Skip to content

Instantly share code, notes, and snippets.

@tkuriyama
Created September 15, 2020 16:13
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 tkuriyama/b4c70f64d8f669261f9ea792ee89f38e to your computer and use it in GitHub Desktop.
Save tkuriyama/b4c70f64d8f669261f9ea792ee89f38e to your computer and use it in GitHub Desktop.
CIS 194 Week 11
module SExpr where
import AParser
import Control.Applicative
import Data.Char
------------------------------------------------------------
-- 1. Parsing repetitions
------------------------------------------------------------
zeroOrMore :: Parser a -> Parser [a]
zeroOrMore p = oneOrMore p <|> pure []
oneOrMore :: Parser a -> Parser [a]
oneOrMore p = liftA2 (:) (Parser $ \s -> runParser p s) (zeroOrMore p)
------------------------------------------------------------
-- 2. Utilities
------------------------------------------------------------
spaces :: Parser String
spaces = zeroOrMore (satisfy isSpace)
ident :: Parser String
ident = liftA2 (:) (satisfy isAlpha) (zeroOrMore (satisfy isAlphaNum))
------------------------------------------------------------
-- 3. Parsing S-expressions
------------------------------------------------------------
-- An "identifier" is represented as just a String; however, only
-- those Strings consisting of a letter followed by any number of
-- letters and digits are valid identifiers.
type Ident = String
-- An "atom" is either an integer value or an identifier.
data Atom = N Integer | I Ident
deriving Show
-- An S-expression is either an atom, or a list of S-expressions.
data SExpr = A Atom
| Comb [SExpr]
deriving Show
parseAtom :: Parser Atom
parseAtom = N <$> posInt <|>
I <$> ident
open :: Parser Char
open = char '('
close :: Parser Char
close = char ')'
parseSExpr :: Parser SExpr
parseSExpr =
spaces *>
(A <$> parseAtom <|>
open *> (Comb <$> oneOrMore parseSExpr) <* close)
<* spaces
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment