fudgets-0.18.3.1: The Fudgets Library
Safe HaskellNone
LanguageHaskell98

Fudgets

Description

Programmers' index. There is very little documentation here. See the Fudget Library Reference Manual instead.

Synopsis

GUI

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

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

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

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

data BMevents Source #

Constructors

BMNormal 
BMInverted 
BMClick 

Instances

Instances details
Eq BMevents Source # 
Instance details

Defined in ButtonGroupF

Ord BMevents Source # 
Instance details

Defined in ButtonGroupF

Show BMevents Source # 
Instance details

Defined in ButtonGroupF

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

data Click Source #

Button clicks

Constructors

Click 

Instances

Instances details
Eq Click Source # 
Instance details

Defined in InputMsg

Methods

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

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

Ord Click Source # 
Instance details

Defined in InputMsg

Methods

compare :: Click -> Click -> Ordering #

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

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

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

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

max :: Click -> Click -> Click #

min :: Click -> Click -> Click #

Show Click Source # 
Instance details

Defined in InputMsg

Methods

showsPrec :: Int -> Click -> ShowS #

show :: Click -> String #

showList :: [Click] -> ShowS #

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

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

Popups

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

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

data ConfirmMsg Source #

Output from dialog popups with OK and Cancel buttons

Constructors

Confirm 
Cancel 

Instances

Instances details
Eq ConfirmMsg Source # 
Instance details

Defined in InputMsg

Ord ConfirmMsg Source # 
Instance details

Defined in InputMsg

Show ConfirmMsg Source # 
Instance details

Defined in InputMsg

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

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

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

Text editor

data EditEvt Source #

Instances

Instances details
Eq EditEvt Source # 
Instance details

Defined in Edit

Methods

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

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

Ord EditEvt Source # 
Instance details

Defined in Edit

data EDirection Source #

Constructors

ELeft 
ERight 

Instances

Instances details
Eq EDirection Source # 
Instance details

Defined in Edtypes

Ord EDirection Source # 
Instance details

Defined in Edtypes

List and text

data TextF Source #

Instances

Instances details
HasSizing TextF Source # 
Instance details

Defined in TextF

HasInitText TextF Source # 
Instance details

Defined in TextF

HasStretchable TextF Source # 
Instance details

Defined in TextF

HasAlign TextF Source # 
Instance details

Defined in TextF

HasMargin TextF Source # 
Instance details

Defined in TextF

HasFgColorSpec TextF Source # 
Instance details

Defined in TextF

HasBgColorSpec TextF Source # 
Instance details

Defined in TextF

HasBorderWidth TextF Source # 
Instance details

Defined in TextF

HasFontSpec TextF Source # 
Instance details

Defined in TextF

class HasInitText xxx where Source #

Minimal complete definition

setInitText, getInitTextMaybe

Instances

Instances details
HasInitText TextF Source # 
Instance details

Defined in TextF

data Sizing Source #

Constructors

Static 
Growing 
Dynamic 

Instances

Instances details
Eq Sizing Source # 
Instance details

Defined in Sizing

Methods

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

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

Read Sizing Source # 
Instance details

Defined in Sizing

Show Sizing Source # 
Instance details

Defined in Sizing

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

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

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

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

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

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

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

data PopupMenu Source #

Instances

Instances details
Show PopupMenu Source # 
Instance details

Defined in MenuPopupF

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 #

data GraphicsF gfx Source #

Instances

Instances details
HasInitDisp GraphicsF Source # 
Instance details

Defined in GraphicsF

HasInitSize GraphicsF Source # 
Instance details

Defined in GraphicsF

HasSizing (GraphicsF a) Source # 
Instance details

Defined in GraphicsF

HasStretchable (GraphicsF a) Source # 
Instance details

Defined in GraphicsF

HasFgColorSpec (GraphicsF a) Source # 
Instance details

Defined in GraphicsF

HasBgColorSpec (GraphicsF a) Source # 
Instance details

Defined in GraphicsF

HasBorderWidth (GraphicsF a) Source # 
Instance details

Defined in GraphicsF

HasFontSpec (GraphicsF a) Source # 
Instance details

Defined in GraphicsF

Fudgets and combinators

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

type Fudget a b = F a b Source #

data F hi ho Source #

Instances

Instances details
StreamProcIO F Source # 
Instance details

Defined in NullF

Methods

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

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

end :: F i o Source #

FudgetIO F Source # 
Instance details

Defined in NullF

Methods

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

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

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

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 #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

nullF :: F hi ho Source #

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

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

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

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

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

idF :: F b b Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

quitF :: F ans ho Source #

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

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

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

data DynMsg a b Source #

Constructors

DynCreate b 
DynDestroy 
DynMsg a 

Instances

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

Defined in Dynforkmerge

Methods

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

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

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

Defined in Dynforkmerge

Methods

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

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

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

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

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

max :: DynMsg a b -> DynMsg a b -> DynMsg a b #

min :: DynMsg a b -> DynMsg a b -> DynMsg a b #

class FudgetIO f where Source #

Methods

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

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

Instances

Instances details
FudgetIO K Source # 
Instance details

Defined in NullF

Methods

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

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

FudgetIO F Source # 
Instance details

Defined in NullF

Methods

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

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

Input

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

data InputMsg a Source #

Constructors

InputChange a 
InputDone KeySym a 

Instances

Instances details
Functor InputMsg Source # 
Instance details

Defined in InputMsg

Methods

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

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

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

Defined in InputMsg

Methods

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

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

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

Defined in InputMsg

Methods

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

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

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

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

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

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

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

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

Defined in InputMsg

Methods

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

show :: InputMsg a -> String #

showList :: [InputMsg a] -> ShowS #

inputListSP :: Eq a => [a] -> SP (a, InputMsg b) (InputMsg [(a, b)]) Source #

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

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

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

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

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

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

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

Layout

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

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

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

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

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

data LayoutDir Source #

Constructors

Horizontal 
Vertical 

Instances

Instances details
Eq LayoutDir Source # 
Instance details

Defined in LayoutDir

Ord LayoutDir Source # 
Instance details

Defined in LayoutDir

Show LayoutDir Source # 
Instance details

Defined in LayoutDir

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

nullLF :: F hi ho Source #

holeF :: F hi ho Source #

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

data LayoutRequest Source #

Instances

Instances details
Show LayoutRequest Source # 
Instance details

Defined in LayoutRequest

data Placer Source #

Instances

Instances details
Show Placer Source # 
Instance details

Defined in LayoutRequest

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

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

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

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

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

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

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

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

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

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

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

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

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

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

data Spacer Source #

Instances

Instances details
Show Spacer Source # 
Instance details

Defined in LayoutRequest

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

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

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

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

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

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

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

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

data PopupMsg a Source #

Constructors

Popup Point a 
Popdown 

Instances

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

Defined in Popupmsg

Methods

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

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

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

Defined in Popupmsg

Methods

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

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

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

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

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

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

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

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

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

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

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

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

data ESelCmd a Source #

Constructors

OwnSel 
SelCmd (SelCmd a) 

Instances

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

Defined in SelectionF

Methods

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

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

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

Defined in SelectionF

Methods

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

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

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

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

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

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

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

data ESelEvt a Source #

Constructors

WantSel 
SelEvt (SelEvt a) 

Instances

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

Defined in SelectionF

Methods

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

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

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

Defined in SelectionF

Methods

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

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

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

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

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

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

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

data SelCmd a Source #

Constructors

Sel a 
ClearSel 
PasteSel 

Instances

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

Defined in SelectionF

Methods

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

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

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

Defined in SelectionF

Methods

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

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

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

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

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

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

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

data SelEvt a Source #

Constructors

LostSel 
SelNotify a 

Instances

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

Defined in SelectionF

Methods

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

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

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

Defined in SelectionF

