{-|
Module      : Monomer.Core.StyleTypes
Copyright   : (c) 2018 Francisco Vallarino
License     : BSD-3-Clause (see the LICENSE file)
Maintainer  : fjvallarino@gmail.com
Stability   : experimental
Portability : non-portable

Basic types for styling widgets.
-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE StrictData #-}

module Monomer.Core.StyleTypes where

import Control.Applicative ((<|>))
import Data.Default
import GHC.Generics

import Monomer.Common
import Monomer.Graphics.Types
import Monomer.Graphics.Util

{-|
Represents a size requirement for a specific axis. Mainly used by stack and box,
with grid using it as the base for its calculations. Each field represents:

- Fixed: A minimum size required by the widget. This type of space is the first
that gets assigned.
- Flex: Additional space the widget accepts, up to the provided value. After
fixed requirements are satisfied, flex sizes are assigned proportionally
considering factor.
- Extra: After flex is satisfied, the remaining space is distributed
proportionally, considering factor, to all non zero extra requirements. There is
no limit to how much extra space can be assigned.
- Factor: How much flex/extra space a widget will get proportionally. This also
affects how much a requirement is willing to lose: a value less than 1 can
receive less space, but gives up less too.
-}
data SizeReq = SizeReq {
  SizeReq -> Double
_szrFixed :: Double,
  SizeReq -> Double
_szrFlex :: Double,
  SizeReq -> Double
_szrExtra :: Double,
  SizeReq -> Double
_szrFactor :: Factor
} deriving (SizeReq -> SizeReq -> Bool
(SizeReq -> SizeReq -> Bool)
-> (SizeReq -> SizeReq -> Bool) -> Eq SizeReq
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SizeReq -> SizeReq -> Bool
$c/= :: SizeReq -> SizeReq -> Bool
== :: SizeReq -> SizeReq -> Bool
$c== :: SizeReq -> SizeReq -> Bool
Eq, Int -> SizeReq -> ShowS
[SizeReq] -> ShowS
SizeReq -> String
(Int -> SizeReq -> ShowS)
-> (SizeReq -> String) -> ([SizeReq] -> ShowS) -> Show SizeReq
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SizeReq] -> ShowS
$cshowList :: [SizeReq] -> ShowS
show :: SizeReq -> String
$cshow :: SizeReq -> String
showsPrec :: Int -> SizeReq -> ShowS
$cshowsPrec :: Int -> SizeReq -> ShowS
Show, (forall x. SizeReq -> Rep SizeReq x)
-> (forall x. Rep SizeReq x -> SizeReq) -> Generic SizeReq
forall x. Rep SizeReq x -> SizeReq
forall x. SizeReq -> Rep SizeReq x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SizeReq x -> SizeReq
$cfrom :: forall x. SizeReq -> Rep SizeReq x
Generic)

instance Default SizeReq where
  def :: SizeReq
def = SizeReq :: Double -> Double -> Double -> Double -> SizeReq
SizeReq {
    _szrFixed :: Double
_szrFixed = Double
0,
    _szrFlex :: Double
_szrFlex = Double
0,
    _szrExtra :: Double
_szrExtra = Double
0,
    _szrFactor :: Double
_szrFactor = Double
1
  }

-- | Different mouse pointer types.
data CursorIcon
  = CursorArrow
  | CursorHand
  | CursorIBeam
  | CursorInvalid
  | CursorSizeH
  | CursorSizeV
  | CursorDiagTL
  | CursorDiagTR
  deriving (CursorIcon -> CursorIcon -> Bool
(CursorIcon -> CursorIcon -> Bool)
-> (CursorIcon -> CursorIcon -> Bool) -> Eq CursorIcon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CursorIcon -> CursorIcon -> Bool
$c/= :: CursorIcon -> CursorIcon -> Bool
== :: CursorIcon -> CursorIcon -> Bool
$c== :: CursorIcon -> CursorIcon -> Bool
Eq, Eq CursorIcon
Eq CursorIcon
-> (CursorIcon -> CursorIcon -> Ordering)
-> (CursorIcon -> CursorIcon -> Bool)
-> (CursorIcon -> CursorIcon -> Bool)
-> (CursorIcon -> CursorIcon -> Bool)
-> (CursorIcon -> CursorIcon -> Bool)
-> (CursorIcon -> CursorIcon -> CursorIcon)
-> (CursorIcon -> CursorIcon -> CursorIcon)
-> Ord CursorIcon
CursorIcon -> CursorIcon -> Bool
CursorIcon -> CursorIcon -> Ordering
CursorIcon -> CursorIcon -> CursorIcon
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 :: CursorIcon -> CursorIcon -> CursorIcon
$cmin :: CursorIcon -> CursorIcon -> CursorIcon
max :: CursorIcon -> CursorIcon -> CursorIcon
$cmax :: CursorIcon -> CursorIcon -> CursorIcon
>= :: CursorIcon -> CursorIcon -> Bool
$c>= :: CursorIcon -> CursorIcon -> Bool
> :: CursorIcon -> CursorIcon -> Bool
$c> :: CursorIcon -> CursorIcon -> Bool
<= :: CursorIcon -> CursorIcon -> Bool
$c<= :: CursorIcon -> CursorIcon -> Bool
< :: CursorIcon -> CursorIcon -> Bool
$c< :: CursorIcon -> CursorIcon -> Bool
compare :: CursorIcon -> CursorIcon -> Ordering
$ccompare :: CursorIcon -> CursorIcon -> Ordering
$cp1Ord :: Eq CursorIcon
Ord, Int -> CursorIcon
CursorIcon -> Int
CursorIcon -> [CursorIcon]
CursorIcon -> CursorIcon
CursorIcon -> CursorIcon -> [CursorIcon]
CursorIcon -> CursorIcon -> CursorIcon -> [CursorIcon]
(CursorIcon -> CursorIcon)
-> (CursorIcon -> CursorIcon)
-> (Int -> CursorIcon)
-> (CursorIcon -> Int)
-> (CursorIcon -> [CursorIcon])
-> (CursorIcon -> CursorIcon -> [CursorIcon])
-> (CursorIcon -> CursorIcon -> [CursorIcon])
-> (CursorIcon -> CursorIcon -> CursorIcon -> [CursorIcon])
-> Enum CursorIcon
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: CursorIcon -> CursorIcon -> CursorIcon -> [CursorIcon]
$cenumFromThenTo :: CursorIcon -> CursorIcon -> CursorIcon -> [CursorIcon]
enumFromTo :: CursorIcon -> CursorIcon -> [CursorIcon]
$cenumFromTo :: CursorIcon -> CursorIcon -> [CursorIcon]
enumFromThen :: CursorIcon -> CursorIcon -> [CursorIcon]
$cenumFromThen :: CursorIcon -> CursorIcon -> [CursorIcon]
enumFrom :: CursorIcon -> [CursorIcon]
$cenumFrom :: CursorIcon -> [CursorIcon]
fromEnum :: CursorIcon -> Int
$cfromEnum :: CursorIcon -> Int
toEnum :: Int -> CursorIcon
$ctoEnum :: Int -> CursorIcon
pred :: CursorIcon -> CursorIcon
$cpred :: CursorIcon -> CursorIcon
succ :: CursorIcon -> CursorIcon
$csucc :: CursorIcon -> CursorIcon
Enum, Int -> CursorIcon -> ShowS
[CursorIcon] -> ShowS
CursorIcon -> String
(Int -> CursorIcon -> ShowS)
-> (CursorIcon -> String)
-> ([CursorIcon] -> ShowS)
-> Show CursorIcon
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CursorIcon] -> ShowS
$cshowList :: [CursorIcon] -> ShowS
show :: CursorIcon -> String
$cshow :: CursorIcon -> String
showsPrec :: Int -> CursorIcon -> ShowS
$cshowsPrec :: Int -> CursorIcon -> ShowS
Show, (forall x. CursorIcon -> Rep CursorIcon x)
-> (forall x. Rep CursorIcon x -> CursorIcon) -> Generic CursorIcon
forall x. Rep CursorIcon x -> CursorIcon
forall x. CursorIcon -> Rep CursorIcon x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CursorIcon x -> CursorIcon
$cfrom :: forall x. CursorIcon -> Rep CursorIcon x
Generic)

