{-# LANGUAGE OverloadedStrings #-}
module Clay.FontFace
( FontFaceFormat (..)
, FontFaceSrc (..)
, fontFaceSrc
) where
import Clay.Common (call)
import Clay.Property (Prefixed (Plain), Value(Value), Val (value), quote)
import Clay.Stylesheet (Css, key)
import Data.Maybe (fromMaybe)
import Data.Text (Text)
data FontFaceFormat
= WOFF
| WOFF2
| TrueType
| OpenType
| EmbeddedOpenType
| SVG
deriving Int -> FontFaceFormat -> ShowS
[FontFaceFormat] -> ShowS
FontFaceFormat -> String
(Int -> FontFaceFormat -> ShowS)
-> (FontFaceFormat -> String)
-> ([FontFaceFormat] -> ShowS)
-> Show FontFaceFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontFaceFormat] -> ShowS
$cshowList :: [FontFaceFormat] -> ShowS
show :: FontFaceFormat -> String
$cshow :: FontFaceFormat -> String
showsPrec :: Int -> FontFaceFormat -> ShowS
$cshowsPrec :: Int -> FontFaceFormat -> ShowS
Show
formatName :: FontFaceFormat -> Text
formatName :: FontFaceFormat -> Text
formatName FontFaceFormat
format = case FontFaceFormat
format of
FontFaceFormat
WOFF -> Text
"woff"
FontFaceFormat
WOFF2 -> Text
"woff2"
FontFaceFormat
TrueType -> Text
"truetype"
FontFaceFormat
OpenType -> Text
"opentype"
FontFaceFormat
EmbeddedOpenType -> Text
"embedded-opentype"
FontFaceFormat
SVG -> Text
"svg"
data FontFaceSrc
= FontFaceSrcUrl Text (Maybe FontFaceFormat)
| FontFaceSrcLocal Text
deriving Int -> FontFaceSrc -> ShowS
[FontFaceSrc] -> ShowS
FontFaceSrc -> String
(Int -> FontFaceSrc -> ShowS)
-> (FontFaceSrc -> String)
-> ([FontFaceSrc] -> ShowS)
-> Show FontFaceSrc
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontFaceSrc] -> ShowS
$cshowList :: [FontFaceSrc] -> ShowS
show :: FontFaceSrc -> String
$cshow :: FontFaceSrc -> String
showsPrec :: Int -> FontFaceSrc -> ShowS
$cshowsPrec :: Int -> FontFaceSrc -> ShowS
Show
instance Val FontFaceSrc where
value :: FontFaceSrc -> Value
value FontFaceSrc
src = Prefixed -> Value
Value (Prefixed -> Value) -> Prefixed -> Value
forall a b. (a -> b) -> a -> b
$ Text -> Prefixed
Plain (Text -> Prefixed) -> Text -> Prefixed
forall a b. (a -> b) -> a -> b
$ case FontFaceSrc
src of
FontFaceSrcLocal Text
name -> Text -> Text -> Text
forall s. (IsString s, Monoid s) => s -> s -> s
call Text
"local" (Text -> Text
quote Text
name)
FontFaceSrcUrl Text
url Maybe FontFaceFormat
mformat ->
Text -> Text -> Text
forall s. (IsString s, Monoid s) => s -> s -> s
call Text
"url" (Text -> Text
quote Text
url)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (Text -> Text -> Text
forall s. (IsString s, Monoid s) => s -> s -> s
call Text
"format" (Text -> Text)
-> (FontFaceFormat -> Text) -> FontFaceFormat -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
quote (Text -> Text)
-> (FontFaceFormat -> Text) -> FontFaceFormat -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FontFaceFormat -> Text
formatName (FontFaceFormat -> Text) -> Maybe FontFaceFormat -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FontFaceFormat
mformat)
fontFaceSrc :: [FontFaceSrc] -> Css
fontFaceSrc :: [FontFaceSrc] -> Css
fontFaceSrc = Key [FontFaceSrc] -> [FontFaceSrc] -> Css
forall a. Val a => Key a -> a -> Css
key Key [FontFaceSrc]
"src"