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

Helper functions for style types.
-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict #-}

module Monomer.Core.StyleUtil (
  getContentArea,
  nodeKey,
  nodeEnabled,
  nodeVisible,
  nodeFocusable,
  styleFont,
  styleFontSize,
  styleFontSpaceH,
  styleFontSpaceV,
  styleFontColor,
  styleTextAlignH,
  styleTextAlignV,
  styleBgColor,
  styleFgColor,
  styleSndColor,
  styleHlColor,
  getOuterSize,
  addOuterSize,
  addOuterBounds,
  removeOuterSize,
  removeOuterBounds,
  addBorder,
  addPadding,
  subtractBorder,
  subtractPadding,
  subtractBorderFromRadius
) where

import Control.Lens ((&), (^.), (^?), (.~), (+~), (%~), (?~), _Just, non)
import Data.Default
import Data.Maybe
import Data.Text (Text)

import Monomer.Common
import Monomer.Core.Combinators
import Monomer.Core.StyleTypes
import Monomer.Core.WidgetTypes
import Monomer.Graphics.Types
import Monomer.Helper

import qualified Monomer.Core.Lens as L

instance CmbStyleBasic Style where
  styleBasic :: Style -> [StyleState] -> Style
styleBasic Style
oldStyle [StyleState]
states = Style
newStyle where
    newStyle :: Style
newStyle = Style
oldStyle Style -> (Style -> Style) -> Style
forall a b. a -> (a -> b) -> b
& (Maybe StyleState -> Identity (Maybe StyleState))
-> Style -> Identity Style
forall s a. HasBasic s a => Lens' s a
L.basic ((Maybe StyleState -> Identity (Maybe StyleState))
 -> Style -> Identity Style)
-> Maybe StyleState -> Style -> Style
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [StyleState] -> Maybe StyleState
forall a. Monoid a => [a] -> Maybe a
maybeConcat [StyleState]
states

instance CmbStyleHover Style where
  styleHover :: Style -> [StyleState] -> Style
styleHover Style
oldStyle [StyleState]
states = Style
newStyle where
    newStyle :: Style
newStyle = Style
oldStyle Style -> (Style -> Style) -> Style
forall a b. a -> (a -> b) -> b
& (Maybe StyleState -> Identity (Maybe StyleState))
-> Style -> Identity Style
forall s a. HasHover s a => Lens' s a
L.hover ((Maybe StyleState -> Identity (Maybe StyleState))
 -> Style -> Identity Style)
-> Maybe StyleState -> Style -> Style
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [StyleState] -> Maybe StyleState
forall a. Monoid a => [a] -> Maybe a
maybeConcat [StyleState]
states

instance CmbStyleFocus Style where
  styleFocus :: Style -> [StyleState] -> Style
styleFocus Style
oldStyle [StyleState]
states = Style
newStyle where
    newStyle :: Style
newStyle = Style
oldStyle Style -> (Style -> Style) -> Style
forall a b. a -> (a -> b) -> b
& (Maybe StyleState -> Identity (Maybe StyleState))
-> Style -> Identity Style
forall s a. HasFocus s a => Lens' s a
L.focus ((Maybe StyleState -> Identity (Maybe StyleState))
 -> Style -> Identity Style)
-> Maybe StyleState -> Style -> Style
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [StyleState] -> Maybe StyleState
forall a. Monoid a => [a] -> Maybe a
maybeConcat [StyleState]
states

instance CmbStyleFocusHover Style where
  styleFocusHover :: Style -> [StyleState] -> Style
styleFocusHover Style
oldStyle [StyleState]
states = Style
newStyle where
    newStyle :: Style
newStyle = Style
oldStyle Style -> (Style -> Style) -> Style
forall a b. a -> (a -> b) -> b
& (Maybe StyleState -> Identity (Maybe StyleState))
-> Style -> Identity Style
forall s a. HasFocusHover s a => Lens' s a
L.focusHover ((Maybe StyleState -> Identity (Maybe StyleState))
 -> Style -> Identity Style)
-> Maybe StyleState -> Style -> Style
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [StyleState] -> Maybe StyleState
forall a. Monoid a => [a] -> Maybe a
maybeConcat [StyleState]
states

instance CmbStyleActive Style where
  styleActive :: Style -> [StyleState] -> Style
styleActive Style
oldStyle [StyleState]
states = Style
newStyle where
    newStyle :: Style
newStyle = Style
oldStyle Style -> (Style -> Style) -> Style
forall a b. a -> (a -> b) -> b
& (Maybe StyleState -> Identity (Maybe StyleState))
-> Style -> Identity Style
forall s a. HasActive s a => Lens' s a
L.active ((Maybe StyleState -> Identity (Maybe StyleState))
 -> Style -> Identity Style)
-> Maybe StyleState -> Style -> Style
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [StyleState] -> Maybe StyleState
forall a. Monoid a => [a] -> Maybe a
maybeConcat [StyleState]
states

instance CmbStyleDisabled Style where
  styleDisabled :: Style -> [StyleState] -> Style
styleDisabled Style
oldStyle [StyleState]
states = Style
newStyle where
    newStyle :: Style
newStyle = Style
oldStyle Style -> (Style -> Style) -> Style
forall a b. a -> (a -> b) -> b
& (Maybe StyleState -> Identity (Maybe StyleState))
-> Style -> Identity Style
forall s a. HasDisabled s a => Lens' s a
L.disabled ((Maybe StyleState -> Identity (Maybe StyleState))
 -> Style -> Identity Style)
-> Maybe StyleState -> Style -> Style
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [StyleState] -> Maybe StyleState
forall a. Monoid a => [a] -> Maybe a
maybeConcat [StyleState]
states

instance CmbStyleBasic (WidgetNode s e) where
  styleBasic :: WidgetNode s e -> [StyleState] -> WidgetNode s e
styleBasic WidgetNode s e
node [StyleState]
states = WidgetNode s e
node WidgetNode s e
-> (WidgetNode s e -> WidgetNode s e) -> WidgetNode s e
forall a b. a -> (a -> b) -> b
& (WidgetNodeInfo -> Identity WidgetNodeInfo)
-> WidgetNode s e -> Identity (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Identity WidgetNodeInfo)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> ((Style -> Identity Style)
    -> WidgetNodeInfo -> Identity WidgetNodeInfo)
-> (Style -> Identity Style)
-> WidgetNode s e
-> Identity (WidgetNode s e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Style -> Identity Style)
-> WidgetNodeInfo -> Identity WidgetNodeInfo
forall s a. HasStyle s a => Lens' s a
L.style ((Style -> Identity Style)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> Style -> WidgetNode s e -> WidgetNode s e
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Style
newStyle where
    state :: StyleState
state = [StyleState] -> StyleState
forall a. Monoid a => [a] -> a
mconcat [StyleState]
states
    oldStyle :: Style
oldStyle = WidgetNode s e
node WidgetNode s e -> Getting Style (WidgetNode s e) Style -> Style
forall s a. s -> Getting a s a -> a
^. (WidgetNodeInfo -> Const Style WidgetNodeInfo)
-> WidgetNode s e -> Const Style (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Const Style WidgetNodeInfo)
 -> WidgetNode s e -> Const Style (WidgetNode s e))
-> ((Style -> Const Style Style)
    -> WidgetNodeInfo -> Const Style WidgetNodeInfo)
-> Getting Style (WidgetNode s e) Style
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Style -> Const Style Style)
-> WidgetNodeInfo -> Const Style WidgetNodeInfo
forall s a. HasStyle s a => Lens' s a
L.style
    newStyle :: Style
