{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# 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
{ forall n. ArrowOpts n -> ArrowHT n
_arrowHead :: ArrowHT n
, forall n. ArrowOpts n -> ArrowHT n
_arrowTail :: ArrowHT n
, forall n. ArrowOpts n -> Trail V2 n
_arrowShaft :: Trail V2 n
, forall n. ArrowOpts n -> Measure n
_headGap :: Measure n
, forall n. ArrowOpts n -> Measure n
_tailGap :: Measure n
, forall n. ArrowOpts n -> Style V2 n
_headStyle :: Style V2 n
, forall n. ArrowOpts n -> Measure n
_headLength :: Measure n
, forall n. ArrowOpts n -> Style V2 n
_tailStyle :: Style V2 n
, forall n. ArrowOpts n -> Measure n
_tailLength :: Measure n
, forall n. ArrowOpts n -> Style V2 n
_shaftStyle :: Style V2 n
}
straightShaft :: OrderedField n => Trail V2 n
straightShaft :: forall n. OrderedField n => Trail V2 n
straightShaft = forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
[v n] -> Trail v n
trailFromOffsets [forall (v :: * -> *) n. (R1 v, Additive v, Num n) => v n
unitX]
instance TypeableFloat n => Default (ArrowOpts n) where
def :: ArrowOpts n
def = ArrowOpts
{ _arrowHead :: ArrowHT n
_arrowHead = forall n. RealFloat n => ArrowHT n
dart
, _arrowTail :: ArrowHT n
_arrowTail = forall n. ArrowHT n
noTail
, _arrowShaft :: Trail V2 n
_arrowShaft = forall n. OrderedField n => Trail V2 n
straightShaft
, _headGap :: Measure n
_headGap = forall n. OrderedField n => Measure n
none
, _tailGap :: Measure n
_tailGap = forall n. OrderedField n => Measure n
none
, _headStyle :: Style V2 n
_headStyle = forall a. Monoid a => a
mempty
, _headLength :: Measure n
_headLength = forall n. OrderedField n => Measure n
normal
, _tailStyle :: Style V2 n
_tailStyle = forall a. Monoid a => a
mempty
, _tailLength :: Measure n
_tailLength = forall n. OrderedField n => Measure n
normal
, _shaftStyle :: Style V2 n
_shaftStyle = 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 :: forall n. Traversal' (ArrowOpts n) (Measure n)
gaps Measure n -> f (Measure n)
f ArrowOpts n
opts = (\Measure n
h Measure n
t -> ArrowOpts n
opts forall a b. a -> (a -> b) -> b
& forall n. Lens' (ArrowOpts n) (Measure n)
headGap forall s t a b. ASetter s t a b -> b -> s -> t
.~ Measure n
h forall a b. a -> (a -> b) -> b
& forall n. Lens' (ArrowOpts n) (Measure n)
tailGap forall s t a b. ASetter s t a b -> b -> s -> t
.~ Measure n
t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Measure n -> f (Measure n)
f (ArrowOpts n
opts forall s a. s -> Getting a s a -> a
^. forall n. Lens' (ArrowOpts n) (Measure n)
headGap)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Measure n -> f (Measure n)
f (ArrowOpts n
opts forall s a. s -> Getting a s a -> a
^. forall n. Lens' (ArrowOpts n) (Measure n)
tailGap)
gap :: Traversal' (ArrowOpts n) (Measure n)
gap :: forall n. Traversal' (ArrowOpts n) (Measure n)
gap = 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 :: forall n. Traversal' (ArrowOpts n) (Measure n)
lengths Measure n -> f (Measure n)
f ArrowOpts n
opts =
(\Measure n
h Measure n
t -> ArrowOpts n
opts forall a b. a -> (a -> b) -> b
& forall n. Lens' (ArrowOpts n) (Measure n)
headLength forall s t a b. ASetter s t a b -> b -> s -> t
.~ Measure n
h forall a b. a -> (a -> b) -> b
& forall n. Lens' (ArrowOpts n) (Measure n)
tailLength forall s t a b. ASetter s t a b -> b -> s -> t
.~ Measure n
t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Measure n -> f (Measure n)
f (ArrowOpts n
opts forall s a. s -> Getting a s a -> a
^. forall n. Lens' (ArrowOpts n) (Measure n)
headLength)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Measure n -> f (Measure n)
f (ArrowOpts n
opts forall s a. s -> Getting a s a -> a
^. forall n. Lens' (ArrowOpts n) (Measure n)
tailLength)
headTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n)
headTexture :: forall n. TypeableFloat n => Lens' (ArrowOpts n) (Texture n)
headTexture = forall n. Lens' (ArrowOpts n) (Style V2 n)
headStyle forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n.
(Typeable n, Floating n) =>
Lens' (Style V2 n) (Texture n)
_fillTexture
tailTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n)
tailTexture :: forall n. TypeableFloat n => Lens' (ArrowOpts n) (Texture n)
tailTexture = forall n. Lens' (ArrowOpts n) (Style V2 n)
tailStyle forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n.
(Typeable n, Floating n) =>
Lens' (Style V2 n) (Texture n)
_fillTexture
shaftTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n)
shaftTexture :: forall n. TypeableFloat n => Lens' (ArrowOpts n) (Texture n)
shaftTexture = forall n. Lens' (ArrowOpts n) (Style V2 n)
shaftStyle forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n.
(Floating n, Typeable n) =>
Lens' (Style V2 n) (Texture n)
_lineTexture
shaftSty :: ArrowOpts n -> Style V2 n
shaftSty :: forall n. ArrowOpts n -> Style V2 n
shaftSty ArrowOpts n
opts = ArrowOpts n
optsforall s a. s -> Getting a s a -> a
^.forall n. Lens' (ArrowOpts n) (Style V2 n)
shaftStyle
headSty :: TypeableFloat n => ArrowOpts n -> Style V2 n
headSty :: forall n. TypeableFloat n => ArrowOpts n -> Style V2 n
headSty ArrowOpts n
opts = forall n a.
(InSpace V2 n a, Floating n, Typeable n, HasStyle a) =>
Colour Double -> a -> a
fc forall a. Num a => Colour a
black (ArrowOpts n
optsforall s a. s -> Getting a s a -> a
^.forall n. Lens' (ArrowOpts n) (Style V2 n)
headStyle)
tailSty :: TypeableFloat n => ArrowOpts n -> Style V2 n
tailSty :: forall n. TypeableFloat n => ArrowOpts n -> Style V2 n
tailSty ArrowOpts n
opts = forall n a.
(InSpace V2 n a, Floating n, Typeable n, HasStyle a) =>
Colour Double -> a -> a
fc forall a. Num a => Colour a
black (ArrowOpts n
optsforall s a. s -> Getting a s a -> a
^.forall n. Lens' (ArrowOpts n) (Style V2 n)
tailStyle)
xWidth :: Floating n => (Traced t, V t ~ V2, N t ~ n) => t -> n
xWidth :: forall n t. (Floating n, Traced t, V t ~ V2, N t ~ n) => t -> n
xWidth t
p = n
a forall a. Num a => a -> a -> a
+ n
b
where
a :: n
a = forall a. a -> Maybe a -> a
fromMaybe n
0 (forall (f :: * -> *) a. (Metric f, Floating a) => f a -> a
norm forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall n a.
(n ~ N a, Num n, Traced a) =>
Point (V a) n -> V a n -> a -> Maybe (V a n)
traceV forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin forall (v :: * -> *) n. (R1 v, Additive v, Num n) => v n
unitX t
p)
b :: n
b = forall a. a -> Maybe a -> a
fromMaybe n
0 (forall (f :: * -> *) a. (Metric f, Floating a) => f a -> a
norm forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall n a.
(n ~ N a, Num n, Traced a) =>
Point (V a) n -> V a n -> a -> Maybe (V a n)
traceV forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin 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 :: forall n. TypeableFloat n => Style V2 n -> Style V2 n
colorJoint Style V2 n
sStyle =
let c :: Maybe (Texture n)
c = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall n. LineTexture n -> Texture n
getLineTexture forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a (v :: * -> *) n. AttributeClass a => Style v n -> Maybe a
getAttr forall a b. (a -> b) -> a -> b
$ Style V2 n
sStyle
o :: Maybe Double
o = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Opacity -> Double
getOpacity forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a (v :: * -> *) n. AttributeClass a => Style v n -> Maybe a
getAttr 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) -> forall n a c.
(InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) =>
c -> a -> a
fillColor forall a. Num a => Colour a
black forall a. Monoid a => a
mempty
(Just Texture n
t, Maybe Double
Nothing) -> forall n a.
(InSpace V2 n a, Typeable n, Floating n, HasStyle a) =>
Texture n -> a -> a
fillTexture Texture n
t forall a. Monoid a => a
mempty
(Maybe (Texture n)
Nothing, Just Double
o') -> forall a. HasStyle a => Double -> a -> a
opacity Double
o' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n a c.
(InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) =>
c -> a -> a
fillColor forall a. Num a => Colour a
black forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => a
mempty
(Just Texture n
t, Just Double
o') -> forall a. HasStyle a => Double -> a -> a
opacity Double
o' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n a.
(InSpace V2 n a, Typeable n, Floating n, HasStyle a) =>
Texture n -> a -> a
fillTexture Texture n
t forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => a
mempty
widthOfJoint :: forall n. TypeableFloat n => Style V2 n -> n -> n -> n
widthOfJoint :: forall n. TypeableFloat n => Style V2 n -> n -> n -> n
widthOfJoint Style V2 n
sStyle n
gToO n
nToO =
forall a. a -> Maybe a -> a
fromMaybe
(forall n a. Num n => n -> n -> Measured n a -> a
fromMeasured n
gToO n
nToO forall n. OrderedField n => Measure n
medium)
(forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall n. LineWidth n -> n
getLineWidth forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a (v :: * -> *) n. AttributeClass a => Style v n -> Maybe a
getAttr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n (v :: * -> *). Num n => n -> n -> Style v n -> Style v n
unmeasureAttrs n
gToO n
nToO 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 :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
n -> ArrowOpts n -> n -> n -> Bool -> (QDiagram b V2 n Any, n)
mkHead = 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 forall (v :: * -> *) n. (R1 v, Additive v, Num n) => v n
unit_X forall n. Lens' (ArrowOpts n) (ArrowHT n)
arrowHead 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 :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
n -> ArrowOpts n -> n -> n -> Bool -> (QDiagram b V2 n Any, n)
mkTail = 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 forall (v :: * -> *) n. (R1 v, Additive v, Num n) => v n
unitX forall n. Lens' (ArrowOpts n) (ArrowHT n)
arrowTail 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 :: 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
xDir Lens' (ArrowOpts n) (n -> n -> (Path V2 n, Path V2 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 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 forall a. Num a => a -> a -> a
+ n
jWidth
)
where
(Path V2 n
ht', Path V2 n
j') = (ArrowOpts n
optsforall s a. s -> Getting a s a -> a
^.Lens' (ArrowOpts n) (n -> n -> (Path V2 n, Path V2 n))
htProj) n
sz
(forall n. TypeableFloat n => Style V2 n -> n -> n -> n
widthOfJoint (forall n. ArrowOpts n -> Style V2 n
shaftSty ArrowOpts n
opts) n
gToO n
nToO)
htWidth :: n
htWidth = forall n t. (Floating n, Traced t, V t ~ V2, N t ~ n) => t -> n
xWidth Path V2 n
ht'
jWidth :: n
jWidth = 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 = 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' forall a b. a -> (a -> b) -> b
# 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 = 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' forall a b. a -> (a -> b) -> b
# forall a. HasStyle a => Style (V a) (N a) -> a -> a
applyStyle (forall n. TypeableFloat n => Style V2 n -> Style V2 n
colorJoint (ArrowOpts n
optsforall s a. s -> Getting a s a -> a
^.forall n. Lens' (ArrowOpts n) (Style V2 n)
shaftStyle))
spine :: TypeableFloat n => Trail V2 n -> n -> n -> n -> Trail V2 n
spine :: forall n.
TypeableFloat n =>
Trail V2 n -> n -> n -> n -> Trail V2 n
spine Trail V2 n
tr n
tw n
hw n
sz = Trail V2 n
tS forall a. Semigroup a => a -> a -> a
<> Trail V2 n
tr forall a b. a -> (a -> b) -> b
# forall (v :: * -> *) n a.
(InSpace v n a, Eq n, Fractional n, Transformable a) =>
n -> a -> a
scale n
sz forall a. Semigroup a => a -> a -> a
<> Trail V2 n
hS
where
tSpine :: Trail V2 n
tSpine = forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
[v n] -> Trail v n
trailFromOffsets [forall (f :: * -> *) a. (Metric f, Floating a) => f a -> f a
signorm forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. EndValues (Tangent t) => t -> Vn t
tangentAtStart forall a b. (a -> b) -> a -> b
$ Trail V2 n
tr] forall a b. a -> (a -> b) -> b
# 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 = forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
[v n] -> Trail v n
trailFromOffsets [forall (f :: * -> *) a. (Metric f, Floating a) => f a -> f a
signorm forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. EndValues (Tangent t) => t -> Vn t
tangentAtEnd forall a b. (a -> b) -> a -> b
$ Trail V2 n
tr] forall a b. a -> (a -> b) -> b
# 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 forall a. Ord a => a -> a -> Bool
> n
0 then Trail V2 n
hSpine else forall a. Monoid a => a
mempty
tS :: Trail V2 n
tS = if n
tw forall a. Ord a => a -> a -> Bool
> n
0 then Trail V2 n
tSpine else forall a. Monoid a => a
mempty
scaleFactor :: TypeableFloat n => Trail V2 n -> n -> n -> n -> n
scaleFactor :: forall n. TypeableFloat n => Trail V2 n -> n -> n -> n -> n
scaleFactor Trail V2 n
tr n
tw n
hw n
t
= case forall d. (Floating d, Ord d) => d -> d -> d -> [d]
quadForm
(forall (f :: * -> *) a. (Metric f, Num a) => f a -> a
quadrance V2 n
v)
(n
2forall a. Num a => a -> a -> a
* (V2 n
v forall (f :: * -> *) a. (Metric f, Num a) => f a -> f a -> a
`dot` (V2 n
tv forall (f :: * -> *) a. (Additive f, Num a) => f a -> f a -> f a
^+^ V2 n
hv)))
(forall (f :: * -> *) a. (Metric f, Num a) => f a -> a
quadrance (V2 n
tv forall (f :: * -> *) a. (Additive f, Num a) => f a -> f a -> f a
^+^ V2 n
hv) forall a. Num a => a -> a -> a
- n
tforall a. Num a => a -> a -> a
*n
t)
of
[] -> n
1
[n
s] -> n
s
[n]
ss -> forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [n]
ss
where
tv :: V2 n
tv = n
tw forall (f :: * -> *) a. (Functor f, Num a) => a -> f a -> f a
*^ (forall t. EndValues (Tangent t) => t -> Vn t
tangentAtStart Trail V2 n
tr forall a b. a -> (a -> b) -> b
# forall (f :: * -> *) a. (Metric f, Floating a) => f a -> f a
signorm)
hv :: V2 n
hv = n
hw forall (f :: * -> *) a. (Functor f, Num a) => a -> f a -> f a
*^ (forall t. EndValues (Tangent t) => t -> Vn t
tangentAtEnd Trail V2 n
tr forall a b. a -> (a -> b) -> b
# forall (f :: * -> *) a. (Metric f, Floating a) => f a -> f a
signorm)
v :: V2 n
v = 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 :: forall n. TypeableFloat n => ArrowOpts n -> n -> Envelope V2 n
arrowEnv ArrowOpts n
opts n
len = 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 forall a b. a -> (a -> b) -> b
# forall n t.
(InSpace V2 n t, Transformable t, Floating n) =>
Angle n -> t -> t
rotate (forall (f :: * -> *) a. (Functor f, Num a) => f a -> f a
negated (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 a b. a -> (a -> b) -> b
# forall (v :: * -> *) n a.
(InSpace v n a, Eq n, Fractional n, Transformable a) =>
n -> a -> a
scale (n
len forall a. Fractional a => a -> a -> a
/ n
m)
m :: n
m = forall (f :: * -> *) a. (Metric f, Floating a) => f a -> a
norm V2 n
v
v :: V2 n
v = 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 forall s a. s -> Getting a s a -> a
^. forall n. Lens' (ArrowOpts n) (Trail V2 n)
arrowShaft
arrow :: (TypeableFloat n, Renderable (Path V2 n) b) => n -> QDiagram b V2 n Any
arrow :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
n -> QDiagram b V2 n Any
arrow = forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> n -> QDiagram b V2 n Any
arrow' forall a. Default a => a
def
arrow' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> n -> QDiagram b V2 n Any
arrow' :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> n -> QDiagram b V2 n Any
arrow' ArrowOpts n
opts n
len = 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' (forall b (v :: * -> *) n m.
(DownAnnots v n -> n -> n -> QDiagram b v n m) -> QDiaLeaf b v n m
DelayedLeaf (Maybe (Transformation V2 n :+: Style V2 n), Name ::: ())
-> n -> n -> QDiagram b V2 n Any
delayedArrow)
(forall n. TypeableFloat n => ArrowOpts n -> n -> Envelope V2 n
arrowEnv ArrowOpts n
opts n
len) forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty
where
delayedArrow :: (Maybe (Transformation V2 n :+: Style V2 n), Name ::: ())
-> n -> n -> QDiagram b V2 n Any
delayedArrow (Maybe (Transformation V2 n :+: Style V2 n), Name ::: ())
da n
g n
n =
let (Transformation V2 n
trans, Style V2 n
globalSty) = forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Monoid a => a
mempty forall m n. (Action m n, Monoid m, Monoid n) => (m :+: n) -> (m, n)
untangle forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall a b. (a -> b) -> a -> b
$ (Maybe (Transformation V2 n :+: Style V2 n), Name ::: ())
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' forall a. Semigroup a => a -> a -> a
<> QDiagram b V2 n Any
t' 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 = forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin forall a b. a -> (a -> b) -> b
# forall t. Transformable t => Transformation (V t) (N t) -> t -> t
transform Transformation V2 n
tr
q :: Point V2 n
q = forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin forall a b. a -> (a -> b) -> b
# forall (v :: * -> *) n t.
(InSpace v n t, R1 v, Transformable t) =>
n -> t -> t
translateX n
ln forall a b. a -> (a -> b) -> b
# forall t. Transformable t => Transformation (V t) (N t) -> t -> t
transform Transformation V2 n
tr
globalLC :: Maybe (Texture n)
globalLC = forall n. LineTexture n -> Texture n
getLineTexture forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a (v :: * -> *) n. AttributeClass a => Style v n -> Maybe a
getAttr Style V2 n
sty
opts' :: ArrowOpts n
opts' = ArrowOpts n
opts
forall a b. a -> (a -> b) -> b
& forall n. Lens' (ArrowOpts n) (Style V2 n)
headStyle forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id forall n a.
(InSpace V2 n a, Typeable n, Floating n, HasStyle a) =>
Texture n -> a -> a
fillTexture Maybe (Texture n)
globalLC
forall a b. a -> (a -> b) -> b
& forall n. Lens' (ArrowOpts n) (Style V2 n)
tailStyle forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id forall n a.
(InSpace V2 n a, Typeable n, Floating n, HasStyle a) =>
Texture n -> a -> a
fillTexture Maybe (Texture n)
globalLC
forall a b. a -> (a -> b) -> b
& forall n. Lens' (ArrowOpts n) (Style V2 n)
shaftStyle forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ forall a. HasStyle a => Style (V a) (N a) -> a -> a
applyStyle Style V2 n
sty forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Transformable t => Transformation (V t) (N t) -> t -> t
transform Transformation V2 n
tr
scaleFromMeasure :: Measured n n -> n
scaleFromMeasure = forall n a. Num n => n -> n -> Measured n a -> a
fromMeasured n
gToO n
nToO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n a. Num n => n -> Measured n a -> Measured n a
scaleLocal (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 forall a b. (a -> b) -> a -> b
$ ArrowOpts n
opts forall s a. s -> Getting a s a -> a
^. forall n. Lens' (ArrowOpts n) (Measure n)
headLength
tSize :: n
tSize = Measured n n -> n
scaleFromMeasure forall a b. (a -> b) -> a -> b
$ ArrowOpts n
opts forall s a. s -> Getting a s a -> a
^. forall n. Lens' (ArrowOpts n) (Measure n)
tailLength
hGap :: n
hGap = Measured n n -> n
scaleFromMeasure forall a b. (a -> b) -> a -> b
$ ArrowOpts n
opts forall s a. s -> Getting a s a -> a
^. forall n. Lens' (ArrowOpts n) (Measure n)
headGap
tGap :: n
tGap = Measured n n -> n
scaleFromMeasure forall a b. (a -> b) -> a -> b
$ ArrowOpts n
opts forall s a. s -> Getting a s a -> a
^. forall n. Lens' (ArrowOpts n) (Measure n)
tailGap
(QDiagram b V2 n Any
h, n
hWidth') = 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 (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') = 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 (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
optsforall s a. s -> Getting a s a -> a
^.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' forall a. Num a => a -> a -> a
+ n
tGap
hWidth :: n
hWidth = n
hWidth' forall a. Num a => a -> a -> a
+ n
hGap
tAngle :: Angle n
tAngle = forall t. EndValues (Tangent t) => t -> Vn t
tangentAtStart Trail V2 n
shaftTrail forall s a. s -> Getting a s a -> a
^. forall (t :: * -> *) n.
(HasTheta t, RealFloat n) =>
Lens' (t n) (Angle n)
_theta
hAngle :: Angle n
hAngle = forall t. EndValues (Tangent t) => t -> Vn t
tangentAtEnd Trail V2 n
shaftTrail forall s a. s -> Getting a s a -> a
^. forall (t :: * -> *) n.
(HasTheta t, RealFloat n) =>
Lens' (t n) (Angle n)
_theta
sf :: n
sf = forall n. TypeableFloat n => Trail V2 n -> n -> n -> n -> n
scaleFactor Trail V2 n
shaftTrail n
tWidth n
hWidth (forall (f :: * -> *) a. (Metric f, Floating a) => f a -> a
norm (Point V2 n
q 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 forall a b. a -> (a -> b) -> b
# 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 = forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Trail V2 n -> QDiagram b V2 n Any
strokeT Trail V2 n
shaftTrail' forall a b. a -> (a -> b) -> b
# forall a. HasStyle a => Style (V a) (N a) -> a -> a
applyStyle (forall n. ArrowOpts n -> Style V2 n
shaftSty ArrowOpts n
opts')
h' :: QDiagram b V2 n Any
h' = QDiagram b V2 n Any
h forall a b. a -> (a -> b) -> b
# 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 forall a b. a -> (a -> b) -> b
# forall n t.
(InSpace V2 n t, Transformable t, Floating n) =>
Angle n -> t -> t
rotate Angle n
tAngle
dir :: Direction V2 n
dir = forall (v :: * -> *) n. v n -> Direction v n
direction (forall (v :: * -> *) n.
(Metric v, OrderedField n) =>
Trail v n -> v n
trailOffset forall a b. (a -> b) -> a -> b
$ 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 :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Point V2 n -> Point V2 n -> QDiagram b V2 n Any
arrowBetween = forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any
arrowBetween' 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' :: 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 = 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 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 :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
Point V2 n -> V2 n -> QDiagram b V2 n Any
arrowAt = forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> Point V2 n -> V2 n -> QDiagram b V2 n Any
arrowAt' 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' :: 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 V2 n
v = 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 = forall (f :: * -> *) a. (Metric f, Floating a) => f a -> a
norm V2 n
v
dir :: Angle n
dir = 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
arrowV :: (TypeableFloat n, Renderable (Path V2 n) b) => V2 n -> QDiagram b V2 n Any
arrowV :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
V2 n -> QDiagram b V2 n Any
arrowV = forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> V2 n -> QDiagram b V2 n Any
arrowV' forall a. Default a => a
def
arrowV'
:: (TypeableFloat n, Renderable (Path V2 n) b)
=> ArrowOpts n -> V2 n -> QDiagram b V2 n Any
arrowV' :: forall n b.
(TypeableFloat n, Renderable (Path V2 n) b) =>
ArrowOpts n -> V2 n -> QDiagram b V2 n Any
arrowV' ArrowOpts n
opts = 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 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 :: forall n b.
(Renderable (Path V2 n) b, RealFloat n, Typeable n) =>
Located (Trail V2 n) -> QDiagram b V2 n Any
arrowFromLocatedTrail = forall n b.
(Renderable (Path V2 n) b, RealFloat n, Typeable n) =>
ArrowOpts n -> Located (Trail V2 n) -> QDiagram b V2 n Any
arrowFromLocatedTrail' 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' :: 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
opts Located (Trail V2 n)
trail = 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' Codomain (Located (Trail V2 n)) (N (Located (Trail V2 n)))
start Codomain (Located (Trail V2 n)) (N (Located (Trail V2 n)))
end
where
opts' :: ArrowOpts n
opts' = ArrowOpts n
opts forall a b. a -> (a -> b) -> b
& forall n. Lens' (ArrowOpts n) (Trail V2 n)
arrowShaft forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. Located a -> a
unLoc Located (Trail V2 n)
trail
start :: Codomain (Located (Trail V2 n)) (N (Located (Trail V2 n)))
start = 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 = 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 :: forall n b n1 n2.
(TypeableFloat n, Renderable (Path V2 n) b, IsName n1,
IsName n2) =>
n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
connect = 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' 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' :: 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
opts n1
n1 n2
n2 =
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 forall a b. (a -> b) -> a -> b
$ \Subdiagram b V2 n Any
sub1 ->
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 forall a b. (a -> b) -> a -> b
$ \Subdiagram b V2 n Any
sub2 ->
let [Point V2 n
s,Point V2 n
e] = forall a b. (a -> b) -> [a] -> [b]
map 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 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 (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 :: forall n b n1 n2.
(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 = 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' 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' :: 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
opts n1
n1 n2
n2 Angle n
a1 Angle n
a2 =
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 forall a b. (a -> b) -> a -> b
$ \Subdiagram b V2 n Any
sub1 ->
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 forall a b. (a -> b) -> a -> b
$ \Subdiagram b V2 n Any
sub2 ->
let [Point V2 n
os, Point V2 n
oe] = forall a b. (a -> b) -> [a] -> [b]
map 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 = forall a. a -> Maybe a -> a
fromMaybe Point V2 n
os (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 V2 n
os (forall (v :: * -> *) n. (R1 v, Additive v, Num n) => v n
unitX forall a b. a -> (a -> b) -> b
# 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 = forall a. a -> Maybe a -> a
fromMaybe Point V2 n
oe (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 V2 n
oe (forall (v :: * -> *) n. (R1 v, Additive v, Num n) => v n
unitX forall a b. a -> (a -> b) -> b
# 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 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 (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 :: forall n b n1 n2.
(TypeableFloat n, Renderable (Path V2 n) b, IsName n1,
IsName n2) =>
n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
connectOutside = 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' 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' :: 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
opts n1
n1 n2
n2 =
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 forall a b. (a -> b) -> a -> b
$ \Subdiagram b V2 n Any
b1 ->
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 forall a b. (a -> b) -> a -> b
$ \Subdiagram b V2 n Any
b2 ->
let v :: Diff (Point V2) n
v = forall (v :: * -> *) n b m.
(Additive v, Num n) =>
Subdiagram b v n m -> Point v n
location Subdiagram b V2 n Any
b2 forall (p :: * -> *) a. (Affine p, Num a) => p a -> p a -> Diff p a
.-. 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 = forall (v :: * -> *) n b m.
(Additive v, Num n) =>
Subdiagram b v n m -> Point v n
location Subdiagram b V2 n Any
b1 forall (p :: * -> *) a. (Affine p, Num a) => p a -> Diff p a -> p a
.+^ (Diff (Point V2) n
v forall (f :: * -> *) a.
(Functor f, Fractional a) =>
f a -> a -> f a
^/ n
2)
s' :: Point V2 n
s' = forall a. a -> Maybe a -> a
fromMaybe (forall (v :: * -> *) n b m.
(Additive v, Num n) =>
Subdiagram b v n m -> Point v n
location Subdiagram b V2 n Any
b1) forall a b. (a -> b) -> a -> b
$ 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 V2 n
midpoint (forall (f :: * -> *) a. (Functor f, Num a) => f a -> f a
negated Diff (Point V2) n
v) Subdiagram b V2 n Any
b1
e' :: Point V2 n
e' = forall a. a -> Maybe a -> a
fromMaybe (forall (v :: * -> *) n b m.
(Additive v, Num n) =>
Subdiagram b v n m -> Point v n
location Subdiagram b V2 n Any
b2) forall a b. (a -> b) -> a -> b
$ 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 V2 n
midpoint Diff (Point V2) n
v Subdiagram b V2 n Any
b2
in
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 (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')