How to combine shapes via set operations? - haskell

I would like to subtract one shape from another, and then combine the resulting shape with another shape. In my example a square is to be clipped in half and that clipped version is to be extended by a half circle to the right.
So I subtract one square from the other via difference and make a union with the whole circle assuming that overlapping areas will just merge.
I'm thinking in terms of set operations where ({1,2,3,4} / {3,4}) U {2,3} equals {1,2,3} but in my implementation it equals {1,3}:
import Diagrams.Backend.SVG.CmdLine
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
import Diagrams.Prelude
import qualified Diagrams.TwoD.Path.Boolean as B
main = mainWith (combination # fc red # bgFrame 0.1 white)
where
combination :: QDiagram B V2 Double Any
combination = strokePath plusCircle
shorterSquare = B.difference Winding (square 2) (square 2 # translateX 1)
plusCircle = B.union Winding (circle 1 <> shorterSquare)
But I get this:
This is not what I want, I want the half circle merged with the rectangle, and the result to be filled just red with no lines inside.

This particular usage of B.difference reverses the direction of the shorterSquare path, so you need to re-reverse it:
shorterSquare = B.difference Winding (square 2) (square 2 # translateX 1)
# reversePath
As this is quite subtle, it is worth it to spend a moment describing how I diagnosed it. Firstly, such fill rule wackiness felt quite like the sort of issue caused by path (or face, etc.) orientations. Secondly, redefining shorterSquare as...
shorterSquare = square 2 # scaleX 0.5 # translateX 0.5
... gives the expected result. That means the issue has to do with B.difference and the definition of shorterSquare, rather than with B.union. Confirmation can be obtained through pathVertices:
GHCi> -- Counterclockwise.
GHCi> pathVertices $ square 2 # scaleX 0.5 # translateX 0.5
[[P (V2 1.0 (-1.0)),P (V2 0.9999999999999999 1.0),P (V2 (-1.1102230246251565e-16) 1.0),P (V2 (-2.220446049250313e-16) (-1.0))]]
GHCi> -- Clockwise.
GHCi> pathVertices $ B.difference Winding (square 2) (square 2 # translateX 1)
[[P (V2 (-1.0) 1.0),P (V2 0.0 1.0),P (V2 0.0 (-1.0)),P (V2 (-1.0) (-1.0))]]

I'm not an expert on Diagrams, but it looks like you are combining stroke paths rather than the shapes they represent. Fill Rules has some interesting things to say about how the Winding fill rule behaves for stroke paths that overlap themselves, which seems relevant to explaining why you get the result you do.
Instead, I'd suggest using the techniques in Composing diagrams, such as atop, to compose the completed shapes.

Related

How to create this simple gif animation with Diagrams

I am trying to understand how to use Diagrams library in Haskell.
Here is my attempt at making a simple gif animation which switches between two circles of radii 1 and 2. I tried to mimic what I saw on
Here is the code, I tried.
{-# LANGUAGE NoMonomorphismRestriction #-}
import Diagrams.Backend.SVG.CmdLine
import Diagrams.Prelude
delays = take 2 (repeat 3)
gif :: [(Diagram B, Int)]
gif = zip [circle 1, circle 2] delays
main = mainWith $ gif
But this fails to compile! The errors I get are
[1 of 1] Compiling Main ( maze.hs, maze.o )
maze.hs:10:8:
No instance for (Diagrams.Backend.CmdLine.Parseable
(Diagrams.Backend.CmdLine.MainOpts
[(QDiagram B V2 Double Any, Int)]))
arising from a use of ‘mainWith’
In the expression: mainWith
In the expression: mainWith $ gif
In an equation for ‘main’: main = mainWith $ gif
Where am I going wrong in the code above?
It took me a moment to figure it out, because the error message is not obvious at all, but it's a backend problem. The documentation states that the cairo backend can create animated gif. However, you are using the svg backend (which is unable to understand what [(Diagram B, Int)] is.
To solve this, make sure you have the diagrams-cairo package installed, and change the line
import Diagrams.Backend.SVG.CmdLine
to
import Diagrams.Backend.Cairo.CmdLine
I'll explain the other steps necessary, since this is one of the first search results for doing animations in diagrams. Diagrams rescales the viewport to the image size for each circle, so that circle 1 and circle 2 are equivalent. To solve this you can lay the circles on invisible squares of the same size as circle 2.
Also the delays are given in 1/100 seconds. The correct code would then be:
{-# LANGUAGE NoMonomorphismRestriction #-}
import Diagrams.Backend.Cairo.CmdLine
import Diagrams.Prelude
gif :: [(Diagram B, Int)]
gif = map (\x -> (x # lc white <> square 4 # lw none,300)) [circle 1,circle 2]
main = mainWith gif

Diagrams boundingRect including the lines' width

Is there an equivalent to the boundingRect function which includes the diagram's lines width(*), so that each line, however thick it is, is entirely contained within the bounding rectangle? (the boundingRect function "ignores" their thickness and parts of the lines stay outside the bounding rectangle).
(*) My question is for lines with width expressed in local units.
Unfortunately there's no way to do this automatically yet. The easiest way would be to frame the diagram before finding the boundingRect. Since you're using the local units you just need to frame half the local width used in the diagram (add half of the line width used for the bounding rectangle if that has a line too).
Here's a simple example:
{-# LANGUAGE GADTs #-}
import Diagrams.Prelude
import Diagrams.Backend.Rasterific.CmdLine
main :: IO ()
main = mainWith $ frame 1 rects
rects :: Diagram B
rects = hsep 1 $ map (dia <>) [br1, br2, br3]
where
br1 = boundingRect dia # lwL 0.2 # lc red
br2 = boundingRect (frame 0.1 dia) # fc dodgerblue # lw none
br3 = boundingRect (frame 0.2 dia) # lwL 0.2 # lc red
dia :: Diagram B
dia = circle 3 # fc orange # lwL 0.2
A more general solution would be to draw the offset curves of each path using the local line width in the Diagram and find the bounding box of that. Diagrams.TwoD.Offset can almost do this but I don't think it works for all cases.

Perspective Projection: Proving that 1/z is Linear?

In 3D rendering (or geometry for that matter), in the rasterization algorithm, when you project the vertices of a triangle onto the screen and then find if a pixel overlaps the 2D triangle, you often need to find the depth or the z-coordinate of the triangle that the pixel overlaps. Generally, the method consists of computing the barycentric coordinates of the pixel in the 2D "projected" image of the triangle, and then use these coordinates to interpolate the triangle original vertices z-coordinates (before the vertices got projected).
Now it's written in all text books that you can't interpolate the vertices coordinates of the vertices directly but that you need to do this instead:
(sorry can't get Latex to work?)
1/z = w0 * 1/v0.z + w1 * 1/v1.z + w2 * 1/v2.z
Where w0, w1, and w2 are the barycentric coordinates of the "pixel" on the triangle.
Now, what I am looking after, are two things:
what would be the formal proof to show that interpolating z doesn't work?
what would be the formal proof to show that 1/z does the right thing?
To show this is not home work ;-) and that I have made some work on my own, I have found the following explanation for question 2.
Basically a triangle can be defined by a plane equation. Thus you can write:
Ax + By + Cz = D.
Then you isolate z to get z = (D - Ax - By)/C
Then you divide this formula by z as you would with a perspective divide and if you develop, regroup, etc. you get:
1/z = C/D + A/Dx/z + B/Dy/z.
Then we name C'=C/D B'=B/D and A'=A/D you get:
1/z = A'x/z + B'y/z + C'
It says that x/z and y/z are just the coordinates of the points on the triangles once projected on the screen and that the equation on the right is an "affine" function therefore 1/z is a linear function???
That doesn't seem like a demonstration to me? Or maybe it's the right idea, but can't really say how you can tell by just looking at the equation that this is an affine function. If you multiply all the terms you just get:
A'x + B'y + C'z = 1.
Which is just basically our original equations (just need to replace A' B' and C' with the proper term).
Not sure what you are trying to ask here, but if you look at:
1/z = A'x/z + B'y/z + C'
and rewrite it as:
1/z = A'u + B'v + C'
where (u,v) are screen coordinates of the triangle after perspective projection, you can see that the depth (z) of a point on the triangle is not linearly related to (u,v) but 1/depth is and that is what the textbooks are trying to teach you.

Koch Snowflake Implementation in Haskell

I was looking at this on the Wikipedia Page and was wondering if anyone has a working implementation of this.
I'm trying to learn Haskell, finding it slightly difficult and am working on the Koch Snowflake and Sierpinski Triangle.
Any code or suggestions welcome.
Thanks
For these kind of pictures which have a lot of structure and are scale independent, I would recommend the diagrams package ( http://projects.haskell.org/diagrams/ ), it's really quite a fantastic piece of code, see the following code to generate Koch snowflake written by yours truly in a matter of minutes :
snowflake :: Int -> Trail R2
snowflake n = k <> k # rotateBy (-1/3) <> k # rotateBy (1/3)
where k = koch n
koch :: Int -> Trail R2
koch 0 = P (-1,0) ~~ P (1,0)
koch n = k <> k # rotateBy (1/6) <> k # rotateBy (-1/6) <> k
where k = koch (n-1) # scale (1/3)
Which is almost self-explanatory, most of the magic is in the Monoid instance of Trail which will "concatenate" the trails end to end.
Note : (<>) is an operator for mappend, diagrams defined it in the past but this is now part of base in GHC 7.4 and will probably be included in a future version of the Haskell report, (#) is just the application reversed because diagrams author found it more pleasant to define a diagram then apply its attribute rather than write it in the other direction (so k # rotateBy (1/6) is just rotateBy (1/6) k).
Calculate the points of a triangle centered in the plane.
At each point of the triangle, calculate the points of a triangle one-third its size, and the other way up (flipped along its horizontal middle).
Pass each triangle to step 2, pass the results of that again to step 2, and so on.
Do all that again, upside down.
That should give you a list of (lists of) triangles. Now draw these triangles on the screen to the depth that you think is reasonable.

Projective transformation

Given two image buffers (assume it's an array of ints of size width * height, with each element a color value), how can I map an area defined by a quadrilateral from one image buffer into the other (always square) image buffer? I'm led to understand this is called "projective transformation".
I'm also looking for a general (not language- or library-specific) way of doing this, such that it could be reasonably applied in any language without relying on "magic function X that does all the work for me".
An example: I've written a short program in Java using the Processing library (processing.org) that captures video from a camera. During an initial "calibrating" step, the captured video is output directly into a window. The user then clicks on four points to define an area of the video that will be transformed, then mapped into the square window during subsequent operation of the program. If the user were to click on the four points defining the corners of a door visible at an angle in the camera's output, then this transformation would cause the subsequent video to map the transformed image of the door to the entire area of the window, albeit somewhat distorted.
Using linear algebra is much easier than all that geometry! Plus you won't need to use sine, cosine, etc, so you can store each number as a rational fraction and get the exact numerical result if you need it.
What you want is a mapping from your old (x,y) co-ordinates to your new (x',y') co-ordinates. You can do it with matrices. You need to find the 2-by-4 projection matrix P such that P times the old coordinates equals the new co-ordinates. We'll assume that you're mapping lines to lines (not, for instance, straight lines to parabolas). Because you have a projection (parallel lines don't stay parallel) and translation (sliding), you need a factor of (xy) and (1), too. Drawn as matrices:
[x ]
[a b c d]*[y ] = [x']
[e f g h] [x*y] [y']
[1 ]
You need to know a through h so solve these equations:
a*x_0 + b*y_0 + c*x_0*y_0 + d = i_0
a*x_1 + b*y_1 + c*x_1*y_1 + d = i_1
a*x_2 + b*y_2 + c*x_2*y_2 + d = i_2
a*x_3 + b*y_3 + c*x_3*y_3 + d = i_3
e*x_0 + f*y_0 + g*x_0*y_0 + h = j_0
e*x_1 + f*y_1 + g*x_1*y_1 + h = j_1
e*x_2 + f*y_2 + g*x_2*y_2 + h = j_2
e*x_3 + f*y_3 + g*x_3*y_3 + h = j_3
Again, you can use linear algebra:
[x_0 y_0 x_0*y_0 1] [a e] [i_0 j_0]
[x_1 y_1 x_1*y_1 1] * [b f] = [i_1 j_1]
[x_2 y_2 x_2*y_2 1] [c g] [i_2 j_2]
[x_3 y_3 x_3*y_3 1] [d h] [i_3 j_3]
Plug in your corners for x_n,y_n,i_n,j_n. (Corners work best because they are far apart to decrease the error if you're picking the points from, say, user-clicks.) Take the inverse of the 4x4 matrix and multiply it by the right side of the equation. The transpose of that matrix is P. You should be able to find functions to compute a matrix inverse and multiply online.
Where you'll probably have bugs:
When computing, remember to check for division by zero. That's a sign that your matrix is not invertible. That might happen if you try to map one (x,y) co-ordinate to two different points.
If you write your own matrix math, remember that matrices are usually specified row,column (vertical,horizontal) and screen graphics are x,y (horizontal,vertical). You're bound to get something wrong the first time.
EDIT
The assumption below of the invariance of angle ratios is incorrect. Projective transformations instead preserve cross-ratios and incidence. A solution then is:
Find the point C' at the intersection of the lines defined by the segments AD and CP.
Find the point B' at the intersection of the lines defined by the segments AD and BP.
Determine the cross-ratio of B'DAC', i.e. r = (BA' * DC') / (DA * B'C').
Construct the projected line F'HEG'. The cross-ratio of these points is equal to r, i.e. r = (F'E * HG') / (HE * F'G').
F'F and G'G will intersect at the projected point Q so equating the cross-ratios and knowing the length of the side of the square you can determine the position of Q with some arithmetic gymnastics.
Hmmmm....I'll take a stab at this one. This solution relies on the assumption that ratios of angles are preserved in the transformation. See the image for guidance (sorry for the poor image quality...it's REALLY late). The algorithm only provides the mapping of a point in the quadrilateral to a point in the square. You would still need to implement dealing with multiple quad points being mapped to the same square point.
Let ABCD be a quadrilateral where A is the top-left vertex, B is the top-right vertex, C is the bottom-right vertex and D is the bottom-left vertex. The pair (xA, yA) represent the x and y coordinates of the vertex A. We are mapping points in this quadrilateral to the square EFGH whose side has length equal to m.
Compute the lengths AD, CD, AC, BD and BC:
AD = sqrt((xA-xD)^2 + (yA-yD)^2)
CD = sqrt((xC-xD)^2 + (yC-yD)^2)
AC = sqrt((xA-xC)^2 + (yA-yC)^2)
BD = sqrt((xB-xD)^2 + (yB-yD)^2)
BC = sqrt((xB-xC)^2 + (yB-yC)^2)
Let thetaD be the angle at the vertex D and thetaC be the angle at the vertex C. Compute these angles using the cosine law:
thetaD = arccos((AD^2 + CD^2 - AC^2) / (2*AD*CD))
thetaC = arccos((BC^2 + CD^2 - BD^2) / (2*BC*CD))
We map each point P in the quadrilateral to a point Q in the square. For each point P in the quadrilateral, do the following:
Find the distance DP:
DP = sqrt((xP-xD)^2 + (yP-yD)^2)
Find the distance CP:
CP = sqrt((xP-xC)^2 + (yP-yC)^2)
Find the angle thetaP1 between CD and DP:
thetaP1 = arccos((DP^2 + CD^2 - CP^2) / (2*DP*CD))
Find the angle thetaP2 between CD and CP:
thetaP2 = arccos((CP^2 + CD^2 - DP^2) / (2*CP*CD))
The ratio of thetaP1 to thetaD should be the ratio of thetaQ1 to 90. Therefore, calculate thetaQ1:
thetaQ1 = thetaP1 * 90 / thetaD
Similarly, calculate thetaQ2:
thetaQ2 = thetaP2 * 90 / thetaC
Find the distance HQ:
HQ = m * sin(thetaQ2) / sin(180-thetaQ1-thetaQ2)
Finally, the x and y position of Q relative to the bottom-left corner of EFGH is:
x = HQ * cos(thetaQ1)
y = HQ * sin(thetaQ1)
You would have to keep track of how many colour values get mapped to each point in the square so that you can calculate an average colour for each of those points.
I think what you're after is a planar homography, have a look at these lecture notes:
http://www.cs.utoronto.ca/~strider/vis-notes/tutHomography04.pdf
If you scroll down to the end you'll see an example of just what you're describing. I expect there's a function in the Intel OpenCV library which will do just this.
There is a C++ project on CodeProject that includes source for projective transformations of bitmaps. The maths are on Wikipedia here. Note that so far as i know, a projective transformation will not map any arbitrary quadrilateral onto another, but will do so for triangles, you may also want to look up skewing transforms.
If this transformation has to look good (as opposed to the way a bitmap looks if you resize it in Paint), you can't just create a formula that maps destination pixels to source pixels. Values in the destination buffer have to be based on a complex averaging of nearby source pixels or else the results will be highly pixelated.
So unless you want to get into some complex coding, use someone else's magic function, as smacl and Ian have suggested.
Here's how would do it in principle:
map the origin of A to the origin of B via a traslation vector t.
take unit vectors of A (1,0) and (0,1) and calculate how they would be mapped onto the unit vectors of B.
this gives you a transformation matrix M so that every vector a in A maps to M a + t
invert the matrix and negate the traslation vector so for every vector b in B you have the inverse mapping b -> M-1 (b - t)
once you have this transformation, for each point in the target area in B, find the corresponding in A and copy.
The advantage of this mapping is that you only calculate the points you need, i.e. you loop on the target points, not the source points. It was a widely used technique in the "demo coding" scene a few years back.

Resources