instance Default CursorIcon where
  def :: CursorIcon
def = CursorIcon
CursorArrow

{-|
Main style type, comprised of configurations for the different states:

- Basic: Starting state for a widget, without any kind of interaction. This
is used as the base for all other states, which override values as needed.
- Hover: The mouse pointer is on top of the current widget.
- Focus: The widget has keyboard focus.
- Focus-Hover: The widget has keyboard focus and mouse is on top. Without this
state one of Hover or Focus would take precedence and it would not be possible
to specify the desired behavior.
- Active: The mouse button is currently presed and the pointer is within the
boundaries of the widget.
- Disabled: The widget is disabled.
-}
data Style = Style {
  Style -> Maybe StyleState
_styleBasic :: Maybe StyleState,
  Style -> Maybe StyleState
_styleHover :: Maybe StyleState,
  Style -> Maybe StyleState
_styleFocus :: Maybe StyleState,
  Style -> Maybe StyleState
_styleFocusHover :: Maybe StyleState,
  Style -> Maybe StyleState
_styleActive :: Maybe StyleState,
  Style -> Maybe StyleState
_styleDisabled :: Maybe StyleState
} deriving (Style -> Style -> Bool
(Style -> Style -> Bool) -> (Style -> Style -> Bool) -> Eq Style
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Style -> Style -> Bool
$c/= :: Style -> Style -> Bool
== :: Style -> Style -> Bool
$c== :: Style -> Style -> Bool
Eq, Int -> Style -> ShowS
[Style] -> ShowS
Style -> String
(Int -> Style -> ShowS)
-> (Style -> String) -> ([Style] -> ShowS) -> Show Style
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Style] -> ShowS
$cshowList :: [Style] -> ShowS
show :: Style -> String
$cshow :: Style -> String
showsPrec :: Int -> Style -> ShowS
$cshowsPrec :: Int -> Style -> ShowS
Show, (forall x. Style -> Rep Style x)
-> (forall x. Rep Style x -> Style) -> Generic Style
forall x. Rep Style x -> Style
forall x. Style -> Rep Style x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Style x -> Style
$cfrom :: forall x. Style -> Rep Style x
Generic)

instance Default Style where
  def :: Style
def = Style :: Maybe StyleState
-> Maybe StyleState
-> Maybe StyleState
-> Maybe StyleState
-> Maybe StyleState
-> Maybe StyleState
-> Style
Style {
    _styleBasic :: Maybe StyleState
_styleBasic = Maybe StyleState
forall a. Maybe a
Nothing,
    _styleHover :: Maybe StyleState
_styleHover = Maybe StyleState
forall a. Maybe a
Nothing,
    _styleFocus :: Maybe StyleState
_styleFocus = Maybe StyleState
forall a. Maybe a
Nothing,
    _styleFocusHover :: Maybe StyleState
_styleFocusHover = Maybe StyleState
forall a. Maybe a
Nothing,
    _styleActive :: Maybe StyleState
_styleActive = Maybe StyleState
forall a. Maybe a
Nothing,
    _styleDisabled :: Maybe StyleState
_styleDisabled = Maybe StyleState
forall a. Maybe a
Nothing
  }

instance Semigroup Style where
  <> :: Style -> Style -> Style
