{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Diagrams.TwoD.Arrow
(
arrowV
, arrowV'
, arrowAt
, arrowAt'
, arrowBetween
, arrowBetween'
, connect
, connect'
, connectPerim
, connectPerim'
, connectOutside
, connectOutside'
, arrow
, arrow'
, arrowFromLocatedTrail
, arrowFromLocatedTrail'
, ArrowOpts(..)
, arrowHead
, arrowTail
, arrowShaft
, headGap
, tailGap
, gaps, gap
, headTexture
, headStyle
, headLength
, tailTexture
, tailStyle
, tailLength
, lengths
, shaftTexture
, shaftStyle
, straightShaft
, module Diagrams.TwoD.Arrowheads
) where
import Control.Lens (Lens', Traversal',
generateSignatures, lensRules,
makeLensesWith, view, (%~), (&),
(.~), (^.))
import Data.Default.Class
import Data.Maybe (fromMaybe)
import Data.Monoid.Coproduct (untangle)
import Data.Semigroup
import Data.Typeable
import Data.Colour hiding (atop)
import Diagrams.Core
import Diagrams.Core.Style (unmeasureAttrs)
import Diagrams.Core.Types (QDiaLeaf (..), mkQD')
import Diagrams.Angle
import Diagrams.Attributes
import Diagrams.Direction hiding (dir)
import Diagrams.Located (Located (..), unLoc)
import Diagrams.Parametric
import Diagrams.Path
import Diagrams.Solve.Polynomial (quadForm)
import Diagrams.Tangent (tangentAtEnd, tangentAtStart)
import Diagrams.Trail
import Diagrams.TwoD.Arrowheads
import Diagrams.TwoD.Attributes
import Diagrams.TwoD.Path (stroke, strokeT)
import Diagrams.TwoD.Transform (reflectY, translateX)
import Diagrams.TwoD.Types
import Diagrams.TwoD.Vector (unitX, unit_X)
import Diagrams.Util (( # ))
import Linear.Affine
import Linear.Metric
import Linear.Vector
data ArrowOpts n
= ArrowOpts
{ ArrowOpts n -> ArrowHT n
_arrowHead :: ArrowHT n
, ArrowOpts n -> ArrowHT n
_arrowTail :: ArrowHT n
, ArrowOpts n -> Trail V2 n
_arrowShaft :: Trail V2 n
, ArrowOpts n -> Measure n
_headGap :: Measure n
, ArrowOpts n -> Measure n
_tailGap :: Measure n
, ArrowOpts n -> Style V2 n
_headStyle :: Style V2 n
, ArrowOpts n -> Measure n
_headLength :: Measure n
, ArrowOpts n -> Style V2 n
_tailStyle :: Style V2 n
, ArrowOpts n -> Measure n
_tailLength :: Measure n
, ArrowOpts n -> Style V2 n
_shaftStyle :: Style V2 n
}
straightShaft :: OrderedField n => Trail V2 n
straightShaft :: Trail V2 n
straightShaft = [V2 n] -> Trail V2 n
forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
[v n] -> Trail v n
trailFromOffsets [V2 n
forall (v :: * -> *) n. (R1 v, Additive v, Num n) => v n
unitX]
instance TypeableFloat n => Default (ArrowOpts n) where
def :: ArrowOpts n
def = ArrowOpts :: forall n.
ArrowHT n
-> ArrowHT n
-> Trail V2 n
-> Measure n
-> Measure n
-> Style V2 n
-> Measure n
-> Style V2 n
-> Measure n
-> Style V2 n
-> ArrowOpts n
ArrowOpts
{ _arrowHead :: ArrowHT n
_arrowHead = ArrowHT n
forall n. RealFloat n => ArrowHT n
dart
, _arrowTail :: ArrowHT n
_arrowTail = ArrowHT n
forall n. ArrowHT n
noTail
, _arrowShaft :: Trail V2 n
_arrowShaft = Trail V2 n
forall n. OrderedField n => Trail V2 n
straightShaft
, _headGap :: Measure n
_headGap = Measure n
forall n. OrderedField n => Measure n
none
, _tailGap :: Measure n
_tailGap = Measure n
forall n. OrderedField n => Measure n
none
, _headStyle :: Style V2 n
_headStyle = Style V2 n
forall a. Monoid a => a
mempty
, _headLength :: Measure n
_headLength = Measure n
forall n. OrderedField n => Measure n
normal
, _tailStyle :: Style V2 n
_tailStyle = Style V2 n
forall a. Monoid a => a
mempty
, _tailLength :: Measure n
_tailLength = Measure n
forall n. OrderedField n => Measure n
normal
, _shaftStyle :: Style V2 n
_shaftStyle = Style V2 n
forall a. Monoid a => a
mempty
}
makeLensesWith (lensRules & generateSignatures .~ False) ''ArrowOpts
arrowHead :: Lens' (ArrowOpts n) (ArrowHT n)
arrowTail :: Lens' (ArrowOpts n) (ArrowHT n)
arrowShaft :: Lens' (ArrowOpts n) (Trail V2 n)
headGap :: Lens' (ArrowOpts n) (Measure n)
tailGap :: Lens' (ArrowOpts n) (Measure n)
gaps :: Traversal' (ArrowOpts n) (Measure n)
gaps :: (Measure n -> f (Measure n)) -> ArrowOpts n -> f (ArrowOpts n)
gaps Measure n -> f (Measure n)
f ArrowOpts n
opts = (\Measure n
h Measure n
t -> ArrowOpts n
opts ArrowOpts n -> (ArrowOpts n -> ArrowOpts n) -> ArrowOpts n
forall a b. a -> (a -> b) -> b
& (Measure n -> Identity (Measure n))
-> ArrowOpts n -> Identity (ArrowOpts n)
forall n. Lens' (ArrowOpts n) (Measure n)
headGap ((Measure n -> Identity (Measure n))
-> ArrowOpts n -> Identity (ArrowOpts n))
-> Measure n -> ArrowOpts n -> ArrowOpts n
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Measure n
h ArrowOpts n -> (ArrowOpts n -> ArrowOpts n) -> ArrowOpts n
forall a b. a -> (a -> b) -> b
& (Measure n -> Identity (Measure n))
-> ArrowOpts n -> Identity (ArrowOpts n)
forall n. Lens' (ArrowOpts n) (Measure n)
tailGap ((Measure n -> Identity (Measure n))
-> ArrowOpts n -> Identity (ArrowOpts n))
-> Measure n -> ArrowOpts n -> ArrowOpts n
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Measure n
t)
(Measure n -> Measure n -> ArrowOpts n)
-> f (Measure n) -> f (Measure n -> ArrowOpts n)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Measure n -> f (Measure n)
f (ArrowOpts n
opts ArrowOpts n
-> Getting (Measure n) (ArrowOpts n) (Measure n) -> Measure n
forall s a. s -> Getting a s a -> a
^. Getting (Measure n) (ArrowOpts n) (Measure n)
forall n. Lens' (ArrowOpts n) (Measure n)
headGap)
f (Measure n -> ArrowOpts n) -> f (Measure n) -> f (ArrowOpts n)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Measure n -> f (Measure n)
f (ArrowOpts n
opts ArrowOpts n
-> Getting (Measure n) (ArrowOpts n) (Measure n) -> Measure n
forall s a. s -> Getting a s a -> a
^. Getting (Measure n) (ArrowOpts n) (Measure n)
forall n. Lens' (ArrowOpts n) (Measure n)
tailGap)
gap :: Traversal' (ArrowOpts n) (Measure n)
gap :: (Measure n -> f (Measure n)) -> ArrowOpts n -> f (ArrowOpts n)
gap = (Measure n -> f (Measure n)) -> ArrowOpts n -> f (ArrowOpts n)
forall n. Traversal' (ArrowOpts n) (Measure n)
gaps
headStyle :: Lens' (ArrowOpts n) (Style V2 n)
tailStyle :: Lens' (ArrowOpts n) (Style V2 n)
shaftStyle :: Lens' (ArrowOpts n) (Style V2 n)
headLength :: Lens' (ArrowOpts n) (Measure n)
tailLength :: Lens' (ArrowOpts n) (Measure n)
lengths :: Traversal' (ArrowOpts n) (Measure n)
lengths :: (Measure n -> f (Measure n)) -> ArrowOpts n -> f (ArrowOpts n)
lengths Measure n -> f (Measure n)
f ArrowOpts n
opts =
(\Measure n
h Measure n
t -> ArrowOpts n
opts ArrowOpts n -> (ArrowOpts n -> ArrowOpts n) -> ArrowOpts n
forall a b. a -> (a -> b) -> b
& (Measure n -> Identity (Measure n))
-> ArrowOpts n -> Identity (ArrowOpts n)
forall n. Lens' (ArrowOpts n) (Measure n)
headLength ((Measure n -> Identity (Measure n))
-> ArrowOpts n -> Identity (ArrowOpts n))
-> Measure n -> ArrowOpts n -> ArrowOpts n
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Measure n
h ArrowOpts n -> (ArrowOpts n -> ArrowOpts n) -> ArrowOpts n
forall a b. a -> (a -> b) -> b
& (Measure n -> Identity (Measure n))
-> ArrowOpts n -> Identity (ArrowOpts n)
forall n. Lens' (ArrowOpts n) (Measure n)
tailLength ((Measure n -> Identity (Measure n))
-> ArrowOpts n -> Identity (ArrowOpts n))
-> Measure n -> ArrowOpts n -> ArrowOpts n
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Measure n
t)
(Measure n -> Measure n -> ArrowOpts n)
-> f (Measure n) -> f (Measure n -> ArrowOpts n)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Measure n -> f (Measure n)
f (ArrowOpts n
opts ArrowOpts n
-> Getting (Measure n) (ArrowOpts n) (Measure n) -> Measure n
forall s a. s -> Getting a s a -> a
^. Getting (Measure n) (ArrowOpts n) (Measure n)
forall n. Lens' (ArrowOpts n) (Measure n)
headLength)
f (Measure n -> ArrowOpts n) -> f (Measure n) -> f (ArrowOpts n)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Measure n -> f (Measure n)
f (ArrowOpts n
opts ArrowOpts n
-> Getting (Measure n) (ArrowOpts n) (Measure n) -> Measure n
forall s a. s -> Getting a s a -> a
^. Getting (Measure n) (ArrowOpts n) (Measure n)
forall n. Lens' (ArrowOpts n) (Measure n)
tailLength)
headTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n)
headTexture :: Lens' (ArrowOpts n) (Texture n)
headTexture = (Style V2 n -> f (Style V2 n)) -> ArrowOpts n -> f (ArrowOpts n)
forall n. Lens' (ArrowOpts n) (Style V2 n)
headStyle ((Style V2 n -> f (Style V2 n)) -> ArrowOpts n -> f (ArrowOpts n))
-> ((Texture n -> f (Texture n)) -> Style V2 n -> f (Style V2 n))
-> (Texture n -> f (Texture n))
-> ArrowOpts n
-> f (ArrowOpts n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Texture n -> f (Texture n)) -> Style V2 n -> f (Style V2 n)
forall n.
(Typeable n, Floating n) =>
Lens' (Style V2 n) (Texture n)
_fillTexture
tailTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n)
tailTexture :: Lens' (ArrowOpts n) (Texture n)
tailTexture = (Style V2 n -> f (Style V2 n)) -> ArrowOpts n -> f (ArrowOpts n)
forall n. Lens' (ArrowOpts n) (Style V2 n)
tailStyle ((Style V2 n -> f (Style V2 n)) -> ArrowOpts n -> f (ArrowOpts n))
-> ((Texture n -> f (Texture n)) -> Style V2 n -> f (Style V2 n))
-> (Texture n -> f (Texture n))
-> ArrowOpts n
-> f (ArrowOpts n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Texture n -> f (Texture n)) -> Style V2 n -> f (Style V2 n)
forall n.
(Typeable n, Floating n) =>
Lens' (Style V2 n) (Texture n)
_fillTexture
shaftTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n)
shaftTexture :: Lens' (ArrowOpts n) (Texture n)
shaftTexture = (Style V2 n -> f (Style V2 n)) -> ArrowOpts n -> f (ArrowOpts n)
forall n. Lens' (ArrowOpts n) (Style V2 n)
shaftStyle ((Style V2 n -> f (Style V2 n)) -> ArrowOpts n -> f (ArrowOpts n))
-> ((Texture n -> f (Texture n)) -> Style V2 n -> f (Style V2 n))
-> (Texture n -> f (Texture n))
-> ArrowOpts n
-> f (ArrowOpts n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Texture n -> f (Texture n)) -> Style V2 n -> f (Style V2 n)
forall n.
(Floating n, Typeable n) =>
Lens' (Style V2 n) (Texture n)
_lineTexture
shaftSty :: ArrowOpts n -> Style V2 n
shaftSty :: ArrowOpts n -> Style V2 n
shaftSty ArrowOpts n
opts = ArrowOpts n
optsArrowOpts n
-> Getting (Style V2 n) (ArrowOpts n) (Style V2 n) -> Style V2 n
forall s a. s -> Getting a s a -> a
^.Getting (Style V2 n) (ArrowOpts n) (Style V2 n)
forall n. Lens' (ArrowOpts n) (Style V2 n)
shaftStyle
headSty :: TypeableFloat n => ArrowOpts n -> Style V2 n
headSty :: ArrowOpts n -> Style V2 n
headSty ArrowOpts n
opts = Colour Double -> Style V2 n -> Style V2 n
forall n a.
(InSpace V2 n a, Floating n, Typeable n, HasStyle a) =>
Colour Double -> a -> a
fc Colour Double
forall a. Num a => Colour a
black (ArrowOpts n
optsArrowOpts n
-> Getting (Style V2 n) (ArrowOpts n) (Style V2 n) -> Style V2 n
forall s a. s -> Getting a s a -> a
^.Getting (Style V2 n) (ArrowOpts n) (Style V2 n)
forall n. Lens' (ArrowOpts n) (Style V2 n)
headStyle)
tailSty :: TypeableFloat n => ArrowOpts n -> Style V2 n
tailSty :: ArrowOpts n -> Style V2 n
tailSty ArrowOpts n
opts = Colour Double -> Style V2 n -> Style V2 n
forall n a.
(InSpace V2 n a, Floating n, Typeable n, HasStyle a) =>
Colour Double -> a -> a
fc Colour Double
forall a. Num a => Colour a
black (ArrowOpts n
optsArrowOpts n
-> Getting (Style V2 n) (ArrowOpts n) (Style V2 n) -> Style V2 n
forall s a. s -> Getting a s a -> a
^.Getting (Style V2 n) (ArrowOpts n) (Style V2 n)
forall n. Lens' (ArrowOpts n) (Style V2 n)
tailStyle)
xWidth :: Floating n => (Traced t, V t ~ V2, N t ~ n) => t -> n
xWidth :: t -> n
xWidth t
p = n
a n -> n -> n
forall a. Num a => a -> a -> a
+ n
b
where
a :: n
a = n -> Maybe n -> n
forall a. a -> Maybe a -> a
fromMaybe n
0 (V2 n -> n
forall (f :: * -> *) a. (Metric f, Floating a) => f a -> a
norm (V2 n -> n) -> Maybe (V2 n) -> Maybe n
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Point (V t) n -> V t n -> t -> Maybe (V t n)
forall n a.
(n ~ N a, Num n, Traced a) =>
Point (V a) n -> V a n -> a -> Maybe (V a n)
traceV Point (V t) n
forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin V t n
forall (v :: * -> *) n. (R1 v, Additive v, Num n) => v n
unitX t
p)
b :: n
b = n -> Maybe n -> n
forall a. a -> Maybe a -> a
fromMaybe n
0 (V2 n -> n
forall (f :: * -> *) a. (Metric f, Floating a) => f a -> a
norm (V2 n -> n) -> Maybe (V2 n) -> Maybe n
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Point (V t) n -> V t n -> t -> Maybe (V t n)
forall n a.
(n ~ N a, Num n, Traced a) =>
Point (V a) n -> V a n -> a -> Maybe (V a n)
traceV Point (V t) n
forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin V t n
forall (v :: * -> *) n. (R1 v, Additive v, Num n) => v n
unit_X t
p)
colorJoint :: TypeableFloat n => Style V2 n -> Style V2 n
colorJoint :: Style V2 n -> Style V2 n
colorJoint Style V2 n
sStyle =
let c :: Maybe (Texture n)
c = (LineTexture n -> Texture n)
-> Maybe (LineTexture n) -> Maybe (Texture n)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap LineTexture n -> Texture n
forall n. LineTexture n -> Texture n
getLineTexture (Maybe (LineTexture n) -> Maybe (Texture n))
-> (Style V2 n -> Maybe (LineTexture n))
-> Style V2 n
-> Maybe (Texture n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Style V2 n -> Maybe (LineTexture n)
forall a (v :: * -> *) n. AttributeClass a => Style v n -> Maybe a
getAttr (Style V2 n -> Maybe (Texture n))
-> Style V2 n -> Maybe (Texture n)
forall a b. (a -> b) -> a -> b
$ Style V2 n
sStyle
o :: Maybe Double
o = (Opacity -> Double) -> Maybe Opacity -> Maybe Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Opacity -> Double
getOpacity (Maybe Opacity -> Maybe Double)
-> (Style V2 n -> Maybe Opacity) -> Style V2 n -> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Style V2 n -> Maybe Opacity
forall a (v :: * -> *) n. AttributeClass a => Style v n -> Maybe a
getAttr (Style V2 n -> Maybe Double) -> Style V2 n -> Maybe Double
forall a b. (a -> b) -> a -> b
$ Style V2 n
sStyle
in
case (Maybe (Texture n)
c, Maybe Double
o) of
(Maybe (Texture n)
Nothing, Maybe Double
Nothing) -> Colour Double -> Style V2 n -> Style V2 n
forall n a c.
(InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) =>
c -> a -> a
fillColor Colour Double
forall a. Num a => Colour a
black Style V2 n
forall a. Monoid a => a
mempty
(Just Texture n
t, Maybe Double
Nothing) -> Texture n -> Style V2 n -> Style V2 n
forall n a.
(InSpace V2 n a, Typeable n, Floating n, HasStyle a) =>
Texture n -> a -> a
fillTexture Texture n
t Style V2 n
forall a. Monoid a => a
mempty
(Maybe (Texture n)
Nothing, Just Double
o') -> Double -> Style V2 n -> Style V2 n
forall a. HasStyle a => Double -> a -> a
opacity Double
o' (Style V2 n -> Style V2 n)
-> (Style V2 n -> Style V2 n) -> Style V2 n -> Style V2 n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Colour Double -> Style V2 n -> Style V2 n
forall n a c.
(InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) =>
c -> a -> a
fillColor Colour Double
forall a. Num a => Colour a
black (Style V2 n -> Style V2 n) -> Style V2 n -> Style V2 n
forall a b. (a -> b) -> a -> b
$ Style V2 n
forall a. Monoid a => a
mempty
(Just Texture n
t, Just Double
o') -> Double -> Style V2 n -> Style V2 n
forall a. HasStyle a => Double -> a -> a
opacity Double
o' (Style V2 n -> Style V2 n)
-> (Style V2 n -> Style V2 n) -> Style V2 n -> Style V2 n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Texture n -> Style V2 n -> Style V2 n
forall n a.
(InSpace V2 n a, Typeable n, Floating n, HasStyle a) =>
Texture n -> a -> a
fillTexture Texture n
t (Style V2 n -> Style V2 n) -> Style V2 n -> Style V2 n
forall a b. (a -> b) -> a -> b
$ Style V2 n
forall a. Monoid a => a
mempty
widthOfJoint :: forall n. TypeableFloat n => Style V2 n -> n -> n -> n
widthOfJoint :: Style V2 n -> n -> n -> n
widthOfJoint Style V2 n
sStyle n
gToO n
nToO =
n -> Maybe n -> n
forall a. a -> Maybe a -> a
fromMaybe
(n -> n -> Measured n n -> n
forall n a. Num n => n -> n -> Measured n a -> a
fromMeasured n
gToO n
nToO Measured n n
forall n. OrderedField n => Measure n
medium)
((LineWidth n -> n) -> Maybe (LineWidth n) -> Maybe n
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap LineWidth n -> n
forall n. LineWidth n -> n
getLineWidth (Maybe (LineWidth n) -> Maybe n)
-> (Style V2 n -> Maybe (LineWidth n)) -> Style V2 n -> Maybe n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Style V2 n -> Maybe (LineWidth n)
forall a (v :: * -> *) n. AttributeClass a => Style v n -> Maybe a
getAttr (Style V2 n -> Maybe (LineWidth n))
-> (Style V2 n -> Style V2 n) -> Style V2 n -> Maybe (LineWidth n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. n -> n -> Style V2 n -> Style V2 n
forall n (v :: * -> *). Num n => n -> n -> Style v n -> Style v n
unmeasureAttrs n
gToO n
nToO (Style V2 n -> Maybe n) -> Style V2 n -> Maybe n
forall a b. (a -> b) -> a -> b
$ Style V2 n
sStyle)
mkHead :: (TypeableFloat n, Renderable (Path V2 n) b) =>
n -> ArrowOpts n -> n -> n -> Bool -> (QDiagram b V2 n Any, n)
mkHead :: n -> ArrowOpts n -> n -> n -> Bool -> (QDiagram b V2 n Any, n)
mkHead = V2 n
-> Lens' (ArrowOpts n) (ArrowHT n)
-> (ArrowOpts n -> Style V2 n)
-> n
-> ArrowOpts n
-> n
-> n
-> Bool
-> (QDiagram b V2 n Any, n)
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
V2 n
-> Lens' (ArrowOpts n) (ArrowHT n)
-> (ArrowOpts n -> Style V2 n)
-> n
-> ArrowOpts n
-> n
-> n
-> Bool
-> (QDiagram b V2 n Any, n)
mkHT V2 n
forall (v :: * -> *) n. (R1 v, Additive v, Num n) => v n
unit_X forall n. Lens' (ArrowOpts n) (ArrowHT n)
Lens' (ArrowOpts n) (ArrowHT n)
arrowHead ArrowOpts n -> Style V2 n
forall n. TypeableFloat n => ArrowOpts n -> Style V2 n
headSty
mkTail :: (TypeableFloat n, Renderable (Path V2 n) b) =>
n -> ArrowOpts n -> n -> n -> Bool -> (QDiagram b V2 n Any, n)
mkTail :: n -> ArrowOpts n -> n -> n -> Bool -> (QDiagram b V2 n Any, n)
mkTail = V2 n
-> Lens' (ArrowOpts n) (ArrowHT n)
-> (ArrowOpts n -> Style V2 n)
-> n
-> ArrowOpts n
-> n
-> n
-> Bool
-> (QDiagram b V2 n Any, n)
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
V2 n
-> Lens' (ArrowOpts n) (ArrowHT n)
-> (ArrowOpts n -> Style V2 n)
-> n
-> ArrowOpts n
-> n
-> n
-> Bool
-> (QDiagram b V2 n Any, n)
mkHT V2 n
forall (v :: * -> *) n. (R1 v, Additive v, Num n) => v n
unitX forall n. Lens' (ArrowOpts n) (ArrowHT n)
Lens' (ArrowOpts n) (ArrowHT n)
arrowTail ArrowOpts n -> Style V2 n
forall n. TypeableFloat n => ArrowOpts n -> Style V2 n
tailSty
mkHT
:: (TypeableFloat n, Renderable (Path V2 n) b)
=> V2 n -> Lens' (ArrowOpts n) (ArrowHT n) -> (ArrowOpts n -> Style V2 n)
-> n -> ArrowOpts n -> n -> n -> Bool -> (QDiagram b V2 n Any, n)
mkHT :: V2 n
-> Lens' (ArrowOpts n) (ArrowHT n)
-> (ArrowOpts n -> Style V2 n)
-> n
-> ArrowOpts n
-> n
-> n
-> Bool
-> (QDiagram b V2 n Any, n)
mkHT V2 n
xDir Lens' (ArrowOpts n) (ArrowHT n)
htProj ArrowOpts n -> Style V2 n
styProj n
sz ArrowOpts n
opts n
gToO n
nToO Bool
reflect
= ( (QDiagram b V2 n Any
j QDiagram b V2 n Any -> QDiagram b V2 n Any -> QDiagram b V2 n Any
forall a. Semigroup a => a -> a -> a
<> QDiagram b V2 n Any
ht)
# (if reflect then reflectY else id)
# moveOriginBy (jWidth *^ xDir) # lwO 0
, n
htWidth n -> n -> n
forall a. Num a => a -> a -> a
+ n
jWidth
)
where
(Path V2 n
ht', Path V2 n
j') = (ArrowOpts n
optsArrowOpts n
-> Getting (ArrowHT n) (ArrowOpts n) (ArrowHT n) -> ArrowHT n
forall s a. s -> Getting a s a -> a
^.Getting (ArrowHT n) (ArrowOpts n) (ArrowHT n)
Lens' (ArrowOpts n) (ArrowHT n)
htProj) n
sz
(Style V2 n -> n -> n -> n
forall n. TypeableFloat n => Style V2 n -> n -> n -> n
widthOfJoint (ArrowOpts n -> Style V2 n
forall n. ArrowOpts n -> Style V2 n
shaftSty ArrowOpts n
opts) n
gToO n
nToO)
htWidth :: n
htWidth = Path V2 n -> n
forall n t. (Floating n, Traced t, V t ~ V2, N t ~ n) => t -> n
xWidth Path V2 n
ht'
jWidth :: n
jWidth = Path V2 n -> n
forall n t. (Floating n, Traced t, V t ~ V2, N t ~ n) => t -> n
xWidth Path V2 n
j'
ht :: QDiagram b V2 n Any
ht = Path V2 n -> QDiagram b V2 n Any
forall n t b.
(InSpace V2 n t, ToPath t, TypeableFloat n,
Renderable (Path V2 n) b) =>
t -> QDiagram b V2 n Any
stroke Path V2 n
ht' QDiagram b V2 n Any
-> (QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
forall a b. a -> (a -> b) -> b
# Style (V (QDiagram b V2 n Any)) (N (QDiagram b V2 n Any))
-> QDiagram b V2 n Any -> QDiagram b V2 n Any
forall a. HasStyle a => Style (V a) (N a) -> a -> a
applyStyle (ArrowOpts n -> Style V2 n
styProj ArrowOpts n
opts)
j :: QDiagram b V2 n Any
j = Path V2 n -> QDiagram b V2 n Any
forall n t b.
(InSpace V2 n t, ToPath t, TypeableFloat n,
Renderable (Path V2 n) b) =>
t -> QDiagram b V2 n Any
stroke Path V2 n
j' QDiagram b V2 n Any
-> (QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
forall a b. a -> (a -> b) -> b
# Style (V (QDiagram b V2 n Any)) (N (QDiagram b V2 n Any))
-> QDiagram b V2 n Any -> QDiagram b V2 n Any
forall a. HasStyle a => Style (V a) (N a) -> a -> a
applyStyle (Style V2 n -> Style V2 n
forall n. TypeableFloat n => Style V2 n -> Style V2 n
colorJoint (ArrowOpts n
optsArrowOpts n
-> Getting (Style V2 n) (ArrowOpts n) (Style V2 n) -> Style V2 n
forall s a. s -> Getting a s a -> a
^.Getting (Style V2 n) (ArrowOpts n) (Style V2 n)
forall n. Lens' (ArrowOpts n) (Style V2 n)
shaftStyle))
spine :: TypeableFloat n => Trail V2 n -> n -> n -> n -> Trail V2 n
spine :: Trail V2 n -> n -> n -> n -> Trail V2 n
spine Trail V2 n
tr n
tw n
hw n
sz = Trail V2 n
tS Trail V2 n -> Trail V2 n -> Trail V2 n
forall a. Semigroup a => a -> a -> a
<> Trail V2 n
tr Trail V2 n -> (Trail V2 n -> Trail V2 n) -> Trail V2 n
forall a b. a -> (a -> b) -> b
# n -> Trail V2 n -> Trail V2 n
forall (v :: * -> *) n a.
(InSpace v n a, Eq n, Fractional n, Transformable a) =>
n -> a -> a
scale n
sz Trail V2 n -> Trail V2 n -> Trail V2 n
forall a. Semigroup a => a -> a -> a
<> Trail V2 n
hS
where
tSpine :: Trail V2 n
tSpine = [V2 n] -> Trail V2 n
forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
[v n] -> Trail v n
trailFromOffsets [V2 n -> V2 n
forall (f :: * -> *) a. (Metric f, Floating a) => f a -> f a
signorm (V2 n -> V2 n) -> (Trail V2 n -> V2 n) -> Trail V2 n -> V2 n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Trail V2 n -> V2 n
forall t. EndValues (Tangent t) => t -> Vn t
tangentAtStart (Trail V2 n -> V2 n) -> Trail V2 n -> V2 n
forall a b. (a -> b) -> a -> b
$ Trail V2 n
tr] Trail V2 n -> (Trail V2 n -> Trail V2 n) -> Trail V2 n
forall a b. a -> (a -> b) -> b
# n -> Trail V2 n -> Trail V2 n
forall (v :: * -> *) n a.
(InSpace v n a, Eq n, Fractional n, Transformable a) =>
n -> a -> a
scale n
tw
hSpine :: Trail V2 n
hSpine = [V2 n] -> Trail V2 n
forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
[v n] -> Trail v n
trailFromOffsets [V2 n -> V2 n
forall (f :: * -> *) a. (Metric f, Floating a) => f a -> f a
signorm (V2 n -> V2 n) -> (Trail V2 n -> V2 n) -> Trail V2 n -> V2 n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Trail V2 n -> V2 n
forall t. EndValues (Tangent t) => t -> Vn t
tangentAtEnd (Trail V2 n -> V2 n) -> Trail V2 n -> V2 n
forall a b. (a -> b) -> a -> b
$ Trail V2 n
tr] Trail V2 n -> (Trail V2 n -> Trail V2 n) -> Trail V2 n
forall a b. a -> (a -> b) -> b
# n -> Trail V2 n -> Trail V2 n
forall (v :: * -> *) n a.
(InSpace v n a, Eq n, Fractional n, Transformable a) =>
n -> a -> a
scale n
hw
hS :: Trail V2 n
hS = if n
hw n -> n -> Bool
forall a. Ord a => a -> a -> Bool
> n
0 then Trail V2 n
hSpine else Trail V2 n
forall a. Monoid a => a
mempty
tS :: Trail V2 n
tS = if n
tw n -> n -> Bool
forall a. Ord a => a -> a -> Bool
> n
0 then Trail V2 n
tSpine else Trail V2 n
forall a. Monoid a => a
mempty
scaleFactor :: TypeableFloat n => Trail V2 n -> n -> n -> n -> n
scaleFactor :: Trail V2 n -> n -> n -> n -> n
scaleFactor Trail V2 n
tr n
tw n
hw n
t
= case n -> n -> n -> [n]
forall d. (Floating d, Ord d) => d -> d -> d -> [d]
quadForm
(V2 n -> n
forall (f :: * -> *) a. (Metric f, Num a) => f a -> a
quadrance V2 n
v)
(n
2n -> n -> n
forall a. Num a => a -> a -> a
* (V2 n
v V2 n -> V2 n -> n
forall (f :: * -> *) a. (Metric f, Num a) => f a -> f a -> a
`dot` (V2 n
tv V2 n -> V2 n -> V2 n
forall (f :: * -> *) a. (Additive f, Num a) => f a -> f a -> f a
^+^ V2 n
hv)))
(V2 n -> n
forall (f :: * -> *) a. (Metric f, Num a) => f a -> a
quadrance (V2 n
tv V2 n -> V2 n -> V2 n
forall (f :: * -> *) a. (Additive f, Num a) => f a -> f a -> f a
^+^ V2 n
hv) n -> n -> n
forall a. Num a => a -> a -> a
- n
tn -> n -> n
forall a. Num a => a -> a -> a
*n
t)
of
[] -> n
1
[n
s] -> n
s
[n]
ss -> [n] -> n
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [n]
ss
where
tv :: V2 n
tv = n
tw n -> V2 n -> V2 n
forall (f :: * -> *) a. (Functor f, Num a) => a -> f a -> f a
*^ (Trail V2 n -> Vn (Trail V2 n)
forall t. EndValues (Tangent t) => t -> Vn t
tangentAtStart Trail V2 n
tr V2 n -> (V2 n -> V2 n) -> V2 n
forall a b. a -> (a -> b) -> b
# V2 n -> V2 n
forall (f :: * -> *) a. (Metric f, Floating a) => f a -> f a
signorm)
hv :: V2 n
hv = n
hw n -> V2 n -> V2 n
forall (f :: * -> *) a. (Functor f, Num a) => a -> f a -> f a
*^ (Trail V2 n -> Vn (Trail V2 n)
forall t. EndValues (Tangent t) => t -> Vn t
tangentAtEnd Trail V2 n
tr V2 n -> (V2 n -> V2 n) -> V2 n
forall a b. a -> (a -> b) -> b
# V2 n -> V2 n
forall (f :: * -> *) a. (Metric f, Floating a) => f a -> f a
signorm)
v :: V2 n
v = Trail V2 n -> V2 n
forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
Trail v n -> v n
trailOffset Trail V2 n
tr
arrowEnv :: TypeableFloat n => ArrowOpts n -> n -> Envelope V2 n
arrowEnv :: ArrowOpts n -> n -> Envelope V2 n
arrowEnv ArrowOpts n
opts n
len = Trail V2 n -> Envelope (V (Trail V2 n)) (N (Trail V2 n))
forall a. Enveloped a => a -> Envelope (V a) (N a)
getEnvelope Trail V2 n
horizShaft
where
horizShaft :: Trail V2 n
horizShaft = Trail V2 n
shaft Trail V2 n -> (Trail V2 n -> Trail V2 n) -> Trail V2 n
forall a b. a -> (a -> b) -> b
# Angle n -> Trail V2 n -> Trail V2 n
forall n t.
(InSpace V2 n t, Transformable t, Floating n) =>
Angle n -> t -> t
rotate (Angle n -> Angle n
forall (f :: * -> *) a. (Functor f, Num a) => f a -> f a
negated (V2 n
v V2 n -> Getting (Angle n) (V2 n) (Angle n) -> Angle n
forall s a. s -> Getting a s a -> a
^. Getting (Angle n) (V2 n) (Angle n)
forall (t :: * -> *) n.
(HasTheta t, RealFloat n) =>
Lens' (t n) (Angle n)
_theta)) Trail V2 n -> (Trail V2 n -> Trail V2 n) -> Trail V2 n
forall a b. a -> (a -> b) -> b
# n -> Trail V2 n -> Trail V2 n
forall (v :: * -> *) n a.
(InSpace v n a, Eq n, Fractional n, Transformable a) =>
n -> a -> a
scale (n
len n -> n -> n
forall a. Fractional a => a -> a -> a
/ n
m)
m :: n
m = V2 n -> n
forall (f :: * -> *) a. (Metric f, Floating a) => f a -> a
norm V2 n
v
v :: V2 n
v = Trail V2 n -> V2 n
forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
Trail v n -> v n
trailOffset Trail V2 n
shaft
shaft :: Trail V2 n
shaft = ArrowOpts n
opts ArrowOpts n
-> Getting (Trail V2 n) (ArrowOpts n) (Trail V2 n) -> Trail V2 n
forall s a. s -> Getting a s a -> a
^. Getting (Trail V2 n) (ArrowOpts n) (Trail V2 n)
forall n. Lens' (ArrowOpts n) (Trail V2 n)
arrowShaft
arrow :: (TypeableFloat n, Renderable (Path V2 n) b) => n -> QDiagram b V2 n Any
arrow :: n -> QDiagram b V2 n Any
arrow = ArrowOpts n -> n -> QDiagram b V2 n Any
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> n -> QDiagram b V2 n Any
arrow' ArrowOpts n
forall a. Default a => a
def
arrow' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> n -> QDiagram b V2 n Any
arrow' :: ArrowOpts n -> n -> QDiagram b V2 n Any
arrow' ArrowOpts n
opts n
len = QDiaLeaf b V2 n Any
-> Envelope V2 n
-> Trace V2 n
-> SubMap b V2 n Any
-> Query V2 n Any
-> QDiagram b V2 n Any
forall b (v :: * -> *) n m.
QDiaLeaf b v n m
-> Envelope v n
-> Trace v n
-> SubMap b v n m
-> Query v n m
-> QDiagram b v n m
mkQD' ((DownAnnots V2 n -> n -> n -> QDiagram b V2 n Any)
-> QDiaLeaf b V2 n Any
forall b (v :: * -> *) n m.
(DownAnnots v n -> n -> n -> QDiagram b v n m) -> QDiaLeaf b v n m
DelayedLeaf DownAnnots V2 n -> n -> n -> QDiagram b V2 n Any
delayedArrow)
(ArrowOpts n -> n -> Envelope V2 n
forall n. TypeableFloat n => ArrowOpts n -> n -> Envelope V2 n
arrowEnv ArrowOpts n
opts n
len) Trace V2 n
forall a. Monoid a => a
mempty SubMap b V2 n Any
forall a. Monoid a => a
mempty Query V2 n Any
forall a. Monoid a => a
mempty
where
delayedArrow :: DownAnnots V2 n -> n -> n -> QDiagram b V2 n Any
delayedArrow DownAnnots V2 n
da n
g n
n =
let (Transformation V2 n
trans, Style V2 n
globalSty) = (Transformation V2 n, Style V2 n)
-> ((Transformation V2 n :+: Style V2 n)
-> (Transformation V2 n, Style V2 n))
-> Maybe (Transformation V2 n :+: Style V2 n)
-> (Transformation V2 n, Style V2 n)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Transformation V2 n, Style V2 n)
forall a. Monoid a => a
mempty (Transformation V2 n :+: Style V2 n)
-> (Transformation V2 n, Style V2 n)
forall m n. (Action m n, Monoid m, Monoid n) => (m :+: n) -> (m, n)
untangle (Maybe (Transformation V2 n :+: Style V2 n)
-> (Transformation V2 n, Style V2 n))
-> (DownAnnots V2 n -> Maybe (Transformation V2 n :+: Style V2 n))
-> DownAnnots V2 n
-> (Transformation V2 n, Style V2 n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DownAnnots V2 n -> Maybe (Transformation V2 n :+: Style V2 n)
forall a b. (a, b) -> a
fst (DownAnnots V2 n -> (Transformation V2 n, Style V2 n))
-> DownAnnots V2 n -> (Transformation V2 n, Style V2 n)
forall a b. (a -> b) -> a -> b
$ DownAnnots V2 n
da
in Style V2 n
-> Transformation V2 n -> n -> n -> n -> QDiagram b V2 n Any
dArrow Style V2 n
globalSty Transformation V2 n
trans n
len n
g n
n
dArrow :: Style V2 n
-> Transformation V2 n -> n -> n -> n -> QDiagram b V2 n Any
dArrow Style V2 n
sty Transformation V2 n
tr n
ln n
gToO n
nToO = (QDiagram b V2 n Any
h' QDiagram b V2 n Any -> QDiagram b V2 n Any -> QDiagram b V2 n Any
forall a. Semigroup a => a -> a -> a
<> QDiagram b V2 n Any
t' QDiagram b V2 n Any -> QDiagram b V2 n Any -> QDiagram b V2 n Any
forall a. Semigroup a => a -> a -> a
<> QDiagram b V2 n Any
shaft)
# moveOriginBy (tWidth *^ (unit_X # rotate tAngle))
# rotate (((q .-. p)^._theta) ^-^ (dir^._theta))
# moveTo p
where
p :: Point V2 n
p = Point V2 n
forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin Point V2 n -> (Point V2 n -> Point V2 n) -> Point V2 n
forall a b. a -> (a -> b) -> b
# Transformation (V (Point V2 n)) (N (Point V2 n))
-> Point V2 n -> Point V2 n
forall t. Transformable t => Transformation (V t) (N t) -> t -> t
transform Transformation (V (Point V2 n)) (N (Point V2 n))
Transformation V2 n
tr
q :: Point V2 n
q = Point V2 n
forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin Point V2 n -> (Point V2 n -> Point V2 n) -> Point V2 n
forall a b. a -> (a -> b) -> b
# n -> Point V2 n -> Point V2 n
forall (v :: * -> *) n t.
(InSpace v n t, R1 v, Transformable t) =>
n -> t -> t
translateX n
ln Point V2 n -> (Point V2 n -> Point V2 n) -> Point V2 n
forall a b. a -> (a -> b) -> b
# Transformation (V (Point V2 n)) (N (Point V2 n))
-> Point V2 n -> Point V2 n
forall t. Transformable t => Transformation (V t) (N t) -> t -> t
transform Transformation (V (Point V2 n)) (N (Point V2 n))
Transformation V2 n
tr
globalLC :: Maybe (Texture n)
globalLC = LineTexture n -> Texture n
forall n. LineTexture n -> Texture n
getLineTexture (LineTexture n -> Texture n)
-> Maybe (LineTexture n) -> Maybe (Texture n)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Style V2 n -> Maybe (LineTexture n)
forall a (v :: * -> *) n. AttributeClass a => Style v n -> Maybe a
getAttr Style V2 n
sty
opts' :: ArrowOpts n
opts' = ArrowOpts n
opts
ArrowOpts n -> (ArrowOpts n -> ArrowOpts n) -> ArrowOpts n
forall a b. a -> (a -> b) -> b
& (Style V2 n -> Identity (Style V2 n))
-> ArrowOpts n -> Identity (ArrowOpts n)
forall n. Lens' (ArrowOpts n) (Style V2 n)
headStyle ((Style V2 n -> Identity (Style V2 n))
-> ArrowOpts n -> Identity (ArrowOpts n))
-> (Style V2 n -> Style V2 n) -> ArrowOpts n -> ArrowOpts n
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (Style V2 n -> Style V2 n)
-> (Texture n -> Style V2 n -> Style V2 n)
-> Maybe (Texture n)
-> Style V2 n
-> Style V2 n
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Style V2 n -> Style V2 n
forall a. a -> a
id Texture n -> Style V2 n -> Style V2 n
forall n a.
(InSpace V2 n a, Typeable n, Floating n, HasStyle a) =>
Texture n -> a -> a
fillTexture Maybe (Texture n)
globalLC
ArrowOpts n -> (ArrowOpts n -> ArrowOpts n) -> ArrowOpts n
forall a b. a -> (a -> b) -> b
& (Style V2 n -> Identity (Style V2 n))
-> ArrowOpts n -> Identity (ArrowOpts n)
forall n. Lens' (ArrowOpts n) (Style V2 n)
tailStyle ((Style V2 n -> Identity (Style V2 n))
-> ArrowOpts n -> Identity (ArrowOpts n))
-> (Style V2 n -> Style V2 n) -> ArrowOpts n -> ArrowOpts n
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (Style V2 n -> Style V2 n)
-> (Texture n -> Style V2 n -> Style V2 n)
-> Maybe (Texture n)
-> Style V2 n
-> Style V2 n
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Style V2 n -> Style V2 n
forall a. a -> a
id Texture n -> Style V2 n -> Style V2 n
forall n a.
(InSpace V2 n a, Typeable n, Floating n, HasStyle a) =>
Texture n -> a -> a
fillTexture Maybe (Texture n)
globalLC
ArrowOpts n -> (ArrowOpts n -> ArrowOpts n) -> ArrowOpts n
forall a b. a -> (a -> b) -> b
& (Style V2 n -> Identity (Style V2 n))
-> ArrowOpts n -> Identity (ArrowOpts n)
forall n. Lens' (ArrowOpts n) (Style V2 n)
shaftStyle ((Style V2 n -> Identity (Style V2 n))
-> ArrowOpts n -> Identity (ArrowOpts n))
-> (Style V2 n -> Style V2 n) -> ArrowOpts n -> ArrowOpts n
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Style (V (Style V2 n)) (N (Style V2 n)) -> Style V2 n -> Style V2 n
forall a. HasStyle a => Style (V a) (N a) -> a -> a
applyStyle Style (V (Style V2 n)) (N (Style V2 n))
Style V2 n
sty (Style V2 n -> Style V2 n)
-> (Style V2 n -> Style V2 n) -> Style V2 n -> Style V2 n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transformation (V (Style V2 n)) (N (Style V2 n))
-> Style V2 n -> Style V2 n
forall t. Transformable t => Transformation (V t) (N t) -> t -> t
transform Transformation (V (Style V2 n)) (N (Style V2 n))
Transformation V2 n
tr
scaleFromMeasure :: Measured n n -> n
scaleFromMeasure = n -> n -> Measured n n -> n
forall n a. Num n => n -> n -> Measured n a -> a
fromMeasured n
gToO n
nToO (Measured n n -> n)
-> (Measured n n -> Measured n n) -> Measured n n -> n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. n -> Measured n n -> Measured n n
forall n a. Num n => n -> Measured n a -> Measured n a
scaleLocal (Transformation V2 n -> n
forall (v :: * -> *) n.
(Additive v, Traversable v, Floating n) =>
Transformation v n -> n
avgScale Transformation V2 n
tr)
hSize :: n
hSize = Measured n n -> n
scaleFromMeasure (Measured n n -> n) -> Measured n n -> n
forall a b. (a -> b) -> a -> b
$ ArrowOpts n
opts ArrowOpts n
-> Getting (Measured n n) (ArrowOpts n) (Measured n n)
-> Measured n n
forall s a. s -> Getting a s a -> a
^. Getting (Measured n n) (ArrowOpts n) (Measured n n)
forall n. Lens' (ArrowOpts n) (Measure n)
headLength
tSize :: n
tSize = Measured n n -> n
scaleFromMeasure (Measured n n -> n) -> Measured n n -> n
forall a b. (a -> b) -> a -> b
$ ArrowOpts n
opts ArrowOpts n
-> Getting (Measured n n) (ArrowOpts n) (Measured n n)
-> Measured n n
forall s a. s -> Getting a s a -> a
^. Getting (Measured n n) (ArrowOpts n) (Measured n n)
forall n. Lens' (ArrowOpts n) (Measure n)
tailLength
hGap :: n
hGap = Measured n n -> n
scaleFromMeasure (Measured n n -> n) -> Measured n n -> n
forall a b. (a -> b) -> a -> b
$ ArrowOpts n
opts ArrowOpts n
-> Getting (Measured n n) (ArrowOpts n) (Measured n n)
-> Measured n n
forall s a. s -> Getting a s a -> a
^. Getting (Measured n n) (ArrowOpts n) (Measured n n)
forall n. Lens' (ArrowOpts n) (Measure n)
headGap
tGap :: n
tGap = Measured n n -> n
scaleFromMeasure (Measured n n -> n) -> Measured n n -> n
forall a b. (a -> b) -> a -> b
$ ArrowOpts n
opts ArrowOpts n
-> Getting (Measured n n) (ArrowOpts n) (Measured n n)
-> Measured n n
forall s a. s -> Getting a s a -> a
^. Getting (Measured n n) (ArrowOpts n) (Measured n n)
forall n. Lens' (ArrowOpts n) (Measure n)
tailGap
(QDiagram b V2 n Any
h, n
hWidth') = n -> ArrowOpts n -> n -> n -> Bool -> (QDiagram b V2 n Any, n)
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
n -> ArrowOpts n -> n -> n -> Bool -> (QDiagram b V2 n Any, n)
mkHead n
hSize ArrowOpts n
opts' n
gToO n
nToO (Transformation V2 n -> Bool
forall (v :: * -> *) n.
(Additive v, Traversable v, Num n, Ord n) =>
Transformation v n -> Bool
isReflection Transformation V2 n
tr)
(QDiagram b V2 n Any
t, n
tWidth') = n -> ArrowOpts n -> n -> n -> Bool -> (QDiagram b V2 n Any, n)
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
n -> ArrowOpts n -> n -> n -> Bool -> (QDiagram b V2 n Any, n)
mkTail n
tSize ArrowOpts n
opts' n
gToO n
nToO (Transformation V2 n -> Bool
forall (v :: * -> *) n.
(Additive v, Traversable v, Num n, Ord n) =>
Transformation v n -> Bool
isReflection Transformation V2 n
tr)
rawShaftTrail :: Trail V2 n
rawShaftTrail = ArrowOpts n
optsArrowOpts n
-> Getting (Trail V2 n) (ArrowOpts n) (Trail V2 n) -> Trail V2 n
forall s a. s -> Getting a s a -> a
^.Getting (Trail V2 n) (ArrowOpts n) (Trail V2 n)
forall n. Lens' (ArrowOpts n) (Trail V2 n)
arrowShaft
shaftTrail :: Trail V2 n
shaftTrail
= Trail V2 n
rawShaftTrail
# rotate (negated . view _theta . trailOffset $ rawShaftTrail)
# transform tr
tWidth :: n
tWidth = n
tWidth' n -> n -> n
forall a. Num a => a -> a -> a
+ n
tGap
hWidth :: n
hWidth = n
hWidth' n -> n -> n
forall a. Num a => a -> a -> a
+ n
hGap
tAngle :: Angle n
tAngle = Trail V2 n -> Vn (Trail V2 n)
forall t. EndValues (Tangent t) => t -> Vn t
tangentAtStart Trail V2 n
shaftTrail V2 n -> Getting (Angle n) (V2 n) (Angle n) -> Angle n
forall s a. s -> Getting a s a -> a
^. Getting (Angle n) (V2 n) (Angle n)
forall (t :: * -> *) n.
(HasTheta t, RealFloat n) =>
Lens' (t n) (Angle n)
_theta
hAngle :: Angle n
hAngle = Trail V2 n -> Vn (Trail V2 n)
forall t. EndValues (Tangent t) => t -> Vn t
tangentAtEnd Trail V2 n
shaftTrail V2 n -> Getting (Angle n) (V2 n) (Angle n) -> Angle n
forall s a. s -> Getting a s a -> a
^. Getting (Angle n) (V2 n) (Angle n)
forall (t :: * -> *) n.
(HasTheta t, RealFloat n) =>
Lens' (t n) (Angle n)
_theta
sf :: n
sf = Trail V2 n -> n -> n -> n -> n
forall n. TypeableFloat n => Trail V2 n -> n -> n -> n -> n
scaleFactor Trail V2 n
shaftTrail n
tWidth n
hWidth (V2 n -> n
forall (f :: * -> *) a. (Metric f, Floating a) => f a -> a
norm (Point V2 n
q Point V2 n -> Point V2 n -> Diff (Point V2) n
forall (p :: * -> *) a. (Affine p, Num a) => p a -> p a -> Diff p a
.-. Point V2 n
p))
shaftTrail' :: Trail V2 n
shaftTrail' = Trail V2 n
shaftTrail Trail V2 n -> (Trail V2 n -> Trail V2 n) -> Trail V2 n
forall a b. a -> (a -> b) -> b
# n -> Trail V2 n -> Trail V2 n
forall (v :: * -> *) n a.
(InSpace v n a, Eq n, Fractional n, Transformable a) =>
n -> a -> a
scale n
sf
shaft :: QDiagram b V2 n Any
shaft = Trail V2 n -> QDiagram b V2 n Any
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Trail V2 n -> QDiagram b V2 n Any
strokeT Trail V2 n
shaftTrail' QDiagram b V2 n Any
-> (QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
forall a b. a -> (a -> b) -> b
# Style (V (QDiagram b V2 n Any)) (N (QDiagram b V2 n Any))
-> QDiagram b V2 n Any -> QDiagram b V2 n Any
forall a. HasStyle a => Style (V a) (N a) -> a -> a
applyStyle (ArrowOpts n -> Style V2 n
forall n. ArrowOpts n -> Style V2 n
shaftSty ArrowOpts n
opts')
h' :: QDiagram b V2 n Any
h' = QDiagram b V2 n Any
h QDiagram b V2 n Any
-> (QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
forall a b. a -> (a -> b) -> b
# Angle n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
forall n t.
(InSpace V2 n t, Transformable t, Floating n) =>
Angle n -> t -> t
rotate Angle n
hAngle
# moveTo (origin .+^ shaftTrail' `atParam` domainUpper shaftTrail')
t' :: QDiagram b V2 n Any
t' = QDiagram b V2 n Any
t QDiagram b V2 n Any
-> (QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
forall a b. a -> (a -> b) -> b
# Angle n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
forall n t.
(InSpace V2 n t, Transformable t, Floating n) =>
Angle n -> t -> t
rotate Angle n
tAngle
dir :: Direction V2 n
dir = V2 n -> Direction V2 n
forall (v :: * -> *) n. v n -> Direction v n
direction (Trail V2 n -> V2 n
forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
Trail v n -> v n
trailOffset (Trail V2 n -> V2 n) -> Trail V2 n -> V2 n
forall a b. (a -> b) -> a -> b
$ Trail V2 n -> n -> n -> n -> Trail V2 n
forall n.
TypeableFloat n =>
Trail V2 n -> n -> n -> n -> Trail V2 n
spine Trail V2 n
shaftTrail n
tWidth n
hWidth n
sf)
arrowBetween :: (TypeableFloat n, Renderable (Path V2 n) b) => Point V2 n -> Point V2 n -> QDiagram b V2 n Any
arrowBetween :: Point V2 n -> Point V2 n -> QDiagram b V2 n Any
arrowBetween = ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any
arrowBetween' ArrowOpts n
forall a. Default a => a
def
arrowBetween'
:: (TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any
arrowBetween' :: ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any
arrowBetween' ArrowOpts n
opts Point V2 n
s Point V2 n
e = ArrowOpts n -> Point V2 n -> V2 n -> QDiagram b V2 n Any
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> Point V2 n -> V2 n -> QDiagram b V2 n Any
arrowAt' ArrowOpts n
opts Point V2 n
s (Point V2 n
e Point V2 n -> Point V2 n -> Diff (Point V2) n
forall (p :: * -> *) a. (Affine p, Num a) => p a -> p a -> Diff p a
.-. Point V2 n
s)
arrowAt :: (TypeableFloat n, Renderable (Path V2 n) b) => Point V2 n -> V2 n -> QDiagram b V2 n Any
arrowAt :: Point V2 n -> V2 n -> QDiagram b V2 n Any
arrowAt = ArrowOpts n -> Point V2 n -> V2 n -> QDiagram b V2 n Any
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> Point V2 n -> V2 n -> QDiagram b V2 n Any
arrowAt' ArrowOpts n
forall a. Default a => a
def
arrowAt'
:: (TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> Point V2 n -> V2 n -> QDiagram b V2 n Any
arrowAt' :: ArrowOpts n -> Point V2 n -> V2 n -> QDiagram b V2 n Any
arrowAt' ArrowOpts n
opts Point V2 n
s V2 n
v = ArrowOpts n -> n -> QDiagram b V2 n Any
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> n -> QDiagram b V2 n Any
arrow' ArrowOpts n
opts n
len
# rotate dir # moveTo s
where
len :: n
len = V2 n -> n
forall (f :: * -> *) a. (Metric f, Floating a) => f a -> a
norm V2 n
v
dir :: Angle n
dir = V2 n
v V2 n -> Getting (Angle n) (V2 n) (Angle n) -> Angle n
forall s a. s -> Getting a s a -> a
^. Getting (Angle n) (V2 n) (Angle n)
forall (t :: * -> *) n.
(HasTheta t, RealFloat n) =>
Lens' (t n) (Angle n)
_theta
arrowV :: (TypeableFloat n, Renderable (Path V2 n) b) => V2 n -> QDiagram b V2 n Any
arrowV :: V2 n -> QDiagram b V2 n Any
arrowV = ArrowOpts n -> V2 n -> QDiagram b V2 n Any
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> V2 n -> QDiagram b V2 n Any
arrowV' ArrowOpts n
forall a. Default a => a
def
arrowV'
:: (TypeableFloat n, Renderable (Path V2 n) b)
=> ArrowOpts n -> V2 n -> QDiagram b V2 n Any
arrowV' :: ArrowOpts n -> V2 n -> QDiagram b V2 n Any
arrowV' ArrowOpts n
opts = ArrowOpts n -> Point V2 n -> V2 n -> QDiagram b V2 n Any
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> Point V2 n -> V2 n -> QDiagram b V2 n Any
arrowAt' ArrowOpts n
opts Point V2 n
forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin
arrowFromLocatedTrail
:: (Renderable (Path V2 n) b, RealFloat n, Typeable n)
=> Located (Trail V2 n) -> QDiagram b V2 n Any
arrowFromLocatedTrail :: Located (Trail V2 n) -> QDiagram b V2 n Any
arrowFromLocatedTrail = ArrowOpts n -> Located (Trail V2 n) -> QDiagram b V2 n Any
forall n b.
(Renderable (Path V2 n) b, RealFloat n, Typeable n) =>
ArrowOpts n -> Located (Trail V2 n) -> QDiagram b V2 n Any
arrowFromLocatedTrail' ArrowOpts n
forall a. Default a => a
def
arrowFromLocatedTrail'
:: (Renderable (Path V2 n) b, RealFloat n, Typeable n)
=> ArrowOpts n -> Located (Trail V2 n) -> QDiagram b V2 n Any
arrowFromLocatedTrail' :: ArrowOpts n -> Located (Trail V2 n) -> QDiagram b V2 n Any
arrowFromLocatedTrail' ArrowOpts n
opts Located (Trail V2 n)
trail = ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any
arrowBetween' ArrowOpts n
opts' Point V2 n
Codomain (Located (Trail V2 n)) (N (Located (Trail V2 n)))
start Point V2 n
Codomain (Located (Trail V2 n)) (N (Located (Trail V2 n)))
end
where
opts' :: ArrowOpts n
opts' = ArrowOpts n
opts ArrowOpts n -> (ArrowOpts n -> ArrowOpts n) -> ArrowOpts n
forall a b. a -> (a -> b) -> b
& (Trail V2 n -> Identity (Trail V2 n))
-> ArrowOpts n -> Identity (ArrowOpts n)
forall n. Lens' (ArrowOpts n) (Trail V2 n)
arrowShaft ((Trail V2 n -> Identity (Trail V2 n))
-> ArrowOpts n -> Identity (ArrowOpts n))
-> Trail V2 n -> ArrowOpts n -> ArrowOpts n
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Located (Trail V2 n) -> Trail V2 n
forall a. Located a -> a
unLoc Located (Trail V2 n)
trail
start :: Codomain (Located (Trail V2 n)) (N (Located (Trail V2 n)))
start = Located (Trail V2 n)
-> Codomain (Located (Trail V2 n)) (N (Located (Trail V2 n)))
forall p. EndValues p => p -> Codomain p (N p)
atStart Located (Trail V2 n)
trail
end :: Codomain (Located (Trail V2 n)) (N (Located (Trail V2 n)))
end = Located (Trail V2 n)
-> Codomain (Located (Trail V2 n)) (N (Located (Trail V2 n)))
forall p. EndValues p => p -> Codomain p (N p)
atEnd Located (Trail V2 n)
trail
connect
:: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2)
=> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
connect :: n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
connect = ArrowOpts n
-> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
forall n b n1 n2.
(TypeableFloat n, Renderable (Path V2 n) b, IsName n1,
IsName n2) =>
ArrowOpts n
-> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
connect' ArrowOpts n
forall a. Default a => a
def
connect'
:: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2)
=> ArrowOpts n -> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
connect' :: ArrowOpts n
-> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
connect' ArrowOpts n
opts n1
n1 n2
n2 =
n1
-> (Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
forall nm (v :: * -> *) m n b.
(IsName nm, Metric v, Semigroup m, OrderedField n) =>
nm
-> (Subdiagram b v n m -> QDiagram b v n m -> QDiagram b v n m)
-> QDiagram b v n m
-> QDiagram b v n m
withName n1
n1 ((Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> (Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
forall a b. (a -> b) -> a -> b
$ \Subdiagram b V2 n Any
sub1 ->
n2
-> (Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
forall nm (v :: * -> *) m n b.
(IsName nm, Metric v, Semigroup m, OrderedField n) =>
nm
-> (Subdiagram b v n m -> QDiagram b v n m -> QDiagram b v n m)
-> QDiagram b v n m
-> QDiagram b v n m
withName n2
n2 ((Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> (Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
forall a b. (a -> b) -> a -> b
$ \Subdiagram b V2 n Any
sub2 ->
let [Point V2 n
s,Point V2 n
e] = (Subdiagram b V2 n Any -> Point V2 n)
-> [Subdiagram b V2 n Any] -> [Point V2 n]
forall a b. (a -> b) -> [a] -> [b]
map Subdiagram b V2 n Any -> Point V2 n
forall (v :: * -> *) n b m.
(Additive v, Num n) =>
Subdiagram b v n m -> Point v n
location [Subdiagram b V2 n Any
sub1, Subdiagram b V2 n Any
sub2]
in QDiagram b V2 n Any -> QDiagram b V2 n Any -> QDiagram b V2 n Any
forall n (v :: * -> *) m b.
(OrderedField n, Metric v, Semigroup m) =>
QDiagram b v n m -> QDiagram b v n m -> QDiagram b v n m
atop (ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any
arrowBetween' ArrowOpts n
opts Point V2 n
s Point V2 n
e)
connectPerim
:: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2)
=> n1 -> n2 -> Angle n -> Angle n
-> QDiagram b V2 n Any -> QDiagram b V2 n Any
connectPerim :: n1
-> n2
-> Angle n
-> Angle n
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
connectPerim = ArrowOpts n
-> n1
-> n2
-> Angle n
-> Angle n
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
forall n b n1 n2.
(TypeableFloat n, Renderable (Path V2 n) b, IsName n1,
IsName n2) =>
ArrowOpts n
-> n1
-> n2
-> Angle n
-> Angle n
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
connectPerim' ArrowOpts n
forall a. Default a => a
def
connectPerim'
:: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2)
=> ArrowOpts n -> n1 -> n2 -> Angle n -> Angle n
-> QDiagram b V2 n Any -> QDiagram b V2 n Any
connectPerim' :: ArrowOpts n
-> n1
-> n2
-> Angle n
-> Angle n
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
connectPerim' ArrowOpts n
opts n1
n1 n2
n2 Angle n
a1 Angle n
a2 =
n1
-> (Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
forall nm (v :: * -> *) m n b.
(IsName nm, Metric v, Semigroup m, OrderedField n) =>
nm
-> (Subdiagram b v n m -> QDiagram b v n m -> QDiagram b v n m)
-> QDiagram b v n m
-> QDiagram b v n m
withName n1
n1 ((Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> (Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
forall a b. (a -> b) -> a -> b
$ \Subdiagram b V2 n Any
sub1 ->
n2
-> (Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
forall nm (v :: * -> *) m n b.
(IsName nm, Metric v, Semigroup m, OrderedField n) =>
nm
-> (Subdiagram b v n m -> QDiagram b v n m -> QDiagram b v n m)
-> QDiagram b v n m
-> QDiagram b v n m
withName n2
n2 ((Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> (Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
forall a b. (a -> b) -> a -> b
$ \Subdiagram b V2 n Any
sub2 ->
let [Point V2 n
os, Point V2 n
oe] = (Subdiagram b V2 n Any -> Point V2 n)
-> [Subdiagram b V2 n Any] -> [Point V2 n]
forall a b. (a -> b) -> [a] -> [b]
map Subdiagram b V2 n Any -> Point V2 n
forall (v :: * -> *) n b m.
(Additive v, Num n) =>
Subdiagram b v n m -> Point v n
location [Subdiagram b V2 n Any
sub1, Subdiagram b V2 n Any
sub2]
s :: Point V2 n
s = Point V2 n -> Maybe (Point V2 n) -> Point V2 n
forall a. a -> Maybe a -> a
fromMaybe Point V2 n
os (Point (V (Subdiagram b V2 n Any)) n
-> V (Subdiagram b V2 n Any) n
-> Subdiagram b V2 n Any
-> Maybe (Point (V (Subdiagram b V2 n Any)) n)
forall n a.
(n ~ N a, Num n, Traced a) =>
Point (V a) n -> V a n -> a -> Maybe (Point (V a) n)
maxTraceP Point (V (Subdiagram b V2 n Any)) n
Point V2 n
os (V2 n
forall (v :: * -> *) n. (R1 v, Additive v, Num n) => v n
unitX V2 n -> (V2 n -> V2 n) -> V2 n
forall a b. a -> (a -> b) -> b
# Angle n -> V2 n -> V2 n
forall n t.
(InSpace V2 n t, Transformable t, Floating n) =>
Angle n -> t -> t
rotate Angle n
a1) Subdiagram b V2 n Any
sub1)
e :: Point V2 n
e = Point V2 n -> Maybe (Point V2 n) -> Point V2 n
forall a. a -> Maybe a -> a
fromMaybe Point V2 n
oe (Point (V (Subdiagram b V2 n Any)) n
-> V (Subdiagram b V2 n Any) n
-> Subdiagram b V2 n Any
-> Maybe (Point (V (Subdiagram b V2 n Any)) n)
forall n a.
(n ~ N a, Num n, Traced a) =>
Point (V a) n -> V a n -> a -> Maybe (Point (V a) n)
maxTraceP Point (V (Subdiagram b V2 n Any)) n
Point V2 n
oe (V2 n
forall (v :: * -> *) n. (R1 v, Additive v, Num n) => v n
unitX V2 n -> (V2 n -> V2 n) -> V2 n
forall a b. a -> (a -> b) -> b
# Angle n -> V2 n -> V2 n
forall n t.
(InSpace V2 n t, Transformable t, Floating n) =>
Angle n -> t -> t
rotate Angle n
a2) Subdiagram b V2 n Any
sub2)
in QDiagram b V2 n Any -> QDiagram b V2 n Any -> QDiagram b V2 n Any
forall n (v :: * -> *) m b.
(OrderedField n, Metric v, Semigroup m) =>
QDiagram b v n m -> QDiagram b v n m -> QDiagram b v n m
atop (ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any
arrowBetween' ArrowOpts n
opts Point V2 n
s Point V2 n
e)
connectOutside
:: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2)
=> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
connectOutside :: n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
connectOutside = ArrowOpts n
-> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
forall n b n1 n2.
(TypeableFloat n, Renderable (Path V2 n) b, IsName n1,
IsName n2) =>
ArrowOpts n
-> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
connectOutside' ArrowOpts n
forall a. Default a => a
def
connectOutside'
:: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2)
=> ArrowOpts n -> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
connectOutside' :: ArrowOpts n
-> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
connectOutside' ArrowOpts n
opts n1
n1 n2
n2 =
n1
-> (Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
forall nm (v :: * -> *) m n b.
(IsName nm, Metric v, Semigroup m, OrderedField n) =>
nm
-> (Subdiagram b v n m -> QDiagram b v n m -> QDiagram b v n m)
-> QDiagram b v n m
-> QDiagram b v n m
withName n1
n1 ((Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> (Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
forall a b. (a -> b) -> a -> b
$ \Subdiagram b V2 n Any
b1 ->
n2
-> (Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
forall nm (v :: * -> *) m n b.
(IsName nm, Metric v, Semigroup m, OrderedField n) =>
nm
-> (Subdiagram b v n m -> QDiagram b v n m -> QDiagram b v n m)
-> QDiagram b v n m
-> QDiagram b v n m
withName n2
n2 ((Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> (Subdiagram b V2 n Any
-> QDiagram b V2 n Any -> QDiagram b V2 n Any)
-> QDiagram b V2 n Any
-> QDiagram b V2 n Any
forall a b. (a -> b) -> a -> b
$ \Subdiagram b V2 n Any
b2 ->
let v :: Diff (Point V2) n
v = Subdiagram b V2 n Any -> Point V2 n
forall (v :: * -> *) n b m.
(Additive v, Num n) =>
Subdiagram b v n m -> Point v n
location Subdiagram b V2 n Any
b2 Point V2 n -> Point V2 n -> Diff (Point V2) n
forall (p :: * -> *) a. (Affine p, Num a) => p a -> p a -> Diff p a
.-. Subdiagram b V2 n Any -> Point V2 n
forall (v :: * -> *) n b m.
(Additive v, Num n) =>
Subdiagram b v n m -> Point v n
location Subdiagram b V2 n Any
b1
midpoint :: Point V2 n
midpoint = Subdiagram b V2 n Any -> Point V2 n
forall (v :: * -> *) n b m.
(Additive v, Num n) =>
Subdiagram b v n m -> Point v n
location Subdiagram b V2 n Any
b1 Point V2 n -> Diff (Point V2) n -> Point V2 n
forall (p :: * -> *) a. (Affine p, Num a) => p a -> Diff p a -> p a
.+^ (Diff (Point V2) n
V2 n
v V2 n -> n -> V2 n
forall (f :: * -> *) a.
(Functor f, Fractional a) =>
f a -> a -> f a
^/ n
2)
s' :: Point V2 n
s' = Point V2 n -> Maybe (Point V2 n) -> Point V2 n
forall a. a -> Maybe a -> a
fromMaybe (Subdiagram b V2 n Any -> Point V2 n
forall (v :: * -> *) n b m.
(Additive v, Num n) =>
Subdiagram b v n m -> Point v n
location Subdiagram b V2 n Any
b1) (Maybe (Point V2 n) -> Point V2 n)
-> Maybe (Point V2 n) -> Point V2 n
forall a b. (a -> b) -> a -> b
$ Point (V (Subdiagram b V2 n Any)) n
-> V (Subdiagram b V2 n Any) n
-> Subdiagram b V2 n Any
-> Maybe (Point (V (Subdiagram b V2 n Any)) n)
forall n a.
(n ~ N a, Traced a, Num n) =>
Point (V a) n -> V a n -> a -> Maybe (Point (V a) n)
traceP Point (V (Subdiagram b V2 n Any)) n
Point V2 n
midpoint (V2 n -> V2 n
forall (f :: * -> *) a. (Functor f, Num a) => f a -> f a
negated Diff (Point V2) n
V2 n
v) Subdiagram b V2 n Any
b1
e' :: Point V2 n
e' = Point V2 n -> Maybe (Point V2 n) -> Point V2 n
forall a. a -> Maybe a -> a
fromMaybe (Subdiagram b V2 n Any -> Point V2 n
forall (v :: * -> *) n b m.
(Additive v, Num n) =>
Subdiagram b v n m -> Point v n
location Subdiagram b V2 n Any
b2) (Maybe (Point V2 n) -> Point V2 n)
-> Maybe (Point V2 n) -> Point V2 n
forall a b. (a -> b) -> a -> b
$ Point (V (Subdiagram b V2 n Any)) n
-> V (Subdiagram b V2 n Any) n
-> Subdiagram b V2 n Any
-> Maybe (Point (V (Subdiagram b V2 n Any)) n)
forall n a.
(n ~ N a, Traced a, Num n) =>
Point (V a) n -> V a n -> a -> Maybe (Point (V a) n)
traceP Point (V (Subdiagram b V2 n Any)) n
Point V2 n
midpoint V (Subdiagram b V2 n Any) n
Diff (Point V2) n
v Subdiagram b V2 n Any
b2
in
QDiagram b V2 n Any -> QDiagram b V2 n Any -> QDiagram b V2 n Any
forall n (v :: * -> *) m b.
(OrderedField n, Metric v, Semigroup m) =>
QDiagram b v n m -> QDiagram b v n m -> QDiagram b v n m
atop (ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any
forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any
arrowBetween' ArrowOpts n
opts Point V2 n
s' Point V2 n
e')