
On Wed, Jul 30, 2008 at 11:09 AM, Markus Barenhoff
Hi, I have written a parsec parser for reading a marshallaled dataformat.
The returned data structure is based on the following data type:
data T = TString String | TInt Integer | TList [TorrentT] | TDict [(TorrentT, TorrentT)]
I think TString and TInt are clear. The elements of a TList always have the same "type" (same constructor). The TDict is a dictionary where the key is always a TString but the value can be of any of the other "types", even in the same dictionary. F.e the key "foo" may map to a TInt while the key "bar" maps to another TDict.
I'am not happy with this declaration, but I'am not sure how to express this better.
One haskell data type for each of the four and then using type classes?
Maybe something like this? :
type TString = String type TInt = Integer type TList = TC t => [t] type TDict = (TC t) => [(TString, t)]
class TC where ...
instance TC TString instance TC TInt instance TC TList instance TC TDict
Thnx for some inseperation! Markus
-- Markus Barenhoff - Münster - 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
Not really a beginners type answer because I need two big language extensions, but anyway: ------------------------------------------------------- {-# 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)] ------------------------------------------------------- Note that it isn't possible to create a 'TList [n,n,n,s]' for example. I don't have much time to explain GADTs and ExistentialQuantification but you can read about them in the GHC user guide: http://www.haskell.org/ghc/docs/6.8.3/html/users_guide/index.html good luck, Bas