¤ Fudget Library 0.18.2 Reference Manual ¤

Created from the Fudget Library sources on 2021-01-18 23:56

Full Index

Sections


GuiElems

Button implementation:
data BMevents = ...
buttonGroupF :: [(ModState, KeySym)] -> F (BMevents  b) c -> F b c
pushButtonF :: [(ModState, KeySym)] -> F b1 b2 -> F b1 (b2  Click)
Buttons:
data ButtonF lbl = ...
data Click = ...
class HasLabelInside xxx where ...
data RadioGroupF = ...
data ToggleButtonF = ...
buttonF :: Graphic lbl => lbl -> F Click Click
buttonF' :: Graphic lbl => Customiser (ButtonF lbl) -> lbl -> F Click Click
buttonF'' :: Graphic lbl => Customiser (ButtonF lbl) -> lbl -> PF (ButtonF lbl) Click Click
quitButtonF :: F Click b
radioGroupF :: (Graphic lbl, Eq alt) => [(alt, lbl)] -> alt -> F alt alt
radioGroupF' :: (Graphic lbl, Eq alt) =>
                Customiser RadioGroupF -> [(alt, lbl)] -> alt -> F alt alt
setLabel :: lbl -> Customiser (ButtonF lbl)
setPlacer :: Placer -> Customiser RadioGroupF
toggleButtonF :: Graphic lbl => lbl -> F Bool Bool
toggleButtonF' :: Graphic lbl => Customiser ToggleButtonF -> lbl -> F Bool Bool
toggleF :: Bool -> [(ModState, KeySym)] -> F c b -> F (Bool  c) (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 (Bool  a) b
buttonBorderF :: Int -> F a b -> F (Bool  a) b
labAboveF :: Graphic g => g -> F c d -> F c d
labBelowF :: Graphic g => g -> F c d -> F c d
labLeftOfF :: Graphic g => g -> F c d -> F c d
labRightOfF :: Graphic g => g -> F c d -> F c d
labelF :: Graphic g => g -> F a b
labelF' :: Graphic g => Customiser (DisplayF g) -> g -> F a b
tieLabelF :: Graphic g => Orientation -> Double -> g -> F c d -> F c d
Displaying and interacting with composite graphical objects:
data GfxChange gfx = ...
data GfxCommand path gfx = ...
data GfxEvent path = ...
data GfxEventMask = ...
type GfxFCmd a = GfxCommand DPath a
type GfxFEvent = GfxEvent DPath
data GraphicsF gfx = ...
graphicsF :: Graphic gfx => F (GfxFCmd gfx) GfxFEvent
graphicsF' :: Graphic gfx => Customiser (GraphicsF gfx) -> F (GfxFCmd gfx) GfxFEvent
highlightGfx :: path -> Bool -> GfxCommand path gfx
hyperGraphicsF :: (Eq d, Graphic leaf) =>
                  Drawing d leaf -> F ((Drawing d leaf)  (d, Drawing d leaf)) d
hyperGraphicsF' :: (Eq d, Graphic leaf) =>
                   (GraphicsF (Drawing d leaf) -> GraphicsF (Drawing d leaf)) ->
                   Drawing d leaf -> F ((Drawing d leaf)  (d, Drawing d leaf)) d
replaceAllGfx :: gfx -> GfxCommand [a] gfx
replaceGfx :: path -> gfx -> GfxCommand path gfx
setAdjustSize :: Bool -> Customiser (GraphicsF gfx)
setCursor :: Int -> Customiser (GraphicsF gfx)
setCursorSolid :: Bool -> Customiser (GraphicsF gfx)
setDoubleBuffer :: Bool -> Customiser (GraphicsF gfx)
setGfxEventMask :: [GfxEventMask] -> Customiser (GraphicsF gfx)
showGfx :: path -> GfxCommand path gfx
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))
textF'' :: Customiser TextF -> PF TextF TextRequest (InputMsg (Int, String))
Displays:
data DisplayF a = ...
displayF :: Graphic g => F g void
displayF' :: Graphic a => Customiser (DisplayF a) -> F a b
intDispF :: F Int b
intDispF' :: Customiser (DisplayF Int) -> F Int b
setSpacer :: Spacer -> Customiser (DisplayF a)
Menus:
menuF :: (Graphic mlbl, Graphic albl) => mlbl -> [(alt, albl)] -> F alt alt
popupMenuF :: (Eq b1, Graphic b1) => [(a, b1)] -> F c b2 -> F ([(a, b1)]  c) (a  b2)
Pop-up windows:
data ConfirmMsg = ...
confirmPopupF :: Graphic msg => F msg (msg, ConfirmMsg)
inputPopupF :: String ->
               InF a c -> Maybe c -> F (Maybe String, Maybe a) ((Maybe String, Maybe a), c)
inputPopupOptF :: String ->
                  InF a b ->
                  Maybe b -> F (Maybe String, Maybe a) ((Maybe String, Maybe a), Maybe b)
messagePopupF :: Graphic msg => F msg (msg, 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)
Sound:
bellF :: F ho ho
Terminating the program:
quitF :: F ans ho
quitIdF :: (ho -> Bool) -> F ho ho
Text editors:
data EDirection = ...
data EditCmd = ...
data EditEvt = ...
data EditStop = ...
data EditStopChoice = ...
type EditStopFn = String -> String -> EditStopChoice
data EditorF = ...
editorF :: F EditCmd EditEvt
editorF' :: (EditorF -> EditorF) -> F EditCmd EditEvt
loadEditor :: String -> [EditCmd]
selectall :: [EditCmd]
setEditorCursorPos :: (Int, Int) -> [EditCmd]
Miscellaneous (the rest):
data EqSnd a b = ...
type IsSelect = Bool
data MenuState = ...
data PopupMenu = ...
data TerminalCmd = ...
bdStringF :: Int -> Sizing -> FontSpec -> String -> F String (InputMsg String)
buttonMenuF :: Graphic lbl =>
               LayoutDir ->
               FontName ->
               lbl ->
               [(a, [(ModState, KeySym)])] ->
               F (MenuState  b) a -> F (MenuState  (lbl  b)) (MenuState  a)
buttonMenuF' :: Graphic lbl =>
                Bool ->
                LayoutDir ->
                FontName ->
                lbl ->
                [(a, [(ModState, KeySym)])] ->
                F (MenuState  b) a -> F (MenuState  (lbl  b)) (MenuState  a)
cmdTerminalF :: FontName -> Int -> Int -> F TerminalCmd a
editF :: FontSpec -> F EditCmd EditEvt
fstEqSnd :: EqSnd a b -> a
gcWarningF :: F a b
generalStringF :: Int ->
                  String ->
                  Sizing ->
                  ColorSpec ->
                  ColorSpec ->
                  FontSpec ->
                  (Char -> Bool) ->
                  (String -> String) ->
                  Int -> String -> F ((StringF -> StringF)  String) (InputMsg String)
getAllowedChar :: StringF -> Char -> Bool
getCursorPos :: StringF -> Int
getInitString :: StringF -> String
getShowString :: StringF -> String -> String
grabberF :: [(a1, [(ModState, KeySym)])] -> F (a2  a1) (MenuState  d) -> F a1 d
graphicsDispF :: Graphic a => F (GfxFCmd a) GfxFEvent
graphicsDispF' :: Graphic gfx => Customiser (GraphicsF gfx) -> F (GfxFCmd gfx) GfxFEvent
graphicsDispGroupF :: Graphic gfx => F i o -> F ((GfxFCmd gfx)  i) (GfxFEvent  o)
graphicsDispGroupF' :: Graphic gfx =>
                       (GraphicsF gfx -> GraphicsF gfx) ->
                       F i o -> F ((GfxFCmd gfx)  i) (GfxFEvent  o)
graphicsGroupF :: Graphic gfx => F i o -> F ((GfxFCmd gfx)  i) (GfxFEvent  o)
graphicsGroupF' :: Graphic gfx =>
                   Customiser (GraphicsF gfx) ->
                   F i o -> F ((GfxFCmd gfx)  i) (GfxFEvent  o)
graphicsLabelF :: Graphic a => a -> F e d
graphicsLabelF' :: Graphic a => (GraphicsF a -> GraphicsF a) -> a -> F e d
inputEditorF :: F String (InputMsg String)
inputEditorF' :: (EditorF -> EditorF) -> F String (InputMsg String)
menuAltsF :: (Eq d, Graphic b) => String -> [d] -> (d -> b) -> F PopupMenu d
menuButtonF :: Graphic lbl => FontName -> lbl -> F lbl Click
menuButtonGroupF :: F (BMevents  b) c -> F b c
menuDown :: MenuState
menuLabelF :: Graphic lbl => FontName -> lbl -> F (Bool  lbl) (GfxEvent DPath)
menuPopupF :: F b d -> F (PopupMenu  b) d
menuPopupF' :: Bool -> F b d -> F (PopupMenu  b) d
newline :: Char
offColor :: String
oldButtonF :: (Graphic e, FontGen a1, Show a1, Show a2, ColorGen a2) =>
              Double ->
              Int ->
              a1 -> ColorSpec -> a2 -> [(ModState, KeySym)] -> e -> F e Click
oldConfirmPopupF :: F String (String, ConfirmMsg)
oldEditorF :: FontSpec -> F EditCmd EditEvt
oldGeneralStringF :: Int ->
                     Sizing ->
                     FontSpec ->
                     (Char -> Bool) ->
                     (String -> String) -> String -> F String (InputMsg String)
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 :: (Eq b1, Graphic b2, Foldable t) =>
                 ColorName ->
                 Bool ->
                 String ->
                 Button ->
                 [Modifiers] ->
                 t (ModState, KeySym) ->
                 [(b1, b3)] -> (b1 -> b2) -> F c d -> F ([(b1, b4)]  c) (b1  d)
oldPopupMenuF' :: (Eq b1, Graphic b2, Foldable t) =>
                  ColorName ->
                  Bool ->
                  String ->
                  Button ->
                  [Modifiers] ->
                  t (ModState, KeySym) ->
                  [(b1, b3)] ->
                  (b1 -> b2) ->
                  F c d ->
                  F ((a  b4)  (([(b1, b5)]  PopupMenu)  c)) (((a  PopupMenu)  b4)  (b1  d))
oldRadioGroupF :: (Eq d, Graphic a1, Show a2, FontGen a2) =>
                  Placer -> Bool -> a2 -> [d] -> d -> (d -> a1) -> F d d
oldStringF :: String -> InF String String
oldToggleButtonF :: (Graphic a1, Show a2, FontGen a2) =>
                    a2 -> [(ModState, KeySym)] -> a1 -> F Bool Bool
oldToggleButtonF' :: (Graphic a1, Show a2, FontGen a2) =>
                     Bool -> a2 -> [(ModState, KeySym)] -> a1 -> F Bool Bool
onColor :: String
onOffDispF :: Bool -> F Bool nothing
passwdPopupOptF :: String ->
                   F (Maybe String, Maybe String) ((Maybe String, Maybe String), Maybe String)
pushButtonF' :: Int -> [(ModState, KeySym)] -> F b1 b2 -> F b1 (b2  Click)
radioF :: (Eq a, Graphic a1, Show a2, FontGen a2) =>
          Placer -> Bool -> a2 -> [(a, a1)] -> a -> F a a
simpleMenuF :: (Eq b, Graphic c, Graphic a) =>
               FontName -> a -> [b] -> (b -> c) -> F a b
smallPickListF :: (d -> String) -> F [d] d
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
toEqSnd :: [(a, b)] -> [EqSnd a b]
toggleGroupF :: [(ModState, KeySym)] -> F ((Bool  Bool)  a) b -> F (Bool  a) (Bool  b)

Combinators

