Copyright | (c) 2015 Nikita Churaev |
---|---|
License | BSD3 |
Safe Haskell | None |
Language | Haskell2010 |
Basic usage example
module Main where import Dialog main = dialog $ do changeTitle "Hello, World!" name <- askLine "What's your name?" displayLine ("Your name is: " ++ name)
- data DialogT m a
- type DialogIO = DialogT IO
- dialog :: MonadIO m => DialogIO () -> m ()
- changeTitle :: String -> DialogT m ()
- changeEndMessage :: String -> DialogT m ()
- displayLine :: String -> DialogT m ()
- askLine :: String -> DialogT m String
- display :: [Paragraph] -> DialogT m ()
- p :: FormattedText -> Paragraph
- (<>) :: Monoid m => m -> m -> m
- str :: String -> FormattedText
- b :: FormattedText -> FormattedText
- i :: FormattedText -> FormattedText
- u :: FormattedText -> FormattedText
- color :: Color -> FormattedText -> FormattedText
- size :: FontSize -> FormattedText -> FormattedText
- url :: String -> FormattedText
- ol :: [ListItem] -> Paragraph
- ul :: [ListItem] -> Paragraph
- li :: FormattedText -> ListItem
- li' :: [Paragraph] -> ListItem
- img :: String -> Paragraph
- table :: [TableRow] -> Paragraph
- tr :: [TableCell] -> TableRow
- th :: FormattedText -> TableCell
- td :: FormattedText -> TableCell
- th' :: [Paragraph] -> TableCell
- td' :: [Paragraph] -> TableCell
- class Monad m => MonadIO m where
- data Paragraph
- data FormattedText
- data PictureSource = PictureFromURL String
- data ListStyle
- newtype ListItem = ListItem [Paragraph]
- newtype TableRow = TableRow [TableCell]
- data TableCell = TableCell CellStyle [Paragraph]
- data CellStyle
- data FontSize
- data Color
- white :: Color
- black :: Color
- red :: Color
- green :: Color
- blue :: Color
- rgb :: Word8 -> Word8 -> Word8 -> Color
- toRGB :: Color -> (Word8, Word8, Word8)
Running dialogs
Dialog monad transformer.
dialog :: MonadIO m => DialogIO () -> m () Source
Opens a dialog window and runs the given dialog in it.
Changing title and end message
changeTitle :: String -> DialogT m () Source
Changes the title of the dialog window. Default: "Dialog"
changeEndMessage :: String -> DialogT m () Source
Changes the end message of the dialog. Default: "End of program."
Simple messages
displayLine :: String -> DialogT m () Source
Displays a plain-text single-line message.
Asking for input
Formatted messages
p :: FormattedText -> Paragraph Source
Shorthand for TextParagraph
.
str :: String -> FormattedText Source
Converts a String
to a FormattedText
. Shorthand for Plain
.
b :: FormattedText -> FormattedText Source
Makes a text bold. Shorthand for Bold
.
i :: FormattedText -> FormattedText Source
Makes a text italic. Shorthand for Italic
.
u :: FormattedText -> FormattedText Source
Makes a text underlined. Shorthand for Underline
.
color :: Color -> FormattedText -> FormattedText Source
Changes the color of a text. Alias of Colored
.
size :: FontSize -> FormattedText -> FormattedText Source
Changes the size of a text. Alias of Size
.
li :: FormattedText -> ListItem Source
Makes a single-line list item. Shorthand for
(
.ListItem
[TextParagraph
text])
th :: FormattedText -> TableCell Source
Makes a table header cell with a single line of text in it. Shorthand for
(
.TableCell
HeaderCell
[TextParagraph
text])
td :: FormattedText -> TableCell Source
Makes a normal table cell with a single line of text in it. Shorthand for
(
.TableCell
NormalCell
[TextParagraph
text])
th' :: [Paragraph] -> TableCell Source
Makes a header table cell. Shorthand for
(
.TableCell
HeaderCell
paragraphs)
td' :: [Paragraph] -> TableCell Source
Makes a normal table cell. Shorthand for
(
.TableCell
NormalCell
paragraphs)
Using IO
Formatted text
data FormattedText Source
data PictureSource Source
Font size
Font size (in percent of the base font size).