{-# LANGUAGE TemplateHaskell #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Graphics.Rendering.Chart.Backend.Types
-- Copyright   :  (c) Tim Docker 2014
-- License     :  BSD-style (see chart/COPYRIGHT)
--

module Graphics.Rendering.Chart.Backend.Types where

import Data.Default.Class
import Data.Colour
import Data.Colour.Names
import Control.Lens

import Graphics.Rendering.Chart.Geometry

-- -----------------------------------------------------------------------
-- Line Types
-- -----------------------------------------------------------------------

-- | The different supported line ends.
data LineCap = LineCapButt   -- ^ Just cut the line straight.
             | LineCapRound  -- ^ Make a rounded line end.
             | LineCapSquare -- ^ Make a square that ends the line.
             deriving (Int -> LineCap -> ShowS
[LineCap] -> ShowS
LineCap -> String
(Int -> LineCap -> ShowS)
-> (LineCap -> String) -> ([LineCap] -> ShowS) -> Show LineCap
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LineCap] -> ShowS
$cshowList :: [LineCap] -> ShowS
show :: LineCap -> String
$cshow :: LineCap -> String
showsPrec :: Int -> LineCap -> ShowS
$cshowsPrec :: Int -> LineCap -> ShowS
Show, LineCap -> LineCap -> Bool
(LineCap -> LineCap -> Bool)
-> (LineCap -> LineCap -> Bool) -> Eq LineCap
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LineCap -> LineCap -> Bool
$c/= :: LineCap -> LineCap -> Bool
== :: LineCap -> LineCap -> Bool
$c== :: LineCap -> LineCap -> Bool
Eq, Eq LineCap
Eq LineCap
-> (LineCap -> LineCap -> Ordering)
-> (LineCap -> LineCap -> Bool)
-> (LineCap -> LineCap -> Bool)
-> (LineCap -> LineCap -> Bool)
-> (LineCap -> LineCap -> Bool)
-> (LineCap -> LineCap -> LineCap)
-> (LineCap -> LineCap -> LineCap)
-> Ord LineCap
LineCap -> LineCap -> Bool
LineCap -> LineCap -> Ordering
LineCap -> LineCap -> LineCap
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LineCap -> LineCap -> LineCap
$cmin :: LineCap -> LineCap -> LineCap
max :: LineCap -> LineCap -> LineCap
$cmax :: LineCap -> LineCap -> LineCap
>= :: LineCap -> LineCap -> Bool
$c>= :: LineCap -> LineCap -> Bool
> :: LineCap -> LineCap -> Bool
$c> :: LineCap -> LineCap -> Bool
<= :: LineCap -> LineCap -> Bool
$c<= :: LineCap -> LineCap -> Bool
< :: LineCap -> LineCap -> Bool
$c< :: LineCap -> LineCap -> Bool
compare :: LineCap -> LineCap -> Ordering
$ccompare :: LineCap -> LineCap -> Ordering
$cp1Ord :: Eq LineCap
Ord)

-- | The different supported ways to join line ends.
data LineJoin = LineJoinMiter -- ^ Extends the outline until they meet each other.
              | LineJoinRound -- ^ Draw a circle fragment to connet line end.
              | LineJoinBevel -- ^ Like miter, but cuts it off if a certain 
                              --   threshold is exceeded.
              deriving (Int -> LineJoin -> ShowS
[LineJoin] -> ShowS
LineJoin -> String
(Int -> LineJoin -> ShowS)
-> (LineJoin -> String) -> ([LineJoin] -> ShowS) -> Show LineJoin
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LineJoin] -> ShowS
$cshowList :: [LineJoin] -> ShowS
show :: LineJoin -> String
$cshow :: LineJoin -> String
showsPrec :: Int -> LineJoin -> ShowS
$cshowsPrec :: Int -> LineJoin -> ShowS
Show, LineJoin -> LineJoin -> Bool
(LineJoin -> LineJoin -> Bool)
-> (LineJoin -> LineJoin -> Bool) -> Eq LineJoin
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LineJoin -> LineJoin -> Bool
$c/= :: LineJoin -> LineJoin -> Bool
== :: LineJoin -> LineJoin -> Bool
$c== :: LineJoin -> LineJoin -> Bool
Eq, Eq LineJoin
Eq LineJoin
-> (LineJoin -> LineJoin -> Ordering)
-> (LineJoin -> LineJoin -> Bool)
-> (LineJoin -> LineJoin -> Bool)
-> (LineJoin -> LineJoin -> Bool)
-> (LineJoin -> LineJoin -> Bool)
-> (LineJoin -> LineJoin -> LineJoin)
-> (LineJoin -> LineJoin -> LineJoin)
-> Ord LineJoin
LineJoin -> LineJoin -> Bool
LineJoin -> LineJoin -> Ordering
LineJoin -> LineJoin -> LineJoin
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LineJoin -> LineJoin -> LineJoin
$cmin :: LineJoin -> LineJoin -> LineJoin
max :: LineJoin -> LineJoin -> LineJoin
$cmax :: LineJoin -> LineJoin -> LineJoin
>= :: LineJoin -> LineJoin -> Bool
$c>= :: LineJoin -> LineJoin -> Bool
> :: LineJoin -> LineJoin -> Bool
$c> :: LineJoin -> LineJoin -> Bool
<= :: LineJoin -> LineJoin -> Bool
$c<= :: LineJoin -> LineJoin -> Bool
< :: LineJoin -> LineJoin -> Bool
$c< :: LineJoin -> LineJoin -> Bool
compare :: LineJoin -> LineJoin -> Ordering
$ccompare :: LineJoin -> LineJoin -> Ordering
$cp1Ord :: Eq LineJoin
Ord)

-- | Data type for the style of a line.
data LineStyle = LineStyle 
  { LineStyle -> Double
_line_width  :: Double
  -- ^ The thickness of a line in device units.
  , LineStyle -> AlphaColour Double
_line_color  :: AlphaColour Double
  -- ^ The color of a line.
  , LineStyle -> [Double]
_line_dashes :: [Double]
  -- ^ The dash pattern. Every value at a even index gives a dash width and 
  --   every value at a odd index gives a gap width in device units.
  , LineStyle -> LineCap
_line_cap    :: LineCap
  -- ^ How to end a line.
  , LineStyle -> LineJoin
_line_join   :: LineJoin
  -- ^ How to connect two lines.
  } deriving (Int -> LineStyle -> ShowS
[LineStyle] -> ShowS
LineStyle -> String
(Int -> LineStyle -> ShowS)
-> (LineStyle -> String)
-> ([LineStyle] -> ShowS)
-> Show LineStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LineStyle] -> ShowS
$cshowList :: [LineStyle] -> ShowS
show :: LineStyle -> String
$cshow :: LineStyle -> String
showsPrec :: Int -> LineStyle -> ShowS
$cshowsPrec :: Int -> LineStyle -> ShowS
Show, LineStyle -> LineStyle -> Bool
(LineStyle -> LineStyle -> Bool)
-> (LineStyle -> LineStyle -> Bool) -> Eq LineStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LineStyle -> LineStyle -> Bool
$c/= :: LineStyle -> LineStyle -> Bool
== :: LineStyle -> LineStyle -> Bool
$c== :: LineStyle -> LineStyle -> Bool
Eq)

-- | The default line style.
instance Default LineStyle where
  def :: LineStyle
def = LineStyle :: Double
-> AlphaColour Double
-> [Double]
-> LineCap
-> LineJoin
-> LineStyle
LineStyle 
    { _line_width :: Double
_line_width  = Double
1
    , _line_color :: AlphaColour Double
_line_color  = Colour Double -> AlphaColour Double
forall a. Num a => Colour a -> AlphaColour a
opaque Colour Double
forall a. Num a => Colour a
black
    , _line_dashes :: [Double]
_line_dashes = []
    , _line_cap :: LineCap
_line_cap    = LineCap
LineCapButt
    , _line_join :: LineJoin
_line_join   = LineJoin
LineJoinBevel
    }