newStyle = Style
oldStyle Style -> (Style -> Style) -> Style
forall a b. a -> (a -> b) -> b
& (Maybe StyleState -> Identity (Maybe StyleState))
-> Style -> Identity Style
forall s a. HasBasic s a => Lens' s a
L.basic ((Maybe StyleState -> Identity (Maybe StyleState))
 -> Style -> Identity Style)
-> StyleState -> Style -> Style
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ StyleState
state

instance CmbStyleHover (WidgetNode s e) where
  styleHover :: WidgetNode s e -> [StyleState] -> WidgetNode s e
styleHover WidgetNode s e
node [StyleState]
states = WidgetNode s e
node WidgetNode s e
-> (WidgetNode s e -> WidgetNode s e) -> WidgetNode s e
forall a b. a -> (a -> b) -> b
& (WidgetNodeInfo -> Identity WidgetNodeInfo)
-> WidgetNode s e -> Identity (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Identity WidgetNodeInfo)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> ((Style -> Identity Style)
    -> WidgetNodeInfo -> Identity WidgetNodeInfo)
-> (Style -> Identity Style)
-> WidgetNode s e
-> Identity (WidgetNode s e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Style -> Identity Style)
-> WidgetNodeInfo -> Identity WidgetNodeInfo
forall s a. HasStyle s a => Lens' s a
L.style ((Style -> Identity Style)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> Style -> WidgetNode s e -> WidgetNode s e
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Style
newStyle where
    state :: StyleState
state = [StyleState] -> StyleState
forall a. Monoid a => [a] -> a
mconcat [StyleState]
states
    oldStyle :: Style
oldStyle = WidgetNode s e
node WidgetNode s e -> Getting Style (WidgetNode s e) Style -> Style
forall s a. s -> Getting a s a -> a
^. (WidgetNodeInfo -> Const Style WidgetNodeInfo)
-> WidgetNode s e -> Const Style (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Const Style WidgetNodeInfo)
 -> WidgetNode s e -> Const Style (WidgetNode s e))
-> ((Style -> Const Style Style)
    -> WidgetNodeInfo -> Const Style WidgetNodeInfo)
-> Getting Style (WidgetNode s e) Style
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Style -> Const Style Style)
-> WidgetNodeInfo -> Const Style WidgetNodeInfo
forall s a. HasStyle s a => Lens' s a
L.style
    newStyle :: Style
newStyle = Style
oldStyle Style -> (Style -> Style) -> Style
forall a b. a -> (a -> b) -> b
& (Maybe StyleState -> Identity (Maybe StyleState))
-> Style -> Identity Style
forall s a. HasHover s a => Lens' s a
L.hover ((Maybe StyleState -> Identity (Maybe StyleState))
 -> Style -> Identity Style)
-> StyleState -> Style -> Style
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ StyleState
state

instance CmbStyleFocus (WidgetNode s e) where
  styleFocus :: WidgetNode s e -> [StyleState] -> WidgetNode s e
styleFocus WidgetNode s e
node [StyleState]
states = WidgetNode s e
node WidgetNode s e
-> (WidgetNode s e -> WidgetNode s e) -> WidgetNode s e
forall a b. a -> (a -> b) -> b
& (WidgetNodeInfo -> Identity WidgetNodeInfo)
-> WidgetNode s e -> Identity (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Identity WidgetNodeInfo)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> ((Style -> Identity Style)
    -> WidgetNodeInfo -> Identity WidgetNodeInfo)
-> (Style -> Identity Style)
-> WidgetNode s e
-> Identity (WidgetNode s e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Style -> Identity Style)
-> WidgetNodeInfo -> Identity WidgetNodeInfo
forall s a. HasStyle s a => Lens' s a
L.style ((Style -> Identity Style)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> Style -> WidgetNode s e -> WidgetNode s e
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Style
newStyle where
    state :: StyleState
state = [StyleState] -> StyleState
forall a. Monoid a => [a] -> a
mconcat [StyleState]
states
    oldStyle :: Style
oldStyle = WidgetNode s e
node WidgetNode s e -> Getting Style (WidgetNode s e) Style -> Style
forall s a. s -> Getting a s a -> a
^. (WidgetNodeInfo -> Const Style WidgetNodeInfo)
-> WidgetNode s e -> Const Style (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Const Style WidgetNodeInfo)
 -> WidgetNode s e -> Const Style (WidgetNode s e))
-> ((Style -> Const Style Style)
    -> WidgetNodeInfo -> Const Style WidgetNodeInfo)
-> Getting Style (WidgetNode s e) Style
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Style -> Const Style Style)
-> WidgetNodeInfo -> Const Style WidgetNodeInfo
forall s a. HasStyle s a => Lens' s a
L.style
    newStyle :: Style
newStyle = Style
oldStyle Style -> (Style -> Style) -> Style
forall a b. a -> (a -> b) -> b
& (Maybe StyleState -> Identity (Maybe StyleState))
-> Style -> Identity Style
forall s a. HasFocus s a => Lens' s a
L.focus ((Maybe StyleState -> Identity (Maybe StyleState))
 -> Style -> Identity Style)
-> StyleState -> Style -> Style
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ StyleState
state

instance CmbStyleFocusHover (WidgetNode s e) where
  styleFocusHover :: WidgetNode s e -> [StyleState] -> WidgetNode s e
styleFocusHover WidgetNode s e
node [StyleState]
states = WidgetNode s e
node WidgetNode s e
-> (WidgetNode s e -> WidgetNode s e) -> WidgetNode s e
forall a b. a -> (a -> b) -> b
& (WidgetNodeInfo -> Identity WidgetNodeInfo)
-> WidgetNode s e -> Identity (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Identity WidgetNodeInfo)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> ((Style -> Identity Style)
    -> WidgetNodeInfo -> Identity WidgetNodeInfo)
-> (Style -> Identity Style)
-> WidgetNode s e
-> Identity (WidgetNode s e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Style -> Identity Style)
-> WidgetNodeInfo -> Identity WidgetNodeInfo
forall s a. HasStyle s a => Lens' s a
L.style ((Style -> Identity Style)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> Style -> WidgetNode s e -> WidgetNode s e
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Style
newStyle where
    state :: StyleState
state = [StyleState] -> StyleState
forall a. Monoid a => [a] -> a
mconcat [StyleState]
states
    oldStyle :: Style
oldStyle = WidgetNode s e
node WidgetNode s e -> Getting Style (WidgetNode s e) Style -> Style
forall s a. s -> Getting a s a -> a
^. (WidgetNodeInfo -> Const Style WidgetNodeInfo)
-> WidgetNode s e -> Const Style (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Const Style WidgetNodeInfo)
 -> WidgetNode s e -> Const Style (WidgetNode s e))
-> ((Style -> Const Style Style)
    -> WidgetNodeInfo -> Const Style WidgetNodeInfo)
-> Getting Style (WidgetNode s e) Style
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Style -> Const Style Style)
-> WidgetNodeInfo -> Const Style WidgetNodeInfo
forall s a. HasStyle s a => Lens' s a
L.style
    newStyle :: Style
newStyle = Style
oldStyle Style -> (Style -> Style) -> Style
forall a b. a -> (a -> b) -> b
& (Maybe StyleState -> Identity (Maybe StyleState))
-> Style -> Identity Style
forall s a. HasFocusHover s a => Lens' s a
L.focusHover ((Maybe StyleState -> Identity (Maybe StyleState))
 -> Style -> Identity Style)
-> StyleState -> Style -> Style
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ StyleState
state

