[Haskell-beginners] data type design question
Markus Barenhoff
alios at alios.org
Thu Jul 31 05:42:13 EDT 2008
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 at alios.org - jabber: alios at jabber.ccc.de - icq: 27998346
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 479 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/beginners/attachments/20080731/f4473d9c/attachment.bin
More information about the Beginners
mailing list