Methods

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

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

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

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

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

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

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

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

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

type Time = Int Source #

Stream processors

Combining stream processors

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

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

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

compEitherSP :: SP a1 a2 -> SP a3 b -> SP (Either a1 a3) (Either a2 b) Source #

idLeftSP :: SP a1 b -> SP (Either a2 a1) (Either a2 b) Source #

idRightSP :: SP a1 a2 -> SP (Either a1 b) (Either a2 b) Source #

postMapSP :: (t -> b) -> SP a t -> SP a b Source #

preMapSP :: SP a b -> (t -> a) -> SP t b Source #

prepostMapSP :: (t1 -> a) -> (t2 -> b) -> SP a t2 -> SP t1 b Source #

serCompSP :: SP a1 b -> SP a2 a1 -> SP a2 b Source #

loopLeftSP :: SP (Either a1 a2) (Either a1 b) -> SP a2 b Source #

loopSP :: SP a a -> SP a a Source #

loopOnlySP :: SP a a -> SP a b Source #

loopThroughRightSP :: SP (Either a1 a2) (Either a3 b) -> SP a3 a1 -> SP a2 b Source #

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

parSP :: SP a b -> SP a b -> SP a b Source #

seqSP :: SP a b -> SP a b -> SP a b Source #

Stream processor primitives

data SP a b Source #

Instances

Instances details
StreamProcIO SP Source # 
Instance details

Defined in StreamProcIO

Methods

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

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

end :: SP i o Source #

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

Defined in SP

Methods

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

show :: SP a b -> String #

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

nullSP :: SP a b Source #

putSP :: b -> SP a b -> SP a b Source #

putsSP :: [b] -> SP a b -> SP a b Source #

getSP :: Cont (SP a b) a Source #

class StreamProcIO sp where Source #

Methods

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

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

end :: sp i o Source #

Instances

Instances details
StreamProcIO SP Source # 
Instance details

Defined in StreamProcIO

Methods

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

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

end :: SP i o Source #

StreamProcIO K Source # 
Instance details

Defined in NullF

Methods

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

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

end :: K i o Source #

StreamProcIO F Source # 
Instance details

Defined in NullF

Methods

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

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

end :: F i o Source #

runSP :: SP a1 a2 -> [a1] -> [a2] Source #

walkSP :: SP a1 a2 -> a1 -> ([a2], SP a1 a2) Source #

pullSP :: SP a1 a2 -> ([a2], SP a1 a2) Source #

Convenient stream processors

idSP :: SP b b Source #

filterSP :: (b -> Bool) -> SP b b Source #

filterLeftSP :: SP (Either b1 b2) b1 Source #

mapFilterSP :: (t -> Maybe b) -> SP t b Source #

splitSP :: SP (a, b) (Either a b) Source #

concatSP :: SP [b] b Source #

concSP :: SP [b] b Source #

mapSP :: (t -> b) -> SP t b Source #

concatMapSP :: (t -> [b]) -> SP t b Source #

concmapSP :: (t -> [b]) -> SP t b Source #

concatMapAccumlSP :: (t -> a -> (t, [b])) -> t -> SP a b Source #

mapstateSP :: (t -> a -> (t, [b])) -> t -> SP a b Source #

mapAccumlSP :: (t -> a -> (t, b)) -> t -> SP a b Source #

zipSP :: [a] -> SP b (a, b) Source #

Stream processor behaviour

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

appendStartSP :: [b] -> SP a b -> SP a b Source #

chopSP :: ((b -> SP a b) -> SP a b) -> SP a b Source #

delaySP :: SP a b -> SP a b Source #

feedSP :: a -> [a] -> SP a b -> SP a b Source #

splitAtElemSP :: (a -> Bool) -> Cont (SP a b) [a] Source #

startupSP :: [a] -> SP a b -> SP a b Source #

stepSP :: [b] -> Cont (SP a b) a Source #

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

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

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

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

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

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

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

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

System (stdio, files, network, subprocesses)