instance CmbStyleActive (WidgetNode s e) where
  styleActive :: WidgetNode s e -> [StyleState] -> WidgetNode s e
styleActive WidgetNode s e
node [StyleState]
states = WidgetNode s e
node WidgetNode s e
-> (WidgetNode s e -> WidgetNode s e) -> WidgetNode s e
forall a b. a -> (a -> b) -> b
& (WidgetNodeInfo -> Identity WidgetNodeInfo)
-> WidgetNode s e -> Identity (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Identity WidgetNodeInfo)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> ((Style -> Identity Style)
    -> WidgetNodeInfo -> Identity WidgetNodeInfo)
-> (Style -> Identity Style)
-> WidgetNode s e
-> Identity (WidgetNode s e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Style -> Identity Style)
-> WidgetNodeInfo -> Identity WidgetNodeInfo
forall s a. HasStyle s a => Lens' s a
L.style ((Style -> Identity Style)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> Style -> WidgetNode s e -> WidgetNode s e
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Style
newStyle where
    state :: StyleState
state = [StyleState] -> StyleState
forall a. Monoid a => [a] -> a
mconcat [StyleState]
states
    oldStyle :: Style
oldStyle = WidgetNode s e
node WidgetNode s e -> Getting Style (WidgetNode s e) Style -> Style
forall s a. s -> Getting a s a -> a
^. (WidgetNodeInfo -> Const Style WidgetNodeInfo)
-> WidgetNode s e -> Const Style (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Const Style WidgetNodeInfo)
 -> WidgetNode s e -> Const Style (WidgetNode s e))
-> ((Style -> Const Style Style)
    -> WidgetNodeInfo -> Const Style WidgetNodeInfo)
-> Getting Style (WidgetNode s e) Style
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Style -> Const Style Style)
-> WidgetNodeInfo -> Const Style WidgetNodeInfo
forall s a. HasStyle s a => Lens' s a
L.style
    newStyle :: Style
newStyle = Style
oldStyle Style -> (Style -> Style) -> Style
forall a b. a -> (a -> b) -> b
& (Maybe StyleState -> Identity (Maybe StyleState))
-> Style -> Identity Style
forall s a. HasActive s a => Lens' s a
L.active ((Maybe StyleState -> Identity (Maybe StyleState))
 -> Style -> Identity Style)
-> StyleState -> Style -> Style
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ StyleState
state

instance CmbStyleDisabled (WidgetNode s e) where
  styleDisabled :: WidgetNode s e -> [StyleState] -> WidgetNode s e
styleDisabled WidgetNode s e
node [StyleState]
states = WidgetNode s e
node WidgetNode s e
-> (WidgetNode s e -> WidgetNode s e) -> WidgetNode s e
forall a b. a -> (a -> b) -> b
& (WidgetNodeInfo -> Identity WidgetNodeInfo)
-> WidgetNode s e -> Identity (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Identity WidgetNodeInfo)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> ((Style -> Identity Style)
    -> WidgetNodeInfo -> Identity WidgetNodeInfo)
-> (Style -> Identity Style)
-> WidgetNode s e
-> Identity (WidgetNode s e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Style -> Identity Style)
-> WidgetNodeInfo -> Identity WidgetNodeInfo
forall s a. HasStyle s a => Lens' s a
L.style ((Style -> Identity Style)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> Style -> WidgetNode s e -> WidgetNode s e
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Style
newStyle where
    state :: StyleState
state = [StyleState] -> StyleState
forall a. Monoid a => [a] -> a
mconcat [StyleState]
states
    oldStyle :: Style
oldStyle = WidgetNode s e
node WidgetNode s e -> Getting Style (WidgetNode s e) Style -> Style
forall s a. s -> Getting a s a -> a
^. (WidgetNodeInfo -> Const Style WidgetNodeInfo)
-> WidgetNode s e -> Const Style (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Const Style WidgetNodeInfo)
 -> WidgetNode s e -> Const Style (WidgetNode s e))
-> ((Style -> Const Style Style)
    -> WidgetNodeInfo -> Const Style WidgetNodeInfo)
-> Getting Style (WidgetNode s e) Style
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Style -> Const Style Style)
-> WidgetNodeInfo -> Const Style WidgetNodeInfo
forall s a. HasStyle s a => Lens' s a
L.style
    newStyle :: Style
newStyle = Style
oldStyle Style -> (Style -> Style) -> Style
forall a b. a -> (a -> b) -> b
& (Maybe StyleState -> Identity (Maybe StyleState))
-> Style -> Identity Style
forall s a. HasDisabled s a => Lens' s a
L.disabled ((Maybe StyleState -> Identity (Maybe StyleState))
 -> Style -> Identity Style)
-> StyleState -> Style -> Style
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ StyleState
state

infixl 5 `nodeKey`
infixl 5 `nodeEnabled`
infixl 5 `nodeVisible`
infixl 5 `nodeFocusable`

-- | Sets the key of the given node.
nodeKey :: WidgetNode s e -> Text -> WidgetNode s e
nodeKey :: WidgetNode s e -> Text -> WidgetNode s e
nodeKey WidgetNode s e
node Text
key = WidgetNode s e
node WidgetNode s e
-> (WidgetNode s e -> WidgetNode s e) -> WidgetNode s e
forall a b. a -> (a -> b) -> b
& (WidgetNodeInfo -> Identity WidgetNodeInfo)
-> WidgetNode s e -> Identity (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Identity WidgetNodeInfo)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> ((Maybe WidgetKey -> Identity (Maybe WidgetKey))
    -> WidgetNodeInfo -> Identity WidgetNodeInfo)
-> (Maybe WidgetKey -> Identity (Maybe WidgetKey))
-> WidgetNode s e
-> Identity (WidgetNode s e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe WidgetKey -> Identity (Maybe WidgetKey))
-> WidgetNodeInfo -> Identity WidgetNodeInfo
forall s a. HasKey s a => Lens' s a
L.key ((Maybe WidgetKey -> Identity (Maybe WidgetKey))
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> WidgetKey -> WidgetNode s e -> WidgetNode s e
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Text -> WidgetKey
WidgetKey Text
key

-- | Sets whether the given node is enabled.
nodeEnabled :: WidgetNode s e -> Bool -> WidgetNode s e
nodeEnabled :: WidgetNode s e -> Bool -> WidgetNode s e
nodeEnabled WidgetNode s e
node Bool
state = WidgetNode s e
node WidgetNode s e
-> (WidgetNode s e -> WidgetNode s e) -> WidgetNode s e
forall a b. a -> (a -> b) -> b
& (WidgetNodeInfo -> Identity WidgetNodeInfo)
-> WidgetNode s e -> Identity (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Identity WidgetNodeInfo)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> ((Bool -> Identity Bool)
    -> WidgetNodeInfo -> Identity WidgetNodeInfo)
-> (Bool -> Identity Bool)
-> WidgetNode s e
-> Identity (WidgetNode s e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Identity Bool)
-> WidgetNodeInfo -> Identity WidgetNodeInfo
forall s a. HasEnabled s a => Lens' s a
L.enabled ((Bool -> Identity Bool)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> Bool -> WidgetNode s e -> WidgetNode s e
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
state

-- | Sets whether the given node is visible.
nodeVisible :: WidgetNode s e -> Bool -> WidgetNode s e
nodeVisible :: WidgetNode s e -> Bool -> WidgetNode s e
nodeVisible WidgetNode s e
node Bool
visibility = WidgetNode s e
node WidgetNode s e
-> (WidgetNode s e -> WidgetNode s e) -> WidgetNode s e
forall a b. a -> (a -> b) -> b
& (WidgetNodeInfo -> Identity WidgetNodeInfo)
-> WidgetNode s e -> Identity (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Identity WidgetNodeInfo)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> ((Bool -> Identity Bool)
    -> WidgetNodeInfo -> Identity WidgetNodeInfo)
-> (Bool -> Identity Bool)
-> WidgetNode s e
-> Identity (WidgetNode s e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Identity Bool)
-> WidgetNodeInfo -> Identity WidgetNodeInfo
forall s a. HasVisible s a => Lens' s a
L.visible ((Bool -> Identity Bool)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> Bool -> WidgetNode s e -> WidgetNode s e
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
visibility

-- | Sets whether the given node is focusable.
nodeFocusable :: WidgetNode s e -> Bool -> WidgetNode s e
nodeFocusable :: WidgetNode s e -> Bool -> WidgetNode s e
nodeFocusable WidgetNode s e
node Bool
isFocusable = WidgetNode s e
node WidgetNode s e
-> (WidgetNode s e -> WidgetNode s e) -> WidgetNode s e
forall a b. a -> (a -> b) -> b
& (WidgetNodeInfo -> Identity WidgetNodeInfo)
-> WidgetNode s e -> Identity (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Identity WidgetNodeInfo)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> ((Bool -> Identity Bool)
    -> WidgetNodeInfo -> Identity WidgetNodeInfo)
-> (Bool -> Identity Bool)
-> WidgetNode s e
-> Identity (WidgetNode s e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Identity Bool)
-> WidgetNodeInfo -> Identity WidgetNodeInfo
forall s a. HasFocusable s a => Lens' s a
L.focusable ((Bool -> Identity Bool)
 -> WidgetNode s e -> Identity (WidgetNode s e))
-> Bool -> WidgetNode s e -> WidgetNode s e
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
isFocusable

-- | Returns the content area (i.e., ignoring border and padding) of the node.
getContentArea :: WidgetNode s e -> StyleState -> Rect
getContentArea :: WidgetNode s e -> StyleState -> Rect
getContentArea WidgetNode s e
node StyleState
style = Rect -> Maybe Rect -> Rect
forall a. a -> Maybe a -> a
fromMaybe Rect
forall a. Default a => a
def Maybe Rect
area where
  area :: Maybe Rect
area = StyleState -> Rect -> Maybe Rect
removeOuterBounds StyleState
style (WidgetNode s e
node WidgetNode s e -> Getting Rect (WidgetNode s e) Rect -> Rect
forall s a. s -> Getting a s a -> a
^. (WidgetNodeInfo -> Const Rect WidgetNodeInfo)
-> WidgetNode s e -> Const Rect (WidgetNode s e)
forall s a. HasInfo s a => Lens' s a
L.info ((WidgetNodeInfo -> Const Rect WidgetNodeInfo)
 -> WidgetNode s e -> Const Rect (WidgetNode s e))
-> ((Rect -> Const Rect Rect)
    -> WidgetNodeInfo -> Const Rect WidgetNodeInfo)
-> Getting Rect (WidgetNode s e) Rect
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rect -> Const Rect Rect)
-> WidgetNodeInfo -> Const Rect WidgetNodeInfo
forall s a. HasViewport s a => Lens' s a
L.viewport)

-- | Returns the font of the given style state, or the default.
styleFont :: StyleState -> Font
styleFont :: StyleState -> Font
styleFont StyleState
style = Font -> Maybe Font -> Font
forall a. a -> Maybe a -> a
fromMaybe Font
forall a. Default a => a
def Maybe Font
font where
  font :: Maybe Font
font = StyleState
style StyleState -> Getting (First Font) StyleState Font -> Maybe Font
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Maybe TextStyle -> Const (First Font) (Maybe TextStyle))
-> StyleState -> Const (First Font) StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Const (First Font) (Maybe TextStyle))
 -> StyleState -> Const (First Font) StyleState)
-> ((Font -> Const (First Font) Font)
    -> Maybe TextStyle -> Const (First Font) (Maybe TextStyle))
-> Getting (First Font) StyleState Font
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TextStyle -> Const (First Font) TextStyle)
-> Maybe TextStyle -> Const (First Font) (Maybe TextStyle)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just  ((TextStyle -> Const (First Font) TextStyle)
 -> Maybe TextStyle -> Const (First Font) (Maybe TextStyle))
-> ((Font -> Const (First Font) Font)
    -> TextStyle -> Const (First Font) TextStyle)
-> (Font -> Const (First Font) Font)
-> Maybe TextStyle
-> Const (First Font) (Maybe TextStyle)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Font -> Const (First Font) (Maybe Font))
-> TextStyle -> Const (First Font) TextStyle
forall s a. HasFont s a => Lens' s a
L.font ((Maybe Font -> Const (First Font) (Maybe Font))
 -> TextStyle -> Const (First Font) TextStyle)
-> ((Font -> Const (First Font) Font)
    -> Maybe Font -> Const (First Font) (Maybe Font))
-> (Font -> Const (First Font) Font)
-> TextStyle
-> Const (First Font) TextStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Font -> Const (First Font) Font)
-> Maybe Font -> Const (First Font) (Maybe Font)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just

-- | Returns the font size of the given style state, or the default.
styleFontSize :: StyleState -> FontSize
styleFontSize :: StyleState -> FontSize
styleFontSize StyleState
style = FontSize -> Maybe FontSize -> FontSize
forall a. a -> Maybe a -> a
fromMaybe FontSize
forall a. Default a => a
def Maybe FontSize
fontSize where
  fontSize :: Maybe FontSize
fontSize = StyleState
style StyleState
-> Getting (First FontSize) StyleState FontSize -> Maybe FontSize
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Maybe TextStyle -> Const (First FontSize) (Maybe TextStyle))
-> StyleState -> Const (First FontSize) StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Const (First FontSize) (Maybe TextStyle))
 -> StyleState -> Const (First FontSize) StyleState)
-> ((FontSize -> Const (First FontSize) FontSize)
    -> Maybe TextStyle -> Const (First FontSize) (Maybe TextStyle))
-> Getting (First FontSize) StyleState FontSize
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TextStyle -> Const (First FontSize) TextStyle)
-> Maybe TextStyle -> Const (First FontSize) (Maybe TextStyle)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((TextStyle -> Const (First FontSize) TextStyle)
 -> Maybe TextStyle -> Const (First FontSize) (Maybe TextStyle))
-> ((FontSize -> Const (First FontSize) FontSize)
    -> TextStyle -> Const (First FontSize) TextStyle)
-> (FontSize -> Const (First FontSize) FontSize)
-> Maybe TextStyle
-> Const (First FontSize) (Maybe TextStyle)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe FontSize -> Const (First FontSize) (Maybe FontSize))
-> TextStyle -> Const (First FontSize) TextStyle
forall s a. HasFontSize s a => Lens' s a
L.fontSize ((Maybe FontSize -> Const (First FontSize) (Maybe FontSize))
 -> TextStyle -> Const (First FontSize) TextStyle)
-> ((FontSize -> Const (First FontSize) FontSize)
    -> Maybe FontSize -> Const (First FontSize) (Maybe FontSize))
-> (FontSize -> Const (First FontSize) FontSize)
-> TextStyle
-> Const (First FontSize) TextStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FontSize -> Const (First FontSize) FontSize)
-> Maybe FontSize -> Const (First FontSize) (Maybe FontSize)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just

