Re: [Haskell] XML Serialization and type constraints

2004-08-26 Thread Simon D. Foster
On Thu, 2004-08-26 at 09:47, MR K P SCHUPKE wrote:
 You can do it using overlapping instances...
 
 data A
 data B b
 data C c
 
 instance Encode A where ...
 
 instance Encode b = Encode (B b) where
 
 instance Encode c = Encode (C c) where
 
   Keean.

I don't understand what you mean; that code segment doesn't require
overlapping instances. How can this help anyway since Encode (or Mixin
or Hook) is a two parameter type-class?

Thanks,

-Si

-- 
Simon D. Foster [EMAIL PROTECTED]
Sheffield University

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] XML Serialization and type constraints

2004-08-25 Thread Tomasz Zielonka
On Tue, Aug 24, 2004 at 07:35:46PM +0100, Simon D. Foster wrote:
 I'm trying to implement an extensible XML De/Serializer in Haskell for
 use with SOAP and XML Schema (using the Haskell XML Toolbox). The idea
 is you have a type-class, which is instantiated for each type you want
 to encode/de-encode. This class (atm) takes the form;
 
 class XMLSerializer a where
 encodeElements:: NamespaceTable - Flags - a - [XmlFilter]
 encodeAttributes  :: NamespaceTable - Flags - a - [XmlFilter]
 encodeTree  :: NamespaceTable - String - Flags - a - XmlFilter
 encodeTrees :: NamespaceTable - String - Flags - a - [XmlFilter]
 
 decodeAttribute   :: String - XmlTree - Maybe a
 decodeElement :: XmlTree - Maybe a
 decodeTree:: XmlTree - Maybe a
 decodeTrees   :: XmlTrees - Maybe a
 
 (and a few default instances)
 
 This type-class can then be used recursively to build XML
 representations of Haskell data.
 
 I now want to expand this system to make is more extensible. For
 starters, to make it useful with SOAP, I need to add optional explicit
 typing of data. To this end I have another class; XSDType, which stores
 the XSD equivalent name and name-space for a particular Haskell type.
 This is what is used to add explicit type data to the XML documents.
 Adding this data involves adding an extra attribute to each node in the
 tree. More generally however each Hook, which adds extra data at each
 node has type NamespaceTable - Flags - a - ([XmlFilter],
 [XmlFilter]), where a is the type of the value.
 
 However, this is where the problem comes. How do I go about expressing
 that a has a constraint XSDType a? I don't want to add this constraint
 to the Serializer class itself since an XML tree may not be typed by
 XSD. Somehow I need a way of adding extra constraints to a dynamically.

