{-# LANGUAGE ScopedTypeVariables #-}
{-|
Paths in 2D space.

This module exposes functions with the same names as "Waterfall.Path", and if used together they should be imported qualified.
-}
module Waterfall.TwoD.Path2D
( Path2D
, Sense (..)
, line
, lineTo
, lineRelative
, arc
, arcTo
, arcRelative
, arcVia
, arcViaTo
, arcViaRelative
, bezier
, bezierTo
, bezierRelative
, pathFrom
, pathFromTo
, repeatLooping
, closeLoop
) where 

import Waterfall.TwoD.Internal.Path2D (Path2D(..), joinPaths)
import Waterfall.TwoD.Transforms (rotate2D)
import qualified Waterfall.Internal.Edges as Internal.Edges
import Control.Arrow (second)
import Data.Foldable (traverse_, foldl')
import Linear.V2 (V2(..))
import Control.Monad.IO.Class (liftIO)
import Control.Lens ((^.))
import Linear ((^*), _xy, distance, normalize, unangle)
import qualified OpenCascade.GP as GP
import qualified OpenCascade.GP.Pnt as GP.Pnt 
import qualified OpenCascade.BRepBuilderAPI.MakeEdge as MakeEdge
import qualified OpenCascade.BRepBuilderAPI.MakeWire as MakeWire
import qualified OpenCascade.TopoDS as TopoDS
import qualified OpenCascade.GC.MakeArcOfCircle as MakeArcOfCircle
import qualified OpenCascade.NCollection.Array1 as NCollection.Array1
import qualified OpenCascade.Geom.BezierCurve as BezierCurve
import OpenCascade.Inheritance (upcast)
import Foreign.Ptr
import Data.Acquire

v2ToPnt :: V2 Double -> Acquire (Ptr GP.Pnt)
v2ToPnt :: V2 Double -> Acquire (Ptr Pnt)
v2ToPnt (V2 Double
x Double
y) = Double -> Double -> Double -> Acquire (Ptr Pnt)
GP.Pnt.new Double
x Double
y Double
0

edgesToPath :: Acquire [Ptr TopoDS.Edge] -> Path2D
edgesToPath :: Acquire [Ptr Edge] -> Path2D
edgesToPath Acquire [Ptr Edge]
es = Acquire (Ptr Wire) -> Path2D
Path2D (Acquire (Ptr Wire) -> Path2D) -> Acquire (Ptr Wire) -> Path2D
forall a b. (a -> b) -> a -> b
$ do
    [Ptr Edge]
edges <- Acquire [Ptr Edge]
es
    Ptr MakeWire
builder <- Acquire (Ptr MakeWire)
MakeWire.new
    IO () -> Acquire ()
forall a. IO a -> Acquire a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Acquire ()) -> IO () -> Acquire ()
forall a b. (a -> b) -> a -> b
$ (Ptr Edge -> IO ()) -> [Ptr Edge] -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (Ptr MakeWire -> Ptr Edge -> IO ()
MakeWire.addEdge Ptr MakeWire
builder) [Ptr Edge]
edges
    Ptr MakeWire -> Acquire (Ptr Wire)
MakeWire.wire Ptr MakeWire
builder

-- | A straight line between two points
line :: V2 Double -> V2 Double -> Path2D
line :: V2 Double -> V2 Double -> Path2D
line V2 Double
start V2 Double
end = Acquire [Ptr Edge] -> Path2D
edgesToPath (Acquire [Ptr Edge] -> Path2D) -> Acquire [Ptr Edge] -> Path2D
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pnt
pt1 <- V2 Double -> Acquire (Ptr Pnt)
v2ToPnt V2 Double
start
    Ptr Pnt
pt2 <- V2 Double -> Acquire (Ptr Pnt)
v2ToPnt V2 Double
end
    Ptr Edge -> [Ptr Edge]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr Edge -> [Ptr Edge])
