Skip to content

Instantly share code, notes, and snippets.

@SeungheonOh
Created August 10, 2021 02:26
Show Gist options
  • Save SeungheonOh/4da4b86c76a5c6a35a657a68e0bb289d to your computer and use it in GitHub Desktop.
Save SeungheonOh/4da4b86c76a5c6a35a657a68e0bb289d to your computer and use it in GitHub Desktop.
{-# LANGUAGE OverloadedStrings #-}
module Main where
import System.IO
import Control.Applicative hiding (many)
import Control.Monad
import Data.Char
import Data.Text (Text)
import qualified Data.Text as T
import Data.Void
import Text.Megaparsec
import Text.Megaparsec.Char
import qualified Text.Megaparsec.Char.Lexer as L
type Parser = Parsec Void Text
type Name = String
data Expr = Var Name
| App Expr Expr
| Lam Name Expr
deriving (Show)
lineComment :: Parser()
lineComment = L.skipLineComment "--"
lexeme :: Parser a -> Parser a
lexeme = L.lexeme $ L.space space1 lineComment empty
pName :: Parser Name
pName = (:[]) <$> (satisfy isAlphaNum :: Parser Char)
-- Variable is a single character
pVar :: Parser Expr
pVar = Var <$> pName
-- λv.e \v.e Both works for Lambda
pLam :: Parser Expr
pLam = (char 'λ' <|> char '\\') *> pName <* char '.'
>>= (\n -> Lam n <$> pExpr)
pParen :: Parser a -> Parser a
pParen p = char '(' *> p <* char ')'
-- Every Lambda and Variable is a Term
pTerm :: Parser Expr
pTerm = try (pParen pExpr)
<|> try pLam
<|> pVar
-- Constructs Application based on all Terms
pExpr :: Parser Expr
pExpr = foldl1 App <$> many (space *> pTerm <* space)
main :: IO ()
main = forever $ hSetBuffering stdin LineBuffering
>> getLine >>= \l -> case (parse pExpr "" . T.pack) l of
Left err -> print err
Right xs -> print xs
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment