[Haskell-cafe] Compiler error in Parsec using ByteString

Roman Cheplyaka roma at ro-che.info
Sat May 18 14:46:24 CEST 2013


Hi,

General advice here is to put type signatures for all non-trivial
definitions. This way you can see exactly where compiler and you
disagree on what the type of something should be.

In this particular case, by following the above recipe, I see that one
problem is that `emptyDef` has type `LanguageDef st` (where
`LanguageDef` is a synonym for `GenLanguageDef String st Identity`) —
i.e. it's not polymorphic in the stream type. (There might be other
issues as well.)

Roman

* mukesh tiwari <mukeshtiwari.iiitm at gmail.com> [2013-05-18 16:37:42+0530]
> Hello all,
> I am trying to write a small calculator using Parsec. Every thing went fine
> and I wrote this [1] and now I am trying to use ByteString to make it more
> faster but getting compiler error which I am not able to figure out. Could
> some one please tell me what is wrong with this code. In case of
> indentation error, code on hpaste[2]
> 
> {-# LANGUAGE OverloadedStrings #-}
> import qualified Text.Parsec.Token as Token
> import Text.Parsec.Prim
> import Text.Parsec.Char
> import Text.Parsec.Expr
> import Text.Parsec.Combinator
> import Text.Parsec.Language
> import qualified Text.Parsec.ByteString.Lazy as T
> import qualified Data.ByteString.Lazy.Char8 as BS
> import Control.Applicative hiding ( ( <|> ) , many )
> import Data.Maybe ( fromJust )
> 
> languageDef = emptyDef { Token.commentStart   = "/*"
>                , Token.commentEnd     = "*/"
>                , Token.commentLine    = "//"
>                , Token.nestedComments = False
>                , Token.identStart     = letter <|> char '_'
>                , Token.identLetter    = alphaNum <|> oneOf "_'"
>                , Token.opStart        = Token.opLetter emptyDef
>                , Token.opLetter       = oneOf ":!#$%&*+./<=>?@\\^|-~"
>                , Token.reservedOpNames= ["*" , "/" , "^" , "+" , "-" ]
>                , Token.reservedNames  = []
>                , Token.caseSensitive  = True
>                }
> 
> lexer = Token.makeTokenParser languageDef
> 
> identifier = Token.identifier lexer
> reserved = Token.reserved lexer
> operator = Token.operator lexer
> reservedOp = Token.reservedOp lexer
> natural = Token.natural lexer
> integer = Token.integer lexer
> float = Token.float lexer
> lexeme = Token.lexeme lexer
> parens = Token.parens lexer
> whiteSpace = Token.whiteSpace lexer
> semi = Token.semi lexer
> comma = Token.comma lexer
> colon = Token.colon lexer
> dot = Token.dot lexer
> semiSep = Token.semiSep lexer
> commaSep = Token.commaSep lexer
> 
> 
> 
> data Expr = Num Integer
>           | Add Expr Expr
>           | Sub Expr Expr
>           | Mul Expr Expr
>           | Div Expr Expr
>           | Exp Expr Expr
>           deriving Show
> 
> exprCal    :: T.Parser Expr
> exprCal    = buildExpressionParser table factor
> 
> 
> table   = [ [ op "^"  Exp AssocRight ]
>           , [ op "*"  Mul AssocLeft, op "/"  Div AssocLeft ]
>           , [ op "+"  Add AssocLeft, op "-"  Sub AssocLeft ]
>           ]
>         where
>           op s f assoc  = Infix ( reservedOp s  >> return f ) assoc
> 
> factor :: T.Parser Expr
> factor  = parens  exprCal
>         <|> Num <$> integer
> 
> 
> 
> calExpression  :: Expr -> Integer
> calExpression ( Num n ) = n
> calExpression ( Add e1 e2 ) = calExpression e1 + calExpression e2
> calExpression ( Sub e1 e2 ) = calExpression e1 - calExpression e2
> calExpression ( Mul e1 e2 ) = calExpression e1 * calExpression e2
> calExpression ( Div e1 e2 ) = div ( calExpression e1 ) ( calExpression e2 )
> calExpression ( Exp e1 e2 ) =   calExpression e1  ^ ( calExpression e2 )
> 
> 
> calculator :: String -> Integer
> calculator expr = case parse ( whiteSpace >> exprCal ) ""  ( BS.pack expr )
> of
>                        Left msg -> error "failed to parse"
>                        Right ( val ) -> calExpression val
> 
> 
> *Main> :load
> "/Users/mukeshtiwari/Programming/Code/Compilers/ParsecExample.hs"
> [1 of 1] Compiling Main             (
> /Users/mukeshtiwari/Programming/Code/Compilers/ParsecExample.hs,
> interpreted )
> 
> /Users/mukeshtiwari/Programming/Code/Compilers/ParsecExample.hs:56:36:
>     Couldn't match type `[Char]' with `BS.ByteString'
>     Expected type: OperatorTable
>                      BS.ByteString () Data.Functor.Identity.Identity Expr
>       Actual type: [[Operator
>                        String () Data.Functor.Identity.Identity Expr]]
>     In the first argument of `buildExpressionParser', namely `table'
>     In the expression: buildExpressionParser table factor
>     In an equation for `exprCal':
>         exprCal = buildExpressionParser table factor
> 
> /Users/mukeshtiwari/Programming/Code/Compilers/ParsecExample.hs:67:11:
>     Couldn't match type `[Char]' with `BS.ByteString'
>     Expected type: ParsecT
>                      BS.ByteString () Data.Functor.Identity.Identity Expr
>       Actual type: ParsecT
>                      String () Data.Functor.Identity.Identity Expr
>     In the return type of a call of `parens'
>     In the first argument of `(<|>)', namely `parens exprCal'
>     In the expression: parens exprCal <|> Num <$> integer
> 
> /Users/mukeshtiwari/Programming/Code/Compilers/ParsecExample.hs:67:19:
>     Couldn't match type `BS.ByteString' with `[Char]'
>     Expected type: ParsecT
>                      String () Data.Functor.Identity.Identity Expr
>       Actual type: T.Parser Expr
>     In the first argument of `parens', namely `exprCal'
>     In the first argument of `(<|>)', namely `parens exprCal'
>     In the expression: parens exprCal <|> Num <$> integer
> 
> /Users/mukeshtiwari/Programming/Code/Compilers/ParsecExample.hs:68:21:
>     Couldn't match type `[Char]' with `BS.ByteString'
>     Expected type: ParsecT
>                      BS.ByteString () Data.Functor.Identity.Identity Integer
>       Actual type: ParsecT
>                      String () Data.Functor.Identity.Identity Integer
>     In the second argument of `(<$>)', namely `integer'
>     In the second argument of `(<|>)', namely `Num <$> integer'
>     In the expression: parens exprCal <|> Num <$> integer
> 
> /Users/mukeshtiwari/Programming/Code/Compilers/ParsecExample.hs:82:46:
>     Couldn't match type `BS.ByteString' with `[Char]'
>     Expected type: ParsecT
>                      String () Data.Functor.Identity.Identity Expr
>       Actual type: T.Parser Expr
>     In the second argument of `(>>)', namely `exprCal'
>     In the first argument of `parse', namely `(whiteSpace >> exprCal)'
>     In the expression: parse (whiteSpace >> exprCal) "" (BS.pack expr)
> 
> /Users/mukeshtiwari/Programming/Code/Compilers/ParsecExample.hs:82:62:
>     Couldn't match type `BS.ByteString' with `[Char]'
>     Expected type: String
>       Actual type: BS.ByteString
>     In the return type of a call of `BS.pack'
>     In the third argument of `parse', namely `(BS.pack expr)'
>     In the expression: parse (whiteSpace >> exprCal) "" (BS.pack expr)
> Failed, modules loaded: none.
> Prelude>
> 
> 
> Mukesh Tiwari
> 
> [1] http://hpaste.org/88155
> [2] http://hpaste.org/88156

> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe




More information about the Haskell-Cafe mailing list