| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Zenity
Contents
Description
A wrapper for Zenity dialog boxes
Zenity is accessed through system calls, so it needs to be installed on the computer in order for this wrapper to work.
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.
Synopsis
- data Text
- data Day
- class Default a where
- def :: a
- data Config = Config {}
- data CalendarFlags = CalendarFlags {}
- data EntryFlags = EntryFlags {}
- data FileSelectionFlags = FileSelectionFlags {}
- data InfoFlags = InfoFlags {}
- data ReturnedColumn a
- data ListFlags = ListFlags {
- text :: Maybe Text
- editable :: Bool
- returnColumn :: ReturnedColumn 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
- Notification :: InfoFlags -> Dialog ()
- Warning :: InfoFlags -> Dialog ()
- 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 space efficient, packed, unboxed Unicode text type.
The Modified Julian Day is a standard count of days, with zero being the day 1858-11-17.
Instances
| Enum Day | |
| Eq Day | |
| Data Day | |
Defined in Data.Time.Calendar.Days Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Day -> c Day # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Day # dataTypeOf :: Day -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Day) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Day) # gmapT :: (forall b. Data b => b -> b) -> Day -> Day # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Day -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Day -> r # gmapQ :: (forall d. Data d => d -> u) -> Day -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Day -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Day -> m Day # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Day -> m Day # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Day -> m Day # | |
| Ord Day | |
| Ix Day | |
| NFData Day | |
Defined in Data.Time.Calendar.Days | |
A class for types with a default value.
Minimal complete definition
Nothing
Instances
Zenity dialogs
General Zenity configuration
Use def for default configuration.
Constructors
| Config | |
Fields
| |
data CalendarFlags Source #
Constructors
| CalendarFlags | |
Instances
| Eq CalendarFlags Source # | |
Defined in Zenity Methods (==) :: CalendarFlags -> CalendarFlags -> Bool # (/=) :: CalendarFlags -> CalendarFlags -> Bool # | |
| Show CalendarFlags Source # | |
Defined in Zenity Methods showsPrec :: Int -> CalendarFlags -> ShowS # show :: CalendarFlags -> String # showList :: [CalendarFlags] -> ShowS # | |
| Default CalendarFlags Source # | |
Defined in Zenity Methods def :: CalendarFlags # | |
data EntryFlags Source #
Constructors
| EntryFlags | |
Instances
| Eq EntryFlags Source # | |
Defined in Zenity | |
| Show EntryFlags Source # | |
Defined in Zenity Methods showsPrec :: Int -> EntryFlags -> ShowS # show :: EntryFlags -> String # showList :: [EntryFlags] -> ShowS # | |
| Default EntryFlags Source # | |
Defined in Zenity Methods def :: EntryFlags # | |
data FileSelectionFlags Source #
Flags for the FileSelection dialog
Use def for default flags.
Constructors
| FileSelectionFlags | |
Instances
| Eq FileSelectionFlags Source # | |
Defined in Zenity Methods (==) :: FileSelectionFlags -> FileSelectionFlags -> Bool # (/=) :: FileSelectionFlags -> FileSelectionFlags -> Bool # | |
| Show FileSelectionFlags Source # | |
Defined in Zenity Methods showsPrec :: Int -> FileSelectionFlags -> ShowS # show :: FileSelectionFlags -> String # showList :: [FileSelectionFlags] -> ShowS # | |
| Default FileSelectionFlags Source # | |
Defined in Zenity Methods | |
Flags for the Error, Info, Notification and Warning dialogs
Note: $sel:noWrap:InfoFlags and $sel:noMarkup:InfoFlags have no effect on Notification dialogs.
Use def for default flags.
Constructors
| InfoFlags | |
data ReturnedColumn a Source #
What column(s) 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 ReturnedColumn Source # | |
Defined in Zenity Methods fmap :: (a -> b) -> ReturnedColumn a -> ReturnedColumn b # (<$) :: a -> ReturnedColumn b -> ReturnedColumn a # | |
| Eq a => Eq (ReturnedColumn a) Source # | |
Defined in Zenity Methods (==) :: ReturnedColumn a -> ReturnedColumn a -> Bool # (/=) :: ReturnedColumn a -> ReturnedColumn a -> Bool # | |
| Show a => Show (ReturnedColumn a) Source # | |
Defined in Zenity Methods showsPrec :: Int -> ReturnedColumn a -> ShowS # show :: ReturnedColumn a -> String # showList :: [ReturnedColumn a] -> ShowS # | |
Constructors
| ListFlags | |
Fields
| |
newtype SelectionHeader Source #
Header for the selection column in a radio or check list (can be empty)
Constructors
| SelectionHeader | |
Fields | |
Instances
| Eq SelectionHeader Source # | |
Defined in Zenity Methods (==) :: SelectionHeader -> SelectionHeader -> Bool # (/=) :: SelectionHeader -> SelectionHeader -> Bool # | |
| Show SelectionHeader Source # | |
Defined in Zenity Methods showsPrec :: Int -> SelectionHeader -> ShowS # show :: SelectionHeader -> String # showList :: [SelectionHeader] -> ShowS # | |
| IsString SelectionHeader Source # | |
Defined in Zenity Methods fromString :: String -> SelectionHeader # | |
data ListType a where Source #
List dialog type
Constructors
| Single :: ListType (Maybe Text) | |
| Multi :: ListType [Text] | |
| Radio :: SelectionHeader -> ListType (Maybe Text) | |
| Check :: SelectionHeader -> ListType [Text] |
Instances
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 | |
| Notification :: InfoFlags -> Dialog () | |
| Warning :: InfoFlags -> Dialog () |
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.