(<>) Style
style1 Style
style2 = Style :: Maybe StyleState
-> Maybe StyleState
-> Maybe StyleState
-> Maybe StyleState
-> Maybe StyleState
-> Maybe StyleState
-> Style
Style {
    _styleBasic :: Maybe StyleState
_styleBasic = Style -> Maybe StyleState
_styleBasic Style
style1 Maybe StyleState -> Maybe StyleState -> Maybe StyleState
forall a. Semigroup a => a -> a -> a
<> Style -> Maybe StyleState
_styleBasic Style
style2,
    _styleHover :: Maybe StyleState
_styleHover = Style -> Maybe StyleState
_styleHover Style
style1 Maybe StyleState -> Maybe StyleState -> Maybe StyleState
forall a. Semigroup a => a -> a -> a
<> Style -> Maybe StyleState
_styleHover Style
style2,
    _styleFocus :: Maybe StyleState
_styleFocus = Style -> Maybe StyleState
_styleFocus Style
style1 Maybe StyleState -> Maybe StyleState -> Maybe StyleState
forall a. Semigroup a => a -> a -> a
<> Style -> Maybe StyleState
_styleFocus Style
style2,
    _styleFocusHover :: Maybe StyleState
_styleFocusHover = Style -> Maybe StyleState
_styleFocusHover Style
style1 Maybe StyleState -> Maybe StyleState -> Maybe StyleState
forall a. Semigroup a => a -> a -> a
<> Style -> Maybe StyleState
_styleFocusHover Style
style2,
    _styleActive :: Maybe StyleState
_styleActive = Style -> Maybe StyleState
_styleActive Style
style1 Maybe StyleState -> Maybe StyleState -> Maybe StyleState
forall a. Semigroup a => a -> a -> a
<> Style -> Maybe StyleState
_styleActive Style
style2,
    _styleDisabled :: Maybe StyleState
_styleDisabled = Style -> Maybe StyleState
_styleDisabled Style
style1 Maybe StyleState -> Maybe StyleState -> Maybe StyleState
forall a. Semigroup a => a -> a -> a
<> Style -> Maybe StyleState
_styleDisabled Style
style2
  }

instance Monoid Style where
  mempty :: Style
mempty = Style
forall a. Default a => a
def

{-|
Customizable style items for a specific state. All values are optional, and can
be combined with the latest values taking precedence when the previous value is
not empty.
-}
data StyleState = StyleState {
  -- | User defined width req. Takes precedence over widget req.
  StyleState -> Maybe SizeReq
_sstSizeReqW :: Maybe SizeReq,
  -- | User defined height req. Takes precedence over widget req.
  StyleState -> Maybe SizeReq
_sstSizeReqH :: Maybe SizeReq,
  -- | Space between the border and the content of the widget
  StyleState -> Maybe Padding
_sstPadding :: Maybe Padding,
  -- | Border definition.
  StyleState -> Maybe Border
_sstBorder :: Maybe Border,
  -- | Radius. Affects both border and background.
  StyleState -> Maybe Radius
_sstRadius :: Maybe Radius,
  -- | Background color.
  StyleState -> Maybe Color
_sstBgColor :: Maybe Color,
  -- | Main foreground color. Each widget decides how it uses it.
  StyleState -> Maybe Color
_sstFgColor :: Maybe Color,
  -- | Secondary foreground color. Each widget decides how it uses it.
  StyleState -> Maybe Color
_sstSndColor :: Maybe Color,
  -- | Highlight color. Each widget decides how it uses it.
  StyleState -> Maybe Color
_sstHlColor :: Maybe Color,
  -- | Text style, including font, size and color.
  StyleState -> Maybe TextStyle
_sstText :: Maybe TextStyle,
  -- | The assigned cursor icon to this specific state.
  StyleState -> Maybe CursorIcon
_sstCursorIcon :: Maybe CursorIcon
} deriving (StyleState -> StyleState -> Bool
(StyleState -> StyleState -> Bool)
-> (StyleState -> StyleState -> Bool) -> Eq StyleState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StyleState -> StyleState -> Bool
$c/= :: StyleState -> StyleState -> Bool
== :: StyleState -> StyleState -> Bool
$c== :: StyleState -> StyleState -> Bool
Eq, Int -> StyleState -> ShowS
[StyleState] -> ShowS
StyleState -> String
(Int -> StyleState -> ShowS)
-> (StyleState -> String)
-> ([StyleState] -> ShowS)
-> Show StyleState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StyleState] -> ShowS
$cshowList :: [StyleState] -> ShowS
show :: StyleState -> String
$cshow :: StyleState -> String
showsPrec :: Int -> StyleState -> ShowS
$cshowsPrec :: Int -> StyleState -> ShowS
Show, (forall x. StyleState -> Rep StyleState x)
-> (forall x. Rep StyleState x -> StyleState) -> Generic StyleState
forall x. Rep StyleState x -> StyleState
forall x. StyleState -> Rep StyleState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StyleState x -> StyleState
$cfrom :: forall x. StyleState -> Rep StyleState x
Generic)

instance Default StyleState where
  def :: StyleState
def = StyleState :: Maybe SizeReq
-> Maybe SizeReq
-> Maybe Padding
-> Maybe Border
-> Maybe Radius
-> Maybe Color
-> Maybe Color
-> Maybe Color
-> Maybe Color
-> Maybe TextStyle
-> Maybe CursorIcon
-> StyleState
StyleState {
    _sstSizeReqW :: Maybe SizeReq
_sstSizeReqW = Maybe SizeReq
forall a. Maybe a
Nothing,
    _sstSizeReqH :: Maybe SizeReq
_sstSizeReqH = Maybe SizeReq
forall a. Maybe a
Nothing,
    _sstPadding :: Maybe Padding
_sstPadding = Maybe Padding
forall a. Maybe a
Nothing,
    _sstBorder :: Maybe Border
_sstBorder = Maybe Border
forall a. Maybe a
Nothing,
    _sstRadius :: Maybe Radius
_sstRadius = Maybe Radius
forall a. Maybe a
Nothing,
    _sstBgColor :: Maybe Color
_sstBgColor = Maybe Color
forall a. Maybe a
Nothing,
    _sstFgColor :: Maybe Color
_sstFgColor = Maybe Color
forall a. Maybe a
Nothing,
    _sstSndColor :: Maybe Color
_sstSndColor = Maybe Color
forall a. Maybe a
Nothing,
    _sstHlColor :: Maybe Color
_sstHlColor = Maybe Color
forall a. Maybe a
Nothing,
    _sstText :: Maybe TextStyle
_sstText = Maybe TextStyle
forall a. Maybe a
Nothing,
    _sstCursorIcon :: Maybe CursorIcon
_sstCursorIcon = Maybe CursorIcon
forall a. Maybe a
Nothing
  }

instance Semigroup StyleState where
  <> :: StyleState -> StyleState -> StyleState
(<>) StyleState
s1 StyleState
s2 = StyleState :: Maybe SizeReq
-> Maybe SizeReq
-> Maybe Padding
-> Maybe Border
-> Maybe Radius
-> Maybe Color
-> Maybe Color
-> Maybe Color
-> Maybe Color
-> Maybe TextStyle
-> Maybe CursorIcon
-> StyleState
StyleState {
    _sstSizeReqW :: Maybe SizeReq
_sstSizeReqW = StyleState -> Maybe SizeReq
_sstSizeReqW StyleState
s2 Maybe SizeReq -> Maybe SizeReq -> Maybe SizeReq
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> StyleState -> Maybe SizeReq
_sstSizeReqW StyleState
s1,
    _sstSizeReqH :: Maybe SizeReq
_sstSizeReqH = StyleState -> Maybe SizeReq
_sstSizeReqH StyleState
s2 Maybe SizeReq -> Maybe SizeReq -> Maybe SizeReq
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> StyleState -> Maybe SizeReq
_sstSizeReqH StyleState
s1,
    _sstPadding :: Maybe Padding
_sstPadding = StyleState -> Maybe Padding
_sstPadding StyleState
s1 Maybe Padding -> Maybe Padding -> Maybe Padding
forall a. Semigroup a => a -> a -> a
<> StyleState -> Maybe Padding
_sstPadding StyleState
s2,
    _sstBorder :: Maybe Border
_sstBorder = StyleState -> Maybe Border
_sstBorder StyleState
s1 Maybe Border -> Maybe Border -> Maybe Border
forall a. Semigroup a => a -> a -> a
<> StyleState -> Maybe Border
_sstBorder StyleState
s2,
    _sstRadius :: Maybe Radius
_sstRadius = StyleState -> Maybe Radius
_sstRadius StyleState
s1 Maybe Radius -> Maybe Radius -> Maybe Radius
forall a. Semigroup a => a -> a -> a
<> StyleState -> Maybe Radius
_sstRadius StyleState
s2,
    _sstBgColor :: Maybe Color
_sstBgColor = StyleState -> Maybe Color
_sstBgColor StyleState
s2 Maybe Color -> Maybe Color -> Maybe Color
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> StyleState -> Maybe Color
_sstBgColor StyleState
s1,
    _sstFgColor :: Maybe Color
_sstFgColor = StyleState -> Maybe Color
_sstFgColor StyleState
s2 Maybe Color -> Maybe Color -> Maybe Color
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> StyleState -> Maybe Color
_sstFgColor StyleState
s1,
    _sstSndColor :: Maybe Color
_sstSndColor = StyleState -> Maybe Color
_sstSndColor StyleState
s2 Maybe Color -> Maybe Color -> Maybe Color
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> StyleState -> Maybe Color
_sstSndColor StyleState
s1,
    _sstHlColor :: Maybe Color
_sstHlColor = StyleState -> Maybe Color
_sstHlColor StyleState
s2 Maybe Color -> Maybe Color -> Maybe Color
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> StyleState -> Maybe Color
_sstHlColor StyleState
s1,
    _sstText :: Maybe TextStyle
_sstText = StyleState -> Maybe TextStyle
_sstText StyleState
s1 Maybe TextStyle -> Maybe TextStyle -> Maybe TextStyle
forall a. Semigroup a => a -> a -> a
<> StyleState -> Maybe TextStyle
_sstText StyleState
s2,
    _sstCursorIcon :: Maybe CursorIcon
_sstCursorIcon = StyleState -> Maybe CursorIcon
_sstCursorIcon StyleState
s2 Maybe CursorIcon -> Maybe CursorIcon -> Maybe CursorIcon
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> StyleState -> Maybe CursorIcon
_sstCursorIcon StyleState
s1
  }

instance Monoid StyleState where
  mempty :: StyleState
mempty = StyleState
forall a. Default a => a
def

-- | Padding definitions (space between border and content) for each side.
data Padding = Padding {
  Padding -> Maybe Double
_padLeft :: Maybe Double,
  Padding -> Maybe Double
_padRight :: Maybe Double,
  Padding -> Maybe Double
_padTop :: Maybe Double,
  Padding -> Maybe Double
_padBottom :: Maybe Double
} deriving (Padding -> Padding -> Bool
(Padding -> Padding -> Bool)
-> (Padding -> Padding -> Bool) -> Eq Padding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Padding -> Padding -> Bool
$c/= :: Padding -> Padding -> Bool
== :: Padding -> Padding -> Bool
$c== :: Padding -> Padding -> Bool
Eq, Int -> Padding -> ShowS
[Padding] -> ShowS
Padding -> String
(Int -> Padding -> ShowS)
-> (Padding -> String) -> ([Padding] -> ShowS) -> Show Padding
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Padding] -> ShowS
$cshowList :: [Padding] -> ShowS
show :: Padding -> String
$cshow :: Padding -> String
showsPrec :: Int -> Padding -> ShowS
$cshowsPrec :: Int -> Padding -> ShowS
Show, (forall x. Padding -> Rep Padding x)
-> (forall x. Rep Padding x -> Padding) -> Generic Padding
forall x. Rep Padding x -> Padding
forall x. Padding -> Rep Padding x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Padding x -> Padding
$cfrom :: forall x. Padding -> Rep Padding x
Generic)

