dialog-0.3.0.0: Simple dialog-based user interfaces

Copyright(c) 2015 Nikita Churaev
LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Dialog

Contents

Description

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)

Synopsis

Running dialogs

data DialogT m a Source

Dialog monad transformer.

type DialogIO = DialogT IO Source

Dialog with IO as the base monad.

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

askLine :: String -> DialogT m String Source

Asks the user for a line of text.

Formatted messages

display :: [Paragraph] -> DialogT m () Source

Displays a message.

(<>) :: Monoid m => m -> m -> m infixr 6

An infix synonym for mappend.

Since: 4.5.0.0

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.

url :: String -> FormattedText Source

Makes an unlabeled link. Shorthand for (Link url (Plain url)).

ol :: [ListItem] -> Paragraph Source

Makes a numbered list. Shorthand for (List NumberedList items).

ul :: [ListItem] -> Paragraph Source

Makes a bullet list. Shorthand for (List BulletList items).

li :: FormattedText -> ListItem Source

Makes a single-line list item. Shorthand for (ListItem [TextParagraph text]).

li' :: [Paragraph] -> ListItem Source

Makes a list item. Shorthand for ListItem.

img :: String -> Paragraph Source

Shorthand for (Picture (PictureFromURL url)).

table :: [TableRow] -> Paragraph Source

Makes a table. Alias for Table.

tr :: [TableCell] -> TableRow Source

Makes a table row. Shorthand for TableRow.

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

class Monad m => MonadIO m where

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Methods

liftIO :: IO a -> m a

Lift a computation from the IO monad.

Instances

MonadIO IO 
MonadIO m => MonadIO (DialogT m) 
MonadIO m => MonadIO (ReaderT r m) 
(Error e, MonadIO m) => MonadIO (ErrorT e m) 

Formatted text

Font size

data FontSize Source

Font size (in percent of the base font size).

Colors

white :: Color Source

Pure white (red: 255, green: 255, blue: 255).

black :: Color Source

Pure black (red: 0, green: 0, blue: 0).

red :: Color Source

Pure red (red: 255, green: 0, blue: 0).

green :: Color Source

Pure green (red: 0, green: 255, blue: 0).

blue :: Color Source

Pure blue (red: 0, green: 0, blue: 255).

rgb :: Word8 -> Word8 -> Word8 -> Color Source

Makes a color from red, green and blue components.

toRGB :: Color -> (Word8, Word8, Word8) Source

Unpacks a color into red, green and blue components.