
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

Hi Markus, Markus Barenhoff wrote:
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.
Maybe something like data T = TString String | TInt Integer | TStringList [String] | TIntList [Integer] | TDict [(String, T)] would work. Tillmann

Hi Tilmann, On Wed, Jul 30, 2008 at 02:10:07PM +0200, Tillmann Rendel wrote:
Hi Markus,
Markus Barenhoff wrote:
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.
Maybe something like
data T = TString String | TInt Integer | TStringList [String] | TIntList [Integer] | TDict [(String, T)]
mmm lists could also contain list or dict, so on must introduce constructors for those too. You will run in problems there because what is with a list of lists then you would need a TIntListList and so on... Maybe some words to the background why I use one type. This is to make the parsec parser work. The toplevel parser looks like this, because the parsed text could start with any of them:
parser :: GenParser Char st T parser = do stringParser <|> integerParser <|> listParser <|> dictParser
Markus -- Markus Barenhoff - Münster - Germany - Europe - Earth e-mail: alios@alios.org - jabber: alios@jabber.ccc.de - icq: 27998346

Hi Markus, Markus Barenhoff wrote:
mmm lists could also contain list or dict, so on must introduce constructors for those too. You will run in problems there because what is with a list of lists then you would need a TIntListList and so on...
I think your problem to be seriously hard :) On the one hand, you want to have your T dynamically typed, so that it can returned by Parsec parsers and so on, and on the other hand, you want it to be statically typed, so that you can express more exact static types e.g. for lists. That means you have to "embed" your T-typesystem into Haskell's typesystem so that your constraints (such as: all elements in this list use the same constructor) are statically checked. This should be possible using advanced techniques, but I'm not sure that extra bit of static type safety is worth it. Maybe you could instead keep your current datatype, and provide some convenience functions for accessing T values: unknown :: T -> Maybe T unknown x = Just x string :: T -> Maybe String string (TString s) = Just s string _ = Nothing dict :: T -> Maybe [(String, T)] dict (TDict d) = Just d dict _ = Nothing listOf :: (T -> a) -> T -> Maybe [T] listOf f (TList xs) = mapM f xs Now code which expects, for example, either a list of list of dictionaries, or a list of strings, could look like: foo t = mconcat [ listOf (listOf dict) t >>= \lld -> ... , listOf string t >>= \ls -> ... ] This way, you could enable clients to easily check for wellformedness while processing the parsed data. Tillmann

A data declaration _defines_ type constructors. You describe what types those constructors can accept, so this: data T = TString String | TInt Integer | TList [T] | TDict [(TString, T)] actually doesn't make any sense -- the list holds what? Holds tuples of `TString` and `T`. What type is `TString` ? It's not a type, it's a constructor! So you need to make it a type. Also, it is not clear to me why the `TDict` can not just map `String`s to `T`s -- if you get a `TString` in the course of parsing, you can unwrap it. -- _jsn

Those are bittorrent types, as defined by the protocol "specifications"
I was thinking:
data TPrimitive= TString String | TInt Integer
data TComplex = TList [TPrimitive] | TDict [(String,TPrimitive)]
data T = TPrimitive | TComplex
Would that work?
On Wed, Jul 30, 2008 at 16:28, Jason Dusek
A data declaration _defines_ type constructors. You describe what types those constructors can accept, so this:
data T = TString String | TInt Integer | TList [T] | TDict [(TString, T)]
actually doesn't make any sense -- the list holds what? Holds tuples of `TString` and `T`. What type is `TString` ? It's not a type, it's a constructor! So you need to make it a type.
Also, it is not clear to me why the `TDict` can not just map `String`s to `T`s -- if you get a `TString` in the course of parsing, you can unwrap it.
-- _jsn _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Rafael Gustavo da Cunha Pereira Pinto Electronic Engineer, MSc.

Rafael Gustavo da Cunha Pereira Pinto schrieb:
I was thinking:
data TPrimitive= TString String | TInt Integer data TComplex = TList [TPrimitive] | TDict [(String,TPrimitive)] data T = TPrimitive | TComplex
Would that work?
This is not what Markus wants for two reasons: (1) T is just an enumeration here, maybe you meant data T = TPrimitive TPrimitive | TComplex TComplex instead. (2) Lists and dictionaries are allowed to contain complex values, but lists are not allowed to contain values of different "types". Tillmann

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

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

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
participants (6)
-
Alexander Dunlap
-
Bas van Dijk
-
Jason Dusek
-
Markus Barenhoff
-
Rafael Gustavo da Cunha Pereira Pinto
-
Tillmann Rendel