-> Acquire (Ptr Edge) -> Acquire [Ptr Edge]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Pnt -> Ptr Pnt -> Acquire (Ptr Edge)
MakeEdge.fromPnts Ptr Pnt
pt1 Ptr Pnt
pt2

-- | Version of `line` designed to work with `pathFrom`
lineTo :: V2 Double -> V2 Double -> (V2 Double, Path2D)
lineTo :: V2 Double -> V2 Double -> (V2 Double, Path2D)
lineTo V2 Double
end = \V2 Double
start -> (V2 Double
end, V2 Double -> V2 Double -> Path2D
line V2 Double
start V2 Double
end) 

-- | Version of `line` designed to work with `pathFrom`
-- 
-- With relative points; specifying the distance of the endpoint
-- relative to the start of the line, rather than in absolute space.
lineRelative :: V2 Double -> V2 Double -> (V2 Double, Path2D)
lineRelative :: V2 Double -> V2 Double -> (V2 Double, Path2D)
lineRelative V2 Double
dEnd = do
    V2 Double
end <- (V2 Double -> V2 Double -> V2 Double
forall a. Num a => a -> a -> a
+ V2 Double
dEnd)
    V2 Double -> V2 Double -> (V2 Double, Path2D)
lineTo V2 Double
end

-- | Section of a circle based on three arguments, the start point, a point on the arc, and the endpoint
arcVia :: V2 Double -> V2 Double -> V2 Double -> Path2D
arcVia :: V2 Double -> V2 Double -> V2 Double -> Path2D
arcVia V2 Double
start V2 Double
mid V2 Double
end = Acquire [Ptr Edge] -> Path2D
edgesToPath (Acquire [Ptr Edge] -> Path2D) -> Acquire [Ptr Edge] -> Path2D
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pnt
s <- V2 Double -> Acquire (Ptr Pnt)
v2ToPnt V2 Double
start
    Ptr Pnt
m <- V2 Double -> Acquire (Ptr Pnt)
v2ToPnt V2 Double
mid
    Ptr Pnt
e <- V2 Double -> Acquire (Ptr Pnt)
v2ToPnt V2 Double
end
    Ptr (Handle TrimmedCurve)
theArc <- Ptr Pnt
-> Ptr Pnt -> Ptr Pnt -> Acquire (Ptr (Handle TrimmedCurve))
MakeArcOfCircle.from3Pnts Ptr Pnt
s Ptr Pnt
m Ptr Pnt
e
    Ptr Edge -> [Ptr Edge]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr Edge -> [Ptr Edge])
-> Acquire (Ptr Edge) -> Acquire [Ptr Edge]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr (Handle Curve) -> Acquire (Ptr Edge)
MakeEdge.fromCurve (Ptr (Handle TrimmedCurve) -> Ptr (Handle Curve)
forall a b. SubTypeOf a b => Ptr b -> Ptr a
upcast Ptr (Handle TrimmedCurve)
theArc)

-- | Version of `arcVia` designed to work with `pathFrom`
--
-- The first argument is a point on the arc.
-- The second argument is the endpoint of the arc
arcViaTo :: V2 Double -> V2 Double -> V2 Double -> (V2 Double, Path2D)
arcViaTo :: V2 Double -> V2 Double -> V2 Double -> (V2 Double, Path2D)
arcViaTo V2 Double
mid V2 Double
end = \V2 Double
start -> (V2 Double
end, V2 Double -> V2 Double -> V2 Double -> Path2D
arcVia V2 Double
start V2 Double
mid V2 Double
end) 


-- | Version of `arcVia` designed to work with `pathFrom`
-- 
-- With relative points; specifying the distance of the midpoint and endpoint
-- relative to the start of the line, rather than in absolute space.
arcViaRelative :: V2 Double -> V2 Double -> V2 Double -> (V2 Double, Path2D)
arcViaRelative :: V2 Double -> V2 Double -> V2 Double -> (V2 Double, Path2D)
arcViaRelative V2 Double
dMid V2 Double
dEnd = do
    V2 Double