-- -----------------------------------------------------------------------
-- Font & Text Types
-- -----------------------------------------------------------------------

-- | The possible slants of a font.
data FontSlant = FontSlantNormal  -- ^ Normal font style without slant.
               | FontSlantItalic  -- ^ With a slight slant.
               | FontSlantOblique -- ^ With a greater slant.
               deriving (Int -> FontSlant -> ShowS
[FontSlant] -> ShowS
FontSlant -> String
(Int -> FontSlant -> ShowS)
-> (FontSlant -> String)
-> ([FontSlant] -> ShowS)
-> Show FontSlant
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontSlant] -> ShowS
$cshowList :: [FontSlant] -> ShowS
show :: FontSlant -> String
$cshow :: FontSlant -> String
showsPrec :: Int -> FontSlant -> ShowS
$cshowsPrec :: Int -> FontSlant -> ShowS
Show, FontSlant -> FontSlant -> Bool
(FontSlant -> FontSlant -> Bool)
-> (FontSlant -> FontSlant -> Bool) -> Eq FontSlant
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontSlant -> FontSlant -> Bool
$c/= :: FontSlant -> FontSlant -> Bool
== :: FontSlant -> FontSlant -> Bool
$c== :: FontSlant -> FontSlant -> Bool
Eq, Eq FontSlant
Eq FontSlant
-> (FontSlant -> FontSlant -> Ordering)
-> (FontSlant -> FontSlant -> Bool)
-> (FontSlant -> FontSlant -> Bool)
-> (FontSlant -> FontSlant -> Bool)
-> (FontSlant -> FontSlant -> Bool)
-> (FontSlant -> FontSlant -> FontSlant)
-> (FontSlant -> FontSlant -> FontSlant)
-> Ord FontSlant
FontSlant -> FontSlant -> Bool
FontSlant -> FontSlant -> Ordering
FontSlant -> FontSlant -> FontSlant
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FontSlant -> FontSlant -> FontSlant
$cmin :: FontSlant -> FontSlant -> FontSlant
max :: FontSlant -> FontSlant -> FontSlant
$cmax :: FontSlant -> FontSlant -> FontSlant
>= :: FontSlant -> FontSlant -> Bool
$c>= :: FontSlant -> FontSlant -> Bool
> :: FontSlant -> FontSlant -> Bool
$c> :: FontSlant -> FontSlant -> Bool
<= :: FontSlant -> FontSlant -> Bool
$c<= :: FontSlant -> FontSlant -> Bool
< :: FontSlant -> FontSlant -> Bool
$c< :: FontSlant -> FontSlant -> Bool
compare :: FontSlant -> FontSlant -> Ordering
$ccompare :: FontSlant -> FontSlant -> Ordering
$cp1Ord :: Eq FontSlant
Ord)

-- | The default font slant.
instance Default FontSlant where
  def :: FontSlant
def = FontSlant
FontSlantNormal

