[Chart] Fwd: [diagrams] Re: [GSoC 2013] Progress - Porting Charts to Diagrams

Jan Bracker jan.bracker at googlemail.com
Wed Jun 12 19:05:50 BST 2013


Yes, that's true. We need to go that way so we can get text metrics.


2013/6/12 Brent Yorgey <byorgey at seas.upenn.edu>

> OK, makes sense.  And in any case when compiling Chart -> diagrams I
> guess you are going to want to convert text to paths via SVGFonts
> anyway, so how diagrams handles text natively is irrelevant for you.
>
> -Brent
>
> On Wed, Jun 12, 2013 at 06:28:39PM +0200, Jan Bracker wrote:
> > Well, I think the necessity of a font color depends on the context. I
> don't
> > know if it actually makes sense for diagrams, esspecially since you might
> > want stroke and fill your font separatly. But since the Chart data types
> > all contain a color attribute and fonts are always filled but never
> stroked
> > it makes sense for Charts.
> >
> >
> > 2013/6/12 Brent Yorgey <byorgey at seas.upenn.edu>
> >
> > > We keep the line color and fill color separate in diagrams (and
> > > indeed, we have to do a bit of extra work for the cairo backend since
> > > it only has the one source color).  We don't have a separate text
> > > color (the fill color is used) but maybe we should...? That would be
> > > easy enough to change (I'm 95% sure) if it would make things simpler
> > > for you.
> > >
> > > -Brent
> > >
> > > On Wed, Jun 12, 2013 at 04:45:02PM +0200, Jan Bracker wrote:
> > > > Hi everybody,
> > > >
> > > > a small follow up: While thinking about and implementing the smaller
> API
> > > I
> > > > noticed that due to the internals of Cairo the source color is used
> to
> > > > render everything. When setting a style (font, fill, line) the source
> > > color
> > > > is changed according to that style. This means each of the
> "with...Style"
> > > > or "withSourceColor" functions constantly overrides the source
> color. Is
> > > > this really desired behaviour? Shouldn't the fill color apply to
> fills,
> > > the
> > > > line color to strokes and the font color to text rendering? If so the
> > > > source color ("withSourceColor") is a useless concept. Of course
> keeping
> > > > these color seperate will expand the cairo rendering backend, but I
> think
> > > > it is useful to avoid confusion to which color is used where.
> > > >
> > > > Example:
> > > >
> > > > 1: withLineStyle ls $ withFillStyle fs $ fillPath p >> strokePath p
> > > >
> > > > should be the same as (according to my thoughts):
> > > >
> > > > 2: withFillStyle fs $ withLineStyle ls $ fillPath p >> strokePath p
> > > >
> > > > but with the current implementation 1 would render both with the fill
> > > color
> > > > and 2 would render them with the line color.
> > > >
> > > > Jan
> > > >
> > > >
> > > >
> > > > 2013/6/12 Jan Bracker <jan.bracker at googlemail.com>
> > > >
> > > > > Hi everybody,
> > > > >
> > > > > Brent: Thanks you for the offer and thanks for your great help on
> those
> > > > > nasty type errors yesterday.
> > > > >
> > > > > On IO in Diagrams: We looked into the SVGFont rendering stuff and
> > > noticed
> > > > > that it has a call to unsafePerformIO (which let us scream in pain
> and
> > > > > agony :-P ). We though it would be nice to remove this hidden call
> and
> > > > > actually offer a function that makes it explicit. I am not sure
> why it
> > > is
> > > > > there and assume its purpose is to keep everything pure. Your
> > > suggestion to
> > > > > produce a IO Diagram is what we thought of too. We are not sure
> which
> > > > > changes would be required up to now, but we will come back to you
> when
> > > we
> > > > > do know.
> > > > >
> > > > > On general note: I have worked on abstracting the backend the last
> two
> > > > > days. Here what I accomplished by now:
> > > > >
> > > > > - I have fully converted my branch to use the abstract rendering
> > > backend
> > > > > ChartBackend [0] instead of the CRender monad directly.
> > > > >
> > > > > - There is a implementation of the backend with Cairo in the
> > > Backend.Cairo
> > > > > module [1].
> > > > >
> > > > > - The current HEAD of the backend-experiment branch [2] is stable
> > > > > (commit ad715c4d216e8fcb494f9919d4fb5459ce7d85c2).
> > > > >
> > > > > - I added reference images [3] of all tests to compare with the
> results
> > > > > that the original code delivered.
> > > > >
> > > > > - All tests are running using the new backend code and pixel-diffs
> [4]
> > > of
> > > > > the produced PNGs show that they render exactly the same.
> > > > >
> > > > > - I ran into the issue that the ToRenderable class was complicated
> to
> > > > > abstract. My abstraction involved a associated type with two
> parameters
> > > > > that are in relation to each other [5,6]. After talking with Tim I
> > > removed
> > > > > the ToRenderable code completely and instead just exported specific
> > > > > functions for all types directly. This also made the examples
> easier to
> > > > > adjust, since the new ToRenderable class made type annotations
> > > necessary
> > > > > everywhere, which, in my point of view, defeats the purpose of the
> > > > > toRenderable function. It was easier just calling the specific
> function
> > > > > directly. I think the change of API is acceptable, since the
> > > generalised
> > > > > backend lets type parameters popup everywhere anyway.
> > > > >
> > > > > The next steps:
> > > > >
> > > > > - Tim suggested this simplified API instead of the rather
> extensive [0]
> > > > > version used right now: http://hpaste.org/89758 . I will work on
> > > trimming
> > > > > down the current API and providing all complex functions in terms
> of
> > > the
> > > > > new API.
> > > > > - The only downside I see is the Matrix type which (I assume) comes
> > > from
> > > > > Cairo.Matrix [7]. I would just give a naive implementation that
> > > contains 6
> > > > > double values for the affine transformations and provide a similar
> > > custom
> > > > > API.
> > > > > - I will also try to provide a small EDSL for writing paths to make
> > > that
> > > > > easier (I guess some short combinators and a monoid instance will
> do
> > > fine).
> > > > >
> > > > > Jan
> > > > >
> > > > > [0]:
> > > > >
> > >
> https://github.com/jbracker/haskell-chart/blob/backend-experiment/chart/Graphics/Rendering/Chart/Types.hs#L85
> > > > > [1]:
> > > > >
> > >
> https://github.com/jbracker/haskell-chart/blob/backend-experiment/chart/Graphics/Rendering/Chart/Backend/Cairo.hs#L80
> > > > > [2]:
> > > > >
> > >
> https://github.com/jbracker/haskell-chart/tree/ad715c4d216e8fcb494f9919d4fb5459ce7d85c2
> > > > > [3]:
> > > > >
> > >
> https://github.com/jbracker/haskell-chart/tree/backend-experiment/chart/tests-reference
> > > > > [4]:
> > > > >
> > >
> https://github.com/jbracker/haskell-chart/blob/backend-experiment/chart/gen-diffs-png.sh
> > > > > [5]:
> > > > >
> > >
> https://github.com/jbracker/haskell-chart/blob/backend-experiment/chart/Graphics/Rendering/Chart/Renderable.hs#L77
> > > > > [6]:
> > > > >
> > >
> https://github.com/jbracker/haskell-chart/blob/backend-experiment/chart/Graphics/Rendering/Chart/Layout.hs#L163
> > > > > [7]:
> > > > >
> > >
> http://hackage.haskell.org/packages/archive/cairo/0.12.4/doc/html/Graphics-Rendering-Cairo-Matrix.html
> > > > >
> > > > >
> > > > > 2013/6/11 Brent Yorgey <byorgey at seas.upenn.edu>
> > > > >
> > > > >> Hi Jan and all,
> > > > >>
> > > > >> Looks like some great progress!  I'm excited. =) Just a couple
> > > > >> thoughts: one, let me know if you want help staring at the funny
> type
> > > > >> errors with Legend and whatnot.  I'm not familiar with the Chart
> code
> > > > >> but perhaps I can help figure out a good solution for the
> abstraction.
> > > > >>
> > > > >> My other general comment is that I know you and Tim have talked a
> bit
> > > > >> about the problems with having font stuff in IO whereas diagrams
> is
> > > > >> pure.  However, from my point of view it wouldn't be that big of a
> > > > >> deal if Chart produced an IO Diagram rather than just a Diagram.
> > > > >> Maybe I haven't thought about it sufficiently but it seems like
> this
> > > > >> would be an easy solution to the problem of needing IO.  I'm
> happy to
> > > > >> talk about it in more detail if you want, and if there are ways
> that
> > > > >> the diagrams API could change to make any of this easier I'm
> happy to
> > > > >> discuss that as well. I'm in the middle of some big refactoring
> anyway
> > > > >> (though don't worry, I don't think it will affect your work on
> porting
> > > > >> Chart very much).
> > > > >>
> > > > >> -Brent
> > > > >>
> > > > >> On Mon, Jun 10, 2013 at 05:24:34PM +0200, Jan Bracker wrote:
> > > > >> > Hi,
> > > > >> >
> > > > >> > Andy: The goal is to abstract Charts from Cairo so we can plug
> in
> > > > >> another
> > > > >> > backend (target is Diagrams). And by that we would also be able
> to
> > > use
> > > > >> > Sunroof through diagrams. Of course in the end it should also be
> > > > >> possible
> > > > >> > to implement a Sunroof backend on its own.
> > > > >> >
> > > > >> > Tim:
> > > > >> >
> > > > >> >  > Rather than have the CRender monad take an extra parameter, I
> > > guess
> > > > >> one
> > > > >> > > could just have a separate data type for each backend (ie
> > > > >> CRenderCairo and
> > > > >> > > CRenderDiagrams) and have the drawing code abstracted over a
> > > typeclass
> > > > >> > > implemented by both. Not sure if this would be better...
> > > > >> > >
> > > > >> >
> > > > >> >  I tried your approach in a new branch:
> > > > >> >
> https://github.com/jbracker/haskell-chart/tree/backend-experiment
> > > > >> >
> > > > >> > It seems to be working quite well. So I started generalizing
> > > everything
> > > > >> > outside of the cairo module to use a general ChartBackend m
> instead
> > > of a
> > > > >> > CRender to draw everything. There are a few spots that are
> giving
> > > me a
> > > > >> hard
> > > > >> > time:
> > > > >> >
> > > > >> > Renderable was implemented in terms of CRender. So I added
> another
> > > type
> > > > >> > parameter and that worked fine until I hit Legend. There I also
> > > added a
> > > > >> > type parameter. But that blew up the ToRenderable instance. So I
> > > had to
> > > > >> > insert a associated type to relate types to each other. After
> doing
> > > so I
> > > > >> > was not able to fix whatever went wrong in Plot.Pie. The
> > > 'ToRenderable
> > > > >> > PieLayout' instance gives me this error:
> > > > >> >
> > > > >> > Graphics/Rendering/Chart/Plot/Pie.hs:121:62:
> > > > >> >     Could not deduce (RenderableT m a0 ~ PieChart)
> > > > >> >     from the context (ChartBackend m)
> > > > >> >       bound by the type signature for
> > > > >> >                  toRenderable :: ChartBackend m =>
> > > > >> >                                  RenderableT m PieLayout ->
> > > Renderable
> > > > >> m ()
> > > > >> >       at Graphics/Rendering/Chart/Plot/Pie.hs:(117,5)-(125,29)
> > > > >> >     The type variable `a0' is ambiguous
> > > > >> >     Possible fix: add a type signature that fixes these type
> > > variable(s)
> > > > >> >     In the return type of a call of `pie_plot_'
> > > > >> >     In the second argument of `($)', namely `pie_plot_ p'
> > > > >> >     In the second argument of `addMargins', namely
> > > > >> >       `(toRenderable $ pie_plot_ p)'
> > > > >> >
> > > > >> > I think I know what is going wrong, but I have no idea how to
> > > specify
> > > > >> the
> > > > >> > instance it should use there. Maybe I am just to tired to see
> the
> > > > >> solution.
> > > > >> >
> > > > >> > Right now I am trying to make things work without extra type
> > > parameters,
> > > > >> > though the definitions that are based on CRender are giving me a
> > > hard
> > > > >> time,
> > > > >> > because then I end up with rank N types.
> > > > >> >
> > > > >> > --
> > > > >> > You received this message because you are subscribed to the
> Google
> > > > >> Groups "diagrams-discuss" group.
> > > > >> > To unsubscribe from this group and stop receiving emails from
> it,
> > > send
> > > > >> an email to diagrams-discuss+unsubscribe at googlegroups.com.
> > > > >> > For more options, visit
> https://groups.google.com/groups/opt_out.
> > > > >> >
> > > > >> >
> > > > >>
> > > > >
> > > > >
> > >
> >
> > --
> > You received this message because you are subscribed to the Google
> Groups "diagrams-discuss" group.
> > To unsubscribe from this group and stop receiving emails from it, send
> an email to diagrams-discuss+unsubscribe at googlegroups.com.
> > For more options, visit https://groups.google.com/groups/opt_out.
> >
> >
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://projects.haskell.org/pipermail/chart/attachments/20130612/b02fae48/attachment-0001.htm>


More information about the Chart mailing list