mid <- (V2 Double -> V2 Double -> V2 Double
forall a. Num a => a -> a -> a
+ V2 Double
dMid) 
    V2 Double
end <- (V2 Double -> V2 Double -> V2 Double
forall a. Num a => a -> a -> a
+ V2 Double
dEnd) 
    V2 Double -> V2 Double -> V2 Double -> (V2 Double, Path2D)
arcViaTo V2 Double
mid V2 Double
end

data Sense = Clockwise | Counterclockwise deriving (Sense -> Sense -> Bool
(Sense -> Sense -> Bool) -> (Sense -> Sense -> Bool) -> Eq Sense
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Sense -> Sense -> Bool
== :: Sense -> Sense -> Bool
$c/= :: Sense -> Sense -> Bool
/= :: Sense -> Sense -> Bool
Eq, Int -> Sense -> ShowS
[Sense] -> ShowS
Sense -> String
(Int -> Sense -> ShowS)
-> (Sense -> String) -> ([Sense] -> ShowS) -> Show Sense
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Sense -> ShowS
showsPrec :: Int -> Sense -> ShowS
$cshow :: Sense -> String
show :: Sense -> String
$cshowList :: [Sense] -> ShowS
showList :: [Sense] -> ShowS
Show)


-- | Section of a circle, with a given radius, that lies between two points.
--
-- This may fail, if the radius is less than half of the distance between the points.
--
-- In general, `arcVia` is the \"safer\" way to construct an arc
arc :: Sense -> Double -> V2 Double -> V2 Double -> Path2D 
arc :: Sense -> Double -> V2 Double -> V2 Double -> Path2D
arc Sense
sense Double
radius V2 Double
start V2 Double
end = 
    let mid :: V2 Double
mid = (V2 Double
start V2 Double -> V2 Double -> V2 Double
forall a. Num a => a -> a -> a
+ V2 Double
end) V2 Double -> Double -> V2 Double
forall (f :: * -> *) a. (Functor f, Num a) => f a -> a -> f a
^* Double
0.5
        (V2 Double
dx Double
dy) = V2 Double -> V2 Double
forall a (f :: * -> *).
(Floating a, Metric f, Epsilon a) =>
f a -> f a
normalize (V2 Double -> V2 Double) -> V2 Double -> V2 Double
forall a b. (a -> b) -> a -> b
$ V2 Double
end V2 Double -> V2 Double -> V2 Double
forall a. Num a => a -> a -> a
- V2 Double
start
        rotD :: V2 Double
rotD = case Sense
sense of    
                Sense
Clockwise -> Double -> Double -> V2 Double
forall a. a -> a -> V2 a
V2 Double
dy (-Double
dx)
                Sense
Counterclockwise -> Double -> Double -> V2 Double
forall a. a -> a -> V2 a
V2 (-Double
dy) Double
dx
        dse :: Double
dse = V2 Double -> V2 Double -> Double
forall a. Floating a => V2 a -> V2 a -> a
forall (f :: * -> *) a. (Metric f, Floating a) => f a -> f a -> a
distance V2 Double
start V2 Double
end 
        tangent :: Double
tangent = Double
radius Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double -> Double
forall a. Floating a => a -> a
sqrt (Double
radius Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
radius Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
dse Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
dse Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
4) 
        arcMid :: V2 Double
arcMid = V2 Double
mid V2 Double -> V2 Double -> V2 Double
forall a. Num a => a -> a -> a
+ V2 Double
rotD V2 Double -> Double -> V2 Double
forall (f :: * -> *) a. (Functor f, Num a) => f a -> a -> f a
^* Double
tangent
    in if Double
dse Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
2 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
radius
            then String -> Path2D
forall a. HasCallStack => String -> a
error String
"points too far apart in arc"
            else V2 Double -> V2 Double -> V2 Double -> Path2D
arcVia V2 Double
start V2 Double
arcMid V2 Double
end  