-- | The possible weights of a font.
data FontWeight = FontWeightNormal -- ^ Normal font style without weight.
                | FontWeightBold   -- ^ Bold font.
                deriving (Int -> FontWeight -> ShowS
[FontWeight] -> ShowS
FontWeight -> String
(Int -> FontWeight -> ShowS)
-> (FontWeight -> String)
-> ([FontWeight] -> ShowS)
-> Show FontWeight
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontWeight] -> ShowS
$cshowList :: [FontWeight] -> ShowS
show :: FontWeight -> String
$cshow :: FontWeight -> String
showsPrec :: Int -> FontWeight -> ShowS
$cshowsPrec :: Int -> FontWeight -> ShowS
Show, FontWeight -> FontWeight -> Bool
(FontWeight -> FontWeight -> Bool)
-> (FontWeight -> FontWeight -> Bool) -> Eq FontWeight
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontWeight -> FontWeight -> Bool
$c/= :: FontWeight -> FontWeight -> Bool
== :: FontWeight -> FontWeight -> Bool
$c== :: FontWeight -> FontWeight -> Bool
Eq, Eq FontWeight
Eq FontWeight
-> (FontWeight -> FontWeight -> Ordering)
-> (FontWeight -> FontWeight -> Bool)
-> (FontWeight -> FontWeight -> Bool)
-> (FontWeight -> FontWeight -> Bool)
-> (FontWeight -> FontWeight -> Bool)
-> (FontWeight -> FontWeight -> FontWeight)
-> (FontWeight -> FontWeight -> FontWeight)
-> Ord FontWeight
FontWeight -> FontWeight -> Bool
FontWeight -> FontWeight -> Ordering
FontWeight -> FontWeight -> FontWeight
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FontWeight -> FontWeight -> FontWeight
$cmin :: FontWeight -> FontWeight -> FontWeight
max :: FontWeight -> FontWeight -> FontWeight
$cmax :: FontWeight -> FontWeight -> FontWeight
>= :: FontWeight -> FontWeight -> Bool
$c>= :: FontWeight -> FontWeight -> Bool
> :: FontWeight -> FontWeight -> Bool
$c> :: FontWeight -> FontWeight -> Bool
<= :: FontWeight -> FontWeight -> Bool
$c<= :: FontWeight -> FontWeight -> Bool
< :: FontWeight -> FontWeight -> Bool
$c< :: FontWeight -> FontWeight -> Bool
compare :: FontWeight -> FontWeight -> Ordering
$ccompare :: FontWeight -> FontWeight -> Ordering
$cp1Ord :: Eq FontWeight
Ord)

-- | The default font weight.
instance Default FontWeight where
  def :: FontWeight
def = FontWeight
FontWeightNormal

-- | Data type for a font.
data FontStyle = FontStyle {
      FontStyle -> String
_font_name   :: String,
      -- ^ The font family or font face to use.
      FontStyle -> Double
_font_size   :: Double,
      -- ^ The height of the rendered font in device coordinates.
      FontStyle -> FontSlant
_font_slant  :: FontSlant,
      -- ^ The slant to render with.
      FontStyle -> FontWeight
_font_weight :: FontWeight,
      -- ^ The weight to render with.
      FontStyle -> AlphaColour Double
_font_color  :: AlphaColour Double
      -- ^ The color to render text with.
} deriving (Int -> FontStyle -> ShowS
[FontStyle] -> ShowS
FontStyle -> String
(Int -> FontStyle -> ShowS)
-> (FontStyle -> String)
-> ([FontStyle] -> ShowS)
-> Show FontStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontStyle] -> ShowS
$cshowList :: [FontStyle] -> ShowS
show :: FontStyle -> String
$cshow :: FontStyle -> String
showsPrec :: Int -> FontStyle -> ShowS
$cshowsPrec :: Int -> FontStyle -> ShowS
Show, FontStyle -> FontStyle -> Bool
(FontStyle -> FontStyle -> Bool)
-> (FontStyle -> FontStyle -> Bool) -> Eq FontStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontStyle -> FontStyle -> Bool
$c/= :: FontStyle -> FontStyle -> Bool
== :: FontStyle -> FontStyle -> Bool
$c== :: FontStyle -> FontStyle -> Bool
Eq)

-- | The default font style.
instance Default FontStyle where
  def :: FontStyle
def = FontStyle :: String
-> Double
-> FontSlant
-> FontWeight
-> AlphaColour Double
-> FontStyle
FontStyle 
    { _font_name :: String
_font_name   = String
"sans-serif"
    , _font_size :: Double
_font_size   = Double
10
    , _font_slant :: FontSlant
_font_slant  = FontSlant
forall a. Default a => a
def
    , _font_weight :: FontWeight
_font_weight = FontWeight
forall a. Default a => a
def
    , _font_color :: AlphaColour Double
_font_color  = Colour Double -> AlphaColour Double
forall a. Num a => Colour a -> AlphaColour a
opaque Colour Double
forall a. Num a => Colour a
black
    }

