-- |
-- Module:     Data.CSS.Properties.Text
-- Copyright:  (c) 2013 Ertugrul Soeylemez
-- License:    BSD3
-- Maintainer: Ertugrul Soeylemez <es@ertes.de>

module Data.CSS.Properties.Text
    ( -- * Alignment and spacing
      letterSpacing,
      textAlign,
      textIndent,
      whiteSpace,
      wordSpacing,

      -- * Direction
      direction,
      unicodeBidi,

      -- * Generated content
      content,
      contentUrl,
      counterIncrement,
      counterReset,
      quotes,

      -- * List formatting
      listStyle,
      listStyleImage,
      listStyleImageUrl,
      listStylePosition,
      listStyleType,
      listStyleUrl,

      -- * Paged media
      orphans,
      widows,

      -- * Transformation
      textTransform
    )
    where

import Blaze.ByteString.Builder
import Blaze.ByteString.Builder.Char8
import Data.ByteString (ByteString)
import Data.CSS.Build
import Data.CSS.Properties.Types
import Data.CSS.Properties.Utils
import Data.CSS.Types
import Data.CSS.Utils
import Data.Monoid
import Data.Text (Text)
import Web.Routes.RouteT


-- | Set the generated @content@ to the given list of parts or @normal@.

content :: Maybe [ContentPart (CssUrl Text)] -> SetProp
content = setProp "content" . maybeProp "normal"


-- | Set the generated @content@ to the given list of parts or @normal@.

contentUrl :: (MonadRoute m) => Maybe [ContentPart (URL m)] -> SetPropM m
contentUrl parts = do
    renderUrl <- askRouteFn
    content . fmap (map (fmap $ CssUrl . flip renderUrl [])) $ parts


-- | Increment the given counters by the given value
-- (@counter-increment@).

counterIncrement :: (Integral a) => [(ByteString, a)] -> SetProp
counterIncrement [] = setProp "counter-increment" (PropValue "none")
counterIncrement cs = setProp "counter-increment" (map (formatCounter 1) cs)


-- | Reset the given counters to the given value (@counter-reset@).

counterReset :: (Integral a) => [(ByteString, a)] -> SetProp
counterReset [] = setProp "counter-reset" (PropValue "none")
counterReset cs = setProp "counter-reset" (map (formatCounter 0) cs)


-- | Set the text @direction@.

direction :: TextDirection -> SetProp
direction = setProp "direction"


-- | Format the given identifier/counter pair for 'counterIncrement' and
-- 'counterReset' with the given default value.

formatCounter :: (Integral a) => a -> (ByteString, a) -> ByteString
formatCounter def (ctr, n)
    | n == def   = ctr
    | otherwise =
        toByteString $
            fromByteString ctr <>
            fromChar ' ' <>
            showReal n


-- | Set the @letter-spacing@ to the specified value or @normal@.

letterSpacing :: (Real a) => Maybe (Length a) -> SetProp
letterSpacing = setProp "letter-spacing" . maybeProp "normal"


-- | Set all @list-style@ properties.

listStyle :: ListStyle -> ListPosition -> Maybe (CssUrl Text) -> SetProp
listStyle style pos url = setProp "list-style" (style, pos, maybeProp "none" url)


-- | Set the @list-style-image@.

listStyleImage :: Maybe (CssUrl Text) -> SetProp
listStyleImage = setProp "list-style-image" . maybeProp "none"


-- | Set the @list-style-image@.

listStyleImageUrl :: (MonadRoute m) => Maybe (URL m) -> SetPropM m
listStyleImageUrl url = do
    renderUrl <- askRouteFn
    listStyleImage . fmap (CssUrl . flip renderUrl []) $ url


-- | Set the @list-style-position@.

listStylePosition :: ListPosition -> SetProp
listStylePosition = setProp "list-style-position"


-- | Set the @list-style-type@.

listStyleType :: ListStyle -> SetProp
listStyleType = setProp "list-style-type"


-- | Set all @list-style@ properties.

listStyleUrl ::
    (MonadRoute m)
    => ListStyle
    -> ListPosition
    -> Maybe (URL m)
    -> SetPropM m
listStyleUrl style pos url = do
    renderUrl <- askRouteFn
    listStyle style pos (fmap (CssUrl . flip renderUrl []) url)


-- | Set the @orphans@ threshold (minimum number of lines at the bottom
-- of a page).

orphans :: (Integral a) => a -> SetProp
orphans = setProp "orphans" . toInteger


-- | Set the @quotes@ pairs (@none@ if empty).

quotes :: [(CssString Text, CssString Text)] -> SetProp
quotes [] = setProp "quotes" (PropValue "none")
quotes qs = setProp "quotes" qs


-- | Set @text-align@.

textAlign :: TextAlign -> SetProp
textAlign = setProp "text-align"


-- | Set the @text-indent@.

textIndent :: (Real a) => FactorLen Length a -> SetProp
textIndent = setProp "text-indent"


-- | Set the @text-transform@.

textTransform :: Maybe TextTransform -> SetProp
textTransform = setProp "text-transform" . maybeProp "none"


-- | Set the @unicode-bidi@ mode.

unicodeBidi :: UnicodeBidiMode -> SetProp
unicodeBidi = setProp "unicode-bidi"


-- | Set the white space collapse and text wrapping modes
-- (@white-space@).

whiteSpace :: TextWrapMode -> SetProp
whiteSpace = setProp "white-space"


-- | Set the @widows@ threshold (minimum number of lines at the top of a
-- page).

widows :: (Integral a) => a -> SetProp
widows = setProp "widows" . toInteger


-- | Set the @word-spacing@ to the specified value or @normal@.

wordSpacing :: (Real a) => Maybe (Length a) -> SetProp
wordSpacing = setProp "word-spacing" . maybeProp "normal"