-- | Version of `arc` designed to work with `pathFrom`
arcTo :: Sense -> Double -> V2 Double -> V2 Double -> (V2 Double, Path2D)
arcTo :: Sense -> Double -> V2 Double -> V2 Double -> (V2 Double, Path2D)
arcTo Sense
sense Double
radius V2 Double
end = \V2 Double
start -> (V2 Double
end, Sense -> Double -> V2 Double -> V2 Double -> Path2D
arc Sense
sense Double
radius V2 Double
start V2 Double
end) 

-- | Version of `arc` designed to work with `pathFrom`
-- 
-- With relative points; specifying the distance of the endpoint
-- relative to the start of the line, rather than in absolute space.
arcRelative :: Sense -> Double -> V2 Double -> V2 Double -> (V2 Double, Path2D)
arcRelative :: Sense -> Double -> V2 Double -> V2 Double -> (V2 Double, Path2D)
arcRelative Sense
sense Double
radius V2 Double
dEnd = do
    V2 Double
end <- (V2 Double -> V2 Double -> V2 Double
forall a. Num a => a -> a -> a
+ V2 Double
dEnd)
    Sense -> Double -> V2 Double -> V2 Double -> (V2 Double, Path2D)
arcTo Sense
sense Double
radius V2 Double
end

-- | Bezier curve of order 3
-- 
-- The arguments are, the start of the curve, the two control points, and the end of the curve
bezier :: V2 Double -> V2 Double -> V2 Double -> V2 Double -> Path2D
bezier :: V2 Double -> V2 Double -> V2 Double -> V2 Double -> Path2D
bezier V2 Double
start V2 Double
controlPoint1 V2 Double
controlPoint2 V2 Double
end = Acquire [Ptr Edge] -> Path2D
edgesToPath (Acquire [Ptr Edge] -> Path2D) -> Acquire [Ptr Edge] -> Path2D
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pnt
s <- V2 Double -> Acquire (Ptr Pnt)
v2ToPnt V2 Double
start
    Ptr Pnt
c1 <- V2 Double -> Acquire (Ptr Pnt)
v2ToPnt V2 Double
controlPoint1
    Ptr Pnt
c2 <- V2 Double -> Acquire (Ptr Pnt)
v2ToPnt V2 Double
controlPoint2
    Ptr Pnt
e <- V2 Double -> Acquire (Ptr Pnt)
v2ToPnt V2 Double
end
    Ptr (Array1 Pnt)
arr <- Int -> Int -> Acquire (Ptr (Array1 Pnt))
NCollection.Array1.newGPPntArray Int
1 Int
4
    IO () -> Acquire ()
forall a. IO a -> Acquire a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Acquire ()) -> IO () -> Acquire ()
forall a b. (a -> b) -> a -> b
$ do 
        Ptr (Array1 Pnt) -> Int -> Ptr Pnt -> IO ()
NCollection.Array1.setValueGPPnt Ptr (Array1 Pnt)
arr Int
1 Ptr Pnt
s
        Ptr (Array1 Pnt) -> Int -> Ptr Pnt -> IO ()
NCollection.Array1.setValueGPPnt Ptr (Array1 Pnt)
arr Int
2 Ptr Pnt
c1
        Ptr (Array1 Pnt) -> Int -> Ptr Pnt -> IO ()
NCollection.Array1.setValueGPPnt Ptr (Array1 Pnt)
arr Int
3 Ptr Pnt
c2
        Ptr (Array1 Pnt) -> Int -> Ptr Pnt -> IO ()
NCollection.Array1.setValueGPPnt Ptr (Array1 Pnt)
arr Int
4 Ptr Pnt
e
    Ptr (Handle BezierCurve)