-- | Returns the horizontal spacing of the given style state, or the default.
styleFontSpaceH :: StyleState -> FontSpace
styleFontSpaceH :: StyleState -> FontSpace
styleFontSpaceH StyleState
style = FontSpace -> Maybe FontSpace -> FontSpace
forall a. a -> Maybe a -> a
fromMaybe FontSpace
forall a. Default a => a
def Maybe FontSpace
fontSpaceH where
  fontSpaceH :: Maybe FontSpace
fontSpaceH = StyleState
style StyleState
-> Getting (First FontSpace) StyleState FontSpace
-> Maybe FontSpace
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Maybe TextStyle -> Const (First FontSpace) (Maybe TextStyle))
-> StyleState -> Const (First FontSpace) StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Const (First FontSpace) (Maybe TextStyle))
 -> StyleState -> Const (First FontSpace) StyleState)
-> ((FontSpace -> Const (First FontSpace) FontSpace)
    -> Maybe TextStyle -> Const (First FontSpace) (Maybe TextStyle))
-> Getting (First FontSpace) StyleState FontSpace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TextStyle -> Const (First FontSpace) TextStyle)
-> Maybe TextStyle -> Const (First FontSpace) (Maybe TextStyle)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((TextStyle -> Const (First FontSpace) TextStyle)
 -> Maybe TextStyle -> Const (First FontSpace) (Maybe TextStyle))
-> ((FontSpace -> Const (First FontSpace) FontSpace)
    -> TextStyle -> Const (First FontSpace) TextStyle)
-> (FontSpace -> Const (First FontSpace) FontSpace)
-> Maybe TextStyle
-> Const (First FontSpace) (Maybe TextStyle)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe FontSpace -> Const (First FontSpace) (Maybe FontSpace))
-> TextStyle -> Const (First FontSpace) TextStyle
forall s a. HasFontSpaceH s a => Lens' s a
L.fontSpaceH ((Maybe FontSpace -> Const (First FontSpace) (Maybe FontSpace))
 -> TextStyle -> Const (First FontSpace) TextStyle)
-> ((FontSpace -> Const (First FontSpace) FontSpace)
    -> Maybe FontSpace -> Const (First FontSpace) (Maybe FontSpace))
-> (FontSpace -> Const (First FontSpace) FontSpace)
-> TextStyle
-> Const (First FontSpace) TextStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FontSpace -> Const (First FontSpace) FontSpace)
-> Maybe FontSpace -> Const (First FontSpace) (Maybe FontSpace)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just

-- | Returns the vertical spacing of the given style state, or the default.
styleFontSpaceV :: StyleState -> FontSpace
styleFontSpaceV :: StyleState -> FontSpace
styleFontSpaceV StyleState
style = FontSpace -> Maybe FontSpace -> FontSpace
forall a. a -> Maybe a -> a
fromMaybe FontSpace
forall a. Default a => a
def Maybe FontSpace
fontSpaceV where
  fontSpaceV :: Maybe FontSpace
fontSpaceV = StyleState
style StyleState
-> Getting (First FontSpace) StyleState FontSpace
-> Maybe FontSpace
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Maybe TextStyle -> Const (First FontSpace) (Maybe TextStyle))
-> StyleState -> Const (First FontSpace) StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Const (First FontSpace) (Maybe TextStyle))
 -> StyleState -> Const (First FontSpace) StyleState)
-> ((FontSpace -> Const (First FontSpace) FontSpace)
    -> Maybe TextStyle -> Const (First FontSpace) (Maybe TextStyle))
-> Getting (First FontSpace) StyleState FontSpace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TextStyle -> Const (First FontSpace) TextStyle)
-> Maybe TextStyle -> Const (First FontSpace) (Maybe TextStyle)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((TextStyle -> Const (First FontSpace) TextStyle)
 -> Maybe TextStyle -> Const (First FontSpace) (Maybe TextStyle))
-> ((FontSpace -> Const (First FontSpace) FontSpace)
    -> TextStyle -> Const (First FontSpace) TextStyle)
-> (FontSpace -> Const (First FontSpace) FontSpace)
-> Maybe TextStyle
-> Const (First FontSpace) (Maybe TextStyle)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe FontSpace -> Const (First FontSpace) (Maybe FontSpace))
-> TextStyle -> Const (First FontSpace) TextStyle
forall s a. HasFontSpaceV s a => Lens' s a
L.fontSpaceV ((Maybe FontSpace -> Const (First FontSpace) (Maybe FontSpace))
 -> TextStyle -> Const (First FontSpace) TextStyle)
-> ((FontSpace -> Const (First FontSpace) FontSpace)
    -> Maybe FontSpace -> Const (First FontSpace) (Maybe FontSpace))
-> (FontSpace -> Const (First FontSpace) FontSpace)
-> TextStyle
-> Const (First FontSpace) TextStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FontSpace -> Const (First FontSpace) FontSpace)
-> Maybe FontSpace -> Const (First FontSpace) (Maybe FontSpace)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just

-- | Returns the font color of the given style state, or the default.
styleFontColor :: StyleState -> Color
styleFontColor :: StyleState -> Color
styleFontColor StyleState
style = Color -> Maybe Color -> Color
forall a. a -> Maybe a -> a
fromMaybe Color
forall a. Default a => a
def Maybe Color
fontColor where
  fontColor :: Maybe Color
fontColor = StyleState
style StyleState -> Getting (First Color) StyleState Color -> Maybe Color
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Maybe TextStyle -> Const (First Color) (Maybe TextStyle))
-> StyleState -> Const (First Color) StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Const (First Color) (Maybe TextStyle))
 -> StyleState -> Const (First Color) StyleState)
-> ((Color -> Const (First Color) Color)
    -> Maybe TextStyle -> Const (First Color) (Maybe TextStyle))
-> Getting (First Color) StyleState Color
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TextStyle -> Const (First Color) TextStyle)
-> Maybe TextStyle -> Const (First Color) (Maybe TextStyle)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((TextStyle -> Const (First Color) TextStyle)
 -> Maybe TextStyle -> Const (First Color) (Maybe TextStyle))
-> ((Color -> Const (First Color) Color)
    -> TextStyle -> Const (First Color) TextStyle)
-> (Color -> Const (First Color) Color)
-> Maybe TextStyle
-> Const (First Color) (Maybe TextStyle)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Color -> Const (First Color) (Maybe Color))
-> TextStyle -> Const (First Color) TextStyle
forall s a. HasFontColor s a => Lens' s a
L.fontColor ((Maybe Color -> Const (First Color) (Maybe Color))
 -> TextStyle -> Const (First Color) TextStyle)
-> ((Color -> Const (First Color) Color)
    -> Maybe Color -> Const (First Color) (Maybe Color))
-> (Color -> Const (First Color) Color)
-> TextStyle
-> Const (First Color) TextStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Color -> Const (First Color) Color)
-> Maybe Color -> Const (First Color) (Maybe Color)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just

-- | Returns the horizontal alignment of the given style state, or the default.
styleTextAlignH :: StyleState -> AlignTH
styleTextAlignH :: StyleState -> AlignTH
styleTextAlignH StyleState
style = AlignTH -> Maybe AlignTH -> AlignTH
forall a. a -> Maybe a -> a
fromMaybe AlignTH
forall a. Default a => a
def Maybe AlignTH
alignH where
  alignH :: Maybe AlignTH
alignH = StyleState
style StyleState
-> Getting (First AlignTH) StyleState AlignTH -> Maybe AlignTH
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Maybe TextStyle -> Const (First AlignTH) (Maybe TextStyle))
-> StyleState -> Const (First AlignTH) StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Const (First AlignTH) (Maybe TextStyle))
 -> StyleState -> Const (First AlignTH) StyleState)