instance Default Padding where
  def :: Padding
def = Padding :: Maybe Double
-> Maybe Double -> Maybe Double -> Maybe Double -> Padding
Padding {
    _padLeft :: Maybe Double
_padLeft = Maybe Double
forall a. Maybe a
Nothing,
    _padRight :: Maybe Double
_padRight = Maybe Double
forall a. Maybe a
Nothing,
    _padTop :: Maybe Double
_padTop = Maybe Double
forall a. Maybe a
Nothing,
    _padBottom :: Maybe Double
_padBottom = Maybe Double
forall a. Maybe a
Nothing
  }

instance Semigroup Padding where
  <> :: Padding -> Padding -> Padding
(<>) Padding
p1 Padding
p2 = Padding :: Maybe Double
-> Maybe Double -> Maybe Double -> Maybe Double -> Padding
Padding {
    _padLeft :: Maybe Double
_padLeft = Padding -> Maybe Double
_padLeft Padding
p2 Maybe Double -> Maybe Double -> Maybe Double
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Padding -> Maybe Double
_padLeft Padding
p1,
    _padRight :: Maybe Double
_padRight = Padding -> Maybe Double
_padRight Padding
p2 Maybe Double -> Maybe Double -> Maybe Double
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Padding -> Maybe Double
_padRight Padding
p1,
    _padTop :: Maybe Double
_padTop = Padding -> Maybe Double
_padTop Padding
p2 Maybe Double -> Maybe Double -> Maybe Double
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Padding -> Maybe Double
_padTop Padding
p1,
    _padBottom :: Maybe Double
_padBottom = Padding -> Maybe Double
_padBottom Padding
p2 Maybe Double -> Maybe Double -> Maybe Double
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Padding -> Maybe Double
_padBottom Padding
p1
  }

instance Monoid Padding where
  mempty :: Padding
mempty = Padding
forall a. Default a => a
def

-- | Defines width and color for a given border side.
data BorderSide = BorderSide {
  BorderSide -> Double
_bsWidth :: Double,
  BorderSide -> Color
_bsColor :: Color
} deriving (BorderSide -> BorderSide -> Bool
(BorderSide -> BorderSide -> Bool)
-> (BorderSide -> BorderSide -> Bool) -> Eq BorderSide
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BorderSide -> BorderSide -> Bool
$c/= :: BorderSide -> BorderSide -> Bool
== :: BorderSide -> BorderSide -> Bool
$c== :: BorderSide -> BorderSide -> Bool
Eq, Int -> BorderSide -> ShowS
[BorderSide] -> ShowS
BorderSide -> String
(Int -> BorderSide -> ShowS)
-> (BorderSide -> String)
-> ([BorderSide] -> ShowS)
-> Show BorderSide
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BorderSide] -> ShowS
$cshowList :: [BorderSide] -> ShowS
show :: BorderSide -> String
$cshow :: BorderSide -> String
showsPrec :: Int -> BorderSide -> ShowS
$cshowsPrec :: Int -> BorderSide -> ShowS
Show, (forall x. BorderSide -> Rep BorderSide x)
-> (forall x. Rep BorderSide x -> BorderSide) -> Generic BorderSide
forall x. Rep BorderSide x -> BorderSide
forall x. BorderSide -> Rep BorderSide x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BorderSide x -> BorderSide
$cfrom :: forall x. BorderSide -> Rep BorderSide x
Generic)

instance Default BorderSide where
  def :: BorderSide
def = BorderSide :: Double -> Color -> BorderSide
BorderSide {
    _bsWidth :: Double
_bsWidth = Double
0,
    _bsColor :: Color
_bsColor = Color
forall a. Default a => a
def
  }

instance Semigroup BorderSide where
  <> :: BorderSide -> BorderSide -> BorderSide
(<>) BorderSide
b1 BorderSide
b2 = BorderSide
b2

instance Monoid BorderSide where
  mempty :: BorderSide
mempty = BorderSide
forall a. Default a => a
def

-- | Border definitions for each side.
data Border = Border {
  Border -> Maybe BorderSide
_brdLeft :: Maybe BorderSide,
  Border -> Maybe BorderSide
_brdRight :: Maybe BorderSide,
  Border -> Maybe BorderSide
_brdTop :: Maybe BorderSide,
  Border -> Maybe BorderSide
_brdBottom :: Maybe BorderSide
} deriving (Border -> Border -> Bool
(Border -> Border -> Bool)
-> (Border -> Border -> Bool) -> Eq Border
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Border -> Border -> Bool
$c/= :: Border -> Border -> Bool
== :: Border -> Border -> Bool
$c== :: Border -> Border -> Bool
Eq, Int -> Border -> ShowS
[Border] -> ShowS
Border -> String
(Int -> Border -> ShowS)
-> (Border -> String) -> ([Border] -> ShowS) -> Show Border
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Border] -> ShowS
$cshowList :: [Border] -> ShowS
show :: Border -> String
$cshow :: Border -> String
showsPrec :: Int -> Border -> ShowS
$cshowsPrec :: Int -> Border -> ShowS
Show, (forall x. Border -> Rep Border x)
-> (forall x. Rep Border x -> Border) -> Generic Border
forall x. Rep Border x -> Border
forall x. Border -> Rep Border x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Border x -> Border
$cfrom :: forall x. Border -> Rep Border x
Generic)

instance Default Border where
  def :: Border
def = Border :: Maybe BorderSide
-> Maybe BorderSide
-> Maybe BorderSide
-> Maybe BorderSide
-> Border
Border {
    _brdLeft :: Maybe BorderSide
_brdLeft = Maybe BorderSide
forall a. Maybe a
Nothing,
    _brdRight :: Maybe BorderSide
_brdRight = Maybe BorderSide
forall a. Maybe a
Nothing,
    _brdTop :: Maybe BorderSide
_brdTop = Maybe BorderSide
forall a. Maybe a
Nothing,
    _brdBottom :: Maybe BorderSide
_brdBottom = Maybe BorderSide
forall a. Maybe a
Nothing
  }