b <- Ptr BezierCurve -> Acquire (Ptr (Handle BezierCurve))
BezierCurve.toHandle (Ptr BezierCurve -> Acquire (Ptr (Handle BezierCurve)))
-> Acquire (Ptr BezierCurve) -> Acquire (Ptr (Handle BezierCurve))
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Array1 Pnt) -> Acquire (Ptr BezierCurve)
BezierCurve.fromPnts Ptr (Array1 Pnt)
arr
    Ptr Edge -> [Ptr Edge]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr Edge -> [Ptr Edge])
-> Acquire (Ptr Edge) -> Acquire [Ptr Edge]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr (Handle Curve) -> Acquire (Ptr Edge)
MakeEdge.fromCurve (Ptr (Handle BezierCurve) -> Ptr (Handle Curve)
forall a b. SubTypeOf a b => Ptr b -> Ptr a
upcast Ptr (Handle BezierCurve)
b)
 
-- | Version of `bezier` designed to work with `pathFrom`
bezierTo :: V2 Double -> V2 Double -> V2 Double -> V2 Double -> (V2 Double, Path2D)
bezierTo :: V2 Double
-> V2 Double -> V2 Double -> V2 Double -> (V2 Double, Path2D)
bezierTo V2 Double
controlPoint1 V2 Double
controlPoint2 V2 Double
end = \V2 Double
start -> (V2 Double
end, V2 Double -> V2 Double -> V2 Double -> V2 Double -> Path2D
bezier V2 Double
start V2 Double
controlPoint1 V2 Double
controlPoint2 V2 Double
end) 

-- | Version of `bezier` designed to work with `pathFrom`
-- 
-- With relative points; specifying the distance of the control points and the endpoint
-- relative to the start of the line, rather than in absolute space.
bezierRelative :: V2 Double -> V2 Double -> V2 Double -> V2 Double -> (V2 Double, Path2D)
bezierRelative :: V2 Double
-> V2 Double -> V2 Double -> V2 Double -> (V2 Double, Path2D)
bezierRelative V2 Double
dControlPoint1 V2 Double
dControlPoint2 V2 Double
dEnd = do
    V2 Double
controlPoint1 <- (V2 Double -> V2 Double -> V2 Double
forall a. Num a => a -> a -> a
+ V2 Double
dControlPoint1)
    V2 Double
controlPoint2 <- (V2 Double -> V2 Double -> V2 Double
forall a. Num a => a -> a -> a
+ V2 Double
dControlPoint2)
    V2 Double
end <- (V2 Double -> V2 Double -> V2 Double
forall a. Num a => a -> a -> a
+ V2 Double
dEnd)
    V2 Double
-> V2 Double -> V2 Double -> V2 Double -> (V2 Double, Path2D)
bezierTo V2 Double
controlPoint1 V2 Double
controlPoint2 V2 Double
end

-- | When combining paths, we're generally interested in pairs of paths that share a common endpoint.
--
-- Rather than having to repeat these common endpoints, `pathFrom` can be used to combine a list of path components.
-- 
-- Where a path component is a function from a start point, to a tuple of an end point, and a path; @ V2 Double -> (V2 Double, Path2D) @. 
-- 
-- A typical use of `pathFrom` uses a list of functions with the suffix \"To\" or \"Relative\", e.g.
--
-- @
--Path2D.pathFrom (V2 (-1) (-1)) 
--    [ Path2D.arcViaTo (V2 (-1.5) 0) (V2 (-1) 1)
--    , Path2D.lineTo (V2 1 1)
--    , Path2D.bezierTo (V2 1.5 1) (V2 1.5 (-1)) (V2 1 (-1))
--    , Path2D.lineTo (V2 (-1) (-1))
--    ] @
pathFrom :: V2 Double -> [V2 Double -> (V2 Double, Path2D)] -> Path2D
pathFrom :: V2 Double -> [V2 Double -> (V2 Double, Path2D)] -> Path2D
pathFrom V2 Double
start [V2 Double -> (V2 Double, Path2D)]
commands = (V2 Double, Path2D) -> Path2D
forall a b. (a, b) -> b
snd ((V2 Double, Path2D) -> Path2D) -> (V2 Double, Path2D) -> Path2D
forall a b. (a -> b) -> a -> b
$ [V2 Double -> (V2 Double, Path2D)]
-> V2 Double -> (V2 Double, Path2D)
pathFromTo [V2 Double -> (V2 Double, Path2D)]
commands V2 Double
start 
     