Abstract fudgets: from stream processors:
absF :: SP a b -> F a b
Abstract fudgets: stateful:
mapstateF :: (t -> a -> (t, [b])) -> t -> F a b
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 a1 b1 -> InF a2 b2 -> InF (a1, a2) (b1, b2)
inputThroughF :: InF a a -> InF a a
Data entry fields:
type InF a b = F a (InputMsg b)
Delay the activation of a stream processor or fudget:
delayF :: F hi ho -> F hi ho
Dynamic fudget creation/destruction:
type DynFMsg a b = DynMsg a (F a b)
dynF :: F a b -> F ((F a b)  a) b
dynListF :: F (Int, DynFMsg a b) (Int, b)
Monadic style:
type Cont c a = (a -> c) -> c
type Ks i o s ans = Ms (K i o) s ans
data Mk k r = ...
type Mkc k = Mk k ()
type Ms k s r = Mk (s -> k) r
type Msc k s = Ms k s ()
fieldMs :: (s -> f) -> Ms k s f
getKs :: Ms (K hi ho) s (KEvent hi)
loadMs :: Ms k s s
modMs :: (s -> s) -> Msc k s
nopMs :: Msc k s
putHighMs :: StreamProcIO sp => o -> Msc (sp i o) r
putHighsMs :: (Foldable t, StreamProcIO sp) => t o -> Msc (sp i o) r
putLowMs :: FudgetIO f => FRequest -> Msc (f hi ho) r
putLowsMs :: (Foldable t, FudgetIO f) => t FRequest -> Msc (f hi ho) r
stateK :: b1 -> Mk (b1 -> a) b2 -> a -> a
stateMonadK :: p -> Mk (p -> t1) t2 -> (t2 -> t1) -> t1
storeMs :: s -> Msc k s
Plumbing: circular connections:
loopCompF :: F ((r2l  inl)  (l2r  inr)) ((l2r  outl)  (r2l  outr)) ->
             F (inl  inr) (outl  outr)
loopF :: F a a -> F a a
loopLeftF :: F (a  b) (a  c) -> F b c
loopOnlyF :: F a a -> F a b
loopRightF :: F (a  b) (c  b) -> F a c
loopThroughBothF :: F (r2l  inl) (l2r  outl) ->
                    F (l2r  inr) (r2l  outr) -> F (inl  inr) (outl  outr)
