
Wow, Thanks! That's precisely what I was after, in extreme detail.
Adrian.
On 16 May 2013 00:21, Brent Yorgey
Hi all,
I'm trying to draw a picture with diagrams (this isn't the gantt chart I was talking about before.)
I have a load of objects strewn around a diagram according to their own sweet logic, and for *some* of them, I want to draw a horizontal line going from the right hand edge of the object to some globally fixed x coordinate, call it the "margin". So those lines are all different lengths because
On Wed, May 15, 2013 at 11:06:28AM +0800, Adrian May wrote: the
objects are all over the place, but their right-hand ends should all be aligned vertically.
This seems quite hard, because that sweet logic is already quite complicated and local to a set of objects in the immediate neighbourhood of the object in question. Somehow I have to tease out a selection of them and process each of them into this line whose properties depend on where the object is from the global perspective.
Hi Adrian,
Actually, diagrams provides some tools specifically for accomplishing this kind of thing, so it is not that bad. (This question would probably be more appropriate on the diagrams mailing list---it has to do with the workings of diagrams in particular and not much to do with Haskell in general---so I'm also cc'ing that mailing list. Luckily I am subscribed to both. =)
The key is that you can give names to subparts of your diagram, combine them using whatever arbitrarily complicated logic you want, and then later learn some things about where they ended up in the overall diagram. Here is an example:
{-# LANGUAGE NoMonomorphismRestriction #-}
import Data.Maybe (fromMaybe) import Diagrams.Backend.SVG.CmdLine -- or Cairo, etc. import Diagrams.Prelude
-- We can "mark" things just by giving them the name () mark = named ()
-- A bunch of stuff, each positioned according to its own sweet logic, -- some of which are marked. Note, it's critical that we mark each -- subdiagram *after* any transformations which we want to affect how -- its "right edge" is determined (e.g. the scaleX on the circle -- below), but *before* any transformations which serve to position it -- in the overall diagram (e.g. the translations of the pentagon and -- square). stuff = ( triangle 3 # mark === circle 1 ) ||| ( pentagon 2 # mark # translateY 5 === circle 0.5 # scaleX 3 # mark ) ||| ( square 2 # mark # translateY 2 )
-- Draw horizontal lines extending from the right edges of any marked -- subdiagram to the given x-coordinate. Extract all the marked -- subdiagrams using 'withNameAll ()', turn each into a function to -- draw the required line, and apply all of them. drawLinesTo x = withNameAll () $ \subs -> applyAll (map drawLineFrom subs) where drawLineFrom sub = atop (edgePt ~~ xPoint) where -- Compute the point on the right edge of the subdiagram. This -- is a little ugly at the moment; I hope to add combinators -- to make this nicer. edgePt = fromMaybe origin (maxTraceP (location sub) unitX sub) -- Compute the other endpoint of the segment. y = snd (unp2 (location sub)) xPoint = p2 (x,y)
main = defaultMain (stuff # drawLinesTo 13 # centerXY # pad 1.1)
which produces this output:
http://www.cis.upenn.edu/~byorgey/hosted/Adrian.pdf
The code of this example is also available here: https://github.com/byorgey/diagrams-play/blob/master/Adrian.hs .
Hope this helps! If you have more questions feel free to ask on the diagrams mailing list or in the #diagrams IRC channel on freenode.
-Brent
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners