fudgets-0.18.3.2: The Fudgets Library
Safe HaskellNone
LanguageHaskell98

AllFudgets

Description

This module exposes everything, but there is very little documentation here. See the Fudget Library Reference Manual instead.

Synopsis

Combinators

branchF :: F (Path, a) b -> F (Path, a) b -> F (Path, a) b Source #

branchFSP :: FSP (Path, a) b -> FSP (Path, a) b -> FSP (Path, a) b Source #

compF :: F a b -> F c d -> F (Either a c) (Either b d) Source #

parF :: F c ho -> F c ho -> F c ho Source #

postProcessHigh :: SP a ho -> F hi a -> F hi ho Source #

postProcessLow :: SP TCommand TCommand -> F hi ho -> F hi ho Source #

preProcessHigh :: F c ho -> SP hi c -> F hi ho Source #

preProcessLow :: F hi ho -> SP TEvent TEvent -> F hi ho Source #

preMapHigh :: F c ho -> (hi -> c) -> F hi ho Source #

postMapHigh :: (a -> ho) -> F hi a -> F hi ho Source #

preMapLow :: F hi ho -> (TEvent -> TEvent) -> F hi ho Source #

postMapLow :: (TCommand -> TCommand) -> F hi ho -> F hi ho Source #

postProcessHighK :: SP a ho -> K hi a -> K hi ho Source #

postProcessLowK :: SP FRequest FRequest -> K hi ho -> K hi ho Source #

preProcessHighK :: K c ho -> SP hi c -> K hi ho Source #

preMapHighK :: K c ho -> (hi -> c) -> K hi ho Source #

postMapHighK :: (a -> ho) -> K hi a -> K hi ho Source #

preMapLowK :: K hi ho -> (FResponse -> FResponse) -> K hi ho Source #

postMapLowK :: (FRequest -> FRequest) -> K hi ho -> K hi ho Source #

postProcessHigh' :: SP a b -> Fa c d e a -> Fa c d e b Source #

postProcessLow' :: SP a b -> Fa c a d e -> Fa c b d e Source #

preProcessHigh' :: Fa a b c d -> SP e c -> Fa a b e d Source #

preProcessLow' :: Fa a b c d -> SP e a -> Fa e b c d Source #

preMapHigh' :: Fa a b c d -> (e -> c) -> Fa a b e d Source #

preMapLow' :: Fa a b c d -> (e -> a) -> Fa e b c d Source #

postMapHigh' :: (a -> b) -> Fa c d e a -> Fa c d e b Source #

postMapLow' :: (a -> b) -> Fa c a d e -> Fa c b d e Source #

prepostMapHigh' :: (a -> b) -> (c -> d) -> Fa e f b c -> Fa e f a d Source #

prepostMapHigh :: (hi -> b) -> (c -> ho) -> F b c -> F hi ho Source #

prepostMapHighK :: (hi -> b) -> (c -> ho) -> K b c -> K hi ho Source #

prepostMapLow' :: (a -> b) -> (c -> d) -> Fa b c e f -> Fa a d e f Source #

prepostMapLow :: (TEvent -> TEvent) -> (TCommand -> TCommand) -> F hi ho -> F hi ho Source #

prepostMapLowK :: (FResponse -> FResponse) -> (FRequest -> FRequest) -> K hi ho -> K hi ho Source #

dynF :: F a b -> F (Either (F a b) a) b Source #

type DynFMsg a b = DynMsg a (F a b) Source #

dynListF :: F (Int, DynFMsg a b) (Int, b) Source #

listF :: Eq a => [(a, F b c)] -> F (a, b) (a, c) Source #

untaggedListF :: [F a b] -> F a b Source #

loopLow :: SP TCommand (FCommand a) -> SP (FEvent a) TEvent -> F b c -> F b c Source #

loopThroughLowSP :: SP (Either c e) (Either c e) -> SP (Message e a) (Message c b) -> SP (Message e a) (Message c b) Source #

loopF :: F a a -> F a a Source #

loopThroughRightF :: F (Either a b) (Either c d) -> F c a -> F b d Source #

loopCompThroughRightF :: F (Either (Either a b) c) (Either (Either c d) a) -> F b d Source #

loopCompThroughLeftF :: F (Either a (Either b c)) (Either b (Either a d)) -> F c d Source #

loopRightF :: F (Either a b) (Either c b) -> F a c Source #

loopLeftF :: F (Either a b) (Either a c) -> F b c Source #

loopOnlyF :: F a a -> F a b Source #

loopCompF :: F (Either (Either r2l inl) (Either l2r inr)) (Either (Either l2r outl) (Either r2l outr)) -> F (Either inl inr) (Either outl outr) Source #

loopCompSP :: SP (Either (Either a1 b1) (Either a2 b2)) (Either (Either a2 a3) (Either a1 b3)) -> SP (Either b1 b2) (Either a3 b3) Source #

loopThroughBothF :: F (Either r2l inl) (Either l2r outl) -> F (Either l2r inr) (Either r2l outr) -> F (Either inl inr) (Either outl outr) Source #

loopThroughBothSP :: SP (Either a1 b1) (Either a2 a3) -> SP (Either a2 b2) (Either a1 b3) -> SP (Either b1 b2) (Either a3 b3) Source #

nullK :: K hi ho Source #

nullF :: F hi ho Source #

putK :: KCommand ho -> K hi ho -> K hi ho Source #

putF :: ho -> F hi ho -> F hi ho Source #

putsF :: [b] -> F a b -> F a b Source #

putsK :: [KCommand b] -> K a b -> K a b Source #

putMessageF :: FCommand ho -> F hi ho -> F hi ho Source #

putMessageFu :: Message FRequest ho -> F hi ho -> F hi ho Source #

putMessagesF :: [FCommand ho] -> F hi ho -> F hi ho Source #

putMessagesFu :: [KCommand b] -> F a b -> F a b Source #

appendStartK :: [KCommand ho] -> K hi ho -> K hi ho Source #

appendStartMessageF :: [FCommand ho] -> F hi ho -> F hi ho Source #

appendStartF :: [ho] -> F hi ho -> F hi ho Source #

getK :: Cont (K hi ho) (KEvent hi) Source #

getMessageF :: Cont (F hi ho) (FEvent hi) Source #

getF :: Cont (F a ho) a Source #

startupK :: [KEvent hi] -> K hi ho -> K hi ho Source #

startupMessageF :: [FEvent hi] -> F hi ho -> F hi ho Source #

startupF :: [hi] -> F hi ho -> F hi ho Source #

delayF :: F hi ho -> F hi ho Source #

type Cont c a = (a -> c) -> c Source #

data K hi ho Source #

Instances

Instances details
StreamProcIO K Source # 
Instance details

Defined in NullF

Methods

put :: o -> K i o -> K i o Source #

get :: (i -> K i o) -> K i o Source #

end :: K i o Source #

FudgetIO K Source # 
Instance details

Defined in NullF

Methods

waitForMsg :: (KEvent hi -> Maybe ans) -> Cont (K hi ho) ans Source #

putMsg :: KCommand ho -> K hi ho -> K hi ho Source #

data F hi ho Source #

Instances

Instances details
StreamProcIO F Source # 
Instance details

Defined in NullF

Methods

put :: o -> F i o -> F i o Source #

get :: (i -> F i o) -> F i o Source #

end :: F i o Source #

FudgetIO F Source # 
Instance details

Defined in NullF

Methods

waitForMsg :: (KEvent hi -> Maybe ans) -> Cont (F hi ho) ans Source #

putMsg :: KCommand ho -> F hi ho -> F hi ho Source #

class StreamProcIO sp where Source #

Methods

put :: o -> sp i o -> sp i o Source #

get :: (i -> sp i o) -> sp i o Source #

end :: sp i o Source #

Instances

Instances details
StreamProcIO SP Source # 
Instance details

Defined in StreamProcIO

Methods

put :: o -> SP i o -> SP i o Source #

get :: (i -> SP i o) -> SP i o Source #

end :: SP i o Source #

StreamProcIO K Source # 
Instance details

Defined in NullF

Methods

put :: o -> K i o -> K i o Source #

get :: (i -> K i o) -> K i o Source #

end :: K i o Source #

StreamProcIO F Source # 
Instance details

Defined in NullF

Methods

put :: o -> F i o -> F i o Source #

get :: (i -> F i o) -> F i o Source #

end :: F i o Source #

class FudgetIO f where Source #

Methods

waitForMsg :: (KEvent hi -> Maybe ans) -> Cont (f hi ho) ans Source #

putMsg :: KCommand ho -> f hi ho -> f hi ho Source #

Instances

Instances details
FudgetIO K Source # 
Instance details

Defined in NullF

Methods

waitForMsg :: (KEvent hi -> Maybe ans) -> Cont (K hi ho) ans Source #

putMsg :: KCommand ho -> K hi ho -> K hi ho Source #

FudgetIO F Source # 
Instance details

Defined in NullF

Methods

waitForMsg :: (KEvent hi -> Maybe ans) -> Cont (F hi ho) ans Source #

putMsg :: KCommand ho -> F hi ho -> F hi ho Source #

prodF :: F a b -> F c d -> F (a, c) (Either b d) Source #

compTurnRight :: (Path, b1) -> Message (Path, b1) b2 Source #

compTurnLeft :: (Path, b1) -> Message (Path, b1) b2 Source #

compPath :: (Path, b1) -> p -> (Either (Message (Path, b1) b2) (Message (Path, b1) b3) -> p) -> p Source #

stubF :: F a b -> F c d Source #

bypassF :: F a a -> F a a Source #

throughF :: F c b -> F c (Either b c) Source #

toBothF :: F b (Either b b) Source #

idF :: F b b Source #

concatMapF :: (a -> [b]) -> F a b Source #

mapF :: (a -> b) -> F a b Source #

mapstateF :: (t -> a -> (t, [b])) -> t -> F a b Source #

absF :: SP a b -> F a b Source #

idLeftF :: F c d -> F (Either b c) (Either b d) Source #

idRightF :: F a b -> F (Either a c) (Either b c) Source #

serCompLeftToRightF :: F (Either a b) (Either b c) -> F a c Source #

serCompRightToLeftF :: F (Either a b) (Either c a) -> F b c Source #

serCompF :: F a1 b -> F a2 a1 -> F a2 b Source #

newtype Mk k r Source #

The continuation monad

Constructors

Mk 

Fields

Instances

Instances details
Monad (Mk k) Source # 
Instance details

Defined in StateMonads

Methods

(>>=) :: Mk k a -> (a -> Mk k b) -> Mk k b #

(>>) :: Mk k a -> Mk k b -> Mk k b #

return :: a -> Mk k a #

Functor (Mk k) Source # 
Instance details

Defined in StateMonads

Methods

fmap :: (a -> b) -> Mk k a -> Mk k b #

(<$) :: a -> Mk k b -> Mk k a #

Applicative (Mk k) Source # 
Instance details

Defined in StateMonads

Methods

pure :: a -> Mk k a #

(<*>) :: Mk k (a -> b) -> Mk k a -> Mk k b #

liftA2 :: (a -> b -> c) -> Mk k a -> Mk k b -> Mk k c #

(*>) :: Mk k a -> Mk k b -> Mk k b #

(<*) :: Mk k a -> Mk k b -> Mk k a #

type Mkc k = Mk k () Source #

Continuation monad with unit result

type Ms k s r = Mk (s -> k) r Source #

Continuation monad with state (just an instance of the continuation monad)

type Msc k s = Ms k s () Source #

loadMs :: Ms k s s Source #

storeMs :: s -> Msc k s Source #

modMs :: (s -> s) -> Msc k s Source #

fieldMs :: (s -> f) -> Ms k s f Source #

nopMs :: Msc k s Source #

toMkc :: (k -> k) -> Mkc k Source #

toMs :: Cont k r -> Ms k s r Source #

bmk :: ((a1 -> c1) -> c2) -> (a1 -> a2 -> c1) -> a2 -> c2 Source #

toMsc :: (k -> k) -> Msc k r Source #

type Ks i o s ans = Ms (K i o) s ans Source #

Fudget Kernel Monad with State (just an instance...)

putHighsMs :: (Foldable t, StreamProcIO sp) => t o -> Msc (sp i o) r Source #

putHighMs :: StreamProcIO sp => o -> Msc (sp i o) r Source #

putLowsMs :: (Foldable t, FudgetIO f) => t FRequest -> Msc (f hi ho) r Source #

putLowMs :: FudgetIO f => FRequest -> Msc (f hi ho) r Source #

getKs :: Ms (K hi ho) s (KEvent hi) Source #

storeKs :: s -> Msc k s Source #

loadKs :: Ms k s s Source #

unitKs :: Monad m => a -> m a Source #

bindKs :: Monad m => m a -> (a -> m b) -> m b Source #

thenKs :: Monad m => m a -> m b -> m b Source #

mapKs :: Functor f => (a -> b) -> f a -> f b Source #

stateMonadK :: p -> Mk (p -> t1) t2 -> (t2 -> t1) -> t1 Source #

stateK :: b1 -> Mk (b1 -> a) b2 -> a -> a Source #

data Tree a Source #

Constructors

Leaf a 
Branch (Tree a) (Tree a) 

Instances

Instances details
Eq a => Eq (Tree a) Source # 
Instance details

Defined in TreeF

Methods

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

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

Ord a => Ord (Tree a) Source # 
Instance details

Defined in TreeF

Methods

compare :: Tree a -> Tree a -> Ordering #

(<) :: Tree a -> Tree a -> Bool #

(<=) :: Tree a -> Tree a -> Bool #

(>) :: Tree a -> Tree a -> Bool #

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

max :: Tree a -> Tree a -> Tree a #

min :: Tree a -> Tree a -> Tree a #

treeF :: Tree (a, F b c) -> F (Path, b) (a, c) Source #

treeF' :: Tree (a, F b c) -> FSP (Path, b) (a, c) Source #

leafF :: a1 -> F b1 b2 -> Fa TEvent TCommand ([a2], b1) (a1, b2) Source #

type InF a b = F a (InputMsg b) Source #

inputPairLF :: Orientation -> InF a1 b1 -> InF a2 b2 -> F (a1, a2) (InputMsg (b1, b2)) Source #

inputListLF :: Eq a => Placer -> [(a, InF b c)] -> F [(a, b)] (InputMsg [(a, c)]) Source #

inputPairF :: InF a1 b1 -> InF a2 b2 -> InF (a1, a2) (b1, b2) Source #

inputListF :: Eq a => [(a, InF b c)] -> InF [(a, b)] [(a, c)] Source #

inputThroughF :: InF a a -> InF a a Source #

contDynF :: F a b -> Cont (F a d) b Source #

contDynFSP :: FSP a b -> Cont (FSP a d) b Source #

Containers

bubbleF :: F a b -> F a b Source #

bubblePopupF :: F b2 d2 -> F (PopupMsg b2) d2 Source #

bubbleRootPopupF :: F b2 d2 -> F (PopupMsg b2) d2 Source #

invisibleGroupF :: Sizing -> [FRequest] -> [WindowAttributes] -> F b ho -> F b ho Source #

simpleGroupF :: [WindowAttributes] -> F b ho -> F b ho Source #

unmappedGroupF :: Sizing -> [FRequest] -> K a b -> F c d -> F (Either a c) (Either b d) Source #

groupF :: [FRequest] -> K a b -> F c d -> F (Either a c) (Either b d) Source #

groupF' :: Sizing -> [FRequest] -> K a b -> F c d -> F (Either a c) (Either b d) Source #

sgroupF :: Sizing -> [FRequest] -> Maybe Rect -> K a b -> F c d -> F (Either a c) (Either b d) Source #

