{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Diagrams.TwoD.Text (
Text(..), TextAlignment(..)
, text, topLeftText, alignedText, baselineText
, mkText, mkText'
, Font(..), _Font
, getFont, font, _font
, FontSize(..), _FontSize
, fontSize, recommendFontSize
, fontSizeN, fontSizeO, fontSizeL, fontSizeG
, getFontSize, fontSizeM
, _fontSizeR, _fontSize, _fontSizeU
, FontSlant(..)
, getFontSlant, fontSlant, italic, oblique, _fontSlant
, FontWeight(..)
, getFontWeight, fontWeight, bold, bolder, lighter, _fontWeight
, thinWeight, ultraLight, light, mediumWeight, heavy, semiBold, ultraBold
) where
import Control.Lens hiding (transform)
import Diagrams.Attributes (committed)
import Diagrams.Core
import Diagrams.Core.Envelope (pointEnvelope)
import Diagrams.TwoD.Attributes (recommendFillColor)
import Diagrams.TwoD.Types
import Data.Colour hiding (over)
import Data.Default.Class
import Data.Monoid.Recommend
import Data.Semigroup
import Data.Typeable
import Linear.Affine
data Text n = Text (T2 n) (TextAlignment n) String
deriving Typeable
type instance V (Text n) = V2
type instance N (Text n) = n
instance Floating n => Transformable (Text n) where
transform :: Transformation (V (Text n)) (N (Text n)) -> Text n -> Text n
transform Transformation (V (Text n)) (N (Text n))
t (Text T2 n
tt TextAlignment n
a String
s) = forall n. T2 n -> TextAlignment n -> String -> Text n
Text (Transformation (V (Text n)) (N (Text n))
t forall a. Semigroup a => a -> a -> a
<> T2 n
tt forall a. Semigroup a => a -> a -> a
<> T2 n
t') TextAlignment n
a String
s
where t' :: T2 n
t' = forall (v :: * -> *) n.
(Additive v, Fractional n) =>
n -> Transformation v n
scaling (n
1 forall a. Fractional a => a -> a -> a
/ forall (v :: * -> *) n.
(Additive v, Traversable v, Floating n) =>
Transformation v n -> n
avgScale Transformation (V (Text n)) (N (Text n))
t)
instance Floating n => HasOrigin (Text n) where
moveOriginTo :: Point (V (Text n)) (N (Text n)) -> Text n -> Text n
moveOriginTo Point (V (Text n)) (N (Text n))
p = forall t. Transformable t => Vn t -> t -> t
translate (forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin forall (p :: * -> *) a. (Affine p, Num a) => p a -> p a -> Diff p a
.-. Point (V (Text n)) (N (Text n))
p)
instance Floating n => Renderable (Text n) NullBackend where
render :: NullBackend
-> Text n -> Render NullBackend (V (Text n)) (N (Text n))
render NullBackend
_ Text n
_ = forall a. Monoid a => a
mempty
data TextAlignment n = BaselineText | BoxAlignedText n n
mkText :: (TypeableFloat n, Renderable (Text n) b)
=> TextAlignment n -> String -> QDiagram b V2 n Any
mkText :: forall n b.
(TypeableFloat n, Renderable (Text n) b) =>
TextAlignment n -> String -> QDiagram b V2 n Any
mkText TextAlignment n
a = forall n a c.
(InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) =>
c -> a -> a
recommendFillColor forall a. Num a => Colour a
black
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a n.
(N a ~ n, Typeable n, HasStyle a) =>
Measure n -> a -> a
recommendFontSize (forall n. Num n => n -> Measure n
local n
1)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n b.
(TypeableFloat n, Renderable (Text n) b) =>
TextAlignment n -> String -> QDiagram b V2 n Any
mkText' TextAlignment n
a
mkText' :: (TypeableFloat n, Renderable (Text n) b)
=> TextAlignment n -> String -> QDiagram b V2 n Any
mkText' :: forall n b.
(TypeableFloat n, Renderable (Text n) b) =>
TextAlignment n -> String -> QDiagram b V2 n Any
mkText' TextAlignment n
a String
t = forall b (v :: * -> *) n m.
Prim b v n
-> Envelope v n
-> Trace v n
-> SubMap b v n m
-> Query v n m
-> QDiagram b v n m
mkQD (forall p b.
(Transformable p, Typeable p, Renderable p b) =>
p -> Prim b (V p) (N p)
Prim forall a b. (a -> b) -> a -> b
$ forall n. T2 n -> TextAlignment n -> String -> Text n
Text forall a. Monoid a => a
mempty TextAlignment n
a String
t)
(forall n (v :: * -> *).
(Fractional n, Metric v) =>
Point v n -> Envelope v n
pointEnvelope forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin)
forall a. Monoid a => a
mempty
forall a. Monoid a => a
mempty
forall a. Monoid a => a
mempty
text :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any
text :: forall n b.
(TypeableFloat n, Renderable (Text n) b) =>
String -> QDiagram b V2 n Any
text = forall n b.
(TypeableFloat n, Renderable (Text n) b) =>
n -> n -> String -> QDiagram b V2 n Any
alignedText n
0.5 n
0.5
topLeftText :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any
topLeftText :: forall n b.
(TypeableFloat n, Renderable (Text n) b) =>
String -> QDiagram b V2 n Any
topLeftText = forall n b.
(TypeableFloat n, Renderable (Text n) b) =>
n -> n -> String -> QDiagram b V2 n Any
alignedText n
0 n
1
alignedText :: (TypeableFloat n, Renderable (Text n) b)
=> n -> n -> String -> QDiagram b V2 n Any
alignedText :: forall n b.
(TypeableFloat n, Renderable (Text n) b) =>
n -> n -> String -> QDiagram b V2 n Any
alignedText n
w n
h = forall n b.
(TypeableFloat n, Renderable (Text n) b) =>
TextAlignment n -> String -> QDiagram b V2 n Any
mkText (forall n. n -> n -> TextAlignment n
BoxAlignedText n
w n
h)
baselineText :: (TypeableFloat n, Renderable (Text n) b)
=> String -> QDiagram b V2 n Any
baselineText :: forall n b.
(TypeableFloat n, Renderable (Text n) b) =>
String -> QDiagram b V2 n Any
baselineText = forall n b.
(TypeableFloat n, Renderable (Text n) b) =>
TextAlignment n -> String -> QDiagram b V2 n Any
mkText forall n. TextAlignment n
BaselineText
newtype Font = Font (Last String)
deriving (Typeable, NonEmpty Font -> Font
Font -> Font -> Font
forall b. Integral b => b -> Font -> Font
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: forall b. Integral b => b -> Font -> Font
$cstimes :: forall b. Integral b => b -> Font -> Font
sconcat :: NonEmpty Font -> Font
$csconcat :: NonEmpty Font -> Font
<> :: Font -> Font -> Font
$c<> :: Font -> Font -> Font
Semigroup, Font -> Font -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Font -> Font -> Bool
$c/= :: Font -> Font -> Bool
== :: Font -> Font -> Bool
$c== :: Font -> Font -> Bool
Eq)
_Font :: Iso' Font String
_Font :: Iso' Font String
_Font = forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Font -> String
getFont (Last String -> Font
Font forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Last a
Last)
instance AttributeClass Font
getFont :: Font -> String
getFont :: Font -> String
getFont (Font (Last String
f)) = String
f
font :: HasStyle a => String -> a -> a
font :: forall a. HasStyle a => String -> a -> a
font = forall a d. (AttributeClass a, HasStyle d) => a -> d -> d
applyAttr forall b c a. (b -> c) -> (a -> b) -> a -> c
. Last String -> Font
Font forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Last a
Last
_font :: Lens' (Style v n) (Maybe String)
_font :: forall (v :: * -> *) n. Lens' (Style v n) (Maybe String)
_font = forall a (v :: * -> *) n.
AttributeClass a =>
Lens' (Style v n) (Maybe a)
atAttr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
mapping Iso' Font String
_Font
newtype FontSize n = FontSize (Recommend (Last n))
deriving (Typeable, NonEmpty (FontSize n) -> FontSize n
FontSize n -> FontSize n -> FontSize n
forall b. Integral b => b -> FontSize n -> FontSize n
forall n. NonEmpty (FontSize n) -> FontSize n
forall n. FontSize n -> FontSize n -> FontSize n
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
forall n b. Integral b => b -> FontSize n -> FontSize n
stimes :: forall b. Integral b => b -> FontSize n -> FontSize n
$cstimes :: forall n b. Integral b => b -> FontSize n -> FontSize n
sconcat :: NonEmpty (FontSize n) -> FontSize n
$csconcat :: forall n. NonEmpty (FontSize n) -> FontSize n
<> :: FontSize n -> FontSize n -> FontSize n
$c<> :: forall n. FontSize n -> FontSize n -> FontSize n
Semigroup)
instance Functor FontSize where
fmap :: forall a b. (a -> b) -> FontSize a -> FontSize b
fmap a -> b
f (FontSize (Recommend (Last a
a))) = forall n. Recommend (Last n) -> FontSize n
FontSize (forall a. a -> Recommend a
Recommend (forall a. a -> Last a
Last (a -> b
f a
a)))
fmap a -> b
f (FontSize (Commit (Last a
a))) = forall n. Recommend (Last n) -> FontSize n
FontSize (forall a. a -> Recommend a
Commit (forall a. a -> Last a
Last (a -> b
f a
a)))
_FontSize :: Iso' (FontSize n) (Recommend n)
_FontSize :: forall n. Iso' (FontSize n) (Recommend n)
_FontSize = forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso forall {a}. FontSize a -> Recommend a
getter forall {n}. Recommend n -> FontSize n
setter
where getter :: FontSize a -> Recommend a
getter (FontSize (Recommend (Last a
a))) = forall a. a -> Recommend a
Recommend a
a
getter (FontSize (Commit (Last a
a))) = forall a. a -> Recommend a
Commit a
a
setter :: Recommend n -> FontSize n
setter (Recommend n
a) = forall n. Recommend (Last n) -> FontSize n
FontSize forall a b. (a -> b) -> a -> b
$ forall a. a -> Recommend a
Recommend (forall a. a -> Last a
Last n
a)
setter (Commit n
a) = forall n. Recommend (Last n) -> FontSize n
FontSize forall a b. (a -> b) -> a -> b
$ forall a. a -> Recommend a
Commit (forall a. a -> Last a
Last n
a)
_FontSizeM :: Iso' (FontSizeM n) (Measured n (Recommend n))
_FontSizeM :: forall n. Iso' (FontSizeM n) (Measured n (Recommend n))
_FontSizeM = forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
mapping forall n. Iso' (FontSize n) (Recommend n)
_FontSize
type FontSizeM n = Measured n (FontSize n)
instance Typeable n => AttributeClass (FontSize n)
instance Num n => Default (FontSizeM n) where
def :: FontSizeM n
def = forall n. Recommend (Last n) -> FontSize n
FontSize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Recommend a
Recommend forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Last a
Last forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall n. Num n => n -> Measure n
local n
1
getFontSize :: FontSize n -> n
getFontSize :: forall n. FontSize n -> n
getFontSize (FontSize (Recommend (Last n
s))) = n
s
getFontSize (FontSize (Commit (Last n
s))) = n
s
fontSize :: (N a ~ n, Typeable n, HasStyle a) => Measure n -> a -> a
fontSize :: forall a n.
(N a ~ n, Typeable n, HasStyle a) =>
Measure n -> a -> a
fontSize = forall a d n.
(AttributeClass a, N d ~ n, HasStyle d) =>
Measured n a -> d -> d
applyMAttr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall n. Recommend (Last n) -> FontSize n
FontSize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Recommend a
Commit forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Last a
Last)
recommendFontSize :: (N a ~ n, Typeable n, HasStyle a) => Measure n -> a -> a
recommendFontSize :: forall a n.
(N a ~ n, Typeable n, HasStyle a) =>
Measure n -> a -> a
recommendFontSize = forall a d n.
(AttributeClass a, N d ~ n, HasStyle d) =>
Measured n a -> d -> d
applyMAttr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall n. Recommend (Last n) -> FontSize n
FontSize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Recommend a
Recommend forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Last a
Last)
fontSizeG :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a
fontSizeG :: forall a n. (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a
fontSizeG = forall a n.
(N a ~ n, Typeable n, HasStyle a) =>
Measure n -> a -> a
fontSize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. Num n => n -> Measure n
global
fontSizeN :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a
fontSizeN :: forall a n. (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a
fontSizeN = forall a n.
(N a ~ n, Typeable n, HasStyle a) =>
Measure n -> a -> a
fontSize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. Num n => n -> Measure n
normalized
fontSizeO :: (N a ~ n, Typeable n, HasStyle a) => n -> a -> a
fontSizeO :: forall a n. (N a ~ n, Typeable n, HasStyle a) => n -> a -> a
fontSizeO = forall a n.
(N a ~ n, Typeable n, HasStyle a) =>
Measure n -> a -> a
fontSize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. n -> Measure n
output
fontSizeL :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a
fontSizeL :: forall a n. (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a
fontSizeL = forall a n.
(N a ~ n, Typeable n, HasStyle a) =>
Measure n -> a -> a
fontSize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. Num n => n -> Measure n
local
fontSizeM :: (N a ~ n, Typeable n, HasStyle a) => FontSizeM n -> a -> a
fontSizeM :: forall a n.
(N a ~ n, Typeable n, HasStyle a) =>
FontSizeM n -> a -> a
fontSizeM = forall a d n.
(AttributeClass a, N d ~ n, HasStyle d) =>
Measured n a -> d -> d
applyMAttr
_fontSizeR :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measured n (Recommend n))
_fontSizeR :: forall n (v :: * -> *).
(Typeable n, OrderedField n) =>
Lens' (Style v n) (Measured n (Recommend n))
_fontSizeR = forall a n (v :: * -> *).
(AttributeClass a, Typeable n) =>
Lens' (Style v n) (Maybe (Measured n a))
atMAttr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> (a -> Bool) -> Iso' (Maybe a) a
anon forall a. Default a => a
def (forall a b. a -> b -> a
const Bool
False) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. Iso' (FontSizeM n) (Measured n (Recommend n))
_FontSizeM
_fontSize :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measure n)
_fontSize :: forall n (v :: * -> *).
(Typeable n, OrderedField n) =>
Lens' (Style v n) (Measure n)
_fontSize = forall n (v :: * -> *).
(Typeable n, OrderedField n) =>
Lens' (Style v n) (Measured n (Recommend n))
_fontSizeR forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
mapping forall a b. Iso (Recommend a) (Recommend b) a b
committed
_fontSizeU :: (Typeable n) => Lens' (Style v n) (Maybe n)
_fontSizeU :: forall n (v :: * -> *). Typeable n => Lens' (Style v n) (Maybe n)
_fontSizeU = forall a (v :: * -> *) n.
AttributeClass a =>
Lens' (Style v n) (Maybe a)
atAttr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
mapping (forall n. Iso' (FontSize n) (Recommend n)
_FontSize forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Iso (Recommend a) (Recommend b) a b
committed)
data FontSlant = FontSlantNormal
| FontSlantItalic
| FontSlantOblique
deriving (FontSlant -> FontSlant -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontSlant -> FontSlant -> Bool
$c/= :: FontSlant -> FontSlant -> Bool
== :: FontSlant -> FontSlant -> Bool
$c== :: FontSlant -> FontSlant -> Bool
Eq, Int -> FontSlant -> ShowS
[FontSlant] -> ShowS
FontSlant -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontSlant] -> ShowS
$cshowList :: [FontSlant] -> ShowS
show :: FontSlant -> String
$cshow :: FontSlant -> String
showsPrec :: Int -> FontSlant -> ShowS
$cshowsPrec :: Int -> FontSlant -> ShowS
Show, Typeable, Eq FontSlant
FontSlant -> FontSlant -> Bool
FontSlant -> FontSlant -> Ordering
FontSlant -> FontSlant -> FontSlant
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FontSlant -> FontSlant -> FontSlant
$cmin :: FontSlant -> FontSlant -> FontSlant
max :: FontSlant -> FontSlant -> FontSlant
$cmax :: FontSlant -> FontSlant -> FontSlant
>= :: FontSlant -> FontSlant -> Bool
$c>= :: FontSlant -> FontSlant -> Bool
> :: FontSlant -> FontSlant -> Bool
$c> :: FontSlant -> FontSlant -> Bool
<= :: FontSlant -> FontSlant -> Bool
$c<= :: FontSlant -> FontSlant -> Bool
< :: FontSlant -> FontSlant -> Bool
$c< :: FontSlant -> FontSlant -> Bool
compare :: FontSlant -> FontSlant -> Ordering
$ccompare :: FontSlant -> FontSlant -> Ordering
Ord)
instance AttributeClass FontSlant where
instance Semigroup FontSlant where
FontSlant
_ <> :: FontSlant -> FontSlant -> FontSlant
<> FontSlant
b = FontSlant
b
instance Default FontSlant where
def :: FontSlant
def = FontSlant
FontSlantNormal
getFontSlant :: FontSlant -> FontSlant
getFontSlant :: FontSlant -> FontSlant
getFontSlant = forall a. a -> a
id
fontSlant :: HasStyle a => FontSlant -> a -> a
fontSlant :: forall a. HasStyle a => FontSlant -> a -> a
fontSlant = forall a d. (AttributeClass a, HasStyle d) => a -> d -> d
applyAttr
_fontSlant :: Lens' (Style v n) FontSlant
_fontSlant :: forall (v :: * -> *) n. Lens' (Style v n) FontSlant
_fontSlant = forall a (v :: * -> *) n.
AttributeClass a =>
Lens' (Style v n) (Maybe a)
atAttr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => a -> Iso' (Maybe a) a
non forall a. Default a => a
def
italic :: HasStyle a => a -> a
italic :: forall a. HasStyle a => a -> a
italic = forall a. HasStyle a => FontSlant -> a -> a
fontSlant FontSlant
FontSlantItalic
oblique :: HasStyle a => a -> a
oblique :: forall a. HasStyle a => a -> a
oblique = forall a. HasStyle a => FontSlant -> a -> a
fontSlant FontSlant
FontSlantOblique
data FontWeight = FontWeightNormal
| FontWeightBold
| FontWeightBolder
| FontWeightLighter
| FontWeightThin
| FontWeightUltraLight
| FontWeightLight
| FontWeightMedium
| FontWeightSemiBold
| FontWeightUltraBold
| FontWeightHeavy
deriving (FontWeight -> FontWeight -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontWeight -> FontWeight -> Bool
$c/= :: FontWeight -> FontWeight -> Bool
== :: FontWeight -> FontWeight -> Bool
$c== :: FontWeight -> FontWeight -> Bool
Eq,
Eq FontWeight
FontWeight -> FontWeight -> Bool
FontWeight -> FontWeight -> Ordering
FontWeight -> FontWeight -> FontWeight
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FontWeight -> FontWeight -> FontWeight
$cmin :: FontWeight -> FontWeight -> FontWeight
max :: FontWeight -> FontWeight -> FontWeight
$cmax :: FontWeight -> FontWeight -> FontWeight
>= :: FontWeight -> FontWeight -> Bool
$c>= :: FontWeight -> FontWeight -> Bool
> :: FontWeight -> FontWeight -> Bool
$c> :: FontWeight -> FontWeight -> Bool
<= :: FontWeight -> FontWeight -> Bool
$c<= :: FontWeight -> FontWeight -> Bool
< :: FontWeight -> FontWeight -> Bool
$c< :: FontWeight -> FontWeight -> Bool
compare :: FontWeight -> FontWeight -> Ordering
$ccompare :: FontWeight -> FontWeight -> Ordering
Ord, Int -> FontWeight -> ShowS
[FontWeight] -> ShowS
FontWeight -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontWeight] -> ShowS
$cshowList :: [FontWeight] -> ShowS
show :: FontWeight -> String
$cshow :: FontWeight -> String
showsPrec :: Int -> FontWeight -> ShowS
$cshowsPrec :: Int -> FontWeight -> ShowS
Show, Typeable)
instance AttributeClass FontWeight
instance Semigroup FontWeight where
FontWeight
_ <> :: FontWeight -> FontWeight -> FontWeight
<> FontWeight
b = FontWeight
b
instance Default FontWeight where
def :: FontWeight
def = FontWeight
FontWeightNormal
getFontWeight :: FontWeight -> FontWeight
getFontWeight :: FontWeight -> FontWeight
getFontWeight = forall a. a -> a
id
fontWeight :: HasStyle a => FontWeight -> a -> a
fontWeight :: forall a. HasStyle a => FontWeight -> a -> a
fontWeight = forall a d. (AttributeClass a, HasStyle d) => a -> d -> d
applyAttr
bold :: HasStyle a => a -> a
bold :: forall a. HasStyle a => a -> a
bold = forall a. HasStyle a => FontWeight -> a -> a
fontWeight FontWeight
FontWeightBold
thinWeight :: HasStyle a => a -> a
thinWeight :: forall a. HasStyle a => a -> a
thinWeight = forall a. HasStyle a => FontWeight -> a -> a
fontWeight FontWeight
FontWeightThin
ultraLight :: HasStyle a => a -> a
ultraLight :: forall a. HasStyle a => a -> a
ultraLight = forall a. HasStyle a => FontWeight -> a -> a
fontWeight FontWeight
FontWeightUltraLight
light :: HasStyle a => a -> a
light :: forall a. HasStyle a => a -> a
light = forall a. HasStyle a => FontWeight -> a -> a
fontWeight FontWeight
FontWeightLight
mediumWeight :: HasStyle a => a -> a
mediumWeight :: forall a. HasStyle a => a -> a
mediumWeight = forall a. HasStyle a => FontWeight -> a -> a
fontWeight FontWeight
FontWeightMedium
semiBold :: HasStyle a => a -> a
semiBold :: forall a. HasStyle a => a -> a
semiBold = forall a. HasStyle a => FontWeight -> a -> a
fontWeight FontWeight
FontWeightSemiBold
ultraBold :: HasStyle a => a -> a
ultraBold :: forall a. HasStyle a => a -> a
ultraBold = forall a. HasStyle a => FontWeight -> a -> a
fontWeight FontWeight
FontWeightUltraBold
heavy :: HasStyle a => a -> a
heavy :: forall a. HasStyle a => a -> a
heavy = forall a. HasStyle a => FontWeight -> a -> a
fontWeight FontWeight
FontWeightHeavy
bolder :: HasStyle a => a -> a
bolder :: forall a. HasStyle a => a -> a
bolder = forall a. HasStyle a => FontWeight -> a -> a
fontWeight FontWeight
FontWeightBolder
lighter :: HasStyle a => a -> a
lighter :: forall a. HasStyle a => a -> a
lighter = forall a. HasStyle a => FontWeight -> a -> a
fontWeight FontWeight
FontWeightLighter
_fontWeight :: Lens' (Style v n) FontWeight
_fontWeight :: forall (v :: * -> *) n. Lens' (Style v n) FontWeight
_fontWeight = forall a (v :: * -> *) n.
AttributeClass a =>
Lens' (Style v n) (Maybe a)
atAttr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Eq a => a -> Iso' (Maybe a) a
non forall a. Default a => a
def