¤ Fudget Library Reference Manual ¤
Created from the Fudget Library sources on Mon Aug  9 17:27:21 CEST 1999
Full Index
Sections
- Audio:
 - 
bellF :: F a a
 - Button implementation:
 - 
data BMevents = ...
- 
buttonGroupF :: [(ModState, KeySym)] -> F (Either BMevents a) b -> F a b
- 
pushButtonF :: [(ModState, KeySym)] -> F a b -> F a (Either b Click)
   - Buttons:
 - 
data Click = ...
- 
data ButtonF a
- 
class HasLabelInside a where ...
- 
data ToggleButtonF
- 
data RadioGroupF
- 
buttonF :: (Graphic a) => a -> F Click Click
- 
buttonF' :: (Graphic a) => Customiser (ButtonF a) -> a -> F Click Click
- 
buttonF'' :: (Graphic a) => Customiser (ButtonF a) -> a -> PF (ButtonF a) Click Click
- 
quitButtonF :: F Click a
- 
radioGroupF :: (Graphic b, Eq a) => [(a, b)] -> a -> F a a
- 
radioGroupF' :: (Graphic b, Eq a) => Customiser RadioGroupF -> [(a, b)] -> a -> F a a
- 
setLabel :: a -> Customiser (ButtonF a)
- 
setPlacer :: Placer -> Customiser RadioGroupF
- 
toggleButtonF :: (Graphic a) => a -> F Bool Bool
- 
toggleButtonF' :: (Graphic a) => Customiser ToggleButtonF -> a -> F Bool Bool
- 
toggleF :: Bool -> [(ModState, KeySym)] -> F a b -> F (Either Bool a) (Either Bool b)
                - Data entry fields:
 - 
data StringF
- 
intF :: F Int (InputMsg Int)
- 
intF' :: Customiser StringF -> F Int (InputMsg Int)
- 
intF'' :: Customiser StringF -> PF StringF Int (InputMsg Int)
- 
intInputF :: F Int Int
- 
intInputF' :: Customiser StringF -> F Int Int
- 
passwdF :: F String (InputMsg String)
- 
passwdF' :: (StringF -> StringF) -> F String (InputMsg String)
- 
passwdF'' :: (StringF -> StringF) -> PF StringF String (InputMsg String)
- 
passwdInputF :: F String String
- 
passwdInputF' :: (StringF -> StringF) -> F String String
- 
setAllowedChar :: (Char -> Bool) -> Customiser StringF
- 
setCursorPos :: Int -> Customiser StringF
- 
setInitString :: String -> Customiser StringF
- 
setInitStringSize :: String -> Customiser StringF
- 
setShowString :: (String -> String) -> Customiser StringF
- 
stringF :: F String (InputMsg String)
- 
stringF' :: Customiser StringF -> F String (InputMsg String)
- 
stringF'' :: Customiser StringF -> PF StringF String (InputMsg String)
- 
stringInputF :: F String String
- 
stringInputF' :: Customiser StringF -> F String String
                     - Decoration:
 - 
border3dF :: Bool -> Int -> F a b -> F (Either Bool a) b
- 
buttonBorderF :: Int -> F a b -> F (Either Bool a) b
- 
labAboveF :: (Graphic a) => a -> F b c -> F b c
- 
labBelowF :: (Graphic a) => a -> F b c -> F b c
- 
labLeftOfF :: (Graphic a) => a -> F b c -> F b c
- 
labRightOfF :: (Graphic a) => a -> F b c -> F b c
- 
labelF :: (Graphic a) => a -> F b c
- 
labelF' :: (Graphic a) => Customiser (DisplayF a) -> a -> F b c
- 
tieLabelF :: (Graphic a) => Orientation -> Alignment -> a -> F b c -> F b c
         - Displaying and interacting with composite graphical objects:
 - 
data GraphicsF a
- 
graphicsF :: (Graphic a) => F (GfxCommand DPath a) (GfxEvent DPath)
- 
graphicsF' :: (Graphic a) => Customiser (GraphicsF a) -> F (GfxCommand DPath a) (GfxEvent DPath)
- 
hyperGraphicsF :: (Eq a, Graphic b) => Drawing a b -> F (Either (Drawing a b) (a, Drawing a b)) a
- 
hyperGraphicsF' :: (Eq a, Graphic b) => (GraphicsF (Drawing a b) -> GraphicsF (Drawing a b)) -> Drawing a b -> F (Either (Drawing a b) (a, Drawing a b)) a
- 
setAdjustSize :: Bool -> Customiser (GraphicsF a)
      - Displaying and interacting with lists:
 - 
type PickListRequest a = ListRequest a
- 
pickListF :: (a -> String) -> F (PickListRequest a) (InputMsg (Int, a))
- 
pickListF' :: Customiser TextF -> (a -> String) -> F (PickListRequest a) (InputMsg (Int, a))
   - Displaying text:
 - 
data TextF
- 
type TextRequest = ListRequest String
- 
moreF :: F [String] (InputMsg (Int, String))
- 
moreF' :: Customiser TextF -> F [String] (InputMsg (Int, String))
- 
moreFileF :: F String (InputMsg (Int, String))
- 
moreFileShellF :: F String (InputMsg (Int, String))
- 
moreShellF :: String -> F [String] (InputMsg (Int, String))
- 
moreShellF' :: Customiser TextF -> String -> F [String] (InputMsg (Int, String))
- 
textF :: F TextRequest (InputMsg (Int, String))
- 
textF' :: Customiser TextF -> F TextRequest (InputMsg (Int, String))
          - Displays:
 - 
data DisplayF a
- 
displayF :: (Graphic a) => F a b
- 
displayF' :: (Graphic a) => Customiser (DisplayF a) -> F a b
- 
intDispF :: F Int a
- 
intDispF' :: Customiser (DisplayF Int) -> F Int a
- 
setSpacer :: Spacer -> Customiser (DisplayF a)
      - Menus:
 - 
menuF :: (Graphic a, Graphic c) => a -> [(b, c)] -> F b b
- 
popupMenuF :: (Graphic b, Eq b) => [(a, b)] -> F c d -> F (Either [(a, b)] c) (Either a d)
  - Pop-up windows:
 - 
data ConfirmMsg = ...
- 
confirmPopupF :: (Graphic a) => F a (a, ConfirmMsg)
- 
inputPopupF :: String -> InF a b -> Maybe b -> F (Maybe String, Maybe a) ((Maybe String, Maybe a), b)
- 
inputPopupOptF :: String -> InF a b -> Maybe b -> F (Maybe String, Maybe a) ((Maybe String, Maybe a), Maybe b)
- 
messagePopupF :: (Graphic a) => F a (a, Click)
- 
passwdPopupF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), String)
- 
stringPopupF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), String)
       - Selecting from dynamic lists of alternatives:
 - 
oldFilePickF :: F String (InputMsg String)
 - Terminating the program:
 - 
quitF :: F a b
- 
quitIdF :: (a -> Bool) -> F a a
  - Text editors:
 - 
data EditEvt = ...
- 
data EditCmd = ...
- 
editorF :: F EditCmd EditEvt
- 
editorF' :: Customiser EditorF -> F EditCmd EditEvt
- 
loadEditor :: String -> [EditCmd]
- 
selectall :: [EditCmd]
- 
setEditorCursorPos :: (Int, Int) -> [EditCmd]
       - Miscellaneous (the rest):
 - 
data EditStop = ...
- 
data EDirection = ...
- 
type EditStopFn = String -> String -> EditStopChoice
- 
data EditStopChoice = ...
- 
type IsSelect = Bool
- 
data EditorF
- 
data GfxEventMask = ...
- 
data GfxCommand a b = ...
- 
data GfxEvent a = ...
- 
data MenuState
- 
data EqSnd a b = ...
- 
data PopupMenu = ...
- 
data TerminalCmd = ...
- 
bdStringF :: Int -> Sizing -> FontName -> [Char] -> F [Char] (InputMsg [Char])
- 
buttonMenuF :: (Graphic a) => LayoutDir -> FontName -> a -> [(b, [(ModState, KeySym)])] -> F (Either MenuState c) b -> F (Either MenuState (Either a c)) (Either MenuState b)
- 
buttonMenuF' :: (Graphic a) => Bool -> LayoutDir -> FontName -> a -> [(b, [(ModState, KeySym)])] -> F (Either MenuState c) b -> F (Either MenuState (Either a c)) (Either MenuState b)
- 
cmdTerminalF :: FontName -> Int -> Int -> F TerminalCmd a
- 
editF :: FontName -> F EditCmd EditEvt
- 
fstEqSnd :: EqSnd a b -> a
- 
gcWarningF :: F a b
- 
generalStringF :: Int -> String -> Sizing -> ColorSpec -> ColorSpec -> FontName -> (Char -> Bool) -> ([Char] -> [Char]) -> Int -> [Char] -> F (Either (StringF -> StringF) [Char]) (InputMsg [Char])
- 
getAllowedChar :: StringF -> Char -> Bool
- 
getCursorPos :: StringF -> Int
- 
getInitString :: StringF -> String
- 
getShowString :: StringF -> String -> String
- 
gfxButton :: GfxEvent a -> Button
- 
gfxHasFocus :: GfxEvent a -> Bool
- 
gfxKeyLookup :: GfxEvent a -> KeyLookup
- 
gfxKeySym :: GfxEvent a -> KeySym
- 
gfxPaths :: GfxEvent a -> [(a, (Point, Rect))]
- 
gfxState :: GfxEvent a -> ModState
- 
gfxType :: GfxEvent a -> Pressed
- 
grabberF :: [(a, [(ModState, KeySym)])] -> F (Either b a) (Either MenuState c) -> F a c
- 
graphicsDispF :: (Graphic a) => F (GfxCommand DPath a) (GfxEvent DPath)
- 
graphicsDispF' :: (Graphic a) => Customiser (GraphicsF a) -> F (GfxCommand DPath a) (GfxEvent DPath)
- 
graphicsDispGroupF :: (Graphic c) => F a b -> F (Either (GfxCommand DPath c) a) (Either (GfxEvent DPath) b)
- 
graphicsDispGroupF' :: (Graphic a) => (GraphicsF a -> GraphicsF a) -> F b c -> F (Either (GfxCommand DPath a) b) (Either (GfxEvent DPath) c)
- 
graphicsGroupF :: (Graphic c) => F a b -> F (Either (GfxCommand DPath c) a) (Either (GfxEvent DPath) b)
- 
graphicsGroupF' :: (Graphic a) => Customiser (GraphicsF a) -> F b c -> F (Either (GfxCommand DPath a) b) (Either (GfxEvent DPath) c)
- 
graphicsLabelF :: (Graphic a) => a -> F b c
- 
graphicsLabelF' :: (Graphic a) => (GraphicsF a -> GraphicsF a) -> a -> F b c
- 
inputEditorF :: F String (InputMsg String)
- 
inputEditorF' :: Customiser EditorF -> F String (InputMsg String)
- 
menuAltsF :: (Graphic b, Eq a) => FontName -> [a] -> (a -> b) -> F PopupMenu a
- 
menuButtonF :: (Graphic a) => FontName -> a -> F a Click
- 
menuButtonGroupF :: F (Either BMevents a) b -> F a b
- 
menuDown :: MenuState
- 
menuLabelF :: (Graphic a) => FontName -> a -> F (Either Bool a) (GfxEvent DPath)
- 
menuPopupF :: F a b -> F (Either PopupMenu a) b
- 
menuPopupF' :: Bool -> F a b -> F (Either PopupMenu a) b
- 
newline :: Char
- 
offColor :: [Char]
- 
oldButtonF :: (Graphic b, Show a, ColorGen a, Graphic c) => Alignment -> Distance -> FontName -> ColorSpec -> a -> [(ModState, KeySym)] -> b -> F c Click
- 
oldConfirmPopupF :: F String (String, ConfirmMsg)
- 
oldEditorF :: FontName -> F EditCmd EditEvt
- 
oldGeneralStringF :: Int -> Sizing -> FontName -> (Char -> Bool) -> ([Char] -> [Char]) -> [Char] -> F [Char] (InputMsg [Char])
- 
oldIntF :: Int -> InF Int Int
- 
oldMenuF :: (Graphic c, Eq b, Graphic a) => FontName -> a -> [(b, [(ModState, KeySym)])] -> (b -> c) -> F a b
- 
oldMessagePopupF :: F String (String, Click)
- 
oldPasswdF :: String -> InF String String
- 
oldPopupMenuF :: (Graphic c, Eq a) => ColorName -> Bool -> FontName -> Button -> ModState -> [(ModState, KeySym)] -> [(a, b)] -> (a -> c) -> F d e -> F (Either [(a, f)] d) (Either a e)
- 
oldRadioGroupF :: (Graphic b, Eq a) => Placer -> Bool -> FontName -> [a] -> a -> (a -> b) -> F a a
- 
oldStringF :: String -> InF String String
- 
oldToggleButtonF :: (Graphic a) => FontName -> [(ModState, KeySym)] -> a -> F Bool Bool
- 
oldToggleButtonF' :: (Graphic a) => Bool -> FontName -> [(ModState, KeySym)] -> a -> F Bool Bool
- 
onColor :: [Char]
- 
onOffDispF :: Bool -> F Bool a
- 
passwdPopupOptF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), Maybe String)
- 
pushButtonF' :: Int -> [(ModState, KeySym)] -> F a b -> F a (Either b Click)
- 
radioF :: (Graphic b, Eq a) => Placer -> Bool -> FontName -> [(a, b)] -> a -> F a a
- 
replaceAllGfx :: a -> GfxCommand [b] a
- 
replaceGfx :: a -> b -> GfxCommand a b
- 
setCursor :: Int -> Customiser (GraphicsF a)
- 
setCursorSolid :: Bool -> Customiser (GraphicsF a)
- 
setGfxEventMask :: [GfxEventMask] -> Customiser (GraphicsF a)
- 
simpleMenuF :: (Graphic c, Eq b, Graphic a) => FontName -> a -> [b] -> (b -> c) -> F a b
- 
smallPickListF :: (a -> String) -> F [a] a
- 
sndEqSnd :: EqSnd a b -> b
- 
stringPopupOptF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), Maybe String)
- 
terminalF :: FontName -> Int -> Int -> F String a
- 
textF'' :: Customiser TextF -> PF TextF TextRequest (InputMsg (Int, String))
- 
toEqSnd :: [(a, b)] -> [EqSnd a b]
- 
toggleGroupF :: [(ModState, KeySym)] -> F (Either (Either Bool Bool) a) b -> F (Either Bool a) (Either Bool b)
                                                                                   
- Abstract fudgets: from stream processors:
 - 
absF :: SP a b -> F a b
 - Abstract fudgets: stateful:
 - 
mapstateF :: (a -> b -> (a, [c])) -> a -> F b c
 - Abstract fudgets: stateless:
 - 
concatMapF :: (a -> [b]) -> F a b
- 
mapF :: (a -> b) -> F a b
  - Combining data entry fields:
 - 
inputListF :: (Eq a) => [(a, InF b c)] -> InF [(a, b)] [(a, c)]
- 
inputPairF :: InF a b -> InF c d -> InF (a, c) (b, d)
- 
inputThroughF :: InF a a -> InF a a
   - Data entry field postprocessors:
 - 
inputDoneSP :: SP (InputMsg a) a
- 
inputLeaveDoneSP :: SP (InputMsg a) a
- 
stripInputSP :: SP (InputMsg a) a
   - Data entry fields:
 - 
type InF a b = F a (InputMsg b)
 - Delay the activation of a stream processor or fudget:
 - 
delayF :: F a b -> F a b
 - Dynamic fudget creation/destruction:
 - 
type DynFMsg a b = DynMsg a (F a b)
- 
dynF :: F a b -> F (Either (F a b) a) b
- 
dynListF :: F (Int, DynFMsg a b) (Int, b)
   - Plumbing: circular connections:
 - 
loopCompF :: F (Either (Either a b) (Either c d)) (Either (Either c e) (Either a f)) -> F (Either b d) (Either e f)
- 
loopF :: F a a -> F a a
- 
loopLeftF :: F (Either a b) (Either a c) -> F b c
- 
loopOnlyF :: F a a -> F a b
- 
loopRightF :: F (Either a b) (Either c b) -> F a c
- 
loopThroughBothF :: F (Either a b) (Either c d) -> F (Either c e) (Either a f) -> F (Either b e) (Either d f)
- 
loopThroughRightF :: F (Either a b) (Either c d) -> F c a -> F b d
       - Plumbing: common patterns of serial and parallel compositions:
 - 
bypassF :: F a a -> F a a
- 
idLeftF :: F a b -> F (Either c a) (Either c b)
- 
idRightF :: F a b -> F (Either a c) (Either b c)
- 
stubF :: F a b -> F c d
- 
throughF :: F a b -> F a (Either b a)
- 
toBothF :: F a (Either a a)
      - Plumbing: serial composition:
 - 
serCompF :: F a b -> F c a -> F c b
 - Plumbing: tagged parallel composition:
 - 
compF :: F a b -> F c d -> F (Either a c) (Either b d)
- 
listF :: (Eq a) => [(a, F b c)] -> F (a, b) (a, c)
  - Plumbing: turn parallel compositions into loops:
 - 
loopCompThroughLeftF :: F (Either a (Either b c)) (Either b (Either a d)) -> F c d
- 
loopCompThroughRightF :: F (Either (Either a b) c) (Either (Either c d) a) -> F b d
  - Plumbing: turning parallel compositions into serial compositions:
 - 
serCompLeftToRightF :: F (Either a b) (Either b c) -> F a c
- 
serCompRightToLeftF :: F (Either a b) (Either c a) -> F b c
  - Plumbing: untagged parallel composition:
 - 
untaggedListF :: [F a b] -> F a b
 - Stream processor combinators that create circular connections:
 - 
loopCompSP :: SP (Either (Either a b) (Either c d)) (Either (Either c e) (Either a f)) -> SP (Either b d) (Either e f)
- 
loopThroughBothSP :: SP (Either a b) (Either c d) -> SP (Either c e) (Either a f) -> SP (Either b e) (Either d f)
  - The Fudget type:
 - 
data F a b
 - The fudget kernel type:
 - 
data K a b
 - The identity fudget:
 - 
idF :: F a a
 - Miscellaneous (the rest):
 - 
type Cont a b = (b -> a) -> a
- 
type Ks a b c d = Ms (K a b) c d
- 
type Ksc a b c = Ks a b c ()
- 
type Msc a b = Ms a b ()
- 
type Ms a b c = Mk (b -> a) c
- 
type Mkc a = Mk a ()
- 
type Mk a b = Cont a b
- 
data Tree a = ...
- 
appendStartF :: [a] -> F b a -> F b a
- 
appendStartK :: [KCommand a] -> K b a -> K b a
- 
appendStartMessageF :: [FCommand a] -> F b a -> F b a
- 
bindKs :: Ks a b c d -> (d -> Ks a b c e) -> Ks a b c e
- 
bindMk :: Mk a b -> (b -> Mk a c) -> Mk a c
- 
bindMs :: Ms a b c -> (c -> Ms a b d) -> Ms a b d
- 
bmk :: ((a -> b) -> c) -> (a -> d -> b) -> d -> c
- 
branchF :: F (Path, a) b -> F (Path, a) b -> F (Path, a) b
- 
branchFSP :: FSP (Path, a) b -> FSP (Path, a) b -> FSP (Path, a) b
- 
compPath :: (Path, a) -> b -> (Either (Message (Path, a) c) (Message (Path, a) d) -> b) -> b
- 
compTurnLeft :: (Path, a) -> Message (Path, a) b
- 
compTurnRight :: (Path, a) -> Message (Path, a) b
- 
contDynF :: F a b -> Cont (F a c) b
- 
contDynFSP :: FSP a b -> Cont (FSP a c) b
- 
fieldMs :: (a -> b) -> Ms c a b
- 
getF :: Cont (F a b) a
- 
getK :: Cont (K a b) (KEvent a)
- 
getKs :: Ks a b c (KEvent a)
- 
getMessageF :: Cont (F a b) (FEvent a)
- 
getMessageFu :: Cont (F a b) (KEvent a)
- 
ifMs :: Bool -> Ms a b () -> Ms a b ()
- 
inputListLF :: (Eq a) => Placer -> [(a, InF b c)] -> F [(a, b)] (InputMsg [(a, c)])
- 
inputListSP :: (Eq a) => [a] -> SP (a, InputMsg b) (InputMsg [(a, b)])
- 
inputPairLF :: Orientation -> InF a b -> InF c d -> F (a, c) (InputMsg (b, d))
- 
inputPairSP :: SP (Either (InputMsg a) (InputMsg b)) (InputMsg (a, b))
- 
leafF :: a -> F b c -> Fa TEvent TCommand ([d], b) (a, c)
- 
loadKs :: Ks a b c c
- 
loadMs :: Ms a b b
- 
loopLow :: SP TCommand (FCommand a) -> SP (FEvent a) TEvent -> F b c -> F b c
- 
loopThroughLowF :: SP (Either TCommand TEvent) (Either TCommand TEvent) -> F a b -> F a b
- 
loopThroughLowSP :: SP (Either a b) (Either a b) -> SP (Message b c) (Message a d) -> SP (Message b c) (Message a d)
- 
mapKs :: (a -> b) -> Ks c d e a -> Ks c d e b
- 
modMs :: (a -> a) -> Msc b a
- 
nopMs :: Ms a b ()
- 
nullF :: F a b
- 
nullK :: K a b
- 
nullKs :: Ks a b c ()
- 
parF :: F a b -> F a b -> F a b
- 
postMapHigh :: (a -> b) -> F c a -> F c b
- 
postMapHigh' :: (a -> b) -> Fa c d e a -> Fa c d e b
- 
postMapHighK :: (a -> b) -> K c a -> K c b
- 
postMapLow :: (TCommand -> TCommand) -> F a b -> F a b
- 
postMapLow' :: (a -> b) -> Fa c a d e -> Fa c b d e
- 
postMapLowK :: (FRequest -> FRequest) -> K a b -> K a b
- 
postProcessHigh :: SP a b -> F c a -> F c b
- 
postProcessHigh' :: SP a b -> Fa c d e a -> Fa c d e b
- 
postProcessHighK :: SP a b -> K c a -> K c b
- 
postProcessLow :: SP TCommand TCommand -> F a b -> F a b
- 
postProcessLow' :: SP a b -> Fa c a d e -> Fa c b d e
- 
postProcessLowK :: SP FRequest FRequest -> K a b -> K a b
- 
preMapHigh :: F a b -> (c -> a) -> F c b
- 
preMapHigh' :: Fa a b c d -> (e -> c) -> Fa a b e d
- 
preMapHighK :: K a b -> (c -> a) -> K c b
- 
preMapLow :: F a b -> (TEvent -> TEvent) -> F a b
- 
preMapLow' :: Fa a b c d -> (e -> a) -> Fa e b c d
- 
preMapLowK :: K a b -> (FResponse -> FResponse) -> K a b
- 
preProcessHigh :: F a b -> SP c a -> F c b
- 
preProcessHigh' :: Fa a b c d -> SP e c -> Fa a b e d
- 
preProcessHighK :: K a b -> SP c a -> K c b
- 
preProcessLow :: F a b -> SP TEvent TEvent -> F a b
- 
preProcessLow' :: Fa a b c d -> SP e a -> Fa e b c d
- 
preProcessLowK :: K a b -> SP FResponse FResponse -> K a b
- 
prepostMapHigh :: (a -> b) -> (c -> d) -> F b c -> F a d
- 
prepostMapHigh' :: (a -> b) -> (c -> d) -> Fa e f b c -> Fa e f a d
- 
prepostMapHighK :: (a -> b) -> (c -> d) -> K b c -> K a d
- 
prepostMapLow :: (TEvent -> TEvent) -> (TCommand -> TCommand) -> F a b -> F a b
- 
prepostMapLow' :: (a -> b) -> (c -> d) -> Fa b c e f -> Fa a d e f
- 
prepostMapLowK :: (FResponse -> FResponse) -> (FRequest -> FRequest) -> K a b -> K a b
- 
prodF :: F a b -> F c d -> F (a, c) (Either b d)
- 
putF :: a -> F b a -> F b a
- 
putK :: KCommand a -> K b a -> K b a
- 
putKs :: KCommand a -> Ksc b a c
- 
putMessageF :: FCommand a -> F b a -> F b a
- 
putMessageFu :: Message FRequest a -> F b a -> F b a
- 
putMessagesF :: [FCommand a] -> F b a -> F b a
- 
putMessagesFu :: [KCommand a] -> F b a -> F b a
- 
putsF :: [a] -> F b a -> F b a
- 
putsK :: [KCommand a] -> K b a -> K b a
- 
putsKs :: [KCommand a] -> Ksc b a c
- 
startupF :: [a] -> F a b -> F a b
- 
startupK :: [KEvent a] -> K a b -> K a b
- 
startupMessageF :: [FEvent a] -> F a b -> F a b
- 
stateK :: a -> Ksc b c a -> K b c -> K b c
- 
stateMonadK :: a -> Ks b c a d -> (d -> K b c) -> K b c
- 
storeKs :: a -> Ks b c a ()
- 
storeMs :: a -> Msc b a
- 
thenKs :: Ks a b c () -> Ks a b c d -> Ks a b c d
- 
thenMk :: Mkc a -> Mk a b -> Mk a b
- 
thenMs :: Msc a b -> Ms a b c -> Ms a b c
- 
toMkc :: (a -> a) -> Mkc a
- 
toMs :: Mk a b -> Ms a c b
- 
toMsc :: (a -> a) -> Msc a b
- 
treeF :: Tree (a, F b c) -> F (Path, b) (a, c)
- 
treeF' :: Tree (a, F b c) -> FSP (Path, b) (a, c)
- 
unitKs :: a -> Ks b c d a
- 
unitMk :: a -> Mk b a
- 
unitMs :: a -> Ms b c a
                                                                                                         
- Plumbing: serial composition:
 - 
infixr 4 >==<
- 
>==< :: F a b -> F c a -> F c b
  - Plumbing: tagged parallel composition:
 - 
infixl 5 >+<
- 
>+< :: F a b -> F c d -> F (Either a c) (Either b d)
  - Plumbing: untagged parallel composition:
 - 
infixl 5 >*<
- 
>*< :: F a b -> F a b -> F a b
  - Miscellaneous (the rest):
 - 
infixr 8 -*-
- 
-*- :: SP a b -> SP a b -> SP a b
- 
infixr 8 -+-
- 
-+- :: SP a b -> SP c d -> SP (Either a c) (Either b d)
- 
infixr 8 -==-
- 
-==- :: SP a b -> SP c a -> SP c b
- 
infixl 9 >#+<
- 
>#+< :: (F a b, Orientation) -> F c d -> F (Either a c) (Either b d)
- 
infixl 9 >#==<
- 
>#==< :: (F a b, Orientation) -> F c a -> F c b
- 
infixl 9 >+#<
- 
>+#< :: F a b -> (Distance, Orientation, F c d) -> F (Either a c) (Either b d)
- 
infixr 5 >..=<
- 
>..=< :: SP TCommand TCommand -> F a b -> F a b
- 
infixr 6 >.=<
- 
>.=< :: (TCommand -> TCommand) -> F a b -> F a b
- 
infixl 6 >=..<
- 
>=..< :: F a b -> SP TEvent TEvent -> F a b
- 
infixl 6 >=.<
- 
>=.< :: F a b -> (TEvent -> TEvent) -> F a b
- 
infixl 9 >==#<
- 
>==#< :: F a b -> (Distance, Orientation, F c a) -> F c b
- 
infixl 6 >=^<
- 
>=^< :: F a b -> (c -> a) -> F c b
- 
infixl 6 >=^^<
- 
>=^^< :: F a b -> SP c a -> F c b
- 
infixr 7 >^=<
- 
>^=< :: (a -> b) -> F c a -> F c b
- 
infixr 7 >^^=<
- 
>^^=< :: SP a b -> F c a -> F c b
                              
- A spacer that centers a box in the available space:
 - 
centerS :: Spacer
 - GUI fudget placement:
 - 
data Placer = ...
- 
alignF :: Size -> Size -> Alignment -> Alignment -> F a b -> F a b
- 
hBoxF :: F a b -> F a b
- 
marginHVAlignF :: Distance -> Alignment -> Alignment -> F a b -> F a b
- 
matrixF :: Int -> F a b -> F a b
- 
noStretchF :: Bool -> Bool -> F a b -> F a b
- 
placerF :: Placer -> F a b -> F a b
- 
revHBoxF :: F a b -> F a b
- 
revVBoxF :: F a b -> F a b
- 
tableF :: Int -> F a b -> F a b
- 
vBoxF :: F a b -> F a b
           - GUI fudget spacing:
 - 
data Spacer = ...
- 
spacerF :: Spacer -> F a b -> F a b
  - Name layout:
 - 
data NameLayout
- 
hBoxNL :: [NameLayout] -> NameLayout
- 
hBoxNL' :: Distance -> [NameLayout] -> NameLayout
- 
hvAlignNL :: Alignment -> Alignment -> NameLayout -> NameLayout
- 
leafNL :: LName -> NameLayout
- 
marginHVAlignNL :: Distance -> Alignment -> Alignment -> NameLayout -> NameLayout
- 
marginNL :: Distance -> NameLayout -> NameLayout
- 
modNL :: (Placer -> Placer) -> NameLayout -> NameLayout
- 
nameLayoutF :: NameLayout -> F a b -> F a b
- 
nullNL :: NameLayout
- 
placeNL :: Placer -> [NameLayout] -> NameLayout
- 
sepNL :: Size -> NameLayout -> NameLayout
- 
spaceNL :: Spacer -> NameLayout -> NameLayout
- 
vBoxNL :: [NameLayout] -> NameLayout
- 
vBoxNL' :: Distance -> [NameLayout] -> NameLayout
               - Placer modifying combinators:
 - 
flipP :: Placer -> Placer
- 
revP :: Placer -> Placer
  - Placers for creating matrixes:
 - 
data LayoutDir = ...
- 
matrixP :: Int -> Placer
- 
matrixP' :: Int -> LayoutDir -> Distance -> Placer
   - Placers for creating tables:
 - 
tableP :: Int -> Placer
- 
tableP' :: Int -> LayoutDir -> Distance -> Placer
  - Placers for vertical and horizontal placement:
 - 
horizontalP :: Placer
- 
verticalP :: Placer
  - Spacer combinators:
 - 
compS :: Spacer -> Spacer -> Spacer
- 
flipS :: Spacer -> Spacer
- 
idS :: Spacer
   - Spacers that add margins to boxes:
 - 
type Distance = Int
- 
hMarginS :: Distance -> Distance -> Spacer
- 
hvMarginS :: Size -> Size -> Spacer
- 
marginS :: Distance -> Spacer
- 
vMarginS :: Distance -> Distance -> Spacer
     - Spacers that add space instead of stretching a box when there is extra space:
 - 
hAlignS :: Alignment -> Spacer
- 
hvAlignS :: Alignment -> Alignment -> Spacer
- 
vAlignS :: Alignment -> Spacer
   - Spacers that align boxes with edges:
 - 
bottomS :: Spacer
- 
hCenterS :: Spacer
- 
leftS :: Spacer
- 
rightS :: Spacer
- 
topS :: Spacer
- 
vCenterS :: Spacer
      - Miscellaneous (the rest):
 - 
type Alignment = Double
- 
data Orientation = ...
- 
data LayoutDirection = ...
- 
data LayoutRequest = ...
- 
data LayoutMessage = ...
- 
data LayoutResponse = ...
- 
type Placer1 = [LayoutRequest] -> Placer2
- 
type Placer2 = (LayoutRequest, Rect -> [Rect])
- 
type Spacer1 = LayoutRequest -> Spacer2
- 
type Spacer2 = (LayoutRequest, Rect -> Rect)
- 
type LayoutHint = String
- 
data Layout
- 
type LName = String
- 
data Sizing = ...
- 
aBottom :: Alignment
- 
aCenter :: Alignment
- 
aLeft :: Alignment
- 
aRight :: Alignment
- 
aTop :: Alignment
- 
alignFixedS :: Alignment -> Alignment -> Spacer
- 
alignFixedS' :: Alignment -> Alignment -> Spacer
- 
alignP :: Placer
- 
alignP' :: Distance -> Placer
- 
atLeastOne :: ([a], [a]) -> ([a], [a])
- 
autoLayoutF :: F a b -> F a b
- 
autoLayoutF' :: Bool -> Sizing -> F a b -> F a b
- 
autoP :: Placer
- 
autoP' :: Size -> Placer
- 
center :: Size -> Rect -> Rect
- 
center' :: Point -> Size -> Rect -> Rect
- 
colinear :: LayoutDir -> a -> a -> a
- 
compLF :: (F a b, Orientation) -> F c d -> F (Either a c) (Either b d)
- 
dynListLF :: Placer -> F (Int, DynFMsg a b) (Int, b)
- 
dynPlacerF :: F a b -> F (Either Placer a) b
- 
dynSpacerF :: F a b -> F (Either Spacer a) b
- 
fixedh :: LayoutRequest -> Bool
- 
fixedv :: LayoutRequest -> Bool
- 
fixh :: LayoutDir -> LayoutRequest -> Bool
- 
fixv :: LayoutDir -> LayoutRequest -> Bool
- 
flipPoint :: Point -> Point
- 
flipRect :: Rect -> Rect
- 
flipReq :: LayoutRequest -> LayoutRequest
- 
flipWanted :: (Point, Point, a) -> (Point, Point, a)
- 
hAdj :: LayoutRequest -> Int -> Size
- 
hBoxLs' :: Distance -> [Layout] -> Layout
- 
holeF :: F a b
- 
holeF' :: Size -> F a b
- 
horizontalAlignP :: Placer
- 
horizontalAlignP' :: Distance -> Placer
- 
horizontalCenterP :: Placer
- 
horizontalCenterP' :: Distance -> Placer
- 
horizontalP' :: Distance -> Placer
- 
hvAlignLs :: Alignment -> Alignment -> Layout -> Layout
- 
idP :: Placer
- 
ifSizeP :: (Size -> Size -> Bool) -> Placer -> Placer -> Placer
- 
ifSizeS :: (Size -> Size -> Bool) -> Spacer -> Spacer -> Spacer
- 
lF :: Int -> LayoutDirection -> Placer -> F a b -> F a b
- 
layoutF :: Layout -> F a b -> F a b
- 
layoutMakeVisible :: Rect -> LayoutMessage
- 
layoutModifierF :: (LayoutRequest -> LayoutRequest) -> F a b -> F a b
- 
layoutModifierS :: (LayoutRequest -> LayoutRequest) -> Spacer
- 
leafLs :: Layout
- 
linearP :: LayoutDir -> Distance -> Placer
- 
listLF :: (Eq a) => Placer -> [(a, F b c)] -> F (a, b) (a, c)
- 
listNF :: (Eq a, Show a) => [(a, F b c)] -> F (a, b) (a, c)
- 
mapAdjLayoutSize :: (Size -> Size) -> (Int -> Int) -> (Int -> Int) -> LayoutRequest -> LayoutRequest
- 
mapLayout :: (Size -> Bool -> Bool -> (Int -> Size) -> (Int -> Size) -> [Point] -> Maybe (Point, Size, Alignment) -> a) -> LayoutRequest -> a
- 
mapLayoutRefs :: (Point -> Point) -> LayoutRequest -> LayoutRequest
- 
mapLayoutSize :: (Size -> Size) -> LayoutRequest -> LayoutRequest
- 
mapP :: (Placer1 -> Placer1) -> Placer -> Placer
- 
mapS :: (Spacer1 -> Spacer1) -> Spacer -> Spacer
- 
marginF :: Distance -> F a b -> F a b
- 
marginHVAlignLs :: Distance -> Alignment -> Alignment -> Layout -> Layout
- 
marginHVAlignS :: Distance -> Alignment -> Alignment -> Spacer
- 
marginLs :: Distance -> Layout -> Layout
- 
maxSizeS :: Size -> Spacer
- 
middleRefs :: Point -> (Point, Point)
- 
minSizeS :: Size -> Spacer
- 
minsize :: LayoutRequest -> Size
- 
mkp :: LayoutDir -> Int -> Int -> Point
- 
moveRefsS :: Point -> Spacer
- 
nameF :: LName -> F a b -> F a b
- 
newSize :: Sizing -> Point -> Point -> Point
- 
noRefsS :: Spacer
- 
noStretchS :: Bool -> Bool -> Spacer
- 
nowait :: Bool
- 
nullLF :: F a b
- 
orientP :: Orientation -> Placer
- 
orthogonal :: LayoutDir -> a -> a -> a
- 
overlayAlignP :: Placer
- 
overlayP :: Placer
- 
paragraphP :: Placer
- 
paragraphP' :: Size -> Placer
- 
paragraphP'' :: (Int -> Placer) -> Size -> Placer
- 
permLs :: [Int] -> Layout -> Layout
- 
permuteP :: [Int] -> Placer -> Placer
- 
placeLs :: Placer -> [Layout] -> Layout
- 
plainLayout :: Size -> Bool -> Bool -> LayoutRequest
- 
refEdgesS :: Spacer
- 
refMiddleS :: Spacer
- 
refMiddleS' :: LayoutRequest -> (LayoutRequest, a -> a)
- 
refpLayout :: Size -> Bool -> Bool -> [Point] -> LayoutRequest
- 
refpoints :: LayoutRequest -> [Point]
- 
resizeS :: (Size -> Size) -> Spacer
- 
revLs :: Layout -> Layout
- 
sepF :: Size -> F a b -> F a b
- 
sepLs :: Size -> Layout -> Layout
- 
sepS :: Size -> Spacer
- 
serCompLF :: (F a b, Orientation) -> F c a -> F c b
- 
sizeS :: Size -> Spacer
- 
spaceLs :: Spacer -> Layout -> Layout
- 
spacer1F :: Spacer -> F a b -> F a b
- 
spacerP :: Spacer -> Placer -> Placer
- 
spacersP :: Placer -> [Spacer] -> Placer
- 
stretchCaseS :: ((Bool, Bool) -> Spacer) -> Spacer
- 
tryLayoutK :: LayoutRequest -> Cont (K a b) Size
- 
unP :: Placer -> Placer1
- 
unS :: Spacer -> Spacer1
- 
untaggedListLF :: Placer -> [F a b] -> F (Int, a) b
- 
userLayoutF :: F a b -> F (Either (Path, Rect) a) (Either (Path, LayoutMessage) b)
- 
vBoxLs' :: Distance -> [Layout] -> Layout
- 
verticalLeftP :: Placer
- 
verticalLeftP' :: Distance -> Placer
- 
verticalP' :: Distance -> Placer
- 
vswap :: LayoutDir -> (a, a) -> (a, a)
- 
wAdj :: LayoutRequest -> Int -> Size
- 
wantedPos :: LayoutRequest -> Maybe (Point, Size, Alignment)
- 
xc :: LayoutDir -> Point -> Int
- 
yc :: LayoutDir -> Point -> Int
                                                                                                                                 
- Scroll bars:
 - 
hScrollF :: F a b -> F a b
- 
scrollF :: F a b -> F a b
- 
vScrollF :: F a b -> F a b
   - Shell (top level windows):
 - 
unmappedShellF :: [FRequest] -> K a b -> F c d -> F (Either a c) (Either b d)
- 
unmappedShellF' :: (ShellF -> ShellF) -> [FRequest] -> K a b -> F c d -> F (Either a c) (Either b d)
- 
unmappedSimpleShellF :: String -> F a b -> F a b
   - Shell (top level) windows:
 - 
data ShellF
- 
data DeleteWindowAction = ...
- 
class HasClickToType a where ...
- 
class HasVisible a where ...
- 
setDeleteQuit :: Bool -> Customiser ShellF
- 
setDeleteWindowAction :: Maybe DeleteWindowAction -> Customiser ShellF
- 
setInitPos :: Maybe Point -> Customiser ShellF
- 
shellF :: String -> F a b -> F a b
- 
shellF' :: Customiser ShellF -> String -> F a b -> F a b
         - Miscellaneous (the rest):
 - 
data PotRequest = ...
- 
type PotState = (Int, Int, Int)
- 
data SelCmd a = ...
- 
data SelEvt a = ...
- 
data ESelCmd a = ...
- 
data ESelEvt a = ...
- 
bubbleF :: F a b -> F a b
- 
bubblePopupF :: F a b -> F (PopupMsg a) b
- 
bubbleRootPopupF :: F a b -> F (PopupMsg a) b
- 
containerGroupF :: Rect -> Rect -> Int -> Button -> ModState -> F a b -> F (Either (Rect, Rect) a) (Either Rect b)
- 
eselectionF :: F (ESelCmd String) (ESelEvt String)
- 
getDeleteWindowActionMaybe' :: (ShellF -> ShellF) -> Maybe (Maybe DeleteWindowAction)
- 
grabScrollKeys :: Bool
- 
groupF :: [FRequest] -> K a b -> F c d -> F (Either a c) (Either b d)
- 
groupF' :: Sizing -> [FRequest] -> K a b -> F c d -> F (Either a c) (Either b d)
- 
hPotF :: F PotRequest (Int, Int, Int)
- 
hPotF' :: Bool -> Maybe Point -> F PotRequest (Int, Int, Int)
- 
invisibleGroupF :: Sizing -> [FRequest] -> [WindowAttributes] -> F a b -> F a b
- 
mapWindowK :: K Bool a
- 
oldHscrollF :: Bool -> (Point, Point) -> F a b -> F a b
- 
oldScrollF :: Bool -> (Point, Point) -> F a b -> F a b
- 
oldVscrollF :: Bool -> (Point, Point) -> F a b -> F a b
- 
popupGroupF :: (Size -> Point, [WindowAttributes], K a b) -> F c d -> F (PopupMsg c) d
- 
popupShellF :: String -> Maybe Point -> F a b -> F a (a, b)
- 
posPopupShellF :: String -> [WindowAttributes] -> F a b -> F (a, Maybe Point) (a, b)
- 
rootGroupF :: K a b -> F c d -> F (Either a c) (Either b d)
- 
rootPopupF :: (Size -> Point, [WindowAttributes], K a b) -> F c d -> F (PopupMsg c) d
- 
rootWindowF :: K a b -> F a b
- 
sF :: Bool -> Maybe Point -> [FRequest] -> K a b -> F c d -> F (Either a c) (Either b d)
- 
scrollShellF :: String -> (Point, Point) -> F a b -> F a b
- 
selectionF :: F (SelCmd String) (SelEvt String)
- 
setFocusMgr :: Bool -> Customiser ShellF
- 
sgroupF :: Sizing -> [FRequest] -> Maybe Rect -> K a b -> F c d -> F (Either a c) (Either b d)
- 
shellKF :: K a b -> F c d -> F (Either a c) (Either b d)
- 
shellKF' :: Customiser ShellF -> K a b -> F c d -> F (Either a c) (Either b d)
- 
simpleGroupF :: [WindowAttributes] -> F a b -> F a b
- 
simpleShellF :: String -> [WindowAttributes] -> F a b -> F a b
- 
swindowF :: [FRequest] -> Maybe Rect -> K a b -> F a b
- 
unmappedGroupF :: Sizing -> [FRequest] -> K a b -> F c d -> F (Either a c) (Either b d)
- 
unmappedSimpleShellF' :: Customiser ShellF -> String -> F a b -> F a b
- 
vPotF :: F PotRequest (Int, Int, Int)
- 
vPotF' :: Bool -> Maybe Point -> F PotRequest (Int, Int, Int)
- 
windowF :: [FRequest] -> K a b -> F a b
                                           
- Miscellaneous (the rest):
 - 
allcacheF :: F a b -> F a b
- 
bitmapdatacacheF :: F a b -> F a b
- 
bitmapfilecacheF :: F a b -> F a b
- 
colorcacheF :: F a b -> F a b
- 
doubleClickF :: Time -> F a b -> F a b
- 
fontcacheF :: F a b -> F a b
- 
fontcursorcacheF :: F a b -> F a b
- 
fstructcacheF :: F a b -> F a b
- 
gCcacheF :: F a b -> F a b
- 
shapeGroupMgr :: F a b -> F a b
          
- Bitmaps:
 - 
data BitmapFile = ...
 - Drawing:
 - 
data GCSpec = ...
- 
data Drawing b a = ...
- 
atomicD :: a -> Drawing b a
- 
attribD :: GCSpec -> Drawing a b -> Drawing a b
- 
fgD :: (Show a, ColorGen a) => a -> Drawing b c -> Drawing b c
- 
fontD :: (Show a, FontGen a) => a -> Drawing b c -> Drawing b c
- 
hardAttribD :: GCtx -> Drawing a b -> Drawing a b
- 
hboxD :: [Drawing a b] -> Drawing a b
- 
hboxD' :: Distance -> [Drawing a b] -> Drawing a b
- 
labelD :: a -> Drawing a b -> Drawing a b
- 
matrixD :: Int -> [Drawing a b] -> Drawing a b
- 
matrixD' :: Distance -> Int -> [Drawing a b] -> Drawing a b
- 
softAttribD :: [GCAttributes ColorSpec FontSpec] -> Drawing a b -> Drawing a b
- 
tableD :: Int -> [Drawing a b] -> Drawing a b
- 
tableD' :: Distance -> Int -> [Drawing a b] -> Drawing a b
- 
vboxD :: [Drawing a b] -> Drawing a b
- 
vboxD' :: Distance -> [Drawing a b] -> Drawing a b
                 - Drawing attributes:
 - 
data ColorSpec = ...
- 
data FontSpec = ...
- 
class ColorGen a where ...
- 
class FontGen a where ...
- 
data GCtx = ...
- 
colorSpec :: (Show a, ColorGen a) => a -> ColorSpec
- 
createGCtx :: (Show b, FontGen b, FudgetIO e, Show a, ColorGen a) => Drawable -> GCtx -> [GCAttributes a b] -> (GCtx -> e c d) -> e c d
- 
fontSpec :: (Show a, FontGen a) => a -> FontSpec
- 
gcBgA :: a -> [GCAttributes a FontSpec]
- 
gcFgA :: a -> [GCAttributes a FontSpec]
- 
gcFontA :: a -> [GCAttributes ColorSpec a]
- 
gctx2gc :: GCtx -> GCId
- 
pmCreateGCtx :: (Show b, FontGen b, FudgetIO e, Show a, ColorGen a) => PixmapId -> GCtx -> [GCAttributes a b] -> (GCtx -> e c d) -> e c d
- 
rootGCtx :: GCtx
- 
wCreateGCtx :: (Show b, FontGen b, FudgetIO e, Show a, ColorGen a) => GCtx -> [GCAttributes a b] -> (GCtx -> e c d) -> e c d
               - Drawing manipulation:
 - 
type DPath = [Int]
- 
deletePart :: Drawing a b -> [Int] -> Drawing a b
- 
drawingAnnots :: Drawing a b -> [(DPath, a)]
- 
drawingPart :: Drawing a b -> DPath -> Drawing a b
- 
mapLabelDrawing :: (a -> b) -> Drawing a c -> Drawing b c
- 
maybeDrawingPart :: Drawing a b -> DPath -> Maybe (Drawing a b)
- 
replacePart :: Drawing a b -> DPath -> Drawing a b -> Drawing a b
- 
up :: DPath -> DPath
- 
updatePart :: Drawing a b -> DPath -> (Drawing a b -> Drawing a b) -> Drawing a b
         - Fixed size drawings:
 - 
data FixedDrawing = ...
- 
data FixedColorDrawing = ...
  - Flexible line drawings:
 - 
data FlexibleDrawing = ...
- 
arc :: Int -> Int -> FlexibleDrawing
- 
ellipse :: FlexibleDrawing
- 
filledTriangleDown :: FlexibleDrawing
- 
filledTriangleUp :: FlexibleDrawing
- 
filler :: Bool -> Bool -> Int -> FlexibleDrawing
- 
flex :: (Rect -> [DrawCommand]) -> FlexibleDrawing
- 
flex' :: Size -> (Rect -> [DrawCommand]) -> FlexibleDrawing
- 
frame :: FlexibleDrawing
- 
frame' :: Size -> FlexibleDrawing
- 
hFiller :: Int -> FlexibleDrawing
- 
lAngleBracket :: FlexibleDrawing
- 
lbrace :: FlexibleDrawing
- 
lbrack :: FlexibleDrawing
- 
lpar :: FlexibleDrawing
- 
rAngleBracket :: FlexibleDrawing
- 
rbrace :: FlexibleDrawing
- 
rbrack :: FlexibleDrawing
- 
rpar :: FlexibleDrawing
- 
vFiller :: Int -> FlexibleDrawing
                    - Font metrics:
 - 
data FontStruct
- 
font_ascent :: FontStruct -> Int
- 
font_descent :: FontStruct -> Int
- 
font_id :: FontStruct -> FontId
- 
font_range :: FontStruct -> (Char, Char)
- 
linespace :: FontStruct -> Int
- 
next_pos :: FontStruct -> [Char] -> Int
- 
poslist :: FontStruct -> [Char] -> [Int]
- 
split_string :: FontStruct -> String -> Int -> (String, String, Int)
- 
string_bounds :: FontStruct -> [Char] -> Rect
- 
string_box_size :: FontStruct -> [Char] -> Point
- 
string_len :: FontStruct -> [Char] -> Int
- 
string_rect :: FontStruct -> [Char] -> Rect
             - Graphics:
 - 
data Gfx = ...
- 
class Graphic a where ...
- 
g :: (Graphic a) => a -> Drawing b Gfx
   - Miscellaneous (the rest):
 - 
data CharStruct = ...
- 
data FontDirection = ...
- 
data FontStructList = ...
- 
type Cont a b = (b -> a) -> a
- 
data MeasuredGraphics
- 
data PixmapImage = ...
- 
class PixmapGen a where ...
- 
abPoints :: Rect -> [Point]
- 
abPoints' :: Rect -> [Point]
- 
allocColor :: (FudgetIO c) => ColormapId -> RGB -> Cont (c a b) Color
- 
allocColorF :: ColormapId -> RGB -> Cont (F a b) Color
- 
allocColorPixel :: (FudgetIO c) => ColormapId -> RGB -> Cont (c a b) Pixel
- 
allocColorPixelF :: ColormapId -> RGB -> Cont (F a b) Pixel
- 
allocNamedColor :: (FudgetIO c) => ColormapId -> ColorName -> Cont (c a b) Color
- 
allocNamedColorDef :: (FudgetIO c) => ColormapId -> ColorName -> [Char] -> Cont (c a b) Color
- 
allocNamedColorDefPixel :: (FudgetIO c) => ColormapId -> ColorName -> [Char] -> (Pixel -> c a b) -> c a b
- 
allocNamedColorF :: ColormapId -> ColorName -> Cont (F a b) Color
- 
allocNamedColorPixel :: (FudgetIO c) => ColormapId -> ColorName -> Cont (c a b) Pixel
- 
allocNamedColorPixelF :: ColormapId -> ColorName -> Cont (F a b) Pixel
- 
annotChildren :: Drawing a b -> [(DPath, Drawing a b)]
- 
annotChildren' :: (a -> Bool) -> Drawing a b -> [(DPath, Drawing a b)]
- 
arc' :: Size -> Int -> Int -> FlexibleDrawing
- 
bFlex :: (Rect -> [DrawCommand]) -> FlexibleDrawing
- 
bFlex' :: Size -> (Rect -> [DrawCommand]) -> FlexibleDrawing
- 
bFlex2 :: (Rect -> [DrawCommand]) -> FlexibleDrawing
- 
bgD :: (Show a, ColorGen a) => a -> Drawing b c -> Drawing b c
- 
bitmapFromData :: BitmapData -> Cont (K a b) BitmapReturn
- 
blank :: FlexibleDrawing
- 
blank' :: Size -> FlexibleDrawing
- 
blankD :: Size -> Drawing a Gfx
- 
boxD :: [Drawing a b] -> Drawing a b
- 
boxVisibleD :: Int -> [Drawing a b] -> Drawing a b
- 
braces :: (FlexibleDrawing, FlexibleDrawing)
- 
bracks :: (FlexibleDrawing, FlexibleDrawing)
- 
convColorK :: (Show a, ColorGen a, FudgetIO d) => a -> (Pixel -> d b c) -> d b c
- 
convFontK :: (Show a, FontGen a, FudgetIO d) => a -> (FontStruct -> d b c) -> d b c
- 
convGCSpecK :: (Show b, FontGen b, FudgetIO e, Show a, ColorGen a) => FontStruct -> [GCAttributes a b] -> ([GCAttributes Pixel FontId] -> FontStruct -> e c d) -> e c d
- 
convGCattrsK :: (FudgetIO c) => [GCAttributes ColorName FontName] -> ([GCAttributes Pixel FontId] -> c a b) -> c a b
- 
convList :: (a -> (Maybe b -> c) -> c) -> [a] -> (Maybe b -> c) -> c
- 
corners :: Rect -> (Point, Point, Point, Point)
- 
createFontCursor :: Int -> Cont (K a b) CursorId
- 
createGC :: (FudgetIO c) => Drawable -> GCId -> GCAttributeList -> (GCId -> c a b) -> c a b
- 
createGCF :: Drawable -> GCId -> GCAttributeList -> (GCId -> F a b) -> F a b
- 
createPixmap :: Size -> Depth -> Cont (K a b) PixmapId
- 
doubleleft :: Rect -> Rect
- 
doubleright :: Rect -> Rect
- 
drawarc :: Int -> Int -> Rect -> [DrawCommand]
- 
drawingAnnotPart :: Drawing a b -> [Int] -> DPath
- 
drawingAnnotPart' :: (a -> Bool) -> Drawing a b -> [Int] -> DPath
- 
drawpoly :: [Point] -> [DrawCommand]
- 
ellipse' :: Size -> FlexibleDrawing
- 
emptyMG :: Size -> MeasuredGraphics
- 
emptyMG' :: LayoutRequest -> MeasuredGraphics
- 
extractParts :: Drawing a b -> (Drawing a b -> Maybe c) -> [(DPath, c)]
- 
fatD :: Drawing a b -> Drawing a b
- 
fillarc :: Int -> Int -> Rect -> [DrawCommand]
- 
filledEllipse :: FlexibleDrawing
- 
filledEllipse' :: Size -> FlexibleDrawing
- 
filledRectD :: Size -> Drawing a Gfx
- 
filledarc :: Int -> Int -> FlexibleDrawing
- 
filledarc' :: Size -> Int -> Int -> FlexibleDrawing
- 
fillpoly :: [Point] -> [DrawCommand]
- 
fsl2fs :: FontStructList -> FontStruct
- 
getWindowId :: Cont (K a b) Window
- 
getWindowRootPoint :: Cont (K a b) Point
- 
hMirror :: (Rect -> [Point]) -> Rect -> [Point]
- 
hboxcD :: [Drawing a b] -> Drawing a b
- 
hboxcD' :: Distance -> [Drawing a b] -> Drawing a b
- 
holeD :: Drawing a Gfx
- 
horizD :: Drawing a b -> Drawing a b
- 
horizD' :: Distance -> Drawing a b -> Drawing a b
- 
horizcD :: Drawing a b -> Drawing a b
- 
horizcD' :: Distance -> Drawing a b -> Drawing a b
- 
isVisibleDrawingPart :: Drawing a b -> DPath -> Bool
- 
loadFont :: (FudgetIO c) => FontName -> (FontId -> c a b) -> c a b
- 
loadFontF :: FontName -> Cont (F a b) FontId
- 
loadQueryFont :: (FudgetIO c) => FontName -> (Maybe FontStruct -> c a b) -> c a b
- 
loadQueryFontF :: FontName -> Cont (F a b) (Maybe FontStruct)
- 
mapLeafDrawing :: (a -> b) -> Drawing c a -> Drawing c b
- 
measureImageK :: (PixmapGen a) => a -> GCtx -> (MeasuredGraphics -> K b c) -> K b c
- 
measureText :: (Show a) => a -> GCtx -> (MeasuredGraphics -> b) -> b
- 
northwestD :: Drawing a b -> Drawing a b
- 
padD :: Distance -> Drawing a b -> Drawing a b
- 
padFD :: Int -> FlexibleDrawing -> FlexibleDrawing
- 
placedD :: Placer -> Drawing a b -> Drawing a b
- 
pmCreateGC :: (FudgetIO c) => PixmapId -> GCId -> GCAttributeList -> (GCId -> c a b) -> c a b
- 
pmCreateGCF :: PixmapId -> GCId -> GCAttributeList -> (GCId -> F a b) -> F a b
- 
queryColor :: (FudgetIO c) => ColormapId -> Pixel -> (Color -> c a b) -> c a b
- 
queryColorF :: ColormapId -> Pixel -> Cont (F a b) Color
- 
queryFont :: (FudgetIO c) => FontId -> (FontStruct -> c a b) -> c a b
- 
queryFontF :: FontId -> Cont (F a b) FontStruct
- 
readBitmapFile :: FilePath -> Cont (K a b) BitmapReturn
- 
rectD :: Size -> Drawing a Gfx
- 
safeLoadQueryFont :: (FudgetIO c) => FontName -> (FontStruct -> c a b) -> c a b
- 
safeLoadQueryFontF :: FontName -> (FontStruct -> F a b) -> F a b
- 
setFontCursor :: Int -> K a b -> K a b
- 
shrink :: Rect -> Rect
- 
size :: Point
- 
spacedD :: Spacer -> Drawing a b -> Drawing a b
- 
stackD :: [Drawing a b] -> Drawing a b
- 
triangleDown :: FlexibleDrawing
- 
trianglePoints :: Rect -> [Point]
- 
trianglePoints' :: Rect -> [Point]
- 
triangleUp :: FlexibleDrawing
- 
tryAllocColor :: (FudgetIO c) => ColormapId -> RGB -> (Maybe Color -> c a b) -> c a b
- 
tryAllocColorF :: ColormapId -> RGB -> Cont (F a b) (Maybe Color)
- 
tryAllocNamedColor :: (FudgetIO c) => ColormapId -> ColorName -> (Maybe Color -> c a b) -> c a b
- 
tryAllocNamedColorF :: ColormapId -> ColorName -> Cont (F a b) (Maybe Color)
- 
tryConvColorRGBK :: (FudgetIO c) => RGB -> (Maybe Pixel -> c a b) -> c a b
- 
vMirror :: (Rect -> [Point]) -> Rect -> [Point]
- 
vboxlD :: [Drawing a b] -> Drawing a b
- 
vboxlD' :: Distance -> [Drawing a b] -> Drawing a b
- 
vertD :: Drawing a b -> Drawing a b
- 
vertD' :: Distance -> Drawing a b -> Drawing a b
- 
vertlD :: Drawing a b -> Drawing a b
- 
vertlD' :: Distance -> Drawing a b -> Drawing a b
- 
visibleAncestor :: Drawing a b -> DPath -> [Int]
- 
wCreateGC :: (FudgetIO c) => GCId -> GCAttributeList -> (GCId -> c a b) -> c a b
- 
wCreateGCF :: GCId -> GCAttributeList -> (GCId -> F a b) -> F a b
- 
westD :: Drawing a b -> Drawing a b
                                                                                                                        
- Miscellaneous (the rest):
 - 