-> ((AlignTH -> Const (First AlignTH) AlignTH)
    -> Maybe TextStyle -> Const (First AlignTH) (Maybe TextStyle))
-> Getting (First AlignTH) StyleState AlignTH
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TextStyle -> Const (First AlignTH) TextStyle)
-> Maybe TextStyle -> Const (First AlignTH) (Maybe TextStyle)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((TextStyle -> Const (First AlignTH) TextStyle)
 -> Maybe TextStyle -> Const (First AlignTH) (Maybe TextStyle))
-> ((AlignTH -> Const (First AlignTH) AlignTH)
    -> TextStyle -> Const (First AlignTH) TextStyle)
-> (AlignTH -> Const (First AlignTH) AlignTH)
-> Maybe TextStyle
-> Const (First AlignTH) (Maybe TextStyle)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe AlignTH -> Const (First AlignTH) (Maybe AlignTH))
-> TextStyle -> Const (First AlignTH) TextStyle
forall s a. HasAlignH s a => Lens' s a
L.alignH ((Maybe AlignTH -> Const (First AlignTH) (Maybe AlignTH))
 -> TextStyle -> Const (First AlignTH) TextStyle)
-> ((AlignTH -> Const (First AlignTH) AlignTH)
    -> Maybe AlignTH -> Const (First AlignTH) (Maybe AlignTH))
-> (AlignTH -> Const (First AlignTH) AlignTH)
-> TextStyle
-> Const (First AlignTH) TextStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AlignTH -> Const (First AlignTH) AlignTH)
-> Maybe AlignTH -> Const (First AlignTH) (Maybe AlignTH)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just

-- | Returns the vertical alignment of the given style state, or the default.
styleTextAlignV :: StyleState -> AlignTV
styleTextAlignV :: StyleState -> AlignTV
styleTextAlignV StyleState
style = AlignTV -> Maybe AlignTV -> AlignTV
forall a. a -> Maybe a -> a
fromMaybe AlignTV
forall a. Default a => a
def Maybe AlignTV
alignV where
  alignV :: Maybe AlignTV
alignV = StyleState
style StyleState
-> Getting (First AlignTV) StyleState AlignTV -> Maybe AlignTV
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Maybe TextStyle -> Const (First AlignTV) (Maybe TextStyle))
-> StyleState -> Const (First AlignTV) StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Const (First AlignTV) (Maybe TextStyle))
 -> StyleState -> Const (First AlignTV) StyleState)
-> ((AlignTV -> Const (First AlignTV) AlignTV)
    -> Maybe TextStyle -> Const (First AlignTV) (Maybe TextStyle))
-> Getting (First AlignTV) StyleState AlignTV
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TextStyle -> Const (First AlignTV) TextStyle)
-> Maybe TextStyle -> Const (First AlignTV) (Maybe TextStyle)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((TextStyle -> Const (First AlignTV) TextStyle)
 -> Maybe TextStyle -> Const (First AlignTV) (Maybe TextStyle))
-> ((AlignTV -> Const (First AlignTV) AlignTV)
    -> TextStyle -> Const (First AlignTV) TextStyle)
-> (AlignTV -> Const (First AlignTV) AlignTV)
-> Maybe TextStyle
-> Const (First AlignTV) (Maybe TextStyle)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe AlignTV -> Const (First AlignTV) (Maybe AlignTV))
-> TextStyle -> Const (First AlignTV) TextStyle
forall s a. HasAlignV s a => Lens' s a
L.alignV ((Maybe AlignTV -> Const (First AlignTV) (Maybe AlignTV))
 -> TextStyle -> Const (First AlignTV) TextStyle)
-> ((AlignTV -> Const (First AlignTV) AlignTV)
    -> Maybe AlignTV -> Const (First AlignTV) (Maybe AlignTV))
-> (AlignTV -> Const (First AlignTV) AlignTV)
-> TextStyle
-> Const (First AlignTV) TextStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AlignTV -> Const (First AlignTV) AlignTV)
-> Maybe AlignTV -> Const (First AlignTV) (Maybe AlignTV)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just

-- | Returns the background color of the given style state, or the default.
styleBgColor :: StyleState -> Color
styleBgColor :: StyleState -> Color
styleBgColor StyleState
style = Color -> Maybe Color -> Color
forall a. a -> Maybe a -> a
fromMaybe Color
forall a. Default a => a
def Maybe Color
bgColor where
  bgColor :: Maybe Color
bgColor = StyleState
style StyleState -> Getting (First Color) StyleState Color -> Maybe Color
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Maybe Color -> Const (First Color) (Maybe Color))
-> StyleState -> Const (First Color) StyleState
forall s a. HasBgColor s a => Lens' s a
L.bgColor ((Maybe Color -> Const (First Color) (Maybe Color))
 -> StyleState -> Const (First Color) StyleState)
-> ((Color -> Const (First Color) Color)
    -> Maybe Color -> Const (First Color) (Maybe Color))
-> Getting (First Color) StyleState Color
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Color -> Const (First Color) Color)
-> Maybe Color -> Const (First Color) (Maybe Color)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just

-- | Returns the foreground color of the given style state, or the default.
styleFgColor :: StyleState -> Color
styleFgColor :: StyleState -> Color
styleFgColor StyleState
style = Color -> Maybe Color -> Color
forall a. a -> Maybe a -> a
fromMaybe Color
forall a. Default a => a
def Maybe Color
fgColor where
  fgColor :: Maybe Color
fgColor = StyleState
style StyleState -> Getting (First Color) StyleState Color -> Maybe Color
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Maybe Color -> Const (First Color) (Maybe Color))
-> StyleState -> Const (First Color) StyleState
forall s a. HasFgColor s a => Lens' s a
L.fgColor ((Maybe Color -> Const (First Color) (Maybe Color))
 -> StyleState -> Const (First Color) StyleState)
-> ((Color -> Const (First Color) Color)
    -> Maybe Color -> Const (First Color) (Maybe Color))
-> Getting (First Color) StyleState Color
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Color -> Const (First Color) Color)
-> Maybe Color -> Const (First Color) (Maybe Color)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just

-- | Returns the secondary color of the given style state, or the default.
styleSndColor :: StyleState -> Color
styleSndColor :: StyleState -> Color
styleSndColor StyleState
style = Color -> Maybe Color -> Color
forall a. a -> Maybe a -> a
fromMaybe Color
forall a. Default a => a
def Maybe Color
sndColor where
  sndColor :: Maybe Color
sndColor = StyleState
style StyleState -> Getting (First Color) StyleState Color -> Maybe Color
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Maybe Color -> Const (First Color) (Maybe Color))
-> StyleState -> Const (First Color) StyleState
forall s a. HasSndColor s a => Lens' s a
L.sndColor ((Maybe Color -> Const (First Color) (Maybe Color))
 -> StyleState -> Const (First Color) StyleState)
-> ((Color -> Const (First Color) Color)
    -> Maybe Color -> Const (First Color) (Maybe Color))
-> Getting (First Color) StyleState Color
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Color -> Const (First Color) Color)
-> Maybe Color -> Const (First Color) (Maybe Color)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just

-- | Returns the highlight color of the given style state, or the default.
styleHlColor :: StyleState -> Color
styleHlColor :: StyleState -> Color
styleHlColor StyleState
style = Color -> Maybe Color -> Color
forall a. a -> Maybe a -> a
fromMaybe Color
forall a. Default a => a
def Maybe Color
hlColor where
  hlColor :: Maybe Color
