{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
module Diagrams.Attributes (
ultraThin, veryThin, thin, medium, thick, veryThick, ultraThick, none
, tiny, verySmall, small, normal, large, veryLarge, huge
, LineWidth, getLineWidth
, _LineWidth, _LineWidthM
, lineWidth, lineWidthM
, _lineWidth, _lw, _lineWidthU
, lw, lwN, lwO, lwL, lwG
, Dashing(..), getDashing
, dashing, dashingN, dashingO, dashingL, dashingG
, _dashing, _dashingU
, Color(..), SomeColor(..), _SomeColor, someToAlpha
, Opacity, _Opacity
, getOpacity, opacity, _opacity
, FillOpacity, _FillOpacity
, getFillOpacity, fillOpacity, _fillOpacity
, StrokeOpacity, _StrokeOpacity
, getStrokeOpacity, strokeOpacity, _strokeOpacity
, colorToSRGBA, colorToRGBA
, LineCap(..)
, getLineCap, lineCap, _lineCap
, LineJoin(..)
, getLineJoin, lineJoin, _lineJoin
, LineMiterLimit(..), _LineMiterLimit
, getLineMiterLimit, lineMiterLimit, lineMiterLimitA, _lineMiterLimit
, _Recommend
, _Commit
, _recommend
, isCommitted
, committed
) where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
#endif
import Control.Lens hiding (none, over)
import Data.Colour
import Data.Colour.RGBSpace (RGB (..))
import Data.Colour.SRGB (toSRGB)
import Data.Default.Class
import Data.Distributive
import Data.Monoid.Recommend
import Data.Semigroup
import Data.Typeable
import Diagrams.Core
none, ultraThin, veryThin, thin, medium, thick, veryThick, ultraThick,
tiny, verySmall, small, normal, large, veryLarge, huge
:: OrderedField n => Measure n
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 n = LineWidth (Last n)
deriving (Typeable, Semigroup)
_LineWidth :: Iso' (LineWidth n) n
_LineWidth = iso getLineWidth (LineWidth . Last)
_LineWidthM :: Iso' (LineWidthM n) (Measure n)
_LineWidthM = mapping _LineWidth
instance Typeable n => AttributeClass (LineWidth n)
type LineWidthM n = Measured n (LineWidth n)
instance OrderedField n => Default (LineWidthM n) where
def = fmap (LineWidth . Last) medium
getLineWidth :: LineWidth n -> n
getLineWidth (LineWidth (Last w)) = w
lineWidth :: (N a ~ n, HasStyle a, Typeable n) => Measure n -> a -> a
lineWidth = applyMAttr . fmap (LineWidth . Last)
lineWidthM :: (N a ~ n, HasStyle a, Typeable n) => LineWidthM n -> a -> a
lineWidthM = applyMAttr
lw :: (N a ~ n, HasStyle a, Typeable n) => Measure n -> a -> a
lw = lineWidth
lwG :: (N a ~ n, HasStyle a, Typeable n, Num n) => n -> a -> a
lwG = lw . global
lwN :: (N a ~ n, HasStyle a, Typeable n, Num n) => n -> a -> a
lwN = lw . normalized
lwO :: (N a ~ n, HasStyle a, Typeable n) => n -> a -> a
lwO = lw . output
lwL :: (N a ~ n, HasStyle a, Typeable n, Num n) => n -> a -> a
lwL = lw . local
_lineWidth, _lw :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measure n)
_lineWidth = atMAttr . anon def (const False) . _LineWidthM
_lw = _lineWidth
_lineWidthU :: Typeable n => Lens' (Style v n) (Maybe n)
_lineWidthU = atAttr . mapping _LineWidth
data Dashing n = Dashing [n] n
deriving (Functor, Typeable, Eq)
instance Semigroup (Dashing n) where
_ <> b = b
instance Typeable n => AttributeClass (Dashing n)
getDashing :: Dashing n -> Dashing n
getDashing = id
dashing :: (N a ~ n, HasStyle a, Typeable n)
=> [Measure n]
-> Measure n
-> a -> a
dashing ds offs = applyMAttr . distribute $ Dashing ds offs
dashingG :: (N a ~ n, HasStyle a, Typeable n, Num n) => [n] -> n -> a -> a
dashingG w v = dashing (map global w) (global v)
dashingN :: (N a ~ n, HasStyle a, Typeable n, Num n) => [n] -> n -> a -> a
dashingN w v = dashing (map normalized w) (normalized v)
dashingO :: (N a ~ n, HasStyle a, Typeable n) => [n] -> n -> a -> a
dashingO w v = dashing (map output w) (output v)
dashingL :: (N a ~ n, HasStyle a, Typeable n, Num n) => [n] -> n -> a -> a
dashingL w v = dashing (map local w) (local v)
_dashing :: Typeable n
=> Lens' (Style v n) (Maybe (Measured n (Dashing n)))
_dashing = atMAttr
_dashingU :: Typeable n => Lens' (Style v n) (Maybe (Dashing n))
_dashingU = atAttr
class Color c where
toAlphaColour :: c -> AlphaColour Double
fromAlphaColour :: AlphaColour Double -> c
data SomeColor = forall c. Color c => SomeColor c
deriving Typeable
instance Show SomeColor where
showsPrec d (colorToSRGBA -> (r,g,b,a)) =
showParen (d > 10) $ showString "SomeColor " .
if a == 0
then showString "transparent"
else showString "(sRGB " . showsPrec 11 r . showChar ' '
. showsPrec 11 g . showChar ' '
. showsPrec 11 b .
(if a /= 1
then showString " `withOpacity` " . showsPrec 11 a
else id) . showChar ')'
_SomeColor :: Iso' SomeColor (AlphaColour Double)
_SomeColor = iso toAlphaColour fromAlphaColour
someToAlpha :: SomeColor -> AlphaColour Double
someToAlpha (SomeColor c) = toAlphaColour c
instance a ~ Double => Color (Colour a) where
toAlphaColour = opaque
fromAlphaColour = (`over` black)
instance a ~ Double => Color (AlphaColour a) where
toAlphaColour = id
fromAlphaColour = id
instance Color SomeColor where
toAlphaColour (SomeColor c) = toAlphaColour c
fromAlphaColour = SomeColor
colorToSRGBA, colorToRGBA :: Color c => c -> (Double, Double, Double, Double)
colorToSRGBA col = (r, g, b, a)
where
c' = toAlphaColour col
c = alphaToColour c'
a = alphaChannel c'
RGB r g b = toSRGB c
colorToRGBA = colorToSRGBA
{-# DEPRECATED colorToRGBA "Renamed to colorToSRGBA." #-}
alphaToColour :: (Floating a, Ord a) => AlphaColour a -> Colour a
alphaToColour ac | alphaChannel ac == 0 = ac `over` black
| otherwise = darken (recip (alphaChannel ac)) (ac `over` black)
newtype Opacity = Opacity (Product Double)
deriving (Typeable, Semigroup)
instance AttributeClass Opacity
_Opacity :: Iso' Opacity Double
_Opacity = iso getOpacity (Opacity . Product)
getOpacity :: Opacity -> Double
getOpacity (Opacity (Product d)) = d
opacity :: HasStyle a => Double -> a -> a
opacity = applyAttr . Opacity . Product
_opacity :: Lens' (Style v n) Double
_opacity = atAttr . mapping _Opacity . non 1
newtype FillOpacity = FillOpacity (Product Double)
deriving (Typeable, Semigroup)
instance AttributeClass FillOpacity
_FillOpacity :: Iso' FillOpacity Double
_FillOpacity = iso getFillOpacity (FillOpacity . Product)
getFillOpacity :: FillOpacity -> Double
getFillOpacity (FillOpacity (Product d)) = d
fillOpacity :: HasStyle a => Double -> a -> a
fillOpacity = applyAttr . FillOpacity . Product
_fillOpacity :: Lens' (Style v n) Double
_fillOpacity = atAttr . mapping _FillOpacity . non 1
newtype StrokeOpacity = StrokeOpacity (Product Double)
deriving (Typeable, Semigroup)
instance AttributeClass StrokeOpacity
_StrokeOpacity :: Iso' StrokeOpacity Double
_StrokeOpacity = iso getStrokeOpacity (StrokeOpacity . Product)
getStrokeOpacity :: StrokeOpacity -> Double
getStrokeOpacity (StrokeOpacity (Product d)) = d
strokeOpacity :: HasStyle a => Double -> a -> a
strokeOpacity = applyAttr . StrokeOpacity . Product
_strokeOpacity :: Lens' (Style v n) Double
_strokeOpacity = atAttr . mapping _StrokeOpacity . non 1
data LineCap = LineCapButt
| LineCapRound
| LineCapSquare
deriving (Eq, Ord, Show, Typeable)
instance Default LineCap where
def = LineCapButt
instance AttributeClass LineCap
instance Semigroup LineCap where
_ <> b = b
getLineCap :: LineCap -> LineCap
getLineCap = id
lineCap :: HasStyle a => LineCap -> a -> a
lineCap = applyAttr
_lineCap :: Lens' (Style v n) LineCap
_lineCap = atAttr . non def
data LineJoin = LineJoinMiter
| LineJoinRound
| LineJoinBevel
deriving (Eq, Ord, Show, Typeable)
instance AttributeClass LineJoin
instance Semigroup LineJoin where
_ <> b = b
instance Default LineJoin where
def = LineJoinMiter
getLineJoin :: LineJoin -> LineJoin
getLineJoin = id
lineJoin :: HasStyle a => LineJoin -> a -> a
lineJoin = applyAttr
_lineJoin :: Lens' (Style v n) LineJoin
_lineJoin = atAttr . non def
newtype LineMiterLimit = LineMiterLimit (Last Double)
deriving (Typeable, Semigroup, Eq, Ord)
instance AttributeClass LineMiterLimit
_LineMiterLimit :: Iso' LineMiterLimit Double
_LineMiterLimit = iso getLineMiterLimit (LineMiterLimit . Last)
instance Default LineMiterLimit where
def = LineMiterLimit (Last 10)
getLineMiterLimit :: LineMiterLimit -> Double
getLineMiterLimit (LineMiterLimit (Last l)) = l
lineMiterLimit :: HasStyle a => Double -> a -> a
lineMiterLimit = applyAttr . LineMiterLimit . Last
lineMiterLimitA :: HasStyle a => LineMiterLimit -> a -> a
lineMiterLimitA = applyAttr
_lineMiterLimit :: Lens' (Style v n) Double
_lineMiterLimit = atAttr . non def . _LineMiterLimit
_Recommend :: Prism' (Recommend a) a
_Recommend = prism' Recommend $ \case (Recommend a) -> Just a; _ -> Nothing
_Commit :: Prism' (Recommend a) a
_Commit = prism' Commit $ \case (Commit a) -> Just a; _ -> Nothing
_recommend :: Lens (Recommend a) (Recommend b) a b
_recommend f (Recommend a) = Recommend <$> f a
_recommend f (Commit a) = Commit <$> f a
isCommitted :: Lens' (Recommend a) Bool
isCommitted f r@(Recommend a) = f False <&> \b -> if b then Commit a else r
isCommitted f r@(Commit a) = f True <&> \b -> if b then r else Recommend a
committed :: Iso (Recommend a) (Recommend b) a b
committed = iso getRecommend Commit