Here is one possible solution. Below is a working implementation for a
simpler class scheme. You should be able to apply this to your problem,
at least in case of adding XSD types, if not generally.

  {-# OPTIONS -fglasgow-exts #-}
  {-# OPTIONS -fallow-undecidable-instances #-}

  module B where

  import List
  import Data.Typeable -- Just to implement one of example mixins

  -- Mixin class - could have better name

  class Mixin a t where
  mixin :: t - a - (String - String)

  -- Serializer class

  -- class Serializer has an additional parameter t which will be used
  -- for passing a mixin to it. Also it is a subclass of Mixin a t, but
  -- it doesn't mean adding unneccesary constraints to Serializer -
  -- one of Mixin's implementations will be identity.
  --
  -- It is important that encodePrim's implementations don't call
  -- directly to encodePrim, only to encode, which makes the
  -- mixin work.
  class Mixin a t = Serializer a t where
  encodePrim :: t - a - String

  encode :: Serializer a t = t - a - String
  encode t x = mixin t x (encodePrim t x)

  -- Serializer instances - I used undecidable instances here.

  instance Mixin Int t = Serializer Int t where
  encodePrim _ = show

  instance Mixin Char t = Serializer Char t where
  encodePrim _ = show

  instance (Serializer a t, Mixin [a] t) = Serializer [a] t where
  encodePrim t l = [ ++ concat (intersperse ,  (map (encode t) l)) ++ ]

  -- example Mixins

  data Id = Id

  instance Mixin a Id where
  mixin Id _ = id

  data TypeOf = TypeOf

  instance Typeable a = Mixin a TypeOf where
  mixin TypeOf t s = ( ++ s ++  ::  ++ show (typeOf t) ++ )

  instance Mixin a (String - String) where
  mixin f a = f

  -- this one can be used for combining mixins
  instance (Mixin a x, Mixin a y) = Mixin a (x, y) where
  mixin (x, y) a = mixin x a . mixin y a

  -- some unTypeable type

  data T a = T a

  instance (Serializer a t, Mixin (T a) t) = Serializer (T a) t where
  encodePrim t (T a) = (T  ++ encode t a ++ )

Example uses:

  *B putStrLn $ encode Id 'a'
  'a'
  *B putStrLn $ encode TypeOf 'a'
  ('a' :: Char)
  *B putStrLn $ encode Id ([1..4] :: [Int])
  [1, 2, 3, 4]
  *B putStrLn $ encode TypeOf ([1..4] :: [Int])
  ([(1 :: Int), (2 :: Int), (3 :: Int), (4 :: Int)] :: [Int])
  *B putStrLn $ encode (TypeOf, TypeOf) ([1..4] :: [Int])
  (([((1 :: Int) :: Int), ((2 :: Int) :: Int), ((3 :: Int) :: Int), ((4 ::
  Int) :: Int)] :: [Int]) :: [Int])
  *B putStrLn $ encode Id (T Hello)
  (T ['H', 'e', 'l', 'l', 'o'])
  *B putStrLn $ encode TypeOf (T Hello)

  interactive:1:
  No instances for (Typeable (T [Char]), Show (IO ()))
arising from use of `encode' at interactive:1
  In the second argument of `($)', namely `encode TypeOf (T Hello)'
  In the definition of `it':
  it = putStrLn $ (encode TypeOf (T Hello))

  interactive:1:
  No instances for (Typeable (T [Char]), Show (IO ()))
arising from use of `print' at interactive:1
  In a 'do' expression: print it

I hope that helps,

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links

Re: [Haskell] XML Serialization and type constraints

2004-08-25 Thread Simon D. Foster
On Wed, 2004-08-25 at 08:39, Tomasz Zielonka wrote:
- snip -

 I hope that helps,
 
 Best regards,
 Tom

That method works perfectly! Thank you so much! I assume there is no way
of achieving this without overlapping instances?

Thanks,

-Si.

-- 
Simon D. Foster [EMAIL PROTECTED]
Sheffield University

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] XML Serialization and type constraints

2004-08-25 Thread Tomasz Zielonka
On Wed, Aug 25, 2004 at 01:54:08PM +0100, Simon D. Foster wrote:
 On Wed, 2004-08-25 at 08:39, Tomasz Zielonka wrote:
 - snip -
 
  I hope that helps,
  
  Best regards,
  Tom
 
 That method works perfectly! Thank you so much! I assume there is no way
 of achieving this without overlapping instances?

Not overlapping, only undecidable. Well, I am not sure. I already
thought about it and I think that it would be possible, but the code
could be much less readable. These instances should be quite 'decidable',
unless someone makes instances of Serializer and Mixin mutually
recursive.

Maybe I will try after work, unless someone else has some good idea?

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] XML Serialization and type constraints

2004-08-25 Thread Simon D. Foster
On Wed, 2004-08-25 at 14:00, Tomasz Zielonka wrote:
 On Wed, Aug 25, 2004 at 01:54:08PM +0100, Simon D. Foster wrote:
  On Wed, 2004-08-25 at 08:39, Tomasz Zielonka wrote:
  - snip -
  
   I hope that helps,
   
   Best regards,
   Tom
  
  That method works perfectly! Thank you so much! I assume there is no way
  of achieving this without overlapping instances?

I think I jumped the gun it a bit; it almost works, but when I try to
declare a serializer for a type with several parts e.g.

data Person = Person PackedString PackedString Int

instance (Hook Person t) = Serializer Person t where ...

If I try to call encode on any of the attributes I get;

Could not deduce (Hook PackedString t)
from the context (Serializer Person t,
  Hook Person t,
  Hook Person t)

Thus, I have to add a (Hook x t) constraint for every type that is part
of the given data-type. For your example try;

data D = D Int  
instance (Mixin D t) = Serializer D t where
  encodePrim t (D n) = (D  ++ encode t n ++ )

Is there anyway of getting around this?

Thanks,

-Si.

