
The problem is this: what is the type of "embeddedParser"? Unless you can answer that question, you're not going to be able to write it. In particular, its *type* depends on the *value* of its argument; the type of embeddedParser [1,2] is different from the type of embeddedParser [1,1,2]. This isn't possible in Haskell; you need a language with an even more exotic type system (Agda, for example) to encode this dependency. Google "dependent types" for more information. You can encode something similar using existentials: data Sealed p = forall a. Sealed (p a) type ParseResult = Sealed HData ... case h of 1 -> do aux <- pInt Sealed rest <- embeddedParser (t ++ [h]) return (Sealed (C (In aux rest))) and a similar transformation on the (2) case and the "end" case; this makes the type of embeddedParser into Parser ParseResult. What you are doing here is saying that the result of a parse is an HData a for *some* a, but you aren't saying which one. You extract the HData from the existential when running the sub parser, then stuff it back into another existential. But you can't extract the type out of the existential ever; it is lost. In particular you can't prove to the compiler that the type matches that of the [1,2] input and get back to the IN and CH values. And you can't return a value that has been extracted out, you can only stuff it back into another existential container or consume it in some other way! A better option is to use a type that matches what you expect to parse, or just use Data.Dynamic if you want multiple types. You aren't going to get any benefit from "HData a" without a lot more type-level work! Also, for your type list, it'd be much more efficient to use (cycle types) to construct an infinite list (in finite space!) rather than keep appending the head back onto the tail. 2008/12/1 Georgel Calin <6c5l7n@googlemail.com>:
Hello everybody,
I have a piece of code that gives me headaches for some time now.
Simply put, I would like to know which is the best way to overpass a "Couldn't match expected type * against inferred type *"-error and an "Occurs check: cannot construct the infinite type:"-error in the following situation:
{-# OPTIONS -fglasgow-exts #-} module Simple where import Text.ParserCombinators.Parsec
data HData a = O | C a deriving (Eq,Ord,Show) data IN l = IN Int (HData l) deriving (Eq,Ord,Show) data CH l = CH Char (HData l) deriving (Eq,Ord,Show) -- data type is well-defined: sample = C(IN 0 (C(CH 'a' (C(IN 1 (C(CH 'b' (C(IN 2 O)))))))))
embeddedParser types = do string "end"; spaces; return O {- <|> do let h = head types let t = tail types case h of 1 -> do aux <- pInt rest <- embeddedParser $t++[h] return $ C (IN aux rest) 2 -> do aux <- pCh rest <- embeddedParser $t++[h] return $ C (CH aux rest) _ -> error "unallowed type" -} pInt = do n <- fmap read $ many1 digit; return $ fromInteger n pCh = do c <- letter; return $ c simple = embeddedParser [1,2]
-- the above result from sample I would like to get by running -- parseTest simple "0a1b2end"
The way I see it, the defined datatype works but I am a bit clueless about how to modify the parser to accept things of the type (e.g.): HData (IN (CH (IN (CH (IN a))))) (and in general of any finite type embedded like this).
Thanks in advance for your help, George _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe