{-# LANGUAGE ConstraintKinds            #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE FlexibleContexts           #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE RankNTypes                 #-}
{-# LANGUAGE ScopedTypeVariables        #-}
{-# LANGUAGE TemplateHaskell            #-}
{-# LANGUAGE TypeFamilies               #-}
{-# LANGUAGE UndecidableInstances       #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Diagrams.TwoD.Arrow
-- Copyright   :  (c) 2013-2015 diagrams-lib team (see LICENSE)
-- License     :  BSD-style (see LICENSE)
-- Maintainer  :  diagrams-discuss@googlegroups.com
--
-- Drawing arrows in two dimensions.  For a tutorial on drawing arrows
-- using this module, see the diagrams website:
-- <https://diagrams.github.io/doc/arrow.html>.
--
-----------------------------------------------------------------------------


module Diagrams.TwoD.Arrow
       ( -- * Examples
         -- ** Example 1
-- | <<diagrams/src_Diagrams_TwoD_Arrow_example1.svg#diagram=example1&width=500>>
--
--   > -- Connecting two diagrams at their origins.
--   >
--   > sq = square 2 # showOrigin # lc darkgray # lw ultraThick
--   > ds = (sq # named "left") ||| strutX 3 ||| (sq # named "right")
--   >
--   > shaft  = cubicSpline False ( map p2 [(0, 0), (1, 0), (1, 0.2), (2, 0.2)])
--   >
--   > example1 = ds # connect' (with & arrowHead .~ dart & arrowTail .~ quill
--   >                                & arrowShaft .~ shaft
--   >                                & headLength .~ huge & tailLength .~ veryLarge)
--   >                                "left" "right" # pad 1.1

         -- ** Example 2

-- | <<diagrams/src_Diagrams_TwoD_Arrow_example2.svg#diagram=example2&width=500>>
--
--   > -- Comparing connect, connectPerim, and arrowAt.
--   >
--   > oct  = octagon 1 # lc darkgray # lw ultraThick # showOrigin
--   > dias = oct # named "first" ||| strut 3 ||| oct # named "second"
--   >
--   > -- Connect two diagrams and two points on their trails.
--   > ex12 = dias # connect' (with & lengths .~ veryLarge) "first" "second"
--   >             # connectPerim' (with & lengths .~ veryLarge)
--   >        "first" "second" (15/16 @@ turn) (9/16 @@ turn)
--   >
--   > -- Place an arrow at (0,0) the size and direction of (0,1).
--   > ex3 = arrowAt origin unit_Y
--   >
--   > example2 = (ex12 <> ex3) # centerXY # pad 1.1

         -- * Creating arrows
         arrowV
       , arrowV'
       , arrowAt
       , arrowAt'
       , arrowBetween
       , arrowBetween'
       , connect
       , connect'
       , connectPerim
       , connectPerim'
       , connectOutside
       , connectOutside'

       , arrow
       , arrow'

       , arrowFromLocatedTrail
       , arrowFromLocatedTrail'

         -- * Options
       , ArrowOpts(..)

       , arrowHead
       , arrowTail
       , arrowShaft
       , headGap
       , tailGap
       , gaps, gap
       , headTexture
       , headStyle
       , headLength
       , tailTexture
       , tailStyle
       , tailLength
       , lengths
       , shaftTexture
       , shaftStyle
       , straightShaft

         -- | See "Diagrams.TwoD.Arrowheads" for a list of standard
         --   arrowheads and help creating your own.
       , 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
    }

-- | Straight line arrow shaft.
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

        -- See note [Default arrow style attributes]
        , _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

-- | A shape to place at the head of the arrow.
arrowHead :: Lens' (ArrowOpts n) (ArrowHT n)

-- | A shape to place at the tail of the arrow.
arrowTail :: Lens' (ArrowOpts n) (ArrowHT n)

-- | The trail to use for the arrow shaft.
arrowShaft :: Lens' (ArrowOpts n) (Trail V2 n)

-- | Distance to leave between the head and the target point.
headGap :: Lens' (ArrowOpts n) (Measure n)

-- | Distance to leave between the starting point and the tail.
tailGap :: Lens' (ArrowOpts n) (Measure n)

-- | Set both the @headGap@ and @tailGap@ simultaneously.
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)

-- | Same as gaps, provided for backward compatiiblity.
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

-- | Style to apply to the head. @headStyle@ is modified by using the lens
--   combinator @%~@ to change the current style. For example, to change
--   an opaque black arrowhead to translucent orange:
--   @(with & headStyle %~ fc orange .  opacity 0.75)@.
headStyle :: Lens' (ArrowOpts n) (Style V2 n)

-- | Style to apply to the tail. See `headStyle`.
tailStyle :: Lens' (ArrowOpts n) (Style V2 n)

-- | Style to apply to the shaft. See `headStyle`.
shaftStyle :: Lens' (ArrowOpts n) (Style V2 n)

-- | The length from the start of the joint to the tip of the head.
headLength :: Lens' (ArrowOpts n) (Measure n)

-- | The length of the tail plus its joint.
tailLength :: Lens' (ArrowOpts n) (Measure n)

-- | Set both the @headLength@ and @tailLength@ simultaneously.
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)

-- | A lens for setting or modifying the texture of an arrowhead. For
--   example, one may write @... (with & headTexture .~ grad)@ to get an
--   arrow with a head filled with a gradient, assuming grad has been
--   defined. Or @... (with & headTexture .~ solid blue@ to set the head
--   color to blue. For more general control over the style of arrowheads,
--   see 'headStyle'.
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

-- | A lens for setting or modifying the texture of an arrow
--   tail. This is *not* a valid lens (see 'committed').
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

-- | A lens for setting or modifying the texture of an arrow
--   shaft.
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

-- Set the default shaft style of an `ArrowOpts` record by applying the
-- default style after all other styles have been applied.
-- The semigroup stucture of the lw attribute will insure that the default
-- is only used if it has not been set in @opts@.
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

-- Set the default head style. See `shaftSty`.
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)

-- Set the default tail style. See `shaftSty`.
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)

-- | Calculate the length of the portion of the horizontal line that passes
--   through the origin and is inside of p.
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)

-- | Get the line color from the shaft to use as the fill color for the joint.
--   And set the opacity of the shaft to the current opacity.
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

-- | Get line width from a style.
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) -- should be same as default line width
    ((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)

-- | Combine the head and its joint into a single scale invariant diagram
--   and move the origin to the attachment point. Return the diagram
--   and its width.
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 tr tw hw sz@ makes a trail with the same angles and offset
--   as an arrow with tail width @t@w, head width @hw@ and shaft @tr@,
--   such that the magnitude of the shaft offset is @sz@. Used for
--   calculating the offset of an arrow.
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 tr tw hw t@ calculates the amount required to scale
--   a shaft trail @tr@ so that an arrow with head width @hw@ and tail
--   width @tw@ has offset @t@.
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

  -- Let tv be a vector representing the tail width, i.e. a vector
  -- of length tw tangent to the trail's start; similarly for hv.
  -- Let v be the vector offset of the trail.
  --
  -- Then we want to find k such that
  --
  --   || tv + k*v + hv || = t.
  --
  -- We can solve by squaring both sides and expanding the LHS as a
  -- dot product, resulting in a quadratic in k.

  = 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   -- no scale works, just return 1
      [n
s] -> n
s   -- single solution
      [n]
ss  -> [n] -> n
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [n]
ss
        -- we will usually get both a positive and a negative solution;
        -- return the maximum (i.e. positive) solution
  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

-- Calculate the approximate envelope of a horizontal arrow
-- as if the arrow were made only of a shaft.
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 len@ creates an arrow of length @len@ with default
--   parameters, starting at the origin and ending at the point
--   @(len,0)@.
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' opts len@ creates an arrow of length @len@ using the
--   given options, starting at the origin and ending at the point
--   @(len,0)@.  In particular, it scales the given 'arrowShaft' so
--   that the entire arrow has length @len@.
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)

      -- Currently we approximate the envelope of an arrow by using the
      -- envelope of its shaft (see 'arrowEnv'). The trace of an arrow is empty.
      (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

    -- Once we learn the global transformation context (da) and the two scale
    -- factors, normal to output (n) and global to output (g), this arrow is
    -- drawn in, we can apply it to the origin and (len,0) to find out
    -- the actual final points between which this arrow should be
    -- drawn.  We need to know this to draw it correctly, since the
    -- head and tail are scale invariant, and hence the precise points
    -- between which we need to draw the shaft do not transform
    -- uniformly as the transformation applied to the entire arrow.
    -- See https://github.com/diagrams/diagrams-lib/issues/112.
    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

    -- Build an arrow and set its endpoints to the image under tr of origin and (len,0).
    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

        -- Use the existing line color for head, tail, and shaft by
        -- default (can be overridden by explicitly setting headStyle,
        -- tailStyle, or shaftStyle).  Also use existing global line width
        -- for shaft if not explicitly set in shaftStyle.
        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

        -- The head size, tail size, head gap, and tail gap are obtained
        -- from the style and converted to output units.
        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

        -- Make the head and tail and save their widths.
        (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 it so it is pointing in the positive X direction
          # rotate (negated . view _theta . trailOffset $ rawShaftTrail)
            -- apply the context transformation -- in case it includes
            -- things like flips and shears (the possibility of shears
            -- is why we must rotate it to a neutral position first)
          # transform tr

        -- Adjust the head width and tail width to take gaps into account
        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

        -- Calculate the angles that the head and tail should point.
        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

        -- Calculte the scaling factor to apply to the shaft shaftTrail so that the entire
        -- arrow will be of length len. Then apply it to the shaft and make the
        -- shaft into a Diagram with using its style.
        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')

        -- Adjust the head and tail to point in the directions of the shaft ends.
        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

        -- Find out what direction the arrow is pointing so we can set it back
        -- to point in the direction unitX when we are done.
        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 s e@ creates an arrow pointing from @s@ to @e@
--   with default parameters.
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' opts s e@ creates an arrow pointing from @s@ to
--   @e@ using the given options.  In particular, it scales and
--   rotates @arrowShaft@ to go between @s@ and @e@, taking head,
--   tail, and gaps into account.
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)

-- | Create an arrow starting at s with length and direction determined by
--   the vector v.
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 v@ creates an arrow with the direction and norm of
--   the vector @v@ (with its tail at the origin), using default
--   parameters.
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' v@ creates an arrow with the direction and norm of
--   the vector @v@ (with its tail at the origin).
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

-- | Turn a located trail into a default arrow by putting an
--   arrowhead at the end of the trail.
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

-- | Turn a located trail into an arrow using the given options.
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 two diagrams with a straight arrow.
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 two diagrams with an arbitrary arrow.
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)

-- | Connect two diagrams at point on the perimeter of the diagrams, choosen
--   by angle.
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)

-- | Draw an arrow from diagram named "n1" to diagram named "n2".  The
--   arrow lies on the line between the centres of the diagrams, but is
--   drawn so that it stops at the boundaries of the diagrams, using traces
--   to find the intersection points.
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')