Sorry , the following line got lost in the copy &amp; paste:<div><br></div><div><font class="Apple-style-span" face="&#39;courier new&#39;, monospace">   {-# LANGUAGE ExistentialQuantification #-}</font><br clear="all"><br>

-Tako<br>
<br><br><div class="gmail_quote">On Tue, Mar 29, 2011 at 11:09, Tako Schotanus <span dir="ltr">&lt;<a href="mailto:tako@codejive.org">tako@codejive.org</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex;">

Hi,<div><br></div><div>just so you know that I have almost no idea what I&#39;m doing, I&#39;m a complete Haskell noob, but trying a bit I came up with this before getting stuck:</div><div><br></div><div><div><font face="&#39;courier new&#39;, monospace">   class Drawable a where</font></div>


<div><font face="&#39;courier new&#39;, monospace">      draw :: a -&gt; String</font></div><div class="im"><div><font face="&#39;courier new&#39;, monospace"><br></font></div><div><font face="&#39;courier new&#39;, monospace">   data Rectangle = Rectangle { rx, ry, rw, rh :: Double }</font></div>


<div><font face="&#39;courier new&#39;, monospace">      deriving (Eq, Show)</font></div><div><span style="white-space:pre-wrap"><font face="&#39;courier new&#39;, monospace">        </font></span></div>
</div><div><font face="&#39;courier new&#39;, monospace">   instance Drawable Rectangle where</font></div><div><font face="&#39;courier new&#39;, monospace">      draw (Rectangle rx ry rw rh) = &quot;Rect&quot;</font></div>

<div class="im">
<div><span style="white-space:pre-wrap"><font face="&#39;courier new&#39;, monospace">        </font></span></div><div><font face="&#39;courier new&#39;, monospace">   data Circle = Circle { cx, cy, cr :: Double }</font></div>
<div><font face="&#39;courier new&#39;, monospace">      deriving (Eq, Show)</font></div><div><span style="white-space:pre-wrap"><font face="&#39;courier new&#39;, monospace">        </font></span></div>
</div><div><font face="&#39;courier new&#39;, monospace">   instance Drawable Circle where</font></div><div><font face="&#39;courier new&#39;, monospace">      draw (Circle cx cy cr) = &quot;Circle&quot;</font></div>
<div><font face="&#39;courier new&#39;, monospace"><br></font></div><div><font face="&#39;courier new&#39;, monospace">   data Shape = ???</font></div><div><br></div><div>
Untill I read about existential types here: <a href="http://www.haskell.org/haskellwiki/Existential_type" target="_blank">http://www.haskell.org/haskellwiki/Existential_type</a></div><div><br></div>And was able to complete the definition:</div>


<div><br></div><div><div><font face="&#39;courier new&#39;, monospace">   data Shape = forall a. Drawable a =&gt; Shape a</font></div></div><div><br></div><div>Testing it with a silly example:</div>
<div><br></div><div><div><font face="&#39;courier new&#39;, monospace">   main :: IO ()</font></div><div><font face="&#39;courier new&#39;, monospace">   main =  do putStr (test shapes)</font></div>
<div><font face="&#39;courier new&#39;, monospace"><br></font></div><div><font face="&#39;courier new&#39;, monospace">   test :: [Shape] -&gt; String</font></div><div><font face="&#39;courier new&#39;, monospace">   test [] = &quot;&quot;</font></div>


<div><font face="&#39;courier new&#39;, monospace">   test ((Shape x):xs) = draw x ++ test xs</font></div><div><font face="&#39;courier new&#39;, monospace"><br></font></div>
<div><font face="&#39;courier new&#39;, monospace">   shapes :: [Shape]</font></div><div><font face="&#39;courier new&#39;, monospace">   shapes = [ Shape (Rectangle 1 1 4 4) , Shape (Circle 2 2 5) ]</font></div>
<div><br></div><div><br></div><div>Don&#39;t know if this helps...</div><div><br></div><div>Cheers,</div>-Tako<div><div></div><div class="h5"><br>
<br><br><div class="gmail_quote">On Tue, Mar 29, 2011 at 07:49, Tad Doxsee <span dir="ltr">&lt;<a href="mailto:tad.doxsee@gmail.com" target="_blank">tad.doxsee@gmail.com</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">


I&#39;ve been trying to learn Haskell for a while now, and recently<br>
wanted to do something that&#39;s very common in the object oriented<br>
world, subtype polymorphism with a heterogeneous collection.<br>
It took me a while, but I found a solution that meets<br>
my needs. It&#39;s a combination of solutions that I saw on the<br>
web, but I&#39;ve never seen it presented in a way that combines both<br>
in a short note. (I&#39;m sure it&#39;s out there somewhere, but it&#39;s off the beaten<br>
path that I&#39;ve been struggling along.)  The related solutions<br>
are<br>
<br>
1. section 3.6 of <a href="http://homepages.cwi.nl/~ralf/OOHaskell/paper.pdf" target="_blank">http://homepages.cwi.nl/~ralf/OOHaskell/paper.pdf</a><br>
<br>
2. The GADT comment at the end of section 4 of<br>
    <a href="http://www.haskell.org/haskellwiki/Heterogenous_collections" target="_blank">http://www.haskell.org/haskellwiki/Heterogenous_collections</a><br>
<br>
I&#39;m looking for comments on the practicality of the solution,<br>
and references to better explanations of, extensions to, or simpler<br>
alternatives for what I&#39;m trying to achieve.<br>
<br>
Using the standard example, here&#39;s the code:<br>
<br>
<br>
data Rectangle = Rectangle { rx, ry, rw, rh :: Double }<br>
                        deriving (Eq, Show)<br>
<br>
drawRect :: Rectangle -&gt; String<br>
drawRect r = &quot;Rect (&quot; ++ show (rx r) ++ &quot;, &quot;  ++ show (ry r) ++ &quot;) -- &quot;<br>
             ++ show (rw r) ++ &quot; x &quot; ++ show (rh r)<br>
<br>
<br>
data Circle = Circle {cx, cy, cr :: Double}<br>
                        deriving (Eq, Show)<br>
<br>
drawCirc :: Circle -&gt; String<br>
drawCirc c = &quot;Circ (&quot; ++ show (cx c) ++ &quot;, &quot; ++ show (cy c)++ &quot;) -- &quot;<br>
             ++ show (cr c)<br>
<br>
r1 = Rectangle 0 0 3 2<br>
r2 = Rectangle 1 1 4 5<br>
c1 = Circle 0 0 5<br>
c2 = Circle 2 0 7<br>
<br>
<br>
rs = [r1, r2]<br>
cs = [c1, c2]<br>
<br>
rDrawing = map drawRect rs<br>
cDrawing = map drawCirc cs<br>
<br>
-- shapes = rs ++ cs<br>
<br>
Of course, the last line won&#39;t compile because the standard Haskell list<br>
may contain only homogeneous types.  What I wanted to do is create a list of<br>
circles and rectangles, put them in a list, and draw them.  It was easy<br>
for me to find on the web and in books how to do that if I controlled<br>
all of the code. What wasn&#39;t immediately obvious to me was how to do that<br>
in a library that could be extended by others.  The references noted<br>
previously suggest this solution:<br>
<br>
<br>
class ShapeC s where<br>
  draw :: s -&gt; String<br>
  copyTo :: s -&gt; Double -&gt; Double -&gt; s<br>
<br>
-- needs {-# LANGUAGE GADTs #-}<br>
data ShapeD  where<br>
  ShapeD :: ShapeC s =&gt; s -&gt; ShapeD<br>
<br>
instance ShapeC ShapeD where<br>
  draw (ShapeD s) = draw s<br>
  copyTo (ShapeD s) x y = ShapeD (copyTo s x y)<br>
<br>
mkShape :: ShapeC s =&gt; s -&gt; ShapeD<br>
mkShape s = ShapeD s<br>
<br>
<br>
<br>
instance ShapeC Rectangle where<br>
  draw = drawRect<br>
  copyTo (Rectangle _ _ rw rh) x y = Rectangle x y rw rh<br>
<br>
instance ShapeC Circle where<br>
  draw = drawCirc<br>
  copyTo (Circle _ _ r) x y = Circle x y r<br>
<br>
<br>
r1s = ShapeD r1<br>
r2s = ShapeD r2<br>
c1s = ShapeD c1<br>
c2s = ShapeD c2<br>
<br>
shapes1 = [r1s, r2s, c1s, c2s]<br>
drawing1 = map draw shapes1<br>
<br>
shapes2 = map mkShape rs ++ map mkShape cs<br>
drawing2 = map draw shapes2<br>
<br>
-- copy the shapes to the origin then draw them<br>
shapes3 = map (\s -&gt; copyTo s 0 0) shapes2<br>
drawing3 = map draw shapes3<br>
<br>
<br>
Another user could create a list of shapes that included triangles by creating<br>
a ShapeC instance for his triangle and using mkShape to add it to a list of<br>
ShapeDs.<br>
<br>
Is the above the standard method in Haskell for creating an extensible<br>
heterogeneous list of &quot;objects&quot; that share a common interface?  Are there better<br>
approaches?  (I ran into a possible limitation to this approach that I plan<br>
to ask about later if I can&#39;t figure it out myself.)<br>
<br>
- Tad<br>
<br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org" target="_blank">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
</blockquote></div><br></div></div></div>
</blockquote></div><br></div>