
Hi, i am not quite sure how to do this in the most elegant way: I have some data structures: data A = A Double data B = B Double data C = C Double ... and i want to allow only a subset in another data structure, so i did something like this: data SubSet = SubSetA A | SubSetC C and use it in Foo: data Foo = Foo [SubSet] No i want to perform a polymorphic operation on the contents of A,B,C, e.g. doSomething :: Foo -> [Double] doSomething (Foo s) = map doSomethingElse s Now i have two questions: 1) Is the way i define and use "SubSet", the only/valid way to define subsets? 2) What's the best way to make "doSomethingElse" polymorphic? There's the tedious way: doSomethingElse (SubSetA x) = doSomethingElse x doSomethingElse (SubSetB x) = doSomethingElse x or i could make SubSet and A,B,C instances of a type class with the function "doSomethingElse". But i have several different subsets so the type class aproach feels like overkill for these helper structures. Whatever my approach is, it does not feel right. Can you help me step back and get the picture? Thanks, Lenny

Hi Lenny,
i am not quite sure how to do this in the most elegant way:
I have some data structures:
data A = A Double data B = B Double data C = C Double ...
and i want to allow only a subset in another data structure, so i did something like this:
data SubSet = SubSetA A | SubSetC C
and use it in Foo:
data Foo = Foo [SubSet]
No i want to perform a polymorphic operation on the contents of A,B,C, e.g.
doSomething :: Foo -> [Double] doSomething (Foo s) = map doSomethingElse s
You can do things similar to this using one of the many generics libraries for Haskell [1,2]. I'm not sure if this is exactly what you're after, but here is a possibility using EMGM [3]. {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-} {-# OPTIONS -fglasgow-exts #-}
import Generics.EMGM import Generics.EMGM.Derive
data A = A Double data B = B Double data C = C Double
data Subset = SubsetA A | SubsetC C
data Foo = Foo [Subset]
$(deriveMany [''A,''B,''C,''Subset,''Foo])
doSomething :: Foo -> [Double] doSomething = collect
In GHCi, I get the following: *Main> doSomething (Foo [SubsetA (A 5.0),SubsetC (C 9.9)]) [5.0,9.9] Other libraries to look at include SYB [4] and Uniplate [5]. Regards, Sean [1] http://hackage.haskell.org/packages/archive/pkg-list.html#cat:generics [2] http://www.cs.uu.nl/research/techreps/UU-CS-2008-010.html [3] http://www.cs.uu.nl/wiki/GenericProgramming/EMGM [4] http://www.cs.uu.nl/wiki/GenericProgramming/SYB [5] http://community.haskell.org/~ndm/uniplate/

On Wed, Dec 16, 2009 at 9:40 AM, haskell@kudling.de
Hi,
i am not quite sure how to do this in the most elegant way:
I have some data structures:
data A = A Double data B = B Double data C = C Double ...
and i want to allow only a subset in another data structure, so i did something like this:
data SubSet = SubSetA A | SubSetC C
I think you might be looking for too much sugar. I don't know much about your problem, but I would use approximately your approach and be straightforward: type SubSet = Either A C
and use it in Foo:
data Foo = Foo [SubSet]
No i want to perform a polymorphic operation on the contents of A,B,C, e.g.
doSomething :: Foo -> [Double] doSomething (Foo s) = map doSomethingElse s
doSomething (Foo s) = map (doSomethingWithA ||| doSomethingWithC) s (||| is from Control.Arrow) If that gets too complicated, you can build the "doSomething" functions in a type-directed way using typeclasses: class DoSomething a where doSomething :: a -> Double instance DoSomething A where ... instance DoSomething B where ... instance DoSomething C where ... instance (DoSomething a, DoSomething b) => DoSomething (Either a b) where doSomething = doSomething ||| doSomething Luke

Hi all, thanks for your ideas so far.
I think you might be looking for too much sugar. I don't know much about your problem, but I would use approximately your approach and be straightforward:
To bother you with some details: i am building a model for an SVG document. http://chlor.svn.sourceforge.net/viewvc/chlor/trunk/haskell/Chlor/FileFormat... There are many SVG elements, of which only a few are valid as the content of each other SVG elements. SvgDocumentElement defines the allowed subset for the SVG document. I want to generate a "DList Char" for all those sub-elements and finally collapse them to one "DList Char" representing the whole SVG document. So it's a bit more complicated than your "Either" example I need to manually efine such subset data structures for most SVG elements which does not feel most elegant already. Additionally instantiating a class for the subset structures, in order to being able to iterate over them, feels even more clumsy. So i wonder whether i am missing a more clean approach to the problem "easily combining data structures but also easy iteration over them".
type SubSet = Either A C
and use it in Foo:
data Foo = Foo [SubSet]
No i want to perform a polymorphic operation on the contents of A,B,C, e.g.
doSomething :: Foo -> [Double] doSomething (Foo s) = map doSomethingElse s
doSomething (Foo s) = map (doSomethingWithA ||| doSomethingWithC) s
(||| is from Control.Arrow)
If that gets too complicated, you can build the "doSomething" functions in a type-directed way using typeclasses:
class DoSomething a where doSomething :: a -> Double
instance DoSomething A where ... instance DoSomething B where ... instance DoSomething C where ...
instance (DoSomething a, DoSomething b) => DoSomething (Either a b) where doSomething = doSomething ||| doSomething
Luke

2009/12/17 haskell@kudling.de
Hi all,
thanks for your ideas so far.
I think you might be looking for too much sugar. I don't know much about your problem, but I would use approximately your approach and be straightforward:
To bother you with some details: i am building a model for an SVG document. http://chlor.svn.sourceforge.net/viewvc/chlor/trunk/haskell/Chlor/FileFormat...
There are many SVG elements, of which only a few are valid as the content of each other SVG elements. SvgDocumentElement defines the allowed subset for the SVG document.
I want to generate a "DList Char" for all those sub-elements and finally collapse them to one "DList Char" representing the whole SVG document. So it's a bit more complicated than your "Either" example
I need to manually efine such subset data structures for most SVG elements which does not feel most elegant already. Additionally instantiating a class for the subset structures, in order to being able to iterate over them, feels even more clumsy.
So i wonder whether i am missing a more clean approach to the problem "easily combining data structures but also easy iteration over them".
Hi, I think your approach is right, even if it seems a bit heavy. After all, the reason it seems heavy maps directly to the very fact your modeling a typed hierarchy of elements. The typing will provide guarantee about the well-formed-ness of your data. You can take a look at the GraphViz package, or TH; you will see such hierarchies. Using generics (such a pointed by the first answer you received) can make it easier to traverse the hierarchy. As a side note, to generate the final textual representation of your SVG document, you might want to look at some XML packages on hackage, if you haven't done yet. Cheers, Thu

Ohhh...
SVG is a truly horrible format though, that almost completely
disguises the fact you are working with geometry. Being rude about the
designers, its as if they realized half way through the job that
putting a function-free PostScript into angle brackets was far too
verbose, so they added several dozen convenience operations to over
egg the pudding (whilst burying Paths - the primordial element of
vector graphics - as a string literal).
Three years ago I tried to embed SVG in Oleg Kiselyov's CSXML. CSXML
is nice and gives you a lot of flexibility but can't disguise SVG's
failings.
I'd strongly recommend you simply choose a set of geometric objects
paths, polygons, whatever... and work with those, only considering SVG
as a final rendering step when you could probably just generate
strings (Wumpus my latest attempt a vector pictures does this).
Hope this helps - I can send you my SVG CXSML if you like but it
really isn't an approach I'd consider anymore.
Best wishes
Stephen
2009/12/17 haskell@kudling.de
To bother you with some details: i am building a model for an SVG document. http://chlor.svn.sourceforge.net/viewvc/chlor/trunk/haskell/Chlor/FileFormat...

I'd strongly recommend you simply choose a set of geometric objects paths, polygons, whatever... and work with those, only considering SVG as a final rendering step when you could probably just generate
I do, cheers. The SVG model is just an intermediate representation for the SVG export/import part. Past experience told me, mapping SVG to my own models in one pass gets pretty ugly. Bye, Lenny

There are many SVG elements, of which only a few are valid as the content of each other SVG elements. SvgDocumentElement defines the allowed subset for the SVG document.
I want to generate a "DList Char" for all those sub-elements and finally collapse them to one "DList Char" representing the whole SVG document. So it's a bit more complicated than your "Either" example
I suggest a monadic combinator approach. The grammar's the thing. Consider:
data View a = AtomicView a | NestViews (View a) (View a) (View a) | ConcatViews (View a) (View a) | Etc...
instance Monad View where return = AtomicView AtomicView v >>= f = f v (NestViews left middle right) >>= f = (ConcatViews (ConcatViews left middle) right) >>= f (ConcatViews left right) >>= f = ConcatVeiws (f left) (f right) -- Etc >>= f = whatever
These are "structural" nodes. Notice how >>= normalizes your document automagically. You would put your specific node types "in" Etc. Writing a renderer from something with this form is pretty straight forward. Enforcing constraints isn't too hard either. Neither is parsing. Just write a parser for each http://www.haskell.org/haskellwiki/Parsec http://legacy.cs.uu.nl/daan/download/parsec/parsec.html
participants (6)
-
Alexander Solla
-
haskell@kudling.de
-
Luke Palmer
-
minh thu
-
Sean Leather
-
Stephen Tetley