instance Semigroup Border where
  <> :: Border -> Border -> Border
(<>) Border
b1 Border
b2 = Border :: Maybe BorderSide
-> Maybe BorderSide
-> Maybe BorderSide
-> Maybe BorderSide
-> Border
Border {
    _brdLeft :: Maybe BorderSide
_brdLeft = Border -> Maybe BorderSide
_brdLeft Border
b1 Maybe BorderSide -> Maybe BorderSide -> Maybe BorderSide
forall a. Semigroup a => a -> a -> a
<> Border -> Maybe BorderSide
_brdLeft Border
b2,
    _brdRight :: Maybe BorderSide
_brdRight = Border -> Maybe BorderSide
_brdRight Border
b1 Maybe BorderSide -> Maybe BorderSide -> Maybe BorderSide
forall a. Semigroup a => a -> a -> a
<> Border -> Maybe BorderSide
_brdRight Border
b2,
    _brdTop :: Maybe BorderSide
_brdTop = Border -> Maybe BorderSide
_brdTop Border
b1 Maybe BorderSide -> Maybe BorderSide -> Maybe BorderSide
forall a. Semigroup a => a -> a -> a
<> Border -> Maybe BorderSide
_brdTop Border
b2,
    _brdBottom :: Maybe BorderSide
_brdBottom = Border -> Maybe BorderSide
_brdBottom Border
b1 Maybe BorderSide -> Maybe BorderSide -> Maybe BorderSide
forall a. Semigroup a => a -> a -> a
<> Border -> Maybe BorderSide
_brdBottom Border
b2
  }

instance Monoid Border where
  mempty :: Border
mempty = Border
forall a. Default a => a
def

-- | Type of corner radius.
data RadiusType
  = RadiusInner
  | RadiusBoth
  deriving (RadiusType -> RadiusType -> Bool
(RadiusType -> RadiusType -> Bool)
-> (RadiusType -> RadiusType -> Bool) -> Eq RadiusType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RadiusType -> RadiusType -> Bool
$c/= :: RadiusType -> RadiusType -> Bool
== :: RadiusType -> RadiusType -> Bool
$c== :: RadiusType -> RadiusType -> Bool
Eq, Int -> RadiusType -> ShowS
[RadiusType] -> ShowS
RadiusType -> String
(Int -> RadiusType -> ShowS)
-> (RadiusType -> String)
-> ([RadiusType] -> ShowS)
-> Show RadiusType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RadiusType] -> ShowS
$cshowList :: [RadiusType] -> ShowS
show :: RadiusType -> String
$cshow :: RadiusType -> String
showsPrec :: Int -> RadiusType -> ShowS
$cshowsPrec :: Int -> RadiusType -> ShowS
Show, (forall x. RadiusType -> Rep RadiusType x)
-> (forall x. Rep RadiusType x -> RadiusType) -> Generic RadiusType
forall x. Rep RadiusType x -> RadiusType
forall x. RadiusType -> Rep RadiusType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RadiusType x -> RadiusType
$cfrom :: forall x. RadiusType -> Rep RadiusType x
Generic)

instance Default RadiusType where
  def :: RadiusType
def = RadiusType
RadiusBoth

instance Semigroup RadiusType where
  <> :: RadiusType -> RadiusType -> RadiusType
(<>) RadiusType
rc1 RadiusType
rc2 = RadiusType
rc2

instance Monoid RadiusType where
  mempty :: RadiusType
mempty = RadiusType
forall a. Default a => a
def

-- | Defines radius type and width/radius for a given corner.
newtype RadiusCorner = RadiusCorner {
  RadiusCorner -> Double
_rcrWidth :: Double
} deriving (RadiusCorner -> RadiusCorner -> Bool
(RadiusCorner -> RadiusCorner -> Bool)
-> (RadiusCorner -> RadiusCorner -> Bool) -> Eq RadiusCorner
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RadiusCorner -> RadiusCorner -> Bool
$c/= :: RadiusCorner -> RadiusCorner -> Bool
== :: RadiusCorner -> RadiusCorner -> Bool
$c== :: RadiusCorner -> RadiusCorner -> Bool
Eq, Int -> RadiusCorner -> ShowS
[RadiusCorner] -> ShowS
RadiusCorner -> String
(Int -> RadiusCorner -> ShowS)
-> (RadiusCorner -> String)
-> ([RadiusCorner] -> ShowS)
-> Show RadiusCorner
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RadiusCorner] -> ShowS
$cshowList :: [RadiusCorner] -> ShowS
show :: RadiusCorner -> String
$cshow :: RadiusCorner -> String
showsPrec :: Int -> RadiusCorner -> ShowS
$cshowsPrec :: Int -> RadiusCorner -> ShowS
Show, (forall x. RadiusCorner -> Rep RadiusCorner x)
-> (forall x. Rep RadiusCorner x -> RadiusCorner)
-> Generic RadiusCorner
forall x. Rep RadiusCorner x -> RadiusCorner
forall x. RadiusCorner -> Rep RadiusCorner x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RadiusCorner x -> RadiusCorner
$cfrom :: forall x. RadiusCorner -> Rep RadiusCorner x
Generic)

instance Default RadiusCorner where
  def :: RadiusCorner
def = RadiusCorner :: Double -> RadiusCorner
RadiusCorner {
    _rcrWidth :: Double
_rcrWidth = Double
forall a. Default a => a
def
  }

instance Semigroup RadiusCorner where
  <> :: RadiusCorner -> RadiusCorner -> RadiusCorner
(<>) RadiusCorner
rc1 RadiusCorner
rc2 = RadiusCorner
rc2

instance Monoid RadiusCorner where
  mempty :: RadiusCorner
mempty = RadiusCorner
forall a. Default a => a
def