-- 
Simon D. Foster [EMAIL PROTECTED]
Sheffield University

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] XML Serialization and type constraints

2004-08-25 Thread Tomasz Zielonka
On Wed, Aug 25, 2004 at 04:14:48PM +0100, Simon D. Foster wrote:
 I think I jumped the gun it a bit; it almost works, but when I try to
 declare a serializer for a type with several parts e.g.
 
 data Person = Person PackedString PackedString Int
 
 instance (Hook Person t) = Serializer Person t where ...
 
 If I try to call encode on any of the attributes I get;
 
 Could not deduce (Hook PackedString t)
 from the context (Serializer Person t,
   Hook Person t,
   Hook Person t)
 
 Thus, I have to add a (Hook x t) constraint for every type that is part
 of the given data-type. For your example try;
 
 data D = D Int  
 instance (Mixin D t) = Serializer D t where
   encodePrim t (D n) = (D  ++ encode t n ++ )
 
 Is there anyway of getting around this?

Perhaps you could just 'encode Id' that parts?

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] XML Serialization and type constraints

2004-08-25 Thread Simon D. Foster
On Wed, 2004-08-25 at 16:19, Tomasz Zielonka wrote:
  
  Is there anyway of getting around this?
 
 Perhaps you could just 'encode Id' that parts?
 
 Best regards,
 Tom

Ok then, well it looks like this method is going to very cumbersome to
use; for example a context for a reasonably simple complex data-type
would be;

(Hook Element t, Hook Bool t, Hook [ERS] t, Hook (Selection ERS) t, Hook
ERS t, Hook (Maybe PackedString) t, Hook PackedString t, Hook
IsQualified t, Hook (Ser t) t, Hook Int t, Hook (Maybe QName) t, Hook
QName t)

(and baring in mind most of the auto-generated code will have types
namespace qualified making that humongously long).

So I was thinking of another method of doing this;

First of all I though of scrapping the extra type-class and just using a
simple extra parameter; e.g. type Mixer a = a - (String - String). But
this doesn't work for any sort of recursive since the a is always
unified with the top-level type. Unless there's someway of getting
around this?

Another thought I had was to use an existentially quantified type to
represent the Mix function;

type Mix = forall a . a - (String - String)

but I don't think this will allow extra constraints to be brought in. 

Is there any other way of doing this without another type-class?

-Si.


-- 
Simon D. Foster [EMAIL PROTECTED]
Sheffield University

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] XML Serialization and type constraints

2004-08-25 Thread Tomasz Zielonka
On Wed, Aug 25, 2004 at 08:38:51PM +0100, Simon D. Foster wrote:
 Ok then, well it looks like this method is going to very cumbersome to
 use; for example a context for a reasonably simple complex data-type
 would be;
 
 (Hook Element t, Hook Bool t, Hook [ERS] t, Hook (Selection ERS) t, Hook
 ERS t, Hook (Maybe PackedString) t, Hook PackedString t, Hook
 IsQualified t, Hook (Ser t) t, Hook Int t, Hook (Maybe QName) t, Hook
 QName t)

Well, yes, that can be tiresome. You can copy/paste this from compiler
error message, but that won't help you to keep these huge contexts up to
date if you remove some fields of your data types.

Hmmm, it is worse that I thought. The contexts will accumulate, like a
snowball. If you have:

data A = A Int
data B = B A
data C = C B
data D = D C

then in the instance for D you would have to include context for all
Int, A, B, C and D.

Apparently this solution doesn't scale. I can think about some hack, but
I'm not sure you will like it, because it introduces more type classes,
one per datatype.

  data S = S { sA :: Int, sB :: String, sC :: [Int] }

  class (Mixin Int t, Mixin Char t, Mixin String t, Mixin [Int] t, Mixin S t) = 
Mixin_S t
  instance (Mixin Int t, Mixin Char t, Mixin String t, Mixin [Int] t, Mixin S t) = 
Mixin_S t

  instance (Mixin_S t) = Serializer S t where
  encodePrim t s =
  concat
  [ S { 
  , encode t (sA s)
  , , 
  , encode t (sB s)
  , , 
  , encode t (sC s)
  ,  }
  ]

  data R = R { rA :: Int, rS :: S }

  class (Mixin_S t, Mixin Int t, Mixin R t) = Mixin_R t where
  instance (Mixin_S t, Mixin Int t, Mixin R t) = Mixin_R t where

  instance (Mixin_R t) = Serializer R t where
  encodePrim t r =
  concat
  [ R { 
  , encode t (rA r)
  , , 
  , encode t (rS r)
  ,  }
  ]

