hzenity-0.2: Haskell interface to Zenity dialogs

Safe HaskellNone
LanguageHaskell2010

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.

Synopsis

Documentation

data Text :: * #

A space efficient, packed, unboxed Unicode text type.

Instances

type Item Text 
type Item Text = Char

class Default a where #

A class for types with a default value.

Methods

def :: a #

The default value for this type.

Instances

Default Double 

Methods

def :: Double #

Default Float 

Methods

def :: Float #

Default Int 

Methods

def :: Int #

Default Int8 

Methods

def :: Int8 #

Default Int16 

Methods

def :: Int16 #

Default Int32 

Methods

def :: Int32 #

Default Int64 

Methods

def :: Int64 #

Default Integer 

Methods

def :: Integer #

Default Ordering 

Methods

def :: Ordering #

Default Word 

Methods

def :: Word #

Default Word8 

Methods

def :: Word8 #

Default Word16 

Methods

def :: Word16 #

Default Word32 

Methods

def :: Word32 #

Default Word64 

Methods

def :: Word64 #

Default () 

Methods

def :: () #

Default All 

Methods

def :: All #

Default Any 

Methods

def :: Any #

Default CShort 

Methods

def :: CShort #

Default CUShort 

Methods

def :: CUShort #

Default CInt 

Methods

def :: CInt #

Default CUInt 

Methods

def :: CUInt #

Default CLong 

Methods

def :: CLong #

Default CULong 

Methods

def :: CULong #

Default CLLong 

Methods

def :: CLLong #

Default CULLong 

Methods

def :: CULLong #

Default CFloat 

Methods

def :: CFloat #

Default CDouble 

Methods

def :: CDouble #

Default CPtrdiff 

Methods

def :: CPtrdiff #

Default CSize 

Methods

def :: CSize #

Default CSigAtomic 

Methods

def :: CSigAtomic #

Default CClock 

Methods

def :: CClock #

Default CTime 

Methods

def :: CTime #

Default CUSeconds 

Methods

def :: CUSeconds #

Default CSUSeconds 

Methods

def :: CSUSeconds #

Default CIntPtr 

Methods

def :: CIntPtr #

Default CUIntPtr 

Methods

def :: CUIntPtr #

Default CIntMax 

Methods

def :: CIntMax #

Default CUIntMax 

Methods

def :: CUIntMax #

Default ListFlags # 

Methods

def :: ListFlags #

Default InfoFlags # 

Methods

def :: InfoFlags #

Default FileSelectionFlags # 
Default EntryFlags # 

Methods

def :: EntryFlags #

Default CalendarFlags # 

Methods

def :: CalendarFlags #

Default Config # 

Methods

def :: Config #

Default [a] 

Methods

def :: [a] #

Default (Maybe a) 

Methods

def :: Maybe a #

Integral a => Default (Ratio a) 

Methods

def :: Ratio a #

Default a => Default (IO a) 

Methods

def :: IO a #

(Default a, RealFloat a) => Default (Complex a) 

Methods

def :: Complex a #

Default a => Default (Dual a) 

Methods

def :: Dual a #

Default (Endo a) 

Methods

def :: Endo a #

Num a => Default (Sum a) 

Methods

def :: Sum a #

Num a => Default (Product a) 

Methods

def :: Product a #

Default (First a) 

Methods

def :: First a #

Default (Last a) 

Methods

def :: Last a #

Default r => Default (e -> r) 

Methods

def :: e -> r #

(Default a, Default b) => Default (a, b) 

Methods

def :: (a, b) #

(Default a, Default b, Default c) => Default (a, b, c) 

Methods

def :: (a, b, c) #

(Default a, Default b, Default c, Default d) => Default (a, b, c, d) 

Methods

def :: (a, b, c, d) #

(Default a, Default b, Default c, Default d, Default e) => Default (a, b, c, d, e) 

Methods

def :: (a, b, c, d, e) #

(Default a, Default b, Default c, Default d, Default e, Default f) => Default (a, b, c, d, e, f) 

Methods

def :: (a, b, c, d, e, f) #

(Default a, Default b, Default c, Default d, Default e, Default f, Default g) => Default (a, b, c, d, e, f, g) 

Methods

def :: (a, b, c, d, e, f, g) #

Zenity dialogs

data Config Source #

General Zenity configuration

Use def for default configuration.

Constructors

Config 

Fields

Instances

data CalendarFlags Source #

Flags for the Calendar dialog

Use def for default flags.

Constructors

CalendarFlags 

Fields

data EntryFlags Source #

Flags for the Entry dialog

Use def for default flags.

Constructors

EntryFlags 

Fields

data FileSelectionFlags Source #

Flags for the FileSelection dialog

Use def for default flags.

Constructors

FileSelectionFlags 

Fields

data InfoFlags Source #

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 

Fields

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.

Constructors

All

Return all columns

Col a

Return the specified column (starting from 1)

data ListFlags Source #

Flags for the List dialog

Use def for default flags.

Constructors

ListFlags 

Fields

data ListType a where Source #

List dialog type

Instances

Eq (ListType a) Source # 

Methods

(==) :: ListType a -> ListType a -> Bool #

(/=) :: ListType a -> ListType a -> Bool #

Show (ListType a) Source # 

Methods

showsPrec :: Int -> ListType a -> ShowS #

show :: ListType a -> String #

showList :: [ListType a] -> ShowS #

radio :: ListType (Maybe Text) Source #

A radio list type with no selection header

check :: ListType [Text] Source #

A check list type with no selection header

data Matrix Source #

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.)

Constructors

Matrix 

Fields

Instances

data Dialog a where Source #

Zenity commands

Things to be aware of:

  • In the very unlikely case of a file name containing newline characters, MultiFileSelection will give an incorrect result. This is because it uses \n to separate the files returned from Zenity.

zenity :: Config -> Dialog a -> IO a Source #

Run a Dialog action

Extra dialogs

keyedList Source #

Arguments

:: (Show a, Read a, Functor f) 
=> Config 
-> ListType (f Text) 
-> ListFlags

returnColumn and hideColumn will be ignored

-> 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.