Dialogue IO

hIOF :: Request -> (Response -> F a b) -> F a b Source #

hIOSuccF :: Request -> F a b -> F a b Source #

hIOerrF :: Request -> (IOError -> F a b) -> (Response -> F a b) -> F a b Source #

haskellIOF :: Request -> (Response -> F a b) -> F a b Source #

Stdio

Subprocesses

Files and directories

appStorageF :: (Read a, Show a) => String -> a -> F a a Source #

Sockets

newtype LSocket Source #

Constructors

LSo Int 

Instances

Instances details
Eq LSocket Source # 
Instance details

Defined in Sockets

Methods

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

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

Ord LSocket Source # 
Instance details

Defined in Sockets

Read LSocket Source # 
Instance details

Defined in Sockets

Show LSocket Source # 
Instance details

Defined in Sockets

type Peer = Host Source #

type Port = Int Source #

newtype Socket Source #

Constructors

So Int 

Instances

Instances details
Eq Socket Source # 
Instance details

Defined in Sockets

Methods

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

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

Ord Socket Source # 
Instance details

Defined in Sockets

Read Socket Source # 
Instance details

Defined in Sockets

Show Socket Source # 
Instance details

Defined in Sockets

openLSocketF :: FudgetIO f => Port -> (LSocket -> f b ho) -> f b ho Source #

openSocketF :: FudgetIO f => Host -> Port -> (Socket -> f b ho) -> f b ho Source #

Timer

data Tick Source #

Constructors

Tick 

Instances

Instances details
Eq Tick Source # 
Instance details

Defined in TimerF

Methods

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

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

Show Tick Source # 
Instance details

Defined in TimerF

Methods

showsPrec :: Int -> Tick -> ShowS #

show :: Tick -> String #

showList :: [Tick] -> ShowS #

Running a fudget

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

data Fudlogue Source #

Instances

Instances details
HasCache Fudlogue Source # 
Instance details

Defined in DFudIO

Command line, environment and defaults

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

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

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

args :: [[Char]] Source #

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

Utilities for the Either type

filterLeft :: [Either b1 b2] -> [b1] Source #

filterRight :: [Either a b] -> [b] Source #

mapEither :: (t1 -> a) -> (t2 -> b) -> Either t1 t2 -> Either a b Source #

fromLeft :: Either a b -> a Source #

fromRight :: Either a b -> b Source #

plookup :: Foldable t => (a -> Bool) -> t (a, b) -> Maybe b Source #

splitEitherList :: [Either a1 a2] -> ([a1], [a2]) Source #

stripRight :: Either a1 a2 -> Maybe a2 Source #

Geometry

data Line Source #

Constructors

Line Point Point 

Instances

Instances details
Eq Line Source # 
Instance details

Defined in Geometry

Methods

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

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

Ord Line Source # 
Instance details

Defined in Geometry

Methods

compare :: Line -> Line -> Ordering #

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

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

(>) :: Line -> Line -> Bool #

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

max :: Line -> Line -> Line #

min :: Line -> Line -> Line #

Read Line Source # 
Instance details

Defined in Geometry

Show Line Source # 
Instance details

Defined in Geometry

Methods

showsPrec :: Int -> Line -> ShowS #

show :: Line -> String #

showList :: [Line] -> ShowS #

Move Line Source # 
Instance details

Defined in Geometry

Methods

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

data Point Source #

Constructors

Point 

Fields

Instances

Instances details
Eq Point Source # 
Instance details

Defined in Geometry

Methods

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

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

Num Point Source # 
Instance details

Defined in Geometry

Ord Point Source # 
Instance details

Defined in Geometry

Methods

compare :: Point -> Point -> Ordering #

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

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

(>) :: Point -> Point -> Bool #

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

max :: Point -> Point -> Point #

min :: Point -> Point -> Point #

Read Point Source # 
Instance details

Defined in Geometry

Show Point Source # 
Instance details

Defined in Geometry

