module Diagrams.TwoD.Arrow
(
arrowV
, arrowV'
, arrowAt
, arrowAt'
, arrowBetween
, arrowBetween'
, connect
, connect'
, connectPerim
, connectPerim'
, connectOutside
, connectOutside'
, arrow
, arrow'
, 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.Applicative ((<*>))
import Control.Lens (Lens', Setter', Traversal',
generateSignatures, lensRules,
makeLensesWith, (%~), (&), (.~),
(^.))
import Data.AffineSpace
import Data.Default.Class
import Data.Functor ((<$>))
import Data.Maybe (fromMaybe)
import Data.Monoid.Coproduct (untangle)
import Data.Semigroup
import Data.VectorSpace
import Data.Colour hiding (atop)
import Diagrams.Core
import Diagrams.Core.Types (QDiaLeaf (..), mkQD')
import Diagrams.Angle
import Diagrams.Attributes
import Diagrams.Parametric
import Diagrams.Path
import Diagrams.Solve (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 (rotate, translateX)
import Diagrams.TwoD.Types
import Diagrams.TwoD.Vector (direction, unitX, unit_X)
import Diagrams.Util (( # ))
data ArrowOpts
= ArrowOpts
{ _arrowHead :: ArrowHT
, _arrowTail :: ArrowHT
, _arrowShaft :: Trail R2
, _headGap :: Measure R2
, _tailGap :: Measure R2
, _headStyle :: Style R2
, _headLength :: Measure R2
, _tailStyle :: Style R2
, _tailLength :: Measure R2
, _shaftStyle :: Style R2
}
straightShaft :: Trail R2
straightShaft = trailFromOffsets [unitX]
instance Default ArrowOpts where
def = ArrowOpts
{ _arrowHead = dart
, _arrowTail = noTail
, _arrowShaft = straightShaft
, _headGap = none
, _tailGap = none
, _headStyle = mempty
, _headLength = normal
, _tailStyle = mempty
, _tailLength = normal
, _shaftStyle = mempty
}
makeLensesWith (lensRules & generateSignatures .~ False) ''ArrowOpts
arrowHead :: Lens' ArrowOpts ArrowHT
arrowTail :: Lens' ArrowOpts ArrowHT
arrowShaft :: Lens' ArrowOpts (Trail R2)
headGap :: Lens' ArrowOpts (Measure R2)
tailGap :: Lens' ArrowOpts (Measure R2)
gaps :: Traversal' ArrowOpts (Measure R2)
gaps f opts = (\h t -> opts & headGap .~ h & tailGap .~ t)
<$> f (opts ^. headGap)
<*> f (opts ^. tailGap)
gap :: Traversal' ArrowOpts (Measure R2)
gap = gaps
headStyle :: Lens' ArrowOpts (Style R2)
tailStyle :: Lens' ArrowOpts (Style R2)
shaftStyle :: Lens' ArrowOpts (Style R2)
headLength :: Lens' ArrowOpts (Measure R2)
tailLength :: Lens' ArrowOpts (Measure R2)
lengths :: Traversal' ArrowOpts (Measure R2)
lengths f opts = (\h t -> opts & headLength .~ h & tailLength .~ t) <$> f (opts ^. headLength)
<*> f (opts ^. tailLength)
headTexture :: Setter' ArrowOpts Texture
headTexture = headStyle . styleFillTexture
tailTexture :: Setter' ArrowOpts Texture
tailTexture = tailStyle . styleFillTexture
shaftTexture :: Setter' ArrowOpts Texture
shaftTexture = shaftStyle . styleLineTexture
shaftSty :: ArrowOpts -> Style R2
shaftSty opts = opts^.shaftStyle
headSty :: ArrowOpts -> Style R2
headSty opts = fc black (opts^.headStyle)
tailSty :: ArrowOpts -> Style R2
tailSty opts = fc black (opts^.tailStyle)
fromMeasure :: Double -> Double -> Measure R2 -> Double
fromMeasure g n m = u
where Output u = toOutput g n m
xWidth :: (Traced t, V t ~ R2) => t -> Double
xWidth p = a + b
where
a = fromMaybe 0 (magnitude <$> traceV origin unitX p)
b = fromMaybe 0 (magnitude <$> traceV origin unit_X p)
colorJoint :: Style R2 -> Style R2
colorJoint sStyle =
let c = fmap getLineTexture . getAttr $ sStyle
o = fmap getOpacity . getAttr $ sStyle
in
case (c, o) of
(Nothing, Nothing) -> fillColor (black :: Colour Double) $ mempty
(Just t, Nothing) -> fillTexture t $ mempty
(Nothing, Just o') -> opacity o' . fillColor (black :: Colour Double) $ mempty
(Just t, Just o') -> opacity o' . fillTexture t $ mempty
widthOfJoint :: Style v -> Double -> Double -> Double
widthOfJoint sStyle gToO nToO =
maybe (fromMeasure gToO nToO (Output 1))
(fromMeasure gToO nToO)
(fmap getLineWidth . getAttr $ sStyle)
mkHead :: Renderable (Path R2) b =>
Double -> ArrowOpts -> Double -> Double -> (Diagram b R2, Double)
mkHead size opts gToO nToO = ((j <> h) # moveOriginBy (jWidth *^ unit_X) # lwO 0
, hWidth + jWidth)
where
(h', j') = (opts^.arrowHead) size
(widthOfJoint (shaftSty opts) gToO nToO)
hWidth = xWidth h'
jWidth = xWidth j'
h = stroke h' # applyStyle (headSty opts)
j = stroke j' # applyStyle (colorJoint (opts^.shaftStyle))
mkTail :: Renderable (Path R2) b =>
Double -> ArrowOpts -> Double -> Double -> (Diagram b R2, Double)
mkTail size opts gToO nToO = ((t <> j) # moveOriginBy (jWidth *^ unitX) # lwO 0
, tWidth + jWidth)
where
(t', j') = (opts^.arrowTail) size
(widthOfJoint (shaftSty opts) gToO nToO)
tWidth = xWidth t'
jWidth = xWidth j'
t = stroke t' # applyStyle (tailSty opts)
j = stroke j' # applyStyle (colorJoint (opts^.shaftStyle))
spine :: Trail R2 -> Double -> Double -> Double -> Trail R2
spine tr tw hw size = tS <> tr # scale size <> hS
where
tSpine = trailFromOffsets [(normalized . tangentAtStart) $ tr] # scale tw
hSpine = trailFromOffsets [(normalized . tangentAtEnd) $ tr] # scale hw
hS = if hw > 0 then hSpine else mempty
tS = if tw > 0 then tSpine else mempty
scaleFactor :: Trail R2 -> Double -> Double -> Double -> Double
scaleFactor tr tw hw t
= case quadForm
(magnitudeSq v)
(2* (v <.> (tv ^+^ hv)))
(magnitudeSq (tv ^+^ hv) t*t)
of
[] -> 1
[s] -> s
ss -> maximum ss
where
tv = tw *^ (tangentAtStart tr # normalized)
hv = hw *^ (tangentAtEnd tr # normalized)
v = trailOffset tr
arrowEnv :: ArrowOpts -> Double -> Envelope R2
arrowEnv opts len = getEnvelope horizShaft
where
horizShaft = shaft # rotate (negateV direction v) # scale (len / m)
m = magnitude v
v = trailOffset shaft
shaft = opts ^. arrowShaft
arrow :: Renderable (Path R2) b => Double -> Diagram b R2
arrow len = arrow' def len
arrow' :: Renderable (Path R2) b => ArrowOpts -> Double -> Diagram b R2
arrow' opts len = mkQD' (DelayedLeaf delayedArrow)
(arrowEnv opts len) mempty mempty mempty
where
delayedArrow da g n =
let (trans, globalSty) = option mempty untangle . fst $ da
in dArrow globalSty trans len g n
dArrow sty tr ln gToO nToO = (h' <> t' <> shaft)
# moveOriginBy (tWidth *^ (unit_X # rotate tAngle))
# rotate (direction (q .-. p) ^-^ dir)
# moveTo p
where
p = origin # transform tr
q = origin # translateX ln # transform tr
globalLC = getLineTexture <$> getAttr sty
opts' = opts
& headStyle %~ maybe id fillTexture globalLC
& tailStyle %~ maybe id fillTexture globalLC
& shaftStyle %~ maybe id lineTexture globalLC
hSize = fromMeasure gToO nToO . transform tr $ opts ^. headLength
tSize = fromMeasure gToO nToO . transform tr $ opts ^. tailLength
hGap = fromMeasure gToO nToO . transform tr $ opts ^. headGap
tGap = fromMeasure gToO nToO . transform tr $ opts ^. tailGap
(h, hWidth') = mkHead hSize opts' gToO nToO
(t, tWidth') = mkTail tSize opts' gToO nToO
rawShaftTrail = opts^.arrowShaft
shaftTrail
= rawShaftTrail
# rotate (negateV direction (trailOffset rawShaftTrail))
# transform tr
tWidth = tWidth' + tGap
hWidth = hWidth' + hGap
tAngle = direction . tangentAtStart $ shaftTrail
hAngle = direction . tangentAtEnd $ shaftTrail
sf = scaleFactor shaftTrail tWidth hWidth (magnitude (q .-. p))
shaftTrail' = shaftTrail # scale sf
shaft = strokeT shaftTrail' # applyStyle (shaftSty opts)
h' = h # rotate hAngle
# moveTo (origin .+^ shaftTrail' `atParam` domainUpper shaftTrail')
t' = t # rotate tAngle
dir = direction (trailOffset $ spine shaftTrail tWidth hWidth sf)
arrowBetween :: Renderable (Path R2) b => P2 -> P2 -> Diagram b R2
arrowBetween = arrowBetween' def
arrowBetween'
:: Renderable (Path R2) b =>
ArrowOpts -> P2 -> P2 -> Diagram b R2
arrowBetween' opts s e = arrowAt' opts s (e .-. s)
arrowAt :: Renderable (Path R2) b => P2 -> R2 -> Diagram b R2
arrowAt s v = arrowAt' def s v
arrowAt'
:: Renderable (Path R2) b =>
ArrowOpts -> P2 -> R2 -> Diagram b R2
arrowAt' opts s v = arrow' opts len
# rotate dir # moveTo s
where
len = magnitude v
dir = direction v
arrowV :: Renderable (Path R2) b => R2 -> Diagram b R2
arrowV = arrowV' def
arrowV'
:: Renderable (Path R2) b
=> ArrowOpts -> R2 -> Diagram b R2
arrowV' opts = arrowAt' opts origin
connect
:: (Renderable (Path R2) b, IsName n1, IsName n2)
=> n1 -> n2 -> (Diagram b R2 -> Diagram b R2)
connect = connect' def
connect'
:: (Renderable (Path R2) b, IsName n1, IsName n2)
=> ArrowOpts -> n1 -> n2 -> (Diagram b R2 -> Diagram b R2)
connect' opts n1 n2 =
withName n1 $ \sub1 ->
withName n2 $ \sub2 ->
let [s,e] = map location [sub1, sub2]
in atop (arrowBetween' opts s e)
connectPerim
:: (Renderable (Path R2) b, IsName n1, IsName n2)
=> n1 -> n2 -> Angle -> Angle
-> (Diagram b R2 -> Diagram b R2)
connectPerim = connectPerim' def
connectPerim'
:: (Renderable (Path R2) b, IsName n1, IsName n2)
=> ArrowOpts -> n1 -> n2 -> Angle -> Angle
-> (Diagram b R2 -> Diagram b R2)
connectPerim' opts n1 n2 a1 a2 =
withName n1 $ \sub1 ->
withName n2 $ \sub2 ->
let [os, oe] = map location [sub1, sub2]
s = fromMaybe os (maxTraceP os (unitX # rotate a1) sub1)
e = fromMaybe oe (maxTraceP oe (unitX # rotate a2) sub2)
in atop (arrowBetween' opts s e)
connectOutside
:: (Renderable (Path R2) b, IsName n1, IsName n2)
=> n1 -> n2 -> (Diagram b R2 -> Diagram b R2)
connectOutside = connectOutside' def
connectOutside'
:: (Renderable (Path R2) b, IsName n1, IsName n2)
=> ArrowOpts -> n1 -> n2 -> (Diagram b R2 -> Diagram b R2)
connectOutside' opts n1 n2 =
withName n1 $ \b1 ->
withName n2 $ \b2 ->
let v = location b2 .-. location b1
midpoint = location b1 .+^ (v/2)
s' = fromMaybe (location b1) $ traceP midpoint (v) b1
e' = fromMaybe (location b2) $ traceP midpoint v b2
in
atop (arrowBetween' opts s' e')