-- | Possible horizontal anchor points for text.
data HTextAnchor = HTA_Left 
                 | HTA_Centre 
                 | HTA_Right 
                 deriving (Int -> HTextAnchor -> ShowS
[HTextAnchor] -> ShowS
HTextAnchor -> String
(Int -> HTextAnchor -> ShowS)
-> (HTextAnchor -> String)
-> ([HTextAnchor] -> ShowS)
-> Show HTextAnchor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HTextAnchor] -> ShowS
$cshowList :: [HTextAnchor] -> ShowS
show :: HTextAnchor -> String
$cshow :: HTextAnchor -> String
showsPrec :: Int -> HTextAnchor -> ShowS
$cshowsPrec :: Int -> HTextAnchor -> ShowS
Show, HTextAnchor -> HTextAnchor -> Bool
(HTextAnchor -> HTextAnchor -> Bool)
-> (HTextAnchor -> HTextAnchor -> Bool) -> Eq HTextAnchor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HTextAnchor -> HTextAnchor -> Bool
$c/= :: HTextAnchor -> HTextAnchor -> Bool
== :: HTextAnchor -> HTextAnchor -> Bool
$c== :: HTextAnchor -> HTextAnchor -> Bool
Eq, Eq HTextAnchor
Eq HTextAnchor
-> (HTextAnchor -> HTextAnchor -> Ordering)
-> (HTextAnchor -> HTextAnchor -> Bool)
-> (HTextAnchor -> HTextAnchor -> Bool)
-> (HTextAnchor -> HTextAnchor -> Bool)
-> (HTextAnchor -> HTextAnchor -> Bool)
-> (HTextAnchor -> HTextAnchor -> HTextAnchor)
-> (HTextAnchor -> HTextAnchor -> HTextAnchor)
-> Ord HTextAnchor
HTextAnchor -> HTextAnchor -> Bool
HTextAnchor -> HTextAnchor -> Ordering
HTextAnchor -> HTextAnchor -> HTextAnchor
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: HTextAnchor -> HTextAnchor -> HTextAnchor
$cmin :: HTextAnchor -> HTextAnchor -> HTextAnchor
max :: HTextAnchor -> HTextAnchor -> HTextAnchor
$cmax :: HTextAnchor -> HTextAnchor -> HTextAnchor
>= :: HTextAnchor -> HTextAnchor -> Bool
$c>= :: HTextAnchor -> HTextAnchor -> Bool
> :: HTextAnchor -> HTextAnchor -> Bool
$c> :: HTextAnchor -> HTextAnchor -> Bool
<= :: HTextAnchor -> HTextAnchor -> Bool
$c<= :: HTextAnchor -> HTextAnchor -> Bool
< :: HTextAnchor -> HTextAnchor -> Bool
$c< :: HTextAnchor -> HTextAnchor -> Bool
compare :: HTextAnchor -> HTextAnchor -> Ordering
$ccompare :: HTextAnchor -> HTextAnchor -> Ordering
$cp1Ord :: Eq HTextAnchor
Ord)

