
On Thu, Jul 31, 2008 at 2:42 AM, Markus Barenhoff
On Thu, Jul 31, 2008 at 08:58:08AM +0200, Bas van Dijk wrote:
Hi,
Not really a beginners type answer because I need two big language extensions, but anyway:
my feeling that there is a sollution somewhere in the extenstions seems to have been right.
------------------------------------------------------- {-# LANGUAGE GADTs #-} {-# LANGUAGE ExistentialQuantification #-}
data DictVal = forall a. D (T a)
data T a where TInt :: Int -> T Int TString :: String -> T String TList :: [T a] -> T [T a] TDict :: [(String, DictVal)] -> T DictVal
-- For example
n = TInt 3 s = TString "abc" l = TList [n,n,n] d = TDict [("n", D n), ("s", D s), ("l", D l)] -------------------------------------------------------
This is what I was looking for. But it looks like that the problem with the type of the "toplevel" parser still exists. The compiler wants a type:
tParser :: GenParser Char st (T a) tParser = do stringParser <|> integerParser <|> listParser <|> dictParser
this causes the compiler to generate the following error:
Couldn't match expected type `[Char]' against inferred type `Int' When generalising the type(s) for `torrentParser'
Any further ideas?
Thanx for all you answers btw.!
Markus
-- Markus Barenhoff - Germany - Europe - Earth e-mail: alios@alios.org - jabber: alios@jabber.ccc.de - icq: 27998346
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
Hi, Maybe you could add a "wrapper" datatype in addition to the GADT solution: data TC = TCInt (T Int) | TCString (T String) | TCList a (T [T a]) | TCDict (T DictVal) Then your parser returns a value of type TC and you can unwrap that using case tc of { ... } to get a value of type T. I haven't tested this, but it seems like it ought to work. Alex