module Diagrams.TwoD.Attributes (
LineWidth, getLineWidth, lineWidth, lineWidthA
, lw, lwN, lwO, lwL, lwG
, ultraThin, veryThin, thin, medium, thick, veryThick, ultraThick, none
, tiny, verySmall, small, normal, large, veryLarge, huge
, Dashing(..), DashingA, getDashing
, dashing, dashingN, dashingO, dashingL, dashingG
, Texture(..), solid, _SC, _LG, _RG, defaultLG, defaultRG
, GradientStop(..), stopColor, stopFraction, mkStops
, SpreadMethod(..), lineLGradient, lineRGradient
, LGradient(..), lGradStops, lGradTrans, lGradStart, lGradEnd
, lGradSpreadMethod, mkLinearGradient
, RGradient(..), rGradStops, rGradTrans
, rGradCenter0, rGradRadius0, rGradCenter1, rGradRadius1
, rGradSpreadMethod, mkRadialGradient
, LineTexture(..), getLineTexture, lineTexture, lineTextureA
, mkLineTexture, styleLineTexture
, lineColor, lc, lcA
, FillTexture(..), getFillTexture, fillTexture
, mkFillTexture, styleFillTexture
, fillColor, fc, fcA, recommendFillColor
, splitTextureFills
) where
import Diagrams.Core
import Diagrams.Core.Style (setAttr)
import Diagrams.Attributes
import Diagrams.Attributes.Compile
import Diagrams.TwoD.Types
import Diagrams.Core.Types (RTree)
import Diagrams.Located (unLoc)
import Diagrams.Path (Path, pathTrails)
import Diagrams.Trail (isLoop)
import Control.Lens ( makeLensesWith, generateSignatures, lensRules
, makePrisms, Lens', (&), (%~), (.~), Setter', sets)
import Data.Colour hiding (AffineSpace)
import Data.Data
import Data.Default.Class
import Data.Maybe (fromMaybe)
import Data.Monoid.Recommend
import Data.Semigroup
none, ultraThin, veryThin, thin, medium, thick, veryThick, ultraThick,
tiny, verySmall, small, normal, large, veryLarge, huge :: Measure R2
none = Output 0
ultraThin = Normalized 0.0005 `atLeast` Output 0.5
veryThin = Normalized 0.001 `atLeast` Output 0.5
thin = Normalized 0.002 `atLeast` Output 0.5
medium = Normalized 0.004 `atLeast` Output 0.5
thick = Normalized 0.0075 `atLeast` Output 0.5
veryThick = Normalized 0.01 `atLeast` Output 0.5
ultraThick = Normalized 0.02 `atLeast` Output 0.5
tiny = Normalized 0.01
verySmall = Normalized 0.015
small = Normalized 0.023
normal = Normalized 0.035
large = Normalized 0.05
veryLarge = Normalized 0.07
huge = Normalized 0.10
newtype LineWidth = LineWidth (Last (Measure R2))
deriving (Typeable, Data, Semigroup)
instance AttributeClass LineWidth
type instance V LineWidth = R2
instance Transformable LineWidth where
transform t (LineWidth (Last w)) =
LineWidth (Last (transform t w))
instance Default LineWidth where
def = LineWidth (Last medium)
getLineWidth :: LineWidth -> Measure R2
getLineWidth (LineWidth (Last w)) = w
lineWidth :: (HasStyle a, V a ~ R2) => Measure R2 -> a -> a
lineWidth = applyGTAttr . LineWidth . Last
lineWidthA :: (HasStyle a, V a ~ R2) => LineWidth -> a -> a
lineWidthA = applyGTAttr
lw :: (HasStyle a, V a ~ R2) => Measure R2 -> a -> a
lw = lineWidth
lwG :: (HasStyle a, V a ~ R2) => Double -> a -> a
lwG w = lineWidth (Global w)
lwN :: (HasStyle a, V a ~ R2) => Double -> a -> a
lwN w = lineWidth (Normalized w)
lwO :: (HasStyle a, V a ~ R2) => Double -> a -> a
lwO w = lineWidth (Output w)
lwL :: (HasStyle a, V a ~ R2) => Double -> a -> a
lwL w = lineWidth (Local w)
data Dashing = Dashing [Measure R2] (Measure R2)
deriving (Typeable, Data, Eq)
newtype DashingA = DashingA (Last Dashing)
deriving (Typeable, Data, Semigroup, Eq)
instance AttributeClass DashingA
type instance V DashingA = R2
instance Transformable DashingA where
transform t (DashingA (Last (Dashing w v))) =
DashingA (Last (Dashing r s))
where
r = map (transform t) w
s = transform t v
getDashing :: DashingA -> Dashing
getDashing (DashingA (Last d)) = d
dashing :: (HasStyle a, V a ~ R2) =>
[Measure R2]
-> Measure R2
-> a -> a
dashing ds offs = applyGTAttr (DashingA (Last (Dashing ds offs)))
dashingG :: (HasStyle a, V a ~ R2) => [Double] -> Double -> a -> a
dashingG w v = dashing (map Global w) (Global v)
dashingN :: (HasStyle a, V a ~ R2) => [Double] -> Double -> a -> a
dashingN w v = dashing (map Normalized w) (Normalized v)
dashingO :: (HasStyle a, V a ~ R2) => [Double] -> Double -> a -> a
dashingO w v = dashing (map Output w) (Output v)
dashingL :: (HasStyle a, V a ~ R2) => [Double] -> Double -> a -> a
dashingL w v = dashing (map Local w) (Local v)
data GradientStop = GradientStop
{ _stopColor :: SomeColor
, _stopFraction :: Double}
makeLensesWith (lensRules & generateSignatures .~ False) ''GradientStop
stopColor :: Lens' GradientStop SomeColor
stopFraction :: Lens' GradientStop Double
data SpreadMethod = GradPad | GradReflect | GradRepeat
data LGradient = LGradient
{ _lGradStops :: [GradientStop]
, _lGradStart :: P2
, _lGradEnd :: P2
, _lGradTrans :: T2
, _lGradSpreadMethod :: SpreadMethod }
makeLensesWith (lensRules & generateSignatures .~ False) ''LGradient
lGradStops :: Lens' LGradient [GradientStop]
lGradTrans :: Lens' LGradient T2
lGradStart :: Lens' LGradient P2
lGradEnd :: Lens' LGradient P2
lGradSpreadMethod :: Lens' LGradient SpreadMethod
data RGradient = RGradient
{ _rGradStops :: [GradientStop]
, _rGradCenter0 :: P2
, _rGradRadius0 :: Double
, _rGradCenter1 :: P2
, _rGradRadius1 :: Double
, _rGradTrans :: T2
, _rGradSpreadMethod :: SpreadMethod }
makeLensesWith (lensRules & generateSignatures .~ False) ''RGradient
rGradStops :: Lens' RGradient [GradientStop]
rGradCenter0 :: Lens' RGradient P2
rGradRadius0 :: Lens' RGradient Double
rGradCenter1 :: Lens' RGradient P2
rGradRadius1 :: Lens' RGradient Double
rGradTrans :: Lens' RGradient T2
rGradSpreadMethod :: Lens' RGradient SpreadMethod
data Texture = SC SomeColor | LG LGradient | RG RGradient
deriving (Typeable)
makePrisms ''Texture
solid :: Color a => a -> Texture
solid = SC . SomeColor
defaultLG :: Texture
defaultLG = LG (LGradient
{ _lGradStops = []
, _lGradStart = mkP2 (0.5) 0
, _lGradEnd = mkP2 (0.5) 0
, _lGradTrans = mempty
, _lGradSpreadMethod = GradPad
})
defaultRG :: Texture
defaultRG = RG (RGradient
{ _rGradStops = []
, _rGradCenter0 = mkP2 0 0
, _rGradRadius0 = 0.0
, _rGradCenter1 = mkP2 0 0
, _rGradRadius1 = 0.5
, _rGradTrans = mempty
, _rGradSpreadMethod = GradPad
})
mkStops :: [(Colour Double, Double, Double)] -> [GradientStop]
mkStops = map (\(x, y, z) -> GradientStop (SomeColor (withOpacity x z)) y)
mkLinearGradient :: [GradientStop] -> P2 -> P2 -> SpreadMethod -> Texture
mkLinearGradient stops start end spreadMethod
= LG (LGradient stops start end mempty spreadMethod)
mkRadialGradient :: [GradientStop] -> P2 -> Double
-> P2 -> Double -> SpreadMethod -> Texture
mkRadialGradient stops c0 r0 c1 r1 spreadMethod
= RG (RGradient stops c0 r0 c1 r1 mempty spreadMethod)
newtype LineTexture = LineTexture (Last Texture)
deriving (Typeable, Semigroup)
instance AttributeClass LineTexture
type instance V LineTexture = R2
instance Transformable LineTexture where
transform t (LineTexture (Last texture)) = LineTexture (Last tx)
where
tx = texture & lgt . rgt
lgt = _LG . lGradTrans %~ f
rgt = _RG . rGradTrans %~ f
f = transform t
instance Default LineTexture where
def = LineTexture (Last (SC (SomeColor (black :: Colour Double))))
getLineTexture :: LineTexture -> Texture
getLineTexture (LineTexture (Last t)) = t
lineTexture :: (HasStyle a, V a ~ R2) => Texture-> a -> a
lineTexture = applyTAttr . LineTexture . Last
lineTextureA :: (HasStyle a, V a ~ R2) => LineTexture -> a -> a
lineTextureA = applyTAttr
mkLineTexture :: Texture -> LineTexture
mkLineTexture = LineTexture . Last
styleLineTexture :: Setter' (Style v) Texture
styleLineTexture = sets modifyLineTexture
where
modifyLineTexture f s
= flip setAttr s
. mkLineTexture
. f
. getLineTexture
. fromMaybe def . getAttr
$ s
lineColor :: (Color c, HasStyle a, V a ~ R2) => c -> a -> a
lineColor = lineTexture . SC . SomeColor
lc :: (HasStyle a, V a ~ R2) => Colour Double -> a -> a
lc = lineColor
lcA :: (HasStyle a, V a ~ R2) => AlphaColour Double -> a -> a
lcA = lineColor
lineLGradient :: (HasStyle a, V a ~ R2) => LGradient -> a -> a
lineLGradient g = lineTexture (LG g)
lineRGradient :: (HasStyle a, V a ~ R2) => RGradient -> a -> a
lineRGradient g = lineTexture (RG g)
newtype FillTexture = FillTexture (Recommend (Last Texture))
deriving (Typeable, Semigroup)
instance AttributeClass FillTexture
type instance V FillTexture = R2
instance Transformable FillTexture where
transform _ tx@(FillTexture (Recommend _)) = tx
transform t (FillTexture (Commit (Last texture))) = FillTexture (Commit (Last tx))
where
tx = texture & lgt . rgt
lgt = _LG . lGradTrans %~ f
rgt = _RG . rGradTrans %~ f
f = transform t
instance Default FillTexture where
def = FillTexture (Recommend (Last (SC
(SomeColor (transparent :: AlphaColour Double)))))
getFillTexture :: FillTexture -> Texture
getFillTexture (FillTexture tx) = getLast . getRecommend $ tx
fillTexture :: (HasStyle a, V a ~ R2) => Texture -> a -> a
fillTexture = applyTAttr . FillTexture . Commit . Last
mkFillTexture :: Texture -> FillTexture
mkFillTexture = FillTexture . Commit . Last
styleFillTexture :: Setter' (Style v) Texture
styleFillTexture = sets modifyFillTexture
where
modifyFillTexture f s
= flip setAttr s
. mkFillTexture
. f
. getFillTexture
. fromMaybe def . getAttr
$ s
fillColor :: (Color c, HasStyle a, V a ~ R2) => c -> a -> a
fillColor = fillTexture . SC . SomeColor
recommendFillColor :: (Color c, HasStyle a, V a ~ R2) => c -> a -> a
recommendFillColor =
applyTAttr . FillTexture . Recommend . Last . SC . SomeColor
fc :: (HasStyle a, V a ~ R2) => Colour Double -> a -> a
fc = fillColor
fcA :: (HasStyle a, V a ~ R2) => AlphaColour Double -> a -> a
fcA = fillColor
data FillTextureLoops v = FillTextureLoops
instance Typeable v => SplitAttribute (FillTextureLoops v) where
type AttrType (FillTextureLoops v) = FillTexture
type PrimType (FillTextureLoops v) = Path v
primOK _ = all (isLoop . unLoc) . pathTrails
splitTextureFills :: forall b v a. Typeable v => RTree b v a -> RTree b v a
splitTextureFills = splitAttr (FillTextureLoops :: FillTextureLoops v)