| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Zenity
Contents
Description
A wrapper for Zenity dialog boxes
It is advised to turn on the following extensions when using this module:
DuplicateRecordFields OverloadedStrings
Here is a simple example for how to use the library. It asks the user for a name and displays a greeting:
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
import Data.Monoid
import Zenity
greeting = do
Just name <-
zenity def {title = Just "Name entry"} $
Entry $ def {text = Just "What's your name?"}
zenity def $ Info def {text = Just $ "Greetings, " <> name <> "!"}
More examples can be found in the examples/ directory.
- data Text :: *
- class Default a where
- data Config = Config {}
- data CalendarFlags = CalendarFlags {}
- data EntryFlags = EntryFlags {}
- data FileSelectionFlags = FileSelectionFlags {}
- data InfoFlags = InfoFlags {}
- data ReturnedColumns a
- data ListFlags = ListFlags {
- text :: Maybe Text
- editable :: Bool
- returnColumn :: ReturnedColumns Word
- hideColumn :: Maybe Word
- hideHeader :: Bool
- newtype SelectionHeader = SelectionHeader {}
- data ListType a where
- radio :: ListType (Maybe Text)
- check :: ListType [Text]
- data Matrix = Matrix {}
- data Dialog a where
- Calendar :: CalendarFlags -> Dialog (Maybe Day)
- Entry :: EntryFlags -> Dialog (Maybe Text)
- Error :: InfoFlags -> Dialog ()
- FileSelection :: FileSelectionFlags -> Dialog (Maybe FilePath)
- MultiFileSelection :: FileSelectionFlags -> Dialog [FilePath]
- Info :: InfoFlags -> Dialog ()
- List :: ListType a -> ListFlags -> Matrix -> Dialog a
- zenity :: Config -> Dialog a -> IO a
- keyedList :: (Show a, Read a, Functor f) => Config -> ListType (f Text) -> ListFlags -> Text -> [(a, Text)] -> IO (f a)
Documentation
A class for types with a default value.
Instances
Zenity dialogs
data FileSelectionFlags Source #
Flags for the FileSelection dialog
Use def for default flags.
Constructors
| FileSelectionFlags | |
Constructors
| InfoFlags | |
data ReturnedColumns a Source #
What columns to return in a List dialog
The default value is .Col 1
When All is specified, the columns will be separated by newline characters
(\n) in the result.
Instances
| Functor ReturnedColumns Source # | |
| Eq a => Eq (ReturnedColumns a) Source # | |
| Show a => Show (ReturnedColumns a) Source # | |
Constructors
| ListFlags | |
Fields
| |
newtype SelectionHeader Source #
Header for the selection column in a radio or check list (can be empty)
Constructors
| SelectionHeader | |
Fields | |
Instances
data ListType a where Source #
List dialog type
The contents of a list dialog
When used in a dialog, the matrix will be transformed in the following ways:
- Make sure that the matrix is rectangular and has at least one column and one row. Any headers or elements that are added will be empty strings.
- Any newline characters will be turned into space characters. (This is because newline characters are used internally as separators when returning multiple rows and/or columns.)
Zenity commands
Things to be aware of:
- In the very unlikely case of a file name containing newline characters,
MultiFileSelectionwill give an incorrect result. This is because it uses\nto separate the files returned from Zenity.
Constructors
| Calendar :: CalendarFlags -> Dialog (Maybe Day) | |
| Entry :: EntryFlags -> Dialog (Maybe Text) | |
| Error :: InfoFlags -> Dialog () | |
| FileSelection :: FileSelectionFlags -> Dialog (Maybe FilePath) | |
| MultiFileSelection :: FileSelectionFlags -> Dialog [FilePath] | |
| Info :: InfoFlags -> Dialog () | |
| List :: ListType a -> ListFlags -> Matrix -> Dialog a |
Extra dialogs
Arguments
| :: (Show a, Read a, Functor f) | |
| => Config | |
| -> ListType (f Text) | |
| -> ListFlags |
|
| -> Text | Column head (can be empty) |
| -> [(a, Text)] | List to select from |
| -> IO (f a) |
Make a list selection dialog that selects values from an association list
Each item is a pair of a value of type a and a text. Only the text will be
shown in the dialog, but the value associated with the selected text will be
returned.