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