cauliflower
cauliflower

Reputation: 63

Haskell parsec gives <<loop>> error

I've been trying to write a parser for the typed lambda calculus using parsec but it keeps getting stuck in a loop resulting in a <> error. Everything seems fine to me; I have probably misunderstood something about parsec.

{-# LANGUAGE UnicodeSyntax #-}

module Parser where

import Semantics ( NmTerm(..)
                 , Ty(..))

import Text.ParserCombinators.Parsec (Parser(..)
                                     , ParseError
                                     , try
                                     , oneOf
                                     , char
                                     , digit
                                     , satisfy
                                     , many1
                                     , choice
                                     , chainl1
                                     , alphaNum
                                     , eof
                                     , letter
                                     , parse)

import qualified Text.Parsec.Token as T
import qualified Text.Parsec.Language as L
import qualified Text.Parsec.Expr as E
import Control.Applicative ((<|>))

------------
-- LEXING --
------------

lexer ∷ T.TokenParser ()
lexer = T.makeTokenParser
        $ L.emptyDef { T.identStart      = letter
                     , T.identLetter     = alphaNum
                     , T.reservedOpNames = ["lambda", ".", ":", "->"]
                     , T.reservedNames   = ["true", "false", "Bool"]
                     , T.opLetter        = oneOf ".:"
                     }

parens ∷ Parser a → Parser a
parens = T.parens lexer

natural ∷ Parser Integer
natural = T.natural lexer

reserved ∷ String → Parser ()
reserved = T.reserved lexer

reservedOp ∷ String → Parser ()
reservedOp = T.reservedOp lexer

identifier ∷ Parser String
identifier = T.identifier lexer

whiteSpace ∷ Parser ()
whiteSpace = T.whiteSpace lexer

-------------------------------------------------------------------------------
-------------------------------------- PARSING --------------------------------
-------------------------------------------------------------------------------
variable ∷ Parser NmTerm
variable = identifier >>= \x → return $ NmVar x

true ∷ Parser NmTerm
true = reserved "true" >> return NmTrue

false ∷ Parser NmTerm
false = reserved "false" >> return NmFalse

bool ∷ Parser NmTerm
bool = true <|> false

boolTy ∷ Parser Ty
boolTy = reserved "Bool" >> return TyBool

arrTy ∷ Parser Ty
arrTy = do
  τ₁ ← anyType
  whiteSpace
  reservedOp "->"
  whiteSpace
  τ₂ ← anyType
  return $ TyArr τ₁ τ₂

anyType ∷ Parser Ty
anyType = arrTy <|> boolTy

abstraction ∷ Parser NmTerm
abstraction = do
  reservedOp "lambda"
  whiteSpace
  x ← identifier
  reservedOp ":"
  τ ← anyType
  reservedOp "."
  whiteSpace
  body ← expr
  return $ NmAbs x τ body

expr ∷ Parser NmTerm
expr =  abstraction
    <|> variable
    <|> bool

parseExpr ∷ String → NmTerm
parseExpr t = case parse expr "" t of
                Left err  → error $ show err
                Right ast → ast

Upvotes: 2

Views: 136

Answers (1)

comingstorm
comingstorm

Reputation: 26097

It might help if you were more specific about your error message. But I suspect the problem is that you have a left-recursive grammar: for example, an arrTy can start with an anyType, which can be an arrTy.

When implemented directly in a top-down parser (which includes combinator parsers such as Parsec), this kind of feature would cause an infinite loop. Parsec provides various facilities to work around this problem; however, the most convenient way to solve your particular problem may also require some re-work of your grammar.

Upvotes: 2

Related Questions