
Thanks for a prompt reply, Roman. On 05/28/2013 04:52 PM, Roman Cheplyaka wrote:
Any syb-style library works with GADTs, by the virtue of dealing with value representations instead of type representations. I tried to use syb, but the following code fails to typecheck for me. What am I doing wrong? {-# LANGUAGE GADTs, EmptyDataDecls, MultiParamTypeClasses, TypeFamilies #-} {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
data HasHoles data Complete deriving instance Typeable HasHoles deriving instance Data HasHoles deriving instance Typeable Complete deriving instance Data Complete type family Holes a b :: * canHaveHolesT :: a -> b -> Holes a b canHaveHolesT _ _ = undefined type instance Holes HasHoles Complete = HasHoles type instance Holes Complete HasHoles = HasHoles type instance Holes HasHoles HasHoles = HasHoles type instance Holes Complete Complete = HasHoles
data Expression k a where EQuote :: a -> String -> Expression HasHoles a IntLit :: a -> Int -> Expression Complete a EArith :: a -> ArithOp -> Expression k1 a -> Expression k2 a -> Expression (Holes k1 k2) a deriving instance Typeable2 (Expression) deriving instance Data (Expression k a) data ArithOp = OpAdd | OpSub | OpMul | OpDiv deriving (Data, Typeable)
Fails with:
Couldn't match type `Complete' with `HasHoles' Expected type: a -> String -> Expression k a Actual type: a -> String -> Expression HasHoles a In the first argument of `z', namely `EQuote' In the first argument of `k', namely `z EQuote' When typechecking the code for `Data.Data.gunfold' in a standalone derived instance for `Data (Expression k a)': To see the code I am typechecking, use -ddump-deriv
Not sure what you mean here — attoparsec does support unlimited lookahead, in the sense that a parser may fail arbitrarily late in the input stream, and backtrack to any previous state. Although attoparsec is a poor choice for programming language parsing, primarily because of the error messages. I guess I have an outdated notion of attoparsec. But yes, error messages seem to be the weak point of attoparsec. Also, the fact that it only accepts bytestrings makes it harder (but no impossible, since we can convert Strings to ByteStrings) to reuse the parser as a QuasiQuoter. So, I'll rephrase my question. What's the best choice for a library for parsing programming languages nowadays?