-- | Possible vertical anchor points for text.
data VTextAnchor = VTA_Top 
                 | VTA_Centre 
                 | VTA_Bottom 
                 | VTA_BaseLine 
                 deriving (Int -> VTextAnchor -> ShowS
[VTextAnchor] -> ShowS
VTextAnchor -> String
(Int -> VTextAnchor -> ShowS)
-> (VTextAnchor -> String)
-> ([VTextAnchor] -> ShowS)
-> Show VTextAnchor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VTextAnchor] -> ShowS
$cshowList :: [VTextAnchor] -> ShowS
show :: VTextAnchor -> String
$cshow :: VTextAnchor -> String
showsPrec :: Int -> VTextAnchor -> ShowS
$cshowsPrec :: Int -> VTextAnchor -> ShowS
Show, VTextAnchor -> VTextAnchor -> Bool
(VTextAnchor -> VTextAnchor -> Bool)
-> (VTextAnchor -> VTextAnchor -> Bool) -> Eq VTextAnchor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VTextAnchor -> VTextAnchor -> Bool
$c/= :: VTextAnchor -> VTextAnchor -> Bool
== :: VTextAnchor -> VTextAnchor -> Bool
$c== :: VTextAnchor -> VTextAnchor -> Bool
Eq, Eq VTextAnchor
Eq VTextAnchor
-> (VTextAnchor -> VTextAnchor -> Ordering)
-> (VTextAnchor -> VTextAnchor -> Bool)
-> (VTextAnchor -> VTextAnchor -> Bool)
-> (VTextAnchor -> VTextAnchor -> Bool)
-> (VTextAnchor -> VTextAnchor -> Bool)
-> (VTextAnchor -> VTextAnchor -> VTextAnchor)
-> (VTextAnchor -> VTextAnchor -> VTextAnchor)
-> Ord VTextAnchor
VTextAnchor -> VTextAnchor -> Bool
VTextAnchor -> VTextAnchor -> Ordering
VTextAnchor -> VTextAnchor -> VTextAnchor
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VTextAnchor -> VTextAnchor -> VTextAnchor
$cmin :: VTextAnchor -> VTextAnchor -> VTextAnchor
max :: VTextAnchor -> VTextAnchor -> VTextAnchor
$cmax :: VTextAnchor -> VTextAnchor -> VTextAnchor
>= :: VTextAnchor -> VTextAnchor -> Bool
$c>= :: VTextAnchor -> VTextAnchor -> Bool
> :: VTextAnchor -> VTextAnchor -> Bool
$c> :: VTextAnchor -> VTextAnchor -> Bool
<= :: VTextAnchor -> VTextAnchor -> Bool
$c<= :: VTextAnchor -> VTextAnchor -> Bool
< :: VTextAnchor -> VTextAnchor -> Bool
$c< :: VTextAnchor -> VTextAnchor -> Bool
compare :: VTextAnchor -> VTextAnchor -> Ordering
$ccompare :: VTextAnchor -> VTextAnchor -> Ordering
$cp1Ord :: Eq VTextAnchor
Ord)

-- | Text metrics returned by 'textSize'.
data TextSize = TextSize 
  { TextSize -> Double
textSizeWidth    :: Double -- ^ The total width of the text.
  , TextSize -> Double
textSizeAscent   :: Double -- ^ The ascent or space above the baseline.
  , TextSize -> Double
textSizeDescent  :: Double -- ^ The decent or space below the baseline.
  , TextSize -> Double
textSizeYBearing :: Double -- ^ The Y bearing.
  , TextSize -> Double
textSizeHeight   :: Double -- ^ The total height of the text.
  } deriving (Int -> TextSize -> ShowS
[TextSize] -> ShowS
TextSize -> String
(Int -> TextSize -> ShowS)
-> (TextSize -> String) -> ([TextSize] -> ShowS) -> Show TextSize
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextSize] -> ShowS
$cshowList :: [TextSize] -> ShowS
show :: TextSize -> String
$cshow :: TextSize -> String
showsPrec :: Int -> TextSize -> ShowS
$cshowsPrec :: Int -> TextSize -> ShowS
Show, TextSize -> TextSize -> Bool
(TextSize -> TextSize -> Bool)
-> (TextSize -> TextSize -> Bool) -> Eq TextSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextSize -> TextSize -> Bool
$c/= :: TextSize -> TextSize -> Bool
== :: TextSize -> TextSize -> Bool
$c== :: TextSize -> TextSize -> Bool
Eq)

-- -----------------------------------------------------------------------
-- Fill Types
-- -----------------------------------------------------------------------