hlColor = StyleState
style StyleState -> Getting (First Color) StyleState Color -> Maybe Color
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Maybe Color -> Const (First Color) (Maybe Color))
-> StyleState -> Const (First Color) StyleState
forall s a. HasHlColor s a => Lens' s a
L.hlColor ((Maybe Color -> Const (First Color) (Maybe Color))
 -> StyleState -> Const (First Color) StyleState)
-> ((Color -> Const (First Color) Color)
    -> Maybe Color -> Const (First Color) (Maybe Color))
-> Getting (First Color) StyleState Color
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Color -> Const (First Color) Color)
-> Maybe Color -> Const (First Color) (Maybe Color)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just

-- | Returns the size used by border and padding.
getOuterSize :: StyleState -> Size
getOuterSize :: StyleState -> Size
getOuterSize StyleState
style = Size -> Maybe Size -> Size
forall a. a -> Maybe a -> a
fromMaybe Size
forall a. Default a => a
def Maybe Size
size where
  size :: Maybe Size
size = StyleState -> Size -> Maybe Size
addOuterSize StyleState
style Size
forall a. Default a => a
def

-- | Adds border and padding to the given size.
addOuterSize :: StyleState -> Size -> Maybe Size
addOuterSize :: StyleState -> Size -> Maybe Size
addOuterSize StyleState
style Size
sz =
  Size -> Maybe Border -> Maybe Size
addBorderSize Size
sz (StyleState -> Maybe Border
_sstBorder StyleState
style)
    Maybe Size -> (Size -> Maybe Size) -> Maybe Size
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Size -> Maybe Padding -> Maybe Size
`addPaddingSize` StyleState -> Maybe Padding
_sstPadding StyleState
style)

-- | Removes border and padding from the given size.
removeOuterSize :: StyleState -> Size -> Maybe Size
removeOuterSize :: StyleState -> Size -> Maybe Size
removeOuterSize StyleState
style Size
sz =
  Size -> Maybe Border -> Maybe Size
subtractBorderSize Size
sz (StyleState -> Maybe Border
_sstBorder StyleState
style)
    Maybe Size -> (Size -> Maybe Size) -> Maybe Size
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Size -> Maybe Padding -> Maybe Size
`subtractPaddingSize` StyleState -> Maybe Padding
_sstPadding StyleState
style)

-- | Adds border and padding to the given rect.
addOuterBounds :: StyleState -> Rect -> Maybe Rect
addOuterBounds :: StyleState -> Rect -> Maybe Rect
addOuterBounds StyleState
style Rect
rect =
  Rect -> Maybe Border -> Maybe Rect
addBorder Rect
rect (StyleState -> Maybe Border
_sstBorder StyleState
style)
    Maybe Rect -> (Rect -> Maybe Rect) -> Maybe Rect
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Rect -> Maybe Padding -> Maybe Rect
`addPadding` StyleState -> Maybe Padding
_sstPadding StyleState
style)

-- | Removes border and padding from the given rect.
removeOuterBounds :: StyleState -> Rect -> Maybe Rect
removeOuterBounds :: StyleState -> Rect -> Maybe Rect
removeOuterBounds StyleState
style Rect
rect =
  Rect -> Maybe Border -> Maybe Rect
subtractBorder Rect
rect (StyleState -> Maybe Border
_sstBorder StyleState
style)
    Maybe Rect -> (Rect -> Maybe Rect) -> Maybe Rect
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Rect -> Maybe Padding -> Maybe Rect
`subtractPadding` StyleState -> Maybe Padding
_sstPadding StyleState
style)

-- | Adds border widths to the given rect.
addBorder :: Rect -> Maybe Border -> Maybe Rect
addBorder :: Rect -> Maybe Border -> Maybe Rect
addBorder Rect
rect Maybe Border
border = Maybe Rect
nRect where
  (Double
bl, Double
br, Double
bt, Double
bb) = Maybe Border -> (Double, Double, Double, Double)
borderWidths Maybe Border
border
  nRect :: Maybe Rect
nRect = Rect -> Double -> Double -> Double -> Double -> Maybe Rect
addToRect Rect
rect Double
bl Double
br Double
bt Double
bb

-- | Adds padding the given rect.
addPadding :: Rect -> Maybe Padding -> Maybe Rect
addPadding :: Rect -> Maybe Padding -> Maybe Rect
addPadding Rect
rect Maybe Padding
Nothing = Rect -> Maybe Rect
forall a. a -> Maybe a
Just Rect
rect
addPadding Rect
rect (Just (Padding Maybe Double
l Maybe Double
r Maybe Double
t Maybe Double
b)) = Maybe Rect
nRect where
  nRect :: Maybe Rect
nRect = Rect -> Double -> Double -> Double -> Double -> Maybe Rect
addToRect Rect
rect (Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
l) (Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
r) (Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
t) (Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
b)

-- | Subtracts border widths from the given rect.
subtractBorder :: Rect -> Maybe Border -> Maybe Rect
subtractBorder :: Rect -> Maybe Border -> Maybe Rect
subtractBorder Rect
rect Maybe Border
border = Maybe Rect
nRect where
  (Double
bl, Double
br, Double
bt, Double
bb) = Maybe Border -> (Double, Double, Double, Double)
borderWidths Maybe Border
border
  nRect :: Maybe Rect
nRect = Rect -> Double -> Double -> Double -> Double -> Maybe Rect
subtractFromRect Rect
rect Double
bl Double
br Double
bt Double
bb

-- | Subbtracts padding from the given rect.
subtractPadding :: Rect -> Maybe Padding -> Maybe Rect
subtractPadding :: Rect -> Maybe Padding -> Maybe Rect
subtractPadding Rect
rect Maybe Padding
Nothing = Rect -> Maybe Rect
forall a. a -> Maybe a
Just Rect
rect
subtractPadding Rect
rect (Just (Padding Maybe Double
l Maybe Double
r Maybe Double
t Maybe Double
b)) = Maybe Rect
nRect where
  nRect :: Maybe Rect
nRect = Rect -> Double -> Double -> Double -> Double -> Maybe Rect
subtractFromRect Rect
rect (Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
l) (Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
r) (Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
t) (Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
b)

{-|
Subtracts border width from radius. This is useful when rendering nested shapes
with rounded corners, which would otherwise have gaps in the corners.
-}
subtractBorderFromRadius :: Maybe Border -> Radius -> Radius
subtractBorderFromRadius :: Maybe Border -> Radius -> Radius
subtractBorderFromRadius Maybe Border
border (Radius Maybe RadiusCorner
rtl Maybe RadiusCorner
rtr Maybe RadiusCorner
rbl Maybe RadiusCorner
rbr) = Radius
newRadius where
  (Double
bl, Double
br, Double
bt, Double
bb) = Maybe Border -> (Double, Double, Double, Double)
borderWidths Maybe Border
border
  ntl :: Maybe RadiusCorner