type Drawer = DrawCommand -> FRequest
- 
type Fms' a b c = MapState a (KEvent b) [KCommand c]
- 
type MapState a b c = a -> b -> (a, c)
- 
changeBackPixel :: (Show a, ColorGen a) => a -> K b c -> K b c
- 
changeBackPixmap :: (Show a, ColorGen a, Show b, ColorGen b) => a -> b -> Size -> [DrawCommand] -> K c d -> K c d
- 
changeBg :: ColorName -> K a b -> K a b
- 
changeGetBackPixel :: (Show a, ColorGen a) => a -> (Pixel -> K b c) -> K b c
- 
compK :: K a b -> K c d -> K (Either a c) (Either b d)
- 
darkGreyBgK :: K a b -> K a b
- 
defaultRootWindowF :: Cont (F a b) Window
- 
defaultRootWindowK :: Cont (K a b) Window
- 
defaultVisual :: (FudgetIO c) => (Visual -> c a b) -> c a b
- 
dynShapeK :: [GCAttributes ColorName FontName] -> (Size -> [DrawCommand]) -> K a b -> K (Either (Size -> [DrawCommand]) a) (Either c b)
- 
exitK :: a -> K b c
- 
getGeometryK :: Cont (K a b) (Rect, Int, Int)
- 
getWindowPropertyK :: Int -> Atom -> Bool -> Atom -> Cont (K a b) (Atom, Int, Int, Int, String)
- 
greyBgK :: K a b -> K a b
- 
internAtomK :: String -> Bool -> Cont (K a b) Atom
- 
knobBgK :: K a b -> K a b
- 
lightGreyBgK :: K a b -> K a b
- 
mapstateK :: (a -> KEvent b -> (a, [KCommand c])) -> a -> K b c
- 
parK :: K a b -> K a b -> K a b
- 
queryPointerK :: Cont (K a b) (Bool, Point, Point, ModState)
- 
queryTreeF :: Cont (F a b) (Window, Window, [Window])
- 
queryTreeK :: Cont (K a b) (Window, Window, [Window])
- 
quitK :: (K (Either String Bool) a -> K (Either String Bool) a) -> K b c
- 
reportK :: K a () -> K a ()
- 
shapeK :: (Size -> [DrawCommand]) -> K a b -> K a b
- 
simpleF :: String -> (Drawer -> Drawer -> Fms' a b c) -> Size -> a -> F b c
- 
simpleK :: (Drawer -> Drawer -> Fms' a b c) -> Size -> a -> K b c
- 
unmapWindowK :: K a b -> K a b
- 
wmDeleteWindowK :: (Atom -> K a b) -> K a b
- 
wmK :: Maybe (K (Either String Bool) a -> K (Either String Bool) a) -> K (Either String Bool) a
                                 
- A stream processor that splits a stream of pairs:
 - 
splitSP :: SP (a, b) (Either a b)
 - Delay the activation of a stream processor or fudget:
 - 
delaySP :: SP a b -> SP a b
 - Stream processor combinators that create circular connections:
 - 
loopLeftSP :: SP (Either a b) (Either a c) -> SP b c
- 
loopSP :: SP a a -> SP a a
  - Stream processor equivalents of some common list processing functions:
 - 
chopSP :: ((a -> SP b a) -> SP b a) -> SP b a
- 
concatMapAccumlSP :: (a -> b -> (a, [c])) -> a -> SP b c
- 
concatMapSP :: (a -> [b]) -> SP a b
- 
concatSP :: SP [a] a
- 
filterSP :: (a -> Bool) -> SP a a
- 
idSP :: SP a a
- 
mapAccumlSP :: (a -> b -> (a, c)) -> a -> SP b c
- 
mapSP :: (a -> b) -> SP a b
- 
splitAtElemSP :: (a -> Bool) -> Cont (SP a b) [a]
- 
zipSP :: [a] -> SP b (a, b)
          - Stream processor input operation:
 - 
getSP :: Cont (SP a b) a
 - Stream processor manipulation:
 - 
startupSP :: [a] -> SP a b -> SP a b
 - Stream processor output operation:
 - 
putSP :: a -> SP b a -> SP b a
 - The function that turns a stream processor into a list processing function:
 - 
runSP :: SP a b -> [a] -> [b]
 - The idle stream processor:
 - 
nullSP :: SP a b
 - The type of plain stream processors:
 - 
data SP a b
 - Miscellaneous (the rest):
 - 
data DynMsg b a = ...
- 
type DynSPMsg a b = DynMsg a (SP a b)
- 
type SPm a b c = Mk (SP a b) c
- 
type SPms a b c d = Ms (SP a b) c d
- 
type Cont a b = (b -> a) -> a
- 
class StreamProcIO a where ...
- 
appendStartSP :: [a] -> SP b a -> SP b a
- 
bindSPm :: SPm a b c -> (c -> SPm a b d) -> SPm a b d
- 
bindSPms :: SPms a b c d -> (d -> SPms a b c e) -> SPms a b c e
- 
compEitherSP :: SP a b -> SP c d -> SP (Either a c) (Either b d)
- 
compMsgSP :: SP a b -> SP c d -> SP (Message a c) (Message b d)
- 
compSP :: SP a b -> SP c d -> SP (Either a c) (Either b d)
- 
concSP :: SP [a] a
- 
concmapSP :: (a -> [b]) -> SP a b
- 
dynforkmerge :: (Eq a) => SP (a, DynSPMsg b c) (a, c)
- 
feedSP :: a -> [a] -> SP a b -> SP a b
- 
filterJustSP :: SP (Maybe a) a
- 
filterLeftSP :: SP (Either a b) a
- 
filterRightSP :: SP (Either a b) b
- 
getSPm :: SPm a b a
- 
getSPms :: SPms a b c a
- 
idHighSP :: SP a b -> SP (Message a c) (Message b c)
- 
idLeftSP :: SP a b -> SP (Either c a) (Either c b)
- 
idLowSP :: SP a b -> SP (Message c a) (Message c b)
- 
idRightSP :: SP a b -> SP (Either a c) (Either b c)
- 
idempotSP :: (Eq a) => SP a a
- 
interpSP :: (a -> b -> b) -> ((c -> b) -> b) -> b -> SP c a -> b
- 
loadSPms :: SPms a b c c
- 
loopOnlySP :: SP a a -> SP a b
- 
loopThroughRightSP :: SP (Either a b) (Either c d) -> SP c a -> SP b d
- 
mapFilterSP :: (a -> Maybe b) -> SP a b
- 
mapSPms :: (a -> b) -> SPms c d e a -> SPms c d e b
- 
mapstateSP :: (a -> b -> (a, [c])) -> a -> SP b c
- 
monadSP :: SPm a b () -> SP a b
- 
nullSPm :: SPm a b ()
- 
nullSPms :: SPms a b c ()
- 
parSP :: SP a b -> SP a b -> SP a b
- 
postMapSP :: (a -> b) -> SP c a -> SP c b
- 
preMapSP :: SP a b -> (c -> a) -> SP c b
- 
prepostMapSP :: (a -> b) -> (c -> d) -> SP b c -> SP a d
- 
pullSP :: SP a b -> ([b], SP a b)
- 
putSPm :: a -> SPm b a ()
- 
putSPms :: a -> SPms b a c ()
- 
puts :: (StreamProcIO c) => [a] -> c b a -> c b a
- 
putsSP :: [a] -> SP b a -> SP b a
- 
putsSPm :: [a] -> SPm b a ()
- 
putsSPms :: [a] -> SPms b a c ()
- 
seqSP :: SP a b -> SP a b -> SP a b
- 
serCompSP :: SP a b -> SP c a -> SP c b
- 
stateMonadSP :: a -> SPms b c a d -> (d -> SP b c) -> SP b c
- 
stepSP :: [a] -> Cont (SP b a) b
- 
storeSPms :: a -> SPms b c a ()
- 
thenSPm :: SPm a b () -> SPm a b c -> SPm a b c
- 
thenSPms :: SPms a b c () -> SPms a b c d -> SPms a b c d
- 
toBothSP :: SP a (Either a a)
- 
toSPm :: SP a b -> SPm a b ()
- 
unitSPm :: a -> SPm b c a
- 
unitSPms :: a -> SPms b c d a
- 
walkSP :: SP a b -> a -> ([b], SP a b)
                                                           
- A fudget that outputs ticks after specific delays and/or at specific intervals:
 - 
data Tick = ...
- 
timerF :: F (Maybe (Int, Int)) Tick
  - File system access:
 - 
readDirF :: F String (String, Either D_IOError [String])
- 
readFileF :: F String (String, Either D_IOError String)
- 
writeFileF :: F (String, String) (String, Either D_IOError ())
   - Haskell Dialogue IO:
 - 
hIO :: (FudgetIO c) => Request -> (_Response -> c a b) -> c a b
- 
hIOF :: Request -> (Response -> F a b) -> F a b
- 
hIOSucc :: (FudgetIO c) => Request -> c a b -> c a b
- 
hIOSuccF :: Request -> F a b -> F a b
- 
hIOerr :: (FudgetIO c) => Request -> (D_IOError -> c a b) -> (_Response -> c a b) -> c a b
- 
hIOerrF :: Request -> (IOError -> F a b) -> (Response -> F a b) -> F a b
- 
haskellIO :: (FudgetIO c) => Request -> (Response -> c a b) -> c a b
- 
haskellIOF :: Request -> (Response -> F a b) -> F a b
        - Sockets:
 - 
asyncTransceiverF :: Socket -> F String String
- 
asyncTransmitterF :: Socket -> F String a
- 
openFileAsSocketErrF :: (FudgetIO c) => String -> String -> (D_IOError -> c a b) -> (Socket -> c a b) -> c a b
- 
openFileAsSocketF :: (FudgetIO c) => String -> String -> (Socket -> c a b) -> c a b
- 
openLSocketErrF :: (FudgetIO c) => Port -> (D_IOError -> c a b) -> (LSocket -> c a b) -> c a b
- 
openLSocketF :: (FudgetIO c) => Port -> (LSocket -> c a b) -> c a b
- 
openSocketErrF :: (FudgetIO c) => Host -> Port -> (D_IOError -> c a b) -> (Socket -> c a b) -> c a b
- 
openSocketF :: (FudgetIO c) => Host -> Port -> (Socket -> c a b) -> c a b
- 
receiverF :: Socket -> F a String
- 
transceiverF :: Socket -> F [Char] String
- 
transmitterF :: Socket -> F [Char] a
           - Stdio:
 - 
appendChanK :: (FudgetIO c) => String -> String -> c a b -> c a b
- 
echoK :: (FudgetIO c) => [Char] -> c a b -> c a b
- 
inputLinesSP :: SP [Char] [Char]
- 
linesSP :: SP Char [Char]
- 
outputF :: String -> F String a
- 
stderrF :: F String a
- 
stdinF :: F a String
- 
stdioF :: F String String
- 
stdoutF :: F String a
         - Miscellaneous (the rest):
 - 
asyncTransmitterF' :: Socket -> F String ()
- 
closerF :: Socket -> F a b
- 
getLocalTime :: (FudgetIO c) => (CalendarTime -> c a b) -> c a b
- 
getTime :: (FudgetIO c) => (ClockTime -> c a b) -> c a b
- 
ioF :: K a b -> F a b
- 
receiverF' :: Socket -> F a String
- 
subProcessF :: String -> F [Char] (Either String String)
- 
transmitterF' :: Socket -> F [Char] ()
- 
unsafeGetDLValue :: DLValue -> a
         
- Sockets:
 - 
sIO :: (FudgetIO c) => SocketRequest -> (SocketResponse -> c a b) -> c a b
- 
sIOerr :: (FudgetIO c) => SocketRequest -> (D_IOError -> c a b) -> (SocketResponse -> c a b) -> c a b
- 
sIOstr :: (FudgetIO c) => SocketRequest -> (String -> c a b) -> c a b
- 
sIOsucc :: (FudgetIO c) => SocketRequest -> c a b -> c a b
- 
select :: (FudgetIO c) => [Descriptor] -> c a b -> c a b
     - The combinator that connects the main fudget to the Haskell I/O system:
 - 
data Fudlogue
- 
fudlogue :: F a b -> IO ()
- 
fudlogue' :: Customiser Fudlogue -> F a b -> IO ()
   - Miscellaneous (the rest):
 - 
type Cont a b = (b -> a) -> a
- 
class HasCache a where ...
- 
class FudgetIO a where ...
- 
adjustBorderWidth :: Int -> Point -> Point
- 
autumnize :: [a] -> [a]
- 
border_width :: Int
- 
cmdContF :: FRequest -> (FResponse -> Maybe a) -> Cont (F b c) a
- 
cmdContK :: FRequest -> (FResponse -> Maybe a) -> Cont (K b c) a
- 
cmdContK' :: KCommand a -> (KEvent b -> Maybe c) -> Cont (K b a) c
- 
cmdContLow :: (FudgetIO d) => FRequest -> (FResponse -> Maybe a) -> (a -> d b c) -> d b c
- 
cmdContMsg :: (FudgetIO d) => KCommand a -> (KEvent b -> Maybe c) -> (c -> d b a) -> d b a
- 
cmdContSP :: a -> (b -> Maybe c) -> Cont (SP b a) c
- 
contMap :: (StreamProcIO c) => (a -> (b -> c a b) -> c a b) -> c a b
- 
conts :: (a -> Cont b c) -> [a] -> Cont b [c]
- 
dropSP :: (a -> Maybe b) -> (b -> SP a c) -> SP a c
- 
fContWrap :: Cont (FSP a b) c -> Cont (F a b) c
- 
getBWidth :: [WindowChanges] -> Maybe Int
- 
getHigh :: (FudgetIO c) => (a -> c a b) -> c a b
- 
getLeftSP :: (a -> SP (Either a b) c) -> SP (Either a b) c
- 
getLow :: (FudgetIO c) => (FResponse -> c a b) -> c a b
- 
getRightSP :: (a -> SP (Either b a) c) -> SP (Either b a) c
- 
kContWrap :: Cont (KSP a b) c -> Cont (K a b) c
- 
kernelF :: K a b -> F a b
- 
kernelTag :: Path
- 
openDisplay :: DisplayName -> Cont (F a b) Display
- 
putHigh :: (FudgetIO c) => a -> c b a -> c b a
- 
putLow :: (FudgetIO c) => FRequest -> c a b -> c a b
- 
putLows :: (FudgetIO c) => [FRequest] -> c a b -> c a b
- 
putMsgs :: (FudgetIO c) => [KCommand a] -> c b a -> c b a
- 
splogue :: SP (Path, Response) (Path, Request) -> Dialogue
- 
tagEventsSP :: F a b -> SP (Path, Response) (Path, Request)
- 
tagRequestsSP :: [_Response] -> SP (Either (Path, _Request) _Response) (Either (Path, _Response) _Request)
- 
toKernel :: [a] -> [Message (Path, a) b]
- 
tryGet :: Cont a (Maybe b) -> Cont a b -> Cont a b
- 
tryM :: Cont a (Maybe b) -> a -> Cont a b
- 
waitForF :: (a -> Maybe b) -> Cont (F a c) b
- 
waitForFu :: (KEvent a -> Maybe b) -> Cont (F a c) b
- 
waitForK :: (KEvent a -> Maybe b) -> Cont (K a c) b
- 
waitForSP :: (a -> Maybe b) -> (b -> SP a c) -> SP a c
- 
windowKF :: (Rect -> FRequest) -> Bool -> Bool -> [FRequest] -> Maybe Rect -> K a b -> F c d -> F (Either a c) (Either b d)
- 
xcommand :: (FudgetIO c) => XCommand -> c a b -> c a b
- 
xcommandF :: XCommand -> F a b -> F a b
- 
xcommandK :: XCommand -> K a b -> K a b
- 
xcommands :: (FudgetIO c) => [XCommand] -> c a b -> c a b
- 
xcommandsF :: [XCommand] -> F a b -> F a b
- 
xcommandsK :: [XCommand] -> K a b -> K a b
- 
xrequest :: (FudgetIO d) => XRequest -> (XResponse -> Maybe a) -> (a -> d b c) -> d b c
- 
xrequestF :: XRequest -> (XResponse -> Maybe a) -> Cont (F b c) a
- 
xrequestK :: XRequest -> (XResponse -> Maybe a) -> Cont (K b c) a
                                                 
- Font metrics:
 - 
data FontStruct
 - Miscellaneous (the rest):
 - 
data FRequest = ...
- 
data FResponse = ...
- 
data LayoutMessage
- 
data LayoutResponse
- 
data XCommand = ...
- 
data XRequest = ...
- 
type Command = XCommand
- 
data BitmapData = ...
- 
type DisplayName = String
- 
data PropertyMode = ...
- 
data Drawable = ...
- 
data KeyCode = ...
- 
data Pressed = ...
- 
data Detail = ...
- 
data Mode = ...
- 
data Visibility = ...
- 
data ClientData = ...
- 
data XEvent = ...
- 
type Event = XEvent
- 
data XResponse = ...
- 
data BitmapReturn = ...
- 
data FontStructList
- 
data DLValue
- 
data SocketRequest = ...
- 
data SocketResponse = ...
- 
type Port = Int
- 
type Host = String
- 
type Peer = Host
- 
data Socket = ...
- 
data LSocket = ...
- 
data Timer = ...
- 
type AsyncInput = (Descriptor, AEvent)
- 
data Descriptor = ...
- 
data AEvent = ...
- 
type DLHandle = Int
- 
type KeyLookup = String
- 
type Width = Int
- 
data Pixel = ...
- 
type PlaneMask = Pixel
- 
data RGB = ...
- 
data Color = ...
- 
data Display = ...
- 
type XDisplay = Display
- 
data Selection = ...
- 
data BackingStore = ...
- 
data GrabPointerResult = ...
- 
data GCFunction = ...
- 
data GCLineStyle = ...
- 
data GCCapStyle = ...
- 
data GCSubwindowMode = ...
- 
data GCFillStyle = ...
- 
data GCAttributes a b = ...
- 
type GCAttributeList = [GCAttributes Pixel FontId]
- 
data WindowAttributes = ...
- 
data WindowChanges = ...
- 
data StackMode = ...
- 
data EventMask = ...
- 
data Gravity = ...
- 
data ShapeKind = ...
- 
data ShapeOperation = ...
- 
data Ordering' = ...
- 
type RmClass = String
- 
type RmName = String
- 
type RmQuery = (RmClass, RmName)
- 
type RmSpec = [RmQuery]
- 
type RmValue = String
- 
type RmDatabase = Int
- 
data Modifiers = ...
- 
data Button = ...
- 
type ModState = [Modifiers]
- 
type KeySym = String
- 
data WindowId = ...
- 
type Window = WindowId
- 
type XWId = WindowId
- 
data PixmapId = ...
- 
data FontId = ...
- 
data GCId = ...
- 
data CursorId = ...
- 
data ColormapId = ...
- 
data Atom = ...
- 
type ColorName = String
- 
type FontName = String
- 
type Time = Int
- 
type Depth = Int
- 
data ImageFormat = ...
- 
data DisplayClass = ...
- 
data VisualID = ...
- 
data Visual = ...
- 
data DrawCommand = ...
- 
data CoordMode = ...
- 
data Shape = ...
- 
bits_per_rgb :: Visual -> Int
- 
black :: Pixel
- 
blue_mask :: Visual -> Word
- 
button :: XEvent -> Button
- 
clEventMask :: [EventMask]
- 
clModifiers :: [Modifiers]
- 
clearArea :: Rect -> Bool -> FRequest
- 
clearWindow :: FRequest
- 
clearWindowExpose :: XCommand
- 
colorPixel :: Color -> Pixel
- 
colorRGB :: Color -> RGB
- 
copyFromParent :: Depth
- 
count :: XEvent -> Int
- 
defaultColormap :: ColormapId
- 
detail :: XEvent -> Detail
- 
draw :: Drawable -> GCId -> DrawCommand -> FRequest
- 
drawCircle :: Point -> Int -> DrawCommand
- 
drawMany :: Drawable -> [(GCId, [DrawCommand])] -> FRequest
- 
fillCircle :: Point -> Int -> DrawCommand
- 
gcoff :: XCommand -> PixmapId
- 
gcon :: XCommand -> PixmapId
- 
green_mask :: Visual -> Word
- 
invcol :: Pixel -> Pixel -> Pixel
- 
invertColorGCattrs :: Pixel -> Pixel -> [GCAttributes Pixel a]
- 
invertGCattrs :: [GCAttributes Pixel a]
- 
keyLookup :: XEvent -> KeyLookup
- 
keySym :: XEvent -> KeySym
- 
keycode :: XEvent -> KeyCode
- 
layoutRequestCmd :: LayoutRequest -> FRequest
- 
major_code :: XEvent -> Int
- 
map_entries :: Visual -> Int
- 
minor_code :: XEvent -> Int
- 
mode :: XEvent -> Mode
- 
moveResizeWindow :: Rect -> XCommand
- 
moveWindow :: Point -> XCommand
- 
noDisplay :: Display
- 
noWindow :: WindowId
- 
none :: PixmapId
- 
parentRelative :: PixmapId
- 
pmCopyArea :: PixmapId -> GCId -> Drawable -> Rect -> Point -> FRequest
- 
pmCopyPlane :: PixmapId -> GCId -> Drawable -> Rect -> Point -> Int -> FRequest
- 
pmCreatePutImage :: PixmapId -> GCId -> Rect -> ImageFormat -> [Pixel] -> FRequest
- 
pmDraw :: PixmapId -> GCId -> DrawCommand -> FRequest
- 
pmDrawArc :: PixmapId -> GCId -> Rect -> Int -> Int -> FRequest
- 
pmDrawImageString :: PixmapId -> GCId -> Point -> String -> FRequest
- 
pmDrawImageString16 :: PixmapId -> GCId -> Point -> String -> FRequest
- 
pmDrawImageStringPS :: PixmapId -> GCId -> Point -> PackedString -> FRequest
- 
pmDrawLine :: PixmapId -> GCId -> Line -> FRequest
- 
pmDrawLines :: PixmapId -> GCId -> CoordMode -> [Point] -> FRequest
- 
pmDrawMany :: PixmapId -> [(GCId, [DrawCommand])] -> FRequest
- 
pmDrawPoint :: PixmapId -> GCId -> Point -> FRequest
- 
pmDrawRectangle :: PixmapId -> GCId -> Rect -> FRequest
- 
pmDrawString :: PixmapId -> GCId -> Point -> String -> FRequest
- 
pmDrawString16 :: PixmapId -> GCId -> Point -> String -> FRequest
- 
pmDrawStringPS :: PixmapId -> GCId -> Point -> PackedString -> FRequest
- 
pmFillArc :: PixmapId -> GCId -> Rect -> Int -> Int -> FRequest
- 
pmFillPolygon :: PixmapId -> GCId -> Shape -> CoordMode -> [Point] -> FRequest
- 
pmFillRectangle :: PixmapId -> GCId -> Rect -> FRequest
- 
pos :: XEvent -> Point
- 
propModeAppend :: PropertyMode
- 
propModePrepend :: PropertyMode
- 
propModeReplace :: PropertyMode
- 
rect :: XEvent -> Rect
- 
red_mask :: Visual -> Word
- 
resizeWindow :: Point -> XCommand
- 
rmNothing :: Int
- 
rootGC :: GCId
- 
rootPos :: XEvent -> Point
- 
rootWindow :: WindowId
- 
state :: XEvent -> ModState
- 
time :: XEvent -> Time
- 
type' :: XEvent -> Pressed
- 
visualClass :: Visual -> DisplayClass
- 
visualid :: Visual -> VisualID
- 
wCopyArea :: GCId -> Drawable -> Rect -> Point -> FRequest
- 
wCopyPlane :: GCId -> Drawable -> Rect -> Point -> Int -> FRequest
- 
wCreatePutImage :: GCId -> Rect -> ImageFormat -> [Pixel] -> FRequest
- 
wDraw :: GCId -> DrawCommand -> FRequest
- 
wDrawArc :: GCId -> Rect -> Int -> Int -> FRequest
- 
wDrawCircle :: GCId -> Point -> Int -> FRequest
- 
wDrawImageString :: GCId -> Point -> String -> FRequest
- 
wDrawImageString16 :: GCId -> Point -> String -> FRequest
- 
wDrawImageStringPS :: GCId -> Point -> PackedString -> FRequest
- 
wDrawLine :: GCId -> Line -> FRequest
- 
wDrawLines :: GCId -> CoordMode -> [Point] -> FRequest
- 
wDrawMany :: [(GCId, [DrawCommand])] -> FRequest
- 
wDrawPoint :: GCId -> Point -> FRequest
- 
wDrawRectangle :: GCId -> Rect -> FRequest
- 
wDrawString :: GCId -> Point -> String -> FRequest
- 
wDrawString16 :: GCId -> Point -> String -> FRequest
- 
wDrawStringPS :: GCId -> Point -> PackedString -> FRequest
- 
wFillArc :: GCId -> Rect -> Int -> Int -> FRequest
- 
wFillCircle :: GCId -> Point -> Int -> FRequest
- 
wFillPolygon :: GCId -> Shape -> CoordMode -> [Point] -> FRequest
- 
wFillRectangle :: GCId -> Rect -> FRequest
- 
white :: Pixel
- 
xyBitmap :: ImageFormat
- 
xyPixmap :: ImageFormat
- 
zPixmap :: ImageFormat
                                                                                                                                                                                              
- Displaying text:
 - 
data ListRequest a = ...
- 
appendItems :: [a] -> ListRequest a
- 
applyListRequest :: ListRequest a -> [a] -> [a]
- 
changeItems :: Int -> [a] -> ListRequest a
- 
deleteItems :: Int -> Int -> ListRequest a
- 
highlightItems :: [Int] -> ListRequest a
- 
insertItems :: Int -> [a] -> ListRequest a
- 
pickItem :: Int -> ListRequest a
- 
replaceAll :: [a] -> ListRequest a
- 
replaceAllFrom :: Int -> [a] -> ListRequest a
- 
replaceItems :: Int -> Int -> [a] -> ListRequest a
           - The Fudget type:
 - 
type TEvent = (Path, FResponse)
- 
type TCommand = (Path, FRequest)
- 
type FEvent a = Message TEvent a
- 
type FCommand a = Message TCommand a
- 
type Fudget a b = F a b
- 
type FSP a b = SP (FEvent a) (FCommand b)
- 
data F a b = ...
       - The fudget kernel type:
 - 
type Fa a b c d = SP (Message a c) (Message b d)
- 
type KEvent a = Message FResponse a
- 
type KCommand a = Message FRequest a
- 
type KSP a b = SP (KEvent a) (KCommand b)
- 
data K a b = ...
     - The type of plain stream processors:
 - 
data SP a b
 - Types for messages from data entry fields:
 - 
data InputMsg a = ...
- 
inputChange :: a -> InputMsg a
- 
inputDone :: InputMsg a -> Maybe a
- 
inputLeaveDone :: InputMsg a -> Maybe a
- 
inputMsg :: a -> InputMsg a
- 
mapInp :: (a -> b) -> InputMsg a -> InputMsg b
- 
stripInputMsg :: InputMsg a -> a
- 
tstInp :: (a -> b) -> InputMsg a -> b
        - Miscellaneous (the rest):
 - 
data Direction = ...
- 
data FRequest
- 
data FResponse
- 
data Message a b = ...
- 
type Path = [Direction]
- 
data PopupMsg a = ...
- 
aHigh :: (a -> b) -> Message c a -> Message c b
- 
aLow :: (a -> b) -> Message a c -> Message b c
- 
absPath :: Path -> Path -> Path
- 
boundingRect :: Rect -> Rect -> Rect
- 
diffRect :: Rect -> Rect -> [Rect]
- 
ff :: FSP a b -> F a b
- 
here :: Path
- 
inputButtonKey :: KeySym
- 
inputLeaveKey :: KeySym
- 
intersectRects :: [Rect] -> Rect -> [Rect]
- 
isHigh :: Message a b -> Bool
- 
isLow :: Message a b -> Bool
- 
kk :: KSP a b -> K a b
- 
listEnd :: Int
- 
mapMessage :: (a -> b) -> (c -> d) -> Message a c -> Message b d
- 
message :: (a -> b) -> (c -> b) -> Message a c -> b
- 
moveDrawCommand :: DrawCommand -> Point -> DrawCommand
- 
moveDrawCommands :: [DrawCommand] -> Point -> [DrawCommand]
- 
overlaps :: Rect -> Rect -> Bool
- 
path :: Path -> (Direction, Path)
- 
pushMsg :: (Functor b) => Message (b a) (b c) -> b (Message a c)
- 
showPath :: Path -> String
- 
stripHigh :: Message a b -> Maybe b
- 
stripLow :: Message a b -> Maybe a
- 
subPath :: Path -> Path -> Bool
- 
turn :: Direction -> Path -> Path
- 
unF :: F a b -> FSP a b
- 
unK :: K a b -> KSP a b
                                  
- Environment:
 - 
argFlag :: [Char] -> Bool -> Bool
- 
argKey :: [Char] -> [Char] -> [Char]
- 
argReadKey :: (Read a, Show a) => [Char] -> a -> a
- 
args :: [[Char]]
- 
bgColor :: ColorName
- 
buttonFont :: FontName
- 
defaultFont :: FontName
- 
fgColor :: ColorName
- 
menuFont :: FontName
- 
options :: [([Char], [Char])]
- 
paperColor :: ColorName
- 
shadowColor :: ColorName
- 
shineColor :: ColorName
             - Geometry, part 1:
 - 
data Point = ...
- 
type Size = Point
- 
data Line = ...
- 
data Rect = ...
- 
lL :: Int -> Int -> Int -> Int -> Line
- 
origin :: Point
- 
pP :: Int -> Int -> Point
- 
rR :: Int -> Int -> Int -> Int -> Rect
- 
rectpos :: Rect -> Point
- 
rectsize :: Rect -> Size
- 
xcoord :: Point -> Int
- 
ycoord :: Point -> Int
            - Geometry, part 2:
 - 
=.> :: Point -> Point -> Bool
- 
confine :: Rect -> Rect -> Rect
- 
freedom :: Rect -> Rect -> Point
- 
growrect :: Rect -> Point -> Rect
- 
inRect :: Point -> Rect -> Bool
- 
moveline :: Line -> Point -> Line
- 
moverect :: Rect -> Point -> Rect
- 
pMax :: [Point] -> Point
- 
pMin :: [Point] -> Point
- 
padd :: Point -> Point -> Point
- 
plim :: Point -> Point -> Point -> Point
- 
pmax :: Point -> Point -> Point
- 
pmin :: Point -> Point -> Point
- 
posrect :: Rect -> Point -> Rect
- 
psub :: Point -> Point -> Point
- 
rectMiddle :: Rect -> Point
- 
rsub :: Rect -> Rect -> Point
- 
scale :: (RealFrac a, Integral c, Integral b) => a -> b -> c
- 
scalePoint :: (RealFrac a) => a -> Point -> Point
- 
sizerect :: Rect -> Size -> Rect
                    - Various utility functions for pairs and lists:
 - 
aboth :: (a -> b) -> (a, a) -> (b, b)
- 
anth :: Int -> (a -> a) -> [a] -> [a]
- 
gmap :: (a -> [b] -> [b]) -> (c -> a) -> [c] -> [b]
- 
issubset :: (Eq a) => [a] -> [a] -> Bool
- 
lhead :: [a] -> [b] -> [b]
- 
loop :: (a -> a) -> a
- 
lsplit :: [a] -> [b] -> ([b], [b])
- 
ltail :: [a] -> [b] -> [b]
- 
mapPair :: (a -> b, c -> d) -> (a, c) -> (b, d)
- 
number :: Int -> [a] -> [(Int, a)]
- 
oo :: (a -> b) -> (c -> d -> a) -> c -> d -> b
- 
pair :: a -> b -> (a, b)
- 
pairwith :: (a -> b) -> a -> (a, b)
- 
part :: (a -> Bool) -> [a] -> ([a], [a])
- 
remove :: (Eq a) => a -> [a] -> [a]
- 
replace :: (Eq a) => (a, b) -> [(a, b)] -> [(a, b)]
- 
swap :: (a, b) -> (b, a)
- 
unionmap :: (Eq b) => (a -> [b]) -> [a] -> [b]
                  - Various utility functions for the 
Either type:
 - 
filterLeft :: [Either a b] -> [a]
- 
filterRight :: [Either a b] -> [b]
- 
fromLeft :: Either a b -> a
- 
fromRight :: Either a b -> b
- 
isLeft :: Either a b -> Bool
- 
isRight :: Either a b -> Bool
- 
mapEither :: (a -> b) -> (c -> d) -> Either a c -> Either b d
- 
splitEitherList :: [Either a b] -> ([a], [b])
- 
stripEither :: Either a a -> a
- 
stripLeft :: Either a b -> Maybe a
- 
stripRight :: Either a b -> Maybe b
- 
swapEither :: Either a b -> Either b a
            - Various utility functions for the 
Maybe type.:
 - 
isM :: Maybe a -> Bool
- 
mapMaybe :: (a -> b) -> Maybe a -> Maybe b
- 
mapfilter :: (a -> Maybe b) -> [a] -> [b]
- 
plookup :: (a -> Bool) -> [(a, b)] -> Maybe b
- 
stripMaybe :: Maybe a -> a
- 
stripMaybeDef :: a -> Maybe a -> a
      - Miscellaneous (the rest):
 - 
data AFilePath
- 
type Cont a b = (b -> a) -> a
- 
aFilePath :: FilePath -> AFilePath
- 
argKeyList :: [Char] -> [[Char]] -> [[Char]]
- 
bitand :: Int -> Int -> Int
- 
bitxor :: Int -> Int -> Int
- 
compactPath :: AFilePath -> AFilePath
- 
defaultPosition :: Maybe Point
- 
defaultSep :: (Num a) => a
- 
defaultSize :: Maybe Point
- 
diag :: Int -> Point
- 
edgeWidth :: Int
- 
expandTabs :: Int -> [Char] -> [Char]
- 
extendPath :: AFilePath -> String -> AFilePath
- 
filePath :: AFilePath -> FilePath
- 
ifC :: (a -> a) -> Bool -> a -> a
- 
inputBg :: ColorName
- 
inputFg :: ColorName
- 
isAbsolute :: AFilePath -> Bool
- 
joinPaths :: AFilePath -> AFilePath -> AFilePath
- 
labelFont :: FontName
- 
line2rect :: Line -> Rect
- 
look3d :: Bool
- 
lunconcat :: [[a]] -> [b] -> [[b]]
- 
mapHigh :: (a -> [b]) -> SP (Message c a) (Message c b)
- 
mapList :: (a -> b) -> [a] -> [b]
- 
mapLow :: (a -> [b]) -> SP (Message a c) (Message b c)
- 
mapstateHigh :: (a -> b -> (a, [c])) -> a -> SP (Message d b) (Message d c)
- 
mapstateLow :: (a -> b -> (a, [c])) -> a -> SP (Message b d) (Message c d)
- 
new3d :: Bool
- 
pathHead :: AFilePath -> AFilePath
- 
pathLength :: AFilePath -> Int
- 
pathRelativeTo :: AFilePath -> AFilePath -> AFilePath
- 
pathTail :: AFilePath -> String
- 
progName :: String
- 
rect2line :: Rect -> Line
- 
resourceName :: String
- 
rmBS :: [Char] -> [Char]
- 
rmax :: Rect -> Rect -> Rect
- 
rootPath :: AFilePath
- 
setFst :: (a, b) -> c -> (c, b)
- 
setSnd :: (a, b) -> c -> (a, c)
- 
thenC :: Bool -> (a -> a) -> a -> a
- 
unconcat :: [Int] -> [a] -> [[a]]
- 
version :: String
- 
version13q :: String
- 
wrapLine :: Int -> [a] -> [[a]]
                                               
- A fudget that shows the high level input and output of a fudget on the standard error output:
 - 
spyF :: (Show b, Show a) => F a b -> F a b
 - An identity fudget that copies messages to the standard error output:
 - 
teeF :: (a -> [Char]) -> [Char] -> F a a
 - Miscellaneous (the rest):
 - 
ctrace :: (Show a) => [Char] -> a -> b -> b
- 
maptrace :: (Eq a) => String -> [a] -> [a]
- 
showCommandF :: String -> F a b -> F a b
   
- Displaying text:
 - 
class HasInitText a where ...
 - Miscellaneous (the rest):
 - 
type Customiser a = a -> a
- 
type PF a b c = F (Either (Customiser a) b) c
- 
type PK a b c = K (Either (Customiser a) b) c
- 
class HasFont a where ...
- 
class HasKeys a where ...
- 
class HasWinAttr a where ...
- 
class HasBorderWidth a where ...
- 
class HasBgColorSpec a where ...
- 
class HasFgColorSpec a where ...
- 
class HasMargin a where ...
- 
class HasAlign a where ...
- 
class HasInitSize a where ...
- 
class HasInitDisp a where ...
- 
class HasStretchable a where ...
- 
class HasSizing a where ...
- 
type Alignment = Double
- 
cust :: (a -> a) -> Customiser a
- 
fromMaybe :: a -> Maybe a -> a
- 
getpar :: (a -> Maybe b) -> [a] -> b
- 
getparMaybe :: (a -> Maybe b) -> [a] -> Maybe b
- 
noPF :: PF a b c -> F b c
- 
setBgColor :: (HasBgColorSpec b, Show a, ColorGen a) => a -> Customiser b
- 
setFgColor :: (HasFgColorSpec b, Show a, ColorGen a) => a -> Customiser b
- 
standard :: Customiser a
                        
- Client/Server programming:
 - 
data ClientMsg a = ...
- 
data SocketMsg a = ...
- 
data TPort a b
- 
data TServerAddress a b
- 
socketServerF :: Port -> (Socket -> Peer -> F a (SocketMsg b)) -> F (Int, a) (Int, ClientMsg b)
- 
tPort :: (Show a, Read a, Show b, Read b) => Port -> TPort a b
- 
tSocketServerF :: (Read a, Show b) => TPort a b -> (Peer -> F b (SocketMsg a) -> F c (SocketMsg d)) -> F (Int, c) (Int, ClientMsg d)
- 
tTransceiverF :: (Show a, Read b) => TServerAddress a b -> F a (SocketMsg b)
        - Containers:
 - 
hSplitF :: F a b -> F c d -> F (Either a c) (Either b d)
- 
hSplitF' :: Alignment -> F a b -> F c d -> F (Either a c) (Either b d)
- 
splitF' :: LayoutDir -> Alignment -> F a b -> F c d -> F (Either a c) (Either b d)
- 
vSplitF :: F a b -> F c d -> F (Either a c) (Either b d)
- 
vSplitF' :: Alignment -> F a b -> F c d -> F (Either a c) (Either b d)
     - Menus:
 - 
menuF :: (Eq a) => Menu a -> F a a
 - Shells:
 - 
auxShellF :: String -> F a b -> F (Either Bool a) (Either Bool b)
- 
auxShellF' :: (ShellF -> ShellF) -> String -> F a b -> F (Either Bool a) (Either Bool b)
- 
delayedAuxShellF :: String -> F a b -> F (Either Bool a) (Either Bool b)
- 
delayedAuxShellF' :: (ShellF -> ShellF) -> String -> F a b -> F (Either Bool a) (Either Bool b)
- 
fileShellF :: (a -> String, String -> Either String a, Maybe a) -> [Char] -> F a (InputMsg a) -> F b c
- 
fileShellF' :: (ShellF -> ShellF) -> (a -> String, String -> Either String a, Maybe a) -> [Char] -> F a (InputMsg a) -> F b c
- 
showReadFileShellF :: (Read a, Show a) => Maybe a -> [Char] -> F a (InputMsg a) -> F b c
- 
showReadFileShellF' :: (Read a, Show a) => (ShellF -> ShellF) -> Maybe a -> [Char] -> F a (InputMsg a) -> F b c
- 
textFileShellF :: [Char] -> F String (InputMsg String) -> F a b
- 
textFileShellF' :: (ShellF -> ShellF) -> [Char] -> F String (InputMsg String) -> F a b
- 
titleShellF :: String -> F a b -> F (Either String a) b
- 
titleShellF' :: (ShellF -> ShellF) -> String -> F a b -> F (Either String a) b
- 
wmShellF :: String -> F a b -> F (Either (Either String Bool) a) (Either () b)
- 
wmShellF' :: (ShellF -> ShellF) -> String -> F a b -> F (Either (Either String Bool) a) (Either () b)
              - Miscellaneous (the rest):
 - 
type FileName = String
- 
data RBBT = ...
- 
data SmileyMode = ...
- 
type MenuBar a = Menu a
- 
type Menu a = [MenuItem' a]
- 
type MenuItem' a = Item (MenuItem a)
- 
data Item a
- 
data MenuItem a = ...
- 
data Transl a b = ...
- 
aFilePath :: FilePath -> AFilePath
- 
bitmapButtonF :: [(ModState, KeySym)] -> FileName -> F BitmapReturn Click
- 
bitmapDispBorderF :: Int -> FileName -> F BitmapReturn a
- 
bitmapDispF :: FileName -> F BitmapReturn a
- 
cmdItem :: (Graphic b) => a -> b -> Item (MenuItem a)
- 
completionStringF :: F (Either [[Char]] [Char]) (Either [[Char]] (InputMsg [Char]))
- 
completionStringF' :: Char -> Customiser StringF -> F (Either [[Char]] [Char]) (Either [[Char]] (InputMsg [Char]))
- 
delayedSubMenuItem :: (Graphic c, Eq a) => Transl a b -> Menu a -> c -> Item (MenuItem b)
- 
endButtonsF :: F (Either Click Click) (Either Click Click)
- 
filePickF :: F (Maybe FilePath) (Maybe FilePath)
- 
filePickF' :: (Graphic a) => [(AFilePath -> AFilePath, KeySym, a)] -> F (Maybe FilePath) (Maybe FilePath)
- 
filePickPopupF :: F (a, Maybe FilePath) ((a, Maybe FilePath), FilePath)
- 
filePickPopupF' :: (Graphic a) => [(AFilePath -> AFilePath, KeySym, a)] -> F (b, Maybe FilePath) ((b, Maybe FilePath), FilePath)
- 
filePickPopupOptF :: F (a, Maybe FilePath) ((a, Maybe FilePath), Maybe FilePath)
- 
filePickPopupOptF' :: (Graphic a) => [(AFilePath -> AFilePath, KeySym, a)] -> F (b, Maybe FilePath) ((b, Maybe FilePath), Maybe FilePath)
- 
helpBubbleF :: (Graphic a) => a -> F b c -> F b c
- 
idT :: Transl a a
- 
item :: (Graphic b) => a -> b -> Item a
- 
item' :: (Graphic b) => [(ModState, KeySym)] -> a -> b -> Item a
- 
key :: Item a -> KeySym -> Item a
- 
mapSocketMsg :: (a -> b) -> SocketMsg a -> SocketMsg b
- 
menu :: (Eq a) => Transl a b -> Menu a -> MenuItem b
- 
menuBarF :: (Eq a) => Menu a -> F a a
- 
meterBg :: ColorSpec
- 
meterD :: (RealFrac a) => a -> FlexibleDrawing
- 
meterF :: (RealFrac a) => InF a (Ratio Int)
- 
meterF' :: (RealFrac a) => (GraphicsF FlexibleDrawing -> GraphicsF FlexibleDrawing) -> F a (InputMsg (Ratio Int))
- 
meterFg :: ColorSpec
- 
radioF1 :: (Eq a) => RBBT -> FontName -> [(a, String)] -> a -> F a a
- 
radioGroupF1 :: (Eq a) => RBBT -> FontName -> [a] -> a -> (a -> String) -> F a a
- 
radioGroupItem :: (Graphic c, Eq a) => Transl a b -> [Item a] -> a -> c -> Item (MenuItem b)
- 
sepItem :: Item (MenuItem a)
- 
smileyD :: SmileyMode -> FixedDrawing
- 
smileyF :: F SmileyMode a
- 
smileyF' :: Customiser (DisplayF SmileyMode) -> F SmileyMode a
- 
startDir :: FilePath
- 
subMenuItem :: (Graphic c, Eq a) => Transl a b -> Menu a -> c -> Item (MenuItem b)
- 
tServerAddress :: Host -> TPort a b -> TServerAddress a b
- 
toggleButtonF1 :: RBBT -> String -> [(ModState, KeySym)] -> String -> F Bool Bool
- 
toggleF1 :: RBBT -> [(ModState, KeySym)] -> F a b -> F (Either Bool a) (Either Bool b)
- 
toggleItem :: (Graphic b) => Transl Bool a -> Bool -> b -> Item (MenuItem a)