-- | Abstract data type for a fill style.
--
--   The contained action sets the required fill
--   style in the rendering state.
newtype FillStyle = FillStyleSolid 
  { FillStyle -> AlphaColour Double
_fill_color :: AlphaColour Double 
  } deriving (Int -> FillStyle -> ShowS
[FillStyle] -> ShowS
FillStyle -> String
(Int -> FillStyle -> ShowS)
-> (FillStyle -> String)
-> ([FillStyle] -> ShowS)
-> Show FillStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FillStyle] -> ShowS
$cshowList :: [FillStyle] -> ShowS
show :: FillStyle -> String
$cshow :: FillStyle -> String
showsPrec :: Int -> FillStyle -> ShowS
$cshowsPrec :: Int -> FillStyle -> ShowS
Show, FillStyle -> FillStyle -> Bool
(FillStyle -> FillStyle -> Bool)
-> (FillStyle -> FillStyle -> Bool) -> Eq FillStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FillStyle -> FillStyle -> Bool
$c/= :: FillStyle -> FillStyle -> Bool
== :: FillStyle -> FillStyle -> Bool
$c== :: FillStyle -> FillStyle -> Bool
Eq)

-- | The default fill style.
instance Default FillStyle where
  def :: FillStyle
def = FillStyleSolid :: AlphaColour Double -> FillStyle
FillStyleSolid { _fill_color :: AlphaColour Double
_fill_color = Colour Double -> AlphaColour Double
forall a. Num a => Colour a -> AlphaColour a
opaque Colour Double
forall a. (Ord a, Floating a) => Colour a
white }

-------------------------------------------------------------------------

-- | A function to align points for a certain rendering device.
type AlignmentFn = Point -> Point

-- | Holds the point and coordinate alignment function.
data AlignmentFns = AlignmentFns {
  AlignmentFns -> AlignmentFn
afPointAlignFn :: AlignmentFn,
  -- ^ An adjustment applied immediately prior to points
  --   being displayed in device coordinates.
  --
  --   When device coordinates correspond to pixels, a cleaner
  --   image is created if this transform rounds to the nearest
  --   pixel. With higher-resolution output, this transform can
  --   just be the identity function.
  --   
  --   This is usually used to align prior to stroking.

  -- | The adjustment applied immediately prior to coordinates
  --   being transformed.
  --   
  --   This is usually used to align prior to filling.
  AlignmentFns -> AlignmentFn
afCoordAlignFn :: AlignmentFn
  }

-- | Alignment to render on raster based graphics.
bitmapAlignmentFns :: AlignmentFns
bitmapAlignmentFns :: AlignmentFns
bitmapAlignmentFns = AlignmentFn -> AlignmentFn -> AlignmentFns
AlignmentFns (Double -> AlignmentFn
adjfn Double
0.5) (Double -> AlignmentFn
adjfn Double
0.0) 
  where
    adjfn :: Double -> AlignmentFn
adjfn Double
offset (Point Double
x Double
y) = Double -> Double -> Point
Point (Double -> Double
adj Double
x) (Double -> Double
adj Double
y)
      where
        -- avoid messages about Integer default
        rnd :: Double -> Integer
        rnd :: Double -> Integer
rnd = Double -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
round
        adj :: Double -> Double
adj Double
v = (Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral(Integer -> Double) -> (Double -> Integer) -> Double -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Double -> Integer
rnd) Double
v Double -> Double -> Double
forall a. Num a => a -> a -> a
+Double
offset

-- | Alignment to render on vector based graphics.
vectorAlignmentFns :: AlignmentFns
vectorAlignmentFns :: AlignmentFns
vectorAlignmentFns = AlignmentFn -> AlignmentFn -> AlignmentFns
AlignmentFns AlignmentFn
forall a. a -> a
id AlignmentFn
forall a. a -> a
id

$( makeLenses ''LineStyle )
$( makeLenses ''FontStyle )
$( makeLenses ''FillStyle )