{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Diagrams.TwoD.Arrowheads
(
tri
, dart
, halfDart
, spike
, thorn
, lineHead
, noHead
, arrowheadTriangle
, arrowheadDart
, arrowheadHalfDart
, arrowheadSpike
, arrowheadThorn
, tri'
, dart'
, halfDart'
, spike'
, thorn'
, lineTail
, noTail
, quill
, block
, arrowtailQuill
, arrowtailBlock
, ArrowHT
) where
import Control.Lens ((&), (.~), (<>~), (^.))
import Data.Default.Class
import Data.Monoid (mempty, (<>))
import Diagrams.Angle
import Diagrams.Core
import Diagrams.Path
import Diagrams.Segment
import Diagrams.Trail
import Diagrams.TrailLike (fromOffsets)
import Diagrams.TwoD.Align
import Diagrams.TwoD.Arc (arc')
import Diagrams.TwoD.Path ()
import Diagrams.TwoD.Polygons
import Diagrams.TwoD.Shapes
import Diagrams.TwoD.Transform
import Diagrams.TwoD.Types
import Diagrams.TwoD.Vector (unitX, unit_X, xDir)
import Diagrams.Util (( # ))
import Linear.Affine
import Linear.Metric
import Linear.Vector
type ArrowHT n = n -> n -> (Path V2 n, Path V2 n)
closedPath :: OrderedField n => Trail V2 n -> Path V2 n
closedPath = pathFromTrail . closeTrail
arrowheadTriangle :: RealFloat n => Angle n -> ArrowHT n
arrowheadTriangle theta = aHead
where
aHead len _ = (p, mempty)
where
psi = pi - (theta ^. rad)
r = len / (1 + cos psi)
p = polygon (def & polyType .~ PolyPolar [theta, (-2) *^ theta]
(repeat r) & polyOrient .~ NoOrient) # alignL
arrowheadDart :: RealFloat n => Angle n -> ArrowHT n
arrowheadDart theta len shaftWidth = (hd # scale sz, jt)
where
hd = snugL . pathFromTrail . glueTrail $ fromOffsets [t1, t2, b2, b1]
jt = pathFromTrail . glueTrail $ j <> reflectY j
j = closeTrail $ fromOffsets [V2 (-jLength) 0, V2 0 (shaftWidth / 2)]
v = rotate theta unitX
(t1, t2) = (unit_X ^+^ v, V2 (-0.5) 0 ^-^ v)
[b1, b2] = map (reflectY . negated) [t1, t2]
psi = pi - negated t2 ^. _theta . rad
jLength = shaftWidth / (2 * tan psi)
sz = max 1 ((len - jLength) / 1.5)
arrowheadHalfDart :: RealFloat n => Angle n -> ArrowHT n
arrowheadHalfDart theta len shaftWidth = (hd, jt)
where
hd = fromOffsets [t1, t2]
# closeTrail # pathFromTrail
# translateX 1.5 # scale sz
# translateY (-shaftWidth/2)
# snugL
jt = snugR . translateY (-shaftWidth/2) . pathFromTrail . closeTrail $ fromOffsets [V2 (-jLength) 0, V2 0 shaftWidth]
v = rotate theta unitX
(t1, t2) = (unit_X ^+^ v, (0.5 *^ unit_X) ^-^ v)
psi = pi - negated t2 ^. _theta . rad
jLength = shaftWidth / tan psi
sz = max 1 ((len - jLength) / 1.5)
arrowheadSpike :: RealFloat n => Angle n -> ArrowHT n
arrowheadSpike theta len shaftWidth = (hd # scale r, jt # scale r)
where
hd = snugL . closedPath $ l1 <> c <> l2
jt = alignR . centerY . pathFromTrail
. closeTrail $ arc' 1 (xDir & _theta <>~ negated phi) (2 *^ phi)
l1 = trailFromSegments [straight $ unit_X ^+^ v]
l2 = trailFromSegments [reverseSegment . straight $ (unit_X ^+^ reflectY v)]
c = arc' 1 (rotate α xDir) ((-2) *^ α)
α = (1/2 @@ turn) ^-^ theta
v = rotate theta unitX
a = 1 - 2 * cos (theta ^. rad)
y = shaftWidth / 2
d = max 1 (len**2 + (1 - a**2) * y**2)
r = (a * len + sqrt d) / (a**2 -1)
phi = asinA (min 1 (y/r))
arrowheadThorn :: RealFloat n => Angle n -> ArrowHT n
arrowheadThorn theta len shaftWidth = (hd # scale sz, jt)
where
hd = snugL . pathFromTrail . glueTrail $ hTop <> reflectY hTop
hTop = closeTrail . trailFromSegments $ [c, l]
jt = pathFromTrail . glueTrail $ j <> reflectY j
j = closeTrail $ fromOffsets [V2 (-jLength) 0, V2 0 (shaftWidth / 2)]
c = curvedSide theta
v = rotate theta unitX
l = reverseSegment . straight $ t
t = v ^-^ V2 (-0.5) 0
psi = fullTurn ^/ 2 ^-^ (negated t ^. _theta)
jLength = shaftWidth / (2 * tanA psi)
sz = max 1 ((len - jLength) / 1.5)
curvedSide :: Floating n => Angle n -> Segment Closed V2 n
curvedSide theta = bezier3 ctrl1 ctrl2 end
where
v0 = unit_X
v1 = rotate theta unitX
ctrl1 = v0
ctrl2 = v0 ^+^ v1
end = v0 ^+^ v1
lineHead :: RealFloat n => ArrowHT n
lineHead s w = (square 1 # scaleX s # scaleY w # alignL, mempty)
noHead :: ArrowHT n
noHead _ _ = (mempty, mempty)
tri :: RealFloat n => ArrowHT n
tri = arrowheadTriangle (1/3 @@ turn)
spike :: RealFloat n => ArrowHT n
spike = arrowheadSpike (3/8 @@ turn)
thorn :: RealFloat n => ArrowHT n
thorn = arrowheadThorn (3/8 @@ turn)
dart :: RealFloat n => ArrowHT n
dart = arrowheadDart (2/5 @@ turn)
halfDart :: RealFloat n => ArrowHT n
halfDart = arrowheadHalfDart (2/5 @@ turn)
headToTail :: OrderedField n => ArrowHT n -> ArrowHT n
headToTail hd = tl
where
tl sz shaftWidth = (t, j)
where
(t', j') = hd sz shaftWidth
t = reflectX t'
j = reflectX j'
arrowtailBlock :: forall n. (RealFloat n) => Angle n -> ArrowHT n
arrowtailBlock theta = aTail
where
aTail len _ = (t, mempty)
where
t = rect len (len * x) # alignR
a' :: V2 n
a' = rotate theta unitX
a = a' ^-^ reflectY a'
x = norm a
arrowtailQuill :: OrderedField n => Angle n -> ArrowHT n
arrowtailQuill theta = aTail
where
aTail len shaftWidth = (t, j)
where
t = closedPath (trailFromVertices [v0, v1, v2, v3, v4, v5, v0])
# scale sz # alignR
sz = len / 0.6
v0 = p2 (0.5, 0)
v2 = origin .+^ (rotate theta unitX # scale 0.5)
v1 = v2 # translateX (5/8)
v3 = p2 (-0.1, 0)
v4 = v2 # reflectY
v5 = v4 # translateX (5/8)
s = 1 - shaftWidth / norm (v1 .-. v5)
n1 = v0 # translateY (0.5 * shaftWidth)
n2 = v1 .-^ ((v1 .-. v0) # scale s)
n3 = v5 .-^ ((v5 .-. v0) # scale s)
n4 = n1 # reflectY
j = closedPath $ trailFromVertices [v0, n1, n2, v0, n3, n4, v0]
lineTail :: RealFloat n => ArrowHT n
lineTail s w = (square 1 # scaleY w # scaleX s # alignR, mempty)
noTail :: ArrowHT n
noTail _ _ = (mempty, mempty)
tri' :: RealFloat n => ArrowHT n
tri' = headToTail tri
spike' :: RealFloat n => ArrowHT n
spike' = headToTail spike
thorn' :: RealFloat n => ArrowHT n
thorn' = headToTail thorn
dart' :: RealFloat n => ArrowHT n
dart' = headToTail dart
halfDart' :: RealFloat n => ArrowHT n
halfDart' = headToTail halfDart
quill :: (Floating n, Ord n) => ArrowHT n
quill = arrowtailQuill (2/5 @@ turn)
block :: RealFloat n => ArrowHT n
block = arrowtailBlock (7/16 @@ turn)