Methods

showsPrec :: Int -> Point -> ShowS #

show :: Point -> String #

showList :: [Point] -> ShowS #

Ix Point Source # 
Instance details

Defined in Geometry

Move Point Source # 
Instance details

Defined in Geometry

Methods

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

data Rect Source #

Constructors

Rect 

Fields

Instances

Instances details
Eq Rect Source # 
Instance details

Defined in Geometry

Methods

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

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

Ord Rect Source # 
Instance details

Defined in Geometry

Methods

compare :: Rect -> Rect -> Ordering #

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

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

(>) :: Rect -> Rect -> Bool #

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

max :: Rect -> Rect -> Rect #

min :: Rect -> Rect -> Rect #

Read Rect Source # 
Instance details

Defined in Geometry

Show Rect Source # 
Instance details

Defined in Geometry

Methods

showsPrec :: Int -> Rect -> ShowS #

show :: Rect -> String #

showList :: [Rect] -> ShowS #

Move Rect Source # 
Instance details

Defined in Geometry

Methods

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

class Move a where Source #

Methods

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

Instances

Instances details
Move Rect Source # 
Instance details

Defined in Geometry

Methods

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

Move Line Source # 
Instance details

Defined in Geometry

Methods

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

Move Point Source # 
Instance details

Defined in Geometry

Methods

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

Move DrawCommand Source # 
Instance details

Defined in Drawcmd

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

Defined in Geometry

Methods

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

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

Defined in Geometry

Methods

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

confine :: Rect -> Rect -> Rect Source #

confine outer inner: moves an shrinks inner to fit within outer

lL :: Int -> Int -> Int -> Int -> Line Source #

pP :: Int -> Int -> Point Source #

rR :: Int -> Int -> Int -> Int -> Rect Source #

rmax :: Rect -> Rect -> Rect Source #

rmax gives an enclosing rect

scale :: (RealFrac a1, Integral b, Integral a2) => a1 -> a2 -> b Source #

Utilities

aboth :: (t -> b) -> (t, t) -> (b, b) Source #

anth :: Int -> (a -> a) -> [a] -> [a] Source #

Apply a function to the nth element of a list

gmap :: Foldable t1 => (t2 -> [a] -> [a]) -> (t3 -> t2) -> t1 t3 -> [a] Source #

issubset :: (Foldable t1, Foldable t2, Eq a) => t1 a -> t2 a -> Bool Source #

lhead :: [a1] -> [a2] -> [a2] Source #

lhead xs ys = take (length xs) ys, but the rhs is stricter

loop :: (t -> t) -> t Source #

lsplit :: [a1] -> [a2] -> ([a2], [a2]) Source #

lsplit xs ys = (lhead xs ys,ltail xs ys), but without the space leak, -fpbu

ltail :: [a1] -> [a2] -> [a2] Source #

ltail xs ys = drop (length xs) ys, but the rhs is stricter

mapPair :: (t1 -> a, t2 -> b) -> (t1, t2) -> (a, b) Source #

number :: Int -> [a] -> [(Int, a)] Source #

oo :: (t1 -> t2) -> (t3 -> t4 -> t1) -> t3 -> t4 -> t2 Source #

pair :: a -> b -> (a, b) Source #

pairwith :: (t -> b) -> t -> (t, b) Source #

part :: (a -> Bool) -> [a] -> ([a], [a]) Source #

JSP 920928

remove :: Eq t => t -> [t] -> [t] Source #

Remove the first occurence

replace :: Eq a => (a, b) -> [(a, b)] -> [(a, b)] Source #

Replace the first occurence

swap :: (b, a) -> (a, b) Source #

unionmap :: (Foldable t1, Eq a) => (t2 -> [a]) -> t1 t2 -> [a] Source #

Xlib types

data XCommand Source #

Instances

Instances details
Read XCommand Source # 
Instance details

Defined in Command

Show XCommand Source # 
Instance details

Defined in Command

data XEvent Source #

Instances

