--------------------------------------------------------------------------------
-- |
-- module:    Dialog.Shorthands
-- copyright: (c) 2015 Nikita Churaev
-- license:   BSD3
--------------------------------------------------------------------------------

{-# OPTIONS_HADDOCK not-home #-}

--------------------------------------------------------------------------------

module Dialog.Shorthands where

--------------------------------------------------------------------------------

import Dialog.Internal

--------------------------------------------------------------------------------

-- | Shorthand for 'TextParagraph'.
p :: FormattedText -> Paragraph
p = TextParagraph

-- | Makes an unlabeled link. Shorthand for @('Link' url ('Plain' url))@.
url :: String -> FormattedText
url linkURL = Link linkURL (Plain linkURL)

-- | Makes a labeled link. Alias for 'Link'.
link :: String -> FormattedText -> FormattedText
link = Link

-- | Shorthand for @('Picture' ('PictureFromURL' url))@.
img :: String -> Paragraph
img imgURL = Picture (PictureFromURL imgURL)

-- | Makes a numbered list. Shorthand for @('List' 'NumberedList' items)@.
ol :: [ListItem] -> Paragraph
ol = List NumberedList

-- | Makes a bullet list. Shorthand for @('List' 'BulletList' items)@.
ul :: [ListItem] -> Paragraph
ul = List BulletList

-- | Makes a single-line list item. Shorthand for 
-- @('ListItem' ['TextParagraph' text])@.
li :: FormattedText -> ListItem
li text = ListItem [TextParagraph text]

-- | Makes a list item. Shorthand for 'ListItem'.
li' :: [Paragraph] -> ListItem
li' = ListItem

-- | Converts a 'String' to a 'FormattedText'. Shorthand for 'Plain'.
str :: String -> FormattedText
str = Plain

-- | Makes a text bold. Shorthand for 'Bold'.
b :: FormattedText -> FormattedText
b = Bold

-- | Makes a text italic. Shorthand for 'Italic'.
i :: FormattedText -> FormattedText
i = Italic

-- | Makes a text underlined. Shorthand for 'Underline'.
u :: FormattedText -> FormattedText
u = Underline

-- | Changes the color of a text. Alias of 'Colored'.
color :: Color -> FormattedText -> FormattedText
color = Colored

-- | Changes the size of a text. Alias of 'Size'.
size :: FontSize -> FormattedText -> FormattedText
size = Size

-- | Makes a table. Alias for 'Table'.
table :: [TableRow] -> Paragraph
table = Table

-- | Makes a table row. Shorthand for 'TableRow'.
tr :: [TableCell] -> TableRow
tr = TableRow

-- | Makes a normal table cell with a single line of text in it. Shorthand for
-- @('TableCell' 'NormalCell' ['TextParagraph' text])@.
td :: FormattedText -> TableCell
td text = TableCell NormalCell [TextParagraph text]

-- | Makes a table header cell with a single line of text in it. Shorthand for
-- @('TableCell' 'HeaderCell' ['TextParagraph' text])@.
th :: FormattedText -> TableCell
th text = TableCell HeaderCell [TextParagraph text]

-- | Makes a normal table cell. Shorthand for
-- @('TableCell' 'NormalCell' paragraphs)@.
td' :: [Paragraph] -> TableCell
td' = TableCell NormalCell

-- | Makes a header table cell. Shorthand for
-- @('TableCell' 'HeaderCell' paragraphs)@.
th' :: [Paragraph] -> TableCell
th' = TableCell HeaderCell

--------------------------------------------------------------------------------