I implemented W3s recommended algorithm for converting SVG-path arcs from endpoint-arcs to center-arcs and back in Haskell.
type EndpointArc = ( Double, Double, Double, Double
, Bool, Bool, Double, Double, Double )
type CenterArc = ( Double, Double, Double, Double
, Double, Double, Double )
endpointToCenter :: EndpointArc -> CenterArc
centerToEndpoint :: CenterArc -> EndpointArc
See full implementation and test-code here.
But I can't get this property to pass:
import Test.QuickCheck
import Data.AEq ((~==))
instance Arbitrary EndpointArc where
arbitrary = do
((x1,y1),(x2,y2)) <- arbitrary `suchThat` (\(u,v) -> u /= v)
rx <- arbitrary `suchThat` (>0)
ry <- arbitrary `suchThat` (>0)
phi <- choose (0,2*pi)
(fA,fS) <- arbitrary
return $ correctRadiiSize (x1, y1, x2, y2, fA, fS, rx, ry, phi)
prop_conversionRetains :: EndpointArc -> Bool
prop_conversionRetains earc =
let result = centerToEndpoint (endpointToCenter earc)
in earc ~== result
Sometimes this is due to floating point errors (which seem to exceed ieee754) but sometimes there are NaNs in the result.
(NaN,NaN,NaN,NaN,False,False,1.0314334509082723,2.732814841776921,1.2776112657142984)
Which indicates there is no solution although I think I scale rx,ry as described in F.6.6.2 in W3's document.
import Numeric.Matrix
m :: [[Double]] -> Matrix Double
m = fromList
toTuple :: Matrix Double -> (Double, Double)
toTuple = (\[[x],[y]] -> (x,y)) . toList
primed :: Double -> Double -> Double -> Double -> Double
-> (Double, Double)
primed x1 y1 x2 y2 phi = toTuple $
m [[ cos phi, sin phi]
,[-sin phi, cos phi]
]
* m [[(x1 - x2)/2]
,[(y1 - y2)/2]
]
correctRadiiSize :: EndpointArc -> EndpointArc
correctRadiiSize (x1, y1, x2, y2, fA, fS, rx, ry, phi) =
let (x1',y1') = primed x1 y1 x2 y2 phi
lambda = (x1'^2/rx^2) + (y1'^2/ry^2)
(rx',ry') | lambda <= 1 = (rx, ry)
| otherwise = ((sqrt lambda) * rx, (sqrt lambda) * ry)
in (x1, y1, x2, y2, fA, fS, rx', ry', phi)
OK, I figured this out myself. The clue was of course in W3s document:
F.6.5.2 in my code is
The radicand that it is referring to is
But of course, because we are working with floats it's not exactly zero but approximately and sometimes it might be something like
-6.99496644301622e-17
which is negative! The square-root of a negative number is a complex number so the calculation returns NaN.The trick really would be to propagate the fact that rx and ry have been resized to return zero and make
sq
zero instead of going through the whole calculation unecessarily but the quick fix is just to take the absolute value of the radicand.After that there are some remaining floating point issues. Firstly the error exceeds what is allowed for by ieee754's
~==
operator so I made my ownapproxEq
Which starts bringing cases where fA is getting flipped. Spot the magic number:
You got it!
fA = abs dtheta > pi
is incenterToEndpoint
so if it's therabouts then it can go either way.So I took out the fA condition and increased the number of tests in quickcheck
Which shows that the threshold approxEq is still not lax enough.
Which I can finally get to pass reliably with a high number of tests. Well its all just to make some funny graphics anyway... I am sure it's accurate enough :)