{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Diagrams.TwoD.Shapes
(
hrule, vrule
, regPoly
, triangle
, eqTriangle
, square
, pentagon
, hexagon
, heptagon
, septagon
, octagon
, nonagon
, decagon
, hendecagon
, dodecagon
, unitSquare
, rect
, roundedRect
, RoundedRectOpts(..), radiusTL, radiusTR, radiusBL, radiusBR
, roundedRect'
) where
import Control.Lens (makeLenses, op, (&), (.~), (<>~), (^.))
import Data.Default.Class
import Data.Semigroup
import Diagrams.Core
import Diagrams.Angle
import Diagrams.Located (at)
import Diagrams.Path
import Diagrams.Segment
import Diagrams.Trail
import Diagrams.TrailLike
import Diagrams.TwoD.Arc
import Diagrams.TwoD.Polygons
import Diagrams.TwoD.Transform
import Diagrams.TwoD.Types
import Diagrams.TwoD.Vector
import Diagrams.Util
hrule :: (InSpace V2 n t, TrailLike t) => n -> t
hrule d = trailLike $ trailFromSegments [straight $ r2 (d, 0)] `at` p2 (-d/2,0)
vrule :: (InSpace V2 n t, TrailLike t) => n -> t
vrule d = trailLike $ trailFromSegments [straight $ r2 (0, -d)] `at` p2 (0,d/2)
unitSquare :: (InSpace V2 n t, TrailLike t) => t
unitSquare = polygon (def & polyType .~ PolyRegular 4 (sqrt 2 / 2)
& polyOrient .~ OrientH)
square :: (InSpace V2 n t, TrailLike t) => n -> t
square d = rect d d
rect :: (InSpace V2 n t, TrailLike t) => n -> n -> t
rect w h = trailLike . head . op Path $ unitSquare # scaleX w # scaleY h
regPoly :: (InSpace V2 n t, TrailLike t) => Int -> n -> t
regPoly n l = polygon (def & polyType .~
PolySides
(repeat (1/fromIntegral n @@ turn))
(replicate (n-1) l)
& polyOrient .~ OrientH
)
eqTriangle :: (InSpace V2 n t, TrailLike t) => n -> t
eqTriangle = triangle
triangle :: (InSpace V2 n t, TrailLike t) => n -> t
triangle = regPoly 3
pentagon :: (InSpace V2 n t, TrailLike t) => n -> t
pentagon = regPoly 5
hexagon :: (InSpace V2 n t, TrailLike t) => n -> t
hexagon = regPoly 6
heptagon :: (InSpace V2 n t, TrailLike t) => n -> t
heptagon = regPoly 7
septagon :: (InSpace V2 n t, TrailLike t) => n -> t
septagon = heptagon
octagon :: (InSpace V2 n t, TrailLike t) => n -> t
octagon = regPoly 8
nonagon :: (InSpace V2 n t, TrailLike t) => n -> t
nonagon = regPoly 9
decagon :: (InSpace V2 n t, TrailLike t) => n -> t
decagon = regPoly 10
hendecagon :: (InSpace V2 n t, TrailLike t) => n -> t
hendecagon = regPoly 11
dodecagon :: (InSpace V2 n t, TrailLike t) => n -> t
dodecagon = regPoly 12
data RoundedRectOpts d = RoundedRectOpts { _radiusTL :: d
, _radiusTR :: d
, _radiusBL :: d
, _radiusBR :: d
}
makeLenses ''RoundedRectOpts
instance (Num d) => Default (RoundedRectOpts d) where
def = RoundedRectOpts 0 0 0 0
-- | @roundedRect w h r@ generates a closed trail, or closed path
-- centered at the origin, of an axis-aligned rectangle with width
-- @w@, height @h@, and circular rounded corners of radius @r@. If
-- @r@ is negative the corner will be cut out in a reverse arc. If
-- the size of @r@ is larger than half the smaller dimension of @w@
-- and @h@, then it will be reduced to fit in that range, to prevent
-- the corners from overlapping. The trail or path begins with the
-- right edge and proceeds counterclockwise. If you need to specify
-- a different radius for each corner individually, use
-- 'roundedRect'' instead.
--
-- <<diagrams/src_Diagrams_TwoD_Shapes_roundedRectEx.svg#diagram=roundedRectEx&width=400>>
--
-- > roundedRectEx = pad 1.1 . centerXY $ hcat' (with & sep .~ 0.2)
-- > [ roundedRect 0.5 0.4 0.1
-- > , roundedRect 0.5 0.4 (-0.1)
-- > , roundedRect' 0.7 0.4 (with & radiusTL .~ 0.2
-- > & radiusTR .~ -0.2
-- > & radiusBR .~ 0.1)
-- > ]
roundedRect :: (InSpace V2 n t, TrailLike t, RealFloat n) => n -> n -> n -> t
roundedRect w h r = roundedRect' w h (def & radiusTL .~ r
& radiusBR .~ r
& radiusTR .~ r
& radiusBL .~ r)
-- | @roundedRect'@ works like @roundedRect@ but allows you to set the radius of
-- each corner indivually, using @RoundedRectOpts@. The default corner radius is 0.
-- Each radius can also be negative, which results in the curves being reversed
-- to be inward instead of outward.
roundedRect' :: (InSpace V2 n t, TrailLike t, RealFloat n) => n -> n -> RoundedRectOpts n -> t
roundedRect' w h opts
= trailLike
. (`at` p2 (w/2, abs rBR - h/2))
. wrapTrail
. glueLine
$ seg (0, h - abs rTR - abs rBR)
<> mkCorner 0 rTR
<> seg (abs rTR + abs rTL - w, 0)
<> mkCorner 1 rTL
<> seg (0, abs rTL + abs rBL - h)
<> mkCorner 2 rBL
<> seg (w - abs rBL - abs rBR, 0)
<> mkCorner 3 rBR
where seg = lineFromOffsets . (:[]) . r2
diag = sqrt (w * w + h * h)
-- to clamp corner radius, need to compare with other corners that share an
-- edge. If the corners overlap then reduce the largest corner first, as far
-- as 50% of the edge in question.
rTL = clampCnr radiusTR radiusBL radiusBR radiusTL
rBL = clampCnr radiusBR radiusTL radiusTR radiusBL
rTR = clampCnr radiusTL radiusBR radiusBL radiusTR
rBR = clampCnr radiusBL radiusTR radiusTL radiusBR
clampCnr rx ry ro r = let (rx',ry',ro',r') = (opts^.rx, opts^.ry, opts^.ro, opts^.r)
in clampDiag ro' . clampAdj h ry' . clampAdj w rx' $ r'
-- prevent curves of adjacent corners from overlapping
clampAdj len adj r = if abs r > len/2
then sign r * max (len/2) (min (len - abs adj) (abs r))
else r
-- prevent inward curves of diagonally opposite corners from intersecting
clampDiag opp r = if r < 0 && opp < 0 && abs r > diag / 2
then sign r * max (diag / 2) (min (abs r) (diag + opp))
else r
sign n = if n < 0 then -1 else 1
mkCorner k r | r == 0 = mempty
| r < 0 = doArc 3 (-1)
| otherwise = doArc 0 1
where
doArc d s =
arc' r (xDir & _theta <>~ ((k+d)/4 @@ turn)) (s/4 @@ turn)