-- | Provides radius definitions for each corner.
data Radius = Radius {
  Radius -> Maybe RadiusCorner
_radTopLeft :: Maybe RadiusCorner,
  Radius -> Maybe RadiusCorner
_radTopRight :: Maybe RadiusCorner,
  Radius -> Maybe RadiusCorner
_radBottomLeft :: Maybe RadiusCorner,
  Radius -> Maybe RadiusCorner
_radBottomRight :: Maybe RadiusCorner
} deriving (Radius -> Radius -> Bool
(Radius -> Radius -> Bool)
-> (Radius -> Radius -> Bool) -> Eq Radius
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Radius -> Radius -> Bool
$c/= :: Radius -> Radius -> Bool
== :: Radius -> Radius -> Bool
$c== :: Radius -> Radius -> Bool
Eq, Int -> Radius -> ShowS
[Radius] -> ShowS
Radius -> String
(Int -> Radius -> ShowS)
-> (Radius -> String) -> ([Radius] -> ShowS) -> Show Radius
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Radius] -> ShowS
$cshowList :: [Radius] -> ShowS
show :: Radius -> String
$cshow :: Radius -> String
showsPrec :: Int -> Radius -> ShowS
$cshowsPrec :: Int -> Radius -> ShowS
Show, (forall x. Radius -> Rep Radius x)
-> (forall x. Rep Radius x -> Radius) -> Generic Radius
forall x. Rep Radius x -> Radius
forall x. Radius -> Rep Radius x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Radius x -> Radius
$cfrom :: forall x. Radius -> Rep Radius x
Generic)

instance Default Radius where
  def :: Radius
def = Radius :: Maybe RadiusCorner
-> Maybe RadiusCorner
-> Maybe RadiusCorner
-> Maybe RadiusCorner
-> Radius
Radius {
    _radTopLeft :: Maybe RadiusCorner
_radTopLeft = Maybe RadiusCorner
forall a. Maybe a
Nothing,
    _radTopRight :: Maybe RadiusCorner
_radTopRight = Maybe RadiusCorner
forall a. Maybe a
Nothing,
    _radBottomLeft :: Maybe RadiusCorner
_radBottomLeft = Maybe RadiusCorner
forall a. Maybe a
Nothing,
    _radBottomRight :: Maybe RadiusCorner
_radBottomRight = Maybe RadiusCorner
forall a. Maybe a
Nothing
  }

instance Semigroup Radius where
  <> :: Radius -> Radius -> Radius
(<>) Radius
r1 Radius
r2 = Radius :: Maybe RadiusCorner
-> Maybe RadiusCorner
-> Maybe RadiusCorner
-> Maybe RadiusCorner
-> Radius
Radius {
    _radTopLeft :: Maybe RadiusCorner
_radTopLeft = Radius -> Maybe RadiusCorner
_radTopLeft Radius
r2 Maybe RadiusCorner -> Maybe RadiusCorner -> Maybe RadiusCorner
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Radius -> Maybe RadiusCorner
_radTopLeft Radius
r1,
    _radTopRight :: Maybe RadiusCorner
_radTopRight = Radius -> Maybe RadiusCorner
_radTopRight Radius
r2 Maybe RadiusCorner -> Maybe RadiusCorner -> Maybe RadiusCorner
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Radius -> Maybe RadiusCorner
_radTopRight Radius
r1,
    _radBottomLeft :: Maybe RadiusCorner
_radBottomLeft = Radius -> Maybe RadiusCorner
_radBottomLeft Radius
r2 Maybe RadiusCorner -> Maybe RadiusCorner -> Maybe RadiusCorner
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Radius -> Maybe RadiusCorner
_radBottomLeft Radius
r1,
    _radBottomRight :: Maybe RadiusCorner
_radBottomRight = Radius -> Maybe RadiusCorner
_radBottomRight Radius
r2 Maybe RadiusCorner -> Maybe RadiusCorner -> Maybe RadiusCorner
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Radius -> Maybe RadiusCorner
_radBottomRight Radius
r1
  }

instance Monoid Radius where
  mempty :: Radius
mempty = Radius
forall a. Default a => a
def

-- | Text related definitions.
data TextStyle = TextStyle {
  TextStyle -> Maybe Font
_txsFont :: Maybe Font,          -- ^ The font type.
  TextStyle -> Maybe FontSize
_txsFontSize :: Maybe FontSize,  -- ^ Text size in pixels.
  TextStyle -> Maybe FontSpace
_txsFontSpaceH :: Maybe FontSpace, -- ^ Horizontal text spacing in pixels.
  TextStyle -> Maybe FontSpace
_txsFontSpaceV :: Maybe FontSpace, -- ^ Vertical text spacing in pixels.
  TextStyle -> Maybe Color
_txsFontColor :: Maybe Color,    -- ^ Text color.
  TextStyle -> Maybe Bool
_txsUnderline :: Maybe Bool,     -- ^ True if underline should be displayed.
  TextStyle -> Maybe Bool
_txsOverline :: Maybe Bool,      -- ^ True if overline should be displayed.
  TextStyle -> Maybe Bool
_txsThroughline :: Maybe Bool,   -- ^ True if throughline should be displayed.
  TextStyle -> Maybe AlignTH
_txsAlignH :: Maybe AlignTH,     -- ^ Horizontal alignment.
  TextStyle -> Maybe AlignTV
_txsAlignV :: Maybe AlignTV      -- ^ Vertical alignment.
} deriving (TextStyle -> TextStyle -> Bool
(TextStyle -> TextStyle -> Bool)
-> (TextStyle -> TextStyle -> Bool) -> Eq TextStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextStyle -> TextStyle -> Bool
$c/= :: TextStyle -> TextStyle -> Bool
== :: TextStyle -> TextStyle -> Bool
$c== :: TextStyle -> TextStyle -> Bool
Eq, Int -> TextStyle -> ShowS
[TextStyle] -> ShowS
TextStyle -> String
(Int -> TextStyle -> ShowS)
-> (TextStyle -> String)
-> ([TextStyle] -> ShowS)
-> Show TextStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextStyle] -> ShowS
$cshowList :: [TextStyle] -> ShowS
show :: TextStyle -> String
$cshow :: TextStyle -> String
showsPrec :: Int -> TextStyle -> ShowS
$cshowsPrec :: Int -> TextStyle -> ShowS
Show, (forall x. TextStyle -> Rep TextStyle x)
-> (forall x. Rep TextStyle x -> TextStyle) -> Generic TextStyle
forall x. Rep TextStyle x -> TextStyle
forall x. TextStyle -> Rep TextStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextStyle x -> TextStyle
$cfrom :: forall x. TextStyle -> Rep TextStyle x
Generic)

