<html><head></head><body style="word-wrap: break-word; -webkit-nbsp-mode: space; -webkit-line-break: after-white-space; ">Ok, I got basic implementations of both methods to work, and what's interesting is how similar the syntax is. &nbsp;I'm going to post it here for anyone who wants to comment, but also for anyone who stumbles upon this thread and wants to see where it leads.<div><br></div><div>Here's the relevant parts of the Existential Types implementation:</div><div><br></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">{-# LANGUAGE ExistentialQuantification #-}</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;"><br></span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">data RenderContext = RenderContext {}<br><br>class Plottable a where<br>&nbsp;&nbsp;renderPlot &nbsp;:: a -&gt; RenderContext -&gt; IO ()<br><br>data PlotWrap = forall a. Plottable a =&gt; PlotWrap a<br><br>instance Plottable PlotWrap where<br>&nbsp;&nbsp;renderPlot (PlotWrap a) = renderPlot a<br><br>data ScatterPlot = ScatterPlot {scatterPoints :: [(Double,Double)]<br>&nbsp;&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; ,pointColor :: Color&nbsp;<br>&nbsp;&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; ,pointSize :: GL.GLfloat}<br><br>defScatterPlot = ScatterPlot {scatterPoints=[]<br>&nbsp;&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; ,pointColor = red<br>&nbsp;&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; ,pointSize = 1}<br><br>instance Plottable ScatterPlot where<br>&nbsp;&nbsp;renderPlot plot@(ScatterPlot {}) context = do<br>&nbsp;&nbsp; &nbsp;GL.color $ pointColor plot<br>&nbsp;&nbsp; &nbsp;GL.pointSize $= pointSize plot<br>&nbsp;&nbsp; &nbsp;GL.renderPrimitive GL.Points $ mapM_ GL.vertex (map pair2vertex $ scatterPoints plot)<br></span></font><br></div><div>Which I use by creating ScatterPlots (the noise functions aren't worth showing here, but they let me plot random data):</div><div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;"><br></span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">testScatter=defScatterPlot {scatterPoints=zip (map (*1) (take 2000 $ uniformNoise 0))&nbsp;</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp;(map (*1) (take 2000 $ uniformNoise 1))}</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;"><br></span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">testScatter2=defScatterPlot {scatterPoints=zip (map (\x -&gt; 5 + x ) (take 2000 $ gaussianNoise 0))&nbsp;</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; (map (\x -&gt; 5 + x ) (take 2000 $ gaussianNoise 1))}</span></font></div></div><div><br></div><div>and then calling this in the OpenGL display callback:</div><div><br></div><div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">mapM_ (($ RenderContext) . renderPlot) [PlotWrap testScatter,PlotWrap testScatter2]</span></font></div></div><div><br></div><div>-----------------------------------------------------------------------------------------------------</div><div>Now here's the "thunked" version (perhaps I'm abusing the term?):</div><div><br></div><div><span class="Apple-style-span" style="font-family: 'Courier New'; font-size: 11px; ">data RenderContext = RenderContext {}</span><span class="Apple-style-span" style="font-family: 'Courier New'; font-size: 11px; "><br></span></div><div><br></div><div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">data PlotThunk = PlotThunk {renderer :: RenderContext -&gt; IO ()}</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;"><br></span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">class Plottable a where</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp;renderPlot &nbsp;:: a -&gt; RenderContext -&gt; IO ()</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp;createThunk :: a -&gt; PlotThunk</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp;createThunk x = PlotThunk {renderer = renderPlot x}</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;"><br></span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">instance Plottable PlotThunk where</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp;renderPlot p context=(renderer p) context</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp;createThunk x = x</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;"><br></span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">data ScatterPlot = ScatterPlot {scatterPoints :: [(Double,Double)]</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; ,pointColor :: Color&nbsp;</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; ,pointSize :: GL.GLfloat}</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;"><br></span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">defScatterPlot = ScatterPlot {scatterPoints=[]</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; ,pointColor = red</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; ,pointSize = 1}</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;"><br></span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">instance Plottable ScatterPlot where</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp;renderPlot plot@(ScatterPlot {}) context = do</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp; &nbsp;GL.color $ pointColor plot</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp; &nbsp;GL.pointSize $= pointSize plot</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp; &nbsp;GL.renderPrimitive GL.Points $ mapM_ GL.vertex (map pair2vertex $ scatterPoints plot)</span></font></div></div><div><br></div><div>I create the ScatterPlots in exactly the same way:</div><div><br></div><div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">testScatter=defScatterPlot {scatterPoints=zip (map (*1) (take 2000 $ uniformNoise 0))&nbsp;</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp;(map (*1) (take 2000 $ uniformNoise 1))}</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;"><br></span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">testScatter2=defScatterPlot {scatterPoints=zip (map (\x -&gt; 5 + x ) (take 2000 $ gaussianNoise 0))&nbsp;</span></font></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">&nbsp;&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; (map (\x -&gt; 5 + x ) (take 2000 $ gaussianNoise 1))}</span></font></div></div><div><br></div><div>and then use this to in the OpenGL callback:</div><div><br></div><div><font class="Apple-style-span" face="'Courier New'" size="3"><span class="Apple-style-span" style="font-size: 11px;">mapM_ (($ RenderContext) . renderPlot) [createThunk testScatter,createThunk testScatter2]</span></font></div><div><br></div><div>------------------------------------------------------------</div><div><br></div><div>The principle differences I see so far (more may appear as I add more plot styles) are these:</div><div><br></div><div>Both versions require creating one additional data type and an added function call when creating the list (creating the thunk, or wrapping the data). &nbsp;The existential type version requires the use of a language extension, but has less confusing syntax and looks like a value construction when forming that list. &nbsp;The thunked version has a slightly more complex class definition, but the calling code is no more complex than the existential typed version.</div><div><br></div><div><br></div><div>Cheers--</div><div>&nbsp;Greg</div><div><br></div><div><br></div><div><br></div><div><br></div><div><br><div><div>On Sep 6, 2010, at 11:44 PM, Greg Best wrote:</div><br class="Apple-interchange-newline"><blockquote type="cite"><div>Two great suggestions (attached below for context), thanks to Daniel and Stephen, both.<br><br>Since a large part of my goal here is to learn the language, I'll probably try both of these just to make sure I can.<br><br><blockquote type="cite">From a cultural standpoint, is there a preferred approach? &nbsp;Existential Types sits more nicely with my OO background and is a more exact interpretation of what I was trying to do, but is that seen as "impure" under Haskell? &nbsp;More generally, what should I keep in mind when using language extensions? &nbsp;Are Existential Types supported across implementations? &nbsp;Are they a likely candidate for adoption into the language proper? &nbsp;Are there performance implications (such as future parallelization)?<br></blockquote><br>Stephen's solution is obvious now that it's been presented. &nbsp;I'm not planning on using GnuPlot, I'm mucking around with the OpenGL bindings, but the point is, I think, the same: don't make a list of of objects, make a list of functions. &nbsp;In this case, they'd be more along the lines of ApplicationContext -&gt; IO ().<br><br>I suppose I could also create a type that contains the disembodied methods from the various plot styles:<br><br>data PlotThunks = PlotThunks { render:: Context -&gt; IO ()<br> &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;, hitTest:: Point -&gt; Bool<br> &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;, extents:: Context -&gt; Rect}<br><br>then functions (perhaps a typeclass method) that build values of that type from each of the various plot styles.<br><br>plotList :: [PlotThunks]<br><br>renderAll :: Context -&gt; [PlotThunks] -&gt; &nbsp;IO ()<br>renderAll context plots= mapM_ (($ context) . render) plots<br><br><br>Thanks again--<br> Greg<br><br><br><br>On Sep 6, 2010, at 6:14 AM, Daniel Fischer wrote:<br><br><blockquote type="cite">you can combine the approaches. As long as all you want to do with your <br></blockquote><blockquote type="cite">container is rendering the contents, <br></blockquote><blockquote type="cite"><br></blockquote><blockquote type="cite">{-# LANGUAGE ExistentialQuantification #-}<br></blockquote><blockquote type="cite"><br></blockquote><blockquote type="cite">class Plot a where<br></blockquote><blockquote type="cite"> &nbsp;&nbsp;render :: a -&gt; IO ()<br></blockquote><blockquote type="cite"> &nbsp;&nbsp;describe :: a -&gt; String<br></blockquote><blockquote type="cite"><br></blockquote><blockquote type="cite">data SomePlot = forall p. Plot p =&gt; SomePlot p<br></blockquote><blockquote type="cite"><br></blockquote><blockquote type="cite">instance Plot SomePlot where<br></blockquote><blockquote type="cite"> &nbsp;&nbsp;render (SomePlot p) = render p<br></blockquote><blockquote type="cite"> &nbsp;&nbsp;describe (SomePlot p) = describe p<br></blockquote><blockquote type="cite"><br></blockquote><blockquote type="cite">gives you a class, so you can define new plot types without modifying the <br></blockquote><blockquote type="cite">library, and a wrapper type, so you can stick plots of different types in <br></blockquote><blockquote type="cite">the same container after wrapping them.<br></blockquote><blockquote type="cite">Once they're wrapped, you can't use anything but the methods of the Plot <br></blockquote><blockquote type="cite">class on them, though, so if you want to do anything else with the <br></blockquote><blockquote type="cite">container's contents, that won't work (you can do something with an <br></blockquote><blockquote type="cite">additional Typeable constraint).<br></blockquote><blockquote type="cite"><br></blockquote><blockquote type="cite"><a href="http://www.haskell.org/haskellwiki/Existential_type">http://www.haskell.org/haskellwiki/Existential_type</a> for more.<br></blockquote><br>On Sep 6, 2010, at 7:57 AM, Stephen Tetley wrote:<br><br><blockquote type="cite">Supposing you are working with GnuPlot - one option is to make Plot a<br></blockquote><blockquote type="cite">functional type that takes a list of some polymorphic input data and<br></blockquote><blockquote type="cite">generates a 'GnuPlot' - where GnuPlot is a type representing output in<br></blockquote><blockquote type="cite">the GnuPlot format.<br></blockquote><blockquote type="cite"><br></blockquote><blockquote type="cite">type Plot a = [a] -&gt; GnuPlot<br></blockquote><blockquote type="cite"><br></blockquote><blockquote type="cite">Or if GnuPlot accepts drawing styles...<br></blockquote><blockquote type="cite"><br></blockquote><blockquote type="cite">type Plot a = [a] -&gt; DrawingStyle -&gt; GnuPlot<br></blockquote><blockquote type="cite"><br></blockquote><blockquote type="cite">Plots are just functions, so clearly you can define as many as you<br></blockquote><blockquote type="cite">like and they are all the same type.<br></blockquote>_______________________________________________<br>Beginners mailing list<br><a href="mailto:Beginners@haskell.org">Beginners@haskell.org</a><br>http://www.haskell.org/mailman/listinfo/beginners<br></div></blockquote></div><br></div></body></html>