data BMevents = ... data ConfirmMsg = ... data EditStop = ... data EditEvt = ... data EditCmd = ... data EDirection = ... type EditStopFn = String -> String -> EditStopChoice data EditStopChoice = ... type IsSelect = Bool data PopupMenu = ... data TextRequest a = ... data TextF class HasInitText a where ... data Sizing = ... class HasSizing a where ... type PickListRequest a = TextRequest a data Click = ... data StringF data TerminalCmd = ... data ButtonF class HasLabelInside a where ... class HasInitDisp a where ... data DisplayF appendText :: [a] -> TextRequest a border3dF :: Bool -> Int -> F a b -> F (Either Bool a) b buttonBorderF :: Int -> F a b -> F (Either Bool a) b buttonF :: (Graphic a) => a -> F Click Click buttonF' :: (Graphic a) => Customiser ButtonF -> a -> F Click Click changeText :: Int -> [a] -> TextRequest a cmdTerminalF :: FontName -> Int -> Int -> F TerminalCmd a confirmPopupF :: F [String] ([String], ConfirmMsg) deleteText :: Int -> Int -> TextRequest a displayF :: F String a displayF' :: Customiser DisplayF -> F String a doTextRequest :: [a] -> TextRequest a -> [a] editF :: FontName -> F EditCmd EditEvt editorF :: F EditCmd EditEvt filePickF :: F String (InputMsg String) highlightText :: [Int] -> TextRequest a hyperGraphicsF :: (Eq a, Graphic b) => Drawing a b -> F (Either (Drawing a b) (a, Drawing a b)) a hyperGraphicsF' :: (Eq a, Graphic b) => Bool -> Int -> ColorName -> Drawing a b -> F (Either (Drawing a b) (a, Drawing a b)) a inputPopupF :: String -> F a (InputMsg b) -> Maybe b -> F (Maybe String, Maybe a) ((Maybe String, Maybe a), b) inputPopupOptF :: String -> F a (InputMsg b) -> Maybe b -> F (Maybe String, Maybe a) ((Maybe String, Maybe a), Maybe b) insertText :: Int -> [a] -> TextRequest a intDispF :: F Int a intDispF' :: Customiser DisplayF -> F Int a intF :: F Int (InputMsg Int) intF' :: Customiser StringF -> F Int (InputMsg Int) intF'' :: Customiser StringF -> PF StringF Int (InputMsg Int) intInputF :: F Int Int labAboveF :: String -> F a b -> F a b labBelowF :: String -> F a b -> F a b labLeftOfF :: String -> F a b -> F a b labRightOfF :: String -> F a b -> F a b labelF :: String -> F a b labelF' :: Customiser DisplayF -> String -> F a b menuF :: (Graphic a, Graphic c) => a -> [(b, c)] -> F b b menuPopupF :: F a b -> F (Either PopupMenu a) b messagePopupF :: F [String] ([String], Click) moreF :: F [String] (InputMsg (Int, String)) moreF' :: (TextF -> TextF) -> F [[Char]] (InputMsg (Int, String)) moreFileF :: F String (InputMsg (Int, String)) moreFileShellF :: F String (InputMsg (Int, String)) moreShellF :: String -> F [[Char]] (InputMsg (Int, String)) moreShellF' :: (TextF -> TextF) -> String -> F [[Char]] (InputMsg (Int, String)) newline :: Char oldConfirmPopupF :: F String (String, ConfirmMsg) oldMessagePopupF :: F String (String, Click) passwdF :: F String (InputMsg String) passwdF' :: (StringF -> StringF) -> F String (InputMsg String) passwdF'' :: (StringF -> StringF) -> PF StringF String (InputMsg String) passwdInputF :: F String String passwdPopupF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), String) passwdPopupOptF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), Maybe String) pickListF :: (a -> String) -> F (PickListRequest a) (InputMsg (Int, a)) pickListF' :: (TextF -> TextF) -> (a -> String) -> F (TextRequest a) (InputMsg (Int, a)) pickText :: Int -> TextRequest a popupMenuF :: (Graphic b, Eq b) => [(a, b)] -> F c d -> F (Either [(a, b)] c) (Either a d) quitButtonF :: F Click a quitF :: F a b quitIdF :: (a -> Bool) -> F a a radioGroupF :: (Graphic b, Eq a) => [(a, b)] -> a -> F a a radioGroupF' :: (Graphic b, Eq a) => Customiser RadioGroupF -> [(a, b)] -> a -> F a a replaceAll :: [a] -> TextRequest a replaceAllFrom :: Int -> [a] -> TextRequest a replaceText :: Int -> Int -> [a] -> TextRequest a selectall :: [EditCmd] setAllowedChar :: (Char -> Bool) -> StringF -> StringF setCursorPos :: Int -> StringF -> StringF setPlacer :: Placer -> RadioGroupF -> RadioGroupF setShowString :: (String -> String) -> StringF -> StringF smallPickListF :: (a -> String) -> F [a] a stringF :: F String (InputMsg String) stringF' :: Customiser StringF -> F String (InputMsg String) stringF'' :: Customiser StringF -> PF StringF String (InputMsg String) stringInputF :: F String String stringPopupF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), String) stringPopupOptF :: String -> F (Maybe String, Maybe String) ((Maybe String, Maybe String), Maybe String) terminalF :: FontName -> Int -> Int -> F String a textF :: F (TextRequest String) (InputMsg (Int, String)) textF' :: Customiser TextF -> F (TextRequest String) (InputMsg (Int, String)) tieLabelF :: Orientation -> Alignment -> String -> F a b -> F a b toggleButtonF :: (Graphic a) => a -> F Bool Bool
type DynFMsg a b = DynMsg a (F a b) type Cont a b = (b -> a) -> a data F a b type InF a b = F a (InputMsg b) absF :: SP a b -> F a b appendStartF :: [a] -> F b a -> F b a bypassF :: F a a -> F a a concatMapF :: (a -> [b]) -> F a b contDynF :: F a b -> Cont (F a c) b delayF :: F a b -> F a b dynF :: F a b -> F (Either (F a b) a) b dynListF :: F (Int, DynFMsg a b) (Int, b) getF :: Cont (F a b) a idF :: F a a idLeftF :: F a b -> F (Either c a) (Either c b) idRightF :: F a b -> F (Either a c) (Either b c) inputDoneSP :: SP (InputMsg a) a inputLeaveDoneSP :: SP (InputMsg a) a inputListLF :: (Eq a) => Placer -> [(a, InF b c)] -> InF [(a, b)] [(a, c)] inputListSP :: (Eq a) => [a] -> SP (a, InputMsg b) (InputMsg [(a, b)]) inputPairLF :: Orientation -> InF a b -> InF c d -> InF (a, c) (b, d) inputPairSP :: SP (Either (InputMsg a) (InputMsg b)) (InputMsg (a, b)) inputThroughF :: F a (InputMsg a) -> F a (InputMsg a) listF :: (Eq a) => [(a, F b c)] -> F (a, b) (a, c) loopCompF :: F (Either (Either a b) (Either c d)) (Either (Either c e) (Either a f)) -> F (Either b d) (Either e f) loopCompSP :: SP (Either (Either a b) (Either c d)) (Either (Either c e) (Either a f)) -> SP (Either b d) (Either e f) 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 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 loopThroughRightF :: F (Either a b) (Either c d) -> F c a -> F b d mapF :: (a -> b) -> F a b mapstateF :: (a -> b -> (a, [c])) -> a -> F b c nullF :: F a b parF :: F a b -> F a b -> F a b prodF :: F a b -> F c d -> F (a, c) (Either b d) putF :: a -> F b a -> F b a putsF :: [a] -> F b a -> F b a serCompLeftToRightF :: F (Either a b) (Either b c) -> F a c serCompRightToLeftF :: F (Either a b) (Either c a) -> F b c startupF :: [a] -> F a b -> F a b stripInputSP :: SP (InputMsg a) a stubF :: F a b -> F c d throughF :: F a b -> F a (Either b a) toBothF :: F a (Either a a) untaggedListF :: [F a b] -> F a b
infixl 9 >#+< >#+< :: (F a b, Orientation) -> F c d -> F (Either a c) (Either b d) infixl 9 >#==< >#==< :: (F a b, Orientation) -> F c a -> F c b infixl 5 >*< >*< :: F a b -> F a b -> F a b infixl 5 >+< >+< :: F a b -> F c d -> F (Either a c) (Either b d) infixr 4 >==< >==< :: F a b -> F c a -> F c b infixl 6 >=^< >=^< :: F a b -> (c -> a) -> F c b infixl 6 >=^^< >=^^< :: F a b -> SP c a -> F c b infixr 7 >^=< >^=< :: (a -> b) -> F c a -> F c b infixr 7 >^^=< >^^=< :: SP a b -> F c a -> F c b
type Distance = Int type Alignment = Double data Orientation = ... data LayoutDir = ... data LayoutRequest = ... type Placer = [LayoutRequest] -> Placer2 type Placer2 = (LayoutRequest, Rect -> [Rect]) type Spacer = LayoutRequest -> Spacer2 type Spacer2 = (LayoutRequest, Rect -> Rect) type LName = String data NameLayout aBottom :: Alignment aCenter :: Alignment aLeft :: Alignment aRight :: Alignment aTop :: Alignment alignF :: Size -> Size -> Alignment -> Alignment -> F a b -> F a b autoP :: Placer barP :: Orientation -> Orientation -> Int -> Placer bottomS :: Spacer center :: Size -> Rect -> Rect center' :: Point -> Size -> Rect -> Rect centerS :: Spacer compS :: Spacer -> Spacer -> Spacer dynListLF :: Placer -> F (Int, DynFMsg a b) (Int, b) fixedh :: LayoutRequest -> Bool fixedv :: LayoutRequest -> Bool flipP :: Placer -> Placer flipPoint :: Point -> Point flipRect :: Rect -> Rect flipReq :: LayoutRequest -> LayoutRequest flipS :: Spacer -> Spacer hAlignS :: Alignment -> Spacer hBoxF :: F a b -> F a b hBoxNL :: [NameLayout] -> NameLayout hBoxNL' :: Int -> [NameLayout] -> NameLayout hCenterS :: Spacer hMarginS :: Distance -> Distance -> Spacer holeF :: F a b horizontalP :: Placer horizontalP' :: Int -> Placer hvAlignNL :: Alignment -> Alignment -> NameLayout -> NameLayout hvAlignS :: Alignment -> Alignment -> Spacer hvMarginS :: Size -> Size -> Spacer idP :: Placer idS :: Spacer layoutModifierF :: (LayoutRequest -> LayoutRequest) -> F a b -> F a b leafNL :: LName -> NameLayout leftS :: Spacer listLF :: (Eq a) => Placer -> [(a, F b c)] -> F (a, b) (a, c) listNF :: (Eq a, Show a) => [(a, F b c)] -> F (a, b) (a, c) marginF :: Distance -> F a b -> F a b marginHVAlignF :: Distance -> Alignment -> Alignment -> F a b -> F a b marginHVAlignNL :: Distance -> Alignment -> Alignment -> NameLayout -> NameLayout marginHVAlignS :: Distance -> Alignment -> Alignment -> Spacer marginNL :: Distance -> NameLayout -> NameLayout marginS :: Distance -> Spacer matrixF :: Int -> F a b -> F a b matrixP :: Int -> Placer matrixP' :: Int -> LayoutDir -> Int -> Placer maxSizeS :: Size -> Spacer minSizeS :: Size -> Spacer modNL :: (Placer -> Placer) -> NameLayout -> NameLayout nameF :: LName -> F a b -> F a b nameLayoutF :: NameLayout -> F a b -> F a b noStretchF :: Bool -> Bool -> F a b -> F a b nullLF :: F a b nullNL :: NameLayout permP :: [Int] -> ([a] -> (b, c -> [d])) -> [a] -> (b, c -> [d]) placeNL :: Placer -> [NameLayout] -> NameLayout placerF :: Placer -> F a b -> F a b rbLayoutF :: Int -> F a b -> F a b revHBoxF :: F a b -> F a b revP :: Placer -> Placer revVBoxF :: F a b -> F a b rightBelowP :: Int -> Placer rightS :: Spacer sepF :: Size -> F a b -> F a b sepNL :: Size -> NameLayout -> NameLayout sepS :: Size -> Spacer sizeS :: Size -> Spacer spaceNL :: Spacer -> NameLayout -> NameLayout spacer1F :: Spacer -> F a b -> F a b spacerF :: Spacer -> F a b -> F a b spacerP :: Spacer -> Placer -> Placer tableF :: Int -> F a b -> F a b tableP :: Int -> Placer tableP' :: Int -> LayoutDir -> Int -> Placer topS :: Spacer untaggedListLF :: Placer -> [F a b] -> F (Int, a) b vAlignS :: Alignment -> Spacer vBoxF :: F a b -> F a b vBoxNL :: [NameLayout] -> NameLayout vBoxNL' :: Int -> [NameLayout] -> NameLayout vCenterS :: Spacer vMarginS :: Distance -> Distance -> Spacer verticalP :: Placer verticalP' :: Int -> Placer
data PotRequest = ... type PotState = (Int, Int, Int) data SelCmd a = ... data SelEvt a = ... data ESelCmd a = ... data ESelEvt a = ... data ShellF class HasDeleteQuit a where ... class HasClickToType a where ... class HasVisible a where ... bubbleF :: F a b -> F a b bubblePopupF :: F a b -> F (PopupMsg a) b bubbleRootPopupF :: F a b -> F (PopupMsg a) b containerGroupF :: Rect -> Rect -> Int -> Button -> ModState -> F a b -> F (Either (Rect, Rect) a) (Either Rect b) eselectionF :: F (ESelCmd String) (ESelEvt String) hPotF :: Maybe Point -> F PotRequest (Int, Int, Int) hScrollF :: F a b -> F a b popupShellF :: String -> Maybe Point -> F a b -> F a (a, b) posPopupShellF :: String -> [WindowAttributes] -> F a b -> F (a, Maybe Point) (a, b) scrollF :: F a b -> F a b scrollShellF :: String -> (Point, Point) -> F a b -> F a b selectionF :: F (SelCmd String) (SelEvt String) shellF :: String -> F a b -> F a b shellF' :: Customiser ShellF -> String -> F a b -> F a b unmappedSimpleShellF :: String -> [WindowAttributes] -> F a b -> F a b vPotF :: Maybe Point -> F PotRequest (Int, Int, Int) vScrollF :: F a b -> F a b
allcacheF :: F a b -> F a b bitmapdatacacheF :: F a b -> F a b bitmapfilecacheF :: F a b -> F a b colorcacheF :: F a b -> F a b doubleClickF :: Time -> F a b -> F a b fontcacheF :: F a b -> F a b fontcursorcacheF :: F a b -> F a b fstructcacheF :: F a b -> F a b gCcacheF :: F a b -> F a b
data FontStruct data Gfx = ... data FixedDrawing = ... data FlexibleDrawing = ... data BitmapFile = ... data Name = ... data ColorSpec = ... data FontSpec = ... class ColorGen a where ... class FontGen a where ... type Cont a b = (b -> a) -> a data GCtx = ... class Graphic a where ... data Drawing b a = ... type DPath = [Int] arc :: Int -> Int -> FlexibleDrawing atomicD :: a -> Drawing b a attribD :: GCSpec -> Drawing a b -> Drawing a b boxD :: [Drawing a b] -> Drawing a b createGCtx :: (FontGen b, FudgetIO e, ColorGen a) => Drawable -> GCtx -> [GCAttributes a b] -> (GCtx -> e c d) -> e c d ellipse :: FlexibleDrawing fgD :: (ColorGen a) => a -> Drawing b c -> Drawing b c fgnD :: ColorName -> Drawing a b -> Drawing a b filler :: Bool -> Bool -> Int -> FlexibleDrawing fontD :: (FontGen a) => a -> Drawing b c -> Drawing b c fontnD :: FontName -> Drawing a b -> Drawing a b frame :: FlexibleDrawing frame' :: Int -> FlexibleDrawing g :: (Graphic a) => a -> Drawing b Gfx hFiller :: Int -> FlexibleDrawing hardAttribD :: GCtx -> Drawing a b -> Drawing a b hboxD :: [Drawing a b] -> Drawing a b hboxD' :: Int -> [Drawing a b] -> Drawing a b labelD :: a -> Drawing a b -> Drawing a b lbrace :: FlexibleDrawing lbrack :: FlexibleDrawing lpar :: FlexibleDrawing rbrace :: FlexibleDrawing rbrack :: FlexibleDrawing rootGCtx :: GCtx rpar :: FlexibleDrawing softAttribD :: [GCAttributes ColorSpec FontSpec] -> Drawing a b -> Drawing a b spacedD :: Spacer -> Drawing a b -> Drawing a b stackD :: [Drawing a b] -> Drawing a b tableD :: Int -> [Drawing a b] -> Drawing a b tableD' :: Int -> Int -> [Drawing a b] -> Drawing a b up :: DPath -> DPath vFiller :: Int -> FlexibleDrawing vboxD :: [Drawing a b] -> Drawing a b vboxD' :: Int -> [Drawing a b] -> Drawing a b wCreateGCtx :: (FontGen b, FudgetIO e, ColorGen a) => GCtx -> [GCAttributes a b] -> (GCtx -> e c d) -> e c d
data DynMsg b a = ... data SP a b type Cont a b = (b -> a) -> a class StreamProcIO a where ... appendStartSP :: [a] -> SP b a -> SP b a chopSP :: ((a -> SP b a) -> SP b a) -> SP b a compEitherSP :: SP a b -> SP c d -> SP (Either a c) (Either b d) concSP :: SP [a] a concatMapAccumlSP :: (a -> b -> (a, [c])) -> a -> SP b c concatMapSP :: (a -> [b]) -> SP a b concatSP :: SP [a] a concmapSP :: (a -> [b]) -> SP a b delaySP :: SP a b -> SP a b feedSP :: a -> [a] -> SP a b -> SP a b filterJustSP :: SP (Maybe a) a filterLeftSP :: SP (Either a b) a filterRightSP :: SP (Either a b) b filterSP :: (a -> Bool) -> SP a a getSP :: Cont (SP a b) a idLeftSP :: SP a b -> SP (Either c a) (Either c b) idRightSP :: SP a b -> SP (Either a c) (Either b c) idSP :: SP a a loopLeftSP :: SP (Either a b) (Either a c) -> SP b c loopSP :: SP a a -> SP a a loopThroughRightSP :: SP (Either a b) (Either c d) -> SP c a -> SP b d mapAccumlSP :: (a -> b -> (a, c)) -> a -> SP b c mapFilterSP :: (a -> Maybe b) -> SP a b mapSP :: (a -> b) -> SP a b mapstateSP :: (a -> b -> (a, [c])) -> a -> SP b c nullSP :: SP a b parSP :: SP a b -> SP a b -> SP a b postMapSP :: (a -> b) -> SP c a -> SP c b preMapSP :: SP a b -> (c -> a) -> SP c b prepostMapSP :: (a -> b) -> (c -> d) -> SP b c -> SP a d pullSP :: SP a b -> ([b], SP a b) putSP :: a -> SP b a -> SP b a putsSP :: [a] -> SP b a -> SP b a runSP :: SP a b -> [a] -> [b] seqSP :: SP a b -> SP a b -> SP a b serCompSP :: SP a b -> SP c a -> SP c b splitAtElemSP :: (a -> Bool) -> Cont (SP a b) [a] splitSP :: SP (a, b) (Either a b) startupSP :: [a] -> SP a b -> SP a b stepSP :: [a] -> Cont (SP b a) b toBothSP :: SP a (Either a a) walkSP :: SP a b -> a -> ([b], SP a b) zipSP :: [a] -> SP b (a, b)
data Tick = ... 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] openLSocketF :: Port -> (LSocket -> F a b) -> F a b openSocketF :: Host -> Port -> (Socket -> F a b) -> F a b outputF :: String -> F String a readDirF :: F String (String, Either D_IOError [String]) readFileF :: F String (String, Either D_IOError String) receiverF :: Socket -> F a String stderrF :: F String a stdinF :: F a String stdioF :: F String String stdoutF :: F String a subProcessF :: String -> F String (Either String String) timerF :: F (Maybe (Int, Int)) Tick transceiverF :: Socket -> F String String transmitterF :: Socket -> F String a
type Cont a b = (b -> a) -> a data Fudlogue class HasCache a where ... class FudgetIO a where ... cmdContSP :: a -> (b -> Maybe c) -> Cont (SP b a) c conts :: (a -> Cont b c) -> [a] -> Cont b [c] dropSP :: (a -> Maybe b) -> (b -> SP a c) -> SP a c fudlogue :: F a b -> IO () fudlogue' :: Customiser Fudlogue -> F a b -> IO () getLeftSP :: (a -> SP (Either a b) c) -> SP (Either a b) c getRightSP :: (a -> SP (Either b a) c) -> SP (Either b a) c waitForF :: (a -> Maybe b) -> Cont (F a c) b waitForSP :: (a -> Maybe b) -> (b -> SP a c) -> SP a c
data XCommand = ... data DrawCommand = ... type Path = [Direction] data Point = ... type Size = Point data Line = ... data Rect = ... data LayoutRequest data Width = ... data GCFunction = ... data GCLineStyle = ... data GCCapStyle = ... data GCFillStyle = ... data GCAttributes a b = ... data WindowAttributes = ... data Modifiers = ... data Button = ... type ModState = [Modifiers] type KeySym = String type ColorName = String type FontName = String type Time = Int data XEvent = ... data FontStruct type Port = Int type Host = String type Peer = Host type Socket = Int type LSocket = Socket =.> :: Point -> Point -> Bool 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 rectpos :: Rect -> Point rectsize :: Rect -> Size rmax :: Rect -> Rect -> Rect rsub :: Rect -> Rect -> Point scale :: (RealFrac a, Integral c, Integral b) => a -> b -> c scalePoint :: (RealFrac a) => a -> Point -> Point sizerect :: Rect -> Size -> Rect xcoord :: Point -> Int ycoord :: Point -> Int
type Fudget a b = F a b data F a b = ... data SP a b data XCommand data XEvent data Message a b = ... type Path = [Direction] data PopupMsg a = ... data InputMsg a = ... inputButtonKey :: KeySym inputDone :: InputMsg a -> Maybe a inputLeaveDone :: InputMsg a -> Maybe a inputLeaveKey :: KeySym inputMsg :: a -> InputMsg a mapInp :: (a -> b) -> InputMsg a -> InputMsg b stripInputMsg :: InputMsg a -> a tstInp :: (a -> b) -> InputMsg a -> b
data Point = ... type Size = Point data Line = ... data Rect = ... type Cont a b = (b -> a) -> a =.> :: Point -> Point -> Bool aboth :: (a -> b) -> (a, a) -> (b, b) anth :: Int -> (a -> a) -> [a] -> [a] argFlag :: [Char] -> Bool -> Bool argKey :: [Char] -> [Char] -> [Char] argReadKey :: (Read a, Show a) => [Char] -> a -> a args :: [[Char]] bgColor :: [Char] buttonFont :: FontName confine :: Rect -> Rect -> Rect defaultFont :: FontName defaultPosition :: Maybe Point defaultSep :: Int diag :: Int -> Point edgeWidth :: Int fgColor :: [Char] filterLeft :: [Either a b] -> [a] filterRight :: [Either a b] -> [b] freedom :: Rect -> Rect -> Point fromLeft :: Either a b -> a fromRight :: Either a b -> b gmap :: (a -> [b] -> [b]) -> (c -> a) -> [c] -> [b] growrect :: Rect -> Point -> Rect inRect :: Point -> Rect -> Bool isLeft :: Either a b -> Bool isM :: Maybe a -> Bool isRight :: Either a b -> Bool issubset :: (Eq a) => [a] -> [a] -> Bool lL :: Int -> Int -> Int -> Int -> Line labelFont :: FontName lhead :: [a] -> [b] -> [b] line2rect :: Line -> Rect look3d :: Bool loop :: (a -> a) -> a lsplit :: [a] -> [b] -> ([b], [b]) ltail :: [a] -> [b] -> [b] mapEither :: (a -> b) -> (c -> d) -> Either a c -> Either b d mapMaybe :: (a -> b) -> Maybe a -> Maybe b mapPair :: (a -> b, c -> d) -> (a, c) -> (b, d) mapfilter :: (a -> Maybe b) -> [a] -> [b] menuFont :: FontName moveline :: Line -> Point -> Line moverect :: Rect -> Point -> Rect number :: Int -> [a] -> [(Int, a)] oo :: (a -> b) -> (c -> d -> a) -> c -> d -> b options :: [([Char], [Char])] origin :: Point pMax :: [Point] -> Point pMin :: [Point] -> Point pP :: Int -> Int -> Point padd :: Point -> Point -> Point pair :: a -> b -> (a, b) pairwith :: (a -> b) -> a -> (a, b) paperColor :: [Char] part :: (a -> Bool) -> [a] -> ([a], [a]) plim :: Point -> Point -> Point -> Point plookup :: (a -> Bool) -> [(a, b)] -> Maybe b 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 rectpos :: Rect -> Point rectsize :: Rect -> Size remove :: (Eq a) => a -> [a] -> [a] replace :: (Eq a) => (a, b) -> [(a, b)] -> [(a, b)] rmax :: Rect -> Rect -> Rect rsub :: Rect -> Rect -> Point scale :: (RealFrac a, Integral c, Integral b) => a -> b -> c scalePoint :: (RealFrac a) => a -> Point -> Point shadowColor :: [Char] shineColor :: [Char] sizerect :: Rect -> Size -> Rect splitEitherList :: [Either a b] -> ([a], [b]) stripEither :: Either a a -> a stripLeft :: Either a b -> Maybe a stripMaybe :: Maybe a -> a stripMaybeDef :: a -> Maybe a -> a stripRight :: Either a b -> Maybe b swap :: (a, b) -> (b, a) swapEither :: Either a b -> Either b a unionmap :: (Eq b) => (a -> [b]) -> [a] -> [b] version :: String version12 :: String xcoord :: Point -> Int ycoord :: Point -> Int
ctrace :: (Show a) => [Char] -> a -> b -> b showCommandF :: String -> F a b -> F a b spyF :: (Show b, Show a) => F a b -> F a b teeF :: (a -> [Char]) -> [Char] -> F a a
type Customiser a = a -> a type PF a b c = F (Either (Customiser a) b) c class HasFont a where ... class HasTitle a where ... class HasKeys a where ... class HasWinAttr a where ... class HasBorderWidth a where ... class HasBgColor a where ... class HasFgColor a where ... class HasMargin a where ... class HasAlign a where ... class HasInitSize a where ... class HasStretchable a where ... class HasInitText a where ... class HasSizing a where ... data Sizing = ... type Alignment = Double standard :: Customiser a