I am moving this big contexts to superclasses of additional classes
Mixin_S and Mixin_R. This way the contexts don't accumulate. These
class/instance pairs could be easily generated with Template Haskell.
But it's a bit ugly.

 Is there any other way of doing this without another type-class?

That would be interesting.

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] XML Serialization and type constraints

2004-08-24 Thread Simon D. Foster
I'm trying to implement an extensible XML De/Serializer in Haskell for
use with SOAP and XML Schema (using the Haskell XML Toolbox). The idea
is you have a type-class, which is instantiated for each type you want
to encode/de-encode. This class (atm) takes the form;

class XMLSerializer a where
encodeElements:: NamespaceTable - Flags - a - [XmlFilter]
encodeAttributes  :: NamespaceTable - Flags - a - [XmlFilter]
encodeTree  :: NamespaceTable - String - Flags - a - XmlFilter
encodeTrees :: NamespaceTable - String - Flags - a - [XmlFilter]

decodeAttribute   :: String - XmlTree - Maybe a
decodeElement :: XmlTree - Maybe a
decodeTree:: XmlTree - Maybe a
decodeTrees   :: XmlTrees - Maybe a

(and a few default instances)

This type-class can then be used recursively to build XML
representations of Haskell data.

I now want to expand this system to make is more extensible. For
starters, to make it useful with SOAP, I need to add optional explicit
typing of data. To this end I have another class; XSDType, which stores
the XSD equivalent name and name-space for a particular Haskell type.
This is what is used to add explicit type data to the XML documents.
Adding this data involves adding an extra attribute to each node in the
tree. More generally however each Hook, which adds extra data at each
node has type NamespaceTable - Flags - a - ([XmlFilter],
[XmlFilter]), where a is the type of the value.

However, this is where the problem comes. How do I go about expressing
that a has a constraint XSDType a? I don't want to add this constraint
to the Serializer class itself since an XML tree may not be typed by
XSD. Somehow I need a way of adding extra constraints to a dynamically.

My first idea was to create another class Encoder;

class Encoder e a where
encode :: NamespaceTable - Flags - e - a - ([XmlFilter],
[XmlFilter])

Encoder is parameterized over two types; the first being a type to
represent the hook itself and the second is the type of the value being
serialized. Thus if I introduced this new class into the Serializer
class non parametrically; eg for encodeElements;

encodeElements :: Encoder e a = NamespaceTable - Flags - e - a -
[XmlFilter]

I can create a dummy type SOAPEnc and an instance of Encoder for it with
the appropriate constraint;

data SOAPEnc = SOAPEnc
instance XSDType a = Encoder SOAPEnc a where
encode ... = ...

and passing SOAPEnc to encodeElements as the e parameter would force the
constraint XSDType onto a. This system works fine in theory, but the
problem comes when I actually try to call encodeElements on any value
parameterised across a. For example lets say we wanted to Serialize a
list of Serializeables;

instance Serializable a = Serializable [a] where
encodeTrees nst n f e x = map (encodeTree nst n f e) x

This does not work because Encoder is parameterized over e and [a] and I
get;

Could not deduce (Encoder e a, XMLSerializer a) 
from the context (XMLSerializer [a], Encoder e [a])

The obvious way to fix this would be with an extra constraint on the
instance; instance (Encoder e a, Serializable a) = Serializable [a].
But since e is not parameterized in Serializable this doesn't help. I
could add an extra parameter to Serializable but this would mean that
for every different hook, I'd need to duplicate all the serializer
functions and the decode functions would all require to be passed an
encoding parameter even though they don't need one. This frankly defeats
the whole objective of a hook system.

My question is this; Is there any way of inserting extra constraints
on 'a' by passing some form of extra parameter to the appropriate
function or by another method and is there anyway of making the above
method work?

-Si.

(Please CC me replies as I'm not subscribed).

-- 
Simon D. Foster [EMAIL PROTECTED]
Sheffield University

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell