{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Diagrams.TwoD.Path
(
stroke, stroke'
, strokePath, strokeP, strokePath', strokeP'
, strokeTrail, strokeT, strokeTrail', strokeT'
, strokeLine, strokeLoop
, strokeLocTrail, strokeLocT, strokeLocLine, strokeLocLoop
, FillRule(..)
, getFillRule, fillRule, _fillRule
, StrokeOpts(..), vertexNames, queryFillRule
, Crossings (..)
, isInsideWinding
, isInsideEvenOdd
, Clip(..), _Clip, _clip
, clipBy, clipTo, clipped
, intersectPoints, intersectPoints'
, intersectPointsP, intersectPointsP'
, intersectPointsT, intersectPointsT'
) where
import Control.Applicative (liftA2)
import Control.Lens hiding (at, transform)
import qualified Data.Foldable as F
import Data.Semigroup
import Data.Typeable
import Data.Default.Class
import Diagrams.Angle
import Diagrams.Combinators (withEnvelope, withTrace)
import Diagrams.Core
import Diagrams.Core.Trace
import Diagrams.Located (Located, mapLoc, unLoc)
import Diagrams.Parametric
import Diagrams.Path
import Diagrams.Query
import Diagrams.Segment
import Diagrams.Solve.Polynomial
import Diagrams.Trail
import Diagrams.TrailLike
import Diagrams.TwoD.Segment
import Diagrams.TwoD.Types
import Diagrams.TwoD.Vector
import Diagrams.Util (tau)
import Linear.Affine
import Linear.Vector
instance RealFloat n => Traced (Trail V2 n) where
getTrace :: Trail V2 n -> Trace (V (Trail V2 n)) (N (Trail V2 n))
getTrace = forall (v :: * -> *) n r.
(Metric v, OrderedField n) =>
(Trail' Line v n -> r) -> Trail v n -> r
withLine forall a b. (a -> b) -> a -> b
$
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr
(\Segment Closed V2 n
seg Trace V2 n
bds -> forall t (v :: * -> *) n.
(V t ~ v, N t ~ n, HasOrigin t) =>
v n -> t -> t
moveOriginBy (forall (f :: * -> *) a. (Functor f, Num a) => f a -> f a
negated forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall p. EndValues p => p -> Codomain p (N p)
atEnd forall a b. (a -> b) -> a -> b
$ Segment Closed V2 n
seg) Trace V2 n
bds forall a. Semigroup a => a -> a -> a
<> forall a. Traced a => a -> Trace (V a) (N a)
getTrace Segment Closed V2 n
seg)
forall a. Monoid a => a
mempty
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) n. Trail' Line v n -> [Segment Closed v n]
lineSegments
instance RealFloat n => Traced (Path V2 n) where
getTrace :: Path V2 n -> Trace (V (Path V2 n)) (N (Path V2 n))
getTrace = forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
F.foldMap forall a. Traced a => a -> Trace (V a) (N a)
getTrace forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. Wrapped s => (Unwrapped s -> s) -> s -> Unwrapped s
op forall (v :: * -> *) n. [Located (Trail v n)] -> Path v n
Path
data FillRule
= Winding
| EvenOdd
deriving (Int -> FillRule -> ShowS
[FillRule] -> ShowS
FillRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FillRule] -> ShowS
$cshowList :: [FillRule] -> ShowS
show :: FillRule -> String
$cshow :: FillRule -> String
showsPrec :: Int -> FillRule -> ShowS
$cshowsPrec :: Int -> FillRule -> ShowS
Show, Typeable, FillRule -> FillRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FillRule -> FillRule -> Bool
$c/= :: FillRule -> FillRule -> Bool
== :: FillRule -> FillRule -> Bool
$c== :: FillRule -> FillRule -> Bool
Eq, Eq FillRule
FillRule -> FillRule -> Bool
FillRule -> FillRule -> Ordering
FillRule -> FillRule -> FillRule
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FillRule -> FillRule -> FillRule
$cmin :: FillRule -> FillRule -> FillRule
max :: FillRule -> FillRule -> FillRule
$cmax :: FillRule -> FillRule -> FillRule
>= :: FillRule -> FillRule -> Bool
$c>= :: FillRule -> FillRule -> Bool
> :: FillRule -> FillRule -> Bool
$c> :: FillRule -> FillRule -> Bool
<= :: FillRule -> FillRule -> Bool
$c<= :: FillRule -> FillRule -> Bool
< :: FillRule -> FillRule -> Bool
$c< :: FillRule -> FillRule -> Bool
compare :: FillRule -> FillRule -> Ordering
$ccompare :: FillRule -> FillRule -> Ordering
Ord)
instance AttributeClass FillRule
instance Semigroup FillRule where
FillRule
_ <> :: FillRule -> FillRule -> FillRule
<> FillRule
b = FillRule
b
instance Default FillRule where
def :: FillRule
def = FillRule
Winding
data StrokeOpts a
= StrokeOpts
{ forall a. StrokeOpts a -> [[a]]
_vertexNames :: [[a]]
, forall a. StrokeOpts a -> FillRule
_queryFillRule :: FillRule
}
makeLensesWith (generateSignatures .~ False $ lensRules) ''StrokeOpts
vertexNames :: Lens (StrokeOpts a) (StrokeOpts a') [[a]] [[a']]
queryFillRule :: Lens' (StrokeOpts a) FillRule
instance Default (StrokeOpts a) where
def :: StrokeOpts a
def = StrokeOpts
{ _vertexNames :: [[a]]
_vertexNames = []
, _queryFillRule :: FillRule
_queryFillRule = forall a. Default a => a
def
}
stroke :: (InSpace V2 n t, ToPath t, TypeableFloat n, Renderable (Path V2 n) b)
=> t -> QDiagram b V2 n Any
stroke :: forall n t b.
(InSpace V2 n t, ToPath t, TypeableFloat n,
Renderable (Path V2 n) b) =>
t -> QDiagram b V2 n Any
stroke = forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Path V2 n -> QDiagram b V2 n Any
strokeP forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t.
(ToPath t, Metric (V t), OrderedField (N t)) =>
t -> Path (V t) (N t)
toPath
stroke' :: (InSpace V2 n t, ToPath t, TypeableFloat n, Renderable (Path V2 n) b, IsName a)
=> StrokeOpts a -> t -> QDiagram b V2 n Any
stroke' :: forall n t b a.
(InSpace V2 n t, ToPath t, TypeableFloat n,
Renderable (Path V2 n) b, IsName a) =>
StrokeOpts a -> t -> QDiagram b V2 n Any
stroke' StrokeOpts a
opts = forall n b a.
(TypeableFloat n, Renderable (Path V2 n) b, IsName a) =>
StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any
strokeP' StrokeOpts a
opts forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t.
(ToPath t, Metric (V t), OrderedField (N t)) =>
t -> Path (V t) (N t)
toPath
strokeP :: (TypeableFloat n, Renderable (Path V2 n) b)
=> Path V2 n -> QDiagram b V2 n Any
strokeP :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Path V2 n -> QDiagram b V2 n Any
strokeP = forall n b a.
(TypeableFloat n, Renderable (Path V2 n) b, IsName a) =>
StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any
strokeP' (forall a. Default a => a
def :: StrokeOpts ())
strokePath :: (TypeableFloat n, Renderable (Path V2 n) b)
=> Path V2 n -> QDiagram b V2 n Any
strokePath :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Path V2 n -> QDiagram b V2 n Any
strokePath = forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Path V2 n -> QDiagram b V2 n Any
strokeP
instance (TypeableFloat n, Renderable (Path V2 n) b)
=> TrailLike (QDiagram b V2 n Any) where
trailLike :: Located (Trail (V (QDiagram b V2 n Any)) (N (QDiagram b V2 n Any)))
-> QDiagram b V2 n Any
trailLike = forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Path V2 n -> QDiagram b V2 n Any
strokeP forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. TrailLike t => Located (Trail (V t) (N t)) -> t
trailLike
strokeP' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a)
=> StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any
strokeP' :: forall n b a.
(TypeableFloat n, Renderable (Path V2 n) b, IsName a) =>
StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any
strokeP' StrokeOpts a
opts Path V2 n
path
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Path V2 n
pLines forall s a. s -> Getting a s a -> a
^. forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped') = Path V2 n -> QDiagram b V2 n Any
mkP Path V2 n
pLoops
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Path V2 n
pLoops forall s a. s -> Getting a s a -> a
^. forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped') = Path V2 n -> QDiagram b V2 n Any
mkP Path V2 n
pLines
| Bool
otherwise = Path V2 n -> QDiagram b V2 n Any
mkP Path V2 n
pLines forall a. Semigroup a => a -> a -> a
<> Path V2 n -> QDiagram b V2 n Any
mkP Path V2 n
pLoops
where
(Path V2 n
pLines,Path V2 n
pLoops) = forall (v :: * -> *) n.
(Located (Trail v n) -> Bool) -> Path v n -> (Path v n, Path v n)
partitionPath (forall (v :: * -> *) n. Trail v n -> Bool
isLine forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Located a -> a
unLoc) Path V2 n
path
mkP :: Path V2 n -> QDiagram b V2 n Any
mkP Path V2 n
p
= forall b (v :: * -> *) n m.
Prim b v n
-> Envelope v n
-> Trace v n
-> SubMap b v n m
-> Query v n m
-> QDiagram b v n m
mkQD (forall p b.
(Transformable p, Typeable p, Renderable p b) =>
p -> Prim b (V p) (N p)
Prim Path V2 n
p)
(forall a. Enveloped a => a -> Envelope (V a) (N a)
getEnvelope Path V2 n
p)
(forall a. Traced a => a -> Trace (V a) (N a)
getTrace Path V2 n
p)
(forall a b (v :: * -> *) n m.
IsName a =>
[(a, Subdiagram b v n m)] -> SubMap b v n m
fromNames forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall a b. [a] -> [b] -> [(a, b)]
zip (StrokeOpts a
optsforall s a. s -> Getting a s a -> a
^.forall a a'. Lens (StrokeOpts a) (StrokeOpts a') [[a]] [[a']]
vertexNames) ((forall a b. (a -> b) -> [a] -> [b]
map forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map) forall (v :: * -> *) n b m.
(Metric v, OrderedField n) =>
Point v n -> Subdiagram b v n m
subPoint (forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
Path v n -> [[Point v n]]
pathVertices Path V2 n
p))
)
(forall (v :: * -> *) n m. (Point v n -> m) -> Query v n m
Query forall a b. (a -> b) -> a -> b
$ Bool -> Any
Any forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall n.
RealFloat n =>
FillRule -> Path V2 n -> Point V2 n -> Bool
runFillRule (StrokeOpts a
optsforall s a. s -> Getting a s a -> a
^.forall a. Lens' (StrokeOpts a) FillRule
queryFillRule)) Path V2 n
p)
strokePath' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a)
=> StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any
strokePath' :: forall n b a.
(TypeableFloat n, Renderable (Path V2 n) b, IsName a) =>
StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any
strokePath' = forall n b a.
(TypeableFloat n, Renderable (Path V2 n) b, IsName a) =>
StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any
strokeP'
strokeTrail :: (TypeableFloat n, Renderable (Path V2 n) b)
=> Trail V2 n -> QDiagram b V2 n Any
strokeTrail :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Trail V2 n -> QDiagram b V2 n Any
strokeTrail = forall n t b.
(InSpace V2 n t, ToPath t, TypeableFloat n,
Renderable (Path V2 n) b) =>
t -> QDiagram b V2 n Any
stroke forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
Trail v n -> Path v n
pathFromTrail
strokeT :: (TypeableFloat n, Renderable (Path V2 n) b)
=> Trail V2 n -> QDiagram b V2 n Any
strokeT :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Trail V2 n -> QDiagram b V2 n Any
strokeT = forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Trail V2 n -> QDiagram b V2 n Any
strokeTrail
strokeTrail' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a)
=> StrokeOpts a -> Trail V2 n -> QDiagram b V2 n Any
strokeTrail' :: forall n b a.
(TypeableFloat n, Renderable (Path V2 n) b, IsName a) =>
StrokeOpts a -> Trail V2 n -> QDiagram b V2 n Any
strokeTrail' StrokeOpts a
opts = forall n t b a.
(InSpace V2 n t, ToPath t, TypeableFloat n,
Renderable (Path V2 n) b, IsName a) =>
StrokeOpts a -> t -> QDiagram b V2 n Any
stroke' StrokeOpts a
opts forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
Trail v n -> Path v n
pathFromTrail
strokeT' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a)
=> StrokeOpts a -> Trail V2 n -> QDiagram b V2 n Any
strokeT' :: forall n b a.
(TypeableFloat n, Renderable (Path V2 n) b, IsName a) =>
StrokeOpts a -> Trail V2 n -> QDiagram b V2 n Any
strokeT' = forall n b a.
(TypeableFloat n, Renderable (Path V2 n) b, IsName a) =>
StrokeOpts a -> Trail V2 n -> QDiagram b V2 n Any
strokeTrail'
strokeLine :: (TypeableFloat n, Renderable (Path V2 n) b)
=> Trail' Line V2 n -> QDiagram b V2 n Any
strokeLine :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Trail' Line V2 n -> QDiagram b V2 n Any
strokeLine = forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Trail V2 n -> QDiagram b V2 n Any
strokeT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) n. Trail' Line v n -> Trail v n
wrapLine
strokeLoop :: (TypeableFloat n, Renderable (Path V2 n) b)
=> Trail' Loop V2 n -> QDiagram b V2 n Any
strokeLoop :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Trail' Loop V2 n -> QDiagram b V2 n Any
strokeLoop = forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Trail V2 n -> QDiagram b V2 n Any
strokeT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) n. Trail' Loop v n -> Trail v n
wrapLoop
strokeLocTrail :: (TypeableFloat n, Renderable (Path V2 n) b)
=> Located (Trail V2 n) -> QDiagram b V2 n Any
strokeLocTrail :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Located (Trail V2 n) -> QDiagram b V2 n Any
strokeLocTrail = forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Path V2 n -> QDiagram b V2 n Any
strokeP forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. TrailLike t => Located (Trail (V t) (N t)) -> t
trailLike
strokeLocT :: (TypeableFloat n, Renderable (Path V2 n) b)
=> Located (Trail V2 n) -> QDiagram b V2 n Any
strokeLocT :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Located (Trail V2 n) -> QDiagram b V2 n Any
strokeLocT = forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Located (Trail V2 n) -> QDiagram b V2 n Any
strokeLocTrail
strokeLocLine :: (TypeableFloat n, Renderable (Path V2 n) b)
=> Located (Trail' Line V2 n) -> QDiagram b V2 n Any
strokeLocLine :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Located (Trail' Line V2 n) -> QDiagram b V2 n Any
strokeLocLine = forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Path V2 n -> QDiagram b V2 n Any
strokeP forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. TrailLike t => Located (Trail (V t) (N t)) -> t
trailLike forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. SameSpace a b => (a -> b) -> Located a -> Located b
mapLoc forall (v :: * -> *) n. Trail' Line v n -> Trail v n
wrapLine
strokeLocLoop :: (TypeableFloat n, Renderable (Path V2 n) b)
=> Located (Trail' Loop V2 n) -> QDiagram b V2 n Any
strokeLocLoop :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Located (Trail' Loop V2 n) -> QDiagram b V2 n Any
strokeLocLoop = forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Path V2 n -> QDiagram b V2 n Any
strokeP forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. TrailLike t => Located (Trail (V t) (N t)) -> t
trailLike forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. SameSpace a b => (a -> b) -> Located a -> Located b
mapLoc forall (v :: * -> *) n. Trail' Loop v n -> Trail v n
wrapLoop
runFillRule :: RealFloat n => FillRule -> Path V2 n -> Point V2 n -> Bool
runFillRule :: forall n.
RealFloat n =>
FillRule -> Path V2 n -> Point V2 n -> Bool
runFillRule FillRule
Winding = forall t. HasQuery t Crossings => t -> Point (V t) (N t) -> Bool
isInsideWinding
runFillRule FillRule
EvenOdd = forall t. HasQuery t Crossings => t -> Point (V t) (N t) -> Bool
isInsideEvenOdd
getFillRule :: FillRule -> FillRule
getFillRule :: FillRule -> FillRule
getFillRule = forall a. a -> a
id
fillRule :: HasStyle a => FillRule -> a -> a
fillRule :: forall a. HasStyle a => FillRule -> a -> a
fillRule = forall a d. (AttributeClass a, HasStyle d) => a -> d -> d
applyAttr
_fillRule :: Lens' (Style V2 n) FillRule
_fillRule :: forall n. Lens' (Style V2 n) FillRule
_fillRule = forall a (v :: * -> *) n.
AttributeClass a =>
Lens' (Style v n) (Maybe a)
atAttr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => a -> Iso' (Maybe a) a
non forall a. Default a => a
def
newtype Crossings = Crossings Int
deriving (Int -> Crossings -> ShowS
[Crossings] -> ShowS
Crossings -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Crossings] -> ShowS
$cshowList :: [Crossings] -> ShowS
show :: Crossings -> String
$cshow :: Crossings -> String
showsPrec :: Int -> Crossings -> ShowS
$cshowsPrec :: Int -> Crossings -> ShowS
Show, Crossings -> Crossings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Crossings -> Crossings -> Bool
$c/= :: Crossings -> Crossings -> Bool
== :: Crossings -> Crossings -> Bool
$c== :: Crossings -> Crossings -> Bool
Eq, Eq Crossings
Crossings -> Crossings -> Bool
Crossings -> Crossings -> Ordering
Crossings -> Crossings -> Crossings
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Crossings -> Crossings -> Crossings
$cmin :: Crossings -> Crossings -> Crossings
max :: Crossings -> Crossings -> Crossings
$cmax :: Crossings -> Crossings -> Crossings
>= :: Crossings -> Crossings -> Bool
$c>= :: Crossings -> Crossings -> Bool
> :: Crossings -> Crossings -> Bool
$c> :: Crossings -> Crossings -> Bool
<= :: Crossings -> Crossings -> Bool
$c<= :: Crossings -> Crossings -> Bool
< :: Crossings -> Crossings -> Bool
$c< :: Crossings -> Crossings -> Bool
compare :: Crossings -> Crossings -> Ordering
$ccompare :: Crossings -> Crossings -> Ordering
Ord, Integer -> Crossings
Crossings -> Crossings
Crossings -> Crossings -> Crossings
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Crossings
$cfromInteger :: Integer -> Crossings
signum :: Crossings -> Crossings
$csignum :: Crossings -> Crossings
abs :: Crossings -> Crossings
$cabs :: Crossings -> Crossings
negate :: Crossings -> Crossings
$cnegate :: Crossings -> Crossings
* :: Crossings -> Crossings -> Crossings
$c* :: Crossings -> Crossings -> Crossings
- :: Crossings -> Crossings -> Crossings
$c- :: Crossings -> Crossings -> Crossings
+ :: Crossings -> Crossings -> Crossings
$c+ :: Crossings -> Crossings -> Crossings
Num, Int -> Crossings
Crossings -> Int
Crossings -> [Crossings]
Crossings -> Crossings
Crossings -> Crossings -> [Crossings]
Crossings -> Crossings -> Crossings -> [Crossings]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Crossings -> Crossings -> Crossings -> [Crossings]
$cenumFromThenTo :: Crossings -> Crossings -> Crossings -> [Crossings]
enumFromTo :: Crossings -> Crossings -> [Crossings]
$cenumFromTo :: Crossings -> Crossings -> [Crossings]
enumFromThen :: Crossings -> Crossings -> [Crossings]
$cenumFromThen :: Crossings -> Crossings -> [Crossings]
enumFrom :: Crossings -> [Crossings]
$cenumFrom :: Crossings -> [Crossings]
fromEnum :: Crossings -> Int
$cfromEnum :: Crossings -> Int
toEnum :: Int -> Crossings
$ctoEnum :: Int -> Crossings
pred :: Crossings -> Crossings
$cpred :: Crossings -> Crossings
succ :: Crossings -> Crossings
$csucc :: Crossings -> Crossings
Enum, Num Crossings
Ord Crossings
Crossings -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Crossings -> Rational
$ctoRational :: Crossings -> Rational
Real, Enum Crossings
Real Crossings
Crossings -> Integer
Crossings -> Crossings -> (Crossings, Crossings)
Crossings -> Crossings -> Crossings
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: Crossings -> Integer
$ctoInteger :: Crossings -> Integer
divMod :: Crossings -> Crossings -> (Crossings, Crossings)
$cdivMod :: Crossings -> Crossings -> (Crossings, Crossings)
quotRem :: Crossings -> Crossings -> (Crossings, Crossings)
$cquotRem :: Crossings -> Crossings -> (Crossings, Crossings)
mod :: Crossings -> Crossings -> Crossings
$cmod :: Crossings -> Crossings -> Crossings
div :: Crossings -> Crossings -> Crossings
$cdiv :: Crossings -> Crossings -> Crossings
rem :: Crossings -> Crossings -> Crossings
$crem :: Crossings -> Crossings -> Crossings
quot :: Crossings -> Crossings -> Crossings
$cquot :: Crossings -> Crossings -> Crossings
Integral)
instance Semigroup Crossings where
Crossings Int
a <> :: Crossings -> Crossings -> Crossings
<> Crossings Int
b = Int -> Crossings
Crossings (Int
a forall a. Num a => a -> a -> a
+ Int
b)
instance Monoid Crossings where
mempty :: Crossings
mempty = Int -> Crossings
Crossings Int
0
mappend :: Crossings -> Crossings -> Crossings
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance RealFloat n => HasQuery (Located (Trail V2 n)) Crossings where
getQuery :: Located (Trail V2 n)
-> Query
(V (Located (Trail V2 n))) (N (Located (Trail V2 n))) Crossings
getQuery Located (Trail V2 n)
trail = forall (v :: * -> *) n m. (Point v n -> m) -> Query v n m
Query forall a b. (a -> b) -> a -> b
$ \Point (V (Located (Trail V2 n))) (N (Located (Trail V2 n)))
p -> forall n.
RealFloat n =>
Point V2 n -> Located (Trail V2 n) -> Crossings
trailCrossings Point (V (Located (Trail V2 n))) (N (Located (Trail V2 n)))
p Located (Trail V2 n)
trail
instance RealFloat n => HasQuery (Located (Trail' l V2 n)) Crossings where
getQuery :: Located (Trail' l V2 n)
-> Query
(V (Located (Trail' l V2 n)))
(N (Located (Trail' l V2 n)))
Crossings
getQuery Located (Trail' l V2 n)
trail' = forall t m. HasQuery t m => t -> Query (V t) (N t) m
getQuery (forall a b. SameSpace a b => (a -> b) -> Located a -> Located b
mapLoc forall l (v :: * -> *) n. Trail' l v n -> Trail v n
Trail Located (Trail' l V2 n)
trail')
instance RealFloat n => HasQuery (Path V2 n) Crossings where
getQuery :: Path V2 n -> Query (V (Path V2 n)) (N (Path V2 n)) Crossings
getQuery = forall r s a. Getting r s a -> (a -> r) -> s -> r
foldMapOf forall s t a b. Each s t a b => Traversal s t a b
each forall t m. HasQuery t m => t -> Query (V t) (N t) m
getQuery
isInsideWinding :: HasQuery t Crossings => t -> Point (V t) (N t) -> Bool
isInsideWinding :: forall t. HasQuery t Crossings => t -> Point (V t) (N t) -> Bool
isInsideWinding t
t = (forall a. Eq a => a -> a -> Bool
/= Crossings
0) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t m. HasQuery t m => t -> Point (V t) (N t) -> m
sample t
t
isInsideEvenOdd :: HasQuery t Crossings => t -> Point (V t) (N t) -> Bool
isInsideEvenOdd :: forall t. HasQuery t Crossings => t -> Point (V t) (N t) -> Bool
isInsideEvenOdd t
t = forall a. Integral a => a -> Bool
odd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t m. HasQuery t m => t -> Point (V t) (N t) -> m
sample t
t
trailCrossings :: RealFloat n => Point V2 n -> Located (Trail V2 n) -> Crossings
trailCrossings :: forall n.
RealFloat n =>
Point V2 n -> Located (Trail V2 n) -> Crossings
trailCrossings Point V2 n
_ Located (Trail V2 n)
t | Bool -> Bool
not (forall (v :: * -> *) n. Trail v n -> Bool
isLoop (forall a. Located a -> a
unLoc Located (Trail V2 n)
t)) = Crossings
0
trailCrossings p :: Point V2 n
p@(forall n. P2 n -> (n, n)
unp2 -> (n
x,n
y)) Located (Trail V2 n)
tr
= forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
F.foldMap FixedSegment V2 n -> Crossings
test forall a b. (a -> b) -> a -> b
$ forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
Located (Trail v n) -> [FixedSegment v n]
fixTrail Located (Trail V2 n)
tr
where
test :: FixedSegment V2 n -> Crossings
test (FLinear a :: Point V2 n
a@(forall n. P2 n -> (n, n)
unp2 -> (n
_,n
ay)) b :: Point V2 n
b@(forall n. P2 n -> (n, n)
unp2 -> (n
_,n
by)))
| n
ay forall a. Ord a => a -> a -> Bool
<= n
y Bool -> Bool -> Bool
&& n
by forall a. Ord a => a -> a -> Bool
> n
y Bool -> Bool -> Bool
&& Point V2 n -> Point V2 n -> n
isLeft Point V2 n
a Point V2 n
b forall a. Ord a => a -> a -> Bool
> n
0 = Crossings
1
| n
by forall a. Ord a => a -> a -> Bool
<= n
y Bool -> Bool -> Bool
&& n
ay forall a. Ord a => a -> a -> Bool
> n
y Bool -> Bool -> Bool
&& Point V2 n -> Point V2 n -> n
isLeft Point V2 n
a Point V2 n
b forall a. Ord a => a -> a -> Bool
< n
0 = -Crossings
1
| Bool
otherwise = Crossings
0
test c :: FixedSegment V2 n
c@(FCubic (P x1 :: V2 n
x1@(V2 n
_ n
x1y))
(P c1 :: V2 n
c1@(V2 n
_ n
c1y))
(P c2 :: V2 n
c2@(V2 n
_ n
c2y))
(P x2 :: V2 n
x2@(V2 n
_ n
x2y))
) =
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map n -> Crossings
testT forall a b. (a -> b) -> a -> b
$ [n]
ts
where ts :: [n]
ts = forall a. (a -> Bool) -> [a] -> [a]
filter (forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 Bool -> Bool -> Bool
(&&) (forall a. Ord a => a -> a -> Bool
>=n
0) (forall a. Ord a => a -> a -> Bool
<=n
1))
forall a b. (a -> b) -> a -> b
$ forall d. (Floating d, Ord d) => d -> d -> d -> d -> [d]
cubForm (- n
x1y forall a. Num a => a -> a -> a
+ n
3forall a. Num a => a -> a -> a
*n
c1y forall a. Num a => a -> a -> a
- n
3forall a. Num a => a -> a -> a
*n
c2y forall a. Num a => a -> a -> a
+ n
x2y)
( n
3forall a. Num a => a -> a -> a
*n
x1y forall a. Num a => a -> a -> a
- n
6forall a. Num a => a -> a -> a
*n
c1y forall a. Num a => a -> a -> a
+ n
3forall a. Num a => a -> a -> a
*n
c2y)
(-n
3forall a. Num a => a -> a -> a
*n
x1y forall a. Num a => a -> a -> a
+ n
3forall a. Num a => a -> a -> a
*n
c1y)
(n
x1y forall a. Num a => a -> a -> a
- n
y)
testT :: n -> Crossings
testT n
t = let (forall n. P2 n -> (n, n)
unp2 -> (n
px,n
_)) = FixedSegment V2 n
c forall p. Parametric p => p -> N p -> Codomain p (N p)
`atParam` n
t
in if n
px forall a. Ord a => a -> a -> Bool
> n
x then n -> Crossings
signFromDerivAt n
t else Crossings
0
signFromDerivAt :: n -> Crossings
signFromDerivAt n
t =
let v :: V2 n
v = (n
3forall a. Num a => a -> a -> a
*n
tforall a. Num a => a -> a -> a
*n
t) forall (f :: * -> *) a. (Functor f, Num a) => a -> f a -> f a
*^ ((-n
1)forall (f :: * -> *) a. (Functor f, Num a) => a -> f a -> f a
*^V2 n
x1 forall (f :: * -> *) a. (Additive f, Num a) => f a -> f a -> f a
^+^ n
3forall (f :: * -> *) a. (Functor f, Num a) => a -> f a -> f a
*^V2 n
c1 forall (f :: * -> *) a. (Additive f, Num a) => f a -> f a -> f a
^-^ n
3forall (f :: * -> *) a. (Functor f, Num a) => a -> f a -> f a
*^V2 n
c2 forall (f :: * -> *) a. (Additive f, Num a) => f a -> f a -> f a
^+^ V2 n
x2)
forall (f :: * -> *) a. (Additive f, Num a) => f a -> f a -> f a
^+^ (n
2forall a. Num a => a -> a -> a
*n
t) forall (f :: * -> *) a. (Functor f, Num a) => a -> f a -> f a
*^ (n
3forall (f :: * -> *) a. (Functor f, Num a) => a -> f a -> f a
*^V2 n
x1 forall (f :: * -> *) a. (Additive f, Num a) => f a -> f a -> f a
^-^ n
6forall (f :: * -> *) a. (Functor f, Num a) => a -> f a -> f a
*^V2 n
c1 forall (f :: * -> *) a. (Additive f, Num a) => f a -> f a -> f a
^+^ n
3forall (f :: * -> *) a. (Functor f, Num a) => a -> f a -> f a
*^V2 n
c2)
forall (f :: * -> *) a. (Additive f, Num a) => f a -> f a -> f a
^+^ ((-n
3)forall (f :: * -> *) a. (Functor f, Num a) => a -> f a -> f a
*^V2 n
x1 forall (f :: * -> *) a. (Additive f, Num a) => f a -> f a -> f a
^+^ n
3forall (f :: * -> *) a. (Functor f, Num a) => a -> f a -> f a
*^V2 n
c1)
ang :: n
ang = V2 n
v forall s a. s -> Getting a s a -> a
^. forall (t :: * -> *) n.
(HasTheta t, RealFloat n) =>
Lens' (t n) (Angle n)
_theta forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. Iso' (Angle n) n
rad
in case () of ()
_ | n
0 forall a. Ord a => a -> a -> Bool
< n
ang Bool -> Bool -> Bool
&& n
ang forall a. Ord a => a -> a -> Bool
< forall a. Floating a => a
tauforall a. Fractional a => a -> a -> a
/n
2 Bool -> Bool -> Bool
&& n
t forall a. Ord a => a -> a -> Bool
< n
1 -> Crossings
1
| -forall a. Floating a => a
tauforall a. Fractional a => a -> a -> a
/n
2 forall a. Ord a => a -> a -> Bool
< n
ang Bool -> Bool -> Bool
&& n
ang forall a. Ord a => a -> a -> Bool
< n
0 Bool -> Bool -> Bool
&& n
t forall a. Ord a => a -> a -> Bool
> n
0 -> -Crossings
1
| Bool
otherwise -> Crossings
0
isLeft :: Point V2 n -> Point V2 n -> n
isLeft Point V2 n
a Point V2 n
b = forall n. Num n => V2 n -> V2 n -> n
cross2 (Point V2 n
b forall (p :: * -> *) a. (Affine p, Num a) => p a -> p a -> Diff p a
.-. Point V2 n
a) (Point V2 n
p forall (p :: * -> *) a. (Affine p, Num a) => p a -> p a -> Diff p a
.-. Point V2 n
a)
newtype Clip n = Clip [Path V2 n]
deriving (Typeable, NonEmpty (Clip n) -> Clip n
Clip n -> Clip n -> Clip n
forall b. Integral b => b -> Clip n -> Clip n
forall n. NonEmpty (Clip n) -> Clip n
forall n. Clip n -> Clip n -> Clip n
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
forall n b. Integral b => b -> Clip n -> Clip n
stimes :: forall b. Integral b => b -> Clip n -> Clip n
$cstimes :: forall n b. Integral b => b -> Clip n -> Clip n
sconcat :: NonEmpty (Clip n) -> Clip n
$csconcat :: forall n. NonEmpty (Clip n) -> Clip n
<> :: Clip n -> Clip n -> Clip n
$c<> :: forall n. Clip n -> Clip n -> Clip n
Semigroup)
makeWrapped ''Clip
instance Typeable n => AttributeClass (Clip n)
instance AsEmpty (Clip n) where
_Empty :: Prism' (Clip n) ()
_Empty = forall n n'. Iso (Clip n) (Clip n') [Path V2 n] [Path V2 n']
_Clip forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. AsEmpty a => Prism' a ()
_Empty
type instance V (Clip n) = V2
type instance N (Clip n) = n
instance (OrderedField n) => Transformable (Clip n) where
transform :: Transformation (V (Clip n)) (N (Clip n)) -> Clip n -> Clip n
transform Transformation (V (Clip n)) (N (Clip n))
t (Clip [Path V2 n]
ps) = forall n. [Path V2 n] -> Clip n
Clip (forall t. Transformable t => Transformation (V t) (N t) -> t -> t
transform Transformation (V (Clip n)) (N (Clip n))
t [Path V2 n]
ps)
instance RealFloat n => HasQuery (Clip n) All where
getQuery :: Clip n -> Query (V (Clip n)) (N (Clip n)) All
getQuery (Clip [Path V2 n]
paths) = forall (v :: * -> *) n m. (Point v n -> m) -> Query v n m
Query forall a b. (a -> b) -> a -> b
$ \Point (V (Clip n)) (N (Clip n))
p ->
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
F.foldMap (Bool -> All
All forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip forall t. HasQuery t Crossings => t -> Point (V t) (N t) -> Bool
isInsideWinding Point (V (Clip n)) (N (Clip n))
p) [Path V2 n]
paths
_Clip :: Iso (Clip n) (Clip n') [Path V2 n] [Path V2 n']
_Clip :: forall n n'. Iso (Clip n) (Clip n') [Path V2 n] [Path V2 n']
_Clip = forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
_Wrapped
_clip :: (Typeable n, OrderedField n) => Lens' (Style V2 n) [Path V2 n]
_clip :: forall n.
(Typeable n, OrderedField n) =>
Lens' (Style V2 n) [Path V2 n]
_clip = forall a (v :: * -> *) n.
(V a ~ v, N a ~ n, AttributeClass a, Transformable a) =>
Lens' (Style v n) (Maybe a)
atTAttr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. APrism' a () -> Iso' (Maybe a) a
non' forall a. AsEmpty a => Prism' a ()
_Empty forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n n'. Iso (Clip n) (Clip n') [Path V2 n] [Path V2 n']
_Clip
clipBy :: (HasStyle a, V a ~ V2, N a ~ n, TypeableFloat n) => Path V2 n -> a -> a
clipBy :: forall a n.
(HasStyle a, V a ~ V2, N a ~ n, TypeableFloat n) =>
Path V2 n -> a -> a
clipBy = forall a d.
(AttributeClass a, Transformable a, V a ~ V d, N a ~ N d,
HasStyle d) =>
a -> d -> d
applyTAttr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. [Path V2 n] -> Clip n
Clip forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> [a] -> [a]
:[])
clipTo :: TypeableFloat n
=> Path V2 n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
clipTo :: forall n b.
TypeableFloat n =>
Path V2 n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
clipTo Path V2 n
p QDiagram b V2 n Any
d = forall b (v :: * -> *) n m.
(OrderedField n, Metric v, Semigroup m) =>
Trace v n -> QDiagram b v n m -> QDiagram b v n m
setTrace Trace V2 n
intersectionTrace forall b c a. (b -> c) -> (a -> b) -> a -> c
. QDiagram b V2 n Any -> QDiagram b V2 n Any
toEnvelope forall a b. (a -> b) -> a -> b
$ forall a n.
(HasStyle a, V a ~ V2, N a ~ n, TypeableFloat n) =>
Path V2 n -> a -> a
clipBy Path V2 n
p QDiagram b V2 n Any
d
where
envP :: Maybe (V2 n -> n)
envP = forall (v :: * -> *) n. Envelope v n -> Maybe (v n -> n)
appEnvelope forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enveloped a => a -> Envelope (V a) (N a)
getEnvelope forall a b. (a -> b) -> a -> b
$ Path V2 n
p
envD :: Maybe (V2 n -> n)
envD = forall (v :: * -> *) n. Envelope v n -> Maybe (v n -> n)
appEnvelope forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enveloped a => a -> Envelope (V a) (N a)
getEnvelope forall a b. (a -> b) -> a -> b
$ QDiagram b V2 n Any
d
toEnvelope :: QDiagram b V2 n Any -> QDiagram b V2 n Any
toEnvelope = case (Maybe (V2 n -> n)
envP, Maybe (V2 n -> n)
envD) of
(Just V2 n -> n
eP, Just V2 n -> n
eD) -> forall b (v :: * -> *) n m.
(OrderedField n, Metric v, Monoid' m) =>
Envelope v n -> QDiagram b v n m -> QDiagram b v n m
setEnvelope forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) n. (v n -> n) -> Envelope v n
mkEnvelope forall a b. (a -> b) -> a -> b
$ \V2 n
v -> forall a. Ord a => a -> a -> a
min (V2 n -> n
eP V2 n
v) (V2 n -> n
eD V2 n
v)
(Maybe (V2 n -> n)
_, Maybe (V2 n -> n)
_) -> forall a. a -> a
id
intersectionTrace :: Trace V2 n
intersectionTrace = forall (v :: * -> *) n.
(Point v n -> v n -> SortedList n) -> Trace v n
Trace Point V2 n -> V2 n -> SortedList n
traceIntersections
traceIntersections :: Point V2 n -> V2 n -> SortedList n
traceIntersections Point V2 n
pt V2 n
v =
forall b a. Ord b => ([a] -> [b]) -> SortedList a -> SortedList b
onSortedList (forall a. (a -> Bool) -> [a] -> [a]
filter n -> Bool
pInside) (forall (v :: * -> *) n.
Trace v n -> Point v n -> v n -> SortedList n
appTrace (forall a. Traced a => a -> Trace (V a) (N a)
getTrace QDiagram b V2 n Any
d) Point V2 n
pt V2 n
v) forall a. Semigroup a => a -> a -> a
<>
forall b a. Ord b => ([a] -> [b]) -> SortedList a -> SortedList b
onSortedList (forall a. (a -> Bool) -> [a] -> [a]
filter n -> Bool
dInside) (forall (v :: * -> *) n.
Trace v n -> Point v n -> v n -> SortedList n
appTrace (forall a. Traced a => a -> Trace (V a) (N a)
getTrace Path V2 n
p) Point V2 n
pt V2 n
v) where
newPt :: n -> Point V2 n
newPt n
dist = Point V2 n
pt forall (p :: * -> *) a. (Affine p, Num a) => p a -> Diff p a -> p a
.+^ V2 n
v forall (f :: * -> *) a. (Functor f, Num a) => f a -> a -> f a
^* n
dist
pInside :: n -> Bool
pInside n
dDist = forall n.
RealFloat n =>
FillRule -> Path V2 n -> Point V2 n -> Bool
runFillRule FillRule
Winding Path V2 n
p (n -> Point V2 n
newPt n
dDist)
dInside :: n -> Bool
dInside n
pDist = Any -> Bool
getAny forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t m. HasQuery t m => t -> Point (V t) (N t) -> m
sample QDiagram b V2 n Any
d forall a b. (a -> b) -> a -> b
$ n -> Point V2 n
newPt n
pDist
clipped :: TypeableFloat n
=> Path V2 n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
clipped :: forall n b.
TypeableFloat n =>
Path V2 n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
clipped Path V2 n
p = forall (v :: * -> *) n a m b.
(InSpace v n a, Metric v, OrderedField n, Monoid' m, Traced a) =>
a -> QDiagram b v n m -> QDiagram b v n m
withTrace Path V2 n
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (v :: * -> *) n a m b.
(InSpace v n a, Monoid' m, Enveloped a) =>
a -> QDiagram b v n m -> QDiagram b v n m
withEnvelope Path V2 n
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a n.
(HasStyle a, V a ~ V2, N a ~ n, TypeableFloat n) =>
Path V2 n -> a -> a
clipBy Path V2 n
p
intersectPoints :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n)
=> t -> s -> [P2 n]
intersectPoints :: forall n t s.
(InSpace V2 n t, SameSpace t s, ToPath t, ToPath s,
OrderedField n) =>
t -> s -> [P2 n]
intersectPoints = forall n t s.
(InSpace V2 n t, SameSpace t s, ToPath t, ToPath s,
OrderedField n) =>
n -> t -> s -> [P2 n]
intersectPoints' n
1e-8
intersectPoints' :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n)
=> n -> t -> s -> [P2 n]
intersectPoints' :: forall n t s.
(InSpace V2 n t, SameSpace t s, ToPath t, ToPath s,
OrderedField n) =>
n -> t -> s -> [P2 n]
intersectPoints' n
eps t
t s
s = forall n. OrderedField n => n -> Path V2 n -> Path V2 n -> [P2 n]
intersectPointsP' n
eps (forall t.
(ToPath t, Metric (V t), OrderedField (N t)) =>
t -> Path (V t) (N t)
toPath t
t) (forall t.
(ToPath t, Metric (V t), OrderedField (N t)) =>
t -> Path (V t) (N t)
toPath s
s)
intersectPointsP :: OrderedField n => Path V2 n -> Path V2 n -> [P2 n]
intersectPointsP :: forall n. OrderedField n => Path V2 n -> Path V2 n -> [P2 n]
intersectPointsP = forall n. OrderedField n => n -> Path V2 n -> Path V2 n -> [P2 n]
intersectPointsP' n
1e-8
intersectPointsP' :: OrderedField n => n -> Path V2 n -> Path V2 n -> [P2 n]
intersectPointsP' :: forall n. OrderedField n => n -> Path V2 n -> Path V2 n -> [P2 n]
intersectPointsP' n
eps Path V2 n
as Path V2 n
bs = do
Located (Trail V2 n)
a <- forall (v :: * -> *) n. Path v n -> [Located (Trail v n)]
pathTrails Path V2 n
as
Located (Trail V2 n)
b <- forall (v :: * -> *) n. Path v n -> [Located (Trail v n)]
pathTrails Path V2 n
bs
forall n.
OrderedField n =>
n -> Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n]
intersectPointsT' n
eps Located (Trail V2 n)
a Located (Trail V2 n)
b
intersectPointsT :: OrderedField n => Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n]
intersectPointsT :: forall n.
OrderedField n =>
Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n]
intersectPointsT = forall n.
OrderedField n =>
n -> Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n]
intersectPointsT' n
1e-8
intersectPointsT' :: OrderedField n => n -> Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n]
intersectPointsT' :: forall n.
OrderedField n =>
n -> Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n]
intersectPointsT' n
eps Located (Trail V2 n)
as Located (Trail V2 n)
bs = do
FixedSegment V2 n
a <- forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
Located (Trail v n) -> [FixedSegment v n]
fixTrail Located (Trail V2 n)
as
FixedSegment V2 n
b <- forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
Located (Trail v n) -> [FixedSegment v n]
fixTrail Located (Trail V2 n)
bs
forall n.
OrderedField n =>
n -> FixedSegment V2 n -> FixedSegment V2 n -> [P2 n]
intersectPointsS' n
eps FixedSegment V2 n
a FixedSegment V2 n
b