instance Default TextStyle where
  def :: TextStyle
def = TextStyle :: Maybe Font
-> Maybe FontSize
-> Maybe FontSpace
-> Maybe FontSpace
-> Maybe Color
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe AlignTH
-> Maybe AlignTV
-> TextStyle
TextStyle {
    _txsFont :: Maybe Font
_txsFont = Maybe Font
forall a. Maybe a
Nothing,
    _txsFontSize :: Maybe FontSize
_txsFontSize = Maybe FontSize
forall a. Maybe a
Nothing,
    _txsFontSpaceH :: Maybe FontSpace
_txsFontSpaceH = Maybe FontSpace
forall a. Maybe a
Nothing,
    _txsFontSpaceV :: Maybe FontSpace
_txsFontSpaceV = Maybe FontSpace
forall a. Maybe a
Nothing,
    _txsFontColor :: Maybe Color
_txsFontColor = Maybe Color
forall a. Maybe a
Nothing,
    _txsUnderline :: Maybe Bool
_txsUnderline = Maybe Bool
forall a. Maybe a
Nothing,
    _txsOverline :: Maybe Bool
_txsOverline = Maybe Bool
forall a. Maybe a
Nothing,
    _txsThroughline :: Maybe Bool
_txsThroughline = Maybe Bool
forall a. Maybe a
Nothing,
    _txsAlignH :: Maybe AlignTH
_txsAlignH = Maybe AlignTH
forall a. Maybe a
Nothing,
    _txsAlignV :: Maybe AlignTV
_txsAlignV = Maybe AlignTV
forall a. Maybe a
Nothing
  }

instance Semigroup TextStyle where
  <> :: TextStyle -> TextStyle -> TextStyle
(<>) TextStyle
ts1 TextStyle
ts2 = TextStyle :: Maybe Font
-> Maybe FontSize
-> Maybe FontSpace
-> Maybe FontSpace
-> Maybe Color
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe AlignTH
-> Maybe AlignTV
-> TextStyle
TextStyle {
    _txsFont :: Maybe Font
_txsFont = TextStyle -> Maybe Font
_txsFont TextStyle
ts2 Maybe Font -> Maybe Font -> Maybe Font
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextStyle -> Maybe Font
_txsFont TextStyle
ts1,
    _txsFontSize :: Maybe FontSize
_txsFontSize = TextStyle -> Maybe FontSize
_txsFontSize TextStyle
ts2 Maybe FontSize -> Maybe FontSize -> Maybe FontSize
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextStyle -> Maybe FontSize
_txsFontSize TextStyle
ts1,
    _txsFontSpaceH :: Maybe FontSpace
_txsFontSpaceH = TextStyle -> Maybe FontSpace
_txsFontSpaceH TextStyle
ts2 Maybe FontSpace -> Maybe FontSpace -> Maybe FontSpace
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextStyle -> Maybe FontSpace
_txsFontSpaceH TextStyle
ts1,
    _txsFontSpaceV :: Maybe FontSpace
_txsFontSpaceV = TextStyle -> Maybe FontSpace
_txsFontSpaceV TextStyle
ts2 Maybe FontSpace -> Maybe FontSpace -> Maybe FontSpace
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextStyle -> Maybe FontSpace
_txsFontSpaceV TextStyle
ts1,
    _txsFontColor :: Maybe Color
_txsFontColor = TextStyle -> Maybe Color
_txsFontColor TextStyle
ts2 Maybe Color -> Maybe Color -> Maybe Color
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextStyle -> Maybe Color
_txsFontColor TextStyle
ts1,
    _txsUnderline :: Maybe Bool
_txsUnderline = TextStyle -> Maybe Bool
_txsUnderline TextStyle
ts2 Maybe Bool -> Maybe Bool -> Maybe Bool
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextStyle -> Maybe Bool
_txsUnderline TextStyle
ts1,
    _txsOverline :: Maybe Bool
_txsOverline = TextStyle -> Maybe Bool
_txsOverline TextStyle
ts2 Maybe Bool -> Maybe Bool -> Maybe Bool
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextStyle -> Maybe Bool
_txsOverline TextStyle
ts1,
    _txsThroughline :: Maybe Bool
_txsThroughline = TextStyle -> Maybe Bool
_txsThroughline TextStyle
ts2 Maybe Bool -> Maybe Bool -> Maybe Bool
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextStyle -> Maybe Bool
_txsThroughline TextStyle
ts1,
    _txsAlignH :: Maybe AlignTH
_txsAlignH = TextStyle -> Maybe AlignTH
_txsAlignH TextStyle
ts2 Maybe AlignTH -> Maybe AlignTH -> Maybe AlignTH
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextStyle -> Maybe AlignTH
_txsAlignH TextStyle
ts1,
    _txsAlignV :: Maybe AlignTV
_txsAlignV = TextStyle -> Maybe AlignTV
_txsAlignV TextStyle
ts2 Maybe AlignTV -> Maybe AlignTV -> Maybe AlignTV
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TextStyle -> Maybe AlignTV
_txsAlignV TextStyle
ts1
  }

instance Monoid TextStyle where
  mempty :: TextStyle
mempty = TextStyle
forall a. Default a => a
def