Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Programmers' index. There is very little documentation here. See the Fudget Library Reference Manual instead.
Synopsis
- buttonF :: Graphic lbl => lbl -> F Click Click
- border3dF :: Bool -> Int -> F a b -> F (Either Bool a) b
- buttonBorderF :: Int -> F a b -> F (Either Bool a) b
- pushButtonF :: [(ModState, KeySym)] -> F a b -> F a (Either b Click)
- data BMevents
- popupMenuF :: (Eq b1, Graphic b1) => [(a, b1)] -> F c b2 -> F (Either [(a, b1)] c) (Either a b2)
- data Click = Click
- radioGroupF :: (Graphic lbl, Eq alt) => [(alt, lbl)] -> alt -> F alt alt
- radioGroupF' :: (Graphic lbl, Eq alt) => Customiser RadioGroupF -> [(alt, lbl)] -> alt -> F alt alt
- intF :: F Int (InputMsg Int)
- passwdF :: F String (InputMsg String)
- stringF :: F String (InputMsg String)
- intInputF :: F Int Int
- stringInputF :: F String String
- passwdInputF :: F String String
- intInputF' :: Customiser StringF -> F Int Int
- stringInputF' :: Customiser StringF -> F String String
- passwdInputF' :: (StringF -> StringF) -> F String String
- toggleButtonF :: Graphic lbl => lbl -> F Bool Bool
- inputPopupOptF :: String -> InF a b -> Maybe b -> F (Maybe String, Maybe a) ((Maybe String, Maybe a), Maybe b)
- inputPopupF :: String -> InF a c -> Maybe c -> F (Maybe String, Maybe a) ((Maybe String, Maybe a), c)
- passwdPopupOptF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), Maybe String)
- passwdPopupF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), String)
- stringPopupOptF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), Maybe String)
- stringPopupF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), String)
- confirmPopupF :: Graphic msg => F msg (msg, ConfirmMsg)
- data ConfirmMsg
- oldConfirmPopupF :: F String (String, ConfirmMsg)
- oldMessagePopupF :: F String (String, Click)
- messagePopupF :: Graphic msg => F msg (msg, Click)
- intDispF :: F Int b
- displayF :: Graphic g => F g void
- labelF :: Graphic a1 => a1 -> F a2 b
- data EditStop
- editF :: FontSpec -> F EditCmd EditEvt
- data EditEvt
- data EditCmd
- editorF :: F EditCmd EditEvt
- editorF' :: Customiser EditorF -> F EditCmd EditEvt
- selectall :: [EditCmd]
- loadEditor :: String -> [EditCmd]
- newline :: Char
- data EDirection
- inputEditorF :: F String (InputMsg String)
- inputEditorF' :: Customiser EditorF -> F String (InputMsg String)
- data EditorF
- type EditStopFn = String -> String -> EditStopChoice
- data EditStopChoice
- type IsSelect = Bool
- setEditorCursorPos :: (Int, Int) -> [EditCmd]
- oldFilePickF :: F FilePath (InputMsg String)
- type PickListRequest a = ListRequest a
- textF :: F TextRequest (InputMsg (Int, String))
- textF' :: Customiser TextF -> F TextRequest (InputMsg (Int, String))
- type TextRequest = ListRequest String
- data TextF
- class HasInitText xxx where
- setInitText :: [String] -> Customiser xxx
- getInitText :: xxx -> [String]
- getInitTextMaybe :: xxx -> Maybe [String]
- class HasSizing xxx where
- setSizing :: Sizing -> Customiser xxx
- getSizing :: xxx -> Sizing
- getSizingMaybe :: xxx -> Maybe Sizing
- data Sizing
- data ListRequest a
- = ReplaceItems Int Int [a]
- | HighlightItems [Int]
- | PickItem Int
- replaceAll :: [a] -> ListRequest a
- replaceAllFrom :: Int -> [a] -> ListRequest a
- deleteItems :: Int -> Int -> ListRequest a
- insertItems :: Int -> [a] -> ListRequest a
- appendItems :: [a] -> ListRequest a
- changeItems :: Int -> [a] -> ListRequest a
- replaceItems :: Int -> Int -> [a] -> ListRequest a
- highlightItems :: [Int] -> ListRequest a
- pickItem :: Int -> ListRequest a
- applyListRequest :: ListRequest a -> [a] -> [a]
- smallPickListF :: (d -> String) -> F [d] d
- labRightOfF :: Graphic p => p -> F c d -> F c d
- labLeftOfF :: Graphic p => p -> F c d -> F c d
- labBelowF :: Graphic p => p -> F c d -> F c d
- labAboveF :: Graphic p => p -> F c d -> F c d
- tieLabelF :: Graphic p => Orientation -> Alignment -> p -> F c d -> F c d
- menuF :: (Graphic mlbl, Graphic albl) => mlbl -> [(alt, albl)] -> F alt alt
- data PopupMenu
- menuPopupF :: F b d -> F (Either PopupMenu b) d
- pickListF :: (a -> String) -> F (PickListRequest a) (InputMsg (Int, a))
- moreShellF :: String -> F [String] (InputMsg (Int, String))
- pickListF' :: Customiser TextF -> (a -> String) -> F (PickListRequest a) (InputMsg (Int, a))
- moreShellF' :: Customiser TextF -> String -> F [String] (InputMsg (Int, String))
- moreFileShellF :: F String (InputMsg (Int, String))
- moreFileF :: F String (InputMsg (Int, String))
- moreF :: F [String] (InputMsg (Int, String))
- moreF' :: Customiser TextF -> F [String] (InputMsg (Int, String))
- terminalF :: FontName -> Int -> Int -> F String a
- cmdTerminalF :: FontName -> Int -> Int -> F TerminalCmd a
- data TerminalCmd
- hyperGraphicsF :: (Eq d, Graphic leaf) => Drawing d leaf -> F (Either (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 (Either (Drawing d leaf) (d, Drawing d leaf)) d
- data GraphicsF gfx
- setAdjustSize :: Bool -> Customiser (GraphicsF gfx)
- contDynF :: F a b -> Cont (F a d) b
- type Fudget a b = F a b
- data F hi ho
- listF :: Eq a => [(a, F b c)] -> F (a, b) (a, c)
- untaggedListF :: [F a b] -> F a b
- loopCompF :: F (Either (Either r2l inl) (Either l2r inr)) (Either (Either l2r outl) (Either r2l outr)) -> F (Either inl inr) (Either outl outr)
- loopCompSP :: SP (Either (Either a1 b1) (Either a2 b2)) (Either (Either a2 a3) (Either a1 b3)) -> SP (Either b1 b2) (Either a3 b3)
- loopF :: F a a -> F a a
- loopLeftF :: F (Either a b) (Either a c) -> F b c
- loopRightF :: F (Either a b) (Either c b) -> F a c
- loopOnlyF :: F a a -> F a b
- loopThroughRightF :: F (Either a b) (Either c d) -> F c a -> F b d
- 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
- loopThroughBothF :: F (Either r2l inl) (Either l2r outl) -> F (Either l2r inr) (Either r2l outr) -> F (Either inl inr) (Either outl outr)
- delayF :: F hi ho -> F hi ho
- getF :: Cont (F a ho) a
- putF :: ho -> F hi ho -> F hi ho
- putsF :: [b] -> F a b -> F a b
- startupF :: [hi] -> F hi ho -> F hi ho
- appendStartF :: [ho] -> F hi ho -> F hi ho
- nullF :: F hi ho
- parF :: F c ho -> F c ho -> F c ho
- prodF :: F a b -> F c d -> F (a, c) (Either b d)
- absF :: SP a b -> F a b
- bypassF :: F a a -> F a a
- concatMapF :: (a -> [b]) -> F a b
- idF :: F b b
- idLeftF :: F c d -> F (Either b c) (Either b d)
- idRightF :: F a b -> F (Either a c) (Either b c)
- mapF :: (a -> b) -> F a b
- mapstateF :: (t -> a -> (t, [b])) -> t -> F a b
- serCompLeftToRightF :: F (Either a b) (Either b c) -> F a c
- serCompRightToLeftF :: F (Either a b) (Either c a) -> F b c
- stubF :: F a b -> F c d
- throughF :: F c b -> F c (Either b c)
- toBothF :: F b (Either b b)
- (>*<) :: F c ho -> F c ho -> F c ho
- (>+<) :: F a b -> F c d -> F (Either a c) (Either b d)
- (>=^<) :: F c d -> (e -> c) -> F e d
- (>=^^<) :: F c d -> SP e c -> F e d
- (>#+<) :: (F a b, Orientation) -> F c d -> F (Either a c) (Either b d)
- (>#==<) :: (F d f, Orientation) -> F e d -> F e f
- (>==<) :: F a1 b -> F a2 a1 -> F a2 b
- (>^=<) :: (a -> b) -> F e a -> F e b
- (>^^=<) :: SP a b -> F e a -> F e b
- prepostMapHigh :: (hi -> b) -> (c -> ho) -> F b c -> F hi ho
- quitIdF :: (ho -> Bool) -> F ho ho
- quitF :: F ans ho
- 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)
- data DynMsg a b
- = DynCreate b
- | DynDestroy
- | DynMsg a
- class FudgetIO f where
- type InF a b = F a (InputMsg b)
- data InputMsg a
- = InputChange a
- | InputDone KeySym a
- inputDoneSP :: SP (InputMsg b) b
- inputLeaveDoneSP :: SP (InputMsg b) b
- inputListSP :: Eq p1 => [p1] -> SP (p1, InputMsg p2) (InputMsg [(p1, p2)])
- inputPairSP :: SP (Either (InputMsg a) (InputMsg b)) (InputMsg (a, b))
- inputThroughF :: InF a a -> InF a a
- inputPairF :: InF a1 b1 -> InF a2 b2 -> InF (a1, a2) (b1, b2)
- inputListF :: Eq a => [(a, InF b c)] -> InF [(a, b)] [(a, c)]
- inputChange :: a -> InputMsg 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))
- stripInputSP :: SP (InputMsg b) b
- inputButtonKey :: KeySym
- inputLeaveKey :: KeySym
- inputMsg :: a -> InputMsg a
- mapInp :: (t -> a) -> InputMsg t -> InputMsg a
- stripInputMsg :: InputMsg a -> a
- inputDone :: InputMsg a -> Maybe a
- inputLeaveDone :: InputMsg a -> Maybe a
- tstInp :: (t1 -> t2) -> InputMsg t1 -> t2
- data Orientation
- alignF :: Size -> Size -> Alignment -> Alignment -> F a b -> F a b
- marginHVAlignF :: Distance -> Alignment -> Alignment -> F a b -> F a b
- layoutModifierF :: (LayoutRequest -> LayoutRequest) -> F a b -> F a b
- noStretchF :: Bool -> Bool -> F a b -> F a b
- marginF :: Distance -> F a b -> F a b
- sepF :: Size -> F a b -> F a b
- autoP :: Placer
- flipP :: Placer -> Placer
- permuteP :: [Int] -> Placer -> Placer
- revP :: Placer -> Placer
- idP :: Placer
- type Alignment = Double
- aBottom :: Alignment
- aCenter :: Alignment
- aLeft :: Alignment
- aRight :: Alignment
- aTop :: Alignment
- dynListLF :: Placer -> F (Int, DynFMsg a b) (Int, b)
- data LayoutDir
- listLF :: Eq a => Placer -> [(a, F b c)] -> F (a, b) (a, c)
- nullLF :: F hi ho
- holeF :: F hi ho
- untaggedListLF :: Placer -> [F a b] -> F (Int, a) b
- data LayoutRequest
- data Placer
- center :: Point -> Rect -> Rect
- center' :: Point -> Size -> Rect -> Rect
- fixedh :: LayoutRequest -> Bool
- fixedv :: LayoutRequest -> Bool
- flipPoint :: Point -> Point
- flipRect :: Rect -> Rect
- flipReq :: LayoutRequest -> LayoutRequest
- data NameLayout
- type LName = String
- hvAlignNL :: Alignment -> Alignment -> NameLayout -> NameLayout
- marginHVAlignNL :: Distance -> Alignment -> Alignment -> NameLayout -> NameLayout
- hBoxNL :: [NameLayout] -> NameLayout
- hBoxNL' :: Distance -> [NameLayout] -> NameLayout
- nullNL :: NameLayout
- leafNL :: LName -> NameLayout
- spaceNL :: Spacer -> NameLayout -> NameLayout
- placeNL :: Placer -> [NameLayout] -> NameLayout
- listNF :: (Eq a, Show a) => [(a, F b c)] -> F (a, b) (a, c)
- modNL :: (Placer -> Placer) -> NameLayout -> NameLayout
- nameF :: LName -> F a b -> F a b
- nameLayoutF :: NameLayout -> F a b -> F a b
- sepNL :: Size -> NameLayout -> NameLayout
- marginNL :: Distance -> NameLayout -> NameLayout
- vBoxNL :: [NameLayout] -> NameLayout
- vBoxNL' :: Distance -> [NameLayout] -> NameLayout
- hBoxF :: F a b -> F a b
- matrixF :: Int -> F a b -> F a b
- placerF :: Placer -> F a b -> F a b
- spacerF :: Spacer -> F a b -> F a b
- spacer1F :: Spacer -> F a b -> F a b
- revHBoxF :: F a b -> F a b
- revVBoxF :: F a b -> F a b
- spacerP :: Spacer -> Placer -> Placer
- tableF :: Int -> F a b -> F a b
- vBoxF :: F a b -> F a b
- horizontalP :: Placer
- horizontalP' :: Distance -> Placer
- matrixP :: Int -> Placer
- matrixP' :: Int -> LayoutDir -> Distance -> Placer
- verticalP :: Placer
- verticalP' :: Distance -> Placer
- paragraphP :: Placer
- paragraphP' :: Size -> Placer
- paragraphP'' :: (Int -> Placer) -> Size -> Placer
- dynPlacerF :: F c ho -> F (Either Placer c) ho
- dynSpacerF :: F c ho -> F (Either Spacer c) ho
- type Distance = Int
- data Spacer
- bottomS :: Spacer
- centerS :: Spacer
- compS :: Spacer -> Spacer -> Spacer
- flipS :: Spacer -> Spacer
- hAlignS :: Alignment -> Spacer
- sizeS :: Size -> Spacer
- maxSizeS :: Size -> Spacer
- minSizeS :: Size -> Spacer
- hCenterS :: Spacer
- hMarginS :: Distance -> Distance -> Spacer
- marginHVAlignS :: Distance -> Alignment -> Alignment -> Spacer
- hvAlignS :: Alignment -> Alignment -> Spacer
- hvMarginS :: Size -> Size -> Spacer
- idS :: Spacer
- leftS :: Spacer
- marginS :: Distance -> Spacer
- sepS :: Size -> Spacer
- noStretchS :: Bool -> Bool -> Spacer
- rightS :: Spacer
- topS :: Spacer
- vAlignS :: Alignment -> Spacer
- vCenterS :: Spacer
- vMarginS :: Distance -> Distance -> Spacer
- tableP :: Int -> Placer
- tableP' :: Int -> LayoutDir -> Distance -> Placer
- bubbleF :: F a b -> F a b
- bubblePopupF :: F b2 d2 -> F (PopupMsg b2) d2
- bubbleRootPopupF :: F b2 d2 -> F (PopupMsg b2) d2
- shellF :: String -> F c d -> F c d
- data PotRequest
- type PotState = (Int, Int, Int)
- containerGroupF :: Rect -> Rect -> Int -> Button -> ModState -> F c b -> F (Either (Rect, Rect) c) (Either Rect b)
- hPotF :: F PotRequest PotState
- vPotF :: F PotRequest PotState
- popupShellF :: String -> Maybe Point -> F a b -> F a (a, b)
- popupShellF' :: Customiser ShellF -> String -> Maybe Point -> F a b -> F a (a, b)
- data PopupMsg a
- posPopupShellF :: String -> [WindowAttributes] -> F c a -> F (c, Maybe Point) (c, a)
- hScrollF :: F b d -> F b d
- scrollF :: F b d -> F b d
- scrollShellF :: String -> (Point, Point) -> F c d -> F c d
- vScrollF :: F b d -> F b d
- data ESelCmd a
- data ESelEvt a
- data SelCmd a
- data SelEvt a
- eselectionF :: F (ESelCmd String) (ESelEvt String)
- selectionF :: F (SelCmd String) (SelEvt String)
- allcacheF :: F i o -> F i o
- doubleClickF :: Time -> F a b -> F a b
- type Time = Int
- (-+-) :: SP a1 a2 -> SP a3 b -> SP (Either a1 a3) (Either a2 b)
- (-*-) :: SP a b -> SP a b -> SP a b
- (-==-) :: SP a1 b -> SP a2 a1 -> SP a2 b
- compEitherSP :: SP a1 a2 -> SP a3 b -> SP (Either a1 a3) (Either a2 b)
- idLeftSP :: SP a1 b -> SP (Either a2 a1) (Either a2 b)
- idRightSP :: SP a1 a2 -> SP (Either a1 b) (Either 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
- loopLeftSP :: SP (Either a b1) (Either a b2) -> SP b1 b2
- loopSP :: SP a a -> SP a a
- loopOnlySP :: SP a a -> SP a b
- loopThroughRightSP :: SP (Either a1 b1) (Either a2 b2) -> SP a2 a1 -> SP b1 b2
- loopThroughBothSP :: SP (Either a1 b1) (Either a2 a3) -> SP (Either a2 b2) (Either a1 b3) -> SP (Either b1 b2) (Either a3 b3)
- parSP :: SP a b -> SP a b -> SP a b
- seqSP :: SP a b -> SP a b -> SP a b
- data SP a b
- nullSP :: SP a b
- putSP :: b -> SP a b -> SP a b
- putsSP :: [b] -> SP a b -> SP a b
- getSP :: Cont (SP a b) a
- class StreamProcIO sp where
- runSP :: SP a1 a2 -> [a1] -> [a2]
- walkSP :: SP a1 a2 -> a1 -> ([a2], SP a1 a2)
- pullSP :: SP a1 a2 -> ([a2], SP a1 a2)
- idSP :: SP b b
- filterSP :: (b -> Bool) -> SP b b
- filterJustSP :: SP (Maybe b) b
- filterLeftSP :: SP (Either b1 b2) b1
- filterRightSP :: SP (Either a1 b) b
- mapFilterSP :: (t -> Maybe b) -> SP t b
- splitSP :: SP (a, b) (Either a b)
- toBothSP :: SP b (Either b b)
- concatSP :: SP [b] b
- concSP :: SP [b] b
- mapSP :: (t -> b) -> SP t b
- concatMapSP :: (t -> [b]) -> SP t b
- concmapSP :: (t -> [b]) -> SP t b
- concatMapAccumlSP :: (t -> a -> (t, [b])) -> t -> SP a b
- mapstateSP :: (t -> a -> (t, [b])) -> t -> SP a b
- mapAccumlSP :: (t -> a -> (t, b)) -> t -> SP a b
- zipSP :: [a] -> SP b (a, b)
- type Cont c a = (a -> c) -> c
- appendStartSP :: [b] -> SP a b -> SP a b
- chopSP :: ((b -> SP a b) -> SP a b) -> SP a b
- delaySP :: SP a b -> SP a b
- feedSP :: a -> [a] -> SP a b -> SP a b
- splitAtElemSP :: (a -> Bool) -> Cont (SP a b) [a]
- startupSP :: [a] -> SP a b -> SP a b
- stepSP :: [b] -> Cont (SP a b) a
- cmdContSP :: a -> (b -> Maybe c) -> Cont (SP b a) c
- conts :: (a -> Cont c b) -> [a] -> Cont c [b]
- getLeftSP :: (t -> SP (Either t b1) b2) -> SP (Either t b1) b2
- getRightSP :: (t -> SP (Either a1 t) b) -> SP (Either a1 t) b
- waitForSP :: (a -> Maybe t) -> (t -> SP a b) -> SP a b
- waitForF :: (a -> Maybe b) -> Cont (F a c) b
- dropSP :: (t1 -> Maybe t2) -> (t2 -> SP t1 b) -> SP t1 b
- contMap :: StreamProcIO sp => (i -> (o -> sp i o) -> sp i o) -> sp i o
- hIOF :: Request -> (Response -> F a b) -> F a b
- hIOSuccF :: Request -> F a b -> F a b
- hIOerrF :: Request -> (IOError -> F a b) -> (Response -> F a b) -> F a b
- haskellIOF :: Request -> (Response -> F a b) -> F a b
- inputLinesSP :: SP [Char] [Char]
- linesSP :: SP Char [Char]
- outputF :: String -> F String a
- stderrF :: F String a
- stdinF :: F hi String
- stdioF :: F String String
- stdoutF :: F String a
- subProcessF :: String -> F [Char] (Either String String)
- appStorageF :: (Read a, Show a) => String -> a -> F a a
- readDirF :: F String (String, Either IOError [String])
- readFileF :: F String (String, Either IOError String)
- writeFileF :: F (String, String) (String, Either IOError ())
- type Host = String
- newtype LSocket = LSo Int
- type Peer = Host
- type Port = Int
- newtype Socket = So Int
- openLSocketF :: FudgetIO f => Port -> (LSocket -> f hi ho) -> f hi ho
- openSocketF :: FudgetIO f => Host -> Port -> (Socket -> f hi ho) -> f hi ho
- receiverF :: Socket -> F e String
- transceiverF :: Socket -> F [Char] String
- transmitterF :: Socket -> F [Char] b
- asyncTransmitterF :: Socket -> F String b
- asyncTransceiverF :: Socket -> F String String
- data Tick = Tick
- timerF :: F (Maybe (Int, Int)) Tick
- fudlogue :: F a b -> IO ()
- fudlogue' :: Customiser Fudlogue -> F a b -> IO ()
- data Fudlogue
- argFlag :: [Char] -> Bool -> Bool
- argKey :: [Char] -> [Char] -> [Char]
- argReadKey :: (Read p, Show p) => [Char] -> p -> p
- argKeyList :: [Char] -> [[Char]] -> [[Char]]
- args :: [[Char]]
- progName :: String
- bgColor :: ColorName
- buttonFont :: FontName
- defaultFont :: FontName
- defaultSize :: Maybe Point
- defaultPosition :: Maybe Point
- defaultSep :: Num a => a
- edgeWidth :: Int
- fgColor :: ColorName
- labelFont :: FontName
- look3d :: Bool
- menuFont :: FontName
- options :: [([Char], [Char])]
- paperColor :: ColorName
- shadowColor :: ColorName
- shineColor :: ColorName
- filterLeft :: [Either b1 b2] -> [b1]
- filterRight :: [Either a b] -> [b]
- isLeft :: Either a b -> Bool
- isRight :: Either a b -> Bool
- mapEither :: (t1 -> a) -> (t2 -> b) -> Either t1 t2 -> Either a b
- fromLeft :: Either a b -> a
- fromRight :: Either a b -> b
- plookup :: Foldable t => (b1 -> Bool) -> t (b1, b2) -> Maybe b2
- splitEitherList :: [Either a1 a2] -> ([a1], [a2])
- stripEither :: Either a a -> a
- stripLeft :: Either a b -> Maybe a
- stripRight :: Either a1 a2 -> Maybe a2
- swapEither :: Either b a -> Either a b
- (=.>) :: Point -> Point -> Bool
- data Line = Line Point Point
- data Point = Point {}
- data Rect = Rect {}
- type Size = Point
- class Move a where
- confine :: Rect -> Rect -> Rect
- diag :: Int -> Point
- freedom :: Rect -> Rect -> Point
- growrect :: Rect -> Point -> Rect
- inRect :: Point -> Rect -> Bool
- lL :: Int -> Int -> Int -> Int -> Line
- line2rect :: Line -> Rect
- moveline :: Line -> Point -> Line
- moverect :: Rect -> Point -> Rect
- origin :: Point
- pMax :: [Point] -> Point
- pMin :: [Point] -> Point
- pP :: Int -> Int -> 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
- rR :: Int -> Int -> Int -> Int -> Rect
- 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
- 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)]
- swap :: (b, a) -> (a, b)
- unionmap :: (Foldable t1, Eq a) => (t2 -> [a]) -> t1 t2 -> [a]
- version :: String
- version_0_18_4 :: String
- data XCommand
- data XEvent
- type Path = [Direction]
- data Button
- type ColorName = String
- type FontName = String
- type KeySym = String
- type FontStruct = FontStructF (Array Char CharStruct)
- data RGB = RGB Int Int Int
- data WindowAttributes
- type ModState = [Modifiers]
- data Modifiers
- data CoordMode
- data Shape
- data DrawCommand
- = DrawLine Line
- | DrawImageString Point String
- | DrawString Point String
- | DrawRectangle Rect
- | FillRectangle Rect
- | FillPolygon Shape CoordMode [Point]
- | DrawArc Rect Int Int
- | FillArc Rect Int Int
- | CopyArea Drawable Rect Point
- | CopyPlane Drawable Rect Point Int
- | DrawPoint Point
- | CreatePutImage Rect ImageFormat [Pixel]
- | DrawLines CoordMode [Point]
- | DrawImageString16 Point String
- | DrawString16 Point String
- fillCircle :: Point -> Int -> DrawCommand
- drawCircle :: Point -> Int -> DrawCommand
- class Graphic a where
- measureGraphicK :: FudgetIO k => a -> GCtx -> Cont (k i o) MeasuredGraphics
- measureGraphicListK :: FudgetIO k => [a] -> GCtx -> Cont (k i o) MeasuredGraphics
- data Drawing lbl leaf
- atomicD :: leaf -> Drawing lbl leaf
- labelD :: lbl -> Drawing lbl leaf -> Drawing lbl leaf
- up :: DPath -> DPath
- boxD :: [Drawing lbl leaf] -> Drawing lbl leaf
- hboxD :: [Drawing lbl leaf] -> Drawing lbl leaf
- hboxD' :: Distance -> [Drawing lbl leaf] -> Drawing lbl leaf
- vboxD :: [Drawing lbl leaf] -> Drawing lbl leaf
- vboxD' :: Distance -> [Drawing lbl leaf] -> Drawing lbl leaf
- tableD :: Int -> [Drawing lbl leaf] -> Drawing lbl leaf
- tableD' :: Distance -> Int -> [Drawing lbl leaf] -> Drawing lbl leaf
- hboxcD :: [Drawing lbl leaf] -> Drawing lbl leaf
- hboxcD' :: Distance -> [Drawing lbl leaf] -> Drawing lbl leaf
- vboxlD :: [Drawing lbl leaf] -> Drawing lbl leaf
- vboxlD' :: Distance -> [Drawing lbl leaf] -> Drawing lbl leaf
- matrixD :: Int -> [Drawing lbl leaf] -> Drawing lbl leaf
- matrixD' :: Distance -> Int -> [Drawing lbl leaf] -> Drawing lbl leaf
- attribD :: GCSpec -> Drawing lbl leaf -> Drawing lbl leaf
- softAttribD :: [GCAttributes ColorSpec FontSpec] -> Drawing lbl leaf -> Drawing lbl leaf
- hardAttribD :: GCtx -> Drawing lbl leaf -> Drawing lbl leaf
- fontD :: (Show a, FontGen a) => a -> Drawing lbl leaf -> Drawing lbl leaf
- fgD :: (Show a, ColorGen a) => a -> Drawing lbl leaf -> Drawing lbl leaf
- stackD :: [Drawing lbl leaf] -> Drawing lbl leaf
- spacedD :: Spacer -> Drawing lbl leaf -> Drawing lbl leaf
- placedD :: Placer -> Drawing lbl leaf -> Drawing lbl leaf
- blankD :: Size -> Drawing lbl Gfx
- filledRectD :: Size -> Drawing lbl Gfx
- rectD :: Size -> Drawing lbl Gfx
- type DPath = [Int]
- data Gfx
- g :: Graphic a => a -> Drawing lbl Gfx
- data FixedDrawing = FixD Size [DrawCommand]
- data FixedColorDrawing = FixCD Size [(GCId, [DrawCommand])]
- gctx2gc :: GCtx -> GCId
- data FlexibleDrawing = FlexD Size Bool Bool (Rect -> [DrawCommand])
- flex :: (Rect -> [DrawCommand]) -> FlexibleDrawing
- flex' :: Size -> (Rect -> [DrawCommand]) -> FlexibleDrawing
- filler :: Bool -> Bool -> Int -> FlexibleDrawing
- hFiller :: Int -> FlexibleDrawing
- vFiller :: Int -> FlexibleDrawing
- frame :: FlexibleDrawing
- frame' :: Size -> FlexibleDrawing
- ellipse :: FlexibleDrawing
- ellipse' :: Size -> FlexibleDrawing
- arc :: Int -> Int -> FlexibleDrawing
- arc' :: Size -> Int -> Int -> FlexibleDrawing
- filledEllipse :: FlexibleDrawing
- filledEllipse' :: Size -> FlexibleDrawing
- filledarc :: Int -> Int -> FlexibleDrawing
- filledarc' :: Size -> Int -> Int -> FlexibleDrawing
- lpar :: FlexibleDrawing
- rpar :: FlexibleDrawing
- lbrack :: FlexibleDrawing
- rbrack :: FlexibleDrawing
- lbrace :: FlexibleDrawing
- rbrace :: FlexibleDrawing
- triangleUp :: FlexibleDrawing
- triangleDown :: FlexibleDrawing
- filledTriangleUp :: FlexibleDrawing
- filledTriangleDown :: FlexibleDrawing
- data BitmapFile = BitmapFile String
- class ColorGen a where
- tryConvColorK :: FudgetIO f => a -> Cont (f i o) (Maybe Pixel)
- convColorListK :: FudgetIO f => [a] -> Cont (f i o) (Maybe Pixel)
- class FontGen a where
- tryConvFontK :: FudgetIO f => a -> Cont (f i o) (Maybe FontData)
- convFontListK :: FudgetIO f => [a] -> Cont (f i o) (Maybe FontData)
- data FontSpec
- data ColorSpec
- colorSpec :: (Show a, ColorGen a) => a -> ColorSpec
- fontSpec :: (Show a, FontGen a) => a -> FontSpec
- data GCtx
- rootGCtx :: GCtx
- wCreateGCtx :: (ColorGen a1, FudgetIO f, FontGen a2, Show a1, Show a2) => GCtx -> [GCAttributes a1 a2] -> (GCtx -> f i o) -> f i o
- createGCtx :: (ColorGen a1, FudgetIO f, FontGen a2, Show a1, Show a2) => Drawable -> GCtx -> [GCAttributes a1 a2] -> (GCtx -> f i o) -> f i o
- gcFgA :: c -> [GCAttributes c FontSpec]
- gcBgA :: c -> [GCAttributes c FontSpec]
- gcFontA :: f -> [GCAttributes ColorSpec f]
- data GCAttributes a b
- data GCFillStyle
- data GCCapStyle
- data GCLineStyle
- data GCFunction
- = GXclear
- | GXand
- | GXandReverse
- | GXcopy
- | GXandInverted
- | GXnoop
- | GXxor
- | GXor
- | GXnor
- | GXequiv
- | GXinvert
- | GXorReverse
- | GXCopyInverted
- | GXorInverted
- | GXnand
- | GXset
- type Width = Int
- type Customiser a = a -> a
- type PF p a b = F (Either (Customiser p) a) b
- standard :: Customiser a
- class HasClickToType xxx where
- setClickToType :: Bool -> Customiser xxx
- getClickToType :: xxx -> Bool
- getClickToTypeMaybe :: xxx -> Maybe Bool
- class HasVisible xxx where
- setVisible :: Bool -> Customiser xxx
- getVisible :: xxx -> Bool
- getVisibleMaybe :: xxx -> Maybe Bool
- class HasFontSpec xxx where
- setFontSpec :: FontSpec -> Customiser xxx
- getFontSpec :: xxx -> FontSpec
- getFontSpecMaybe :: xxx -> Maybe FontSpec
- setFont :: (HasFontSpec xxx, Show a, FontGen a) => a -> Customiser xxx
- class HasKeys xxx where
- class HasWinAttr xxx where
- setWinAttr :: [WindowAttributes] -> Customiser xxx
- getWinAttr :: xxx -> [WindowAttributes]
- getWinAttrMaybe :: xxx -> Maybe [WindowAttributes]
- class HasBorderWidth xxx where
- setBorderWidth :: Int -> Customiser xxx
- getBorderWidth :: xxx -> Int
- getBorderWidthMaybe :: xxx -> Maybe Int
- class HasBgColorSpec xxx where
- setBgColorSpec :: ColorSpec -> Customiser xxx
- getBgColorSpec :: xxx -> ColorSpec
- getBgColorSpecMaybe :: xxx -> Maybe ColorSpec
- class HasFgColorSpec xxx where
- setFgColorSpec :: ColorSpec -> Customiser xxx
- getFgColorSpec :: xxx -> ColorSpec
- getFgColorSpecMaybe :: xxx -> Maybe ColorSpec
- class HasMargin xxx where
- setMargin :: Int -> Customiser xxx
- getMargin :: xxx -> Int
- getMarginMaybe :: xxx -> Maybe Int
- setBgColor :: (HasBgColorSpec xxx, Show p, ColorGen p) => p -> Customiser xxx
- setFgColor :: (HasFgColorSpec xxx, Show p, ColorGen p) => p -> Customiser xxx
- class HasAlign xxx where
- setAlign :: Alignment -> Customiser xxx
- getAlign :: xxx -> Alignment
- getAlignMaybe :: xxx -> Maybe Alignment
- setAllowedChar :: (Char -> Bool) -> Customiser StringF
- setShowString :: (String -> String) -> Customiser StringF
- setCursorPos :: Int -> Customiser StringF
- class HasCache xxx where
- setCache :: Bool -> Customiser xxx
- getCache :: xxx -> Bool
- getCacheMaybe :: xxx -> Maybe Bool
- setDeleteQuit :: Bool -> Customiser ShellF
- setDeleteWindowAction :: Maybe DeleteWindowAction -> Customiser ShellF
- data DeleteWindowAction
- class HasInitSize xxx where
- setInitSize :: a -> Customiser (xxx a)
- getInitSizeMaybe :: xxx a -> Maybe a
- getInitSize :: xxx a -> a
- class HasInitDisp xxx where
- setInitDisp :: a -> Customiser (xxx a)
- getInitDispMaybe :: xxx a -> Maybe a
- getInitDisp :: xxx a -> a
- setSpacer :: Spacer -> Customiser (DisplayF a)
- class HasStretchable xxx where
- setStretchable :: (Bool, Bool) -> Customiser xxx
- getStretchable :: xxx -> (Bool, Bool)
- getStretchableMaybe :: xxx -> Maybe (Bool, Bool)
- class HasLabelInside xxx where
- setLabelInside :: Bool -> Customiser xxx
- getLabelInside :: xxx -> Bool
- getLabelInsideMaybe :: xxx -> Maybe Bool
- setPlacer :: Placer -> Customiser RadioGroupF
- data ShellF
- shellF' :: Customiser ShellF -> String -> F c d -> F c d
- setInitPos :: Maybe Point -> Customiser ShellF
- unmappedSimpleShellF :: String -> F i o -> F i o
- unmappedSimpleShellF' :: Customiser ShellF -> String -> F i o -> F i o
- data ButtonF lbl
- buttonF' :: Graphic lbl => Customiser (ButtonF lbl) -> lbl -> F Click Click
- buttonF'' :: Graphic lbl => Customiser (ButtonF lbl) -> lbl -> PF (ButtonF lbl) Click Click
- setLabel :: lbl -> Customiser (ButtonF lbl)
- data DisplayF a
- displayF' :: Graphic a => Customiser (DisplayF a) -> F a b
- labelF' :: Graphic a1 => Customiser (DisplayF a1) -> a1 -> F a2 b
- data StringF
- stringF' :: Customiser StringF -> F String (InputMsg String)
- stringF'' :: Customiser StringF -> PF StringF String (InputMsg String)
- setInitString :: String -> Customiser StringF
- setInitStringSize :: String -> Customiser StringF
- passwdF' :: (StringF -> StringF) -> F String (InputMsg String)
- passwdF'' :: (StringF -> StringF) -> PF StringF String (InputMsg String)
- intF' :: Customiser StringF -> F Int (InputMsg Int)
- intF'' :: Customiser StringF -> PF StringF Int (InputMsg Int)
- intDispF' :: Customiser (DisplayF Int) -> F Int b
- gcWarningF :: F a b
- bellF :: F ho ho
- getTime :: FudgetIO f => (ClockTime -> f hi ho) -> f hi ho
- getLocalTime :: FudgetIO f => (CalendarTime -> f hi ho) -> f hi ho
- getCurrentTime :: FudgetIO f => (UTCTime -> f hi ho) -> f hi ho
- getZonedTime :: FudgetIO f => (ZonedTime -> f hi ho) -> f hi ho
- spyF :: (Show b, Show a1) => F a1 b -> F a1 b
- teeF :: (b -> [Char]) -> [Char] -> F b b
- ctrace :: Show a1 => [Char] -> a1 -> a2 -> a2
- showCommandF :: String -> F a b -> F a b
GUI
popupMenuF :: (Eq b1, Graphic b1) => [(a, b1)] -> F c b2 -> F (Either [(a, b1)] c) (Either a b2) Source #
radioGroupF' :: (Graphic lbl, Eq alt) => Customiser RadioGroupF -> [(alt, lbl)] -> alt -> F alt alt Source #
intInputF' :: Customiser StringF -> F Int Int Source #
stringInputF' :: Customiser StringF -> F String String Source #
Popups
inputPopupOptF :: String -> InF a b -> Maybe b -> F (Maybe String, Maybe a) ((Maybe String, Maybe a), Maybe b) Source #
inputPopupF :: String -> InF a c -> Maybe c -> F (Maybe String, Maybe a) ((Maybe String, Maybe a), c) Source #
passwdPopupOptF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), Maybe String) Source #
passwdPopupF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), String) Source #
stringPopupOptF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), Maybe String) Source #
stringPopupF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), String) Source #
confirmPopupF :: Graphic msg => F msg (msg, ConfirmMsg) Source #
data ConfirmMsg Source #
Output from dialog popups with OK and Cancel buttons
Instances
Show ConfirmMsg Source # | |
Defined in InputMsg showsPrec :: Int -> ConfirmMsg -> ShowS # show :: ConfirmMsg -> String # showList :: [ConfirmMsg] -> ShowS # | |
Eq ConfirmMsg Source # | |
Defined in InputMsg (==) :: ConfirmMsg -> ConfirmMsg -> Bool # (/=) :: ConfirmMsg -> ConfirmMsg -> Bool # | |
Ord ConfirmMsg Source # | |
Defined in InputMsg compare :: ConfirmMsg -> ConfirmMsg -> Ordering # (<) :: ConfirmMsg -> ConfirmMsg -> Bool # (<=) :: ConfirmMsg -> ConfirmMsg -> Bool # (>) :: ConfirmMsg -> ConfirmMsg -> Bool # (>=) :: ConfirmMsg -> ConfirmMsg -> Bool # max :: ConfirmMsg -> ConfirmMsg -> ConfirmMsg # min :: ConfirmMsg -> ConfirmMsg -> ConfirmMsg # |
oldConfirmPopupF :: F String (String, ConfirmMsg) Source #
Text editor
loadEditor :: String -> [EditCmd] Source #
data EDirection Source #
Instances
Eq EDirection Source # | |
Defined in Edtypes (==) :: EDirection -> EDirection -> Bool # (/=) :: EDirection -> EDirection -> Bool # | |
Ord EDirection Source # | |
Defined in Edtypes compare :: EDirection -> EDirection -> Ordering # (<) :: EDirection -> EDirection -> Bool # (<=) :: EDirection -> EDirection -> Bool # (>) :: EDirection -> EDirection -> Bool # (>=) :: EDirection -> EDirection -> Bool # max :: EDirection -> EDirection -> EDirection # min :: EDirection -> EDirection -> EDirection # |
inputEditorF' :: Customiser EditorF -> F String (InputMsg String) Source #
Instances
HasFontSpec EditorF Source # | |
Defined in InputEditorF setFontSpec :: FontSpec -> Customiser EditorF Source # getFontSpec :: EditorF -> FontSpec Source # |
type EditStopFn = String -> String -> EditStopChoice Source #
List and text
type PickListRequest a = ListRequest a Source #
textF' :: Customiser TextF -> F TextRequest (InputMsg (Int, String)) Source #
type TextRequest = ListRequest String Source #
Instances
HasAlign TextF Source # | |
HasBgColorSpec TextF Source # | |
Defined in TextF setBgColorSpec :: ColorSpec -> Customiser TextF Source # getBgColorSpec :: TextF -> ColorSpec Source # | |
HasBorderWidth TextF Source # | |
Defined in TextF setBorderWidth :: Int -> Customiser TextF Source # getBorderWidth :: TextF -> Int Source # | |
HasFgColorSpec TextF Source # | |
Defined in TextF setFgColorSpec :: ColorSpec -> Customiser TextF Source # getFgColorSpec :: TextF -> ColorSpec Source # | |
HasFontSpec TextF Source # | |
Defined in TextF setFontSpec :: FontSpec -> Customiser TextF Source # getFontSpec :: TextF -> FontSpec Source # | |
HasInitText TextF Source # | |
Defined in TextF setInitText :: [String] -> Customiser TextF Source # getInitText :: TextF -> [String] Source # | |
HasMargin TextF Source # | |
HasSizing TextF Source # | |
HasStretchable TextF Source # | |
class HasInitText xxx where Source #
setInitText :: [String] -> Customiser xxx Source #
getInitText :: xxx -> [String] Source #
getInitTextMaybe :: xxx -> Maybe [String] Source #
Instances
HasInitText TextF Source # | |
Defined in TextF setInitText :: [String] -> Customiser TextF Source # getInitText :: TextF -> [String] Source # |
class HasSizing xxx where Source #
setSizing :: Sizing -> Customiser xxx Source #
getSizing :: xxx -> Sizing Source #
getSizingMaybe :: xxx -> Maybe Sizing Source #
data ListRequest a Source #
ReplaceItems Int Int [a] | |
HighlightItems [Int] | |
PickItem Int |
replaceAll :: [a] -> ListRequest a Source #
replaceAllFrom :: Int -> [a] -> ListRequest a Source #
deleteItems :: Int -> Int -> ListRequest a Source #
insertItems :: Int -> [a] -> ListRequest a Source #
appendItems :: [a] -> ListRequest a Source #
changeItems :: Int -> [a] -> ListRequest a Source #
replaceItems :: Int -> Int -> [a] -> ListRequest a Source #
highlightItems :: [Int] -> ListRequest a Source #
pickItem :: Int -> ListRequest a Source #
applyListRequest :: ListRequest a -> [a] -> [a] Source #
smallPickListF :: (d -> String) -> F [d] d Source #
pickListF' :: Customiser TextF -> (a -> String) -> F (PickListRequest a) (InputMsg (Int, a)) Source #
cmdTerminalF :: FontName -> Int -> Int -> F TerminalCmd a Source #
Graphics
hyperGraphicsF :: (Eq d, Graphic leaf) => Drawing d leaf -> F (Either (Drawing d leaf) (d, Drawing d leaf)) d Source #
hyperGraphicsF' :: (Eq d, Graphic leaf) => (GraphicsF (Drawing d leaf) -> GraphicsF (Drawing d leaf)) -> Drawing d leaf -> F (Either (Drawing d leaf) (d, Drawing d leaf)) d Source #
Instances
setAdjustSize :: Bool -> Customiser (GraphicsF gfx) Source #
Fudgets and combinators
Instances
untaggedListF :: [F a b] -> F a b Source #
loopCompF :: F (Either (Either r2l inl) (Either l2r inr)) (Either (Either l2r outl) (Either r2l outr)) -> F (Either inl inr) (Either outl outr) Source #
loopCompSP :: SP (Either (Either a1 b1) (Either a2 b2)) (Either (Either a2 a3) (Either a1 b3)) -> SP (Either b1 b2) (Either a3 b3) Source #
loopThroughBothF :: F (Either r2l inl) (Either l2r outl) -> F (Either l2r inr) (Either r2l outr) -> F (Either inl inr) (Either outl outr) Source #
appendStartF :: [ho] -> F hi ho -> F hi ho Source #
concatMapF :: (a -> [b]) -> F a b Source #
prepostMapHigh :: (hi -> b) -> (c -> ho) -> F b c -> F hi ho Source #
Instances
(Eq b, Eq a) => Eq (DynMsg a b) Source # | |
(Ord b, Ord a) => Ord (DynMsg a b) Source # | |
Input
Instances
Functor InputMsg Source # | |
Show a => Show (InputMsg a) Source # | |
Eq a => Eq (InputMsg a) Source # | |
Ord a => Ord (InputMsg a) Source # | |
inputDoneSP :: SP (InputMsg b) b Source #
inputLeaveDoneSP :: SP (InputMsg b) b Source #
inputThroughF :: InF a a -> InF a a Source #
inputChange :: a -> InputMsg a Source #
inputPairLF :: Orientation -> InF a1 b1 -> InF a2 b2 -> F (a1, a2) (InputMsg (b1, b2)) Source #
stripInputSP :: SP (InputMsg b) b Source #
stripInputMsg :: InputMsg a -> a Source #
inputLeaveDone :: InputMsg a -> Maybe a Source #
Layout
data Orientation Source #
Instances
Show Orientation Source # | |
Defined in LayoutDir showsPrec :: Int -> Orientation -> ShowS # show :: Orientation -> String # showList :: [Orientation] -> ShowS # | |
Eq Orientation Source # | |
Defined in LayoutDir (==) :: Orientation -> Orientation -> Bool # (/=) :: Orientation -> Orientation -> Bool # | |
Ord Orientation Source # | |
Defined in LayoutDir compare :: Orientation -> Orientation -> Ordering # (<) :: Orientation -> Orientation -> Bool # (<=) :: Orientation -> Orientation -> Bool # (>) :: Orientation -> Orientation -> Bool # (>=) :: Orientation -> Orientation -> Bool # max :: Orientation -> Orientation -> Orientation # min :: Orientation -> Orientation -> Orientation # |
layoutModifierF :: (LayoutRequest -> LayoutRequest) -> F a b -> F a b Source #
data LayoutRequest Source #
Instances
Show LayoutRequest Source # | |
Defined in LayoutRequest showsPrec :: Int -> LayoutRequest -> ShowS # show :: LayoutRequest -> String # showList :: [LayoutRequest] -> ShowS # |
fixedh :: LayoutRequest -> Bool Source #
fixedv :: LayoutRequest -> Bool Source #
flipReq :: LayoutRequest -> LayoutRequest Source #
data NameLayout Source #
hvAlignNL :: Alignment -> Alignment -> NameLayout -> NameLayout Source #
marginHVAlignNL :: Distance -> Alignment -> Alignment -> NameLayout -> NameLayout Source #
hBoxNL :: [NameLayout] -> NameLayout Source #
hBoxNL' :: Distance -> [NameLayout] -> NameLayout Source #
nullNL :: NameLayout Source #
leafNL :: LName -> NameLayout Source #
spaceNL :: Spacer -> NameLayout -> NameLayout Source #
placeNL :: Placer -> [NameLayout] -> NameLayout Source #
modNL :: (Placer -> Placer) -> NameLayout -> NameLayout Source #
nameLayoutF :: NameLayout -> F a b -> F a b Source #
sepNL :: Size -> NameLayout -> NameLayout Source #
marginNL :: Distance -> NameLayout -> NameLayout Source #
vBoxNL :: [NameLayout] -> NameLayout Source #
vBoxNL' :: Distance -> [NameLayout] -> NameLayout Source #
horizontalP :: Placer Source #
horizontalP' :: Distance -> Placer Source #
verticalP' :: Distance -> Placer Source #
paragraphP :: Placer Source #
paragraphP' :: Size -> Placer Source #
data PotRequest Source #
containerGroupF :: Rect -> Rect -> Int -> Button -> ModState -> F c b -> F (Either (Rect, Rect) c) (Either Rect b) Source #
popupShellF' :: Customiser ShellF -> String -> Maybe Point -> F a b -> F a (a, b) Source #
Instances
Eq a => Eq (PopupMsg a) Source # | |
Ord a => Ord (PopupMsg a) Source # | |
posPopupShellF :: String -> [WindowAttributes] -> F c a -> F (c, Maybe Point) (c, a) Source #
Stream processors
Combining stream processors
prepostMapSP :: (t1 -> a) -> (t2 -> b) -> SP a t2 -> SP t1 b Source #
loopOnlySP :: SP a a -> SP a b Source #
loopThroughBothSP :: SP (Either a1 b1) (Either a2 a3) -> SP (Either a2 b2) (Either a1 b3) -> SP (Either b1 b2) (Either a3 b3) Source #
Stream processor primitives
class StreamProcIO sp where Source #
Instances
Convenient stream processors
filterJustSP :: SP (Maybe b) b Source #
filterLeftSP :: SP (Either b1 b2) b1 Source #
filterRightSP :: SP (Either a1 b) b Source #
mapFilterSP :: (t -> Maybe b) -> SP t b Source #
concatMapSP :: (t -> [b]) -> SP t b Source #
concatMapAccumlSP :: (t -> a -> (t, [b])) -> t -> SP a b Source #
mapstateSP :: (t -> a -> (t, [b])) -> t -> SP a b Source #
mapAccumlSP :: (t -> a -> (t, b)) -> t -> SP a b Source #
Stream processor behaviour
appendStartSP :: [b] -> SP a b -> SP a b Source #
contMap :: StreamProcIO sp => (i -> (o -> sp i o) -> sp i o) -> sp i o Source #
System (stdio, files, network, subprocesses)
Dialogue IO
Stdio
Subprocesses
Files and directories
Sockets
Timer
Running a fudget
Command line, environment and defaults
defaultSize :: Maybe Point Source #
defaultSep :: Num a => a Source #
Utilities for the Either type
filterLeft :: [Either b1 b2] -> [b1] Source #
filterRight :: [Either a b] -> [b] Source #
splitEitherList :: [Either a1 a2] -> ([a1], [a2]) Source #
stripEither :: Either a a -> a Source #
stripRight :: Either a1 a2 -> Maybe a2 Source #
swapEither :: Either b a -> Either a b Source #
Geometry
confine :: Rect -> Rect -> Rect Source #
confine outer inner: moves an shrinks inner to fit within outer
rectMiddle :: Rect -> Point Source #
Utilities
lsplit :: [a1] -> [a2] -> ([a2], [a2]) Source #
lsplit xs ys = (lhead xs ys,ltail xs ys), but without the space leak, -fpbu
version_0_18_4 :: String Source #
only for documentation, use version
instead
Xlib types
Instances
type FontStruct = FontStructF (Array Char CharStruct) Source #
data WindowAttributes Source #
Instances
Read WindowAttributes Source # | |
Defined in Xtypes | |
Show WindowAttributes Source # | |
Defined in Xtypes showsPrec :: Int -> WindowAttributes -> ShowS # show :: WindowAttributes -> String # showList :: [WindowAttributes] -> ShowS # | |
Eq WindowAttributes Source # | |
Defined in Xtypes (==) :: WindowAttributes -> WindowAttributes -> Bool # (/=) :: WindowAttributes -> WindowAttributes -> Bool # | |
Ord WindowAttributes Source # | |
Defined in Xtypes compare :: WindowAttributes -> WindowAttributes -> Ordering # (<) :: WindowAttributes -> WindowAttributes -> Bool # (<=) :: WindowAttributes -> WindowAttributes -> Bool # (>) :: WindowAttributes -> WindowAttributes -> Bool # (>=) :: WindowAttributes -> WindowAttributes -> Bool # max :: WindowAttributes -> WindowAttributes -> WindowAttributes # min :: WindowAttributes -> WindowAttributes -> WindowAttributes # |
Instances
Bounded Modifiers Source # | |
Enum Modifiers Source # | |
Defined in AuxTypes succ :: Modifiers -> Modifiers # pred :: Modifiers -> Modifiers # fromEnum :: Modifiers -> Int # enumFrom :: Modifiers -> [Modifiers] # enumFromThen :: Modifiers -> Modifiers -> [Modifiers] # enumFromTo :: Modifiers -> Modifiers -> [Modifiers] # enumFromThenTo :: Modifiers -> Modifiers -> Modifiers -> [Modifiers] # | |
Read Modifiers Source # | |
Show Modifiers Source # | |
Eq Modifiers Source # | |
Ord Modifiers Source # | |
Defined in AuxTypes |
Graphics and drawings
Instances
Bounded CoordMode Source # | |
Enum CoordMode Source # | |
Defined in DrawTypes succ :: CoordMode -> CoordMode # pred :: CoordMode -> CoordMode # fromEnum :: CoordMode -> Int # enumFrom :: CoordMode -> [CoordMode] # enumFromThen :: CoordMode -> CoordMode -> [CoordMode] # enumFromTo :: CoordMode -> CoordMode -> [CoordMode] # enumFromThenTo :: CoordMode -> CoordMode -> CoordMode -> [CoordMode] # | |
Read CoordMode Source # | |
Show CoordMode Source # | |
Eq CoordMode Source # | |
Ord CoordMode Source # | |
Defined in DrawTypes |
data DrawCommand Source #
Instances
Read DrawCommand Source # | |
Defined in DrawTypes readsPrec :: Int -> ReadS DrawCommand # readList :: ReadS [DrawCommand] # readPrec :: ReadPrec DrawCommand # readListPrec :: ReadPrec [DrawCommand] # | |
Show DrawCommand Source # | |
Defined in DrawTypes showsPrec :: Int -> DrawCommand -> ShowS # show :: DrawCommand -> String # showList :: [DrawCommand] -> ShowS # | |
Move DrawCommand Source # | |
Defined in Drawcmd move :: Point -> DrawCommand -> DrawCommand Source # | |
Eq DrawCommand Source # | |
Defined in DrawTypes (==) :: DrawCommand -> DrawCommand -> Bool # (/=) :: DrawCommand -> DrawCommand -> Bool # | |
Ord DrawCommand Source # | |
Defined in DrawTypes compare :: DrawCommand -> DrawCommand -> Ordering # (<) :: DrawCommand -> DrawCommand -> Bool # (<=) :: DrawCommand -> DrawCommand -> Bool # (>) :: DrawCommand -> DrawCommand -> Bool # (>=) :: DrawCommand -> DrawCommand -> Bool # max :: DrawCommand -> DrawCommand -> DrawCommand # min :: DrawCommand -> DrawCommand -> DrawCommand # |
fillCircle :: Point -> Int -> DrawCommand Source #
drawCircle :: Point -> Int -> DrawCommand Source #
class Graphic a where Source #
measureGraphicK :: FudgetIO k => a -> GCtx -> Cont (k i o) MeasuredGraphics Source #
measureGraphicListK :: FudgetIO k => [a] -> GCtx -> Cont (k i o) MeasuredGraphics Source #
Instances
data Drawing lbl leaf Source #
AtomicD leaf | |
LabelD lbl (Drawing lbl leaf) | |
AttribD GCSpec (Drawing lbl leaf) | |
SpacedD Spacer (Drawing lbl leaf) | |
PlacedD Placer (Drawing lbl leaf) | |
ComposedD Int [Drawing lbl leaf] | Int=how many visible components |
CreateHardAttribD GCtx [GCAttributes ColorSpec FontSpec] (GCtx -> Drawing lbl leaf) |
Instances
Functor (Drawing lbl) Source # | |
(Show leaf, Show lbl) => Show (Drawing lbl leaf) Source # | |
Graphic leaf => Graphic (Drawing annot leaf) Source # | |
Defined in Drawing measureGraphicK :: FudgetIO k => Drawing annot leaf -> GCtx -> Cont (k i o) MeasuredGraphics Source # measureGraphicListK :: FudgetIO k => [Drawing annot leaf] -> GCtx -> Cont (k i o) MeasuredGraphics Source # |
softAttribD :: [GCAttributes ColorSpec FontSpec] -> Drawing lbl leaf -> Drawing lbl leaf Source #
Instances
Show Gfx Source # | |
Graphic Gfx Source # | |
Defined in DrawingUtils measureGraphicK :: FudgetIO k => Gfx -> GCtx -> Cont (k i o) MeasuredGraphics Source # measureGraphicListK :: FudgetIO k => [Gfx] -> GCtx -> Cont (k i o) MeasuredGraphics Source # |
data FixedDrawing Source #
Instances
Show FixedDrawing Source # | |
Defined in FixedDrawing showsPrec :: Int -> FixedDrawing -> ShowS # show :: FixedDrawing -> String # showList :: [FixedDrawing] -> ShowS # | |
Graphic FixedDrawing Source # | |
Defined in FixedDrawing measureGraphicK :: FudgetIO k => FixedDrawing -> GCtx -> Cont (k i o) MeasuredGraphics Source # measureGraphicListK :: FudgetIO k => [FixedDrawing] -> GCtx -> Cont (k i o) MeasuredGraphics Source # |
data FixedColorDrawing Source #
FixCD Size [(GCId, [DrawCommand])] |
Instances
Show FixedColorDrawing Source # | |
Defined in FixedDrawing showsPrec :: Int -> FixedColorDrawing -> ShowS # show :: FixedColorDrawing -> String # showList :: [FixedColorDrawing] -> ShowS # | |
Graphic FixedColorDrawing Source # | |
Defined in FixedDrawing measureGraphicK :: FudgetIO k => FixedColorDrawing -> GCtx -> Cont (k i o) MeasuredGraphics Source # measureGraphicListK :: FudgetIO k => [FixedColorDrawing] -> GCtx -> Cont (k i o) MeasuredGraphics Source # | |
PixmapGen FixedColorDrawing Source # | |
Defined in Graphic2Pixmap convToPixmapK :: FudgetIO c => FixedColorDrawing -> Cont (c i o) PixmapImage Source # |
data FlexibleDrawing Source #
Instances
Show FlexibleDrawing Source # | |
Defined in FlexibleDrawing showsPrec :: Int -> FlexibleDrawing -> ShowS # show :: FlexibleDrawing -> String # showList :: [FlexibleDrawing] -> ShowS # | |
Graphic FlexibleDrawing Source # | |
Defined in FlexibleDrawing measureGraphicK :: FudgetIO k => FlexibleDrawing -> GCtx -> Cont (k i o) MeasuredGraphics Source # measureGraphicListK :: FudgetIO k => [FlexibleDrawing] -> GCtx -> Cont (k i o) MeasuredGraphics Source # |
flex :: (Rect -> [DrawCommand]) -> FlexibleDrawing Source #
flex' :: Size -> (Rect -> [DrawCommand]) -> FlexibleDrawing Source #
hFiller :: Int -> FlexibleDrawing Source #
vFiller :: Int -> FlexibleDrawing Source #
frame' :: Size -> FlexibleDrawing Source #
ellipse' :: Size -> FlexibleDrawing Source #
filledEllipse' :: Size -> FlexibleDrawing Source #
filledarc' :: Size -> Int -> Int -> FlexibleDrawing Source #
data BitmapFile Source #
Instances
Graphic BitmapFile Source # | |
Defined in BitmapDrawing measureGraphicK :: FudgetIO k => BitmapFile -> GCtx -> Cont (k i o) MeasuredGraphics Source # measureGraphicListK :: FudgetIO k => [BitmapFile] -> GCtx -> Cont (k i o) MeasuredGraphics Source # |
class ColorGen a where Source #
tryConvColorK :: FudgetIO f => a -> Cont (f i o) (Maybe Pixel) Source #
convColorListK :: FudgetIO f => [a] -> Cont (f i o) (Maybe Pixel) Source #
class FontGen a where Source #
tryConvFontK :: FudgetIO f => a -> Cont (f i o) (Maybe FontData) Source #
convFontListK :: FudgetIO f => [a] -> Cont (f i o) (Maybe FontData) Source #
Instances
wCreateGCtx :: (ColorGen a1, FudgetIO f, FontGen a2, Show a1, Show a2) => GCtx -> [GCAttributes a1 a2] -> (GCtx -> f i o) -> f i o Source #
createGCtx :: (ColorGen a1, FudgetIO f, FontGen a2, Show a1, Show a2) => Drawable -> GCtx -> [GCAttributes a1 a2] -> (GCtx -> f i o) -> f i o Source #
gcFgA :: c -> [GCAttributes c FontSpec] Source #
gcBgA :: c -> [GCAttributes c FontSpec] Source #
gcFontA :: f -> [GCAttributes ColorSpec f] Source #
data GCAttributes a b Source #
Instances
data GCFillStyle Source #
Instances
data GCCapStyle Source #
Instances
data GCLineStyle Source #
Instances
data GCFunction Source #
GXclear | |
GXand | |
GXandReverse | |
GXcopy | |
GXandInverted | |
GXnoop | |
GXxor | |
GXor | |
GXnor | |
GXequiv | |
GXinvert | |
GXorReverse | |
GXCopyInverted | |
GXorInverted | |
GXnand | |
GXset |
Instances
Customisation
type Customiser a = a -> a Source #
standard :: Customiser a Source #
class HasClickToType xxx where Source #
setClickToType :: Bool -> Customiser xxx Source #
getClickToType :: xxx -> Bool Source #
getClickToTypeMaybe :: xxx -> Maybe Bool Source #
Instances
HasClickToType ShellF Source # | |
Defined in DShellF setClickToType :: Bool -> Customiser ShellF Source # getClickToType :: ShellF -> Bool Source # |
class HasVisible xxx where Source #
setVisible :: Bool -> Customiser xxx Source #
getVisible :: xxx -> Bool Source #
getVisibleMaybe :: xxx -> Maybe Bool Source #
Instances
HasVisible ShellF Source # | |
Defined in DShellF setVisible :: Bool -> Customiser ShellF Source # getVisible :: ShellF -> Bool Source # |
class HasFontSpec xxx where Source #
setFontSpec :: FontSpec -> Customiser xxx Source #
getFontSpec :: xxx -> FontSpec Source #
getFontSpecMaybe :: xxx -> Maybe FontSpec Source #
Instances
setFont :: (HasFontSpec xxx, Show a, FontGen a) => a -> Customiser xxx Source #
class HasKeys xxx where Source #
setKeys :: [(ModState, KeySym)] -> Customiser xxx Source #
Instances
HasKeys ToggleButtonF Source # | |
Defined in DToggleButtonF setKeys :: [(ModState, KeySym)] -> Customiser ToggleButtonF Source # getKeys :: ToggleButtonF -> [(ModState, KeySym)] Source # getKeysMaybe :: ToggleButtonF -> Maybe [(ModState, KeySym)] Source # | |
HasKeys (ButtonF a) Source # | |
class HasWinAttr xxx where Source #
setWinAttr :: [WindowAttributes] -> Customiser xxx Source #
getWinAttr :: xxx -> [WindowAttributes] Source #
getWinAttrMaybe :: xxx -> Maybe [WindowAttributes] Source #
Instances
HasWinAttr ShellF Source # | |
Defined in DShellF setWinAttr :: [WindowAttributes] -> Customiser ShellF Source # getWinAttr :: ShellF -> [WindowAttributes] Source # getWinAttrMaybe :: ShellF -> Maybe [WindowAttributes] Source # |
class HasBorderWidth xxx where Source #
setBorderWidth :: Int -> Customiser xxx Source #
getBorderWidth :: xxx -> Int Source #
getBorderWidthMaybe :: xxx -> Maybe Int Source #
Instances
HasBorderWidth StringF Source # | |
Defined in StringF setBorderWidth :: Int -> Customiser StringF Source # getBorderWidth :: StringF -> Int Source # | |
HasBorderWidth TextF Source # | |
Defined in TextF setBorderWidth :: Int -> Customiser TextF Source # getBorderWidth :: TextF -> Int Source # | |
HasBorderWidth (DisplayF a) Source # | |
Defined in DDisplayF setBorderWidth :: Int -> Customiser (DisplayF a) Source # getBorderWidth :: DisplayF a -> Int Source # | |
HasBorderWidth (GraphicsF a) Source # | |
Defined in GraphicsF setBorderWidth :: Int -> Customiser (GraphicsF a) Source # getBorderWidth :: GraphicsF a -> Int Source # |
class HasBgColorSpec xxx where Source #
setBgColorSpec :: ColorSpec -> Customiser xxx Source #
getBgColorSpec :: xxx -> ColorSpec Source #
getBgColorSpecMaybe :: xxx -> Maybe ColorSpec Source #
Instances
HasBgColorSpec StringF Source # | |
Defined in StringF | |
HasBgColorSpec TextF Source # | |
Defined in TextF setBgColorSpec :: ColorSpec -> Customiser TextF Source # getBgColorSpec :: TextF -> ColorSpec Source # | |
HasBgColorSpec (ButtonF a) Source # | |
Defined in DButtonF setBgColorSpec :: ColorSpec -> Customiser (ButtonF a) Source # getBgColorSpec :: ButtonF a -> ColorSpec Source # getBgColorSpecMaybe :: ButtonF a -> Maybe ColorSpec Source # | |
HasBgColorSpec (DisplayF a) Source # | |
Defined in DDisplayF setBgColorSpec :: ColorSpec -> Customiser (DisplayF a) Source # getBgColorSpec :: DisplayF a -> ColorSpec Source # getBgColorSpecMaybe :: DisplayF a -> Maybe ColorSpec Source # | |
HasBgColorSpec (GraphicsF a) Source # | |
Defined in GraphicsF setBgColorSpec :: ColorSpec -> Customiser (GraphicsF a) Source # getBgColorSpec :: GraphicsF a -> ColorSpec Source # getBgColorSpecMaybe :: GraphicsF a -> Maybe ColorSpec Source # |
class HasFgColorSpec xxx where Source #
setFgColorSpec :: ColorSpec -> Customiser xxx Source #
getFgColorSpec :: xxx -> ColorSpec Source #
getFgColorSpecMaybe :: xxx -> Maybe ColorSpec Source #
Instances
HasFgColorSpec StringF Source # | |
Defined in StringF | |
HasFgColorSpec TextF Source # | |
Defined in TextF setFgColorSpec :: ColorSpec -> Customiser TextF Source # getFgColorSpec :: TextF -> ColorSpec Source # | |
HasFgColorSpec (ButtonF a) Source # | |
Defined in DButtonF setFgColorSpec :: ColorSpec -> Customiser (ButtonF a) Source # getFgColorSpec :: ButtonF a -> ColorSpec Source # getFgColorSpecMaybe :: ButtonF a -> Maybe ColorSpec Source # | |
HasFgColorSpec (DisplayF a) Source # | |
Defined in DDisplayF setFgColorSpec :: ColorSpec -> Customiser (DisplayF a) Source # getFgColorSpec :: DisplayF a -> ColorSpec Source # getFgColorSpecMaybe :: DisplayF a -> Maybe ColorSpec Source # | |
HasFgColorSpec (GraphicsF a) Source # | |
Defined in GraphicsF setFgColorSpec :: ColorSpec -> Customiser (GraphicsF a) Source # getFgColorSpec :: GraphicsF a -> ColorSpec Source # getFgColorSpecMaybe :: GraphicsF a -> Maybe ColorSpec Source # |
class HasMargin xxx where Source #
setMargin :: Int -> Customiser xxx Source #
getMargin :: xxx -> Int Source #
getMarginMaybe :: xxx -> Maybe Int Source #
setBgColor :: (HasBgColorSpec xxx, Show p, ColorGen p) => p -> Customiser xxx Source #
setFgColor :: (HasFgColorSpec xxx, Show p, ColorGen p) => p -> Customiser xxx Source #
class HasAlign xxx where Source #
setAlign :: Alignment -> Customiser xxx Source #
getAlign :: xxx -> Alignment Source #
getAlignMaybe :: xxx -> Maybe Alignment Source #
setAllowedChar :: (Char -> Bool) -> Customiser StringF Source #
setShowString :: (String -> String) -> Customiser StringF Source #
setCursorPos :: Int -> Customiser StringF Source #
setDeleteQuit :: Bool -> Customiser ShellF Source #
data DeleteWindowAction Source #
Instances
Show DeleteWindowAction Source # | |
Defined in DShellF showsPrec :: Int -> DeleteWindowAction -> ShowS # show :: DeleteWindowAction -> String # showList :: [DeleteWindowAction] -> ShowS # | |
Eq DeleteWindowAction Source # | |
Defined in DShellF (==) :: DeleteWindowAction -> DeleteWindowAction -> Bool # (/=) :: DeleteWindowAction -> DeleteWindowAction -> Bool # |
class HasInitSize xxx where Source #
setInitSize :: a -> Customiser (xxx a) Source #
getInitSizeMaybe :: xxx a -> Maybe a Source #
getInitSize :: xxx a -> a Source #
Instances
HasInitSize DisplayF Source # | |
Defined in DDisplayF setInitSize :: a -> Customiser (DisplayF a) Source # getInitSizeMaybe :: DisplayF a -> Maybe a Source # getInitSize :: DisplayF a -> a Source # | |
HasInitSize GraphicsF Source # | |
Defined in GraphicsF setInitSize :: a -> Customiser (GraphicsF a) Source # getInitSizeMaybe :: GraphicsF a -> Maybe a Source # getInitSize :: GraphicsF a -> a Source # |
class HasInitDisp xxx where Source #
setInitDisp :: a -> Customiser (xxx a) Source #
getInitDispMaybe :: xxx a -> Maybe a Source #
getInitDisp :: xxx a -> a Source #
Instances
HasInitDisp DisplayF Source # | |
Defined in DDisplayF setInitDisp :: a -> Customiser (DisplayF a) Source # getInitDispMaybe :: DisplayF a -> Maybe a Source # getInitDisp :: DisplayF a -> a Source # | |
HasInitDisp GraphicsF Source # | |
Defined in GraphicsF setInitDisp :: a -> Customiser (GraphicsF a) Source # getInitDispMaybe :: GraphicsF a -> Maybe a Source # getInitDisp :: GraphicsF a -> a Source # |
class HasStretchable xxx where Source #
setStretchable :: (Bool, Bool) -> Customiser xxx Source #
getStretchable :: xxx -> (Bool, Bool) Source #
Instances
class HasLabelInside xxx where Source #
setLabelInside :: Bool -> Customiser xxx Source #
getLabelInside :: xxx -> Bool Source #
getLabelInsideMaybe :: xxx -> Maybe Bool Source #
Instances
HasLabelInside RadioGroupF Source # | |
Defined in DRadioF setLabelInside :: Bool -> Customiser RadioGroupF Source # getLabelInside :: RadioGroupF -> Bool Source # | |
HasLabelInside ToggleButtonF Source # | |
Defined in DToggleButtonF |
setPlacer :: Placer -> Customiser RadioGroupF Source #
Instances
HasClickToType ShellF Source # | |
Defined in DShellF setClickToType :: Bool -> Customiser ShellF Source # getClickToType :: ShellF -> Bool Source # | |
HasVisible ShellF Source # | |
Defined in DShellF setVisible :: Bool -> Customiser ShellF Source # getVisible :: ShellF -> Bool Source # | |
HasMargin ShellF Source # | |
HasSizing ShellF Source # | |
HasWinAttr ShellF Source # | |
Defined in DShellF setWinAttr :: [WindowAttributes] -> Customiser ShellF Source # getWinAttr :: ShellF -> [WindowAttributes] Source # getWinAttrMaybe :: ShellF -> Maybe [WindowAttributes] Source # |
setInitPos :: Maybe Point -> Customiser ShellF Source #
unmappedSimpleShellF' :: Customiser ShellF -> String -> F i o -> F i o Source #
Instances
HasAlign (ButtonF a) Source # | |
HasBgColorSpec (ButtonF a) Source # | |
Defined in DButtonF setBgColorSpec :: ColorSpec -> Customiser (ButtonF a) Source # getBgColorSpec :: ButtonF a -> ColorSpec Source # getBgColorSpecMaybe :: ButtonF a -> Maybe ColorSpec Source # | |
HasFgColorSpec (ButtonF a) Source # | |
Defined in DButtonF setFgColorSpec :: ColorSpec -> Customiser (ButtonF a) Source # getFgColorSpec :: ButtonF a -> ColorSpec Source # getFgColorSpecMaybe :: ButtonF a -> Maybe ColorSpec Source # | |
HasFontSpec (ButtonF a) Source # | |
Defined in DButtonF setFontSpec :: FontSpec -> Customiser (ButtonF a) Source # getFontSpec :: ButtonF a -> FontSpec Source # | |
HasKeys (ButtonF a) Source # | |
HasMargin (ButtonF a) Source # | |
buttonF'' :: Graphic lbl => Customiser (ButtonF lbl) -> lbl -> PF (ButtonF lbl) Click Click Source #
setLabel :: lbl -> Customiser (ButtonF lbl) Source #
Instances
Instances
HasBgColorSpec StringF Source # | |
Defined in StringF | |
HasBorderWidth StringF Source # | |
Defined in StringF setBorderWidth :: Int -> Customiser StringF Source # getBorderWidth :: StringF -> Int Source # | |
HasFgColorSpec StringF Source # | |
Defined in StringF | |
HasFontSpec StringF Source # | |
Defined in StringF setFontSpec :: FontSpec -> Customiser StringF Source # getFontSpec :: StringF -> FontSpec Source # | |
HasSizing StringF Source # | |
setInitString :: String -> Customiser StringF Source #
Miscellaneous
gcWarningF :: F a b Source #
Time
getLocalTime :: FudgetIO f => (CalendarTime -> f hi ho) -> f hi ho Source #
getCurrentTime :: FudgetIO f => (UTCTime -> f hi ho) -> f hi ho Source #
getZonedTime :: FudgetIO f => (ZonedTime -> f hi ho) -> f hi ho Source #