{-# LANGUAGE
OverloadedStrings
, GeneralizedNewtypeDeriving
, FlexibleInstances
#-}
module Clay.Font
(
Font (font)
, Optional (..)
, Required (..)
, fontColor
, color
, fontFamily
, sansSerif
, serif
, monospace
, cursive
, fantasy
, FontSize
, fontSize
, fontSizeCustom
, xxSmall, xSmall, small, medium, large, xLarge, xxLarge, smaller, larger
, FontStyle
, fontStyle
, italic, oblique
, FontVariant
, fontVariant
, smallCaps
, FontWeight
, fontWeight
, bold, bolder, lighter
, weight
, NamedFont
, caption, icon, menu, messageBox, smallCaption, statusBar
, lineHeight
)
where
import Control.Applicative
import Data.Text (pack, Text)
import Data.Monoid
import Prelude hiding (Left, Right)
import Clay.Color
import Clay.Common
import Clay.Property
import Clay.Stylesheet
import Clay.Size
class Val a => Font a where
font :: a -> Css
font = key "font"
data Optional =
Optional
(Maybe FontWeight)
(Maybe FontVariant)
(Maybe FontStyle)
instance Val Optional where
value (Optional a b c) = value (a ! b ! c)
data Required a =
Required
(Size a)
(Maybe (Size a))
[Text]
[GenericFontFamily]
instance Val (Required a) where
value (Required a Nothing c d) = value (a ! (Literal <$> c) ! d)
value (Required a (Just b) c d) = value ((value a <> "/" <> value b) ! (Literal <$> c) ! d)
instance Font ( Required a)
instance Font (Optional, Required a)
fontColor :: Color -> Css
fontColor = key "color"
color :: Color -> Css
color = key "color"
newtype GenericFontFamily = GenericFontFamily Value
deriving (Val, Inherit, Auto, Other)
sansSerif, serif, monospace, cursive, fantasy :: GenericFontFamily
sansSerif = GenericFontFamily "sans-serif"
serif = GenericFontFamily "serif"
monospace = GenericFontFamily "monospace"
cursive = GenericFontFamily "cursive"
fantasy = GenericFontFamily "fantasy"
fontFamily :: [Text] -> [GenericFontFamily] -> Css
fontFamily a b = key "font-family" $
let sep = if null a || null b then "" else ", "
in value (Literal <$> a) <> sep <> value b
newtype FontSize = FontSize Value
deriving (Val, Inherit, Auto, Other)
xxSmall, xSmall, small, medium, large, xLarge, xxLarge, smaller, larger :: FontSize
xxSmall = FontSize "xx-small"
xSmall = FontSize "x-small"
small = FontSize "small"
medium = FontSize "medium"
large = FontSize "large"
xLarge = FontSize "x-large"
xxLarge = FontSize "xx-large"
smaller = FontSize "smaller"
larger = FontSize "larger"
fontSize :: Size a -> Css
fontSize = key "font-size"
fontSizeCustom :: FontSize -> Css
fontSizeCustom = key "font-size"
newtype FontStyle = FontStyle Value
deriving (Val, Inherit, Normal, Other)
italic, oblique :: FontStyle
italic = FontStyle "italic"
oblique = FontStyle "oblique"
fontStyle :: FontStyle -> Css
fontStyle = key "font-style"
newtype FontVariant = FontVariant Value
deriving (Val, Inherit, Normal, Other)
smallCaps :: FontVariant
smallCaps = FontVariant "small-caps"
fontVariant :: FontVariant -> Css
fontVariant = key "font-variant"
newtype FontWeight = FontWeight Value
deriving (Val, Inherit, Normal, Other)
bold, bolder, lighter :: FontWeight
bold = FontWeight "bold"
bolder = FontWeight "bolder"
lighter = FontWeight "lighter"
weight :: Integer -> FontWeight
weight i = FontWeight (value (pack (show i)))
fontWeight :: FontWeight -> Css
fontWeight = key "font-weight"
newtype NamedFont = NamedFont Value
deriving (Val, Other)
caption, icon, menu, messageBox, smallCaption, statusBar :: NamedFont
caption = NamedFont "caption"
icon = NamedFont "icon"
menu = NamedFont "menu"
messageBox = NamedFont "message-box"
smallCaption = NamedFont "small-caption"
statusBar = NamedFont "status-bar"
lineHeight :: Size a -> Css
lineHeight = key "line-height"