swindowF :: [FRequest] -> Maybe Rect -> K a ho -> F a ho Source #

windowF :: [FRequest] -> K a b -> F a b Source #

sF :: Bool -> Maybe Point -> [FRequest] -> K a b -> F c d -> F (Either a c) (Either b d) Source #

containerGroupF :: Rect -> Rect -> Int -> Button -> [Modifiers] -> F c b -> F (Either (Rect, Rect) c) (Either Rect b) Source #

type PotState = (Int, Int, Int) Source #

popupShellF :: String -> Maybe Point -> F a b -> F a (a, b) Source #

popupShellF' :: Customiser ShellF -> String -> Maybe Point -> F a b -> F a (a, b) Source #

popupGroupF :: (Size -> Point, [WindowAttributes], K b1 d1) -> F b2 d2 -> F (PopupMsg b2) d2 Source #

rootPopupF :: (Size -> Point, [WindowAttributes], K b1 d1) -> F b2 d2 -> F (PopupMsg b2) d2 Source #

posPopupShellF :: [Char] -> [WindowAttributes] -> F c a -> F (c, Maybe Point) (c, a) Source #

scrollShellF :: [Char] -> (Point, Point) -> F c d -> F c d Source #

scrollF :: F b d -> F b d Source #

oldScrollF :: Bool -> (Point, Point) -> F b d -> F b d Source #

vScrollF :: F b d -> F b d Source #

oldVscrollF :: Bool -> (Point, Point) -> F b d -> F b d Source #

hScrollF :: F b d -> F b d Source #

oldHscrollF :: Bool -> (Point, Point) -> F b d -> F b d Source #

data SelCmd a Source #

Constructors

Sel a 
ClearSel 
PasteSel 

Instances

Instances details
Eq a => Eq (SelCmd a) Source # 
Instance details

Defined in SelectionF

Methods

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

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

Ord a => Ord (SelCmd a) Source # 
Instance details

Defined in SelectionF

Methods

compare :: SelCmd a -> SelCmd a -> Ordering #

(<) :: SelCmd a -> SelCmd a -> Bool #

(<=) :: SelCmd a -> SelCmd a -> Bool #

(>) :: SelCmd a -> SelCmd a -> Bool #

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

max :: SelCmd a -> SelCmd a -> SelCmd a #

min :: SelCmd a -> SelCmd a -> SelCmd a #

data SelEvt a Source #

Constructors

LostSel 
SelNotify a 

Instances

Instances details
Eq a => Eq (SelEvt a) Source # 
Instance details

Defined in SelectionF

Methods

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

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

Ord a => Ord (SelEvt a) Source # 
Instance details

Defined in SelectionF

Methods

compare :: SelEvt a -> SelEvt a -> Ordering #

(<) :: SelEvt a -> SelEvt a -> Bool #

(<=) :: SelEvt a -> SelEvt a -> Bool #

(>) :: SelEvt a -> SelEvt a -> Bool #

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

max :: SelEvt a -> SelEvt a -> SelEvt a #

min :: SelEvt a -> SelEvt a -> SelEvt a #

data ESelCmd a Source #

Constructors

OwnSel 
SelCmd (SelCmd a) 

Instances

Instances details
Eq a => Eq (ESelCmd a) Source # 
Instance details

Defined in SelectionF

Methods

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

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

Ord a => Ord (ESelCmd a) Source # 
Instance details

Defined in SelectionF

Methods

compare :: ESelCmd a -> ESelCmd a -> Ordering #

(<) :: ESelCmd a -> ESelCmd a -> Bool #

(<=) :: ESelCmd a -> ESelCmd a -> Bool #

(>) :: ESelCmd a -> ESelCmd a -> Bool #

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

max :: ESelCmd a -> ESelCmd a -> ESelCmd a #

min :: ESelCmd a -> ESelCmd a -> ESelCmd a #

data ESelEvt a Source #

Constructors

WantSel 
SelEvt (SelEvt a) 

Instances

Instances details
Eq a => Eq (ESelEvt a) Source # 
Instance details

Defined in SelectionF

Methods

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

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

Ord a => Ord (ESelEvt a) Source # 
Instance details

Defined in SelectionF

Methods

compare :: ESelEvt a -> ESelEvt a -> Ordering #

(<) :: ESelEvt a -> ESelEvt a -> Bool #

(<=) :: ESelEvt a -> ESelEvt a -> Bool #

(>) :: ESelEvt a -> ESelEvt a -> Bool #

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

max :: ESelEvt a -> ESelEvt a -> ESelEvt a #

min :: ESelEvt a -> ESelEvt a -> ESelEvt a #

shellF :: [Char] -> F c d -> F c d Source #

shellF' :: Customiser ShellF -> [Char] -> F c d -> F c d Source #

shellKF :: K a b -> F c d -> F (Either a c) (Either b d) Source #

shellKF' :: Customiser ShellF -> K a b -> F c d -> F (Either a c) (Either b d) Source #

class HasVisible xxx where Source #

Minimal complete definition

setVisible, getVisibleMaybe

Instances

Instances details
HasVisible ShellF Source # 
Instance details

Defined in DShellF

unmappedShellF :: Foldable t => t FRequest -> K a b -> F c d -> F (Either a c) (Either b d) Source #

unmappedShellF' :: Foldable t => (ShellF -> ShellF) -> t FRequest -> K a b -> F c d -> F (Either a c) (Either b d) Source #

simpleShellF :: [Char] -> [WindowAttributes] -> F c d -> F c d Source #

rootWindowF :: K b c -> F b c Source #

rootGroupF :: K a b -> F c d -> F (Either a c) (Either b d) Source #

Debug

maptrace :: Eq b => String -> [b] -> [b] Source #

ctrace :: Show a1 => [Char] -> a1 -> a2 -> a2 Source #

showCommandF :: String -> F a b -> F a b Source #

spyF :: (Show b, Show a2) => F a2 b -> F a2 b Source #

teeF :: (b -> [Char]) -> [Char] -> F b b Source #

Drawing

Colors

tryAllocColor :: FudgetIO f => ColormapId -> RGB -> (Maybe Color -> f b ho) -> f b ho Source #

tryAllocNamedColor :: FudgetIO f => ColormapId -> ColorName -> (Maybe Color -> f b ho) -> f b ho Source #

allocNamedColorDefPixel :: FudgetIO f => ColormapId -> ColorName -> [Char] -> (Pixel -> f b ho) -> f b ho Source #

queryColor :: FudgetIO f => ColormapId -> Pixel -> (Color -> f b ho) -> f b ho Source #

Cursors

setFontCursor :: Int -> K a b -> K a b Source #

defineCursor :: CursorId -> K i o -> K i o Source #

undefineCusror :: K i o -> K i o Source #

Fonts

data CharStruct Source #

Constructors

CharStruct Int 

Instances

Instances details
Eq CharStruct Source # 
Instance details

Defined in Font

Ord CharStruct Source # 
Instance details

Defined in Font

Read CharStruct Source # 
Instance details

Defined in Font

Show CharStruct Source # 
Instance details

Defined in Font

FontGen FontStruct Source # 
Instance details

Defined in GCAttrs

data FontStructF per_char Source #

Instances

Instances details
FontGen FontStruct Source # 
Instance details

Defined in GCAttrs

Eq per_char => Eq (FontStructF per_char) Source # 
Instance details

Defined in Font

Methods

(==) :: FontStructF per_char -> FontStructF per_char -> Bool #

(/=) :: FontStructF per_char -> FontStructF per_char -> Bool #

Ord per_char => Ord (FontStructF per_char) Source # 
Instance details

Defined in Font

Methods

compare :: FontStructF per_char -> FontStructF per_char -> Ordering #

(<) :: FontStructF per_char -> FontStructF per_char -> Bool #

(<=) :: FontStructF per_char -> FontStructF per_char -> Bool #

(>) :: FontStructF per_char -> FontStructF per_char -> Bool #

(>=) :: FontStructF per_char -> FontStructF per_char -> Bool #

max :: FontStructF per_char -> FontStructF per_char -> FontStructF per_char #

min :: FontStructF per_char -> FontStructF per_char -> FontStructF per_char #

Read per_char => Read (FontStructF per_char) Source # 
Instance details

Defined in Font

Methods

readsPrec :: Int -> ReadS (FontStructF per_char) #

readList :: ReadS [FontStructF per_char] #

readPrec :: ReadPrec (FontStructF per_char) #

readListPrec :: ReadPrec [FontStructF per_char] #

Show per_char => Show (FontStructF per_char) Source # 
Instance details

Defined in Font

Methods

showsPrec :: Int -> FontStructF per_char -> ShowS #

show :: FontStructF per_char -> String #

showList :: [FontStructF per_char] -> ShowS #

data FontDirection Source #

data FontProp Source #

Constructors

FontProp Atom Int 

Instances

Instances details
Eq FontProp Source # 
Instance details

Defined in Font

Ord FontProp Source # 
Instance details

Defined in Font

Read FontProp Source # 
Instance details

Defined in Font

Show FontProp Source # 
Instance details

Defined in Font

loadQueryFont :: FudgetIO f => [Char] -> (Maybe (FontStructF (Array Char CharStruct)) -> f b ho) -> f b ho Source #

queryFont :: FudgetIO f => FontId -> (FontStructF (Array Char CharStruct) -> f b ho) -> f b ho Source #

loadFont :: FudgetIO f => [Char] -> (FontId -> f b ho) -> f b ho Source #

listFonts :: FudgetIO f => [Char] -> Int -> ([FontName] -> f b ho) -> f b ho Source #

listFontsF :: [Char] -> Int -> Cont (F b c) [FontName] Source #

listFontsWithInfo :: FudgetIO f => [Char] -> Int -> ([(FontName, FontStructF (Array Char CharStruct))] -> f b ho) -> f b ho Source #

tryLoadFont :: FudgetIO f => [Char] -> (Maybe FontId -> f b ho) -> f b ho Source #

Graphics Contexts

pmCreateGC :: FudgetIO f => PixmapId -> GCId -> [GCAttributes Pixel FontId] -> (GCId -> f b ho) -> f b ho Source #

wCreateGC :: FudgetIO f => GCId -> [GCAttributes Pixel FontId] -> (GCId -> f b ho) -> f b ho Source #

createGC :: FudgetIO f => Drawable -> GCId -> [GCAttributes Pixel FontId] -> (GCId -> f b ho) -> f b ho Source #

createGCF :: Drawable -> GCId -> GCAttributeList -> (GCId -> F a b) -> F a b Source #

wCreateGCF :: GCId -> GCAttributeList -> (GCId -> F a b) -> F a b Source #

pmCreateGCF :: PixmapId -> GCId -> GCAttributeList -> (GCId -> F a b) -> F a b Source #

class FontGen a where Source #

Minimal complete definition

tryConvFontK

Methods

tryConvFontK :: FudgetIO f => a -> Cont (f i o) (Maybe FontData) Source #

convFontListK :: FudgetIO f => [a] -> Cont (f i o) (Maybe FontData) Source #

Instances

Instances details
FontGen Char Source # 
Instance details

Defined in GCAttrs

Methods

tryConvFontK :: FudgetIO f => Char -> Cont (f i o) (Maybe FontData) Source #

convFontListK :: FudgetIO f => [Char] -> Cont (f i o) (Maybe FontData) Source #

FontGen FontStruct Source # 
Instance details

Defined in GCAttrs

FontGen FontSpec Source # 
Instance details

Defined in GCAttrs

FontGen a => FontGen [a] Source # 
Instance details

Defined in GCAttrs

Methods

tryConvFontK :: FudgetIO f => [a] -> Cont (f i o) (Maybe FontData) Source #

convFontListK :: FudgetIO f => [[a]] -> Cont (f i o) (Maybe FontData) Source #

class ColorGen a where Source #

Minimal complete definition

tryConvColorK

Methods

tryConvColorK :: FudgetIO f => a -> Cont (f i o) (Maybe Pixel) Source #

convColorListK :: FudgetIO f => [a] -> Cont (f i o) (Maybe Pixel) Source #

Instances

Instances details
ColorGen Char Source # 
Instance details

Defined in GCAttrs

Methods

tryConvColorK :: FudgetIO f => Char -> Cont (f i o) (Maybe Pixel) Source #

convColorListK :: FudgetIO f => [Char] -> Cont (f i o) (Maybe Pixel) Source #

ColorGen RGB Source # 
Instance details

Defined in GCAttrs

Methods

tryConvColorK :: FudgetIO f => RGB -> Cont (f i o) (Maybe Pixel) Source #

convColorListK :: FudgetIO f => [RGB] -> Cont (f i o) (Maybe Pixel) Source #

ColorGen Pixel Source # 
Instance details

Defined in GCAttrs

Methods

tryConvColorK :: FudgetIO f => Pixel -> Cont (f i o) (Maybe Pixel) Source #

convColorListK :: FudgetIO f => [Pixel] -> Cont (f i o) (Maybe Pixel) Source #

ColorGen ColorSpec Source # 
Instance details

Defined in GCAttrs

ColorGen c => ColorGen [c] Source # 
Instance details

Defined in GCAttrs

Methods

tryConvColorK :: FudgetIO f => [c] -> Cont (f i o) (Maybe Pixel) Source #

convColorListK :: FudgetIO f => [[c]] -> Cont (f i o) (Maybe Pixel) Source #

data FontSpec Source #

Constructors

forall a.(Show a, FontGen a) => FontSpeci a 

Instances

Instances details
Show FontSpec Source # 
Instance details

Defined in GCAttrs

FontGen FontSpec Source # 
Instance details

Defined in GCAttrs

data ColorSpec Source #

Constructors

forall a.(Show a, ColorGen a) => ColorSpec a 

Instances

Instances details
Show ColorSpec Source # 
Instance details

Defined in GCAttrs

ColorGen ColorSpec Source # 
Instance details

Defined in GCAttrs

fontSpec :: (Show a, FontGen a) => a -> FontSpec Source #

convColorK :: (ColorGen a, FudgetIO f, Show a) => a -> (Pixel -> f i o) -> f i o Source #

convFontK :: (FontGen a, FudgetIO f, Show a) => a -> (FontData -> f i o) -> f i o Source #

convList :: (t -> (Maybe a -> b) -> b) -> [t] -> (Maybe a -> b) -> b Source #

tryConvColorRGBK :: FudgetIO f => RGB -> (Maybe Pixel -> f b ho) -> f b ho Source #

convGCSpecK :: (ColorGen a1, FudgetIO f, FontGen a2, Show a1, Show a2) => FontData -> [GCAttributes a1 a2] -> ([GCAttributes Pixel FontId] -> FontData -> f i o) -> f i o Source #

type Cont c a = (a -> c) -> c Source #

data GCtx Source #

Constructors

GC GCId FontData 

Instances

Instances details
Show GCtx Source # 
Instance details

Defined in GCtx

Methods

showsPrec :: Int -> GCtx -> ShowS #

show :: GCtx -> String #

showList :: [GCtx] -> ShowS #

data GCSpec Source #

Instances

Instances details
Show GCSpec Source # 
Instance details

Defined in GCtx

createGCtx :: (ColorGen a1, FudgetIO f, FontGen a2, Show a1, Show a2) => Drawable -> GCtx -> [GCAttributes a1 a2] -> (GCtx -> f i o) -> f i o Source #

wCreateGCtx :: (ColorGen a1, FudgetIO f, FontGen a2, Show a1, Show a2) => GCtx -> [GCAttributes a1 a2] -> (GCtx -> f i o) -> f i o Source #

pmCreateGCtx :: (ColorGen a1, FudgetIO f, FontGen a2, Show a1, Show a2) => PixmapId -> GCtx -> [GCAttributes a1 a2] -> (GCtx -> f i o) -> f i o Source #

class Graphic

class Graphic a where Source #

Minimal complete definition

measureGraphicK

Instances

Instances details
Graphic Bool Source # 
Instance details

Defined in Graphic

Graphic Char Source # 
Instance details

Defined in Graphic

Graphic Double Source # 
Instance details

Defined in Graphic

Graphic Float Source # 
Instance details

Defined in Graphic

Graphic Int Source # 
Instance details

Defined in Graphic

Graphic Integer Source # 
Instance details

Defined in Graphic

Graphic MeasuredGraphics Source # 
Instance details

Defined in Graphic

Graphic PixmapImage Source # 
Instance details

Defined in PixmapGen

Graphic FlexibleDrawing Source # 
Instance details

Defined in FlexibleDrawing

Graphic ImageString Source # 
Instance details

Defined in FixedDrawing

Graphic FixedColorDrawing Source # 
Instance details

Defined in FixedDrawing

Graphic FixedDrawing Source # 
Instance details

Defined in FixedDrawing

Graphic Gfx Source # 
Instance details

Defined in DrawingUtils

Graphic BitmapFile Source # 
Instance details

Defined in BitmapDrawing

Graphic SmileyMode Source # 
Instance details

Defined in SmileyF

Graphic a => Graphic [a] Source # 
Instance details

Defined in Graphic

Graphic a => Graphic (Maybe a) Source # 
Instance details

Defined in Graphic

Graphic (Item a) Source # 
Instance details

Defined in MenuBarF

(Graphic a, Graphic b) => Graphic (Either a b) Source # 
Instance details

Defined in Graphic

(Graphic a, Graphic b) => Graphic (a, b) Source # 
Instance details

Defined in Graphic

Methods

measureGraphicK :: FudgetIO k => (a, b) -> GCtx -> Cont (k i o) MeasuredGraphics Source #

measureGraphicListK :: FudgetIO k => [(a, b)] -> GCtx -> Cont (k i o) MeasuredGraphics Source #

Graphic leaf => Graphic (Drawing annot leaf) Source # 
Instance details

Defined in Drawing

Methods

measureGraphicK :: FudgetIO k => Drawing annot leaf -> GCtx -> Cont (k i o) MeasuredGraphics Source #

measureGraphicListK :: FudgetIO k => [Drawing annot leaf] -> GCtx -> Cont (k i o) MeasuredGraphics Source #

measureText :: (FudgetIO f, Show a) => a -> GCtx -> (MeasuredGraphics -> f b ho) -> f b ho Source #

data GCtx Source #

Instances

Instances details
Show GCtx Source # 
Instance details

Defined in GCtx

Methods

showsPrec :: Int -> GCtx -> ShowS #

show :: GCtx -> String #

showList :: [GCtx] -> ShowS #

type Cont c a = (a -> c) -> c Source #

Atomic Drawings

data FixedDrawing Source #

Constructors

FixD Size [DrawCommand] 

Instances

Instances details
Show FixedDrawing Source # 
Instance details

Defined in FixedDrawing

Graphic FixedDrawing Source # 
Instance details

Defined in FixedDrawing

newtype ImageString Source #

Constructors

ImageString String 

Instances

Instances details
Graphic ImageString Source # 
Instance details

Defined in FixedDrawing

vMirror :: (Rect -> [Point]) -> Rect -> [Point] Source #

hMirror :: (Rect -> [Point]) -> Rect -> [Point] Source #

data BitmapFile Source #

Constructors

BitmapFile String 

Instances

Instances details
Graphic BitmapFile Source # 
Instance details

Defined in BitmapDrawing

bitmapFromData :: FudgetIO f => BitmapData -> (BitmapReturn -> f b ho) -> f b ho Source #

readBitmapFile :: FudgetIO f => [Char] -> (BitmapReturn -> f b ho) -> f b ho Source #

createPixmap :: FudgetIO f => Point -> Int -> (PixmapId -> f b ho) -> f b ho Source #

data PixmapImage Source #

Constructors

PixmapImage Size PixmapId 

Instances

Instances details
Graphic PixmapImage Source # 
Instance details

Defined in PixmapGen

PixmapGen PixmapImage Source # 
Instance details

Defined in PixmapGen

class PixmapGen a where Source #

Methods

convToPixmapK :: FudgetIO c => a -> Cont (c i o) PixmapImage Source #

Instances

Instances details
PixmapGen MeasuredGraphics Source # 
Instance details

Defined in Graphic2Pixmap

PixmapGen PixmapImage Source # 
Instance details

Defined in PixmapGen

PixmapGen FixedColorDrawing Source # 
Instance details

Defined in Graphic2Pixmap

measureImageK :: (PixmapGen a, FudgetIO c) => a -> GCtx -> (MeasuredGraphics -> c i o) -> c i o Source #

Composed drawings

data Drawing lbl leaf Source #

Constructors

AtomicD leaf 
LabelD lbl (Drawing lbl leaf) 
AttribD GCSpec (Drawing lbl leaf) 
SpacedD Spacer (Drawing lbl leaf) 
PlacedD Placer (Drawing lbl leaf) 
ComposedD Int [Drawing lbl leaf]

Int=how many visible components

CreateHardAttribD GCtx [GCAttributes ColorSpec FontSpec] (GCtx -> Drawing lbl leaf) 

Instances

Instances details
Functor (Drawing lbl) Source # 
Instance details

Defined in Drawing

Methods

fmap :: (a -> b) -> Drawing lbl a -> Drawing lbl b #

(<$) :: a -> Drawing lbl b -> Drawing lbl a #

(Show leaf, Show lbl) => Show (Drawing lbl leaf) Source # 
Instance details

Defined in Drawing

Methods

showsPrec :: Int -> Drawing lbl leaf -> ShowS #

show :: Drawing lbl leaf -> String #

showList :: [Drawing lbl leaf] -> ShowS #

Graphic leaf => Graphic (Drawing annot leaf) Source # 
Instance details

Defined in Drawing

Methods

measureGraphicK :: FudgetIO k => Drawing annot leaf -> GCtx -> Cont (k i o) MeasuredGraphics Source #

measureGraphicListK :: FudgetIO k => [Drawing annot leaf] -> GCtx -> Cont (k i o) MeasuredGraphics Source #

labelD :: lbl -> Drawing lbl leaf -> Drawing lbl leaf Source #

placedD :: Placer -> Drawing lbl leaf -> Drawing lbl leaf Source #

atomicD :: leaf -> Drawing lbl leaf Source #

type DPath = [Int] Source #

data GCSpec Source #

Instances

Instances details
Show GCSpec Source # 
Instance details

Defined in GCtx

boxVisibleD :: Int -> [Drawing lbl leaf] -> Drawing lbl leaf Source #

boxD :: [Drawing lbl leaf] -> Drawing lbl leaf Source #

stackD :: [Drawing lbl leaf] -> Drawing lbl leaf Source #

vertD :: Drawing lbl leaf -> Drawing lbl leaf Source #

vertD' :: Distance -> Drawing lbl leaf -> Drawing lbl leaf Source #

horizD :: Drawing lbl leaf -> Drawing lbl leaf Source #

horizD' :: Distance -> Drawing lbl leaf -> Drawing lbl leaf Source #

vboxD :: [Drawing lbl leaf] -> Drawing lbl leaf Source #

hboxD :: [Drawing lbl leaf] -> Drawing lbl leaf Source #

vboxD' :: Distance -> [Drawing lbl leaf] -> Drawing lbl leaf Source #

hboxD' :: Distance -> [Drawing lbl leaf] -> Drawing lbl leaf Source #

vertlD :: Drawing lbl leaf -> Drawing lbl leaf Source #

vertlD' :: Distance -> Drawing lbl leaf -> Drawing lbl leaf Source #

vboxlD :: [Drawing lbl leaf] -> Drawing lbl leaf Source #

vboxlD' :: Distance -> [Drawing lbl leaf] -> Drawing lbl leaf Source #

horizcD :: Drawing lbl leaf -> Drawing lbl leaf Source #

horizcD' :: Distance -> Drawing lbl leaf -> Drawing lbl leaf Source #

hboxcD :: [Drawing lbl leaf] -> Drawing lbl leaf Source #

hboxcD' :: Distance -> [Drawing lbl leaf] -> Drawing lbl leaf Source #

tableD :: Int -> [Drawing lbl leaf] -> Drawing lbl leaf Source #

tableD' :: Distance -> Int -> [Drawing lbl leaf] -> Drawing lbl leaf Source #

matrixD :: Int -> [Drawing lbl leaf] -> Drawing lbl leaf Source #

matrixD' :: Distance -> Int -> [Drawing lbl leaf] -> Drawing lbl leaf Source #

westD :: Drawing lbl leaf -> Drawing lbl leaf Source #

northwestD :: Drawing lbl leaf -> Drawing lbl leaf Source #

padD :: Distance -> Drawing lbl leaf -> Drawing lbl leaf Source #

fontD :: (Show a, FontGen a) => a -> Drawing lbl leaf -> Drawing lbl leaf Source #

fgD :: (Show a, ColorGen a) => a -> Drawing lbl leaf -> Drawing lbl leaf Source #

bgD :: (Show a, ColorGen a) => a -> Drawing lbl leaf -> Drawing lbl leaf Source #

fatD :: Drawing lbl leaf -> Drawing lbl leaf Source #

attribD :: GCSpec -> Drawing lbl leaf -> Drawing lbl leaf Source #

hardAttribD :: GCtx -> Drawing lbl leaf -> Drawing lbl leaf Source #

spacedD :: Spacer -> Drawing lbl leaf -> Drawing lbl leaf Source #

data Gfx Source #

Constructors

forall a.Graphic a => G a 

Instances

Instances details
Show Gfx Source # 
Instance details

Defined in DrawingUtils

Methods

showsPrec :: Int -> Gfx -> ShowS #

show :: Gfx -> String #

showList :: [Gfx] -> ShowS #

Graphic Gfx Source # 
Instance details

Defined in DrawingUtils

g :: Graphic a => a -> Drawing lbl Gfx Source #

drawingPart :: Drawing lbl leaf -> DPath -> Drawing lbl leaf Source #

maybeDrawingPart :: Drawing lbl leaf -> DPath -> Maybe (Drawing lbl leaf) Source #

drawingAnnotPart' :: (t -> Bool) -> Drawing t leaf -> DPath -> [Int] Source #

visibleAncestor :: Drawing lbl leaf -> [Int] -> [Int] Source #

replacePart :: Drawing lbl leaf -> DPath -> Drawing lbl leaf -> Drawing lbl leaf Source #

updatePart :: Drawing lbl leaf -> DPath -> (Drawing lbl leaf -> Drawing lbl leaf) -> Drawing lbl leaf Source #

mapLabelDrawing :: (t -> lbl) -> Drawing t leaf -> Drawing lbl leaf Source #

mapLeafDrawing :: (t -> leaf) -> Drawing lbl t -> Drawing lbl leaf Source #

annotChildren' :: (a -> Bool) -> Drawing a d -> [(DPath, Drawing a d)] Source #

drawingAnnots :: Drawing a leaf -> [(DPath, a)] Source #

extractParts :: Drawing lbl leaf -> (Drawing lbl leaf -> Maybe a) -> [(DPath, a)] Source #

deletePart :: Drawing lbl leaf -> [Int] -> Drawing lbl leaf Source #

groupParts :: Int -> Int -> Drawing lbl leaf -> Drawing lbl leaf Source #

ungroupParts :: Int -> Drawing lbl leaf -> Drawing lbl leaf Source #

graphic2PixmapImage :: (Graphic a, FudgetIO k) => a -> GCtx -> (PixmapImage -> k i o) -> k i o Source #

data PixmapImage Source #

Constructors

PixmapImage Size PixmapId 

Instances

Instances details
Graphic PixmapImage Source # 
Instance details

Defined in PixmapGen

PixmapGen PixmapImage Source # 
Instance details

Defined in PixmapGen

Misc

type DPath = [Int] Source #

measureString :: FudgetIO f => [Char] -> GCtx -> (MeasuredGraphics -> f b ho) -> f b ho Source #

measureImageString :: FudgetIO f => [Char] -> GCtx -> (MeasuredGraphics -> f b ho) -> f b ho Source #

measurePackedString :: FudgetIO f => PackedString -> GCtx -> (MeasuredGraphics -> f b ho) -> f b ho Source #

Filters

allcacheF :: F i o -> F i o Source #

shapeGroupMgr :: F a b -> F a b Source #

doubleClickF :: Time -> F a b -> F a b Source #

GUI elements

Buttons

buttonF :: Graphic lbl => lbl -> F Click Click Source #

buttonF' :: Graphic lbl => Customiser (ButtonF lbl) -> lbl -> F Click Click Source #

buttonF'' :: Graphic lbl => Customiser (ButtonF lbl) -> lbl -> PF (ButtonF lbl) Click Click Source #

radioGroupF :: (Graphic lbl, Eq alt) => [(alt, lbl)] -> alt -> F alt alt Source #

radioGroupF' :: (Graphic lbl, Eq alt) => Customiser RadioGroupF -> [(alt, lbl)] -> alt -> F alt alt Source #

border3dF :: Bool -> Int -> F a b -> F (Either Bool a) b Source #

buttonBorderF :: Int -> F a b -> F (Either Bool a) b Source #

oldButtonF :: (Graphic e, FontGen a1, Show a1, Show a2, ColorGen a2) => Double -> Int -> a1 -> ColorSpec -> a2 -> [(ModState, KeySym)] -> e -> F e Click Source #

data BMevents Source #

Constructors

BMNormal 
BMInverted 
BMClick 

Instances

Instances details
Eq BMevents Source # 
Instance details

Defined in ButtonGroupF

Ord BMevents Source # 
Instance details

Defined in ButtonGroupF

Show BMevents Source # 
Instance details

Defined in ButtonGroupF

pushButtonF :: [(ModState, KeySym)] -> F b1 b2 -> F b1 (Either b2 Click) Source #

pushButtonF' :: Int -> [(ModState, KeySym)] -> F b1 b2 -> F b1 (Either b2 Click) Source #

data Click Source #

Button clicks

Constructors

Click 

Instances

Instances details
Eq Click Source # 
Instance details

Defined in InputMsg

Methods

(==) :: Click -> Click -> Bool #

(/=) :: Click -> Click -> Bool #

Ord Click Source # 
Instance details

Defined in InputMsg

Methods

compare :: Click -> Click -> Ordering #

(<) :: Click -> Click -> Bool #

(<=) :: Click -> Click -> Bool #

(>) :: Click -> Click -> Bool #

(>=) :: Click -> Click -> Bool #

max :: Click -> Click -> Click #

min :: Click -> Click -> Click #

Show Click Source # 
Instance details

Defined in InputMsg

Methods

showsPrec :: Int -> Click -> ShowS #

show :: Click -> String #

showList :: [Click] -> ShowS #

quitIdF :: (ho -> Bool) -> F ho ho Source #

quitF :: F ans ho Source #

radioF :: (Eq a, Graphic a1, Show a2, FontGen a2) => Placer -> Bool -> a2 -> [(a, a1)] -> a -> F a a Source #

oldRadioGroupF :: (Eq d, Graphic a1, Show a2, FontGen a2) => Placer -> Bool -> a2 -> [d] -> d -> (d -> a1) -> F d d Source #

toggleF :: Bool -> [(ModState, KeySym)] -> F c b -> F (Either Bool c) (Either Bool b) Source #

oldToggleButtonF :: (Graphic a1, Show a2, FontGen a2) => a2 -> [(ModState, KeySym)] -> a1 -> F Bool Bool Source #

oldToggleButtonF' :: (Graphic a1, Show a2, FontGen a2) => Bool -> a2 -> [(ModState, KeySym)] -> a1 -> F Bool Bool Source #

Graphics

data GraphicsF gfx Source #

Instances

Instances details
HasInitDisp GraphicsF Source # 
Instance details

Defined in GraphicsF

HasInitSize GraphicsF Source # 
Instance details

Defined in GraphicsF

HasSizing (GraphicsF a) Source # 
Instance details

Defined in GraphicsF

HasStretchable (GraphicsF a) Source # 
Instance details

Defined in GraphicsF

HasFgColorSpec (GraphicsF a) Source # 
Instance details

Defined in GraphicsF

HasBgColorSpec (GraphicsF a) Source # 
Instance details

Defined in GraphicsF

HasBorderWidth (GraphicsF a) Source # 
Instance details

Defined in GraphicsF

HasFontSpec (GraphicsF a) Source # 
Instance details

Defined in GraphicsF

graphicsGroupF :: Graphic gfx => F i o -> F (Either (GfxFCmd gfx) i) (Either GfxFEvent o) Source #

graphicsDispGroupF' :: Graphic gfx => (GraphicsF gfx -> GraphicsF gfx) -> F i o -> F (Either (GfxFCmd gfx) i) (Either GfxFEvent o) Source #

graphicsLabelF :: Graphic a => a -> F e d Source #

graphicsLabelF' :: Graphic a => (GraphicsF a -> GraphicsF a) -> a -> F e d Source #

data GfxChange gfx Source #

Instances

Instances details
Functor GfxChange Source # 
Instance details

Defined in GraphicsF

Methods

fmap :: (a -> b) -> GfxChange a -> GfxChange b #

(<$) :: a -> GfxChange b -> GfxChange a #

data GfxCommand path gfx Source #

Instances

Instances details
Functor (GfxCommand path) Source # 
Instance details

Defined in GraphicsF

Methods

fmap :: (a -> b) -> GfxCommand path a -> GfxCommand path b #

(<$) :: a -> GfxCommand path b -> GfxCommand path a #

data GfxEvent path Source #

Instances

Instances details
Eq path => Eq (GfxEvent path) Source # 
Instance details

Defined in GraphicsF

Methods

(==) :: GfxEvent path -> GfxEvent path -> Bool #

(/=) :: GfxEvent path -> GfxEvent path -> Bool #

Show path => Show (GfxEvent path) Source # 
Instance details

Defined in GraphicsF

Methods

showsPrec :: Int -> GfxEvent path -> ShowS #

show :: GfxEvent path -> String #

showList :: [GfxEvent path] -> ShowS #

replaceGfx :: path -> gfx -> GfxCommand path gfx Source #

replaceAllGfx :: gfx -> GfxCommand [a] gfx Source #

showGfx :: path -> GfxCommand path gfx Source #

highlightGfx :: path -> Bool -> GfxCommand path gfx Source #

hyperGraphicsF :: (Eq d, Graphic leaf) => Drawing d leaf -> F (Either (Drawing d leaf) (d, Drawing d leaf)) d Source #

hyperGraphicsF' :: (Eq d, Graphic leaf) => (GraphicsF (Drawing d leaf) -> GraphicsF (Drawing d leaf)) -> Drawing d leaf -> F (Either (Drawing d leaf) (d, Drawing d leaf)) d Source #

Menus

menuButtonF :: Graphic lbl => FontName -> lbl -> F lbl Click Source #

simpleMenuF :: (Eq b, Graphic c, Graphic a) => FontName -> a -> [b] -> (b -> c) -> F a b Source #

menuAltsF :: (Eq d, Graphic b) => [Char] -> [d] -> (d -> b) -> F PopupMenu d Source #

menuF :: (Graphic mlbl, Graphic albl) => mlbl -> [(alt, albl)] -> F alt alt Source #

oldMenuF :: (Graphic c, Eq b, Graphic a) => FontName -> a -> [(b, [(ModState, KeySym)])] -> (b -> c) -> F a b Source #

buttonMenuF :: Graphic lbl => LayoutDir -> FontName -> lbl -> [(a, [(ModState, KeySym)])] -> F (Either MenuState b) a -> F (Either MenuState (Either lbl b)) (Either MenuState a) Source #

buttonMenuF' :: Graphic lbl => Bool -> LayoutDir -> FontName -> lbl -> [(a, [(ModState, KeySym)])] -> F (Either MenuState b) a -> F (Either MenuState (Either lbl b)) (Either MenuState a) Source #

grabberF :: [(a1, [(ModState, KeySym)])] -> F (Either a2 a1) (Either MenuState d) -> F a1 d Source #

data MenuState Source #

Instances

Instances details
Show MenuState Source # 
Instance details

Defined in MenuF

data EqSnd a b Source #

Constructors

EqSnd a b 

Instances

Instances details
Eq b => Eq (EqSnd a b) Source # 
Instance details

Defined in MenuF

Methods

(==) :: EqSnd a b -> EqSnd a b -> Bool #

(/=) :: EqSnd a b -> EqSnd a b -> Bool #

fstEqSnd :: EqSnd a b -> a Source #

sndEqSnd :: EqSnd a b -> b Source #

toEqSnd :: [(a, b)] -> [EqSnd a b] Source #

data PopupMenu Source #

Instances

Instances details
Show PopupMenu Source # 
Instance details

Defined in MenuPopupF

menuPopupF' :: Bool -> F b d -> F (Either PopupMenu b) d Source #

Popups

inputPopupF :: String -> InF a c -> Maybe c -> F (Maybe String, Maybe a) ((Maybe String, Maybe a), c) Source #

confirmPopupF :: Graphic msg => F msg (msg, ConfirmMsg) Source #

data ConfirmMsg Source #

Output from dialog popups with OK and Cancel buttons

Constructors

Confirm 
Cancel 

Instances

Instances details
Eq ConfirmMsg Source # 
Instance details

Defined in InputMsg

Ord ConfirmMsg Source # 
Instance details

Defined in InputMsg

Show ConfirmMsg Source # 
Instance details

Defined in InputMsg

messagePopupF :: Graphic msg => F msg (msg, Click) Source #

popupMenuF :: (Eq b1, Graphic b1) => [(a, b1)] -> F c b2 -> F (Either [(a, b1)] c) (Either a b2) Source #

oldPopupMenuF :: (Eq b1, Graphic b2, Foldable t) => ColorName -> Bool -> [Char] -> Button -> [Modifiers] -> t (ModState, KeySym) -> [(b1, b3)] -> (b1 -> b2) -> F c d -> F (Either [(b1, b4)] c) (Either b1 d) Source #

oldPopupMenuF' :: forall t b1 b2 b3 c d a b4 b5. (Eq b1, Graphic b2, Foldable t) => ColorName -> Bool -> [Char] -> Button -> [Modifiers] -> t (ModState, KeySym) -> [(b1, b3)] -> (b1 -> b2) -> F c d -> F (Either (Either a b4) (Either (Either [(b1, b5)] PopupMenu) c)) (Either (Either (Either a PopupMenu) b4) (Either b1 d)) Source #

smallPickListF :: (d -> String) -> F [d] d Source #

Text elements

labRightOfF :: Graphic g => g -> F c d -> F c d Source #

labLeftOfF :: Graphic g => g -> F c d -> F c d Source #

labBelowF :: Graphic g => g -> F c d -> F c d Source #

labAboveF :: Graphic g => g -> F c d -> F c d Source #

tieLabelF :: Graphic g => Orientation -> Double -> g -> F c d -> F c d Source #

data DisplayF a Source #

Instances

Instances details
HasInitDisp DisplayF Source # 
Instance details

Defined in DDisplayF

HasInitSize DisplayF Source # 
Instance details

Defined in DDisplayF