ntl = Maybe RadiusCorner
rtl Maybe RadiusCorner
-> (Maybe RadiusCorner -> Maybe RadiusCorner) -> Maybe RadiusCorner
forall a b. a -> (a -> b) -> b
& (RadiusCorner -> Identity RadiusCorner)
-> Maybe RadiusCorner -> Identity (Maybe RadiusCorner)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((RadiusCorner -> Identity RadiusCorner)
 -> Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> ((Double -> Identity Double)
    -> RadiusCorner -> Identity RadiusCorner)
-> (Double -> Identity Double)
-> Maybe RadiusCorner
-> Identity (Maybe RadiusCorner)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Identity Double)
-> RadiusCorner -> Identity RadiusCorner
forall s a. HasWidth s a => Lens' s a
L.width ((Double -> Identity Double)
 -> Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> (Double -> Double) -> Maybe RadiusCorner -> Maybe RadiusCorner
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ \Double
w -> Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
0 (Double
w Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
bl Double
bt)
  ntr :: Maybe RadiusCorner
ntr = Maybe RadiusCorner
rtr Maybe RadiusCorner
-> (Maybe RadiusCorner -> Maybe RadiusCorner) -> Maybe RadiusCorner
forall a b. a -> (a -> b) -> b
& (RadiusCorner -> Identity RadiusCorner)
-> Maybe RadiusCorner -> Identity (Maybe RadiusCorner)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((RadiusCorner -> Identity RadiusCorner)
 -> Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> ((Double -> Identity Double)
    -> RadiusCorner -> Identity RadiusCorner)
-> (Double -> Identity Double)
-> Maybe RadiusCorner
-> Identity (Maybe RadiusCorner)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Identity Double)
-> RadiusCorner -> Identity RadiusCorner
forall s a. HasWidth s a => Lens' s a
L.width ((Double -> Identity Double)
 -> Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> (Double -> Double) -> Maybe RadiusCorner -> Maybe RadiusCorner
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ \Double
w -> Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
0 (Double
w Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
br Double
bt)
  nbl :: Maybe RadiusCorner
nbl = Maybe RadiusCorner
rbl Maybe RadiusCorner
-> (Maybe RadiusCorner -> Maybe RadiusCorner) -> Maybe RadiusCorner
forall a b. a -> (a -> b) -> b
& (RadiusCorner -> Identity RadiusCorner)
-> Maybe RadiusCorner -> Identity (Maybe RadiusCorner)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((RadiusCorner -> Identity RadiusCorner)
 -> Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> ((Double -> Identity Double)
    -> RadiusCorner -> Identity RadiusCorner)
-> (Double -> Identity Double)
-> Maybe RadiusCorner
-> Identity (Maybe RadiusCorner)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Identity Double)
-> RadiusCorner -> Identity RadiusCorner
forall s a. HasWidth s a => Lens' s a
L.width ((Double -> Identity Double)
 -> Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> (Double -> Double) -> Maybe RadiusCorner -> Maybe RadiusCorner
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ \Double
w -> Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
0 (Double
w Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
bl Double
bb)
  nbr :: Maybe RadiusCorner
nbr = Maybe RadiusCorner
rbr Maybe RadiusCorner
-> (Maybe RadiusCorner -> Maybe RadiusCorner) -> Maybe RadiusCorner
forall a b. a -> (a -> b) -> b
& (RadiusCorner -> Identity RadiusCorner)
-> Maybe RadiusCorner -> Identity (Maybe RadiusCorner)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((RadiusCorner -> Identity RadiusCorner)
 -> Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> ((Double -> Identity Double)
    -> RadiusCorner -> Identity RadiusCorner)
-> (Double -> Identity Double)
-> Maybe RadiusCorner
-> Identity (Maybe RadiusCorner)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Identity Double)
-> RadiusCorner -> Identity RadiusCorner
forall s a. HasWidth s a => Lens' s a
L.width ((Double -> Identity Double)
 -> Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> (Double -> Double) -> Maybe RadiusCorner -> Maybe RadiusCorner
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ \Double
w -> Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
0 (Double
w Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
br Double
bb)
  newRadius :: Radius
newRadius = Maybe RadiusCorner
-> Maybe RadiusCorner
-> Maybe RadiusCorner
-> Maybe RadiusCorner
-> Radius
Radius Maybe RadiusCorner
ntl Maybe RadiusCorner
ntr Maybe RadiusCorner
nbl Maybe RadiusCorner
nbr

-- Internal
addBorderSize :: Size -> Maybe Border -> Maybe Size
addBorderSize :: Size -> Maybe Border -> Maybe Size
addBorderSize Size
sz Maybe Border
border = Maybe Size
nSize where
  (Double
bl, Double
br, Double
bt, Double
bb) = Maybe Border -> (Double, Double, Double, Double)
borderWidths Maybe Border
border
  nSize :: Maybe Size
nSize = Size -> Double -> Double -> Maybe Size
addToSize Size
sz (Double
bl Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
br) (Double
bt Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
bb)

addPaddingSize :: Size -> Maybe Padding -> Maybe Size
addPaddingSize :: Size -> Maybe Padding -> Maybe Size
addPaddingSize Size
sz Maybe Padding
Nothing = Size -> Maybe Size
forall a. a -> Maybe a
Just Size
sz
addPaddingSize Size
sz (Just (Padding Maybe Double
l Maybe Double
r Maybe Double
t Maybe Double
b)) = Maybe Size
nSize where
  nSize :: Maybe Size
nSize = Size -> Double -> Double -> Maybe Size
addToSize Size
sz (Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
l Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
r) (Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
t Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
b)

subtractBorderSize :: Size -> Maybe Border -> Maybe Size
subtractBorderSize :: Size -> Maybe Border -> Maybe Size
subtractBorderSize Size
sz Maybe Border
border = Maybe Size
nSize where
  (Double
bl, Double
br, Double
bt, Double
bb) = Maybe Border -> (Double, Double, Double, Double)
borderWidths Maybe Border
border
  nSize :: Maybe Size
nSize = Size -> Double -> Double -> Maybe Size
subtractFromSize Size
sz (Double
bl Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
br) (Double
bt Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
bb)

subtractPaddingSize :: Size -> Maybe Padding -> Maybe Size
subtractPaddingSize :: Size -> Maybe Padding -> Maybe Size
subtractPaddingSize Size
sz Maybe Padding
Nothing = Size -> Maybe Size
forall a. a -> Maybe a
Just Size
sz
subtractPaddingSize Size
sz (Just (Padding Maybe Double
l Maybe Double
r Maybe Double
t Maybe Double
b)) = Maybe Size
nSize where
  nSize :: Maybe Size
nSize = Size -> Double -> Double -> Maybe Size
subtractFromSize Size
sz (Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
l Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
r) (Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
t Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Maybe Double -> Double
forall a. Default a => Maybe a -> a
justDef Maybe Double
b)

borderWidths :: Maybe Border -> (Double, Double, Double, Double)
borderWidths :: Maybe Border -> (Double, Double, Double, Double)
borderWidths Maybe Border
Nothing = (Double
0, Double
0, Double
0, Double
0)
borderWidths (Just Border
border) = (Double
bl, Double
br, Double
bt, Double
bb) where
  bl :: Double
bl = Double -> (BorderSide -> Double) -> Maybe BorderSide -> Double
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Double
0 BorderSide -> Double
_bsWidth (Border -> Maybe BorderSide
_brdLeft Border
border)
  br :: Double
br = Double -> (BorderSide -> Double) -> Maybe BorderSide -> Double
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Double
0 BorderSide -> Double
_bsWidth (Border -> Maybe BorderSide
_brdRight Border
border)
  bt :: Double
bt = Double -> (BorderSide -> Double) -> Maybe BorderSide -> Double
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Double
0 BorderSide -> Double
_bsWidth (Border -> Maybe BorderSide
_brdTop Border
border)
  bb :: Double
bb = Double -> (BorderSide -> Double) -> Maybe BorderSide -> Double
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Double
0 BorderSide -> Double
_bsWidth (Border -> Maybe BorderSide
_brdBottom Border
border)

justDef :: (Default a) => Maybe a -> a
justDef :: Maybe a -> a
justDef Maybe a
val = a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
forall a. Default a => a
def Maybe a
val