loopThroughRightF :: F (a  b) (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 c d -> F (b  c) (b  d)
idRightF :: F a b -> F (a  c) (b  c)
stubF :: F a b -> F c d
throughF :: F c b -> F c (b  c)
toBothF :: F b (b  b)
Plumbing: serial composition:
serCompF :: F a1 b -> F a2 a1 -> F a2 b
Plumbing: tagged parallel composition:
compF :: F a b -> F c d -> F (a  c) (b  d)
listF :: Eq a => [(a, F b c)] -> F (a, b) (a, c)
Plumbing: turn parallel compositions into loops:
loopCompThroughLeftF :: F (a  (b  c)) (b  (a  d)) -> F c d
loopCompThroughRightF :: F ((a  b)  c) ((c  d)  a) -> F b d
Plumbing: turning parallel compositions into serial compositions:
serCompLeftToRightF :: F (a  b) (b  c) -> F a c
serCompRightToLeftF :: F (a  b) (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 ((a1  b1)  (a2  b2)) ((a2  a3)  (a1  b3)) -> SP (b1  b2) (a3  b3)
loopThroughBothSP :: SP (a1  b1) (a2  a3) ->
                     SP (a2  b2) (a1  b3) -> SP (b1  b2) (a3  b3)
The Fudget type:
data F hi ho = ...
The fudget kernel type:
data K hi ho = ...
The identity fudget:
idF :: F b b
Miscellaneous (the rest):
class FudgetIO f where ...
class StreamProcIO sp where ...
data Tree a = ...
appendStartF :: [ho] -> F hi ho -> F hi ho
appendStartK :: [KCommand ho] -> K hi ho -> K hi ho
appendStartMessageF :: [FCommand ho] -> F hi ho -> F hi ho
bindKs :: Monad m => m a -> (a -> m b) -> m b
bmk :: ((a1 -> c1) -> c2) -> (a1 -> a2 -> c1) -> a2 -> c2
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, b1) ->
            p -> ((Message (Path, b1) b2)  (Message (Path, b1) b3) -> p) -> p
compTurnLeft :: (Path, b1) -> Message (Path, b1) b2
compTurnRight :: (Path, b1) -> Message (Path, b1) b2
contDynF :: F a b -> Cont (F a d) b
contDynFSP :: FSP a b -> Cont (FSP a d) b
getF :: Cont (F a ho) a
getK :: Cont (K hi ho) (KEvent hi)
getMessageF :: Cont (F hi ho) (FEvent hi)
getMessageFu :: Cont (F a b) (KEvent a)
inputListLF :: Eq a => Placer -> [(a, InF b c)] -> F [(a, b)] (InputMsg [(a, c)])
inputPairLF :: Orientation -> InF a1 b1 -> InF a2 b2 -> F (a1, a2) (InputMsg (b1, b2))
leafF :: a1 -> F b1 b2 -> Fa TEvent TCommand ([a2], b1) (a1, b2)
loadKs :: Ms k s s
loopLow :: SP TCommand (FCommand a) -> SP (FEvent a) TEvent -> F b c -> F b c
loopThroughLowF :: SP (TCommand  TEvent) (TCommand  TEvent) -> F i o -> F i o
loopThroughLowSP :: SP (c  e) (c  e) ->
                    SP (Message e a) (Message c b) -> SP (Message e a) (Message c b)
mapKs :: Functor f => (a -> b) -> f a -> f b
nullF :: F hi ho
nullK :: K hi ho
nullKs :: Msc k s
parF :: F c ho -> F c ho -> F c ho
postMapHigh :: (a -> ho) -> F hi a -> F hi ho
postMapHigh' :: (a -> b) -> Fa c d e a -> Fa c d e b
postMapHighK :: (a -> ho) -> K hi a -> K hi ho
postMapLow :: (TCommand -> TCommand) -> F hi ho -> F hi ho
postMapLow' :: (a -> b) -> Fa c a d e -> Fa c b d e
postMapLowK :: (FRequest -> FRequest) -> K hi ho -> K hi ho
postProcessHigh :: SP a ho -> F hi a -> F hi ho
postProcessHigh' :: SP a b -> Fa c d e a -> Fa c d e b
postProcessHighK :: SP a ho -> K hi a -> K hi ho
postProcessLow :: SP TCommand TCommand -> F hi ho -> F hi ho
postProcessLow' :: SP a b -> Fa c a d e -> Fa c b d e
postProcessLowK :: SP FRequest FRequest -> K hi ho -> K hi ho
preMapHigh :: F c ho -> (hi -> c) -> F hi ho
preMapHigh' :: Fa a b c d -> (e -> c) -> Fa a b e d
preMapHighK :: K c ho -> (hi -> c) -> K hi ho
preMapLow :: F hi ho -> (TEvent -> TEvent) -> F hi ho
preMapLow' :: Fa a b c d -> (e -> a) -> Fa e b c d
preMapLowK :: K hi ho -> (FResponse -> FResponse) -> K hi ho
preProcessHigh :: F c ho -> SP hi c -> F hi ho
preProcessHigh' :: Fa a b c d -> SP e c -> Fa a b e d
preProcessHighK :: K c ho -> SP hi c -> K hi ho
preProcessLow :: F hi ho -> SP TEvent TEvent -> F hi ho
preProcessLow' :: Fa a b c d -> SP e a -> Fa e b c d
preProcessLowK :: K hi ho -> SP FResponse FResponse -> K hi ho
prepostMapHigh :: (hi -> b) -> (c -> ho) -> F b c -> F hi ho
prepostMapHigh' :: (a -> b) -> (c -> d) -> Fa e f b c -> Fa e f a d
prepostMapHighK :: (hi -> b) -> (c -> ho) -> K b c -> K hi ho
prepostMapLow :: (TEvent -> TEvent) -> (TCommand -> TCommand) -> F hi ho -> F hi ho
prepostMapLow' :: (a -> b) -> (c -> d) -> Fa b c e f -> Fa a d e f
prepostMapLowK :: (FResponse -> FResponse) ->
                  (FRequest -> FRequest) -> K hi ho -> K hi ho
prodF :: F a b -> F c d -> F (a, c) (b  d)
putF :: ho -> F hi ho -> F hi ho
putK :: KCommand ho -> K hi ho -> K hi ho
putMessageF :: FCommand ho -> F hi ho -> F hi ho
putMessageFu :: Message FRequest ho -> F hi ho -> F hi ho
putMessagesF :: [FCommand ho] -> F hi ho -> F hi ho
putMessagesFu :: [KCommand b] -> F a b -> F a b
putsF :: [b] -> F a b -> F a b
putsK :: [KCommand b] -> K a b -> K a b
startupF :: [hi] -> F hi ho -> F hi ho
startupK :: [KEvent hi] -> K hi ho -> K hi ho
startupMessageF :: [FEvent hi] -> F hi ho -> F hi ho
storeKs :: s -> Msc k s
thenKs :: Monad m => m a -> m b -> m b
toMkc :: (k -> k) -> Mkc k
toMs :: Cont k r -> Ms k s r
toMsc :: (k -> k) -> Msc k r
treeF :: Tree (a, F b c) -> F (Path, b) (a, c)
treeF' :: Tree (a, F b c) -> FSP (Path, b) (a, c)
unitKs :: Monad m => a -> m a

InfixOps

Plumbing: serial composition:
>==< :: F a1 b -> F a2 a1 -> F a2 b
Plumbing: tagged parallel composition:
>+< :: F a b -> F c d -> F (a  c) (b  d)
Plumbing: untagged parallel composition:
>*< :: F c ho -> F c ho -> F c ho
Stream processor combinators:
-+- :: SP a1 a2 -> SP a3 b -> SP (a1  a3) (a2  b)
-==- :: SP a1 b -> SP a2 a1 -> SP a2 b
Miscellaneous (the rest):
-*- :: SP a b -> SP a b -> SP a b
>#+< :: (F a b, Orientation) -> F c d -> F (a  c) (b  d)
>#==< :: (F a1 f, Orientation) -> F e a1 -> F e f
>+#< :: F a b -> (Distance, Orientation, F c d) -> F (a  c) (b  d)
>..=< :: SP TCommand TCommand -> F hi ho -> F hi ho
>.=< :: (TCommand -> TCommand) -> F hi ho -> F hi ho
>=..< :: F hi ho -> SP TEvent TEvent -> F hi ho
>=.< :: F hi ho -> (TEvent -> TEvent) -> F hi ho
>==#< :: F a1 b -> (Distance, Orientation, F a a1) -> F a b
>=^< :: F c d -> (e -> c) -> F e d
>=^^< :: F c d -> SP e c -> F e d
>^=< :: (a -> b) -> F e a -> F e b
>^^=< :: SP a b -> F e a -> F e b

Layout

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 placement: dynamic:
dynPlacerF :: F c ho -> F (Placer  c) ho
dynSpacerF :: F c ho -> F (Spacer  c) ho
GUI fudget spacing:
data Spacer = ...
marginF :: Distance -> F a b -> F a b
sepF :: Size -> F a b -> F a b
spacer1F :: Spacer -> F a b -> F a b
spacerF :: Spacer -> F a b -> F a b
Name layout:
type LName = String
data NameLayout = ...
leafNL :: LName -> NameLayout
nameF :: LName -> F a b -> F a b
nameLayoutF :: NameLayout -> F a b -> F a b
nullNL :: NameLayout
placeNL :: Placer -> [NameLayout] -> NameLayout
spaceNL :: Spacer -> NameLayout -> NameLayout
Name layout convenience:
hBoxNL :: [NameLayout] -> NameLayout
hBoxNL' :: Distance -> [NameLayout] -> NameLayout
hvAlignNL :: Alignment -> Alignment -> NameLayout -> NameLayout
marginHVAlignNL :: Distance -> Alignment -> Alignment -> NameLayout -> NameLayout
marginNL :: Distance -> NameLayout -> NameLayout
modNL :: (Placer -> Placer) -> NameLayout -> NameLayout
sepNL :: Size -> NameLayout -> NameLayout
vBoxNL :: [NameLayout] -> NameLayout
vBoxNL' :: Distance -> [NameLayout] -> NameLayout
Placer modifying combinators:
flipP :: Placer -> Placer
permuteP :: [Int] -> Placer -> Placer
revP :: Placer -> Placer
spacerP :: Spacer -> Placer -> Placer
Placers: automatic layout:
autoP :: Placer
autoP' :: Size -> Placer
Placers: linear layouts:
horizontalP :: Placer
horizontalP' :: Distance -> Placer
verticalP :: Placer
verticalP' :: Distance -> Placer
Placers: matrixes and tables:
data LayoutDir = ...
matrixP :: Int -> Placer
matrixP' :: Int -> LayoutDir -> Distance -> Placer
tableP :: Int -> Placer
tableP' :: Int -> LayoutDir -> Distance -> Placer
Placers: other:
horizontalCenterP :: Placer
horizontalCenterP' :: Distance -> Placer
overlayP :: Placer
verticalLeftP :: Placer
verticalLeftP' :: Distance -> Placer
Placers: paragraphs:
paragraphP :: Placer
paragraphP' :: Size -> Placer
paragraphP'' :: (Int -> Placer) -> Size -> 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
marginHVAlignS :: Distance -> Alignment -> Alignment -> Spacer
marginS :: Distance -> Spacer
sepS :: Size -> 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
Spacers: alignment:
type Alignment = Double
aBottom :: Alignment
aCenter :: Alignment
aLeft :: Alignment
aRight :: Alignment
aTop :: Alignment
Spacers: put limits on the allowed size of a box:
maxSizeS :: Size -> Spacer
minSizeS :: Size -> Spacer
sizeS :: Size -> Spacer
Miscellaneous (the rest):
data Layout = ...
data LayoutDirection = ...
type LayoutHint = String
data LayoutMessage = ...
data LayoutRequest = ...
data LayoutResponse = ...
data Orientation = ...
type Placer1 = [LayoutRequest] -> Placer2
type Placer2 = (LayoutRequest, Rect -> [Rect])
data Sizing = ...
type Spacer1 = LayoutRequest -> Spacer2
type Spacer2 = (LayoutRequest, Rect -> Rect)
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
center :: Point -> Rect -> Rect
center' :: Point -> Size -> Rect -> Rect
colinear :: LayoutDir -> p -> p -> p
compLF :: (F a b, Orientation) -> F c d -> F (a  c) (b  d)
dynListLF :: Placer -> F (Int, DynFMsg a b) (Int, b)
fixh :: LayoutDir -> LayoutRequest -> Bool
fixv :: LayoutDir -> LayoutRequest -> Bool
flipPoint :: Point -> Point
flipRect :: Rect -> Rect
flipReq :: LayoutRequest -> LayoutRequest
flipWanted :: (Point, Point, c) -> (Point, Point, c)
hBoxLs' :: Distance -> [Layout] -> Layout
holeF :: F hi ho
holeF' :: Size -> F hi ho
horizontalAlignP :: Placer
horizontalAlignP' :: 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) -> t) ->
             LayoutRequest -> t
mapLayoutRefs :: (Point -> Point) -> LayoutRequest -> LayoutRequest
mapLayoutSize :: (Size -> Size) -> LayoutRequest -> LayoutRequest
mapP :: (Placer1 -> Placer1) -> Placer -> Placer
mapS :: (Spacer1 -> Spacer1) -> Spacer -> Spacer
marginHVAlignLs :: Distance -> Alignment -> Alignment -> Layout -> Layout
marginLs :: Distance -> Layout -> Layout
middleRefs :: Point -> (Point, Point)
mkp :: LayoutDir -> Int -> Int -> Point
moveRefsS :: Point -> Spacer
newSize :: Sizing -> Point -> Point -> Point
noRefsS :: Spacer
noStretchS :: Bool -> Bool -> Spacer
nowait :: Bool
nullLF :: F hi ho
orientP :: Orientation -> Placer
orthogonal :: LayoutDir -> p -> p -> p
overlayAlignP :: Placer
permLs :: [Int] -> Layout -> Layout
placeLs :: Placer -> [Layout] -> Layout
plainLayout :: Size -> Bool -> Bool -> LayoutRequest
refEdgesS :: Spacer
refMiddleS :: Spacer
refMiddleS' :: LayoutRequest -> (LayoutRequest, a -> a)
refpLayout :: Size -> Bool -> Bool -> [Point] -> LayoutRequest
resizeS :: (Size -> Size) -> Spacer
revLs :: Layout -> Layout
sepLs :: Size -> Layout -> Layout
serCompLF :: (F a1 f, Orientation) -> F e a1 -> F e f
spaceLs :: Spacer -> Layout -> Layout
spacersP :: Placer -> [Spacer] -> Placer
stretchCaseS :: ((Bool, Bool) -> Spacer) -> Spacer
tryLayoutK :: LayoutRequest -> Cont (K b c) Size
unP :: Placer -> Placer1
unS :: Spacer -> Spacer1
untaggedListLF :: Placer -> [F a b] -> F (Int, a) b
userLayoutF :: F a b -> F ((Path, Rect)  a) ((Path, LayoutMessage)  b)
vBoxLs' :: Distance -> [Layout] -> Layout
vswap :: LayoutDir -> (b, b) -> (b, b)
xc :: LayoutDir -> Point -> Int
yc :: LayoutDir -> Point -> Int

Containers

Scroll bars:
hScrollF :: F b d -> F b d
scrollF :: F b d -> F b d
vScrollF :: F b d -> F b d
Shell (top level) windows:
data DeleteWindowAction = ...
class HasClickToType xxx where ...
class HasVisible xxx where ...
data ShellF = ...
setDeleteQuit :: Bool -> Customiser ShellF
setDeleteWindowAction :: Maybe DeleteWindowAction -> Customiser ShellF
setInitPos :: Maybe Point -> Customiser ShellF
shellF :: String -> F c d -> F c d
shellF' :: Customiser ShellF -> String -> F c d -> F c d
unmappedShellF :: Foldable t => t FRequest -> K a b -> F c d -> F (a  c) (b  d)
unmappedShellF' :: Foldable t =>
                   (ShellF -> ShellF) ->
                   t FRequest -> K a b -> F c d -> F (a  c) (b  d)
unmappedSimpleShellF :: String -> F i o -> F i o
Miscellaneous (the rest):
data ESelCmd a = ...
data ESelEvt a = ...
data PotRequest = ...
type PotState = (Int, Int, Int)
data SelCmd a = ...
data SelEvt a = ...
bubbleF :: F a b -> F a b
bubblePopupF :: F b2 d2 -> F (PopupMsg b2) d2
bubbleRootPopupF :: F b2 d2 -> F (PopupMsg b2) d2
containerGroupF :: Rect ->
                   Rect ->
                   Int ->
                   Button -> [Modifiers] -> F c b -> F ((Rect, Rect)  c) (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 (a  c) (b  d)
groupF' :: Sizing -> [FRequest] -> K a b -> F c d -> F (a  c) (b  d)
hPotF :: F PotRequest PotState
hPotF' :: Bool -> Maybe Point -> F PotRequest PotState
invisibleGroupF :: Sizing -> [FRequest] -> [WindowAttributes] -> F b ho -> F b ho
mapWindowK :: K Bool ho
oldHscrollF :: Bool -> (Point, Point) -> F b d -> F b d
oldScrollF :: Bool -> (Point, Point) -> F b d -> F b d
oldVscrollF :: Bool -> (Point, Point) -> F b d -> F b d
popupGroupF :: (Size -> Point, [WindowAttributes], K b1 d1) ->
               F b2 d2 -> F (PopupMsg b2) d2
popupShellF :: String -> Maybe Point -> F a b -> F a (a, b)
popupShellF' :: Customiser ShellF -> String -> Maybe Point -> F a b -> F a (a, b)
posPopupShellF :: String -> [WindowAttributes] -> F c a -> F (c, Maybe Point) (c, a)
rootGroupF :: K a b -> F c d -> F (a  c) (b  d)
rootPopupF :: (Size -> Point, [WindowAttributes], K b1 d1) -> F b2 d2 -> F (PopupMsg b2) d2
rootWindowF :: K b c -> F b c
sF :: Bool -> Maybe Point -> [FRequest] -> K a b -> F c d -> F (a  c) (b  d)
scrollShellF :: String -> (Point, Point) -> F c d -> F c d
selectionF :: F (SelCmd String) (SelEvt String)
setFocusMgr :: Bool -> Customiser ShellF
sgroupF :: Sizing -> [FRequest] -> Maybe Rect -> K a b -> F c d -> F (a  c) (b  d)
shellKF :: K a b -> F c d -> F (a  c) (b  d)
shellKF' :: Customiser ShellF -> K a b -> F c d -> F (a  c) (b  d)
simpleGroupF :: [WindowAttributes] -> F b ho -> F b ho
simpleShellF :: String -> [WindowAttributes] -> F c d -> F c d
swindowF :: [FRequest] -> Maybe Rect -> K a ho -> F a ho
unmappedGroupF :: Sizing -> [FRequest] -> K a b -> F c d -> F (a  c) (b  d)
unmappedSimpleShellF' :: Customiser ShellF -> String -> F i o -> F i o
vPotF :: F PotRequest PotState
vPotF' :: Bool -> Maybe Point -> F PotRequest PotState
windowF :: [FRequest] -> K a b -> F a b

Filters

Miscellaneous (the rest):
allcacheF :: F i o -> F i o
doubleClickF :: Time -> F a b -> F a b
shapeGroupMgr :: F a b -> F a b

DrawingModules

Bitmaps:
data BitmapFile = ...
Color:
allocColor :: FudgetIO f => ColormapId -> RGB -> Cont (f b ho) Color
allocColorF :: ColormapId -> RGB -> Cont (F b c) Color
allocColorPixel :: FudgetIO f => ColormapId -> RGB -> Cont (f b ho) Pixel
allocColorPixelF :: ColormapId -> RGB -> Cont (F b c) Pixel
allocNamedColor :: FudgetIO f => ColormapId -> ColorName -> Cont (f b ho) Color
allocNamedColorDef :: FudgetIO f =>
                      ColormapId -> ColorName -> String -> Cont (f b ho) Color
allocNamedColorDefPixel :: FudgetIO f =>
                           ColormapId ->
                           ColorName -> String -> (Pixel -> f b ho) -> f b ho
allocNamedColorF :: ColormapId -> ColorName -> Cont (F b c) Color
allocNamedColorPixel :: FudgetIO f => ColormapId -> ColorName -> Cont (f b ho) Pixel
allocNamedColorPixelF :: ColormapId -> ColorName -> Cont (F b c) Pixel
queryColor :: FudgetIO f => ColormapId -> Pixel -> (Color -> f b ho) -> f b ho
queryColorF :: ColormapId -> Pixel -> Cont (F b c) Color
tryAllocColor :: FudgetIO f => ColormapId -> RGB -> (Maybe Color -> f b ho) -> f b ho
tryAllocColorF :: ColormapId -> RGB -> Cont (F b c) (Maybe Color)
tryAllocNamedColor :: FudgetIO f =>
                      ColormapId -> ColorName -> (Maybe Color -> f b ho) -> f b ho
tryAllocNamedColorF :: ColormapId -> ColorName -> Cont (F b c) (Maybe Color)
Drawing:
data Drawing lbl leaf = ...
data GCSpec = ...
atomicD :: leaf -> Drawing lbl leaf
attribD :: GCSpec -> Drawing lbl leaf -> Drawing lbl leaf
fgD :: (Show a, ColorGen a) => a -> Drawing lbl leaf -> Drawing lbl leaf
fontD :: (Show a, FontGen a) => a -> Drawing lbl leaf -> Drawing lbl leaf
hardAttribD :: GCtx -> Drawing lbl leaf -> Drawing lbl leaf
hboxD :: [Drawing lbl leaf] -> Drawing lbl leaf
hboxD' :: Distance -> [Drawing lbl leaf] -> Drawing lbl leaf
labelD :: lbl -> Drawing lbl leaf -> Drawing lbl leaf
matrixD :: Int -> [Drawing lbl leaf] -> Drawing lbl leaf
matrixD' :: Distance -> Int -> [Drawing lbl leaf] -> Drawing lbl leaf
softAttribD :: [GCAttributes ColorSpec FontSpec] -> Drawing lbl leaf -> Drawing lbl leaf
tableD :: Int -> [Drawing lbl leaf] -> Drawing lbl leaf
tableD' :: Distance -> Int -> [Drawing lbl leaf] -> Drawing lbl leaf
vboxD :: [Drawing lbl leaf] -> Drawing lbl leaf
vboxD' :: Distance -> [Drawing lbl leaf] -> Drawing lbl leaf
Drawing attributes:
class ColorGen a where ...
data ColorSpec = ...
class FontGen a where ...
data FontSpec = ...
data GCtx = ...
colorSpec :: (Show a, ColorGen a) => a -> ColorSpec
createGCtx :: (ColorGen a1, FudgetIO f, FontGen a2, Show a1, Show a2) =>
              Drawable -> GCtx -> [GCAttributes a1 a2] -> (GCtx -> f i o) -> f i o
fontSpec :: (Show a, FontGen a) => a -> FontSpec
gcBgA :: c -> [GCAttributes c FontSpec]
gcFgA :: c -> [GCAttributes c FontSpec]
gcFontA :: f -> [GCAttributes ColorSpec f]
gctx2gc :: GCtx -> GCId
pmCreateGCtx :: (ColorGen a1, FudgetIO f, FontGen a2, Show a1, Show a2) =>
                PixmapId -> GCtx -> [GCAttributes a1 a2] -> (GCtx -> f i o) -> f i o
rootGCtx :: GCtx
wCreateGCtx :: (ColorGen a1, FudgetIO f, FontGen a2, Show a1, Show a2) =>
               GCtx -> [GCAttributes a1 a2] -> (GCtx -> f i o) -> f i o
Drawing manipulation:
type DPath = [Int]
deletePart :: Drawing lbl leaf -> [Int] -> Drawing lbl leaf
drawingAnnots :: Drawing a leaf -> [(DPath, a)]
drawingPart :: Drawing lbl leaf -> DPath -> Drawing lbl leaf
mapLabelDrawing :: (t -> lbl) -> Drawing t leaf -> Drawing lbl leaf
maybeDrawingPart :: Drawing lbl leaf -> DPath -> Maybe (Drawing lbl leaf)
replacePart :: Drawing lbl leaf -> DPath -> Drawing lbl leaf -> Drawing lbl leaf
up :: DPath -> DPath
updatePart :: Drawing lbl leaf ->
              DPath -> (Drawing lbl leaf -> Drawing lbl leaf) -> Drawing lbl leaf
Drawing utilities:
drawarc :: Int -> Int -> Rect -> [DrawCommand]
drawpoly :: [Point] -> [DrawCommand]
fillarc :: Int -> Int -> Rect -> [DrawCommand]
trianglePoints :: Rect -> [Point]
trianglePoints' :: Rect -> [Point]
Fixed size drawings:
data FixedColorDrawing = ...
data FixedDrawing = ...
Flexible line drawings:
data FlexibleDrawing = ...
arc :: Int -> Int -> FlexibleDrawing
arc' :: Size -> Int -> Int -> FlexibleDrawing
blank :: FlexibleDrawing
blank' :: Size -> FlexibleDrawing
braces :: (FlexibleDrawing, FlexibleDrawing)
bracks :: (FlexibleDrawing, FlexibleDrawing)
ellipse :: FlexibleDrawing
ellipse' :: Size -> FlexibleDrawing
filledEllipse :: FlexibleDrawing
filledEllipse' :: Size -> FlexibleDrawing
filledTriangleDown :: FlexibleDrawing
filledTriangleUp :: FlexibleDrawing
filledarc :: Int -> Int -> FlexibleDrawing
filledarc' :: Size -> Int -> Int -> 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
triangleDown :: FlexibleDrawing
triangleUp :: FlexibleDrawing
vFiller :: Int -> FlexibleDrawing
Font metrics:
data CharStruct = ...
data FontData = ...
data FontDirection = ...
data FontProp = ...
data FontStruct = ...
char_rbearing :: CharStruct -> Int
char_width :: CharStruct -> Int
font_ascent :: FontStruct -> Int
font_descent :: FontStruct -> Int
font_id :: FontStruct -> FontId
font_prop :: FontStruct -> [FontProp]
font_range :: FontStruct -> (Char, Char)
fontdata2struct :: FontData -> (FontStruct -> p) -> p
linespace :: FontStruct -> Int
next_pos :: FontStruct -> String -> Int
poslist :: FontStruct -> String -> [Int]
split_string :: FontStruct -> String -> Int -> (String, String, Int)
string_bounds :: FontStruct -> String -> Rect
string_box_size :: FontStruct -> String -> Point
string_len :: FontStruct -> String -> Int
string_rect :: FontStruct -> String -> Rect
Graphics:
data Gfx = ...
class Graphic a where ...
g :: Graphic a => a -> Drawing lbl Gfx
Monadic style:
type Cont c a = (a -> c) -> c
Miscellaneous (the rest):
data CompiledGraphics = ...
type Cursor = Bool
data FontStructList = ...
data ImageString = ...
data MeasuredGraphics = ...
class PixmapGen a where ...
data PixmapImage = ...
abPoints :: Rect -> [Point]
abPoints' :: Rect -> [Point]
addcursor :: CompiledGraphics -> CompiledGraphics
annotChildren :: Drawing b d -> [(DPath, Drawing b d)]
annotChildren' :: (a -> Bool) -> Drawing a d -> [(DPath, Drawing a d)]
bFlex :: (Rect -> [DrawCommand]) -> FlexibleDrawing
bFlex' :: Size -> (Rect -> [DrawCommand]) -> FlexibleDrawing
bFlex2 :: (Rect -> [DrawCommand]) -> FlexibleDrawing
bgD :: (Show a, ColorGen a) => a -> Drawing lbl leaf -> Drawing lbl leaf
bitmapFromData :: FudgetIO f => BitmapData -> (BitmapReturn -> f b ho) -> f b ho
blankD :: Size -> Drawing lbl Gfx
boxD :: [Drawing lbl leaf] -> Drawing lbl leaf
boxVisibleD :: Int -> [Drawing lbl leaf] -> Drawing lbl leaf
cgCompose :: Rect -> [CompiledGraphics] -> CompiledGraphics
cgGroup :: Int -> Int -> CompiledGraphics -> CompiledGraphics
cgLeaf :: Rect -> (Rect -> [(GCId, [DrawCommand])]) -> CompiledGraphics
cgMark :: CompiledGraphics -> CompiledGraphics
cgUngroup :: Int -> CompiledGraphics -> CompiledGraphics
cgcursors :: CompiledGraphics -> [[Int]]
cgpart :: CompiledGraphics -> [Int] -> CompiledGraphics
cgrect :: CompiledGraphics -> Rect
cgreplace :: CompiledGraphics -> [Int] -> CompiledGraphics -> CompiledGraphics
cgsize :: CompiledGraphics -> Size
cgupdate :: CompiledGraphics ->
            [Int] -> (CompiledGraphics -> CompiledGraphics) -> CompiledGraphics
compileMG :: (Size -> Size) -> MeasuredGraphics -> (CompiledGraphics, LayoutRequest)
convColorK :: (ColorGen a, FudgetIO f, Show a) => a -> (Pixel -> f i o) -> f i o
convFontK :: (FontGen a, FudgetIO f, Show a) => a -> (FontData -> f i o) -> f i o
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
convGCattrsK :: FudgetIO f =>
                [GCAttributes ColorName String] ->
                ([GCAttributes Pixel FontId] -> f b ho) -> f b ho
convList :: (t -> (Maybe a -> b) -> b) -> [t] -> (Maybe a -> b) -> b
corners :: Rect -> (Point, Point, Point, Point)
createFontCursor :: Int -> Cont (K b c) CursorId
createGC :: FudgetIO f =>
            Drawable ->
            GCId -> [GCAttributes Pixel FontId] -> (GCId -> f b ho) -> f b ho
createGCF :: Drawable -> GCId -> GCAttributeList -> (GCId -> F a b) -> F a b
createPixmap :: FudgetIO f => Point -> Int -> (PixmapId -> f b ho) -> f b ho
defineCursor :: CursorId -> K i o -> K i o
doubleleft :: Rect -> Rect
doubleright :: Rect -> Rect
drawingAnnotPart :: Drawing b leaf -> DPath -> [Int]
drawingAnnotPart' :: (t -> Bool) -> Drawing t leaf -> DPath -> [Int]
emptyMG :: Size -> MeasuredGraphics
emptyMG' :: LayoutRequest -> MeasuredGraphics
extractParts :: Drawing lbl leaf -> (Drawing lbl leaf -> Maybe a) -> [(DPath, a)]
fatD :: Drawing lbl leaf -> Drawing lbl leaf
fdFontId :: FontData -> FontId
filledRectD :: Size -> Drawing lbl Gfx
fillpoly :: [Point] -> [DrawCommand]
fsl2fs :: FontStructList -> FontStruct
getFontData :: FudgetIO f => String -> Cont (f i o) (Maybe FontData)
getWindowId :: Cont (K a b) Window
getWindowRootPoint :: Cont (K a b) Point
graphic2PixmapImage :: Graphic a => a -> GCtx -> (PixmapImage -> K i o) -> K i o
groupParts :: Int -> Int -> Drawing lbl leaf -> Drawing lbl leaf
hMirror :: (Rect -> [Point]) -> Rect -> [Point]
hascursor :: CompiledGraphics -> Cursor
hboxcD :: [Drawing lbl leaf] -> Drawing lbl leaf
hboxcD' :: Distance -> [Drawing lbl leaf] -> Drawing lbl leaf
holeD :: Drawing lbl Gfx
horizD :: Drawing lbl leaf -> Drawing lbl leaf
horizD' :: Distance -> Drawing lbl leaf -> Drawing lbl leaf
horizcD :: Drawing lbl leaf -> Drawing lbl leaf
horizcD' :: Distance -> Drawing lbl leaf -> Drawing lbl leaf
isVisibleDrawingPart :: Drawing lbl leaf -> DPath -> Bool
listFonts :: FudgetIO f => String -> Int -> ([FontName] -> f b ho) -> f b ho
listFontsF :: String -> Int -> Cont (F b c) [FontName]
listFontsWithInfo :: FudgetIO f =>
                     String -> Int -> ([(FontName, FontStruct)] -> f b ho) -> f b ho
loadFont :: FudgetIO f => String -> (FontId -> f b ho) -> f b ho
loadFontF :: String -> Cont (F b c) FontId
loadQueryFont :: FudgetIO f => String -> (Maybe FontStruct -> f b ho) -> f b ho
loadQueryFontF :: String -> Cont (F b c) (Maybe FontStruct)
mapLeafDrawing :: (t -> leaf) -> Drawing lbl t -> Drawing lbl leaf
measureImageK :: PixmapGen a => a -> GCtx -> (MeasuredGraphics -> K i o) -> K i o
measureImageString :: String -> GCtx -> (MeasuredGraphics -> K b c) -> K b c
measurePackedString :: PackedString -> GCtx -> (MeasuredGraphics -> K b c) -> K b c
measureString :: String -> GCtx -> (MeasuredGraphics -> K b c) -> K b c
measureText :: Show a => a -> GCtx -> (MeasuredGraphics -> K b c) -> K b c
measuredGraphics2Pixmap :: FudgetIO f =>
                           MeasuredGraphics -> (PixmapImage -> f b ho) -> f b ho
northwestD :: Drawing lbl leaf -> Drawing lbl leaf
padD :: Distance -> Drawing lbl leaf -> Drawing lbl leaf
padFD :: Int -> FlexibleDrawing -> FlexibleDrawing
placedD :: Placer -> Drawing lbl leaf -> Drawing lbl leaf
pmCreateGC :: FudgetIO f =>
              PixmapId ->
              GCId -> [GCAttributes Pixel FontId] -> (GCId -> f b ho) -> f b ho
pmCreateGCF :: PixmapId -> GCId -> GCAttributeList -> (GCId -> F a b) -> F a b
queryFont :: FudgetIO f => FontId -> (FontStruct -> f b ho) -> f b ho
queryFontF :: FontId -> Cont (F b c) FontStruct
readBitmapFile :: FudgetIO f => String -> (BitmapReturn -> f b ho) -> f b ho
rectD :: Size -> Drawing lbl Gfx
removecursor :: CompiledGraphics -> CompiledGraphics
safeLoadQueryFont :: FudgetIO f => FontName -> (FontStruct -> f b ho) -> f b ho
safeLoadQueryFontF :: FontName -> (FontStruct -> F b c) -> F b c
setFontCursor :: Int -> K a b -> K a b
shrink :: Rect -> Rect
size :: Point
spacedD :: Spacer -> Drawing lbl leaf -> Drawing lbl leaf
stackD :: [Drawing lbl leaf] -> Drawing lbl leaf
tryConvColorRGBK :: FudgetIO f => RGB -> (Maybe Pixel -> f b ho) -> f b ho
tryLoadFont :: FudgetIO f => String -> (Maybe FontId -> f b ho) -> f b ho
undefineCusror :: K i o -> K i o
ungroupParts :: Int -> Drawing lbl leaf -> Drawing lbl leaf
update_font_id :: FontStruct -> FontId -> FontStruct
usefontstructs :: String
vMirror :: (Rect -> [Point]) -> Rect -> [Point]
vboxlD :: [Drawing lbl leaf] -> Drawing lbl leaf
vboxlD' :: Distance -> [Drawing lbl leaf] -> Drawing lbl leaf
vertD :: Drawing lbl leaf -> Drawing lbl leaf
vertD' :: Distance -> Drawing lbl leaf -> Drawing lbl leaf
vertlD :: Drawing lbl leaf -> Drawing lbl leaf
vertlD' :: Distance -> Drawing lbl leaf -> Drawing lbl leaf
visibleAncestor :: Drawing lbl leaf -> [Int] -> [Int]
wCreateGC :: FudgetIO f =>
             GCId -> [GCAttributes Pixel FontId] -> (GCId -> f b ho) -> f b ho
wCreateGCF :: GCId -> GCAttributeList -> (GCId -> F a b) -> F a b
westD :: Drawing lbl leaf -> Drawing lbl leaf

KernelUtils

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)
atomName :: FudgetIO f => Atom -> (Maybe String -> f b ho) -> f b ho
atomNameF :: Atom -> Cont (F b c) (Maybe String)
atomNameK :: Atom -> Cont (K b c) (Maybe String)
changeBackPixel :: (Show a, ColorGen a) => a -> K i o -> K i o
changeBackPixmap :: (ColorGen a1, ColorGen a2, Show a1, Show a2) =>
                    a1 -> a2 -> Point -> [DrawCommand] -> K i o -> K i o
changeBg :: ColorName -> K a b -> K a b
changeGetBackPixel :: (Show a, ColorGen a) => a -> (Pixel -> K i o) -> K i o
compK :: K a b -> K c d -> K (a  c) (b  d)
darkGreyBgK :: K b ho -> K b ho
defaultRootWindowF :: Cont (F b c) Window
defaultRootWindowK :: Cont (K b c) Window
defaultVisual :: FudgetIO f => (Visual -> f b ho) -> f b ho
dynShapeK :: [GCAttributes ColorName String] ->
             (Size -> [DrawCommand]) -> K c d -> K ((Size -> [DrawCommand])  c) (b  d)
exitK :: p -> K b ho
getGeometryK :: Cont (K b c) (Rect, Int, Int)
getWindowPropertyK :: Int ->
                      Atom -> Bool -> Atom -> Cont (K b c) (Atom, Int, Int, Int, String)
greyBgK :: K b ho -> K b ho
internAtom :: FudgetIO f => String -> Bool -> (Atom -> f b ho) -> f b ho
internAtomF :: String -> Bool -> Cont (F b c) Atom
internAtomK :: String -> Bool -> Cont (K b c) Atom
knobBgK :: K b ho -> K b ho
lightGreyBgK :: K b ho -> K b ho
mapstateK :: (t -> KEvent hi -> (t, [KCommand ho])) -> t -> K hi ho
parK :: K a b -> K a b -> K a b
queryPointerK :: Cont (K b c) (Bool, Point, Point, ModState)
queryTreeF :: Cont (F b c) (Window, Window, [Window])
queryTreeK :: Cont (K b c) (Window, Window, [Window])
quitK :: (K (String  Bool) a -> K (String  Bool) a) -> K hi ho
reportK :: K hi () -> K hi ()
shapeK :: (Size -> [DrawCommand]) -> K a b -> K a b
simpleF :: String -> (Drawer -> Drawer -> Fms' a c d) -> Size -> a -> F c d
simpleK :: (Drawer -> Drawer -> Fms' a b c) -> Size -> a -> K b c
simpleWindowF :: (Drawer -> Drawer -> Fms' a1 a2 b) ->
                 Size -> Bool -> Bool -> a1 -> F a2 b
unmapWindowK :: K i o -> K i o
wmDeleteWindowK :: (Atom -> K b c) -> K b c
wmK :: Maybe (K (String  Bool) c -> K (String  Bool) c) -> K (String  Bool) c

StreamProc

Data entry field postprocessors:
inputDoneSP :: SP (InputMsg b) b
inputLeaveDoneSP :: SP (InputMsg b) b
stripInputSP :: SP (InputMsg b) b
Delay the activation of a stream processor or fudget:
delaySP :: SP a b -> SP a b
Monadic style:
type Cont c a = (a -> c) -> c
Stream processor combinators:
compEitherSP :: SP a1 a2 -> SP a3 b -> SP (a1  a3) (a2  b)
compMsgSP :: SP a1 a2 -> SP a3 b -> SP (Message a1 a3) (Message a2 b)
idHighSP :: SP a1 a2 -> SP (Message a1 b) (Message a2 b)
idLeftSP :: SP a1 b -> SP (a2  a1) (a2  b)
idLowSP :: SP a1 b -> SP (Message a2 a1) (Message a2 b)
idRightSP :: SP a1 a2 -> SP (a1  b) (a2  b)
postMapSP :: (t -> b) -> SP a t -> SP a b
preMapSP :: SP a b -> (t -> a) -> SP t b
prepostMapSP :: (t1 -> a) -> (t2 -> b) -> SP a t2 -> SP t1 b
serCompSP :: SP a1 b -> SP a2 a1 -> SP a2 b
Stream processor combinators that create circular connections:
loopLeftSP :: SP (a1  a2) (a1  b) -> SP a2 b
loopSP :: SP a a -> SP a a
Stream processor construction:
getSP :: Cont (SP a b) a
nullSP :: SP a b
putSP :: b -> SP a b -> SP a b
Stream processor equivalents of some common list processing functions:
chopSP :: ((b -> SP a b) -> SP a b) -> SP a b
concatMapAccumlSP :: (t -> a -> (t, [b])) -> t -> SP a b
concatMapSP :: (t -> [b]) -> SP t b
concatSP :: SP [b] b
filterSP :: (b -> Bool) -> SP b b
idSP :: SP b b
mapAccumlSP :: (t -> a -> (t, b)) -> t -> SP a b
mapSP :: (t -> b) -> SP t b
splitAtElemSP :: (a -> Bool) -> Cont (SP a b) [a]
zipSP :: [a] -> SP b (a, b)
Stream processor manipulation:
startupSP :: [a] -> SP a b -> SP a b
Stream processor that splits a stream of pairs:
splitSP :: SP (a, b) (a  b)
The function that turns a stream processor into a list processing function:
runSP :: SP a1 a2 -> [a1] -> [a2]
The type of plain stream processors:
data SP a b = ...
Miscellaneous (the rest):
data DynMsg a b = ...
type DynSPMsg a b = DynMsg a (SP a b)
type SPm i o ans = Mk (SP i o) ans
type SPms i o s ans = Ms (SP i o) s ans
class StreamProcIO sp where ...
appendStartSP :: [b] -> SP a b -> SP a b
compSP :: SP a1 a2 -> SP a3 b -> SP (a1  a3) (a2  b)
concSP :: SP [b] b
concmapSP :: (t -> [b]) -> SP t b
dynforkmerge :: Eq a => SP (a, DynSPMsg b c) (a, c)
feedSP :: a -> [a] -> SP a b -> SP a b
filterJustSP :: SP (Maybe b) b
filterLeftSP :: SP (b1  b2) b1
filterRightSP :: SP (a1  b) b
getSPm :: SPm i o i
getSPms :: SPms i o s i
idempotSP :: Eq a => SP a a
inputListSP :: Eq a => [a] -> SP (a, InputMsg b) (InputMsg [(a, b)])
inputPairSP :: SP ((InputMsg a)  (InputMsg b)) (InputMsg (a, b))
interpSP :: (t1 -> t2 -> t2) -> ((a -> t2) -> t2) -> t2 -> SP a t1 -> t2
loadSPms :: SPms i o s s
loopOnlySP :: SP a a -> SP a b
loopThroughRightSP :: SP (a1  a2) (a3  b) -> SP a3 a1 -> SP a2 b
mapFilterSP :: (t -> Maybe b) -> SP t b
mapstateSP :: (t -> a -> (t, [b])) -> t -> SP a b
monadSP :: SPm i o () -> SP i o
nullSPm :: SPm i o ()
nullSPms :: SPms i o s ()
parSP :: SP a b -> SP a b -> SP a b
pullSP :: SP a1 a2 -> ([a2], SP a1 a2)
putSPm :: o -> SPm i o ()
putSPms :: o -> SPms i o s ()
puts :: (Foldable t, StreamProcIO sp) => t o -> sp i o -> sp i o
putsSP :: [b] -> SP a b -> SP a b
putsSPm :: [o] -> SPm i o ()
putsSPms :: [o] -> SPms i o s ()
seqSP :: SP a b -> SP a b -> SP a b
stateMonadSP :: s -> SPms i o s ans -> (ans -> SP i o) -> SP i o
stepSP :: [b] -> Cont (SP a b) a
storeSPms :: s -> SPms i o s ()
toBothSP :: SP b (b  b)
toSPm :: SP i o -> SPm i o ()
walkSP :: SP a1 a2 -> a1 -> ([a2], SP a1 a2)

InOut

A fudget that outputs ticks after specific delays and/or at specific intervals:
data Tick = ...
timerF :: F (Maybe (Int, Int)) Tick
File system access:
appStorageF :: (Read a, Show a) => String -> a -> F a a
readDirF :: F String (String, IOError  [String])
readFileF :: F String (String, IOError  String)
readXdgFileF :: XdgDirectory -> F String (String, IOError  String)
writeFileF :: F (String, String) (String, IOError  ())
writeXdgFileF :: XdgDirectory -> F (String, String) (String, IOError  ())
Haskell Dialogue IO:
hIO :: FudgetIO f => Request -> (Response -> f b ho) -> f b ho
hIOF :: Request -> (Response -> F a b) -> F a b
hIOSucc :: FudgetIO f => Request -> f b ho -> f b ho
hIOSuccF :: Request -> F a b -> F a b
hIOerr :: FudgetIO f =>
          Request -> (IOError -> f b ho) -> (Response -> f b ho) -> f b ho
hIOerrF :: Request -> (IOError -> F a b) -> (Response -> F a b) -> F a b
haskellIO :: FudgetIO f => Request -> (Response -> f b ho) -> f b ho
haskellIOF :: Request -> (Response -> F a b) -> F a b
Sockets:
asyncTransceiverF :: Socket -> F String String
asyncTransmitterF :: Socket -> F String b
openFileAsSocketErrF :: FudgetIO f =>
                        String ->
                        String -> (IOError -> f b ho) -> (Socket -> f b ho) -> f b ho
openFileAsSocketF :: FudgetIO f => String -> String -> (Socket -> f b ho) -> f b ho
openLSocketErrF :: FudgetIO f =>
                   Port -> (IOError -> f b ho) -> (LSocket -> f b ho) -> f b ho
openLSocketF :: FudgetIO f => Port -> (LSocket -> f b ho) -> f b ho
openSocketErrF :: FudgetIO f =>
                  Host ->
                  Port -> (IOError -> f b ho) -> (Socket -> f b ho) -> f b ho
openSocketF :: FudgetIO f => Host -> Port -> (Socket -> f b ho) -> f b ho
receiverF :: Socket -> F e String
transceiverF :: Socket -> F String String
transmitterF :: Socket -> F String b
Stdio:
appendChanK :: FudgetIO f => String -> String -> f b ho -> f b ho
echoK :: FudgetIO f => String -> f b ho -> f b ho
inputLinesSP :: SP String String
linesSP :: SP Char String
outputF :: String -> F String a
stderrF :: F String a
stdinF :: F b String
stdioF :: F String String
stdoutF :: F String a
Miscellaneous (the rest):
asyncTransmitterF' :: Socket -> F String ()
closerF :: Socket -> F ans ho
getLocalTime :: FudgetIO f => (CalendarTime -> f b ho) -> f b ho
getModificationTime :: FudgetIO f =>
                       FilePath ->
                       (IOError -> f b ho) -> (ClockTime -> f b ho) -> f b ho
getTime :: FudgetIO f => (ClockTime -> f b ho) -> f b ho
ioF :: K a b -> F a b
readBinaryFileF :: F String (String, IOError  String)
readM :: Read a => String -> Maybe a
receiverF' :: Socket -> F hi String
subProcessF :: String -> F String (String  String)
transmitterF' :: Socket -> F String ()
unsafeGetDLValue :: DLValue -> a
writeFileF' :: (a -> t -> Request) -> F (a, t) (a, IOError  ())

LowLevel

Monadic style:
type Cont c a = (a -> c) -> c
Sockets:
sIO :: FudgetIO f => SocketRequest -> (SocketResponse -> f b ho) -> f b ho
sIOerr :: FudgetIO f =>
          SocketRequest ->
          (IOError -> f b ho) -> (SocketResponse -> f b ho) -> f b ho
sIOstr :: FudgetIO f => SocketRequest -> (String -> f b ho) -> f b ho
sIOsucc :: FudgetIO f => SocketRequest -> f b ho -> f b ho
select :: FudgetIO f => [Descriptor] -> f hi ho -> f hi ho
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):
class FudgetIO f where ...
class HasCache xxx 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 ho -> (KEvent hi -> Maybe a) -> Cont (K hi ho) a
cmdContLow :: FudgetIO f =>
              FRequest -> (FResponse -> Maybe ans) -> (ans -> f b ho) -> f b ho
cmdContMsg :: FudgetIO f =>
              KCommand ho -> (KEvent hi -> Maybe ans) -> (ans -> f hi ho) -> f hi ho
cmdContSP :: a -> (b -> Maybe c) -> Cont (SP b a) c
contMap :: StreamProcIO sp => (i -> (o -> sp i o) -> sp i o) -> sp i o
conts :: (a -> Cont c b) -> [a] -> Cont c [b]
dropSP :: (t1 -> Maybe t2) -> (t2 -> SP t1 b) -> SP t1 b
fContWrap :: Cont (FSP hi ho) a -> Cont (F hi ho) a
getBWidth :: [WindowChanges] -> Maybe Int
getHigh :: FudgetIO f => (ans -> f ans ho) -> f ans ho
getLeftSP :: (t -> SP (t  b1) b2) -> SP (t  b1) b2
getLow :: FudgetIO f => (FResponse -> f b ho) -> f b ho
getRightSP :: (t -> SP (a1  t) b) -> SP (a1  t) b
kContWrap :: Cont (KSP hi ho) a -> Cont (K hi ho) a
kernelF :: K a b -> F a b
kernelTag :: Path
openDisplay :: DisplayName -> Cont (F b c) Display
putHigh :: FudgetIO f => ho -> f hi ho -> f hi ho
putLow :: FudgetIO f => FRequest -> f hi ho -> f hi ho
putLows :: (Foldable t, FudgetIO f) => t FRequest -> f hi ho -> f hi ho
putMsgs :: (Foldable t, FudgetIO f) => t (KCommand ho) -> f hi ho -> f hi ho
spIO :: SP (Path, Response) (Path, Request) -> IO ()
tagEventsSP :: F i o -> SP (Path, Response) (Path, Request)
toKernel :: [b1] -> [Message (Path, b1) b2]
tryGet :: Cont c (Maybe a) -> Cont c a -> Cont c a
tryM :: Cont c (Maybe a) -> c -> Cont c a
waitForF :: (a -> Maybe b) -> Cont (F a c) b
waitForFu :: (KEvent hi -> Maybe ans) -> Cont (F hi ho) ans
waitForK :: (KEvent hi -> Maybe a) -> Cont (K hi ho) a
waitForSP :: (a -> Maybe t) -> (t -> SP a b) -> SP a b
windowKF :: (Rect -> FRequest) ->
            Bool ->
            Bool -> [FRequest] -> Maybe Rect -> K a b -> F c d -> F (a  c) (b  d)
xcommand :: FudgetIO f => XCommand -> f hi ho -> f hi ho
xcommandF :: XCommand -> F i o -> F i o
xcommandK :: XCommand -> K i o -> K i o
xcommands :: FudgetIO f => [XCommand] -> f hi ho -> f hi ho
xcommandsF :: [XCommand] -> F i o -> F i o
xcommandsK :: [XCommand] -> K i o -> K i o
xrequest :: FudgetIO f =>
            XRequest -> (XResponse -> Maybe ans) -> (ans -> f b ho) -> f b ho
xrequestF :: XRequest -> (XResponse -> Maybe a) -> Cont (F b c) a
xrequestK :: XRequest -> (XResponse -> Maybe a) -> Cont (K b c) a

XTypesModules

Drawing commands:
data DrawCommand = ...
data Drawable = ...
draw :: Drawable -> GCId -> DrawCommand -> FRequest
drawCircle :: Point -> Int -> DrawCommand
drawMany :: Drawable -> [(GCId, [DrawCommand])] -> FRequest
fillCircle :: Point -> Int -> DrawCommand
pmDraw :: PixmapId -> GCId -> DrawCommand -> FRequest
pmDrawMany :: PixmapId -> [(GCId, [DrawCommand])] -> FRequest
wDraw :: GCId -> DrawCommand -> FRequest
wDrawMany :: [(GCId, [DrawCommand])] -> FRequest
Drawing in a pixmap:
pmCopyArea :: PixmapId -> GCId -> Drawable -> Rect -> Point -> FRequest
pmCopyPlane :: PixmapId -> GCId -> Drawable -> Rect -> Point -> Int -> FRequest
pmCreatePutImage :: PixmapId -> GCId -> Rect -> ImageFormat -> [Pixel] -> FRequest
pmDrawArc :: PixmapId -> GCId -> Rect -> Int -> Int -> FRequest
pmDrawImageString :: PixmapId -> GCId -> Point -> String -> FRequest
pmDrawImageString16 :: PixmapId -> GCId -> Point -> String -> FRequest
pmDrawLine :: PixmapId -> GCId -> Line -> FRequest
pmDrawLines :: PixmapId -> GCId -> CoordMode -> [Point] -> FRequest
pmDrawPoint :: PixmapId -> GCId -> Point -> FRequest
pmDrawRectangle :: PixmapId -> GCId -> Rect -> FRequest
pmDrawString :: PixmapId -> GCId -> Point -> String -> FRequest
pmDrawString16 :: PixmapId -> GCId -> Point -> String -> FRequest
pmFillArc :: PixmapId -> GCId -> Rect -> Int -> Int -> FRequest
pmFillPolygon :: PixmapId -> GCId -> Shape -> CoordMode -> [Point] -> FRequest
pmFillRectangle :: PixmapId -> GCId -> Rect -> FRequest
Drawing in a window:
clearArea :: Rect -> Bool -> FRequest
clearWindow :: FRequest
wCopyArea :: GCId -> Drawable -> Rect -> Point -> FRequest
wCopyPlane :: GCId -> Drawable -> Rect -> Point -> Int -> FRequest
wCreatePutImage :: GCId -> Rect -> ImageFormat -> [Pixel] -> FRequest
wDrawArc :: GCId -> Rect -> Int -> Int -> FRequest
wDrawCircle :: GCId -> Point -> Int -> FRequest
wDrawImageString :: GCId -> Point -> String -> FRequest
wDrawImageString16 :: GCId -> Point -> String -> FRequest
wDrawLine :: GCId -> Line -> FRequest
wDrawLines :: GCId -> CoordMode -> [Point] -> FRequest
wDrawPoint :: GCId -> Point -> FRequest
wDrawRectangle :: GCId -> Rect -> FRequest
wDrawString :: GCId -> Point -> String -> FRequest
wDrawString16 :: GCId -> Point -> String -> FRequest
wFillArc :: GCId -> Rect -> Int -> Int -> FRequest
wFillCircle :: GCId -> Point -> Int -> FRequest
wFillPolygon :: GCId -> Shape -> CoordMode -> [Point] -> FRequest
wFillRectangle :: GCId -> Rect -> FRequest
Drawing: auxiliary types:
data CoordMode = ...
type GCAttributeList = [GCAttributes Pixel FontId]
data GCAttributes a b = ...
data GCCapStyle = ...
data GCFillStyle = ...
data GCFunction = ...
data GCJoinStyle = ...
data GCLineStyle = ...
data GCSubwindowMode = ...
data ImageFormat = ...
data Shape = ...
xyBitmap :: ImageFormat
xyPixmap :: ImageFormat
zPixmap :: ImageFormat
Drawing: colors:
data Color = ...
data Pixel = ...
data RGB = ...
blackRGB :: RGB
grayRGB :: Int -> RGB
maxRGB :: Int
pixel0 :: Pixel
pixel1 :: Pixel
whiteRGB :: RGB
Events:
type Event = XEvent
data XEvent = ...
Events: auxiliary types:
data Button = ...
data ClientData = ...
data Detail = ...
data EventMask = ...
data GrabPointerResult = ...
data KeyCode = ...
type KeyLookup = String
type ModState = [Modifiers]
data Mode = ...
data Modifiers = ...
data Pressed = ...
data Visibility = ...
Font metrics:
data FontStruct = ...
Fudget low-level stream types:
data AEvent = ...
type AsyncInput = (Descriptor, AEvent)
type Command = XCommand
data FRequest = ...
data FResponse = ...
data SocketRequest = ...
data SocketResponse = ...
data XCommand = ...
data XRequest = ...
data XResponse = ...
clearWindowExpose :: XCommand
moveResizeWindow :: Rect -> XCommand
moveWindow :: Point -> XCommand
resizeWindow :: Point -> XCommand
Resource identifiers:
data Atom = ...
data ColormapId = ...
data CursorId = ...
data FontId = ...
data GCId = ...
data PixmapId = ...
data VisualID = ...
type Window = WindowId
data WindowId = ...
defaultColormap :: ColormapId
rootGC :: GCId
Window configuration:
data BackingStore = ...
data Gravity = ...
data ShapeKind = ...
data ShapeOperation = ...
data StackMode = ...
data WindowAttributes = ...
data WindowChanges = ...
Miscellaneous (the rest):
data BitmapData = ...
data BitmapReturn = ...
type ColorName = String
data DLHandle = ...
data DLValue = ...
data DbeBackBufferId = ...
type Depth = Int
data Descriptor = ...
data Display = ...
data DisplayClass = ...
type DisplayName = String
type FontName = String
data FontStructList = ...
type Host = String
type KeySym = String
data LSocket = ...
data LayoutMessage = ...
data LayoutResponse = ...
data Ordering' = ...
type Peer = Host
type PlaneMask = Pixel
type Port = Int
data PropertyMode = ...
type RmClass = String
type RmDatabase = Int
type RmName = String
type RmQuery = (RmClass, RmName)
type RmSpec = [RmQuery]
type RmValue = String
data Selection = ...
data Socket = ...
data SwapAction = ...
type Time = Int
data Timer = ...
data Visual = ...
type Width = Int
type XDisplay = Display
data XID = ...
type XWId = WindowId
clEventMask :: [EventMask]
clModifiers :: [Modifiers]
copyFromParent :: Depth
currentTime :: Time
cursorNone :: CursorId
invcol :: Pixel -> Pixel -> Pixel
invertColorGCattrs :: Pixel -> Pixel -> [GCAttributes Pixel b]
layoutRequestCmd :: LayoutRequest -> FRequest
noDisplay :: Display
noWindow :: WindowId
none :: PixmapId
parentRelative :: PixmapId
pmDrawImageStringPS :: PixmapId -> GCId -> Point -> PackedString -> FRequest
pmDrawStringPS :: PixmapId -> GCId -> Point -> PackedString -> FRequest
propModeAppend :: PropertyMode
propModePrepend :: PropertyMode
propModeReplace :: PropertyMode
rmNothing :: Int
rootWindow :: WindowId
wDrawImageStringPS :: GCId -> Point -> PackedString -> FRequest
wDrawStringPS :: GCId -> Point -> PackedString -> FRequest
windowNone :: WindowId

Types

Buttons:
data Click = ...
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
Fudget low-level stream types:
data FRequest = ...
data FResponse = ...
Geometry:
boundingRect :: Rect -> Rect -> Rect
diffRect :: Rect -> Rect -> [Rect]
intersectRects :: [Rect] -> Rect -> [Rect]
overlaps :: Rect -> Rect -> Bool
Pop-up windows:
data ConfirmMsg = ...
The Fudget type:
data F hi ho = ...
type FCommand a = Message TCommand a
type FEvent a = Message TEvent a
type FSP hi ho = SP (FEvent hi) (FCommand ho)
type Fudget a b = F a b
type TCommand = (Path, FRequest)
type TEvent = (Path, FResponse)
The fudget kernel type:
type Fa a b c d = SP (Message a c) (Message b d)
data K hi ho = ...
type KCommand a = Message FRequest a
type KEvent a = Message FResponse a
type KSP hi ho = SP (KEvent hi) (KCommand ho)
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 :: (t -> a) -> InputMsg t -> InputMsg a
stripInputMsg :: InputMsg p -> p
tstInp :: (t -> p) -> InputMsg t -> p
Miscellaneous (the rest):
data Direction = ...
data Message a b = ...
type Path = [Direction]
data PopupMsg a = ...
aHigh :: (t -> b) -> Message a t -> Message a b
aLow :: (t -> a) -> Message t b -> Message a b
absPath :: Path -> Path -> Path
ff :: FSP hi ho -> F hi ho
fromConfirm :: ConfirmMsg -> Click  Click
here :: Path
inputButtonKey :: KeySym
inputLeaveKey :: KeySym
isHigh :: Message a b -> Bool
isLow :: Message a b -> Bool
kk :: KSP hi ho -> K hi ho
listEnd :: Int
mapMessage :: (t1 -> a) -> (t2 -> b) -> Message t1 t2 -> Message a b
message :: (t1 -> p) -> (t2 -> p) -> Message t1 t2 -> p
moveDrawCommand :: DrawCommand -> Point -> DrawCommand
moveDrawCommands :: [DrawCommand] -> Point -> [DrawCommand]
path :: Path -> (Direction, Path)
pushMsg :: Functor f => Message (f a) (f b) -> f (Message a b)
showPath :: Path -> String
stripHigh :: Message a1 a2 -> Maybe a2
stripLow :: Message a b -> Maybe a
subPath :: Path -> Path -> Bool
toConfirm :: a  b -> ConfirmMsg
turn :: Direction -> Path -> Path
unF :: F hi ho -> FSP hi ho
unK :: K hi ho -> KSP hi ho

FudUtilities

Abstract data type for file paths:
data AFilePath = ...
aFilePath :: FilePath -> AFilePath
compactPath :: AFilePath -> AFilePath
extendPath :: AFilePath -> String -> AFilePath
filePath :: AFilePath -> FilePath
isAbsolute :: AFilePath -> Bool
joinPaths :: AFilePath -> AFilePath -> AFilePath
pathHead :: AFilePath -> AFilePath
pathLength :: AFilePath -> Int
pathRelativeTo :: AFilePath -> AFilePath -> AFilePath
pathTail :: AFilePath -> String
rootPath :: AFilePath
Environment:
argFlag :: String -> Bool -> Bool
argKey :: String -> String -> String
argReadKey :: (Read p, Show p) => String -> p -> p
args :: [String]
bgColor :: ColorName
buttonFont :: FontName
defaultFont :: FontName
defaultPosition :: Maybe Point
defaultSep :: Num a => a
defaultSize :: Maybe Point
edgeWidth :: Int
fgColor :: ColorName
inputBg :: ColorName
inputFg :: ColorName
labelFont :: FontName
look3d :: Bool
menuFont :: FontName
new3d :: Bool
options :: [(String, String)]
paperColor :: ColorName
progName :: String
resourceName :: String
shadowColor :: ColorName
shineColor :: ColorName
Geometry, part 1:
data Line = ...
data Point = ...
data Rect = ...
type Size = Point
diag :: Int -> Point
lL :: Int -> Int -> Int -> Int -> Line
origin :: Point
pP :: Int -> Int -> Point
rR :: Int -> Int -> Int -> Int -> Rect
Geometry, part 2:
class Move a where ...
=.> :: Point -> Point -> Bool
confine :: Rect -> Rect -> Rect
fmove :: (Functor f, Move b) => Point -> f b -> f b
freedom :: Rect -> Rect -> Point
growrect :: Rect -> Point -> Rect
inRect :: Point -> Rect -> Bool
line2rect :: Line -> Rect
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
rect2line :: Rect -> Line
rectMiddle :: Rect -> Point
rmax :: Rect -> Rect -> Rect
rsub :: Rect -> Rect -> Point
scale :: (RealFrac a1, Integral b, Integral a2) => a1 -> a2 -> b
scalePoint :: RealFrac a => a -> Point -> Point
sizerect :: Rect -> Size -> Rect
Monadic style:
type Cont c a = (a -> c) -> c
Text utilities:
expandTabs :: Int -> String -> String
rmBS :: String -> String
wrapLine :: Int -> [a] -> [[a]]
Various utility functions for pairs and lists:
aboth :: (t -> b) -> (t, t) -> (b, b)
anth :: Int -> (a -> a) -> [a] -> [a]
gmap :: Foldable t1 => (t2 -> [a] -> [a]) -> (t3 -> t2) -> t1 t3 -> [a]
issubset :: (Foldable t1, Foldable t2, Eq a) => t1 a -> t2 a -> Bool
lhead :: [a1] -> [a2] -> [a2]
loop :: (t -> t) -> t
lsplit :: [a1] -> [a2] -> ([a2], [a2])
ltail :: [a1] -> [a2] -> [a2]
mapPair :: (t1 -> a, t2 -> b) -> (t1, t2) -> (a, b)
number :: Int -> [a] -> [(Int, a)]
oo :: (t1 -> t2) -> (t3 -> t4 -> t1) -> t3 -> t4 -> t2
pair :: a -> b -> (a, b)
pairwith :: (t -> b) -> t -> (t, b)
part :: (a -> Bool) -> [a] -> ([a], [a])
remove :: Eq t => t -> [t] -> [t]
replace :: Eq a => (a, b) -> [(a, b)] -> [(a, b)]
segments :: (a -> Bool) -> [a] -> [[a]]
setFst :: (a1, b) -> a2 -> (a2, b)
setSnd :: (a, b1) -> b2 -> (a, b2)
swap :: (b, a) -> (a, b)
unionmap :: (Foldable t1, Eq a) => (t2 -> [a]) -> t1 t2 -> [a]
Various utility functions for the Either type:
filterLeft :: [b1  b2] -> [b1]
filterRight :: [a  b] -> [b]
fromLeft :: a  b -> a
fromRight :: a  b -> b
isLeft :: a  b -> Bool
isRight :: a  b -> Bool
mapEither :: (t1 -> a) -> (t2 -> b) -> t1  t2 -> a  b
splitEitherList :: [a1  a2] -> ([a1], [a2])
stripEither :: p  p -> p
stripLeft :: a  b -> Maybe a
stripRight :: a1  a2 -> Maybe a2
swapEither :: b  a -> a  b
Various utility functions for the Maybe type.:
plookup :: Foldable t => (a -> Bool) -> t (a, b) -> Maybe b
Miscellaneous (the rest):
argKeyList :: String -> [String] -> [String]
ifC :: (a -> a) -> Bool -> a -> a
lunconcat :: [[a1]] -> [a2] -> [[a2]]
mapHigh :: (t -> [b]) -> SP (Message a t) (Message a b)
mapList :: (a -> b) -> [a] -> [b]
mapLow :: (t -> [a]) -> SP (Message t b) (Message a b)
mapstateHigh :: (t1 -> t2 -> (t1, [b])) -> t1 -> SP (Message a t2) (Message a b)
mapstateLow :: (t1 -> t2 -> (t1, [a])) -> t1 -> SP (Message t2 b) (Message a b)
thenC :: Bool -> (a -> a) -> a -> a
unconcat :: [Int] -> [a] -> [[a]]
version :: String
version_0_18_2 :: String

Debug

A fudget that shows the high level input and output of a fudget on the standard error output:
spyF :: (Show b, Show a2) => F a2 b -> F a2 b
An identity fudget that copies messages to the standard error output:
teeF :: (b -> String) -> String -> F b b
Miscellaneous (the rest):
ctrace :: Show a1 => String -> a1 -> a2 -> a2
maptrace :: Eq b => String -> [b] -> [b]
showCommandF :: String -> F a b -> F a b

DefaultParams

Displaying text:
class HasInitText xxx where ...
Spacers: alignment:
type Alignment = Double
Miscellaneous (the rest):
type Customiser a = a -> a
class HasAlign xxx where ...
class HasBgColorSpec xxx where ...
class HasBorderWidth xxx where ...
class HasFgColorSpec xxx where ...
class HasFontSpec xxx where ...
class HasInitDisp xxx where ...
class HasInitSize xxx where ...
class HasKeys xxx where ...
class HasMargin xxx where ...
class HasSizing xxx where ...
class HasStretchable xxx where ...
class HasWinAttr xxx where ...
type PF p a b = F ((Customiser p)  a) b
type PK p a b = K ((Customiser p)  a) b
cust :: (a -> a) -> Customiser a
fromMaybe :: a -> Maybe a -> a
getpar :: (t -> Maybe c) -> [t] -> c
getparMaybe :: (t -> Maybe a) -> [t] -> Maybe a
noPF :: PF p a b -> F a b
setBgColor :: (HasBgColorSpec xxx, Show a, ColorGen a) => a -> Customiser xxx
setFgColor :: (HasFgColorSpec xxx, Show a, ColorGen a) => a -> Customiser xxx
setFont :: (HasFontSpec xxx, Show a, FontGen a) => a -> Customiser xxx
standard :: Customiser a

ContribFudgets

Abstract data type for file paths:
aFilePath :: FilePath -> AFilePath
Client/Server programming:
data ClientMsg a = ...
data SocketMsg a = ...
data TPort a b = ...
data TServerAddress c s = ...
socketServerF :: Int ->
                 (Socket -> Peer -> F a1 (SocketMsg a2)) -> F (Int, a1) (Int, ClientMsg a2)
tPort :: (Show a, Read a, Show b, Read b) => Port -> TPort a b
tSocketServerF :: (Read c, Show s) =>
                  TPort c s ->
                  (Peer -> F s (SocketMsg c) -> F a (SocketMsg b)) ->
                  F (Int, a) (Int, ClientMsg b)
tTransceiverF :: (Show c, Read s) => TServerAddress c s -> F c (SocketMsg s)
Containers:
hSplitF :: F a1 a2 -> F c b -> F (a1  c) (a2  b)
hSplitF' :: Double -> F a1 a2 -> F c b -> F (a1  c) (a2  b)
splitF' :: LayoutDir -> Double -> F a1 a2 -> F c b -> F (a1  c) (a2  b)
vSplitF :: F a1 a2 -> F c b -> F (a1  c) (a2  b)
vSplitF' :: Double -> F a1 a2 -> F c b -> F (a1  c) (a2  b)
Displaying and interacting with composite graphical objects:
data GfxChange gfx = ...
data GfxCommand path gfx = ...
data GfxEvent path = ...
highlightGfx :: path -> Bool -> GfxCommand path gfx
isGfxButtonEvent :: GfxEvent path -> Maybe Button
isMouseClick :: GfxEvent a -> Maybe a
mapGfxCommandPath :: (t -> path) -> GfxCommand t gfx -> GfxCommand path gfx
mapGfxEventPath :: (t -> Maybe path) -> GfxEvent t -> GfxEvent path
replaceGfx :: path -> gfx -> GfxCommand path gfx
Menus:
menuF :: Eq a => Menu a -> F a a
Shells:
auxShellF :: String -> F c b -> F (Bool  c) (Bool  b)
auxShellF' :: (ShellF -> ShellF) -> String -> F c b -> F (Bool  c) (Bool  b)
delayedAuxShellF :: String -> F c b -> F (Bool  c) (Bool  b)
delayedAuxShellF' :: (ShellF -> ShellF) -> String -> F c b -> F (Bool  c) (Bool  b)
fileShellF :: (c1 -> String, String -> String  c1, Maybe c1) ->
              String -> F c1 (InputMsg c1) -> F c2 d
fileShellF' :: (ShellF -> ShellF) ->
               (c1 -> String, String -> String  c1, Maybe c1) ->
               String -> F c1 (InputMsg c1) -> F c2 d
showReadFileShellF :: (Show a, Read a) => Maybe a -> String -> F a (InputMsg a) -> F c d
showReadFileShellF' :: (Show a, Read a) =>
                       (ShellF -> ShellF) ->
                       Maybe a -> String -> F a (InputMsg a) -> F c d
textFileShellF :: String -> F String (InputMsg String) -> F c d
textFileShellF' :: (ShellF -> ShellF) -> String -> F String (InputMsg String) -> F c d
titleShellF :: String -> F c d -> F (String  c) d
titleShellF' :: (ShellF -> ShellF) -> String -> F c d -> F (String  c) d
wmShellF :: String -> F c d -> F ((String  Bool)  c) (()  d)
wmShellF' :: (ShellF -> ShellF) -> String -> F c d -> F ((String  Bool)  c) (()  d)
Miscellaneous (the rest):
data Item a = ...
type Menu a = [MenuItem' a]
type MenuBar a = Menu a
data MenuItem a = ...
type MenuItem' a = Item (MenuItem a)
data RBBT = ...
data ReactionM s o a = ...
data SmileyMode = ...
class Tag f where ...
data TagF i o h t = ...
data Tags f1 f2 a = ...
data Transl l g = ...
data Tree leaf node = ...
>&< :: (Tag f2, Tag f1) =>
                 TagF i o1 h f1 -> TagF b o2 h f2 -> TagF (i  b) (o1  o2) h (Tags f1 f2)
bitmapButtonF :: [(ModState, KeySym)] -> String -> F BitmapReturn Click
bitmapDispBorderF :: Int -> FilePath -> F BitmapReturn a
bitmapDispF :: FilePath -> F BitmapReturn a
cmdItem :: Graphic a1 => a2 -> a1 -> Item (MenuItem a2)
compT :: Transl l g -> Transl c l -> Transl c g
compTagF :: (Tag f2, Tag f1) =>
            (F i o1 -> F b o2 -> F (i  b) (o1  o2)) ->
            TagF i o1 h f1 -> TagF b o2 h f2 -> TagF (i  b) (o1  o2) h (Tags f1 f2)
completeFromList :: Eq a => [[a]] -> [a] -> [([a], [a])]
completionStringF :: F ((String -> [(a, String)])  String) ([(a, String)]  (InputMsg String))
completionStringF' :: Char ->
                      Customiser StringF ->
                      F ((String -> [(a, String)])  String) ([(a, String)]  (InputMsg String))
completionStringF'' :: Char ->
                       Customiser StringF ->
                       F ((String -> [(a, String)])  ((Customiser StringF)  String))
                         ([(a, String)]  (InputMsg String))
delayedSubMenuItem :: (Graphic a1, Eq b) =>
                      Transl b a2 -> Menu b -> a1 -> Item (MenuItem a2)
dynRadioGroupItem :: (Graphic a1, Eq b) =>
                     Transl ([Item b], b) a2 ->
                     [Item b] -> b -> a1 -> Item (MenuItem a2)
endButtonsF :: F (Click  Click) (Click  Click)
endButtonsF' :: F String (Click  Click)
field :: (a -> b) -> ReactionM a o b
filePickF :: F (String, Maybe FilePath) (Maybe FilePath)
filePickF' :: Graphic lbl =>
              [(AFilePath -> AFilePath, KeySym, lbl)] ->
              F (String, Maybe FilePath) (Maybe FilePath)
filePickPopupF :: F (a, (String, Maybe FilePath)) ((a, (String, Maybe FilePath)), FilePath)
filePickPopupF' :: Graphic lbl =>
                   [(AFilePath -> AFilePath, KeySym, lbl)] ->
                   F (a, (String, Maybe FilePath)) ((a, (String, Maybe FilePath)), FilePath)
filePickPopupOptF :: F (a, (String, Maybe FilePath)) ((a, (String, Maybe FilePath)), Maybe FilePath)
filePickPopupOptF' :: Graphic lbl =>
                      [(AFilePath -> AFilePath, KeySym, lbl)] ->
                      F (a, (String, Maybe FilePath))
                        ((a, (String, Maybe FilePath)), Maybe FilePath)
get :: ReactionM a o a
gfxEventPaths :: GfxEvent path -> Maybe [(path, (Point, Rect))]
helpBubbleF :: Graphic g => g -> F c d -> F c d
hyperGraphicsF2 :: (Graphic leaf, Ord k) =>
                   Drawing k leaf -> F (GfxCommand k (Drawing k leaf)) (GfxEvent k)
hyperGraphicsF2' :: (Graphic leaf, Ord k) =>
                    (GraphicsF (Drawing k leaf) -> GraphicsF (Drawing k leaf)) ->
                    Drawing k leaf -> F (GfxCommand k (Drawing k leaf)) (GfxEvent k)
idT :: Transl b b
item :: Graphic a1 => a2 -> a1 -> Item a2
item' :: Graphic a1 => Keys -> a2 -> a1 -> Item a2
itemValue :: Item a -> a
key :: Item a -> String -> Item a
left :: (a1 -> Maybe a2) -> a1  p -> Maybe a2
leftleft :: (a1 -> Maybe a2) -> (a1  p1)  p2 -> Maybe a2
leftyes :: a  p -> Maybe a
lift :: Maybe a -> ReactionM s o a
ltr :: Tag f2 =>
       (b1 -> c) -> TagF a o c f2 -> (F a o, o  b1 -> c, Tags ((->) b2) f2 (a  b2))
mapSocketMsg :: (t -> a) -> SocketMsg t -> SocketMsg a
mapTF :: (F i o -> F i o) -> TagF i o h t -> TagF i o h t
menu :: Eq b => Transl b a -> Menu b -> MenuItem a
menuBarF :: Eq a => Menu a -> F a a
menuIcon :: FixedDrawing
meterBg :: ColorSpec
meterD :: RealFrac a1 => a1 -> FlexibleDrawing
meterF :: RealFrac v => InF v (Ratio Int)
meterF' :: RealFrac a1 =>
           (GraphicsF FlexibleDrawing -> GraphicsF FlexibleDrawing) ->
           F a1 (InputMsg (Ratio Int))
meterFg :: ColorSpec
mouseClicksSP :: SP (GfxEvent b) b
no :: p -> Maybe a
nop :: Monad m => m ()
nullPath :: GfxEvent path -> Bool
popup :: (String, Maybe a)
put :: a1 -> ReactionM a2 a1 ()
radioF1 :: Eq a => RadioButtonBorderType -> FontName -> [(a, String)] -> a -> F a a
radioGroupF1 :: Eq a =>
                RadioButtonBorderType ->
                FontName -> [a] -> a -> (a -> String) -> F a a
radioGroupItem :: (Graphic a1, Eq b) =>
                  Transl b a2 -> [Item b] -> b -> a1 -> Item (MenuItem a2)
react :: ReactionM a1 o a2 -> a1 -> (a1, [o])
reactiveF :: (a -> ReactionM t b a2) -> t -> F a b
reactiveSP :: (a -> ReactionM t b a2) -> t -> SP a b
rfail :: ReactionM s o a
right :: (b -> Maybe a) -> p  b -> Maybe a
sepItem :: Item (MenuItem a)
set :: s -> ReactionM s o ()
smileyD :: SmileyMode -> FixedDrawing
smileyF :: F SmileyMode void
smileyF' :: Customiser (DisplayF SmileyMode) -> F SmileyMode void
startDir :: FilePath
stdcc :: Char
subMenuItem :: (Graphic a1, Eq b) => Transl b a2 -> Menu b -> a1 -> Item (MenuItem a2)
tServerAddress :: Host -> TPort c s -> TServerAddress c s
tagF :: (o -> h) -> F i o -> TagF i o h ((->) i)
toggleButtonF1 :: RadioButtonBorderType ->
                  String -> [(ModState, KeySym)] -> String -> F Bool Bool
toggleF1 :: RBBT -> [(ModState, KeySym)] -> F a b -> F (Bool  a) (Bool  b)
toggleItem :: Graphic a1 => Transl Bool a2 -> Bool -> a1 -> Item (MenuItem a2)
treeBrowserF' :: (Graphic node, Graphic leaf) =>
                 Tree leaf node -> F (Tree leaf node) (Tree leaf node)
treeDisplayF' :: (Graphic node, Graphic leaf) =>
                 Tree leaf node -> F (Tree leaf node) (Tree leaf node)
update :: (t -> t) -> ReactionM t o ()
yes :: a -> Maybe a