Instances details
Read XEvent Source # 
Instance details

Defined in Event

Show XEvent Source # 
Instance details

Defined in Event

data Button Source #

Constructors

AnyButton 
Button Int 

Instances

Instances details
Eq Button Source # 
Instance details

Defined in AuxTypes

Methods

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

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

Ord Button Source # 
Instance details

Defined in AuxTypes

Read Button Source # 
Instance details

Defined in AuxTypes

Show Button Source # 
Instance details

Defined in AuxTypes

data RGB Source #

Constructors

RGB Int Int Int 

Instances

Instances details
Eq RGB Source # 
Instance details

Defined in Xtypes

Methods

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

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

Ord RGB Source # 
Instance details

Defined in Xtypes

Methods

compare :: RGB -> RGB -> Ordering #

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

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

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

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

max :: RGB -> RGB -> RGB #

min :: RGB -> RGB -> RGB #

Read RGB Source # 
Instance details

Defined in Xtypes

Show RGB Source # 
Instance details

Defined in Xtypes

Methods

showsPrec :: Int -> RGB -> ShowS #

show :: RGB -> String #

showList :: [RGB] -> ShowS #

Ix RGB Source # 
Instance details

Defined in Xtypes

Methods

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

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

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

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

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

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

ColorGen RGB Source # 
Instance details

Defined in GCAttrs

Methods

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

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

data Modifiers Source #

Graphics and drawings

data CoordMode Source #

data Shape Source #

Constructors

Complex 
Nonconvex 
Convex 

Instances

Instances details
Bounded Shape Source # 
Instance details

Defined in DrawTypes

Enum Shape Source # 
Instance details

Defined in DrawTypes

Eq Shape Source # 
Instance details

Defined in DrawTypes

Methods

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

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

Ord Shape Source # 
Instance details

Defined in DrawTypes

Methods

compare :: Shape -> Shape -> Ordering #

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

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

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

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

max :: Shape -> Shape -> Shape #

min :: Shape -> Shape -> Shape #

Read Shape Source # 
Instance details

Defined in DrawTypes

Show Shape Source # 
Instance details

Defined in DrawTypes

Methods

showsPrec :: Int -> Shape -> ShowS #

show :: Shape -> String #

showList :: [Shape] -> ShowS #

data DrawCommand Source #

class Graphic a where Source #

Minimal complete definition

measureGraphicK

Instances

Instances details
Graphic Bool Source # 
Instance details

Defined in Graphic

Graphic Char Source # 
Instance details

Defined in Graphic

Graphic Double Source # 
Instance details

Defined in Graphic

Graphic Float Source # 
Instance details

Defined in Graphic

Graphic Int Source # 
Instance details

Defined in Graphic

Graphic Integer Source # 
Instance details

Defined in Graphic

Graphic MeasuredGraphics Source # 
Instance details

Defined in Graphic

Graphic PixmapImage Source # 
Instance details

Defined in PixmapGen

Graphic FlexibleDrawing Source # 
Instance details

Defined in FlexibleDrawing

Graphic ImageString Source # 
Instance details

Defined in FixedDrawing

Graphic FixedColorDrawing Source # 
Instance details

Defined in FixedDrawing

Graphic FixedDrawing Source # 
Instance details

Defined in FixedDrawing

Graphic Gfx Source # 
Instance details

Defined in DrawingUtils

Graphic BitmapFile Source # 
Instance details

Defined in BitmapDrawing

Graphic SmileyMode Source # 
Instance details

Defined in SmileyF

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

Defined in Graphic

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

Defined in Graphic

Graphic (Item a) Source # 
Instance details

Defined in MenuBarF

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

Defined in Graphic

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

Defined in Graphic

Methods

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

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

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

Defined in Drawing

Methods

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

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

data Drawing lbl leaf Source #

Constructors

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

Int=how many visible components

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

Instances

Instances details
Functor (Drawing lbl) Source # 
Instance details

Defined in Drawing

