{-# LANGUAGE OverloadedStrings, GeneralizedNewtypeDeriving #-}
module Clay.Text
(
letterSpacing
, wordSpacing
, TextRendering
, textRendering
, optimizeSpeed, optimizeLegibility, geometricPrecision
, textShadow
, TextIndent
, textIndent
, eachLine, hanging
, indent
, TextDirection
, direction
, ltr
, rtl
, TextAlign
, textAlign
, textAlignLast
, justify, matchParent, start, end
, alignSide
, alignString
, WhiteSpace
, whiteSpace
, pre, nowrap, preWrap, preLine
, TextDecoration
, textDecoration
, textDecorationStyle
, textDecorationLine
, textDecorationColor
, underline, overline, lineThrough, blink
, TextTransform
, textTransform
, capitalize, uppercase, lowercase, fullWidth
, TextOverflow
, textOverflow
, overflowClip, overflowEllipsis
, WordBreak
, wordBreak
, breakAll
, keepAll
, OverflowWrap
, overflowWrap
, wordWrap
, breakWord
, Content
, content
, contents
, attrContent
, stringContent
, uriContent
, urlContent
, openQuote, closeQuote, noOpenQuote, noCloseQuote
)
where
import Data.String
import Data.Text (Text)
import Clay.Background
import Clay.Border
import Clay.Color
import Clay.Common
import Clay.Property
import Clay.Stylesheet
import Clay.Size
letterSpacing :: Size a -> Css
letterSpacing :: Size a -> Css
letterSpacing = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"letter-spacing"
wordSpacing :: Size a -> Css
wordSpacing :: Size a -> Css
wordSpacing = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"word-spacing"
newtype TextRendering = TextRendering Value
deriving (TextRendering -> Value
(TextRendering -> Value) -> Val TextRendering
forall a. (a -> Value) -> Val a
value :: TextRendering -> Value
$cvalue :: TextRendering -> Value
Val, TextRendering
TextRendering -> Auto TextRendering
forall a. a -> Auto a
auto :: TextRendering
$cauto :: TextRendering
Auto, TextRendering
TextRendering -> Inherit TextRendering
forall a. a -> Inherit a
inherit :: TextRendering
$cinherit :: TextRendering
Inherit, Value -> TextRendering
(Value -> TextRendering) -> Other TextRendering
forall a. (Value -> a) -> Other a
other :: Value -> TextRendering
$cother :: Value -> TextRendering
Other)
optimizeSpeed, optimizeLegibility, geometricPrecision :: TextRendering
optimizeSpeed :: TextRendering
optimizeSpeed = Value -> TextRendering
TextRendering Value
"optimizeSpeed"
optimizeLegibility :: TextRendering
optimizeLegibility = Value -> TextRendering
TextRendering Value
"optimizeLegibility"
geometricPrecision :: TextRendering
geometricPrecision = Value -> TextRendering
TextRendering Value
"geometricPrecision"
textRendering :: TextRendering -> Css
textRendering :: TextRendering -> Css
textRendering = Key TextRendering -> TextRendering -> Css
forall a. Val a => Key a -> a -> Css
key Key TextRendering
"text-rendering"
textShadow :: Size a -> Size a -> Size a -> Color -> Css
textShadow :: Size a -> Size a -> Size a -> Color -> Css
textShadow Size a
x Size a
y Size a
w Color
c = Key (Size a, (Size a, (Size a, Color)))
-> (Size a, (Size a, (Size a, Color))) -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a, (Size a, (Size a, Color)))
"text-shadow" (Size a
x Size a
-> (Size a, (Size a, Color)) -> (Size a, (Size a, (Size a, Color)))
forall a b. a -> b -> (a, b)
! Size a
y Size a -> (Size a, Color) -> (Size a, (Size a, Color))
forall a b. a -> b -> (a, b)
! Size a
w Size a -> Color -> (Size a, Color)
forall a b. a -> b -> (a, b)
! Color
c)
newtype TextIndent = TextIndent Value
deriving (TextIndent -> Value
(TextIndent -> Value) -> Val TextIndent
forall a. (a -> Value) -> Val a
value :: TextIndent -> Value
$cvalue :: TextIndent -> Value
Val, TextIndent
TextIndent -> Inherit TextIndent
forall a. a -> Inherit a
inherit :: TextIndent
$cinherit :: TextIndent
Inherit, TextIndent
TextIndent -> Initial TextIndent
forall a. a -> Initial a
initial :: TextIndent
$cinitial :: TextIndent
Initial, TextIndent
TextIndent -> Unset TextIndent
forall a. a -> Unset a
unset :: TextIndent
$cunset :: TextIndent
Unset, Value -> TextIndent
(Value -> TextIndent) -> Other TextIndent
forall a. (Value -> a) -> Other a
other :: Value -> TextIndent
$cother :: Value -> TextIndent
Other)
tagTextIndent :: Value -> TextIndent -> TextIndent
tagTextIndent :: Value -> TextIndent -> TextIndent
tagTextIndent Value
v (TextIndent Value
v0) = Value -> TextIndent
TextIndent (Value -> TextIndent)
-> ((Value, Value) -> Value) -> (Value, Value) -> TextIndent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Value, Value) -> Value
forall a. Val a => a -> Value
value ((Value, Value) -> TextIndent) -> (Value, Value) -> TextIndent
forall a b. (a -> b) -> a -> b
$ (Value
v0, Value
v)
eachLine, hanging :: TextIndent -> TextIndent
eachLine :: TextIndent -> TextIndent
eachLine = Value -> TextIndent -> TextIndent
tagTextIndent Value
"each-line"
hanging :: TextIndent -> TextIndent
hanging = Value -> TextIndent -> TextIndent
tagTextIndent Value
"hanging"
indent :: Size a -> TextIndent
indent :: Size a -> TextIndent
indent = Value -> TextIndent
TextIndent (Value -> TextIndent) -> (Size a -> Value) -> Size a -> TextIndent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Size a -> Value
forall a. Val a => a -> Value
value
textIndent :: TextIndent -> Css
textIndent :: TextIndent -> Css
textIndent = Key TextIndent -> TextIndent -> Css
forall a. Val a => Key a -> a -> Css
key Key TextIndent
"text-indent"
newtype TextDirection = TextDirection Value
deriving (TextDirection -> Value
(TextDirection -> Value) -> Val TextDirection
forall a. (a -> Value) -> Val a
value :: TextDirection -> Value
$cvalue :: TextDirection -> Value
Val, TextDirection
TextDirection -> Normal TextDirection
forall a. a -> Normal a
normal :: TextDirection
$cnormal :: TextDirection
Normal, TextDirection
TextDirection -> Inherit TextDirection
forall a. a -> Inherit a
inherit :: TextDirection
$cinherit :: TextDirection
Inherit, Value -> TextDirection
(Value -> TextDirection) -> Other TextDirection
forall a. (Value -> a) -> Other a
other :: Value -> TextDirection
$cother :: Value -> TextDirection
Other)
ltr :: TextDirection
ltr :: TextDirection
ltr = Value -> TextDirection
TextDirection Value
"ltr"
rtl :: TextDirection
rtl :: TextDirection
rtl = Value -> TextDirection
TextDirection Value
"rtl"
direction :: TextDirection -> Css
direction :: TextDirection -> Css
direction = Key TextDirection -> TextDirection -> Css
forall a. Val a => Key a -> a -> Css
key Key TextDirection
"direction"
newtype TextAlign = TextAlign Value
deriving (TextAlign -> Value
(TextAlign -> Value) -> Val TextAlign
forall a. (a -> Value) -> Val a
value :: TextAlign -> Value
$cvalue :: TextAlign -> Value
Val, TextAlign
TextAlign -> Normal TextAlign
forall a. a -> Normal a
normal :: TextAlign
$cnormal :: TextAlign
Normal, TextAlign
TextAlign -> Inherit TextAlign
forall a. a -> Inherit a
inherit :: TextAlign
$cinherit :: TextAlign
Inherit, Value -> TextAlign
(Value -> TextAlign) -> Other TextAlign
forall a. (Value -> a) -> Other a
other :: Value -> TextAlign
$cother :: Value -> TextAlign
Other, TextAlign
TextAlign -> Center TextAlign
forall a. a -> Center a
center :: TextAlign
$ccenter :: TextAlign
Center)
justify, matchParent, start, end :: TextAlign
justify :: TextAlign
justify = Value -> TextAlign
TextAlign Value
"justify"
matchParent :: TextAlign
matchParent = Value -> TextAlign
TextAlign Value
"match-parent"
start :: TextAlign
start = Value -> TextAlign
TextAlign Value
"start"
end :: TextAlign
end = Value -> TextAlign
TextAlign Value
"end"
alignSide :: Side -> TextAlign
alignSide :: Side -> TextAlign
alignSide = Value -> TextAlign
TextAlign (Value -> TextAlign) -> (Side -> Value) -> Side -> TextAlign
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Side -> Value
forall a. Val a => a -> Value
value
alignString :: Char -> TextAlign
alignString :: Char -> TextAlign
alignString = Value -> TextAlign
TextAlign (Value -> TextAlign) -> (Char -> Value) -> Char -> TextAlign
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Literal -> Value
forall a. Val a => a -> Value
value (Literal -> Value) -> (Char -> Literal) -> Char -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Literal
Literal (Text -> Literal) -> (Char -> Text) -> Char -> Literal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. IsString a => String -> a
fromString (String -> Text) -> (Char -> String) -> Char -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> String
forall (m :: * -> *) a. Monad m => a -> m a
return
textAlign :: TextAlign -> Css
textAlign :: TextAlign -> Css
textAlign = Key TextAlign -> TextAlign -> Css
forall a. Val a => Key a -> a -> Css
key Key TextAlign
"text-align"
textAlignLast :: TextAlign -> Css
textAlignLast :: TextAlign -> Css
textAlignLast = Key TextAlign -> TextAlign -> Css
forall a. Val a => Key a -> a -> Css
key Key TextAlign
"text-align-last"
newtype WhiteSpace = WhiteSpace Value
deriving (WhiteSpace -> Value
(WhiteSpace -> Value) -> Val WhiteSpace
forall a. (a -> Value) -> Val a
value :: WhiteSpace -> Value
$cvalue :: WhiteSpace -> Value
Val, WhiteSpace
WhiteSpace -> Normal WhiteSpace
forall a. a -> Normal a
normal :: WhiteSpace
$cnormal :: WhiteSpace
Normal, WhiteSpace
WhiteSpace -> Inherit WhiteSpace
forall a. a -> Inherit a
inherit :: WhiteSpace
$cinherit :: WhiteSpace
Inherit, Value -> WhiteSpace
(Value -> WhiteSpace) -> Other WhiteSpace
forall a. (Value -> a) -> Other a
other :: Value -> WhiteSpace
$cother :: Value -> WhiteSpace
Other)
whiteSpace :: WhiteSpace -> Css
whiteSpace :: WhiteSpace -> Css
whiteSpace = Key WhiteSpace -> WhiteSpace -> Css
forall a. Val a => Key a -> a -> Css
key Key WhiteSpace
"white-space"
pre, nowrap, preWrap, preLine :: WhiteSpace
pre :: WhiteSpace
pre = Value -> WhiteSpace
WhiteSpace Value
"pre"
nowrap :: WhiteSpace
nowrap = Value -> WhiteSpace
WhiteSpace Value
"nowrap"
preWrap :: WhiteSpace
preWrap = Value -> WhiteSpace
WhiteSpace Value
"pre-wrap"
preLine :: WhiteSpace
preLine = Value -> WhiteSpace
WhiteSpace Value
"pre-line"
newtype TextDecoration = TextDecoration Value
deriving (TextDecoration -> Value
(TextDecoration -> Value) -> Val TextDecoration
forall a. (a -> Value) -> Val a
value :: TextDecoration -> Value
$cvalue :: TextDecoration -> Value
Val, TextDecoration
TextDecoration -> None TextDecoration
forall a. a -> None a
none :: TextDecoration
$cnone :: TextDecoration
None, TextDecoration
TextDecoration -> Inherit TextDecoration
forall a. a -> Inherit a
inherit :: TextDecoration
$cinherit :: TextDecoration
Inherit, Value -> TextDecoration
(Value -> TextDecoration) -> Other TextDecoration
forall a. (Value -> a) -> Other a
other :: Value -> TextDecoration
$cother :: Value -> TextDecoration
Other)
underline, overline, lineThrough, blink :: TextDecoration
underline :: TextDecoration
underline = Value -> TextDecoration
TextDecoration Value
"underline"
overline :: TextDecoration
overline = Value -> TextDecoration
TextDecoration Value
"overline"
lineThrough :: TextDecoration
lineThrough = Value -> TextDecoration
TextDecoration Value
"line-through"
blink :: TextDecoration
blink = Value -> TextDecoration
TextDecoration Value
"blink"
textDecorationLine :: TextDecoration -> Css
textDecorationLine :: TextDecoration -> Css
textDecorationLine = Key TextDecoration -> TextDecoration -> Css
forall a. Val a => Key a -> a -> Css
key Key TextDecoration
"text-decoration-line"
textDecorationColor :: Color -> Css
textDecorationColor :: Color -> Css
textDecorationColor = Key Color -> Color -> Css
forall a. Val a => Key a -> a -> Css
key Key Color
"text-decoration-color"
textDecoration :: TextDecoration -> Css
textDecoration :: TextDecoration -> Css
textDecoration = Key TextDecoration -> TextDecoration -> Css
forall a. Val a => Key a -> a -> Css
key Key TextDecoration
"text-decoration"
textDecorationStyle :: Stroke -> Css
textDecorationStyle :: Stroke -> Css
textDecorationStyle = Key Stroke -> Stroke -> Css
forall a. Val a => Key a -> a -> Css
key Key Stroke
"text-decoration-style"
newtype TextTransform = TextTransform Value
deriving (TextTransform -> Value
(TextTransform -> Value) -> Val TextTransform
forall a. (a -> Value) -> Val a
value :: TextTransform -> Value
$cvalue :: TextTransform -> Value
Val, TextTransform
TextTransform -> None TextTransform
forall a. a -> None a
none :: TextTransform
$cnone :: TextTransform
None, TextTransform
TextTransform -> Inherit TextTransform
forall a. a -> Inherit a
inherit :: TextTransform
$cinherit :: TextTransform
Inherit)
capitalize, uppercase, lowercase, fullWidth :: TextTransform
capitalize :: TextTransform
capitalize = Value -> TextTransform
TextTransform Value
"capitalize"
uppercase :: TextTransform
uppercase = Value -> TextTransform
TextTransform Value
"uppercase"
lowercase :: TextTransform
lowercase = Value -> TextTransform
TextTransform Value
"lowercase"
fullWidth :: TextTransform
fullWidth = Value -> TextTransform
TextTransform Value
"full-width"
textTransform :: TextTransform -> Css
textTransform :: TextTransform -> Css
textTransform = Key TextTransform -> TextTransform -> Css
forall a. Val a => Key a -> a -> Css
key Key TextTransform
"text-transform"
newtype WordBreak = WordBreak Value
deriving (WordBreak -> Value
(WordBreak -> Value) -> Val WordBreak
forall a. (a -> Value) -> Val a
value :: WordBreak -> Value
$cvalue :: WordBreak -> Value
Val, WordBreak
WordBreak -> Inherit WordBreak
forall a. a -> Inherit a
inherit :: WordBreak
$cinherit :: WordBreak
Inherit, WordBreak
WordBreak -> Initial WordBreak
forall a. a -> Initial a
initial :: WordBreak
$cinitial :: WordBreak
Initial, WordBreak
WordBreak -> Unset WordBreak
forall a. a -> Unset a
unset :: WordBreak
$cunset :: WordBreak
Unset, WordBreak
WordBreak -> Normal WordBreak
forall a. a -> Normal a
normal :: WordBreak
$cnormal :: WordBreak
Normal)
breakAll, keepAll :: WordBreak
breakAll :: WordBreak
breakAll = Value -> WordBreak
WordBreak Value
"break-all"
keepAll :: WordBreak
keepAll = Value -> WordBreak
WordBreak Value
"keep-all"
wordBreak :: WordBreak -> Css
wordBreak :: WordBreak -> Css
wordBreak = Key WordBreak -> WordBreak -> Css
forall a. Val a => Key a -> a -> Css
key Key WordBreak
"word-break"
newtype OverflowWrap = OverflowWrap Value
deriving (OverflowWrap -> Value
(OverflowWrap -> Value) -> Val OverflowWrap
forall a. (a -> Value) -> Val a
value :: OverflowWrap -> Value
$cvalue :: OverflowWrap -> Value
Val, OverflowWrap
OverflowWrap -> Inherit OverflowWrap
forall a. a -> Inherit a
inherit :: OverflowWrap
$cinherit :: OverflowWrap
Inherit, OverflowWrap
OverflowWrap -> Initial OverflowWrap
forall a. a -> Initial a
initial :: OverflowWrap
$cinitial :: OverflowWrap
Initial, OverflowWrap
OverflowWrap -> Unset OverflowWrap
forall a. a -> Unset a
unset :: OverflowWrap
$cunset :: OverflowWrap
Unset, OverflowWrap
OverflowWrap -> Normal OverflowWrap
forall a. a -> Normal a
normal :: OverflowWrap
$cnormal :: OverflowWrap
Normal)
breakWord :: OverflowWrap
breakWord :: OverflowWrap
breakWord = Value -> OverflowWrap
OverflowWrap Value
"break-word"
overflowWrap, wordWrap :: OverflowWrap -> Css
wordWrap :: OverflowWrap -> Css
wordWrap = Key OverflowWrap -> OverflowWrap -> Css
forall a. Val a => Key a -> a -> Css
key Key OverflowWrap
"word-wrap"
overflowWrap :: OverflowWrap -> Css
overflowWrap = Key OverflowWrap -> OverflowWrap -> Css
forall a. Val a => Key a -> a -> Css
key Key OverflowWrap
"overflow-wrap"
newtype TextOverflow = TextOverflow Value
deriving (TextOverflow -> Value
(TextOverflow -> Value) -> Val TextOverflow
forall a. (a -> Value) -> Val a
value :: TextOverflow -> Value
$cvalue :: TextOverflow -> Value
Val, TextOverflow
TextOverflow -> None TextOverflow
forall a. a -> None a
none :: TextOverflow
$cnone :: TextOverflow
None, TextOverflow
TextOverflow -> Inherit TextOverflow
forall a. a -> Inherit a
inherit :: TextOverflow
$cinherit :: TextOverflow
Inherit, TextOverflow
TextOverflow -> Initial TextOverflow
forall a. a -> Initial a
initial :: TextOverflow
$cinitial :: TextOverflow
Initial)
overflowClip, overflowEllipsis :: TextOverflow
overflowClip :: TextOverflow
overflowClip = Value -> TextOverflow
TextOverflow Value
"clip"
overflowEllipsis :: TextOverflow
overflowEllipsis = Value -> TextOverflow
TextOverflow Value
"ellipsis"
textOverflow :: TextOverflow -> Css
textOverflow :: TextOverflow -> Css
textOverflow = Key TextOverflow -> TextOverflow -> Css
forall a. Val a => Key a -> a -> Css
key Key TextOverflow
"text-overflow"
newtype Content = Content Value
deriving (Content -> Value
(Content -> Value) -> Val Content
forall a. (a -> Value) -> Val a
value :: Content -> Value
$cvalue :: Content -> Value
Val, Content
Content -> None Content
forall a. a -> None a
none :: Content
$cnone :: Content
None, Content
Content -> Normal Content
forall a. a -> Normal a
normal :: Content
$cnormal :: Content
Normal, Content
Content -> Inherit Content
forall a. a -> Inherit a
inherit :: Content
$cinherit :: Content
Inherit, Content
Content -> Initial Content
forall a. a -> Initial a
initial :: Content
$cinitial :: Content
Initial)
attrContent :: Text -> Content
attrContent :: Text -> Content
attrContent Text
a = Value -> Content
Content (Value
"attr(" Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> Text -> Value
forall a. Val a => a -> Value
value Text
a Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> Value
")")
stringContent :: Text -> Content
stringContent :: Text -> Content
stringContent = Value -> Content
Content (Value -> Content) -> (Text -> Value) -> Text -> Content
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Literal -> Value
forall a. Val a => a -> Value
value (Literal -> Value) -> (Text -> Literal) -> Text -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Literal
Literal
uriContent :: Text -> Content
uriContent :: Text -> Content
uriContent Text
u = Value -> Content
Content (Value
"uri(" Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> Literal -> Value
forall a. Val a => a -> Value
value (Text -> Literal
Literal Text
u) Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> Value
")")
urlContent :: Text -> Content
urlContent :: Text -> Content
urlContent Text
u = Value -> Content
Content (Value
"url(" Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> Literal -> Value
forall a. Val a => a -> Value
value (Text -> Literal
Literal Text
u) Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> Value
")")
openQuote, closeQuote, noOpenQuote, noCloseQuote :: Content
openQuote :: Content
openQuote = Value -> Content
Content Value
"open-quote"
closeQuote :: Content
closeQuote = Value -> Content
Content Value
"close-quote"
noOpenQuote :: Content
noOpenQuote = Value -> Content
Content Value
"no-open-quote"
noCloseQuote :: Content
noCloseQuote = Value -> Content
Content Value
"no-close-quote"
content :: Content -> Css
content :: Content -> Css
content = Key Content -> Content -> Css
forall a. Val a => Key a -> a -> Css
key Key Content
"content"
contents :: [Content] -> Css
contents :: [Content] -> Css
contents [Content]
cs = Key Value -> Value -> Css
forall a. Val a => Key a -> a -> Css
key Key Value
"content" ([Content] -> Value
forall a. Val a => [a] -> Value
noCommas [Content]
cs)