HasSizing (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasStretchable (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasAlign (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasMargin (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasFgColorSpec (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasBgColorSpec (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasBorderWidth (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasFontSpec (DisplayF a) Source # 
Instance details

Defined in DDisplayF

displayF :: Graphic g => F g void Source #

labelF :: Graphic g => g -> F a b Source #

labelF' :: Graphic g => Customiser (DisplayF g) -> g -> F a b Source #

data TextF Source #

Instances

Instances details
HasSizing TextF Source # 
Instance details

Defined in TextF

HasInitText TextF Source # 
Instance details

Defined in TextF

HasStretchable TextF Source # 
Instance details

Defined in TextF

HasAlign TextF Source # 
Instance details

Defined in TextF

HasMargin TextF Source # 
Instance details

Defined in TextF

HasFgColorSpec TextF Source # 
Instance details

Defined in TextF

HasBgColorSpec TextF Source # 
Instance details

Defined in TextF

HasBorderWidth TextF Source # 
Instance details

Defined in TextF

HasFontSpec TextF Source # 
Instance details

Defined in TextF

Special indicators

onOffDispF :: Bool -> F Bool nothing Source #

bellF :: F ho ho Source #

Editors

data EditEvt Source #

Instances

Instances details
Eq EditEvt Source # 
Instance details

Defined in Edit

Methods

(==) :: EditEvt -> EditEvt -> Bool #

(/=) :: EditEvt -> EditEvt -> Bool #

Ord EditEvt Source # 
Instance details

Defined in Edit

data EDirection Source #

Constructors

ELeft 
ERight 

Instances

Instances details
Eq EDirection Source # 
Instance details

Defined in Edtypes

Ord EDirection Source # 
Instance details

Defined in Edtypes

InfixOps

(-==-) :: SP a1 b -> SP a2 a1 -> SP a2 b infixr 8 Source #

(-+-) :: SP a1 a2 -> SP a3 b -> SP (Either a1 a3) (Either a2 b) infixr 8 Source #

(-*-) :: SP a b -> SP a b -> SP a b infixr 8 Source #

(>+<) :: F a b -> F c d -> F (Either a c) (Either b d) infixl 5 Source #

(>*<) :: F c ho -> F c ho -> F c ho infixl 5 Source #

(>==<) :: F a1 b -> F a2 a1 -> F a2 b infixr 4 Source #

(>^^=<) :: SP a b -> F e a -> F e b infixr 7 Source #

(>=^^<) :: F c d -> SP e c -> F e d infixl 6 Source #

(>^=<) :: (a -> b) -> F e a -> F e b infixr 7 Source #

(>=^<) :: F c d -> (e -> c) -> F e d infixl 6 Source #

(>..=<) :: SP TCommand TCommand -> F hi ho -> F hi ho infixr 5 Source #

(>=..<) :: F hi ho -> SP TEvent TEvent -> F hi ho infixl 6 Source #

(>.=<) :: (TCommand -> TCommand) -> F hi ho -> F hi ho infixr 6 Source #

(>=.<) :: F hi ho -> (TEvent -> TEvent) -> F hi ho infixl 6 Source #

(>#==<) :: (F a1 f, Orientation) -> F e a1 -> F e f infixl 9 Source #

(>#+<) :: (F a b, Orientation) -> F c d -> F (Either a c) (Either b d) infixl 9 Source #

(>==#<) :: F a1 b -> (Distance, Orientation, F a a1) -> F a b infixl 9 Source #

(>+#<) :: F a b -> (Distance, Orientation, F c d) -> F (Either a c) (Either b d) infixl 9 Source #

Kernel utilities

changeBackPixel :: (Show a, ColorGen a) => a -> K i o -> K i o Source #

changeGetBackPixel :: (Show a, ColorGen a) => a -> (Pixel -> K i o) -> K i o Source #

changeBg :: ColorName -> K a b -> K a b Source #

darkGreyBgK :: K b ho -> K b ho Source #

lightGreyBgK :: K b ho -> K b ho Source #

greyBgK :: K b ho -> K b ho Source #

knobBgK :: K b ho -> K b ho Source #

changeBackPixmap :: (ColorGen a1, ColorGen a2, Show a1, Show a2) => a1 -> a2 -> Point -> [DrawCommand] -> K i o -> K i o Source #

internAtom :: FudgetIO f => String -> Bool -> (Atom -> f b ho) -> f b ho Source #

atomName :: FudgetIO f => Atom -> (Maybe String -> f b ho) -> f b ho Source #

parK :: K a b -> K a b -> K a b Source #

compK :: K a b -> K c d -> K (Either a c) (Either b d) Source #

quitK :: (K (Either String Bool) a -> K (Either String Bool) a) -> K hi ho Source #

exitK :: p -> K b ho Source #

unmapWindowK :: K i o -> K i o Source #

reportK :: K hi () -> K hi () Source #

wmDeleteWindowK :: (Atom -> K b c) -> K b c Source #

dynShapeK :: [GCAttributes ColorName [Char]] -> (Size -> [DrawCommand]) -> K c d -> K (Either (Size -> [DrawCommand]) c) (Either b d) Source #

shapeK :: (Size -> [DrawCommand]) -> K a b -> K a b Source #

type Fms' a b c = MapState a (KEvent b) [KCommand c] Source #

type MapState a b c = a -> b -> (a, c) Source #

simpleF :: [Char] -> (Drawer -> Drawer -> Fms' a c d) -> Size -> a -> F c d Source #

simpleWindowF :: (Drawer -> Drawer -> Fms' a1 a2 b) -> Size -> Bool -> Bool -> a1 -> F a2 b Source #

simpleK :: (Drawer -> Drawer -> Fms' a b c) -> Size -> a -> K b c Source #

defaultVisual :: FudgetIO f => (Visual -> f b ho) -> f b ho Source #

mapstateK :: (t -> KEvent hi -> (t, [KCommand ho])) -> t -> K hi ho Source #

Layout

autoLayoutF :: F a b -> F a b Source #

autoLayoutF' :: Bool -> Sizing -> F a b -> F a b Source #

data LayoutDir Source #

Constructors

Horizontal 
Vertical 

Instances

Instances details
Eq LayoutDir Source # 
Instance details

Defined in LayoutDir

Ord LayoutDir Source # 
Instance details

Defined in LayoutDir

Show LayoutDir Source # 
Instance details

Defined in LayoutDir

vswap :: LayoutDir -> (b, b) -> (b, b) Source #

colinear :: LayoutDir -> p -> p -> p Source #

orthogonal :: LayoutDir -> p -> p -> p Source #

serCompLF :: (F a1 f, Orientation) -> F e a1 -> F e f Source #

compLF :: (F a b, Orientation) -> F c d -> F (Either a c) (Either b d) Source #

listLF :: Eq a => Placer -> [(a, F b c)] -> F (a, b) (a, c) Source #

untaggedListLF :: Placer -> [F a b] -> F (Int, a) b Source #

nullLF :: F hi ho Source #

holeF :: F hi ho Source #

holeF' :: Size -> F hi ho Source #

lF :: Int -> LayoutDirection -> Placer -> F a b -> F a b Source #

data LayoutRequest Source #

Constructors

Layout 

Instances

Instances details
Show LayoutRequest Source # 
Instance details

Defined in LayoutRequest

data LayoutResponse Source #

Instances

Instances details
Show LayoutResponse Source # 
Instance details

Defined in LayoutRequest

newtype Placer Source #

Constructors

P Placer1 

Instances

Instances details
Show Placer Source # 
Instance details

Defined in LayoutRequest

newtype Spacer Source #

Constructors

S Spacer1 

Instances

Instances details
Show Spacer Source # 
Instance details

Defined in LayoutRequest

layoutF :: Layout -> F a b -> F a b Source #

nameF :: LName -> F a b -> F a b Source #

listNF :: (Eq a, Show a) => [(a, F b c)] -> F (a, b) (a, c) Source #

nameLayoutF :: NameLayout -> F a b -> F a b Source #

dynListLF :: Placer -> F (Int, DynFMsg a b) (Int, b) Source #

placerF :: Placer -> F a b -> F a b Source #

spacerF :: Spacer -> F a b -> F a b Source #

spacer1F :: Spacer -> F a b -> F a b Source #

hBoxF :: F a b -> F a b Source #

vBoxF :: F a b -> F a b Source #

revHBoxF :: F a b -> F a b Source #

revVBoxF :: F a b -> F a b Source #

matrixF :: Int -> F a b -> F a b Source #

tableF :: Int -> F a b -> F a b Source #

alignF :: Size -> Size -> Alignment -> Alignment -> F a b -> F a b Source #

noStretchF :: Bool -> Bool -> F a b -> F a b Source #

sepF :: Size -> F a b -> F a b Source #

marginF :: Distance -> F a b -> F a b Source #

mapLayout :: (Size -> Bool -> Bool -> (Int -> Size) -> (Int -> Size) -> [Point] -> Maybe (Point, Size, Alignment) -> t) -> LayoutRequest -> t Source #

dynSpacerF :: F c ho -> F (Either Spacer c) ho Source #

dynPlacerF :: F c ho -> F (Either Placer c) ho Source #

data Sizing Source #

Constructors

Static 
Growing 
Dynamic 

Instances

Instances details
Eq Sizing Source # 
Instance details

Defined in Sizing

Methods

(==) :: Sizing -> Sizing -> Bool #

(/=) :: Sizing -> Sizing -> Bool #

Read Sizing Source # 
Instance details

Defined in Sizing

Show Sizing Source # 
Instance details

Defined in Sizing

atLeastOne :: ([a], [a]) -> ([a], [a]) Source #

Low level

type Cont c a = (a -> c) -> c Source #

conts :: (a -> Cont c b) -> [a] -> Cont c [b] Source #

tryM :: Cont c (Maybe a) -> c -> Cont c a Source #

cmdContF :: FRequest -> (FResponse -> Maybe a) -> Cont (F b c) a Source #

cmdContK :: FRequest -> (FResponse -> Maybe a) -> Cont (K b c) a Source #

cmdContK' :: KCommand ho -> (KEvent hi -> Maybe a) -> Cont (K hi ho) a Source #

waitForSP :: (a -> Maybe t) -> (t -> SP a b) -> SP a b Source #

waitForK :: (KEvent hi -> Maybe a) -> Cont (K hi ho) a Source #

waitForF :: (a -> Maybe b) -> Cont (F a c) b Source #

waitForFu :: (KEvent hi -> Maybe ans) -> Cont (F hi ho) ans Source #

cmdContSP :: a -> (b -> Maybe c) -> Cont (SP b a) c Source #

tryGet :: Cont c (Maybe a) -> Cont c a -> Cont c a Source #

getLeftSP :: (t -> SP (Either t b1) b2) -> SP (Either t b1) b2 Source #

getRightSP :: (t -> SP (Either a1 t) b) -> SP (Either a1 t) b Source #

fContWrap :: Cont (FSP hi ho) a -> Cont (F hi ho) a Source #

kContWrap :: Cont (KSP hi ho) a -> Cont (K hi ho) a Source #

dropSP :: (t1 -> Maybe t2) -> (t2 -> SP t1 b) -> SP t1 b Source #

contMap :: StreamProcIO sp => (i -> (o -> sp i o) -> sp i o) -> sp i o Source #

kernelF :: K a b -> F a b Source #

toKernel :: [b1] -> [Message (Path, b1) b2] Source #

autumnize :: [a] -> [a] Source #

windowKF :: (Rect -> FRequest) -> Bool -> Bool -> [FRequest] -> Maybe Rect -> K a b -> F c d -> F (Either a c) (Either b d) Source #

xrequest :: FudgetIO f => XRequest -> (XResponse -> Maybe ans) -> (ans -> f b ho) -> f b ho Source #

xrequestF :: XRequest -> (XResponse -> Maybe a) -> Cont (F b c) a Source #

xrequestK :: XRequest -> (XResponse -> Maybe a) -> Cont (K b c) a Source #

type Cont c a = (a -> c) -> c Source #

xcommand :: FudgetIO f => XCommand -> f hi ho -> f hi ho Source #

xcommandK :: XCommand -> K i o -> K i o Source #

xcommandF :: XCommand -> F i o -> F i o Source #

xcommands :: FudgetIO f => [XCommand] -> f hi ho -> f hi ho Source #

xcommandsK :: [XCommand] -> K i o -> K i o Source #

xcommandsF :: [XCommand] -> F i o -> F i o Source #

select :: FudgetIO f => [Descriptor] -> f hi ho -> f hi ho Source #

sIOsucc :: FudgetIO f => SocketRequest -> f b ho -> f b ho Source #

sIOstr :: FudgetIO f => SocketRequest -> (String -> f b ho) -> f b ho Source #

sIOerr :: FudgetIO f => SocketRequest -> (IOError -> f b ho) -> (SocketResponse -> f b ho) -> f b ho Source #

sIO :: FudgetIO f => SocketRequest -> (SocketResponse -> f b ho) -> f b ho Source #

type Cont c a = (a -> c) -> c Source #

data Fudlogue Source #

Instances

Instances details
HasCache Fudlogue Source # 
Instance details

Defined in DFudIO

fudlogue :: F a b -> IO () Source #

class HasCache xxx where Source #

Minimal complete definition

setCache, getCacheMaybe

Instances

Instances details
HasCache Fudlogue Source # 
Instance details

Defined in DFudIO

class FudgetIO f where Source #

Methods

waitForMsg :: (KEvent hi -> Maybe ans) -> Cont (f hi ho) ans Source #

putMsg :: KCommand ho -> f hi ho -> f hi ho Source #

Instances

Instances details
FudgetIO K Source # 
Instance details

Defined in NullF

Methods

waitForMsg :: (KEvent hi -> Maybe ans) -> Cont (K hi ho) ans Source #

putMsg :: KCommand ho -> K hi ho -> K hi ho Source #

FudgetIO F Source # 
Instance details

Defined in NullF

Methods

waitForMsg :: (KEvent hi -> Maybe ans) -> Cont (F hi ho) ans Source #

putMsg :: KCommand ho -> F hi ho -> F hi ho Source #

putMsgs :: (Foldable t, FudgetIO f) => t (KCommand ho) -> f hi ho -> f hi ho Source #

putHigh :: FudgetIO f => ho -> f hi ho -> f hi ho Source #

putLow :: FudgetIO f => FRequest -> f hi ho -> f hi ho Source #

putLows :: (Foldable t, FudgetIO f) => t FRequest -> f hi ho -> f hi ho Source #

getHigh :: FudgetIO f => (ans -> f ans ho) -> f ans ho Source #

getLow :: FudgetIO f => (FResponse -> f b ho) -> f b ho Source #

cmdContMsg :: FudgetIO f => KCommand ho -> (KEvent hi -> Maybe ans) -> (ans -> f hi ho) -> f hi ho Source #

cmdContLow :: FudgetIO f => FRequest -> (FResponse -> Maybe ans) -> (ans -> f b ho) -> f b ho Source #

Types

data Direction Source #

Constructors

L 
R 
Dno Int 

Instances

Instances details
Eq Direction Source # 
Instance details

Defined in Direction

Ord Direction Source # 
Instance details

Defined in Direction

Read Direction Source # 
Instance details

Defined in Direction

Show Direction Source # 
Instance details

Defined in Direction

move :: Move a => Point -> a -> a Source #

newtype K hi ho Source #

Constructors

K (KSP hi ho) 

Instances

Instances details
StreamProcIO K Source # 
Instance details

Defined in NullF

Methods

put :: o -> K i o -> K i o Source #

get :: (i -> K i o) -> K i o Source #

end :: K i o Source #

FudgetIO K Source # 
Instance details

Defined in NullF

Methods

waitForMsg :: (KEvent hi -> Maybe ans) -> Cont (K hi ho) ans Source #

putMsg :: KCommand ho -> K hi ho -> K hi ho Source #

newtype F hi ho Source #

Constructors

F (FSP hi ho) 

Instances

Instances details
StreamProcIO F Source # 
Instance details

Defined in NullF

Methods

put :: o -> F i o -> F i o Source #

get :: (i -> F i o) -> F i o Source #

end :: F i o Source #

FudgetIO F Source # 
Instance details

Defined in NullF

Methods

waitForMsg :: (KEvent hi -> Maybe ans) -> Cont (F hi ho) ans Source #

putMsg :: KCommand ho -> F hi ho -> F hi ho Source #

type KSP hi ho = SP (KEvent hi) (KCommand ho) Source #

type FSP hi ho = SP (FEvent hi) (FCommand ho) Source #

type Fudget a b = F a b Source #

type Fa a b c d = SP (Message a c) (Message b d) Source #

kk :: KSP hi ho -> K hi ho Source #

ff :: FSP hi ho -> F hi ho Source #

unK :: K hi ho -> KSP hi ho Source #

unF :: F hi ho -> FSP hi ho Source #

data SP a b Source #

Instances

Instances details
StreamProcIO SP Source # 
Instance details

Defined in StreamProcIO

Methods

put :: o -> SP i o -> SP i o Source #

get :: (i -> SP i o) -> SP i o Source #

end :: SP i o Source #

Show b => Show (SP a b) Source # 
Instance details

Defined in SP

Methods

showsPrec :: Int -> SP a b -> ShowS #

show :: SP a b -> String #

showList :: [SP a b] -> ShowS #

data FRequest Source #

Instances

Instances details
Show FRequest Source # 
Instance details

Defined in FRequest

data FResponse Source #

Instances

Instances details
Show FResponse Source # 
Instance details

Defined in FRequest

data Message a b Source #

Constructors

Low a 
High b 

Instances

Instances details
Functor (Message a) Source # 
Instance details

Defined in Message

Methods

fmap :: (a0 -> b) -> Message a a0 -> Message a b #

(<$) :: a0 -> Message a b -> Message a a0 #

(Eq a, Eq b) => Eq (Message a b) Source # 
Instance details

Defined in Message

Methods

(==) :: Message a b -> Message a b -> Bool #

(/=) :: Message a b -> Message a b -> Bool #

(Ord a, Ord b) => Ord (Message a b) Source # 
Instance details

Defined in Message

Methods

compare :: Message a b -> Message a b -> Ordering #

(<) :: Message a b -> Message a b -> Bool #

(<=) :: Message a b -> Message a b -> Bool #

(>) :: Message a b -> Message a b -> Bool #

(>=) :: Message a b -> Message a b -> Bool #

max :: Message a b -> Message a b -> Message a b #

min :: Message a b -> Message a b -> Message a b #

(Show a, Show b) => Show (Message a b) Source # 
Instance details

Defined in Message

Methods

showsPrec :: Int -> Message a b -> ShowS #

show :: Message a b -> String #

showList :: [Message a b] -> ShowS #

data Direction Source #

Instances

Instances details
Eq Direction Source # 
Instance details

Defined in Direction

Ord Direction Source # 
Instance details

Defined in Direction

Read Direction Source # 
Instance details

Defined in Direction

Show Direction Source # 
Instance details

Defined in Direction

data Message a b Source #

Constructors

Low a 
High b 

Instances

Instances details
Functor (Message a) Source # 
Instance details

Defined in Message

Methods

fmap :: (a0 -> b) -> Message a a0 -> Message a b #

(<$) :: a0 -> Message a b -> Message a a0 #

(Eq a, Eq b) => Eq (Message a b) Source # 
Instance details

Defined in Message

Methods

(==) :: Message a b -> Message a b -> Bool #

(/=) :: Message a b -> Message a b -> Bool #

(Ord a, Ord b) => Ord (Message a b) Source # 
Instance details

Defined in Message

Methods

compare :: Message a b -> Message a b -> Ordering #

(<) :: Message a b -> Message a b -> Bool #

(<=) :: Message a b -> Message a b -> Bool #

(>) :: Message a b -> Message a b -> Bool #

(>=) :: Message a b -> Message a b -> Bool #

max :: Message a b -> Message a b -> Message a b #

min :: Message a b -> Message a b -> Message a b #

(Show a, Show b) => Show (Message a b) Source # 
Instance details

Defined in Message

Methods

showsPrec :: Int -> Message a b -> ShowS #

show :: Message a b -> String #

showList :: [Message a b] -> ShowS #

stripHigh :: Message a1 a2 -> Maybe a2 Source #

mapMessage :: (t1 -> a) -> (t2 -> b) -> Message t1 t2 -> Message a b Source #

message :: (t1 -> p) -> (t2 -> p) -> Message t1 t2 -> p Source #

aLow :: (t -> a) -> Message t b -> Message a b Source #

aHigh :: (t -> b) -> Message a t -> Message a b Source #

pushMsg :: Functor f => Message (f a) (f b) -> f (Message a b) Source #

data PopupMsg a Source #

Constructors

Popup Point a 
Popdown 

Instances

Instances details
Eq a => Eq (PopupMsg a) Source # 
Instance details

Defined in Popupmsg

Methods

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

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

Ord a => Ord (PopupMsg a) Source # 
Instance details

Defined in Popupmsg

Methods

compare :: PopupMsg a -> PopupMsg a -> Ordering #

(<) :: PopupMsg a -> PopupMsg a -> Bool #

(<=) :: PopupMsg a -> PopupMsg a -> Bool #

(>) :: PopupMsg a -> PopupMsg a -> Bool #

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

max :: PopupMsg a -> PopupMsg a -> PopupMsg a #

min :: PopupMsg a -> PopupMsg a -> PopupMsg a #

data Click Source #

Button clicks

Constructors

Click 

Instances

Instances details
Eq Click Source # 
Instance details

Defined in InputMsg

Methods

(==) :: Click -> Click -> Bool #

(/=) :: Click -> Click -> Bool #

Ord Click Source # 
Instance details

Defined in InputMsg

Methods

compare :: Click -> Click -> Ordering #

(<) :: Click -> Click -> Bool #

(<=) :: Click -> Click -> Bool #

(>) :: Click -> Click -> Bool #

(>=) :: Click -> Click -> Bool #

max :: Click -> Click -> Click #

min :: Click -> Click -> Click #

Show Click Source # 
Instance details

Defined in InputMsg

Methods

showsPrec :: Int -> Click -> ShowS #

show :: Click -> String #

showList :: [Click] -> ShowS #

data ConfirmMsg Source #

Output from dialog popups with OK and Cancel buttons

Constructors

Confirm 
Cancel 

Instances

Instances details
Eq ConfirmMsg Source # 
Instance details

Defined in InputMsg

Ord ConfirmMsg Source # 
Instance details

Defined in InputMsg

Show ConfirmMsg Source # 
Instance details

Defined in InputMsg

data InputMsg a Source #

Constructors

InputChange a 
InputDone KeySym a 

Instances

Instances details
Functor InputMsg Source # 
Instance details

Defined in InputMsg

Methods

fmap :: (a -> b) -> InputMsg a -> InputMsg b #

(<$) :: a -> InputMsg b -> InputMsg a #

Eq a => Eq (InputMsg a) Source # 
Instance details

Defined in InputMsg

Methods

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

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

Ord a => Ord (InputMsg a) Source # 
Instance details

Defined in InputMsg

Methods

compare :: InputMsg a -> InputMsg a -> Ordering #

(<) :: InputMsg a -> InputMsg a -> Bool #

(<=) :: InputMsg a -> InputMsg a -> Bool #

(>) :: InputMsg a -> InputMsg a -> Bool #

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

max :: InputMsg a -> InputMsg a -> InputMsg a #

min :: InputMsg a -> InputMsg a -> InputMsg a #

Show a => Show (InputMsg a) Source # 
Instance details

Defined in InputMsg

Methods

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

show :: InputMsg a -> String #

showList :: [InputMsg a] -> ShowS #

tstInp :: (t -> p) -> InputMsg t -> p Source #

mapInp :: (t -> a) -> InputMsg t -> InputMsg a Source #

X types

data FResponse Source #

Instances

Instances details
Show FResponse Source # 
Instance details

Defined in FRequest

data FRequest Source #

Instances

Instances details
Show FRequest Source # 
Instance details

Defined in FRequest

data XCommand Source #

Instances

Instances details
Read XCommand Source # 
Instance details

Defined in Command

Show XCommand Source # 
Instance details

Defined in Command

data XEvent Source #

Instances

Instances details
Read XEvent Source # 
Instance details

Defined in Event

Show XEvent Source # 
Instance details

Defined in Event

data XRequest Source #

Instances

Instances details
Eq XRequest Source # 
Instance details

Defined in Command

Ord XRequest Source # 
Instance details

Defined in Command

Read XRequest Source # 
Instance details

Defined in Command

Show XRequest Source # 
Instance details

Defined in Command

data XResponse Source #

Instances

Instances details
Read XResponse Source # 
Instance details

Defined in Event

Show XResponse Source # 
Instance details

Defined in Event

data LayoutMessage Source #

Instances

Instances details
Show LayoutMessage Source # 
Instance details

Defined in LayoutRequest

data LayoutResponse Source #

Instances

Instances details
Show LayoutResponse Source # 
Instance details

Defined in LayoutRequest

data XRequest Source #

Instances

Instances details
Eq XRequest Source # 
Instance details

Defined in Command

Ord XRequest Source # 
Instance details

Defined in Command

Read XRequest Source # 
Instance details

Defined in Command

Show XRequest Source # 
Instance details

Defined in Command

data XCommand Source #

Instances

Instances details
Read XCommand Source # 
Instance details

Defined in Command

Show XCommand Source # 
Instance details

Defined in Command

data Drawable Source #

Instances

Instances details
Eq Drawable Source # 
Instance details

Defined in DrawTypes

Ord Drawable Source # 
Instance details

Defined in DrawTypes

Read Drawable Source # 
Instance details

Defined in DrawTypes

Show Drawable Source # 
Instance details

Defined in DrawTypes

data XEvent Source #

Instances

Instances details
Read XEvent Source # 
Instance details

Defined in Event

Show XEvent Source # 
Instance details

Defined in Event

data ClientData Source #

Constructors

Byte String 
Short [Int] 
Long [Int] 

data Visibility Source #

data Mode Source #

Instances

Instances details
Bounded Mode Source # 
Instance details

Defined in Event

Enum Mode Source # 
Instance details

Defined in Event

Methods

succ :: Mode -> Mode #

pred :: Mode -> Mode #

toEnum :: Int -> Mode #

fromEnum :: Mode -> Int #

enumFrom :: Mode -> [Mode] #

enumFromThen :: Mode -> Mode -> [Mode] #

enumFromTo :: Mode -> Mode -> [Mode] #

enumFromThenTo :: Mode -> Mode -> Mode -> [Mode] #

Eq Mode Source # 
Instance details

Defined in Event

Methods

(==) :: Mode -> Mode -> Bool #

(/=) :: Mode -> Mode -> Bool #

Ord Mode Source # 
Instance details

Defined in Event

Methods

compare :: Mode -> Mode -> Ordering #

(<) :: Mode -> Mode -> Bool #

(<=) :: Mode -> Mode -> Bool #

(>) :: Mode -> Mode -> Bool #

(>=) :: Mode -> Mode -> Bool #

max :: Mode -> Mode -> Mode #

min :: Mode -> Mode -> Mode #

Read Mode Source # 
Instance details

Defined in Event

Show Mode Source # 
Instance details

Defined in Event

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

data Detail Source #

Instances

Instances details
Bounded Detail Source # 
Instance details

Defined in Event

Enum Detail Source # 
Instance details

Defined in Event

Eq Detail Source # 
Instance details

Defined in Event

Methods

(==) :: Detail -> Detail -> Bool #

(/=) :: Detail -> Detail -> Bool #

Ord Detail Source # 
Instance details

Defined in Event

Read Detail Source # 
Instance details

Defined in Event

Show Detail Source # 
Instance details

Defined in Event

data Pressed Source #

Constructors

Pressed 
Released 
MultiClick Int 

Instances

Instances details
Eq Pressed Source # 
Instance details

Defined in Event

Methods

(==) :: Pressed -> Pressed -> Bool #

(/=) :: Pressed -> Pressed -> Bool #

Ord Pressed Source # 
Instance details

Defined in Event

Read Pressed Source # 
Instance details

Defined in Event

Show Pressed Source # 
Instance details

Defined in Event

newtype KeyCode Source #

Constructors

KeyCode Int 

Instances

Instances details
Eq KeyCode Source # 
Instance details

Defined in Event

Methods

(==) :: KeyCode -> KeyCode -> Bool #

(/=) :: KeyCode -> KeyCode -> Bool #

Ord KeyCode Source # 
Instance details

Defined in Event

Read KeyCode Source # 
Instance details

Defined in Event

Show KeyCode Source # 
Instance details

Defined in Event

data DLValue Source #

Instances

Instances details
Read DLValue Source # 
Instance details

Defined in DLValue

Show DLValue Source # 
Instance details

Defined in DLValue

newtype DLHandle Source #

Constructors

DL DL 

Instances

Instances details
Read DLHandle Source # 
Instance details

Defined in Sockets

Show DLHandle Source # 
Instance details

Defined in Sockets

data AEvent Source #

Instances

Instances details
Read AEvent Source # 
Instance details

Defined in Sockets

Show AEvent Source # 
Instance details

Defined in Sockets

newtype Timer Source #

Constructors

Ti Int 

Instances

Instances details
Eq Timer Source # 
Instance details

Defined in Sockets

Methods

(==) :: Timer -> Timer -> Bool #

(/=) :: Timer -> Timer -> Bool #

Ord Timer Source # 
Instance details

Defined in Sockets

Methods

compare :: Timer -> Timer -> Ordering #

(<) :: Timer -> Timer -> Bool #

(<=) :: Timer -> Timer -> Bool #

(>) :: Timer -> Timer -> Bool #

(>=) :: Timer -> Timer -> Bool #

max :: Timer -> Timer -> Timer #

min :: Timer -> Timer -> Timer #

Read Timer Source # 
Instance details

Defined in Sockets

Show Timer Source # 
Instance details

Defined in Sockets

Methods

showsPrec :: Int -> Timer -> ShowS #

show :: Timer -> String #

showList :: [Timer] -> ShowS #

newtype LSocket Source #

Constructors

LSo Int 

Instances

Instances details
Eq LSocket Source # 
Instance details

Defined in Sockets

Methods

(==) :: LSocket -> LSocket -> Bool #

(/=) :: LSocket -> LSocket -> Bool #

Ord LSocket Source # 
Instance details

Defined in Sockets

Read LSocket Source # 
Instance details

Defined in Sockets

Show LSocket Source # 
Instance details

Defined in Sockets

newtype Socket Source #

Constructors

So Int 

Instances

Instances details
Eq Socket Source # 
Instance details

Defined in Sockets

Methods

(==) :: Socket -> Socket -> Bool #

(/=) :: Socket -> Socket -> Bool #

Ord Socket Source # 
Instance details

Defined in Sockets

Read Socket Source # 
Instance details

Defined in Sockets

Show Socket Source # 
Instance details

Defined in Sockets

type Peer = Host Source #

type Port = Int Source #

data SwapAction Source #

data StackMode Source #

data GCAttributes a b Source #

Instances

Instances details
(Eq a, Eq b) => Eq (GCAttributes a b) Source # 
Instance details

Defined in Xtypes

Methods

(==) :: GCAttributes a b -> GCAttributes a b -> Bool #

(/=) :: GCAttributes a b -> GCAttributes a b -> Bool #

(Ord a, Ord b) => Ord (GCAttributes a b) Source # 
Instance details

Defined in Xtypes

(Read a, Read b) => Read (GCAttributes a b) Source # 
Instance details

Defined in Xtypes

(Show a, Show b) => Show (GCAttributes a b) Source # 
Instance details

Defined in Xtypes

data GCFillStyle Source #

Instances

Instances details
Bounded GCFillStyle Source # 
Instance details

Defined in Xtypes

Enum GCFillStyle Source # 
Instance details

Defined in Xtypes

Eq GCFillStyle Source # 
Instance details

Defined in Xtypes

Ord GCFillStyle Source # 
Instance details

Defined in Xtypes

Read GCFillStyle Source # 
Instance details

Defined in Xtypes

Show GCFillStyle Source # 
Instance details

Defined in Xtypes

data GCSubwindowMode Source #

Instances

Instances details
Bounded GCSubwindowMode Source # 
Instance details

Defined in Xtypes

Enum GCSubwindowMode Source # 
Instance details

Defined in Xtypes

Eq GCSubwindowMode Source # 
Instance details

Defined in Xtypes

Ord GCSubwindowMode Source # 
Instance details

Defined in Xtypes

Read GCSubwindowMode Source # 
Instance details

Defined in Xtypes

Show GCSubwindowMode Source # 
Instance details

Defined in Xtypes

data GCJoinStyle Source #

Constructors

JoinMiter 
JoinRound 
JoinBevel 

Instances

Instances details
Bounded GCJoinStyle Source # 
Instance details

Defined in Xtypes

Enum GCJoinStyle Source # 
Instance details

Defined in Xtypes

Eq GCJoinStyle Source # 
Instance details

Defined in Xtypes

Ord GCJoinStyle Source # 
Instance details

Defined in Xtypes

Read GCJoinStyle Source # 
Instance details

Defined in Xtypes

Show GCJoinStyle Source # 
Instance details

Defined in Xtypes

data GCCapStyle Source #

data GCLineStyle Source #

Instances

Instances details
Bounded GCLineStyle Source # 
Instance details

Defined in Xtypes

Enum GCLineStyle Source # 
Instance details

Defined in Xtypes

Eq GCLineStyle Source # 
Instance details

Defined in Xtypes

Ord GCLineStyle Source # 
Instance details

Defined in Xtypes

Read GCLineStyle Source # 
Instance details

Defined in Xtypes

Show GCLineStyle Source # 
Instance details

Defined in Xtypes

data GCFunction Source #

data GrabPointerResult Source #

Instances

Instances details
Bounded GrabPointerResult Source # 
Instance details

Defined in Xtypes

Enum GrabPointerResult Source # 
Instance details

Defined in Xtypes

Eq GrabPointerResult Source # 
Instance details

Defined in Xtypes

Ord GrabPointerResult Source # 
Instance details

Defined in Xtypes

Read GrabPointerResult Source # 
Instance details

Defined in Xtypes

Show GrabPointerResult Source # 
Instance details

Defined in Xtypes

data BackingStore Source #

Constructors

NotUseful 
WhenMapped 
Always 

Instances

Instances details
Bounded BackingStore Source # 
Instance details

Defined in Xtypes

Enum BackingStore Source # 
Instance details

Defined in Xtypes

Eq BackingStore Source # 
Instance details

Defined in Xtypes

Ord BackingStore Source # 
Instance details

Defined in Xtypes

Read BackingStore Source # 
Instance details

Defined in Xtypes

Show BackingStore Source # 
Instance details

Defined in Xtypes

data Selection Source #

Constructors

Selection Atom Atom Atom 

Instances

Instances details
Eq Selection Source # 
Instance details

Defined in Xtypes

Ord Selection Source # 
Instance details

Defined in Xtypes

Read Selection Source # 
Instance details

Defined in Xtypes

Show Selection Source # 
Instance details

Defined in Xtypes

data Color Source #

Constructors

Color 

Fields

Instances

Instances details
Eq Color Source # 
Instance details

Defined in Xtypes

Methods

(==) :: Color -> Color -> Bool #

(/=) :: Color -> Color -> Bool #

Ord Color Source # 
Instance details

Defined in Xtypes

Methods

compare :: Color -> Color -> Ordering #

(<) :: Color -> Color -> Bool #

(<=) :: Color -> Color -> Bool #

(>) :: Color -> Color -> Bool #

(>=) :: Color -> Color -> Bool #

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

Read Color Source # 
Instance details

Defined in Xtypes

Show Color Source # 
Instance details

Defined in Xtypes

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

data RGB Source #

Constructors

RGB Int Int Int 

Instances

Instances details
Eq RGB Source # 
Instance details

Defined in Xtypes

Methods

(==) :: RGB -> RGB -> Bool #

(/=) :: RGB -> RGB -> Bool #

Ord RGB Source # 
Instance details

Defined in Xtypes

Methods

compare :: RGB -> RGB -> Ordering #

(<) :: RGB -> RGB -> Bool #

(<=) :: RGB -> RGB -> Bool #

(>) :: RGB -> RGB -> Bool #

(>=) :: RGB -> RGB -> Bool #

max :: RGB -> RGB -> RGB #

min :: RGB -> RGB -> RGB #

Read RGB Source # 
Instance details

Defined in Xtypes

Show RGB Source # 
Instance details

Defined in Xtypes

Methods

showsPrec :: Int -> RGB -> ShowS #

show :: RGB -> String #

showList :: [RGB] -> ShowS #

Ix RGB Source # 
Instance details

Defined in Xtypes

Methods

range :: (RGB, RGB) -> [RGB] #

index :: (RGB, RGB) -> RGB -> Int #

unsafeIndex :: (RGB, RGB) -> RGB -> Int #

inRange :: (RGB, RGB) -> RGB -> Bool #

rangeSize :: (RGB, RGB) -> Int #

unsafeRangeSize :: (RGB, RGB) -> Int #

ColorGen RGB Source # 
Instance details

Defined in GCAttrs

Methods

tryConvColorK :: FudgetIO f => RGB -> Cont (f i o) (Maybe Pixel) Source #

convColorListK :: FudgetIO f => [RGB] -> Cont (f i o) (Maybe Pixel) Source #

newtype Pixel Source #

Constructors

Pixel Word 

Instances

Instances details
Eq Pixel Source # 
Instance details

Defined in Xtypes

Methods

(==) :: Pixel -> Pixel -> Bool #

(/=) :: Pixel -> Pixel -> Bool #

Ord Pixel Source # 
Instance details

Defined in Xtypes

Methods

compare :: Pixel -> Pixel -> Ordering #

(<) :: Pixel -> Pixel -> Bool #

(<=) :: Pixel -> Pixel -> Bool #

(>) :: Pixel -> Pixel -> Bool #

(>=) :: Pixel -> Pixel -> Bool #

max :: Pixel -> Pixel -> Pixel #

min :: Pixel -> Pixel -> Pixel #

Read Pixel Source # 
Instance details

Defined in Xtypes

Show Pixel Source # 
Instance details

Defined in Xtypes

Methods

showsPrec :: Int -> Pixel -> ShowS #

show :: Pixel -> String #

showList :: [Pixel] -> ShowS #

ColorGen Pixel Source # 
Instance details

Defined in GCAttrs

Methods

tryConvColorK :: FudgetIO f => Pixel -> Cont (f i o) (Maybe Pixel) Source #

convColorListK :: FudgetIO f => [Pixel] -> Cont (f i o) (Maybe Pixel) Source #

type Width = Int Source #

newtype Display Source #

Constructors

Display Int 

Instances

Instances details
Eq Display Source # 
Instance details

Defined in Xtypes

Methods

(==) :: Display -> Display -> Bool #

(/=) :: Display -> Display -> Bool #

Ord Display Source # 
Instance details

Defined in Xtypes

Read Display Source # 
Instance details

Defined in Xtypes

Show Display Source # 
Instance details

Defined in Xtypes

data EventMask Source #

data Gravity Source #

Instances

Instances details
Bounded Gravity Source # 
Instance details

Defined in AuxTypes

Enum Gravity Source # 
Instance details

Defined in AuxTypes

Eq Gravity Source # 
Instance details

Defined in AuxTypes

Methods

(==) :: Gravity -> Gravity -> Bool #

(/=) :: Gravity -> Gravity -> Bool #

Ord Gravity Source # 
Instance details

Defined in AuxTypes

Read Gravity Source # 
Instance details

Defined in AuxTypes

Show Gravity Source # 
Instance details

Defined in AuxTypes

data ShapeOperation Source #

Instances

Instances details
Bounded ShapeOperation Source # 
Instance details

Defined in AuxTypes

Enum ShapeOperation Source # 
Instance details

Defined in AuxTypes

Eq ShapeOperation Source # 
Instance details

Defined in AuxTypes

Ord ShapeOperation Source # 
Instance details

Defined in AuxTypes

Read ShapeOperation Source # 
Instance details

Defined in AuxTypes

Show ShapeOperation Source # 
Instance details

Defined in AuxTypes

data Ordering' Source #

data Modifiers Source #

data Button Source #

Constructors

AnyButton 
Button Int 

Instances

Instances details
Eq Button Source # 
Instance details

Defined in AuxTypes

Methods

(==) :: Button -> Button -> Bool #

(/=) :: Button -> Button -> Bool #

Ord Button Source # 
Instance details

Defined in AuxTypes

Read Button Source # 
Instance details

Defined in AuxTypes

Show Button Source # 
Instance details

Defined in AuxTypes

newtype XID Source #

Constructors

XID Int 

Instances

Instances details
Eq XID Source # 
Instance details

Defined in ResourceIds

Methods

(==) :: XID -> XID -> Bool #

(/=) :: XID -> XID -> Bool #

Ord XID Source # 
Instance details

Defined in ResourceIds

Methods

compare :: XID -> XID -> Ordering #

(<) :: XID -> XID -> Bool #

(<=) :: XID -> XID -> Bool #

(>) :: XID -> XID -> Bool #

(>=) :: XID -> XID -> Bool #

max :: XID -> XID -> XID #

min :: XID -> XID -> XID #

Read XID Source # 
Instance details

Defined in ResourceIds

Show XID Source # 
Instance details

Defined in ResourceIds

Methods

showsPrec :: Int -> XID -> ShowS #

show :: XID -> String #

showList :: [XID] -> ShowS #

Storable XID Source # 
Instance details

Defined in EncodeEvent

Methods

sizeOf :: XID -> Int #

alignment :: XID -> Int #

peekElemOff :: Ptr XID -> Int -> IO XID #

pokeElemOff :: Ptr XID -> Int -> XID -> IO () #

peekByteOff :: Ptr b -> Int -> IO XID #

pokeByteOff :: Ptr b -> Int -> XID -> IO () #

peek :: Ptr XID -> IO XID #

poke :: Ptr XID -> XID -> IO () #

newtype WindowId Source #

Constructors

WindowId XID 

Instances

Instances details
Eq WindowId Source # 
Instance details

Defined in ResourceIds

Ord WindowId Source # 
Instance details

Defined in ResourceIds

Read WindowId Source # 
Instance details

Defined in ResourceIds

Show WindowId Source # 
Instance details

Defined in ResourceIds

newtype PixmapId Source #

Constructors

PixmapId XID 

Instances

Instances details
Eq PixmapId Source # 
Instance details

Defined in ResourceIds

Ord PixmapId Source # 
Instance details

Defined in ResourceIds

Read PixmapId Source # 
Instance details

Defined in ResourceIds

Show PixmapId Source # 
Instance details

Defined in ResourceIds

newtype FontId Source #

Constructors

FontId XID 

Instances

Instances details
Eq FontId Source # 
Instance details

Defined in ResourceIds

Methods

(==) :: FontId -> FontId -> Bool #

(/=) :: FontId -> FontId -> Bool #

Ord FontId Source # 
Instance details

Defined in ResourceIds

Read FontId Source # 
Instance details

Defined in ResourceIds

Show FontId Source # 
Instance details

Defined in ResourceIds

newtype GCId Source #

Constructors

GCId Int 

Instances

Instances details
Eq GCId Source # 
Instance details

Defined in ResourceIds

Methods

(==) :: GCId -> GCId -> Bool #

(/=) :: GCId -> GCId -> Bool #

Ord GCId Source # 
Instance details

Defined in ResourceIds

Methods

compare :: GCId -> GCId -> Ordering #

(<) :: GCId -> GCId -> Bool #

(<=) :: GCId -> GCId -> Bool #

(>) :: GCId -> GCId -> Bool #

(>=) :: GCId -> GCId -> Bool #

max :: GCId -> GCId -> GCId #

min :: GCId -> GCId -> GCId #

Read GCId Source # 
Instance details

Defined in ResourceIds

Show GCId Source # 
Instance details

Defined in ResourceIds

Methods

showsPrec :: Int -> GCId -> ShowS #

show :: GCId -> String #

showList :: [GCId] -> ShowS #

newtype CursorId Source #

Constructors

CursorId XID 

Instances

Instances details
Eq CursorId Source # 
Instance details

Defined in ResourceIds

Ord CursorId Source # 
Instance details

Defined in ResourceIds

Read CursorId Source # 
Instance details

Defined in ResourceIds

Show CursorId Source # 
Instance details

Defined in ResourceIds

newtype Atom Source #

Constructors

Atom Int 

Instances

Instances details
Eq Atom Source # 
Instance details

Defined in ResourceIds

Methods

(==) :: Atom -> Atom -> Bool #

(/=) :: Atom -> Atom -> Bool #

Ord Atom Source # 
Instance details

Defined in ResourceIds

Methods

compare :: Atom -> Atom -> Ordering #

(<) :: Atom -> Atom -> Bool #

(<=) :: Atom -> Atom -> Bool #

(>) :: Atom -> Atom -> Bool #

(>=) :: Atom -> Atom -> Bool #

max :: Atom -> Atom -> Atom #

min :: Atom -> Atom -> Atom #

Read Atom Source # 
Instance details

Defined in ResourceIds

Show Atom Source # 
Instance details

Defined in ResourceIds

Methods

showsPrec :: Int -> Atom -> ShowS #

show :: Atom -> String #

showList :: [Atom] -> ShowS #

type Time = Int Source #

type Depth = Int Source #

newtype VisualID Source #

Constructors

VisualID Int 

Instances

Instances details
Eq VisualID Source # 
Instance details

Defined in Visual

Read VisualID Source # 
Instance details

Defined in Visual

Show VisualID Source # 
Instance details

Defined in Visual

data Visual Source #

Instances

Instances details
Read Visual Source # 
Instance details

Defined in Visual

Show Visual Source # 
Instance details

Defined in Visual

data DrawCommand Source #

data Drawable Source #

Instances

Instances details
Eq Drawable Source # 
Instance details

Defined in DrawTypes

Ord Drawable Source # 
Instance details

Defined in DrawTypes

Read Drawable Source # 
Instance details

Defined in DrawTypes

Show Drawable Source # 
Instance details

Defined in DrawTypes

data CoordMode Source #

data Shape Source #

Constructors

Complex 
Nonconvex 
Convex 

Instances

Instances details
Bounded Shape Source # 
Instance details

Defined in DrawTypes

Enum Shape Source # 
Instance details

Defined in DrawTypes

Eq Shape Source # 
Instance details

Defined in DrawTypes

Methods

(==) :: Shape -> Shape -> Bool #

(/=) :: Shape -> Shape -> Bool #

Ord Shape Source # 
Instance details

Defined in DrawTypes

Methods

compare :: Shape -> Shape -> Ordering #

(<) :: Shape -> Shape -> Bool #

(<=) :: Shape -> Shape -> Bool #

(>) :: Shape -> Shape -> Bool #

(>=) :: Shape -> Shape -> Bool #

max :: Shape -> Shape -> Shape #

min :: Shape -> Shape -> Shape #

Read Shape Source # 
Instance details

Defined in DrawTypes

Show Shape Source # 
Instance details

Defined in DrawTypes

Methods

showsPrec :: Int -> Shape -> ShowS #

show :: Shape -> String #

showList :: [Shape] -> ShowS #

pmDrawImageStringPS :: PixmapId -> GCId -> Point -> PackedString -> FRequest Source #

pmDrawStringPS :: PixmapId -> GCId -> Point -> PackedString -> FRequest Source #

wDrawImageStringPS :: GCId -> Point -> PackedString -> FRequest Source #

wDrawStringPS :: GCId -> Point -> PackedString -> FRequest Source #

Utilities

metaKey :: Modifiers Source #

This should be modifier corresponding to Meta_L & Meta_R (see xmodmap). It is usually Mod1, but in XQuartz it appears to be Mod2 instead...

options :: [([Char], [Char])] Source #

args :: [[Char]] Source #

argKey :: [Char] -> [Char] -> [Char] Source #

argReadKey :: (Read p, Show p) => [Char] -> p -> p Source #

argKeyList :: [Char] -> [[Char]] -> [[Char]] Source #

data AFilePath Source #

Instances

Instances details
Eq AFilePath Source # 
Instance details

Defined in FilePaths

Ord AFilePath Source # 
Instance details

Defined in FilePaths

class Move a where Source #

Methods

move :: Point -> a -> a Source #

Instances

Instances details
Move Rect Source # 
Instance details

Defined in Geometry

Methods

move :: Point -> Rect -> Rect Source #

Move Line Source # 
Instance details

Defined in Geometry

Methods

move :: Point -> Line -> Line Source #

Move Point Source # 
Instance details

Defined in Geometry

Methods

move :: Point -> Point -> Point Source #

Move DrawCommand Source # 
Instance details

Defined in Drawcmd

Move a => Move [a] Source # 
Instance details

Defined in Geometry

Methods

move :: Point -> [a] -> [a] Source #

Move a => Move (Maybe a) Source # 
Instance details

Defined in Geometry

Methods

move :: Point -> Maybe a -> Maybe a Source #

fmove :: (Functor f, Move b) => Point -> f b -> f b Source #

data Point Source #

Constructors

Point 

Fields

Instances

Instances details
Eq Point Source # 
Instance details

Defined in Geometry

Methods

(==) :: Point -> Point -> Bool #

(/=) :: Point -> Point -> Bool #

Num Point Source # 
Instance details

Defined in Geometry

Ord Point Source # 
Instance details

Defined in Geometry

Methods

compare :: Point -> Point -> Ordering #

(<) :: Point -> Point -> Bool #

(<=) :: Point -> Point -> Bool #

(>) :: Point -> Point -> Bool #

(>=) :: Point -> Point -> Bool #

max :: Point -> Point -> Point #

min :: Point -> Point -> Point #

Read Point Source # 
Instance details

Defined in Geometry

Show Point Source # 
Instance details

Defined in Geometry

Methods

showsPrec :: Int -> Point -> ShowS #

show :: Point -> String #

showList :: [Point] -> ShowS #

Ix Point Source # 
Instance details

Defined in Geometry

Move Point Source # 
Instance details

Defined in Geometry

Methods

move :: Point -> Point -> Point Source #

data Line Source #

Constructors

Line Point Point 

Instances

Instances details
Eq Line Source # 
Instance details

Defined in Geometry

Methods

(==) :: Line -> Line -> Bool #

(/=) :: Line -> Line -> Bool #

Ord Line Source # 
Instance details

Defined in Geometry

Methods

compare :: Line -> Line -> Ordering #

(<) :: Line -> Line -> Bool #

(<=) :: Line -> Line -> Bool #

(>) :: Line -> Line -> Bool #

(>=) :: Line -> Line -> Bool #

max :: Line -> Line -> Line #

min :: Line -> Line -> Line #

Read Line Source # 
Instance details

Defined in Geometry

Show Line Source # 
Instance details

Defined in Geometry

Methods

showsPrec :: Int -> Line -> ShowS #

show :: Line -> String #

showList :: [Line] -> ShowS #

Move Line Source # 
Instance details

Defined in Geometry

Methods

move :: Point -> Line -> Line Source #

data Rect Source #

Constructors

Rect 

Fields

Instances

Instances details
Eq Rect Source # 
Instance details

Defined in Geometry

Methods

(==) :: Rect -> Rect -> Bool #

(/=) :: Rect -> Rect -> Bool #

Ord Rect Source # 
Instance details

Defined in Geometry

Methods

compare :: Rect -> Rect -> Ordering #

(<) :: Rect -> Rect -> Bool #

(<=) :: Rect -> Rect -> Bool #

(>) :: Rect -> Rect -> Bool #

(>=) :: Rect -> Rect -> Bool #

max :: Rect -> Rect -> Rect #

min :: Rect -> Rect -> Rect #

Read Rect Source # 
Instance details

Defined in Geometry

Show Rect Source # 
Instance details

Defined in Geometry

Methods

showsPrec :: Int -> Rect -> ShowS #

show :: Rect -> String #

showList :: [Rect] -> ShowS #

Move Rect Source # 
Instance details

Defined in Geometry

Methods

move :: Point -> Rect -> Rect Source #

pP :: Int -> Int -> Point Source #

lL :: Int -> Int -> Int -> Int -> Line Source #

rR :: Int -> Int -> Int -> Int -> Rect Source #

scale :: (RealFrac a1, Integral b, Integral a2) => a1 -> a2 -> b Source #

confine :: Rect -> Rect -> Rect Source #

confine outer inner: moves an shrinks inner to fit within outer

rmax :: Rect -> Rect -> Rect Source #

rmax gives an enclosing rect

mapLow :: (t -> [a]) -> SP (Message t b) (Message a b) Source #

mapHigh :: (t -> [b]) -> SP (Message a t) (Message a b) Source #

mapstateLow :: (t1 -> t2 -> (t1, [a])) -> t1 -> SP (Message t2 b) (Message a b) Source #

mapstateHigh :: (t1 -> t2 -> (t1, [b])) -> t1 -> SP (Message a t2) (Message a b) Source #

type Cont c a = (a -> c) -> c Source #

plookup :: Foldable t => (a -> Bool) -> t (a, b) -> Maybe b Source #

stripRight :: Either a1 a2 -> Maybe a2 Source #

filterLeft :: [Either b1 b2] -> [b1] Source #

filterRight :: [Either a b] -> [b] Source #

mapEither :: (t1 -> a) -> (t2 -> b) -> Either t1 t2 -> Either a b Source #

splitEitherList :: [Either a1 a2] -> ([a1], [a2]) Source #

fromLeft :: Either a b -> a Source #

fromRight :: Either a b -> b Source #

rmBS :: [Char] -> [Char] Source #

wrapLine :: Int -> [a] -> [[a]] Source #

aboth :: (t -> b) -> (t, t) -> (b, b) Source #

mapPair :: (t1 -> a, t2 -> b) -> (t1, t2) -> (a, b) Source #

pairwith :: (t -> b) -> t -> (t, b) Source #

swap :: (b, a) -> (a, b) Source #

pair :: a -> b -> (a, b) Source #

setFst :: (a1, b) -> a2 -> (a2, b) Source #

setSnd :: (a, b1) -> b2 -> (a, b2) Source #

oo :: (t1 -> t2) -> (t3 -> t4 -> t1) -> t3 -> t4 -> t2 Source #

anth :: Int -> (a -> a) -> [a] -> [a] Source #

Apply a function to the nth element of a list

number :: Int -> [a] -> [(Int, a)] Source #

loop :: (t -> t) -> t Source #

ifC :: (a -> a) -> Bool -> a -> a infixl 1 Source #

thenC :: Bool -> (a -> a) -> a -> a infixr 1 Source #

gmap :: Foldable t1 => (t2 -> [a] -> [a]) -> (t3 -> t2) -> t1 t3 -> [a] Source #

unionmap :: (Foldable t1, Eq a) => (t2 -> [a]) -> t1 t2 -> [a] Source #

remove :: Eq t => t -> [t] -> [t] Source #

Remove the first occurence

replace :: Eq a => (a, b) -> [(a, b)] -> [(a, b)] Source #

Replace the first occurence

unconcat :: [Int] -> [a] -> [[a]] Source #

lunconcat :: [[a1]] -> [a2] -> [[a2]] Source #

lunconcat xss ys = unconcat (map length xss) ys

lhead :: [a1] -> [a2] -> [a2] Source #

lhead xs ys = take (length xs) ys, but the rhs is stricter

ltail :: [a1] -> [a2] -> [a2] Source #

ltail xs ys = drop (length xs) ys, but the rhs is stricter

lsplit :: [a1] -> [a2] -> ([a2], [a2]) Source #

lsplit xs ys = (lhead xs ys,ltail xs ys), but without the space leak, -fpbu

part :: (a -> Bool) -> [a] -> ([a], [a]) Source #

JSP 920928

issubset :: (Foldable t1, Foldable t2, Eq a) => t1 a -> t2 a -> Bool Source #

mapList :: (a -> b) -> [a] -> [b] Source #

To avoid problems caused by poor type inference for constructor classes in Haskell 1.3:

segments :: (a -> Bool) -> [a] -> [[a]] Source #

chopList (breakAt c) == segments (/=c)

Stream processors

prepostMapSP :: (t1 -> a) -> (t2 -> b) -> SP a t2 -> SP t1 b Source #

postMapSP :: (t -> b) -> SP a t -> SP a b Source #

preMapSP :: SP a b -> (t -> a) -> SP t b Source #

idRightSP :: SP a1 a2 -> SP (Either a1 b) (Either a2 b) Source #

idLeftSP :: SP a1 b -> SP (Either a2 a1) (Either a2 b) Source #

idHighSP :: SP a1 a2 -> SP (Message a1 b) (Message a2 b) Source #

idLowSP :: SP a1 b -> SP (Message a2 a1) (Message a2 b) Source #

compMsgSP :: SP a1 a2 -> SP a3 b -> SP (Message a1 a3) (Message a2 b) Source #

compSP :: SP a1 a2 -> SP a3 b -> SP (Either a1 a3) (Either a2 b) Source #

compEitherSP :: SP a1 a2 -> SP a3 b -> SP (Either a1 a3) (Either a2 b) Source #

serCompSP :: SP a1 b -> SP a2 a1 -> SP a2 b Source #

data DynMsg a b Source #

Constructors

DynCreate b 
DynDestroy 
DynMsg a 

Instances

Instances details
(Eq b, Eq a) => Eq (DynMsg a b) Source # 
Instance details

Defined in Dynforkmerge

Methods

(==) :: DynMsg a b -> DynMsg a b -> Bool #

(/=) :: DynMsg a b -> DynMsg a b -> Bool #

(Ord b, Ord a) => Ord (DynMsg a b) Source # 
Instance details

Defined in Dynforkmerge

Methods

compare :: DynMsg a b -> DynMsg a b -> Ordering #

(<) :: DynMsg a b -> DynMsg a b -> Bool #

(<=) :: DynMsg a b -> DynMsg a b -> Bool #

(>) :: DynMsg a b -> DynMsg a b -> Bool #

(>=) :: DynMsg a b -> DynMsg a b -> Bool #

max :: DynMsg a b -> DynMsg a b -> DynMsg a b #

min :: DynMsg a b -> DynMsg a b -> DynMsg a b #

type DynSPMsg a b = DynMsg a (SP a b) Source #

dynforkmerge :: Eq a => SP (a, DynSPMsg b c) (a, c) Source #

loopLeftSP :: SP (Either a1 a2) (Either a1 b) -> SP a2 b Source #

loopSP :: SP a a -> SP a a Source #

loopOnlySP :: SP a a -> SP a b Source #

loopThroughRightSP :: SP (Either a1 a2) (Either a3 b) -> SP a3 a1 -> SP a2 b Source #

seqSP :: SP a b -> SP a b -> SP a b Source #

parSP :: SP a b -> SP a b -> SP a b Source #

data SP a b Source #

Instances

Instances details
StreamProcIO SP Source # 
Instance details

Defined in StreamProcIO

Methods

put :: o -> SP i o -> SP i o Source #

get :: (i -> SP i o) -> SP i o Source #

end :: SP i o Source #

Show b => Show (SP a b) Source # 
Instance details

Defined in SP

Methods

showsPrec :: Int -> SP a b -> ShowS #

show :: SP a b -> String #

showList :: [SP a b] -> ShowS #

type SPm i o ans = Mk (SP i o) ans Source #

putsSPm :: [o] -> SPm i o () Source #

putSPm :: o -> SPm i o () Source #

getSPm :: SPm i o i Source #

nullSPm :: SPm i o () Source #

monadSP :: SPm i o () -> SP i o Source #

toSPm :: SP i o -> SPm i o () Source #

type SPms i o s ans = Ms (SP i o) s ans Source #

putsSPms :: [o] -> SPms i o s () Source #

putSPms :: o -> SPms i o s () Source #

getSPms :: SPms i o s i Source #

nullSPms :: SPms i o s () Source #

loadSPms :: SPms i o s s Source #

storeSPms :: s -> SPms i o s () Source #

stateMonadSP :: s -> SPms i o s ans -> (ans -> SP i o) -> SP i o Source #

interpSP :: (t1 -> t2 -> t2) -> ((a -> t2) -> t2) -> t2 -> SP a t1 -> t2 Source #

nullSP :: SP a b Source #

putsSP :: [b] -> SP a b -> SP a b Source #

putSP :: b -> SP a b -> SP a b Source #

appendStartSP :: [b] -> SP a b -> SP a b Source #

stepSP :: [b] -> Cont (SP a b) a Source #

getSP :: Cont (SP a b) a Source #

walkSP :: SP a1 a2 -> a1 -> ([a2], SP a1 a2) Source #

pullSP :: SP a1 a2 -> ([a2], SP a1 a2) Source #

runSP :: SP a1 a2 -> [a1] -> [a2] Source #

feedSP :: a -> [a] -> SP a b -> SP a b Source #

startupSP :: [a] -> SP a b -> SP a b Source #

delaySP :: SP a b -> SP a b Source #

mapSP :: (t -> b) -> SP t b Source #

idSP :: SP b b Source #

concatMapSP :: (t -> [b]) -> SP t b Source #

concmapSP :: (t -> [b]) -> SP t b Source #

concatMapAccumlSP :: (t -> a -> (t, [b])) -> t -> SP a b Source #

mapstateSP :: (t -> a -> (t, [b])) -> t -> SP a b Source #

mapAccumlSP :: (t -> a -> (t, b)) -> t -> SP a b Source #

concatSP :: SP [b] b Source #

concSP :: SP [b] b Source #

zipSP :: [a] -> SP b (a, b) Source #

filterSP :: (b -> Bool) -> SP b b Source #

splitAtElemSP :: (a -> Bool) -> Cont (SP a b) [a] Source #

chopSP :: ((b -> SP a b) -> SP a b) -> SP a b Source #

type Cont c a = (a -> c) -> c Source #

mapFilterSP :: (t -> Maybe b) -> SP t b Source #

filterLeftSP :: SP (Either b1 b2) b1 Source #

splitSP :: SP (a, b) (Either a b) Source #

idempotSP :: Eq a => SP a a Source #

class StreamProcIO sp where Source #

Methods

put :: o -> sp i o -> sp i o Source #

get :: (i -> sp i o) -> sp i o Source #

end :: sp i o Source #

Instances

Instances details
StreamProcIO SP Source # 
Instance details

Defined in StreamProcIO

Methods

put :: o -> SP i o -> SP i o Source #

get :: (i -> SP i o) -> SP i o Source #

end :: SP i o Source #

StreamProcIO K Source # 
Instance details

Defined in NullF

Methods

put :: o -> K i o -> K i o Source #

get :: (i -> K i o) -> K i o Source #

end :: K i o Source #

StreamProcIO F Source # 
Instance details

Defined in NullF

Methods

put :: o -> F i o -> F i o Source #

get :: (i -> F i o) -> F i o Source #

end :: F i o Source #

puts :: (Foldable t, StreamProcIO sp) => t o -> sp i o -> sp i o Source #

inputListSP :: Eq a => [a] -> SP (a, InputMsg b) (InputMsg [(a, b)]) Source #

IO

hIOSucc :: FudgetIO f => Request -> f b ho -> f b ho Source #

hIOerr :: FudgetIO f => Request -> (IOError -> f b ho) -> (Response -> f b ho) -> f b ho Source #

haskellIO :: FudgetIO f => Request -> (Response -> f b ho) -> f b ho Source #

hIO :: FudgetIO f => Request -> (Response -> f b ho) -> f b ho Source #

haskellIOF :: Request -> (Response -> F a b) -> F a b Source #

hIOerrF :: Request -> (IOError -> F a b) -> (Response -> F a b) -> F a b Source #

hIOF :: Request -> (Response -> F a b) -> F a b Source #

hIOSuccF :: Request -> F a b -> F a b Source #

echoK :: FudgetIO f => [Char] -> f b ho -> f b ho Source #

echoStderrK :: FudgetIO f => [Char] -> f b ho -> f b ho Source #

appendChanK :: FudgetIO f => String -> String -> f b ho -> f b ho Source #

appendStdoutK :: FudgetIO f => String -> f b ho -> f b ho Source #

appendStderrK :: FudgetIO f => String -> f b ho -> f b ho Source #

ioF :: K a b -> F a b Source #

openSocketF :: FudgetIO f => Host -> Port -> (Socket -> f b ho) -> f b ho Source #

openSocketErrF :: FudgetIO f => Host -> Port -> (IOError -> f b ho) -> (Socket -> f b ho) -> f b ho Source #

openLSocketF :: FudgetIO f => Port -> (LSocket -> f b ho) -> f b ho Source #

openLSocketErrF :: FudgetIO f => Port -> (IOError -> f b ho) -> (LSocket -> f b ho) -> f b ho Source #

openFileAsSocketF :: FudgetIO f => String -> String -> (Socket -> f b ho) -> f b ho Source #

openFileAsSocketErrF :: FudgetIO f => String -> String -> (IOError -> f b ho) -> (Socket -> f b ho) -> f b ho Source #

closerF :: Socket -> F ans ho Source #

data Tick Source #

Constructors

Tick 

Instances

Instances details
Eq Tick Source # 
Instance details

Defined in TimerF

Methods

(==) :: Tick -> Tick -> Bool #

(/=) :: Tick -> Tick -> Bool #

Show Tick Source # 
Instance details

Defined in TimerF

Methods

showsPrec :: Int -> Tick -> ShowS #

show :: Tick -> String #

showList :: [Tick] -> ShowS #

writeFileF' :: (a -> t -> Request) -> F (a, t) (a, Either IOError ()) Source #

appStorageF :: (Read a, Show a) => String -> a -> F a a Source #

readM :: Read a => String -> Maybe a Source #

getTime :: FudgetIO f => (ClockTime -> f b ho) -> f b ho Source #

getLocalTime :: FudgetIO f => (CalendarTime -> f b ho) -> f b ho Source #

getCurrentTime :: FudgetIO f => (UTCTime -> f b ho) -> f b ho Source #

getZonedTime :: FudgetIO f => (ZonedTime -> f b ho) -> f b ho Source #

getModificationTime :: FudgetIO f => FilePath -> (IOError -> f b ho) -> (ClockTime -> f b ho) -> f b ho Source #

Default parameters

class HasInitText xxx where Source #

Minimal complete definition

setInitText, getInitTextMaybe

Instances

Instances details
HasInitText TextF Source # 
Instance details

Defined in TextF

class HasInitDisp xxx where Source #

Minimal complete definition

setInitDisp, getInitDispMaybe

Methods

setInitDisp :: a -> Customiser (xxx a) Source #

getInitDispMaybe :: xxx a -> Maybe a Source #

getInitDisp :: xxx a -> a Source #

Instances

Instances details
HasInitDisp GraphicsF Source # 
Instance details

Defined in GraphicsF

HasInitDisp DisplayF Source # 
Instance details

Defined in DDisplayF

class HasInitSize xxx where Source #

Minimal complete definition

setInitSize, getInitSizeMaybe

Methods

setInitSize :: a -> Customiser (xxx a) Source #

getInitSizeMaybe :: xxx a -> Maybe a Source #

getInitSize :: xxx a -> a Source #

Instances

Instances details
HasInitSize GraphicsF Source # 
Instance details

Defined in GraphicsF

HasInitSize DisplayF Source # 
Instance details

Defined in DDisplayF

class HasMargin xxx where Source #

Minimal complete definition

setMargin, getMarginMaybe

Instances

Instances details
HasMargin TextF Source # 
Instance details

Defined in TextF

HasMargin ShellF Source # 
Instance details

Defined in DShellF

HasMargin (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasMargin (ButtonF a) Source # 
Instance details

Defined in DButtonF

class HasFgColorSpec xxx where Source #

Minimal complete definition

setFgColorSpec, getFgColorSpecMaybe

class HasBgColorSpec xxx where Source #

Minimal complete definition

setBgColorSpec, getBgColorSpecMaybe

class HasKeys xxx where Source #

Minimal complete definition

setKeys, getKeysMaybe

class HasFontSpec xxx where Source #

Minimal complete definition

setFontSpec, getFontSpecMaybe

Instances

Instances details
HasFontSpec TextF Source # 
Instance details

Defined in TextF

HasFontSpec ToggleButtonF Source # 
Instance details

Defined in DToggleButtonF

HasFontSpec RadioGroupF Source # 
Instance details

Defined in DRadioF

HasFontSpec StringF Source # 
Instance details

Defined in StringF

HasFontSpec EditorF Source # 
Instance details

Defined in InputEditorF

HasFontSpec (GraphicsF a) Source # 
Instance details

Defined in GraphicsF

HasFontSpec (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasFontSpec (ButtonF a) Source # 
Instance details

Defined in DButtonF

type PK p a b = K (Either (Customiser p) a) b Source #

type PF p a b = F (Either (Customiser p) a) b Source #

type Customiser a = a -> a Source #

cust :: (a -> a) -> Customiser a Source #

getpar :: (t -> Maybe c) -> [t] -> c Source #

getparMaybe :: (t -> Maybe a) -> [t] -> Maybe a Source #

noPF :: PF p a b -> F a b Source #

setFont :: (HasFontSpec xxx, Show a, FontGen a) => a -> Customiser xxx Source #

fromMaybe :: a -> Maybe a -> a #

The fromMaybe function takes a default value and and Maybe value. If the Maybe is Nothing, it returns the default values; otherwise, it returns the value contained in the Maybe.

Examples

Expand

Basic usage:

>>> fromMaybe "" (Just "Hello, World!")
"Hello, World!"
>>> fromMaybe "" Nothing
""

Read an integer from a string using readMaybe. If we fail to parse an integer, we want to return 0 by default:

>>> import Text.Read ( readMaybe )
>>> fromMaybe 0 (readMaybe "5")
5
>>> fromMaybe 0 (readMaybe "")
0