Methods

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

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

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

Defined in Drawing

Methods

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

show :: Drawing lbl leaf -> String #

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

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

Defined in Drawing

Methods

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

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

atomicD :: leaf -> Drawing lbl leaf Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

type DPath = [Int] Source #

data Gfx Source #

Instances

Instances details
Show Gfx Source # 
Instance details

Defined in DrawingUtils

Methods

showsPrec :: Int -> Gfx -> ShowS #

show :: Gfx -> String #

showList :: [Gfx] -> ShowS #

Graphic Gfx Source # 
Instance details

Defined in DrawingUtils

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

data FixedDrawing Source #

Constructors

FixD Size [DrawCommand] 

Instances

Instances details
Show FixedDrawing Source # 
Instance details

Defined in FixedDrawing

Graphic FixedDrawing Source # 
Instance details

Defined in FixedDrawing

data BitmapFile Source #

Constructors

BitmapFile String 

Instances

Instances details
Graphic BitmapFile Source # 
Instance details

Defined in BitmapDrawing

class ColorGen a where Source #

Minimal complete definition

tryConvColorK

Methods

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

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

Instances

Instances details
ColorGen Char Source # 
Instance details

Defined in GCAttrs

Methods

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

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

ColorGen RGB Source # 
Instance details

Defined in GCAttrs

Methods

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

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

ColorGen Pixel Source # 
Instance details

Defined in GCAttrs

Methods

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

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

ColorGen ColorSpec Source # 
Instance details

Defined in GCAttrs

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

Defined in GCAttrs

Methods

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

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

class FontGen a where Source #

Minimal complete definition

tryConvFontK

Methods

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

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

Instances

Instances details
FontGen Char Source # 
Instance details

Defined in GCAttrs

Methods

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

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

FontGen FontStruct Source # 
Instance details

Defined in GCAttrs

FontGen FontSpec Source # 
Instance details

Defined in GCAttrs

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

Defined in GCAttrs

Methods

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

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

data FontSpec Source #

Instances

Instances details
Show FontSpec Source # 
Instance details

Defined in GCAttrs

FontGen FontSpec Source # 
Instance details

Defined in GCAttrs

data ColorSpec Source #

Instances

Instances details
Show ColorSpec Source # 
Instance details

Defined in GCAttrs

ColorGen ColorSpec Source # 
Instance details

Defined in GCAttrs

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

data GCtx Source #

Instances

Instances details
Show GCtx Source # 
Instance details

Defined in GCtx

Methods

showsPrec :: Int -> GCtx -> ShowS #

show :: GCtx -> String #

showList :: [GCtx] -> ShowS #

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 #

data GCAttributes a b Source #

Instances

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

Defined in Xtypes

Methods

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

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

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

Defined in Xtypes

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

Defined in Xtypes

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

Defined in Xtypes

data GCFillStyle Source #

Instances

Instances details
Bounded GCFillStyle Source # 
Instance details

Defined in Xtypes

Enum GCFillStyle Source # 
Instance details

Defined in Xtypes

Eq GCFillStyle Source # 
Instance details

Defined in Xtypes

Ord GCFillStyle Source # 
Instance details

Defined in Xtypes

Read GCFillStyle Source # 
Instance details

Defined in Xtypes

Show GCFillStyle Source # 
Instance details

Defined in Xtypes

data GCCapStyle Source #

data GCLineStyle Source #

Instances

Instances details
Bounded GCLineStyle Source # 
Instance details

Defined in Xtypes

Enum GCLineStyle Source # 
Instance details

Defined in Xtypes

Eq GCLineStyle Source # 
Instance details

Defined in Xtypes

Ord GCLineStyle Source # 
Instance details

Defined in Xtypes

Read GCLineStyle Source # 
Instance details

Defined in Xtypes

Show GCLineStyle Source # 
Instance details

Defined in Xtypes

data GCFunction Source #

type Width = Int Source #

Customisation

type Customiser a = a -> a Source #