-- | Combines a list of "path components", as used by `pathFrom`
pathFromTo :: [V2 Double -> (V2 Double, Path2D)] -> V2 Double -> (V2 Double, Path2D)
pathFromTo :: [V2 Double -> (V2 Double, Path2D)]
-> V2 Double -> (V2 Double, Path2D)
pathFromTo [V2 Double -> (V2 Double, Path2D)]
commands V2 Double
start = 
    let go :: (t, [b]) -> (t -> (d, b)) -> (d, [b])
go (t
pos, [b]
paths) t -> (d, b)
cmd = (b -> [b]) -> (d, b) -> (d, [b])
forall b c d. (b -> c) -> (d, b) -> (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second (b -> [b] -> [b]
forall a. a -> [a] -> [a]
:[b]
paths) (t -> (d, b)
cmd t
pos)
        (V2 Double
end, [Path2D]
allPaths) = ((V2 Double, [Path2D])
 -> (V2 Double -> (V2 Double, Path2D)) -> (V2 Double, [Path2D]))
-> (V2 Double, [Path2D])
-> [V2 Double -> (V2 Double, Path2D)]
-> (V2 Double, [Path2D])
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (V2 Double, [Path2D])
-> (V2 Double -> (V2 Double, Path2D)) -> (V2 Double, [Path2D])
forall {t} {b} {d}. (t, [b]) -> (t -> (d, b)) -> (d, [b])
go (V2 Double
start, []) [V2 Double -> (V2 Double, Path2D)]
commands
     in (V2 Double
end, [Path2D] -> Path2D
joinPaths [Path2D]
allPaths)

-- | Given a Path where both endpoints are equidistant from the origin.
--
-- And which subtends an angle \( φ \) from the origin that evenly divides a complete revolution, such that \(n φ = 2 π \).
-- 
-- Replicates the path \( n \) times, rotating it by \( φ \), until the resulting path completes one revolution around the origin.
--
-- This can be used to construct paths with rotational symmetry, such as regular polygons, or gears.
repeatLooping :: Path2D -> Path2D
repeatLooping :: Path2D -> Path2D
repeatLooping Path2D
p = Acquire (Ptr Wire) -> Path2D
Path2D (Acquire (Ptr Wire) -> Path2D) -> Acquire (Ptr Wire) -> Path2D
forall a b. (a -> b) -> a -> b
$ do
    Ptr Wire
path <- Path2D -> Acquire (Ptr Wire)
runPath Path2D
p 
    (V3 Double
s, V3 Double
e) <- IO (V3 Double, V3 Double) -> Acquire (V3 Double, V3 Double)
forall a. IO a -> Acquire a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (V3 Double, V3 Double) -> Acquire (V3 Double, V3 Double))
-> (Ptr Wire -> IO (V3 Double, V3 Double))
-> Ptr Wire
-> Acquire (V3 Double, V3 Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Wire -> IO (V3 Double, V3 Double)
Internal.Edges.wireEndpoints (Ptr Wire -> Acquire (V3 Double, V3 Double))
-> Ptr Wire -> Acquire (V3 Double, V3 Double)
forall a b. (a -> b) -> a -> b
$ Ptr Wire
path
    let a :: Double
a = V2 Double -> Double
forall a. (Floating a, Ord a) => V2 a -> a
unangle (V3 Double
e V3 Double
-> Getting (V2 Double) (V3 Double) (V2 Double) -> V2 Double
forall s a. s -> Getting a s a -> a
^. Getting (V2 Double) (V3 Double) (V2 Double)
forall a. Lens' (V3 a) (V2 a)
forall (t :: * -> *) a. R2 t => Lens' (t a) (V2 a)
_xy) Double -> Double -> Double
forall a. Num a => a -> a -> a
- V2 Double -> Double
forall a. (Floating a, Ord a) => V2 a -> a
unangle (V3 Double
s V3 Double
-> Getting (V2 Double) (V3 Double) (V2 Double) -> V2 Double
forall s a. s -> Getting a s a -> a
^. Getting (V2 Double) (V3 Double) (V2 Double)
forall a. Lens' (V3 a) (V2 a)
forall (t :: * -> *) a. R2 t => Lens' (t a) (V2 a)
_xy)
    let Integer
times :: Integer = Integer -> Integer
forall a. Num a => a -> a
abs (Integer -> Integer) -> (Double -> Integer) -> Double -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Integer
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
round (Double -> Integer) -> Double -> Integer
forall a b. (a -> b) -> a -> b
$ Double
forall a. Floating a => a
pi Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
2 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
a 
    Path2D -> Acquire (Ptr Wire)
runPath (Path2D -> Acquire (Ptr Wire)) -> Path2D -> Acquire (Ptr Wire)
forall a b. (a -> b) -> a -> b
$ [Path2D] -> Path2D
forall a. Monoid a => [a] -> a
mconcat [Double -> Path2D -> Path2D
forall a. Transformable2D a => Double -> a -> a
rotate2D (Double -> Double
forall a. Num a => a -> a
negate (Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n) Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
a) Path2D
p | Integer
n <- [Integer
0..Integer
times]]

-- | Given a path, return a new path with the endpoints joined by a straight line.
closeLoop :: Path2D -> Path2D
closeLoop :: Path2D -> Path2D
closeLoop Path2D
p = Acquire (Ptr Wire) -> Path2D
Path2D (Acquire (Ptr Wire) -> Path2D) -> Acquire (Ptr Wire) -> Path2D
forall a b. (a -> b) -> a -> b
$ do
    Ptr Wire
path <- Path2D -> Acquire (Ptr Wire)
runPath Path2D
p
    (V3 Double
s, V3 Double
e) <- IO (V3 Double, V3 Double) -> Acquire (V3 Double, V3 Double)
forall a. IO a -> Acquire a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (V3 Double, V3 Double) -> Acquire (V3 Double, V3 Double))
-> (Ptr Wire -> IO (V3 Double, V3 Double))
-> Ptr Wire
-> Acquire (V3 Double, V3 Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Wire -> IO (V3 Double, V3 Double)
Internal.Edges.wireEndpoints (Ptr Wire -> Acquire (V3 Double, V3 Double))
-> Ptr Wire -> Acquire (V3 Double, V3 Double)
forall a b. (a -> b) -> a -> b
$ Ptr Wire
path
    Path2D -> Acquire (Ptr Wire)
runPath (Path2D -> Acquire (Ptr Wire)) -> Path2D -> Acquire (Ptr Wire)
forall a b. (a -> b) -> a -> b
$ [Path2D] -> Path2D
forall a. Monoid a => [a] -> a
mconcat [Path2D
p, V2 Double -> V2 Double -> Path2D
line (V3 Double
e V3 Double
-> Getting (V2 Double) (V3 Double) (V2 Double) -> V2 Double
forall s a. s -> Getting a s a -> a
^. Getting (V2 Double) (V3 Double) (V2 Double)
forall a. Lens' (V3 a) (V2 a)
forall (t :: * -> *) a. R2 t => Lens' (t a) (V2 a)
_xy)  (V3 Double
s V3 Double
-> Getting (V2 Double) (V3 Double) (V2 Double) -> V2 Double
forall s a. s -> Getting a s a -> a
^. Getting (V2 Double) (V3 Double) (V2 Double)
forall a. Lens' (V3 a) (V2 a)
forall (t :: * -> *) a. R2 t => Lens' (t a) (V2 a)
_xy)]