type PF p a b = F (Either (Customiser p) a) b Source #

class HasVisible xxx where Source #

Minimal complete definition

setVisible, getVisibleMaybe

Instances

Instances details
HasVisible ShellF Source # 
Instance details

Defined in DShellF

class HasFontSpec xxx where Source #

Minimal complete definition

setFontSpec, getFontSpecMaybe

Instances

Instances details
HasFontSpec TextF Source # 
Instance details

Defined in TextF

HasFontSpec ToggleButtonF Source # 
Instance details

Defined in DToggleButtonF

HasFontSpec RadioGroupF Source # 
Instance details

Defined in DRadioF

HasFontSpec StringF Source # 
Instance details

Defined in StringF

HasFontSpec EditorF Source # 
Instance details

Defined in InputEditorF

HasFontSpec (GraphicsF a) Source # 
Instance details

Defined in GraphicsF

HasFontSpec (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasFontSpec (ButtonF a) Source # 
Instance details

Defined in DButtonF

setFont :: (HasFontSpec xxx, Show a, FontGen a) => a -> Customiser xxx Source #

class HasKeys xxx where Source #

Minimal complete definition

setKeys, getKeysMaybe

class HasBgColorSpec xxx where Source #

Minimal complete definition

setBgColorSpec, getBgColorSpecMaybe

class HasFgColorSpec xxx where Source #

Minimal complete definition

setFgColorSpec, getFgColorSpecMaybe

class HasMargin xxx where Source #

Minimal complete definition

setMargin, getMarginMaybe

Instances

Instances details
HasMargin TextF Source # 
Instance details

Defined in TextF

HasMargin ShellF Source # 
Instance details

Defined in DShellF

HasMargin (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasMargin (ButtonF a) Source # 
Instance details

Defined in DButtonF

class HasCache xxx where Source #

Minimal complete definition

setCache, getCacheMaybe

Instances

Instances details
HasCache Fudlogue Source # 
Instance details

Defined in DFudIO

class HasInitSize xxx where Source #

Minimal complete definition

setInitSize, getInitSizeMaybe

Methods

setInitSize :: a -> Customiser (xxx a) Source #

getInitSizeMaybe :: xxx a -> Maybe a Source #

getInitSize :: xxx a -> a Source #

Instances

Instances details
HasInitSize GraphicsF Source # 
Instance details

Defined in GraphicsF

HasInitSize DisplayF Source # 
Instance details

Defined in DDisplayF

class HasInitDisp xxx where Source #

Minimal complete definition

setInitDisp, getInitDispMaybe

Methods

setInitDisp :: a -> Customiser (xxx a) Source #

getInitDispMaybe :: xxx a -> Maybe a Source #

getInitDisp :: xxx a -> a Source #

Instances

Instances details
HasInitDisp GraphicsF Source # 
Instance details

Defined in GraphicsF

HasInitDisp DisplayF Source # 
Instance details

Defined in DDisplayF

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

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

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

data DisplayF a Source #

Instances

Instances details
HasInitDisp DisplayF Source # 
Instance details

Defined in DDisplayF

HasInitSize DisplayF Source # 
Instance details

Defined in DDisplayF

HasSizing (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasStretchable (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasAlign (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasMargin (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasFgColorSpec (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasBgColorSpec (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasBorderWidth (DisplayF a) Source # 
Instance details

Defined in DDisplayF

HasFontSpec (DisplayF a) Source # 
Instance details

Defined in DDisplayF

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

Miscellaneous

bellF :: F ho ho Source #

Time

getTime :: FudgetIO f => (ClockTime -> f b ho) -> f b ho Source #

getLocalTime :: FudgetIO f => (CalendarTime -> f b ho) -> f b ho Source #

getCurrentTime :: FudgetIO f => (UTCTime -> f b ho) -> f b ho Source #

getZonedTime :: FudgetIO f => (ZonedTime -> f b ho) -> f b ho Source #

Debugging

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

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

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

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