| Copyright | (c) K. Luettich Rene Wagner Uni Bremen 2002-2005 | 
|---|---|
| License | GPLv2 or higher, see LICENSE.txt | 
| Maintainer | luecke@informatik.uni-bremen.de | 
| Stability | provisional | 
| Portability | non-portable (imports HTk) | 
| Safe Haskell | None | 
GUI.HTkUtils
Description
Utilities on top of HTk
Synopsis
- data LBGoalView = LBGoalView {
- statIndicator :: LBStatusIndicator
 - goalDescription :: String
 
 - data LBStatusIndicator
 - data EnableWid = forall wid.HasEnable wid => EnW wid
 - type GUIMVar = MVar (Maybe Toplevel)
 - listBox :: String -> [String] -> IO (Maybe Int)
 - errorMess :: String -> IO ()
 - confirmMess :: String -> IO Bool
 - messageMess :: String -> IO ()
 - askFileNameAndSave :: String -> String -> IO ()
 - createTextSaveDisplay :: String -> String -> String -> IO ()
 - newFileDialogStr :: String -> FilePath -> IO (Event (Maybe FilePath))
 - fileDialogStr :: String -> FilePath -> IO (Event (Maybe FilePath))
 - displayTheoryWithWarning :: String -> String -> String -> G_theory -> IO ()
 - populateGoalsListBox :: ListBox String -> [LBGoalView] -> IO ()
 - indicatorFromProofStatus :: ProofStatus a -> LBStatusIndicator
 - indicatorFromBasicProof :: BasicProof -> LBStatusIndicator
 - indicatorString :: LBStatusIndicator -> String
 - enableWids :: [EnableWid] -> IO ()
 - disableWids :: [EnableWid] -> IO ()
 - enableWidsUponSelection :: ListBox String -> [EnableWid] -> IO ()
 - when :: Applicative f => Bool -> f () -> f ()
 - try :: Exception e => IO a -> IO (Either e a)
 - forever :: Applicative f => f a -> f b
 - unless :: Applicative f => Bool -> f () -> f ()
 - newtype Event a = Event (Toggle -> (IO a -> IO ()) -> IO Result)
 - class Destroyable o where
- destroy :: o -> IO ()
 
 - class Destroyable o => Destructible o where
 - data Result
- = Immediate
 - | Awaiting (IO ())
 - | AwaitingAlways (IO ())
 
 - class HasConfig option configuration where
- ($$) :: option -> configuration -> configuration
 - configUsed :: option -> configuration -> Bool
 
 - data Channel a
 - data WithError a
 - toWithError :: Either String a -> WithError a
 - newChannel :: IO (Channel a)
 - (+>) :: Event a -> Event a -> Event a
 - (>>>) :: Event a -> IO b -> Event b
 - (>>>=) :: Event a -> (a -> IO b) -> Event b
 - allowWhile :: Event () -> Event a -> Event a
 - always :: IO a -> Event a
 - choose :: [Event a] -> Event a
 - computeEvent :: IO (Event a) -> Event a
 - doRequest :: Request a b -> a -> IO (Event b, IO ())
 - doneEvent :: a -> Event a
 - getAllQueued :: Event a -> IO [a]
 - never :: Event a
 - noWait :: Event a -> Event ()
 - poll :: Event a -> IO (Maybe a)
 - receiveIO :: HasReceive chan => chan a -> IO a
 - request :: Request a b -> a -> IO b
 - sendIO :: HasSend chan => chan a -> a -> IO ()
 - spawnEvent :: Event () -> IO (IO ())
 - sync :: Event a -> IO a
 - syncNoWait :: Event a -> IO ()
 - thenEvent :: Event a -> Event b -> Event b
 - thenGetEvent :: Event a -> (a -> Event b) -> Event b
 - tryEV :: Event a -> Event (Either SomeException a)
 - wrapAbort :: IO (Event a, IO ()) -> Event a
 - spawn :: IO () -> IO (IO ())
 - createArc :: Canvas -> [Config Arc] -> IO Arc
 - extent :: Degree -> Config Arc
 - getExtent :: Arc -> IO Degree
 - getStart :: Arc -> IO Degree
 - start :: Degree -> Config Arc
 - createBitMapItem :: Canvas -> [Config BitMapItem] -> IO BitMapItem
 - declVar :: CanvasTagOrID -> TclScript
 - declVarList :: CanvasTagOrID -> TclCmd
 - itemsNotOnSameCanvas :: IOError
 - lowerItem :: (CanvasItem ci, CanvasItem w) => ci -> w -> IO ()
 - moveItem :: (Synchronized w, CanvasItem w) => w -> Distance -> Distance -> IO ()
 - putItemAtBottom :: CanvasItem ci => ci -> IO ()
 - putItemOnTop :: CanvasItem w => w -> IO ()
 - raiseItem :: (CanvasItem ci, CanvasItem w) => ci -> w -> IO ()
 - scaleItem :: (Synchronized w, CanvasItem w) => w -> Distance -> Distance -> Double -> Double -> IO ()
 - (&#&) :: CanvasTag -> CanvasTag -> IO CanvasTag
 - (^#) :: CanvasTag -> CanvasTag -> IO CanvasTag
 - aboveItem :: CanvasItem item => item -> SearchSpec
 - addCanvasTag :: SearchSpec -> CanvasTag -> IO ()
 - allItems :: SearchSpec
 - belowItem :: CanvasItem item => item -> SearchSpec
 - closest :: Position -> SearchSpec
 - createCanvasTag :: Canvas -> [Config CanvasTag] -> IO CanvasTag
 - enclosed :: Position -> Position -> SearchSpec
 - overlapping :: Position -> Position -> SearchSpec
 - removeCanvasTag :: CanvasItem i => i -> CanvasTag -> IO ()
 - tagNot :: CanvasTag -> IO CanvasTag
 - withTag :: CanvasItem item => item -> SearchSpec
 - (|#|) :: CanvasTag -> CanvasTag -> IO CanvasTag
 - createEmbeddedCanvasWin :: Widget w => Canvas -> w -> [Config EmbeddedCanvasWin] -> IO EmbeddedCanvasWin
 - createImageItem :: Canvas -> [Config ImageItem] -> IO ImageItem
 - arrowshape :: ArrowShape -> Config Line
 - arrowstyle :: ArrowHead -> Config Line
 - capstyle :: CapStyle -> Config Line
 - createLine :: Canvas -> [Config Line] -> IO Line
 - getArrowshape :: Line -> IO ArrowShape
 - getArrowstyle :: Line -> IO ArrowHead
 - getCapstyle :: Line -> IO CapStyle
 - getJoinstyle :: Line -> IO JoinStyle
 - joinstyle :: JoinStyle -> Config Line
 - createOval :: Canvas -> [Config Oval] -> IO Oval
 - createPolygon :: Canvas -> [Config Polygon] -> IO Polygon
 - createRectangle :: Canvas -> [Config Rectangle] -> IO Rectangle
 - createTextItem :: Canvas -> [Config TextItem] -> IO TextItem
 - errmap :: BitMapHandle
 - getBitMapHandle :: GUIObject w => w -> ConfigID -> IO BitMapHandle
 - gray25 :: BitMapHandle
 - gray50 :: BitMapHandle
 - hourglass :: BitMapHandle
 - info :: BitMapHandle
 - newBitMap :: [Config BitMap] -> IO BitMap
 - questhead :: BitMapHandle
 - question :: BitMapHandle
 - setBitMapHandle :: GUIObject w => w -> ConfigID -> BitMapHandle -> Bool -> IO w
 - stringToBitMapHandle :: String -> IO BitMapHandle
 - warning :: BitMapHandle
 - focusModel :: Window w => FocusModel -> Config w
 - forceFocus :: Widget w => w -> IO ()
 - getCurrentGrab :: IO (Maybe CurrentGrab)
 - getFocus :: Window w => w -> IO (Maybe CurrentFocus)
 - getFocusModel :: Window w => w -> IO FocusModel
 - getGrabStatus :: Widget w => w -> IO (Maybe GrabStatus)
 - getRecentFocus :: Window w => w -> IO (Maybe CurrentFocus)
 - grabGlobal :: Widget w => w -> IO ()
 - grabLocal :: Widget w => w -> IO ()
 - releaseGrab :: Widget w => w -> IO ()
 - returnGrab :: Maybe CurrentGrab -> IO ()
 - setFocus :: Widget w => w -> IO ()
 - getIconMask :: Window w => Icon w -> IO BitMapHandle
 - iconMask :: (Window w, BitMapDesignator h) => h -> Config (Icon w)
 - imageToInt :: Image -> IO Int
 - imgData :: Format -> String -> Config Image
 - imgGamma :: Double -> Config Image
 - imgPalette :: PaletteSpec p => p -> Config Image
 - intToImage :: Int -> IO (Maybe Image)
 - newImage :: [Config Image] -> IO Image
 - newBox :: Container par => par -> Flexibility -> [Config Box] -> IO Box
 - newHBox :: Container par => par -> [Config Box] -> IO Box
 - newHFBox :: Container par => par -> [Config Box] -> IO Box
 - newVBox :: Container par => par -> [Config Box] -> IO Box
 - newVFBox :: Container par => par -> [Config Box] -> IO Box
 - newFrame :: Container par => par -> [Config Frame] -> IO Frame
 - createToplevel :: [Config Toplevel] -> IO Toplevel
 - tkGetToplevelConfig :: ObjectName -> ConfigID -> TclScript
 - tkSetToplevelConfigs :: ObjectName -> [ConfigOption] -> TclScript
 - getMaxSize :: Window w => w -> IO Size
 - getMinSize :: Window w => w -> IO Size
 - isWMConfig :: ConfigID -> Bool
 - lowerWin :: (Window w1, Window w2) => w1 -> w2 -> IO ()
 - maxSize :: Window w => Size -> Config w
 - minSize :: Window w => Size -> Config w
 - raiseWin :: (Window w1, Window w2) => w1 -> w2 -> IO ()
 - bell :: IO ()
 - ringBell :: Window w => Maybe w -> IO ()
 - colourmode :: ColourMode -> CreationConfig PostScript
 - pageAnchor :: Anchor -> CreationConfig PostScript
 - pageheight :: Distance -> CreationConfig PostScript
 - pagewidth :: Distance -> CreationConfig PostScript
 - pagex :: Distance -> CreationConfig PostScript
 - pagey :: Distance -> CreationConfig PostScript
 - psfile :: String -> CreationConfig PostScript
 - psheight :: Distance -> CreationConfig PostScript
 - pssize :: Size -> CreationConfig PostScript
 - pswidth :: Distance -> CreationConfig PostScript
 - rotate :: Bool -> CreationConfig PostScript
 - getScreenHeight :: Window a => Screen a -> IO Distance
 - getScreenManager :: Window a => Screen a -> IO String
 - getScreenVisual :: Window a => Screen a -> IO VisualClass
 - getScreenWidth :: Window a => Screen a -> IO Distance
 - buttonColours :: HasColour w => w -> ConfigID -> Bool
 - activeBackground :: (ColourDesignator c, HasColour w) => c -> Config w
 - activeForeground :: (ColourDesignator c, HasColour w) => c -> Config w
 - background :: (ColourDesignator c, HasColour w) => c -> Config w
 - bg :: (ColourDesignator c, HasColour w) => c -> Config w
 - disabledForeground :: (ColourDesignator c, HasColour w) => c -> Config w
 - fg :: (ColourDesignator c, HasColour w) => c -> Config w
 - foreground :: (ColourDesignator c, HasColour w) => c -> Config w
 - getActiveBackground :: HasColour w => w -> IO Colour
 - getActiveForeground :: HasColour w => w -> IO Colour
 - getBackground :: HasColour w => w -> IO Colour
 - getDisabledForeground :: HasColour w => w -> IO Colour
 - getForeground :: HasColour w => w -> IO Colour
 - hasBackGroundColour :: HasColour w => w -> ConfigID -> Bool
 - hasForeGroundColour :: HasColour w => w -> ConfigID -> Bool
 - bind :: GUIObject wid => wid -> [WishEvent] -> IO (Event EventInfo, IO ())
 - bindPath :: Widget wid => wid -> [WishEvent] -> IO (Event EventInfo, IO ())
 - bindPathSimple :: Widget wid => wid -> WishEventType -> IO (Event (), IO ())
 - bindSimple :: GUIObject wid => wid -> WishEventType -> IO (Event (), IO ())
 - arrow :: Cursor
 - circle :: Cursor
 - clock :: Cursor
 - diamondCross :: Cursor
 - dot :: Cursor
 - drapedBox :: Cursor
 - exchange :: Cursor
 - fleur :: Cursor
 - gobbler :: Cursor
 - gumby :: Cursor
 - hand1 :: Cursor
 - hand2 :: Cursor
 - pencil :: Cursor
 - plus :: Cursor
 - spraycan :: Cursor
 - tcross :: Cursor
 - watch :: Cursor
 - xterm :: Cursor
 - addEventInfoSet :: EventInfoSet -> [EventParameter] -> EventInfoSet
 - defaultEventInfoSet :: EventInfoSet
 - delEventInfoSet :: EventInfoSet -> [EventParameter] -> EventInfoSet
 - emptyEventInfoSet :: EventInfoSet
 - epFromChar :: Char -> EventParameter
 - epToChar :: EventParameter -> Char
 - listEventInfoSet :: EventInfoSet -> [EventParameter]
 - mkEventInfo :: [(EventParameter, String)] -> EventInfo
 - mkEventInfoSet :: [EventParameter] -> EventInfoSet
 - xfont :: XFont
 - creadTk :: GUIValue a => String -> IO a
 - delimitString :: String -> String
 - escapeString :: String -> String
 - illegalGUIValue :: IOError
 - toTkString :: String -> String
 - cm :: Double -> Distance
 - ic :: Double -> Distance
 - mm :: Double -> Distance
 - pp :: Double -> Distance
 - tocm :: Distance -> Double
 - toinch :: Distance -> Double
 - showGridPackOptions :: [GridPackOption] -> String
 - showPackOptions :: [PackOption] -> String
 - grid :: Widget w => w -> [GridPackOption] -> IO ()
 - pack :: Widget w => w -> [PackOption] -> IO ()
 - showCreationConfigs :: [CreationConfig a] -> IO String
 - toggle :: Toggle -> Toggle
 - createTkVariable :: GUIValue a => a -> IO (TkVariable a)
 - readTkVariable :: GUIValue a => TkVariable a -> IO a
 - setTkVariable :: GUIValue a => TkVariable a -> a -> IO ()
 - cleanupWish :: IO ()
 - delayWish :: IO a -> IO a
 - forgetPackage :: String -> IO ()
 - isPackageAvailable :: String -> IO Bool
 - isTixAvailable :: IO Bool
 - requirePackage :: String -> IO Bool
 - createMenu :: GUIObject par => par -> Bool -> [Config Menu] -> IO Menu
 - popup :: GUIObject i => Menu -> Position -> Maybe i -> IO ()
 - post :: Menu -> Position -> IO ()
 - unpost :: Menu -> IO ()
 - createMenuCascade :: Menu -> [Config MenuCascade] -> IO MenuCascade
 - createPulldownMenu :: Menu -> [Config MenuCascade] -> IO Menu
 - createMenuCheckButton :: Menu -> [Config MenuCheckButton] -> IO MenuCheckButton
 - createMenuCommand :: Menu -> [Config MenuCommand] -> IO MenuCommand
 - createMenuRadioButton :: Menu -> [Config MenuRadioButton] -> IO MenuRadioButton
 - createMenuSeparator :: Menu -> [Config MenuSeparator] -> IO MenuSeparator
 - createEmbeddedTextWin :: (HasIndex Editor i BaseIndex, Widget w) => Editor -> i -> w -> [Config EmbeddedTextWin] -> IO EmbeddedTextWin
 - getStretch :: EmbeddedTextWin -> IO Toggle
 - stretch :: Toggle -> Config EmbeddedTextWin
 - createMark :: HasIndex Editor i BaseIndex => Editor -> String -> i -> IO Mark
 - getCurrentMarks :: Editor -> IO [Mark]
 - setMark :: HasIndex Editor i BaseIndex => Mark -> i -> IO ()
 - setMarkGravity :: Mark -> Gravity -> IO ()
 - unsetMark :: Mark -> IO ()
 - addTextTag :: (HasIndex Editor i1 BaseIndex, HasIndex Editor i2 BaseIndex) => TextTag -> i1 -> i2 -> IO ()
 - bgstipple :: BitMapHandle -> Config TextTag
 - createTextTag :: (HasIndex Editor i1 BaseIndex, HasIndex Editor i2 BaseIndex) => Editor -> i1 -> i2 -> [Config TextTag] -> IO TextTag
 - fgstipple :: BitMapHandle -> Config TextTag
 - getBgstipple :: TextTag -> IO BitMapHandle
 - getFgstipple :: TextTag -> IO BitMapHandle
 - getLmargin1 :: TextTag -> IO Distance
 - getLmargin2 :: TextTag -> IO Distance
 - getOffset :: TextTag -> IO Distance
 - getOverstrike :: TextTag -> IO Toggle
 - getRmargin :: TextTag -> IO Distance
 - getUnderlined :: TextTag -> IO Toggle
 - lmargin1 :: Distance -> Config TextTag
 - lmargin2 :: Distance -> Config TextTag
 - lowerTextTag :: TextTag -> IO ()
 - offset :: Distance -> Config TextTag
 - overstrike :: Toggle -> Config TextTag
 - raiseTextTag :: TextTag -> IO ()
 - removeTextTag :: (HasIndex Editor i1 BaseIndex, HasIndex Editor i2 BaseIndex) => TextTag -> i1 -> i2 -> IO ()
 - rmargin :: Distance -> Config TextTag
 - underlined :: Toggle -> Config TextTag
 - getLabelSide :: LabelFrame -> IO LabelSide
 - labelSide :: LabelSide -> Config LabelFrame
 - newLabelFrame :: Container par => par -> [Config LabelFrame] -> IO LabelFrame
 - createNoteBookPage :: NoteBook -> String -> [Config NoteBookPage] -> IO NoteBookPage
 - newNoteBook :: Container par => par -> [Config NoteBook] -> IO NoteBook
 - after :: Pane -> CreationConfig Pane
 - at :: Int -> CreationConfig Pane
 - before :: Pane -> CreationConfig Pane
 - createPane :: PanedWindow -> [CreationConfig Pane] -> [Config Pane] -> IO Pane
 - expand :: Double -> CreationConfig Pane
 - initsize :: Int -> CreationConfig Pane
 - maxsize :: Int -> CreationConfig Pane
 - minsize :: Int -> CreationConfig Pane
 - newPanedWindow :: Container par => par -> Orientation -> [Config PanedWindow] -> IO PanedWindow
 - finishHTk :: IO ()
 - getHTk :: IO HTk
 - initHTk :: [Config HTk] -> IO HTk
 - resourceFile :: String -> Config HTk
 - updateAllTasks :: IO ()
 - updateIdleTasks :: IO ()
 - withdrawMainWin :: Config HTk
 - withdrawWish :: IO ()
 - newButton :: Container par => par -> [Config Button] -> IO Button
 - closeEnough :: Double -> Canvas -> IO Canvas
 - confine :: Bool -> Canvas -> IO Canvas
 - getCloseEnough :: Canvas -> IO Double
 - getConfine :: Canvas -> IO Bool
 - getScrollRegion :: Canvas -> IO ScrollRegion
 - newCanvas :: Container par => par -> [Config Canvas] -> IO Canvas
 - screenToCanvasCoord :: Canvas -> Orientation -> Distance -> Maybe Distance -> IO Distance
 - scrollIncrement :: Orientation -> Distance -> Canvas -> IO Canvas
 - scrollRegion :: ScrollRegion -> Canvas -> IO Canvas
 - newCheckButton :: Container par => par -> [Config (CheckButton a)] -> IO (CheckButton a)
 - entrySubwidget :: GUIValue a => ComboBox a -> Entry a
 - listBoxSubwidget :: GUIValue a => ComboBox a -> ListBox a
 - newComboBox :: (GUIValue a, Container par) => par -> Bool -> [Config (ComboBox a)] -> IO (ComboBox a)
 - pick :: GUIValue a => Int -> Config (ComboBox a)
 - adjustViewTo :: HasIndex Editor i BaseIndex => Editor -> i -> IO ()
 - appendText :: Editor -> String -> IO ()
 - compareIndices :: (HasIndex Editor i1 BaseIndex, HasIndex Editor i2 BaseIndex) => Editor -> String -> i1 -> i2 -> IO Bool
 - deleteText :: HasIndex Editor i BaseIndex => Editor -> i -> IO ()
 - deleteTextRange :: (HasIndex Editor i1 BaseIndex, HasIndex Editor i2 BaseIndex) => Editor -> i1 -> i2 -> IO ()
 - getIndexPosition :: HasIndex Editor i BaseIndex => Editor -> i -> IO Position
 - getTextLine :: HasIndex Editor i BaseIndex => Editor -> i -> IO String
 - getTextRange :: (HasIndex Editor i1 BaseIndex, HasIndex Editor i2 BaseIndex) => Editor -> i1 -> i2 -> IO String
 - getWrapMode :: Editor -> IO WrapMode
 - insertNewline :: Editor -> IO ()
 - insertText :: (HasIndex Editor i BaseIndex, GUIValue a) => Editor -> i -> a -> IO ()
 - newEditor :: Container par => par -> [Config Editor] -> IO Editor
 - readTextFromFile :: Editor -> FilePath -> IO ()
 - scanDragTo :: HasIndex Editor i BaseIndex => Editor -> i -> IO ()
 - scanMark :: HasIndex Editor i BaseIndex => Editor -> i -> IO ()
 - search :: HasIndex Editor i BaseIndex => Editor -> SearchSwitch -> String -> i -> IO (Maybe BaseIndex)
 - wrap :: WrapMode -> Config Editor
 - writeTextToFile :: Editor -> FilePath -> IO ()
 - getShowText :: GUIValue a => Entry a -> IO Char
 - newEntry :: (Container par, GUIValue a) => par -> [Config (Entry a)] -> IO (Entry a)
 - showText :: GUIValue a => Char -> Entry a -> IO (Entry a)
 - newLabel :: Container par => par -> [Config Label] -> IO Label
 - activateElem :: HasIndex (ListBox a) i Int => ListBox a -> i -> IO ()
 - elemNotFound :: IOError
 - getSelectMode :: GUIValue a => ListBox a -> IO SelectMode
 - newListBox :: (Container par, GUIValue a) => par -> [Config (ListBox a)] -> IO (ListBox a)
 - selectMode :: GUIValue a => SelectMode -> ListBox a -> IO (ListBox a)
 - selectionAnchor :: HasIndex (ListBox a) i Int => ListBox a -> i -> IO ()
 - newMenuButton :: Container par => par -> [Config MenuButton] -> IO MenuButton
 - aspect :: Int -> Config Message
 - getAspect :: Message -> IO Int
 - newMessage :: Container par => par -> [Config Message] -> IO Message
 - newOptionMenu :: (Container par, GUIValue a) => par -> [a] -> [Config (OptionMenu a)] -> IO (OptionMenu a)
 - newRadioButton :: Container par => par -> [Config (RadioButton a)] -> IO (RadioButton a)
 - bigIncrement :: ScaleValue a => a -> Config (Slider (Scale a))
 - digits :: Int -> Config (Scale a)
 - getBigIncrement :: ScaleValue a => Slider (Scale a) -> IO a
 - getDigits :: Scale a -> IO Int
 - getInterval :: ScaleValue a => Scale a -> IO (a, a)
 - getIntervalFrom :: ScaleValue a => Scale a -> IO a
 - getIntervalTo :: ScaleValue a => Scale a -> IO a
 - getShowValue :: Slider (Scale a) -> IO Toggle
 - interval :: ScaleValue a => (a, a) -> Config (Scale a)
 - intervalFrom :: ScaleValue a => a -> Config (Scale a)
 - intervalTo :: ScaleValue a => a -> Config (Scale a)
 - newScale :: (GUIValue a, ScaleValue a, Container par) => par -> [Config (Scale a)] -> IO (Scale a)
 - showValue :: Toggle -> Config (Slider (Scale a))
 - activateScrollBarElem :: ScrollBar -> ScrollBarElem -> IO ()
 - fraction :: ScrollBar -> Position -> IO Fraction
 - getActivatedElem :: ScrollBar -> IO (Maybe ScrollBarElem)
 - identify :: ScrollBar -> Position -> IO (Maybe ScrollBarElem)
 - newScrollBar :: Container par => par -> [Config ScrollBar] -> IO ScrollBar
 - setView :: ScrollBar -> Fraction -> Fraction -> IO ()
 - (#) :: a -> (a -> b) -> b
 - coerceWithError :: WithError a -> a
 - coerceWithErrorIO :: WithError a -> IO a
 - coerceWithErrorOrBreak :: (String -> a) -> WithError a -> a
 - coerceWithErrorOrBreakIO :: (String -> a) -> WithError a -> IO a
 - coerceWithErrorOrBreakIOPrefix :: String -> (String -> a) -> WithError a -> IO a
 - coerceWithErrorOrBreakPrefix :: String -> (String -> a) -> WithError a -> a
 - coerceWithErrorStringIO :: String -> WithError a -> IO a
 - concatWithError :: [WithError a] -> WithError [a]
 - config :: IO () -> Config w
 - configure :: w -> [Config w] -> IO w
 - done :: Monad m => m ()
 - exceptionToError :: Exception e => (e -> Maybe String) -> IO a -> IO (WithError a)
 - foreach :: Monad m => [a] -> (a -> m b) -> m ()
 - foreverUntil :: Monad m => m Bool -> m ()
 - fromWithError :: WithError a -> Either String a
 - fromWithError1 :: a -> WithError a -> a
 - hasError :: String -> WithError a
 - hasValue :: a -> WithError a
 - incase :: Maybe a -> (a -> IO b) -> IO ()
 - isError :: WithError a -> Bool
 - listWithError :: [WithError a] -> WithError [a]
 - mapWithError :: (a -> b) -> WithError a -> WithError b
 - mapWithError' :: (a -> WithError b) -> WithError a -> WithError b
 - mapWithErrorIO :: (a -> IO b) -> WithError a -> IO (WithError b)
 - mapWithErrorIO' :: (a -> IO (WithError b)) -> WithError a -> IO (WithError b)
 - monadifyWithError :: forall (m :: Type -> Type) a. Monad m => WithError a -> MonadWithError m a
 - pairWithError :: WithError a -> WithError b -> WithError (a, b)
 - propagate :: Answer a -> IO a
 - raise :: IOError -> IO a
 - swapIOWithError :: WithError (IO a) -> IO (WithError a)
 - toMonadWithError :: Monad m => m a -> MonadWithError m a
 - tryUntilOK :: IO a -> IO a
 - while :: Monad m => m a -> (a -> Bool) -> m a
 - class HasEvent (eventType :: Type -> Type) where
 - class HasReceive (chan :: Type -> Type) where
 - class HasSend (chan :: Type -> Type) where
 - data Request a b = Request (a -> IO (Event b, IO ()))
 - class Synchronized a where
- synchronize :: a -> IO b -> IO b
 
 - data Arc
 - data BitMapItem
 - class GUIObject w => CanvasItem w
 - class CanvasItem w => FilledCanvasItem w where
- filling :: ColourDesignator c => c -> Config w
 - getFilling :: w -> IO Colour
 - outline :: ColourDesignator c => c -> Config w
 - getOutline :: w -> IO Colour
 - stipple :: BitMapHandle -> Config w
 - getStipple :: w -> IO BitMapHandle
 - outlinewidth :: Distance -> Config w
 - getOutlineWidth :: w -> IO Distance
 
 - class HasCoords w where
 - class CanvasItem w => SegmentedCanvasItem w where
- splinesteps :: Int -> Config w
 - getSplinesteps :: w -> IO Int
 - smooth :: Bool -> Config w
 - getSmooth :: w -> IO Bool
 
 - data CanvasTag
 - data SearchSpec
 - class CanvasItem w => TaggedCanvasItem w where
 - data EmbeddedCanvasWin
 - data ImageItem
 - data ArrowHead
 - data CapStyle
 - data JoinStyle
 - data Line
 - data Oval
 - data Polygon
 - data Rectangle
 - data TextItem
 - data BitMap
 - class BitMapDesignator d where
- toBitMap :: d -> BitMapHandle
 
 - data BitMapHandle
- = Predefined String
 - | BitMapHandle BitMap
 - | BitMapFile String
 
 - class GUIObject w => HasBitMap w where
- bitmap :: BitMapDesignator d => d -> Config w
 - getBitMap :: w -> IO BitMapHandle
 
 - data CurrentFocus
 - data CurrentGrab = CurrentGrab GUIOBJECT
 - data FocusModel
 - data GrabStatus
 - data Window w => Icon w = Icon w
 - data Format
 - class GUIObject w => HasPhoto w where
 - data Image
 - data BaseIndex
 - data EndOfText = EndOfText
 - data First = First
 - class HasIndex w i b where
- getBaseIndex :: w -> i -> IO b
 
 - data Last = Last
 - data Pixels = Pixels Distance Distance
 - class GUIObject w => HasSelection w where
- clearSelection :: w -> IO ()
 
 - class HasSelectionBaseIndex w i where
- getSelection :: w -> IO (Maybe i)
 
 - class HasSelectionIndex w i => HasSelectionBaseIndexRange w i where
- getSelectionStart :: w -> IO (Maybe i)
 - getSelectionEnd :: w -> IO (Maybe i)
 - getSelectionRange :: w -> IO (Maybe (i, i))
 
 - class HasSelectionIndex w i where
- selection :: i -> Config w
 - isSelected :: w -> i -> IO Bool
 
 - class HasSelectionIndexRange w i1 i2 where
- selectionRange :: i1 -> i2 -> Config w
 
 - newtype Selection w = Selection w
 - class Widget w => HasSlider w where
- repeatInterval :: Int -> Config (Slider w)
 - getRepeatInterval :: Slider w -> IO Int
 - repeatDelay :: Int -> Config (Slider w)
 - getRepeatDelay :: Slider w -> IO Int
 
 - newtype Slider w = Slider w
 - data Box
 - data Frame
 - newtype Toplevel = Toplevel GUIOBJECT
 - data AspectRatio
 - type Display = String
 - data Whom
 - class GUIObject w => Window w where
- iconify :: w -> IO ()
 - deiconify :: w -> IO ()
 - withdraw :: w -> IO ()
 - putWinOnTop :: w -> IO ()
 - putWinAtBottom :: w -> IO ()
 - screen :: Display -> Config w
 - getScreen :: w -> IO Display
 - getClassName :: w -> IO String
 - getWindowState :: w -> IO WindowState
 - aspectRatio :: AspectRatio -> Config w
 - getAspectRatio :: w -> IO AspectRatio
 - positionFrom :: Whom -> Config w
 - getPositionFrom :: w -> IO Whom
 - sizeFrom :: Whom -> Config w
 - getSizeFrom :: w -> IO Whom
 
 - data WindowState
 - data ColourMode
 - class GUIObject w => HasPostscript w where
- postscript :: w -> [CreationConfig PostScript] -> IO ()
 
 - data PostScript
 - newtype Screen w = Screen w
 - data VisualClass
 - class GUIObject w => Widget w where
- cursor :: CursorDesignator ch => ch -> Config w
 - getCursor :: w -> IO Cursor
 - takeFocus :: Bool -> Config w
 - getTakeFocus :: w -> IO Bool
 
 - class Widget w => ButtonWidget w where
 - newtype Colour = Colour String
 - class ColourDesignator c where
 - class GUIObject w => HasAlign w where
 - class GUIObject w => HasAnchor w where
 - class GUIObject w => HasBBox w i where
 - class GUIObject w => HasBorder w where
- borderwidth :: Distance -> Config w
 - getBorderwidth :: w -> IO Distance
 - relief :: Relief -> Config w
 - getRelief :: w -> IO Relief
 
 - class GUIObject w => HasCanvAnchor w where
- canvAnchor :: Anchor -> Config w
 - getCanvAnchor :: w -> IO Anchor
 
 - class GUIObject w => HasColour w where
- legalColourID :: w -> ConfigID -> Bool
 - setColour :: w -> ConfigID -> Colour -> IO w
 - getColour :: w -> ConfigID -> IO Colour
 
 - class GUIObject w => HasEnable w where
 - class GUIObject w => HasFile w where
- filename :: String -> Config w
 - getFileName :: w -> IO String
 
 - class GUIObject w => HasFont w where
- font :: FontDesignator f => f -> Config w
 - getFont :: w -> IO Font
 
 - class (HasSize w, HasPosition w) => HasGeometry w where
- geometry :: Geometry -> Config w
 - getGeometry :: w -> IO Geometry
 
 - class GUIObject w => HasGrid w where
 - class HasIncrement w a where
- increment :: a -> Config w
 - getIncrement :: w -> IO a
 
 - class GUIObject w => HasJustify w where
- justify :: Justify -> Config w
 - getJustify :: w -> IO Justify
 
 - class GUIObject w => HasOrientation w where
- orient :: Orientation -> Config w
 - getOrient :: w -> IO Orientation
 
 - class GUIObject w => HasPosition w where
- position :: Position -> Config w
 - getPosition :: w -> IO Position
 
 - class GUIObject w => HasSize w where
 - class (GUIObject w, GUIValue v) => HasText w v where
 - class GUIObject w => HasUnderline w where
- underline :: Int -> Config w
 - getUnderline :: w -> IO Int
 - wraplength :: Int -> Config w
 - getWraplength :: w -> IO Int
 
 - class (GUIObject w, GUIValue v) => HasValue w v where
 - class GUIObject w => HasCommand w where
 - data BCursor = BCursor String (Maybe String) Colour (Maybe Colour)
 - newtype Cursor = Cursor String
 - class CursorDesignator ch where
 - data XCursor = XCursor String (Maybe Colour) (Maybe Colour)
 - data EventInfo = EventInfo Distance Distance Distance Distance Int
 - data EventInfoSet
 - data EventParameter
 - newtype Font = Font String
 - class FontDesignator fh where
 - data FontFamily
 - data FontSlant
 - data FontSpacing
 - data FontWeight
- = NormalWeight
 - | Medium
 - | Bold
 
 - data FontWidth
 - data XFont
- = XFont { }
 - | XFontAlias String
 
 - data GUIVALUE = GUIVALUE Generator String
 - class (Show a, Read a) => GUIValue a where
- cdefault :: a
 - toGUIValue :: a -> GUIVALUE
 - maybeGUIValue :: GUIVALUE -> Maybe a
 - fromGUIValue :: GUIVALUE -> a
 
 - data Generator
 - newtype RawData = RawData String
 - newtype TkCommand = TkCommand String
 - type Coord = [Position]
 - newtype Distance = Distance Int
 - type Geometry = (Distance, Distance, Distance, Distance)
 - type Position = (Distance, Distance)
 - type Size = (Distance, Distance)
 - data GridPackOption
 - data StickyKind
 - data FillSpec
 - data PackOption
 - data SideSpec
 - data AbstractWidget = NONE
 - class GUIObject a => Container a
 - data Alignment
 - data Anchor
 - type CreationConfig w = IO String
 - data Flexibility
 - data Justify
 - data Orientation
 - data Relief
 - data State
 - data Toggle
 - class GUIObject w => HasVariable w where
- variable :: TkVariable v -> Config w
 
 - newtype GUIValue a => TkVariable a = TkVariable ObjectID
 - class GUIObject w => HasTooltip w where
- tooltip :: String -> w -> IO w
 - destroyTooltip :: w -> IO ()
 
 - newtype KeySym = KeySym String
 - data WishEvent = WishEvent [WishEventModifier] WishEventType
 - data WishEventModifier
 - data WishEventType
- = Activate
 - | ButtonPress (Maybe BNo)
 - | ButtonRelease (Maybe BNo)
 - | Circulate
 - | Colormap
 - | Configure
 - | Deactivate
 - | Destroy
 - | Enter
 - | Expose
 - | FocusIn
 - | FocusOut
 - | Gravity
 - | KeyPress (Maybe KeySym)
 - | KeyRelease (Maybe KeySym)
 - | Motion
 - | Leave
 - | Map
 - | Property
 - | Reparent
 - | Unmap
 - | Visibility
 
 - class GUIObject w => HasMenu w where
 - data Menu = Menu GUIOBJECT (Ref Int)
 - data MenuCascade
 - data MenuCheckButton
 - data MenuCommand
 - data MenuRadioButton
 - data MenuSeparator
 - data EmbeddedTextWin
 - data Gravity
 - data Mark = Mark Editor String
 - data TextTag
 - data LabelFrame
 - data LabelSide
 - data NoteBook
 - data NoteBookPage
 - data Pane
 - data PanedWindow
 - data HTk
 - data Button
 - data Canvas
 - type ScrollRegion = (Position, Position)
 - data CheckButton a
 - data GUIValue a => ComboBox a
 - data Editor
 - class GUIObject w => HasLineSpacing w where
- spaceAbove :: Distance -> Config w
 - getSpaceAbove :: w -> IO Distance
 - spaceWrap :: Distance -> Config w
 - getSpaceWrap :: w -> IO Distance
 - spaceBelow :: Distance -> Config w
 - getSpaceBelow :: w -> IO Distance
 
 - class GUIObject w => HasTabulators w where
 - data IndexModifier
- = ForwardChars Int
 - | BackwardChars Int
 - | ForwardLines Int
 - | BackwardLines Int
 - | LineStart
 - | LineEnd
 - | WordStart
 - | WordEnd
 
 - newtype IndexModifiers = IndexModifiers [IndexModifier]
 - data SearchDirection
 - data SearchMode
 - data SearchSwitch = SearchSwitch {
- searchdirection :: SearchDirection
 - searchmode :: SearchMode
 - rexexp :: Bool
 
 - data WrapMode
 - data Entry a
 - data XCoord = XCoord Distance
 - data Label
 - data ListBox a
 - data Eq a => ListBoxElem a = ListBoxElem a
 - data SelectMode
 - data MenuButton
 - data Message
 - data OptionMenu a
 - data RadioButton a
 - data Scale a
 - class (Num a, GUIValue a) => ScaleValue a where
- toDouble :: a -> Double
 - fromDouble :: Double -> a
 
 - type Fraction = Double
 - class Widget w => HasScroller w where
- isWfOrientation :: w -> Orientation -> Bool
 - scrollbar :: Orientation -> ScrollBar -> Config w
 - moveto :: Orientation -> w -> Fraction -> IO ()
 - scroll :: Orientation -> w -> Int -> ScrollUnit -> IO ()
 - view :: Orientation -> w -> IO (Fraction, Fraction)
 
 - data ScrollBar
 - data ScrollBarElem
 - data ScrollUnit
 - type Answer a = Either SomeException a
 - type Config w = w -> IO w
 - newtype MonadWithError (m :: Type -> Type) a = MonadWithError (m (WithError a))
 - getScrollBars :: HasScroller a => ScrollBox a -> [ScrollBar]
 - getScrolledWidget :: (Widget a, HasScroller a) => ScrollBox a -> a
 - newScrollBox :: (Widget wid, HasScroller wid, Container par) => par -> (Frame -> IO wid) -> [Config (ScrollBox wid)] -> IO (ScrollBox wid, wid)
 - data ScrollBox a = ScrollBox {
- fScrollFrame :: Frame
 - fPadFrames :: [Frame]
 - fScrollBars :: [ScrollBar]
 - fScrolledWidget :: a
 
 - (//) :: Form value1 -> Form value2 -> Form (value1, value2)
 - (\\) :: Form x -> Form y -> Form (x, y)
 - column :: [Form value] -> Form [value]
 - doForm :: String -> Form value -> IO (Maybe value)
 - doFormList :: String -> [(Form x, String)] -> IO (Event (WithError x), IO ())
 - doFormMust :: String -> Form value -> IO value
 - editableTextForm :: [Config Editor] -> Form String
 - editableTextForm0 :: [Config Editor] -> Form String
 - emptyForm :: Form ()
 - guardForm :: (x -> Bool) -> String -> Form x -> Form x
 - guardFormIO :: (x -> IO Bool) -> String -> Form x -> Form x
 - guardNothing :: String -> Form (Maybe x) -> Form x
 - mapForm :: (x -> WithError y) -> Form x -> Form y
 - mapFormIO :: (x -> IO (WithError y)) -> Form x -> Form y
 - mapMakeFormEntry :: FormValue value2 => (value1 -> value2) -> (value2 -> value1) -> Frame -> value1 -> IO (EnteredForm value1)
 - newFormEntry :: (FormLabel label, FormValue value) => label -> value -> Form value
 - newFormMenu :: FormLabel label => label -> HTkMenu value -> Form (Maybe value)
 - newFormOptionMenu :: GUIValue a => [a] -> Form a
 - newFormOptionMenu2 :: (Eq a, GUIValue a) => [(a, b)] -> Form b
 - nullForm :: FormLabel label => label -> Form ()
 - row :: [Form value] -> Form [value]
 - data EmptyLabel = EmptyLabel
 - data Form value
 - class FormLabel label where
 - class FormTextField value where
- makeFormString :: value -> String
 - readFormString :: String -> WithError value
 
 - class FormTextFieldIO value where
- makeFormStringIO :: value -> IO String
 - readFormStringIO :: String -> IO (WithError value)
 
 - class FormValue value where
- makeFormEntry :: Frame -> value -> IO (EnteredForm value)
 
 - class HasConfigRadioButton value where
- configRadioButton :: value -> Config (RadioButton Int)
 
 - newtype Password value = Password value
 - data Radio x
 - data WrappedFormLabel = FormLabel label => WrappedFormLabel label
 - createTextDisplay :: String -> String -> [Config Editor] -> IO ()
 - createTextDisplayExt :: String -> String -> [Config Editor] -> IO () -> IO (Toplevel, Editor)
 
Documentation
data LBGoalView Source #
Represents a goal in a ListBox that uses populateGoalsListBox 
Constructors
| LBGoalView | |
Fields 
  | |
data LBStatusIndicator Source #
existential type for widgets that can be enabled and disabled
listBox :: String -> [String] -> IO (Maybe Int) Source #
create a window with title and list of options, return selected option
confirmMess :: String -> IO Bool #
messageMess :: String -> IO () #
Arguments
| :: String | default filename for saving the text  | 
| -> String | text to be saved  | 
| -> IO () | 
createTextSaveDisplay Source #
Arguments
| :: String | title of the window  | 
| -> String | default filename for saving the text  | 
| -> String | text to be displayed  | 
| -> IO () | 
Display some (longish) text in an uneditable, scrollable editor. Simplified version of createTextSaveDisplayExt
newFileDialogStr :: String -> FilePath -> IO (Event (Maybe FilePath)) #
fileDialogStr :: String -> FilePath -> IO (Event (Maybe FilePath)) #
displayTheoryWithWarning Source #
Arguments
| :: String | kind of theory  | 
| -> String | name of theory  | 
| -> String | warning text  | 
| -> G_theory | to be shown theory  | 
| -> IO () | 
returns a window displaying the given theory and the given warning text.
Arguments
| :: ListBox String | listbox  | 
| -> [LBGoalView] | list of goals length must remain constant after the first call  | 
| -> IO () | 
Populates a ListBox with goals. After the initial call to this function
the number of goals is assumed to remain constant in ensuing calls. 
indicatorFromProofStatus :: ProofStatus a -> LBStatusIndicator Source #
Converts a ProofStatus into a LBStatusIndicator
indicatorFromBasicProof :: BasicProof -> LBStatusIndicator Source #
Converts a BasicProof into a LBStatusIndicator
indicatorString :: LBStatusIndicator -> String Source #
Converts a LBStatusIndicator into a short String representing it in
a ListBox 
enableWids :: [EnableWid] -> IO () Source #
disableWids :: [EnableWid] -> IO () Source #
enableWidsUponSelection :: ListBox String -> [EnableWid] -> IO () Source #
enables widgets only if at least one entry is selected in the listbox, otherwise the widgets are disabled
Instances
| Monad Event | |
| Functor Event | |
| MonadFail Event | |
Defined in Events.Events  | |
| Applicative Event | |
| HasEvent Event | |
Defined in Events.Events  | |
class Destroyable o where #
Instances
class Destroyable o => Destructible o where #
Instances
| Destructible DaVinciGraph | |
Defined in UDrawGraph.Graph  | |
| Destructible Context | |
Defined in UDrawGraph.Basic  | |
| GraphAll graph graphParms node nodeType nodeTypeParms arc arcType arcTypeParms => Destructible (Graph graph graphParms node nodeType nodeTypeParms arc arcType arcTypeParms) | |
Defined in Graphs.GraphDisp  | |
Constructors
| Immediate | |
| Awaiting (IO ()) | |
| AwaitingAlways (IO ()) | 
class HasConfig option configuration where #
Methods
($$) :: option -> configuration -> configuration #
configUsed :: option -> configuration -> Bool #
Instances
| GraphConfig graphConfig => HasConfig graphConfig DaVinciGraphParms | |
Defined in UDrawGraph.Graph Methods ($$) :: graphConfig -> DaVinciGraphParms -> DaVinciGraphParms # configUsed :: graphConfig -> DaVinciGraphParms -> Bool #  | |
| HasConfig GlobalMenu DaVinciGraphParms | |
Defined in UDrawGraph.Graph Methods ($$) :: GlobalMenu -> DaVinciGraphParms -> DaVinciGraphParms # configUsed :: GlobalMenu -> DaVinciGraphParms -> Bool #  | |
| HasConfig GraphTitle DaVinciGraphParms | |
Defined in UDrawGraph.Graph Methods ($$) :: GraphTitle -> DaVinciGraphParms -> DaVinciGraphParms # configUsed :: GraphTitle -> DaVinciGraphParms -> Bool #  | |
| HasConfig Delayer DaVinciGraphParms | |
Defined in UDrawGraph.Graph Methods ($$) :: Delayer -> DaVinciGraphParms -> DaVinciGraphParms # configUsed :: Delayer -> DaVinciGraphParms -> Bool #  | |
| HasConfig Orientation DaVinciGraphParms | |
Defined in UDrawGraph.Graph Methods ($$) :: Orientation -> DaVinciGraphParms -> DaVinciGraphParms # configUsed :: Orientation -> DaVinciGraphParms -> Bool #  | |
| HasConfig ActionWrapper DaVinciGraphParms | |
Defined in UDrawGraph.Graph Methods ($$) :: ActionWrapper -> DaVinciGraphParms -> DaVinciGraphParms # configUsed :: ActionWrapper -> DaVinciGraphParms -> Bool #  | |
| HasConfig AllowClose DaVinciGraphParms | |
Defined in UDrawGraph.Graph Methods ($$) :: AllowClose -> DaVinciGraphParms -> DaVinciGraphParms # configUsed :: AllowClose -> DaVinciGraphParms -> Bool #  | |
| HasConfig AllowDragging DaVinciGraphParms | |
Defined in UDrawGraph.Graph Methods ($$) :: AllowDragging -> DaVinciGraphParms -> DaVinciGraphParms # configUsed :: AllowDragging -> DaVinciGraphParms -> Bool #  | |
| HasConfig FileMenuAct DaVinciGraphParms | |
Defined in UDrawGraph.Graph Methods ($$) :: FileMenuAct -> DaVinciGraphParms -> DaVinciGraphParms # configUsed :: FileMenuAct -> DaVinciGraphParms -> Bool #  | |
| HasConfig GraphGesture DaVinciGraphParms | |
Defined in UDrawGraph.Graph Methods ($$) :: GraphGesture -> DaVinciGraphParms -> DaVinciGraphParms # configUsed :: GraphGesture -> DaVinciGraphParms -> Bool #  | |
| HasConfig OptimiseLayout DaVinciGraphParms | |
Defined in UDrawGraph.Graph Methods ($$) :: OptimiseLayout -> DaVinciGraphParms -> DaVinciGraphParms # configUsed :: OptimiseLayout -> DaVinciGraphParms -> Bool #  | |
| HasConfig SurveyView DaVinciGraphParms | |
Defined in UDrawGraph.Graph Methods ($$) :: SurveyView -> DaVinciGraphParms -> DaVinciGraphParms # configUsed :: SurveyView -> DaVinciGraphParms -> Bool #  | |
| HasConfig (SimpleSource GraphTitle) DaVinciGraphParms | |
Defined in UDrawGraph.Graph Methods ($$) :: SimpleSource GraphTitle -> DaVinciGraphParms -> DaVinciGraphParms # configUsed :: SimpleSource GraphTitle -> DaVinciGraphParms -> Bool #  | |
| HasConfig (FileMenuOption, Maybe (DaVinciGraph -> IO ())) DaVinciGraphParms | |
Defined in UDrawGraph.Graph Methods ($$) :: (FileMenuOption, Maybe (DaVinciGraph -> IO ())) -> DaVinciGraphParms -> DaVinciGraphParms # configUsed :: (FileMenuOption, Maybe (DaVinciGraph -> IO ())) -> DaVinciGraphParms -> Bool #  | |
Instances
| HasReceive Channel | |
Defined in Events.Channels  | |
| HasSend Channel | |
Defined in Events.Channels  | |
Instances
| Monad WithError | |
| Functor WithError | |
| MonadFail WithError | |
Defined in Util.Computation  | |
| Applicative WithError | |
toWithError :: Either String a -> WithError a #
newChannel :: IO (Channel a) #
allowWhile :: Event () -> Event a -> Event a #
computeEvent :: IO (Event a) -> Event a #
getAllQueued :: Event a -> IO [a] #
receiveIO :: HasReceive chan => chan a -> IO a #
spawnEvent :: Event () -> IO (IO ()) #
syncNoWait :: Event a -> IO () #
thenGetEvent :: Event a -> (a -> Event b) -> Event b #
createBitMapItem :: Canvas -> [Config BitMapItem] -> IO BitMapItem #
declVarList :: CanvasTagOrID -> TclCmd #
itemsNotOnSameCanvas :: IOError #
lowerItem :: (CanvasItem ci, CanvasItem w) => ci -> w -> IO () #
moveItem :: (Synchronized w, CanvasItem w) => w -> Distance -> Distance -> IO () #
putItemAtBottom :: CanvasItem ci => ci -> IO () #
putItemOnTop :: CanvasItem w => w -> IO () #
raiseItem :: (CanvasItem ci, CanvasItem w) => ci -> w -> IO () #
scaleItem :: (Synchronized w, CanvasItem w) => w -> Distance -> Distance -> Double -> Double -> IO () #
aboveItem :: CanvasItem item => item -> SearchSpec #
addCanvasTag :: SearchSpec -> CanvasTag -> IO () #
allItems :: SearchSpec #
belowItem :: CanvasItem item => item -> SearchSpec #
closest :: Position -> SearchSpec #
enclosed :: Position -> Position -> SearchSpec #
overlapping :: Position -> Position -> SearchSpec #
removeCanvasTag :: CanvasItem i => i -> CanvasTag -> IO () #
withTag :: CanvasItem item => item -> SearchSpec #
createEmbeddedCanvasWin :: Widget w => Canvas -> w -> [Config EmbeddedCanvasWin] -> IO EmbeddedCanvasWin #
arrowshape :: ArrowShape -> Config Line #
arrowstyle :: ArrowHead -> Config Line #
getArrowshape :: Line -> IO ArrowShape #
getArrowstyle :: Line -> IO ArrowHead #
getCapstyle :: Line -> IO CapStyle #
getJoinstyle :: Line -> IO JoinStyle #
errmap :: BitMapHandle #
getBitMapHandle :: GUIObject w => w -> ConfigID -> IO BitMapHandle #
gray25 :: BitMapHandle #
gray50 :: BitMapHandle #
info :: BitMapHandle #
setBitMapHandle :: GUIObject w => w -> ConfigID -> BitMapHandle -> Bool -> IO w #
stringToBitMapHandle :: String -> IO BitMapHandle #
warning :: BitMapHandle #
focusModel :: Window w => FocusModel -> Config w #
forceFocus :: Widget w => w -> IO () #
getCurrentGrab :: IO (Maybe CurrentGrab) #
getFocus :: Window w => w -> IO (Maybe CurrentFocus) #
getFocusModel :: Window w => w -> IO FocusModel #
getGrabStatus :: Widget w => w -> IO (Maybe GrabStatus) #
getRecentFocus :: Window w => w -> IO (Maybe CurrentFocus) #
grabGlobal :: Widget w => w -> IO () #
releaseGrab :: Widget w => w -> IO () #
returnGrab :: Maybe CurrentGrab -> IO () #
getIconMask :: Window w => Icon w -> IO BitMapHandle #
imageToInt :: Image -> IO Int #
imgPalette :: PaletteSpec p => p -> Config Image #
intToImage :: Int -> IO (Maybe Image) #
createToplevel :: [Config Toplevel] -> IO Toplevel #
tkGetToplevelConfig :: ObjectName -> ConfigID -> TclScript #
tkSetToplevelConfigs :: ObjectName -> [ConfigOption] -> TclScript #
getMaxSize :: Window w => w -> IO Size #
getMinSize :: Window w => w -> IO Size #
isWMConfig :: ConfigID -> Bool #
pagex :: Distance -> CreationConfig PostScript #
pagey :: Distance -> CreationConfig PostScript #
psfile :: String -> CreationConfig PostScript #
pssize :: Size -> CreationConfig PostScript #
pswidth :: Distance -> CreationConfig PostScript #
rotate :: Bool -> CreationConfig PostScript #
getScreenHeight :: Window a => Screen a -> IO Distance #
getScreenManager :: Window a => Screen a -> IO String #
getScreenVisual :: Window a => Screen a -> IO VisualClass #
getScreenWidth :: Window a => Screen a -> IO Distance #
buttonColours :: HasColour w => w -> ConfigID -> Bool #
activeBackground :: (ColourDesignator c, HasColour w) => c -> Config w #
activeForeground :: (ColourDesignator c, HasColour w) => c -> Config w #
background :: (ColourDesignator c, HasColour w) => c -> Config w #
bg :: (ColourDesignator c, HasColour w) => c -> Config w #
disabledForeground :: (ColourDesignator c, HasColour w) => c -> Config w #
fg :: (ColourDesignator c, HasColour w) => c -> Config w #
foreground :: (ColourDesignator c, HasColour w) => c -> Config w #
getActiveBackground :: HasColour w => w -> IO Colour #
getActiveForeground :: HasColour w => w -> IO Colour #
getBackground :: HasColour w => w -> IO Colour #
getDisabledForeground :: HasColour w => w -> IO Colour #
getForeground :: HasColour w => w -> IO Colour #
hasBackGroundColour :: HasColour w => w -> ConfigID -> Bool #
hasForeGroundColour :: HasColour w => w -> ConfigID -> Bool #
bindPathSimple :: Widget wid => wid -> WishEventType -> IO (Event (), IO ()) #
bindSimple :: GUIObject wid => wid -> WishEventType -> IO (Event (), IO ()) #
diamondCross :: Cursor #
addEventInfoSet :: EventInfoSet -> [EventParameter] -> EventInfoSet #
delEventInfoSet :: EventInfoSet -> [EventParameter] -> EventInfoSet #
epFromChar :: Char -> EventParameter #
epToChar :: EventParameter -> Char #
listEventInfoSet :: EventInfoSet -> [EventParameter] #
mkEventInfo :: [(EventParameter, String)] -> EventInfo #
mkEventInfoSet :: [EventParameter] -> EventInfoSet #
delimitString :: String -> String #
escapeString :: String -> String #
illegalGUIValue :: IOError #
toTkString :: String -> String #
showGridPackOptions :: [GridPackOption] -> String #
showPackOptions :: [PackOption] -> String #
grid :: Widget w => w -> [GridPackOption] -> IO () #
pack :: Widget w => w -> [PackOption] -> IO () #
showCreationConfigs :: [CreationConfig a] -> IO String #
createTkVariable :: GUIValue a => a -> IO (TkVariable a) #
readTkVariable :: GUIValue a => TkVariable a -> IO a #
setTkVariable :: GUIValue a => TkVariable a -> a -> IO () #
cleanupWish :: IO () #
forgetPackage :: String -> IO () #
isPackageAvailable :: String -> IO Bool #
isTixAvailable :: IO Bool #
requirePackage :: String -> IO Bool #
createMenu :: GUIObject par => par -> Bool -> [Config Menu] -> IO Menu #
createMenuCascade :: Menu -> [Config MenuCascade] -> IO MenuCascade #
createPulldownMenu :: Menu -> [Config MenuCascade] -> IO Menu #
createMenuCheckButton :: Menu -> [Config MenuCheckButton] -> IO MenuCheckButton #
createMenuCommand :: Menu -> [Config MenuCommand] -> IO MenuCommand #
createMenuRadioButton :: Menu -> [Config MenuRadioButton] -> IO MenuRadioButton #
createMenuSeparator :: Menu -> [Config MenuSeparator] -> IO MenuSeparator #
createEmbeddedTextWin :: (HasIndex Editor i BaseIndex, Widget w) => Editor -> i -> w -> [Config EmbeddedTextWin] -> IO EmbeddedTextWin #
getStretch :: EmbeddedTextWin -> IO Toggle #
stretch :: Toggle -> Config EmbeddedTextWin #
getCurrentMarks :: Editor -> IO [Mark] #
setMarkGravity :: Mark -> Gravity -> IO () #
addTextTag :: (HasIndex Editor i1 BaseIndex, HasIndex Editor i2 BaseIndex) => TextTag -> i1 -> i2 -> IO () #
bgstipple :: BitMapHandle -> Config TextTag #
createTextTag :: (HasIndex Editor i1 BaseIndex, HasIndex Editor i2 BaseIndex) => Editor -> i1 -> i2 -> [Config TextTag] -> IO TextTag #
fgstipple :: BitMapHandle -> Config TextTag #
getBgstipple :: TextTag -> IO BitMapHandle #
getFgstipple :: TextTag -> IO BitMapHandle #
getLmargin1 :: TextTag -> IO Distance #
getLmargin2 :: TextTag -> IO Distance #
getOverstrike :: TextTag -> IO Toggle #
getRmargin :: TextTag -> IO Distance #
getUnderlined :: TextTag -> IO Toggle #
lowerTextTag :: TextTag -> IO () #
overstrike :: Toggle -> Config TextTag #
raiseTextTag :: TextTag -> IO () #
removeTextTag :: (HasIndex Editor i1 BaseIndex, HasIndex Editor i2 BaseIndex) => TextTag -> i1 -> i2 -> IO () #
underlined :: Toggle -> Config TextTag #
getLabelSide :: LabelFrame -> IO LabelSide #
labelSide :: LabelSide -> Config LabelFrame #
newLabelFrame :: Container par => par -> [Config LabelFrame] -> IO LabelFrame #
createNoteBookPage :: NoteBook -> String -> [Config NoteBookPage] -> IO NoteBookPage #
after :: Pane -> CreationConfig Pane #
at :: Int -> CreationConfig Pane #
before :: Pane -> CreationConfig Pane #
createPane :: PanedWindow -> [CreationConfig Pane] -> [Config Pane] -> IO Pane #
expand :: Double -> CreationConfig Pane #
initsize :: Int -> CreationConfig Pane #
maxsize :: Int -> CreationConfig Pane #
minsize :: Int -> CreationConfig Pane #
newPanedWindow :: Container par => par -> Orientation -> [Config PanedWindow] -> IO PanedWindow #
resourceFile :: String -> Config HTk #
updateAllTasks :: IO () #
updateIdleTasks :: IO () #
withdrawWish :: IO () #
closeEnough :: Double -> Canvas -> IO Canvas #
getCloseEnough :: Canvas -> IO Double #
getConfine :: Canvas -> IO Bool #
getScrollRegion :: Canvas -> IO ScrollRegion #
screenToCanvasCoord :: Canvas -> Orientation -> Distance -> Maybe Distance -> IO Distance #
scrollIncrement :: Orientation -> Distance -> Canvas -> IO Canvas #
scrollRegion :: ScrollRegion -> Canvas -> IO Canvas #
newCheckButton :: Container par => par -> [Config (CheckButton a)] -> IO (CheckButton a) #
entrySubwidget :: GUIValue a => ComboBox a -> Entry a #
listBoxSubwidget :: GUIValue a => ComboBox a -> ListBox a #
newComboBox :: (GUIValue a, Container par) => par -> Bool -> [Config (ComboBox a)] -> IO (ComboBox a) #
appendText :: Editor -> String -> IO () #
compareIndices :: (HasIndex Editor i1 BaseIndex, HasIndex Editor i2 BaseIndex) => Editor -> String -> i1 -> i2 -> IO Bool #
deleteTextRange :: (HasIndex Editor i1 BaseIndex, HasIndex Editor i2 BaseIndex) => Editor -> i1 -> i2 -> IO () #
getTextRange :: (HasIndex Editor i1 BaseIndex, HasIndex Editor i2 BaseIndex) => Editor -> i1 -> i2 -> IO String #
getWrapMode :: Editor -> IO WrapMode #
insertNewline :: Editor -> IO () #
readTextFromFile :: Editor -> FilePath -> IO () #
search :: HasIndex Editor i BaseIndex => Editor -> SearchSwitch -> String -> i -> IO (Maybe BaseIndex) #
writeTextToFile :: Editor -> FilePath -> IO () #
getShowText :: GUIValue a => Entry a -> IO Char #
activateElem :: HasIndex (ListBox a) i Int => ListBox a -> i -> IO () #
elemNotFound :: IOError #
getSelectMode :: GUIValue a => ListBox a -> IO SelectMode #
selectMode :: GUIValue a => SelectMode -> ListBox a -> IO (ListBox a) #
selectionAnchor :: HasIndex (ListBox a) i Int => ListBox a -> i -> IO () #
newMenuButton :: Container par => par -> [Config MenuButton] -> IO MenuButton #
newOptionMenu :: (Container par, GUIValue a) => par -> [a] -> [Config (OptionMenu a)] -> IO (OptionMenu a) #
newRadioButton :: Container par => par -> [Config (RadioButton a)] -> IO (RadioButton a) #
bigIncrement :: ScaleValue a => a -> Config (Slider (Scale a)) #
getBigIncrement :: ScaleValue a => Slider (Scale a) -> IO a #
getInterval :: ScaleValue a => Scale a -> IO (a, a) #
getIntervalFrom :: ScaleValue a => Scale a -> IO a #
getIntervalTo :: ScaleValue a => Scale a -> IO a #
getShowValue :: Slider (Scale a) -> IO Toggle #
interval :: ScaleValue a => (a, a) -> Config (Scale a) #
intervalFrom :: ScaleValue a => a -> Config (Scale a) #
intervalTo :: ScaleValue a => a -> Config (Scale a) #
newScale :: (GUIValue a, ScaleValue a, Container par) => par -> [Config (Scale a)] -> IO (Scale a) #
activateScrollBarElem :: ScrollBar -> ScrollBarElem -> IO () #
getActivatedElem :: ScrollBar -> IO (Maybe ScrollBarElem) #
identify :: ScrollBar -> Position -> IO (Maybe ScrollBarElem) #
coerceWithError :: WithError a -> a #
coerceWithErrorIO :: WithError a -> IO a #
coerceWithErrorOrBreak :: (String -> a) -> WithError a -> a #
coerceWithErrorOrBreakIO :: (String -> a) -> WithError a -> IO a #
coerceWithErrorOrBreakIOPrefix :: String -> (String -> a) -> WithError a -> IO a #
coerceWithErrorOrBreakPrefix :: String -> (String -> a) -> WithError a -> a #
coerceWithErrorStringIO :: String -> WithError a -> IO a #
concatWithError :: [WithError a] -> WithError [a] #
exceptionToError :: Exception e => (e -> Maybe String) -> IO a -> IO (WithError a) #
foreverUntil :: Monad m => m Bool -> m () #
fromWithError :: WithError a -> Either String a #
fromWithError1 :: a -> WithError a -> a #
listWithError :: [WithError a] -> WithError [a] #
mapWithError :: (a -> b) -> WithError a -> WithError b #
mapWithError' :: (a -> WithError b) -> WithError a -> WithError b #
mapWithErrorIO :: (a -> IO b) -> WithError a -> IO (WithError b) #
mapWithErrorIO' :: (a -> IO (WithError b)) -> WithError a -> IO (WithError b) #
monadifyWithError :: forall (m :: Type -> Type) a. Monad m => WithError a -> MonadWithError m a #
pairWithError :: WithError a -> WithError b -> WithError (a, b) #
swapIOWithError :: WithError (IO a) -> IO (WithError a) #
toMonadWithError :: Monad m => m a -> MonadWithError m a #
tryUntilOK :: IO a -> IO a #
class HasReceive (chan :: Type -> Type) where #
Instances
| HasReceive Channel | |
Defined in Events.Channels  | |
class Synchronized a where #
Methods
synchronize :: a -> IO b -> IO b #
Instances
Instances
| Eq Arc | |
| Destroyable Arc | |
Defined in HTk.Canvasitems.Arc  | |
| Synchronized Arc | |
Defined in HTk.Canvasitems.Arc Methods synchronize :: Arc -> IO b -> IO b #  | |
| CanvasItem Arc | |
Defined in HTk.Canvasitems.Arc  | |
| FilledCanvasItem Arc | |
Defined in HTk.Canvasitems.Arc Methods filling :: ColourDesignator c => c -> Config Arc # getFilling :: Arc -> IO Colour # outline :: ColourDesignator c => c -> Config Arc # getOutline :: Arc -> IO Colour # stipple :: BitMapHandle -> Config Arc # getStipple :: Arc -> IO BitMapHandle # outlinewidth :: Distance -> Config Arc # getOutlineWidth :: Arc -> IO Distance #  | |
| TaggedCanvasItem Arc | |
| HasGeometry Arc | |
Defined in HTk.Canvasitems.Arc  | |
| HasPosition Arc | |
Defined in HTk.Canvasitems.Arc  | |
| HasSize Arc | |
| GUIObject Arc | |
data BitMapItem #
Instances
class GUIObject w => CanvasItem w #
Instances
| CanvasItem Arc | |
Defined in HTk.Canvasitems.Arc  | |
| CanvasItem BitMapItem | |
Defined in HTk.Canvasitems.BitMapItem  | |
| CanvasItem CanvasTag | |
Defined in HTk.Canvasitems.CanvasTag  | |
| CanvasItem EmbeddedCanvasWin | |
Defined in HTk.Canvasitems.EmbeddedCanvasWin  | |
| CanvasItem ImageItem | |
Defined in HTk.Canvasitems.ImageItem  | |
| CanvasItem Line | |
Defined in HTk.Canvasitems.Line  | |
| CanvasItem Oval | |
Defined in HTk.Canvasitems.Oval  | |
| CanvasItem Polygon | |
Defined in HTk.Canvasitems.Polygon  | |
| CanvasItem Rectangle | |
Defined in HTk.Canvasitems.Rectangle  | |
| CanvasItem TextItem | |
Defined in HTk.Canvasitems.TextItem  | |
class CanvasItem w => FilledCanvasItem w where #
Minimal complete definition
Nothing
Methods
filling :: ColourDesignator c => c -> Config w #
getFilling :: w -> IO Colour #
outline :: ColourDesignator c => c -> Config w #
getOutline :: w -> IO Colour #
stipple :: BitMapHandle -> Config w #
getStipple :: w -> IO BitMapHandle #
outlinewidth :: Distance -> Config w #
getOutlineWidth :: w -> IO Distance #
Instances
Instances
| CanvasItem w => HasCoords w | |
class CanvasItem w => SegmentedCanvasItem w where #
Minimal complete definition
Nothing
Instances
| SegmentedCanvasItem Line | |
Defined in HTk.Canvasitems.Line  | |
| SegmentedCanvasItem Polygon | |
Defined in HTk.Canvasitems.Polygon  | |
Instances
| Eq CanvasTag | |
| Destroyable CanvasTag | |
Defined in HTk.Canvasitems.CanvasTag  | |
| Synchronized CanvasTag | |
Defined in HTk.Canvasitems.CanvasTag Methods synchronize :: CanvasTag -> IO b -> IO b #  | |
| CanvasItem CanvasTag | |
Defined in HTk.Canvasitems.CanvasTag  | |
| GUIObject CanvasTag | |
data SearchSpec #
class CanvasItem w => TaggedCanvasItem w where #
Minimal complete definition
Nothing
Instances
data EmbeddedCanvasWin #
Instances
Instances
| Eq ImageItem | |
| Destroyable ImageItem | |
Defined in HTk.Canvasitems.ImageItem  | |
| Synchronized ImageItem | |
Defined in HTk.Canvasitems.ImageItem Methods synchronize :: ImageItem -> IO b -> IO b #  | |
| CanvasItem ImageItem | |
Defined in HTk.Canvasitems.ImageItem  | |
| TaggedCanvasItem ImageItem | |
| HasPhoto ImageItem | |
| HasCanvAnchor ImageItem | |
Defined in HTk.Canvasitems.ImageItem  | |
| HasPosition ImageItem | |
Defined in HTk.Canvasitems.ImageItem  | |
| GUIObject ImageItem | |
Instances
| Enum ArrowHead | |
Defined in HTk.Canvasitems.Line  | |
| Eq ArrowHead | |
| Ord ArrowHead | |
Defined in HTk.Canvasitems.Line  | |
| Read ArrowHead | |
Defined in HTk.Canvasitems.Line  | |
| Show ArrowHead | |
| GUIValue ArrowHead | |
Defined in HTk.Canvasitems.Line Methods toGUIValue :: ArrowHead -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe ArrowHead # fromGUIValue :: GUIVALUE -> ArrowHead #  | |
Constructors
| CapRound | |
| CapProjecting | |
| CapButt | 
Instances
| Enum CapStyle | |
Defined in HTk.Canvasitems.Line  | |
| Eq CapStyle | |
| Ord CapStyle | |
Defined in HTk.Canvasitems.Line  | |
| Read CapStyle | |
Defined in HTk.Canvasitems.Line  | |
| Show CapStyle | |
| GUIValue CapStyle | |
Defined in HTk.Canvasitems.Line Methods toGUIValue :: CapStyle -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe CapStyle # fromGUIValue :: GUIVALUE -> CapStyle #  | |
Instances
| Enum JoinStyle | |
Defined in HTk.Canvasitems.Line  | |
| Eq JoinStyle | |
| Ord JoinStyle | |
Defined in HTk.Canvasitems.Line  | |
| Read JoinStyle | |
Defined in HTk.Canvasitems.Line  | |
| Show JoinStyle | |
| GUIValue JoinStyle | |
Defined in HTk.Canvasitems.Line Methods toGUIValue :: JoinStyle -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe JoinStyle # fromGUIValue :: GUIVALUE -> JoinStyle #  | |
Instances
| Eq Line | |
| Destroyable Line | |
Defined in HTk.Canvasitems.Line  | |
| Synchronized Line | |
Defined in HTk.Canvasitems.Line Methods synchronize :: Line -> IO b -> IO b #  | |
| CanvasItem Line | |
Defined in HTk.Canvasitems.Line  | |
| FilledCanvasItem Line | |
Defined in HTk.Canvasitems.Line Methods filling :: ColourDesignator c => c -> Config Line # getFilling :: Line -> IO Colour # outline :: ColourDesignator c => c -> Config Line # getOutline :: Line -> IO Colour # stipple :: BitMapHandle -> Config Line # getStipple :: Line -> IO BitMapHandle # outlinewidth :: Distance -> Config Line # getOutlineWidth :: Line -> IO Distance #  | |
| SegmentedCanvasItem Line | |
Defined in HTk.Canvasitems.Line  | |
| TaggedCanvasItem Line | |
| HasSize Line | |
| GUIObject Line | |
Instances
| Eq Oval | |
| Destroyable Oval | |
Defined in HTk.Canvasitems.Oval  | |
| Synchronized Oval | |
Defined in HTk.Canvasitems.Oval Methods synchronize :: Oval -> IO b -> IO b #  | |
| CanvasItem Oval | |
Defined in HTk.Canvasitems.Oval  | |
| FilledCanvasItem Oval | |
Defined in HTk.Canvasitems.Oval Methods filling :: ColourDesignator c => c -> Config Oval # getFilling :: Oval -> IO Colour # outline :: ColourDesignator c => c -> Config Oval # getOutline :: Oval -> IO Colour # stipple :: BitMapHandle -> Config Oval # getStipple :: Oval -> IO BitMapHandle # outlinewidth :: Distance -> Config Oval # getOutlineWidth :: Oval -> IO Distance #  | |
| TaggedCanvasItem Oval | |
| HasGeometry Oval | |
Defined in HTk.Canvasitems.Oval  | |
| HasPosition Oval | |
Defined in HTk.Canvasitems.Oval  | |
| HasSize Oval | |
| GUIObject Oval | |
Instances
| Eq Polygon | |
| Destroyable Polygon | |
Defined in HTk.Canvasitems.Polygon  | |
| Synchronized Polygon | |
Defined in HTk.Canvasitems.Polygon Methods synchronize :: Polygon -> IO b -> IO b #  | |
| CanvasItem Polygon | |
Defined in HTk.Canvasitems.Polygon  | |
| FilledCanvasItem Polygon | |
Defined in HTk.Canvasitems.Polygon Methods filling :: ColourDesignator c => c -> Config Polygon # getFilling :: Polygon -> IO Colour # outline :: ColourDesignator c => c -> Config Polygon # getOutline :: Polygon -> IO Colour # stipple :: BitMapHandle -> Config Polygon # getStipple :: Polygon -> IO BitMapHandle # outlinewidth :: Distance -> Config Polygon # getOutlineWidth :: Polygon -> IO Distance #  | |
| SegmentedCanvasItem Polygon | |
Defined in HTk.Canvasitems.Polygon  | |
| TaggedCanvasItem Polygon | |
| GUIObject Polygon | |
Instances
| Eq Rectangle | |
| Destroyable Rectangle | |
Defined in HTk.Canvasitems.Rectangle  | |
| Synchronized Rectangle | |
Defined in HTk.Canvasitems.Rectangle Methods synchronize :: Rectangle -> IO b -> IO b #  | |
| CanvasItem Rectangle | |
Defined in HTk.Canvasitems.Rectangle  | |
| FilledCanvasItem Rectangle | |
Defined in HTk.Canvasitems.Rectangle Methods filling :: ColourDesignator c => c -> Config Rectangle # getFilling :: Rectangle -> IO Colour # outline :: ColourDesignator c => c -> Config Rectangle # getOutline :: Rectangle -> IO Colour # stipple :: BitMapHandle -> Config Rectangle # getStipple :: Rectangle -> IO BitMapHandle # outlinewidth :: Distance -> Config Rectangle # getOutlineWidth :: Rectangle -> IO Distance #  | |
| TaggedCanvasItem Rectangle | |
| HasGeometry Rectangle | |
Defined in HTk.Canvasitems.Rectangle  | |
| HasPosition Rectangle | |
Defined in HTk.Canvasitems.Rectangle  | |
| HasSize Rectangle | |
| GUIObject Rectangle | |
Instances
Instances
| Eq BitMap | |
| Destroyable BitMap | |
Defined in HTk.Components.BitMap  | |
| Synchronized BitMap | |
Defined in HTk.Components.BitMap Methods synchronize :: BitMap -> IO b -> IO b #  | |
| BitMapDesignator BitMap | |
Defined in HTk.Components.BitMap Methods toBitMap :: BitMap -> BitMapHandle #  | |
| Widget BitMap | |
| HasBorder BitMap | |
| HasColour BitMap | |
| HasFile BitMap | |
Defined in HTk.Components.BitMap  | |
| HasSize BitMap | |
| GUIObject BitMap | |
class BitMapDesignator d where #
Methods
toBitMap :: d -> BitMapHandle #
Instances
| BitMapDesignator BitMap | |
Defined in HTk.Components.BitMap Methods toBitMap :: BitMap -> BitMapHandle #  | |
| BitMapDesignator BitMapHandle | |
Defined in HTk.Components.BitMap Methods toBitMap :: BitMapHandle -> BitMapHandle #  | |
| BitMapDesignator [Char] | |
Defined in HTk.Components.BitMap Methods toBitMap :: [Char] -> BitMapHandle #  | |
data BitMapHandle #
Constructors
| Predefined String | |
| BitMapHandle BitMap | |
| BitMapFile String | 
Instances
| BitMapDesignator BitMapHandle | |
Defined in HTk.Components.BitMap Methods toBitMap :: BitMapHandle -> BitMapHandle #  | |
class GUIObject w => HasBitMap w where #
Minimal complete definition
Nothing
Instances
data CurrentFocus #
Instances
| Object CurrentFocus | |
Defined in HTk.Components.Focus Methods objectID :: CurrentFocus -> ObjectID  | |
| Widget CurrentFocus | |
Defined in HTk.Components.Focus Methods cursor :: CursorDesignator ch => ch -> Config CurrentFocus # getCursor :: CurrentFocus -> IO Cursor # takeFocus :: Bool -> Config CurrentFocus # getTakeFocus :: CurrentFocus -> IO Bool #  | |
| GUIObject CurrentFocus | |
Defined in HTk.Components.Focus Methods toGUIObject :: CurrentFocus -> GUIOBJECT cname :: CurrentFocus -> String cset :: GUIValue a => CurrentFocus -> ConfigID -> a -> IO CurrentFocus cget :: GUIValue a => CurrentFocus -> ConfigID -> IO a  | |
data CurrentGrab #
Constructors
| CurrentGrab GUIOBJECT | 
Instances
| Eq CurrentGrab | |
Defined in HTk.Components.Focus  | |
| Object CurrentGrab | |
Defined in HTk.Components.Focus Methods objectID :: CurrentGrab -> ObjectID  | |
| Widget CurrentGrab | |
Defined in HTk.Components.Focus Methods cursor :: CursorDesignator ch => ch -> Config CurrentGrab # getCursor :: CurrentGrab -> IO Cursor # takeFocus :: Bool -> Config CurrentGrab # getTakeFocus :: CurrentGrab -> IO Bool #  | |
| GUIObject CurrentGrab | |
Defined in HTk.Components.Focus Methods toGUIObject :: CurrentGrab -> GUIOBJECT cname :: CurrentGrab -> String cset :: GUIValue a => CurrentGrab -> ConfigID -> a -> IO CurrentGrab cget :: GUIValue a => CurrentGrab -> ConfigID -> IO a  | |
data FocusModel #
Constructors
| ActiveFocus | |
| PassiveFocus | 
Instances
data GrabStatus #
Instances
Constructors
| Icon w | 
Instances
| (Window w, Eq w) => Eq (Icon w) | |
| (Window w, Ord w) => Ord (Icon w) | |
| Window w => Synchronized (Icon w) | |
Defined in HTk.Components.Icon Methods synchronize :: Icon w -> IO b -> IO b #  | |
| Window w => HasBitMap (Icon w) | |
Defined in HTk.Components.Icon Methods bitmap :: BitMapDesignator d => d -> Config (Icon w) # getBitMap :: Icon w -> IO BitMapHandle #  | |
| Window w => HasPosition (Icon w) | |
Defined in HTk.Components.Icon  | |
| Window w => GUIObject (Icon w) | |
| (Window w, GUIValue v) => HasText (Icon w) v | |
class GUIObject w => HasPhoto w where #
Minimal complete definition
Nothing
Instances
| HasPhoto ImageItem | |
| HasPhoto MenuCascade | |
Defined in HTk.Menuitems.MenuCascade  | |
| HasPhoto MenuCheckButton | |
Defined in HTk.Menuitems.MenuCheckButton  | |
| HasPhoto MenuCommand | |
Defined in HTk.Menuitems.MenuCommand  | |
| HasPhoto MenuRadioButton | |
Defined in HTk.Menuitems.MenuRadioButton  | |
| HasPhoto Button | |
| HasPhoto Label | |
| HasPhoto MenuButton | |
Defined in HTk.Widgets.MenuButton  | |
| HasPhoto (CheckButton a) | |
Defined in HTk.Widgets.CheckButton  | |
| HasPhoto (RadioButton a) | |
Defined in HTk.Widgets.RadioButton  | |
| HasPhoto (Dialog a) | |
Instances
| Eq Image | |
| Destroyable Image | |
Defined in HTk.Components.Image  | |
| Synchronized Image | |
Defined in HTk.Components.Image Methods synchronize :: Image -> IO b -> IO b #  | |
| Widget Image | |
| HasBorder Image | |
| HasColour Image | |
| HasFile Image | |
Defined in HTk.Components.Image  | |
| HasSize Image | |
| GUIObject Image | |
| FormLabel Image | |
Defined in HTk.Toolkit.SimpleForm  | |
Instances
Constructors
| EndOfText | 
Instances
| Eq EndOfText | |
| Read EndOfText | |
Defined in HTk.Components.Index  | |
| Show EndOfText | |
| GUIValue EndOfText | |
Defined in HTk.Components.Index Methods toGUIValue :: EndOfText -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe EndOfText # fromGUIValue :: GUIVALUE -> EndOfText #  | |
| HasIndex Editor EndOfText BaseIndex | |
Defined in HTk.Widgets.Editor Methods getBaseIndex :: Editor -> EndOfText -> IO BaseIndex #  | |
| HasIndex (Entry a) EndOfText BaseIndex | |
Defined in HTk.Widgets.Entry Methods getBaseIndex :: Entry a -> EndOfText -> IO BaseIndex #  | |
| HasIndex (ListBox a) EndOfText Int | |
Defined in HTk.Widgets.ListBox Methods getBaseIndex :: ListBox a -> EndOfText -> IO Int #  | |
Constructors
| First | 
Methods
getBaseIndex :: w -> i -> IO b #
Instances
Constructors
| Last | 
Instances
| Show Pixels | |
| HasIndex Editor Pixels BaseIndex | |
Defined in HTk.Widgets.Editor Methods getBaseIndex :: Editor -> Pixels -> IO BaseIndex #  | |
| HasIndex (ListBox a) Pixels Int | |
Defined in HTk.Widgets.ListBox Methods getBaseIndex :: ListBox a -> Pixels -> IO Int #  | |
class GUIObject w => HasSelection w where #
Methods
clearSelection :: w -> IO () #
Instances
| HasSelection Editor | |
Defined in HTk.Widgets.Editor Methods clearSelection :: Editor -> IO () #  | |
| HasSelection (Entry a) | |
Defined in HTk.Widgets.Entry Methods clearSelection :: Entry a -> IO () #  | |
| HasSelection (ListBox a) | |
Defined in HTk.Widgets.ListBox Methods clearSelection :: ListBox a -> IO () #  | |
class HasSelectionBaseIndex w i where #
Methods
getSelection :: w -> IO (Maybe i) #
Instances
| HasSelectionBaseIndex Editor ((Distance, Distance), (Distance, Distance)) | |
Defined in HTk.Widgets.Editor  | |
| HasSelectionBaseIndex (ListBox a) [Int] | |
Defined in HTk.Widgets.ListBox Methods getSelection :: ListBox a -> IO (Maybe [Int]) #  | |
| HasSelectionBaseIndex (Entry a) (Int, Int) | |
Defined in HTk.Widgets.Entry Methods getSelection :: Entry a -> IO (Maybe (Int, Int)) #  | |
class HasSelectionIndex w i => HasSelectionBaseIndexRange w i where #
Minimal complete definition
Methods
getSelectionStart :: w -> IO (Maybe i) #
getSelectionEnd :: w -> IO (Maybe i) #
getSelectionRange :: w -> IO (Maybe (i, i)) #
Instances
| HasSelectionBaseIndexRange Editor (Distance, Distance) | |
Defined in HTk.Widgets.Editor  | |
| HasSelectionBaseIndexRange (Entry a) Int | |
Defined in HTk.Widgets.Entry Methods getSelectionStart :: Entry a -> IO (Maybe Int) # getSelectionEnd :: Entry a -> IO (Maybe Int) # getSelectionRange :: Entry a -> IO (Maybe (Int, Int)) #  | |
| HasSelectionBaseIndexRange (ListBox a) Int | |
Defined in HTk.Widgets.ListBox Methods getSelectionStart :: ListBox a -> IO (Maybe Int) # getSelectionEnd :: ListBox a -> IO (Maybe Int) # getSelectionRange :: ListBox a -> IO (Maybe (Int, Int)) #  | |
class HasSelectionIndex w i where #
Instances
| HasIndex Editor i BaseIndex => HasSelectionIndex Editor i | |
Defined in HTk.Widgets.Editor  | |
| HasIndex (Entry a) i BaseIndex => HasSelectionIndex (Entry a) i | |
Defined in HTk.Widgets.Entry  | |
| HasIndex (ListBox a) i Int => HasSelectionIndex (ListBox a) i | |
Defined in HTk.Widgets.ListBox  | |
class HasSelectionIndexRange w i1 i2 where #
Methods
selectionRange :: i1 -> i2 -> Config w #
Instances
| (HasIndex Editor i1 BaseIndex, HasIndex Editor i2 BaseIndex) => HasSelectionIndexRange Editor i1 i2 | |
Defined in HTk.Widgets.Editor Methods selectionRange :: i1 -> i2 -> Config Editor #  | |
| (HasIndex (Entry a) i1 BaseIndex, HasIndex (Entry a) i2 BaseIndex) => HasSelectionIndexRange (Entry a) i1 i2 | |
Defined in HTk.Widgets.Entry Methods selectionRange :: i1 -> i2 -> Config (Entry a) #  | |
| (HasIndex (ListBox a) i1 Int, HasIndex (ListBox a) i2 Int) => HasSelectionIndexRange (ListBox a) i1 i2 | |
Defined in HTk.Widgets.ListBox Methods selectionRange :: i1 -> i2 -> Config (ListBox a) #  | |
Constructors
| Selection w | 
Instances
| (HasSelection w, Widget w) => HasBorder (Selection w) | |
| (HasSelection w, Widget w) => HasColour (Selection w) | |
| GUIObject w => GUIObject (Selection w) | |
| HasIndex (Entry a) (Selection (Entry a), First) BaseIndex | |
Defined in HTk.Widgets.Entry  | |
| HasIndex (Entry a) (Selection (Entry a), Last) BaseIndex | |
Defined in HTk.Widgets.Entry  | |
class Widget w => HasSlider w where #
Minimal complete definition
Nothing
Methods
repeatInterval :: Int -> Config (Slider w) #
getRepeatInterval :: Slider w -> IO Int #
repeatDelay :: Int -> Config (Slider w) #
getRepeatDelay :: Slider w -> IO Int #
Instances
| HasSlider ScrollBar | |
Defined in HTk.Widgets.ScrollBar Methods repeatInterval :: Int -> Config (Slider ScrollBar) # getRepeatInterval :: Slider ScrollBar -> IO Int # repeatDelay :: Int -> Config (Slider ScrollBar) # getRepeatDelay :: Slider ScrollBar -> IO Int #  | |
| HasSlider (Scale a) | |
Defined in HTk.Widgets.Scale Methods repeatInterval :: Int -> Config (Slider (Scale a)) # getRepeatInterval :: Slider (Scale a) -> IO Int # repeatDelay :: Int -> Config (Slider (Scale a)) # getRepeatDelay :: Slider (Scale a) -> IO Int #  | |
Constructors
| Slider w | 
Instances
| (HasSlider w, GUIObject w) => HasColour (Slider w) | |
| HasSize (Slider (Scale a)) | |
Defined in HTk.Widgets.Scale  | |
| GUIObject w => GUIObject (Slider w) | |
| ScaleValue a => HasIncrement (Slider (Scale a)) a | |
Defined in HTk.Widgets.Scale  | |
Instances
| Eq Box | |
| Destroyable Box | |
Defined in HTk.Containers.Box  | |
| Synchronized Box | |
Defined in HTk.Containers.Box Methods synchronize :: Box -> IO b -> IO b #  | |
| Widget Box | |
| HasBorder Box | |
| HasColour Box | |
| HasOrientation Box | |
Defined in HTk.Containers.Box  | |
| HasSize Box | |
| Container Box | |
Defined in HTk.Containers.Box  | |
| GUIObject Box | |
Instances
| Eq Frame | |
| Destroyable Frame | |
Defined in HTk.Containers.Frame  | |
| Synchronized Frame | |
Defined in HTk.Containers.Frame Methods synchronize :: Frame -> IO b -> IO b #  | |
| Widget Frame | |
| HasBorder Frame | |
| HasColour Frame | |
| HasSize Frame | |
| Container Frame | |
Defined in HTk.Containers.Frame  | |
| GUIObject Frame | |
Constructors
| Toplevel GUIOBJECT | 
Instances
| Eq Toplevel | |
| Destroyable Toplevel | |
Defined in HTk.Containers.Toplevel  | |
| Synchronized Toplevel | |
Defined in HTk.Containers.Toplevel Methods synchronize :: Toplevel -> IO b -> IO b #  | |
| Window Toplevel | |
Defined in HTk.Containers.Toplevel Methods iconify :: Toplevel -> IO () # deiconify :: Toplevel -> IO () # withdraw :: Toplevel -> IO () # putWinOnTop :: Toplevel -> IO () # putWinAtBottom :: Toplevel -> IO () # screen :: Display -> Config Toplevel # getScreen :: Toplevel -> IO Display # getClassName :: Toplevel -> IO String # getWindowState :: Toplevel -> IO WindowState # aspectRatio :: AspectRatio -> Config Toplevel # getAspectRatio :: Toplevel -> IO AspectRatio # positionFrom :: Whom -> Config Toplevel # getPositionFrom :: Toplevel -> IO Whom # sizeFrom :: Whom -> Config Toplevel # getSizeFrom :: Toplevel -> IO Whom #  | |
| Widget Toplevel | |
| Container Toplevel | |
Defined in HTk.Containers.Toplevel  | |
| GUIObject Toplevel | |
data AspectRatio #
Instances
| Eq AspectRatio | |
Defined in HTk.Containers.Window  | |
| Read AspectRatio | |
Defined in HTk.Containers.Window Methods readsPrec :: Int -> ReadS AspectRatio readList :: ReadS [AspectRatio] readPrec :: ReadPrec AspectRatio readListPrec :: ReadPrec [AspectRatio]  | |
| Show AspectRatio | |
Defined in HTk.Containers.Window Methods showsPrec :: Int -> AspectRatio -> ShowS show :: AspectRatio -> String showList :: [AspectRatio] -> ShowS  | |
| GUIValue AspectRatio | |
Defined in HTk.Containers.Window Methods cdefault :: AspectRatio # toGUIValue :: AspectRatio -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe AspectRatio # fromGUIValue :: GUIVALUE -> AspectRatio #  | |
Instances
| Enum Whom | |
| Eq Whom | |
| Ord Whom | |
| Read Whom | |
Defined in HTk.Containers.Window  | |
| Show Whom | |
| GUIValue Whom | |
Defined in HTk.Containers.Window Methods toGUIValue :: Whom -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe Whom # fromGUIValue :: GUIVALUE -> Whom #  | |
class GUIObject w => Window w where #
Minimal complete definition
Nothing
Methods
putWinOnTop :: w -> IO () #
putWinAtBottom :: w -> IO () #
screen :: Display -> Config w #
getScreen :: w -> IO Display #
getClassName :: w -> IO String #
getWindowState :: w -> IO WindowState #
aspectRatio :: AspectRatio -> Config w #
getAspectRatio :: w -> IO AspectRatio #
positionFrom :: Whom -> Config w #
getPositionFrom :: w -> IO Whom #
sizeFrom :: Whom -> Config w #
getSizeFrom :: w -> IO Whom #
Instances
data WindowState #
Constructors
| Deiconified | |
| Iconified | |
| Withdrawn | 
Instances
data ColourMode #
Constructors
| FullColourMode | |
| GrayScaleMode | |
| MonoChromeMode | 
Instances
class GUIObject w => HasPostscript w where #
Minimal complete definition
Nothing
Methods
postscript :: w -> [CreationConfig PostScript] -> IO () #
Instances
| HasPostscript Canvas | |
Defined in HTk.Widgets.Canvas Methods postscript :: Canvas -> [CreationConfig PostScript] -> IO () #  | |
data PostScript #
data VisualClass #
Constructors
| DirectColour | |
| GrayScale | |
| PseudoColour | |
| StaticColour | |
| StaticGray | |
| TrueColour | 
Instances
class GUIObject w => Widget w where #
Minimal complete definition
Nothing
Methods
cursor :: CursorDesignator ch => ch -> Config w #
takeFocus :: Bool -> Config w #
getTakeFocus :: w -> IO Bool #
Instances
class Widget w => ButtonWidget w where #
Minimal complete definition
Nothing
Instances
| ButtonWidget Button | |
| ButtonWidget MenuButton | |
Defined in HTk.Widgets.MenuButton  | |
| ButtonWidget (CheckButton a) | |
Defined in HTk.Widgets.CheckButton  | |
| ButtonWidget (RadioButton a) | |
Defined in HTk.Widgets.RadioButton  | |
Constructors
| Colour String | 
Instances
| Read Colour | |
Defined in HTk.Kernel.Colour  | |
| Show Colour | |
| ColourDesignator Colour | |
Defined in HTk.Kernel.Colour  | |
| GUIValue Colour | |
Defined in HTk.Kernel.Colour Methods toGUIValue :: Colour -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe Colour # fromGUIValue :: GUIVALUE -> Colour #  | |
| CursorDesignator (String, Colour) | |
Defined in HTk.Kernel.Cursor  | |
| CursorDesignator (String, Colour, Colour) | |
| CursorDesignator ([Char], [Char], Colour, Colour) | |
class ColourDesignator c where #
Instances
| ColourDesignator Colour | |
Defined in HTk.Kernel.Colour  | |
| ColourDesignator [Char] | |
Defined in HTk.Kernel.Colour  | |
| ColourDesignator (Double, Double, Double) | |
Defined in HTk.Kernel.Colour  | |
| ColourDesignator (Int, Int, Int) | |
Defined in HTk.Kernel.Colour  | |
class GUIObject w => HasAnchor w where #
Minimal complete definition
Nothing
Instances
| HasAnchor TextItem | |
| HasAnchor Button | |
| HasAnchor Label | |
| HasAnchor MenuButton | |
Defined in HTk.Widgets.MenuButton  | |
| HasAnchor Message | |
| HasAnchor (CheckButton a) | |
Defined in HTk.Widgets.CheckButton  | |
| GUIValue a => HasAnchor (ComboBox a) | |
| HasAnchor (OptionMenu a) | |
Defined in HTk.Widgets.OptionMenu  | |
class GUIObject w => HasBorder w where #
Minimal complete definition
Nothing
Methods
borderwidth :: Distance -> Config w #
getBorderwidth :: w -> IO Distance #
Instances
class GUIObject w => HasCanvAnchor w where #
Instances
| HasCanvAnchor BitMapItem | |
Defined in HTk.Canvasitems.BitMapItem  | |
| HasCanvAnchor EmbeddedCanvasWin | |
Defined in HTk.Canvasitems.EmbeddedCanvasWin Methods canvAnchor :: Anchor -> Config EmbeddedCanvasWin # getCanvAnchor :: EmbeddedCanvasWin -> IO Anchor #  | |
| HasCanvAnchor ImageItem | |
Defined in HTk.Canvasitems.ImageItem  | |
| HasCanvAnchor TextItem | |
Defined in HTk.Canvasitems.TextItem  | |
class GUIObject w => HasColour w where #
Minimal complete definition
Nothing
Instances
class GUIObject w => HasEnable w where #
Minimal complete definition
Nothing
Methods
Instances
class GUIObject w => HasFile w where #
Instances
| HasFile BitMap | |
Defined in HTk.Components.BitMap  | |
| HasFile Image | |
Defined in HTk.Components.Image  | |
class GUIObject w => HasFont w where #
Minimal complete definition
Nothing
Instances
class (HasSize w, HasPosition w) => HasGeometry w where #
Instances
| HasGeometry Arc | |
Defined in HTk.Canvasitems.Arc  | |
| HasGeometry Oval | |
Defined in HTk.Canvasitems.Oval  | |
| HasGeometry Rectangle | |
Defined in HTk.Canvasitems.Rectangle  | |
class HasIncrement w a where #
Instances
| ScaleValue a => HasIncrement (Slider (Scale a)) a | |
Defined in HTk.Widgets.Scale  | |
| ScaleValue a => HasIncrement (Scale a) a | |
Defined in HTk.Widgets.Scale  | |
class GUIObject w => HasJustify w where #
Minimal complete definition
Nothing
Instances
| HasJustify TextItem | |
Defined in HTk.Canvasitems.TextItem  | |
| HasJustify MenuCascade | |
Defined in HTk.Menuitems.MenuCascade  | |
| HasJustify MenuCheckButton | |
Defined in HTk.Menuitems.MenuCheckButton  | |
| HasJustify MenuCommand | |
Defined in HTk.Menuitems.MenuCommand  | |
| HasJustify MenuRadioButton | |
Defined in HTk.Menuitems.MenuRadioButton  | |
| HasJustify TextTag | |
Defined in HTk.Textitems.TextTag  | |
| HasJustify Button | |
Defined in HTk.Widgets.Button  | |
| HasJustify Label | |
Defined in HTk.Widgets.Label  | |
| HasJustify MenuButton | |
Defined in HTk.Widgets.MenuButton  | |
| HasJustify Message | |
Defined in HTk.Widgets.Message  | |
| HasJustify (CheckButton a) | |
Defined in HTk.Widgets.CheckButton  | |
| HasJustify (Entry a) | |
Defined in HTk.Widgets.Entry  | |
| HasJustify (RadioButton a) | |
Defined in HTk.Widgets.RadioButton  | |
class GUIObject w => HasOrientation w where #
Minimal complete definition
Nothing
Instances
| HasOrientation Box | |
Defined in HTk.Containers.Box  | |
| HasOrientation MenuSeparator | |
Defined in HTk.Menuitems.MenuSeparator Methods orient :: Orientation -> Config MenuSeparator # getOrient :: MenuSeparator -> IO Orientation #  | |
| HasOrientation ScrollBar | |
Defined in HTk.Widgets.ScrollBar  | |
| HasOrientation (Scale a) | |
Defined in HTk.Widgets.Scale  | |
class GUIObject w => HasPosition w where #
Instances
| HasPosition Arc | |
Defined in HTk.Canvasitems.Arc  | |
| HasPosition BitMapItem | |
Defined in HTk.Canvasitems.BitMapItem  | |
| HasPosition EmbeddedCanvasWin | |
Defined in HTk.Canvasitems.EmbeddedCanvasWin Methods position :: Position -> Config EmbeddedCanvasWin # getPosition :: EmbeddedCanvasWin -> IO Position #  | |
| HasPosition ImageItem | |
Defined in HTk.Canvasitems.ImageItem  | |
| HasPosition Oval | |
Defined in HTk.Canvasitems.Oval  | |
| HasPosition Rectangle | |
Defined in HTk.Canvasitems.Rectangle  | |
| HasPosition TextItem | |
Defined in HTk.Canvasitems.TextItem  | |
| Window w => HasPosition (Icon w) | |
Defined in HTk.Components.Icon  | |
class GUIObject w => HasSize w where #
Minimal complete definition
Nothing
Methods
width :: Distance -> Config w #
getWidth :: w -> IO Distance #
height :: Distance -> Config w #
Instances
class (GUIObject w, GUIValue v) => HasText w v where #
Minimal complete definition
Nothing
Instances
| GUIValue b => HasText TextItem b | |
| GUIValue v => HasText MenuCascade v | |
Defined in HTk.Menuitems.MenuCascade  | |
| GUIValue v => HasText MenuCheckButton v | |
Defined in HTk.Menuitems.MenuCheckButton  | |
| GUIValue v => HasText MenuCommand v | |
Defined in HTk.Menuitems.MenuCommand  | |
| GUIValue v => HasText MenuRadioButton v | |
Defined in HTk.Menuitems.MenuRadioButton  | |
| GUIValue v => HasText LabelFrame v | |
Defined in HTk.Tix.LabelFrame  | |
| GUIValue a => HasText NoteBookPage a | |
Defined in HTk.Tix.NoteBook  | |
| GUIValue v => HasText Button v | |
| GUIValue b => HasText Label b | |
| GUIValue v => HasText MenuButton v | |
Defined in HTk.Widgets.MenuButton  | |
| GUIValue b => HasText Message b | |
| (Window w, GUIValue v) => HasText (Icon w) v | |
| GUIValue v => HasText (CheckButton a) v | |
Defined in HTk.Widgets.CheckButton  | |
| GUIValue v => HasText (RadioButton a) v | |
Defined in HTk.Widgets.RadioButton  | |
| GUIValue v => HasText (Scale a) v | |
| GUIValue v => HasText (Dialog a) v | |
class GUIObject w => HasUnderline w where #
Minimal complete definition
Nothing
Methods
underline :: Int -> Config w #
getUnderline :: w -> IO Int #
wraplength :: Int -> Config w #
getWraplength :: w -> IO Int #
Instances
class (GUIObject w, GUIValue v) => HasValue w v where #
Minimal complete definition
Nothing
Instances
| GUIValue v => HasValue MenuCheckButton v | |
Defined in HTk.Menuitems.MenuCheckButton  | |
| GUIValue v => HasValue MenuRadioButton v | |
Defined in HTk.Menuitems.MenuRadioButton  | |
| GUIValue v => HasValue HTk v | |
| GUIValue a => HasValue Editor a | |
| GUIValue a => HasValue (Entry a) a | |
| GUIValue a => HasValue (OptionMenu a) a | |
Defined in HTk.Widgets.OptionMenu  | |
| GUIValue c => HasValue (RadioButton a) c | |
Defined in HTk.Widgets.RadioButton  | |
| (GUIValue a, GUIValue [a]) => HasValue (ComboBox a) [a] | |
| (GUIValue a, GUIValue [a]) => HasValue (ListBox a) [a] | |
class GUIObject w => HasCommand w where #
Minimal complete definition
Nothing
Instances
| HasCommand MenuCheckButton | |
Defined in HTk.Menuitems.MenuCheckButton Methods clicked :: MenuCheckButton -> IO (Event ()) #  | |
| HasCommand MenuCommand | |
Defined in HTk.Menuitems.MenuCommand Methods clicked :: MenuCommand -> IO (Event ()) #  | |
| HasCommand MenuRadioButton | |
Defined in HTk.Menuitems.MenuRadioButton Methods clicked :: MenuRadioButton -> IO (Event ()) #  | |
| HasCommand Button | |
Defined in HTk.Widgets.Button  | |
| HasCommand MenuButton | |
Defined in HTk.Widgets.MenuButton Methods clicked :: MenuButton -> IO (Event ()) #  | |
| HasCommand (CheckButton a) | |
Defined in HTk.Widgets.CheckButton Methods clicked :: CheckButton a -> IO (Event ()) #  | |
| HasCommand (RadioButton a) | |
Defined in HTk.Widgets.RadioButton Methods clicked :: RadioButton a -> IO (Event ()) #  | |
Instances
| Show BCursor | |
| CursorDesignator BCursor | |
Defined in HTk.Kernel.Cursor  | |
Constructors
| Cursor String | 
Instances
| Read Cursor | |
Defined in HTk.Kernel.Cursor  | |
| Show Cursor | |
| CursorDesignator Cursor | |
Defined in HTk.Kernel.Cursor  | |
| GUIValue Cursor | |
Defined in HTk.Kernel.Cursor Methods toGUIValue :: Cursor -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe Cursor # fromGUIValue :: GUIVALUE -> Cursor #  | |
class CursorDesignator ch where #
Instances
| CursorDesignator String | |
Defined in HTk.Kernel.Cursor  | |
| CursorDesignator BCursor | |
Defined in HTk.Kernel.Cursor  | |
| CursorDesignator Cursor | |
Defined in HTk.Kernel.Cursor  | |
| CursorDesignator XCursor | |
Defined in HTk.Kernel.Cursor  | |
| CursorDesignator (String, Colour) | |
Defined in HTk.Kernel.Cursor  | |
| CursorDesignator (String, Colour, Colour) | |
| CursorDesignator ([Char], [Char], Colour, Colour) | |
Instances
| Show XCursor | |
| CursorDesignator XCursor | |
Defined in HTk.Kernel.Cursor  | |
data EventInfoSet #
data EventParameter #
Instances
| Eq EventParameter | |
Defined in HTk.Kernel.EventInfo Methods (==) :: EventParameter -> EventParameter -> Bool (/=) :: EventParameter -> EventParameter -> Bool  | |
| Ord EventParameter | |
Defined in HTk.Kernel.EventInfo Methods compare :: EventParameter -> EventParameter -> Ordering (<) :: EventParameter -> EventParameter -> Bool (<=) :: EventParameter -> EventParameter -> Bool (>) :: EventParameter -> EventParameter -> Bool (>=) :: EventParameter -> EventParameter -> Bool max :: EventParameter -> EventParameter -> EventParameter min :: EventParameter -> EventParameter -> EventParameter  | |
| Read EventParameter | |
Defined in HTk.Kernel.EventInfo Methods readsPrec :: Int -> ReadS EventParameter readList :: ReadS [EventParameter] readPrec :: ReadPrec EventParameter readListPrec :: ReadPrec [EventParameter]  | |
| Show EventParameter | |
Defined in HTk.Kernel.EventInfo Methods showsPrec :: Int -> EventParameter -> ShowS show :: EventParameter -> String showList :: [EventParameter] -> ShowS  | |
Constructors
| Font String | 
Instances
| Read Font | |
Defined in HTk.Kernel.Font  | |
| Show Font | |
| FontDesignator Font | |
Defined in HTk.Kernel.Font  | |
| GUIValue Font | |
Defined in HTk.Kernel.Font Methods toGUIValue :: Font -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe Font # fromGUIValue :: GUIVALUE -> Font #  | |
class FontDesignator fh where #
Instances
| FontDesignator String | |
Defined in HTk.Kernel.Font  | |
| FontDesignator Font | |
Defined in HTk.Kernel.Font  | |
| FontDesignator FontFamily | |
Defined in HTk.Kernel.Font Methods toFont :: FontFamily -> Font #  | |
| FontDesignator XFont | |
Defined in HTk.Kernel.Font  | |
| FontDesignator (FontFamily, Int) | |
Defined in HTk.Kernel.Font Methods toFont :: (FontFamily, Int) -> Font #  | |
| FontDesignator (FontFamily, FontSlant, Int) | |
Defined in HTk.Kernel.Font Methods toFont :: (FontFamily, FontSlant, Int) -> Font #  | |
| FontDesignator (FontFamily, FontWeight, Int) | |
Defined in HTk.Kernel.Font Methods toFont :: (FontFamily, FontWeight, Int) -> Font #  | |
data FontFamily #
Instances
| Read FontFamily | |
Defined in HTk.Kernel.Font Methods readsPrec :: Int -> ReadS FontFamily readList :: ReadS [FontFamily] readPrec :: ReadPrec FontFamily readListPrec :: ReadPrec [FontFamily]  | |
| Show FontFamily | |
Defined in HTk.Kernel.Font Methods showsPrec :: Int -> FontFamily -> ShowS show :: FontFamily -> String showList :: [FontFamily] -> ShowS  | |
| FontDesignator FontFamily | |
Defined in HTk.Kernel.Font Methods toFont :: FontFamily -> Font #  | |
| GUIValue FontFamily | |
Defined in HTk.Kernel.Font Methods cdefault :: FontFamily # toGUIValue :: FontFamily -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe FontFamily # fromGUIValue :: GUIVALUE -> FontFamily #  | |
| FontDesignator (FontFamily, Int) | |
Defined in HTk.Kernel.Font Methods toFont :: (FontFamily, Int) -> Font #  | |
| FontDesignator (FontFamily, FontSlant, Int) | |
Defined in HTk.Kernel.Font Methods toFont :: (FontFamily, FontSlant, Int) -> Font #  | |
| FontDesignator (FontFamily, FontWeight, Int) | |
Defined in HTk.Kernel.Font Methods toFont :: (FontFamily, FontWeight, Int) -> Font #  | |
Instances
| Read FontSlant | |
Defined in HTk.Kernel.Font  | |
| Show FontSlant | |
| GUIValue FontSlant | |
Defined in HTk.Kernel.Font Methods toGUIValue :: FontSlant -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe FontSlant # fromGUIValue :: GUIVALUE -> FontSlant #  | |
| FontDesignator (FontFamily, FontSlant, Int) | |
Defined in HTk.Kernel.Font Methods toFont :: (FontFamily, FontSlant, Int) -> Font #  | |
data FontSpacing #
Constructors
| MonoSpace | |
| Proportional | 
Instances
| Read FontSpacing | |
Defined in HTk.Kernel.Font Methods readsPrec :: Int -> ReadS FontSpacing readList :: ReadS [FontSpacing] readPrec :: ReadPrec FontSpacing readListPrec :: ReadPrec [FontSpacing]  | |
| Show FontSpacing | |
Defined in HTk.Kernel.Font Methods showsPrec :: Int -> FontSpacing -> ShowS show :: FontSpacing -> String showList :: [FontSpacing] -> ShowS  | |
| GUIValue FontSpacing | |
Defined in HTk.Kernel.Font Methods cdefault :: FontSpacing # toGUIValue :: FontSpacing -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe FontSpacing # fromGUIValue :: GUIVALUE -> FontSpacing #  | |
data FontWeight #
Constructors
| NormalWeight | |
| Medium | |
| Bold | 
Instances
| Read FontWeight | |
Defined in HTk.Kernel.Font Methods readsPrec :: Int -> ReadS FontWeight readList :: ReadS [FontWeight] readPrec :: ReadPrec FontWeight readListPrec :: ReadPrec [FontWeight]  | |
| Show FontWeight | |
Defined in HTk.Kernel.Font Methods showsPrec :: Int -> FontWeight -> ShowS show :: FontWeight -> String showList :: [FontWeight] -> ShowS  | |
| GUIValue FontWeight | |
Defined in HTk.Kernel.Font Methods cdefault :: FontWeight # toGUIValue :: FontWeight -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe FontWeight # fromGUIValue :: GUIVALUE -> FontWeight #  | |
| FontDesignator (FontFamily, FontWeight, Int) | |
Defined in HTk.Kernel.Font Methods toFont :: (FontFamily, FontWeight, Int) -> Font #  | |
Constructors
| NormalWidth | |
| Condensed | |
| Narrow | 
Instances
| Read FontWidth | |
Defined in HTk.Kernel.Font  | |
| Show FontWidth | |
| GUIValue FontWidth | |
Defined in HTk.Kernel.Font Methods toGUIValue :: FontWidth -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe FontWidth # fromGUIValue :: GUIVALUE -> FontWidth #  | |
Constructors
| XFont | |
| XFontAlias String | |
Instances
| Read XFont | |
Defined in HTk.Kernel.Font  | |
| Show XFont | |
| FontDesignator XFont | |
Defined in HTk.Kernel.Font  | |
| GUIValue XFont | |
Defined in HTk.Kernel.Font Methods toGUIValue :: XFont -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe XFont # fromGUIValue :: GUIVALUE -> XFont #  | |
Instances
| Read GUIVALUE | |
Defined in HTk.Kernel.GUIValue  | |
| Show GUIVALUE | |
| GUIValue GUIVALUE | |
Defined in HTk.Kernel.GUIValue Methods toGUIValue :: GUIVALUE -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe GUIVALUE # fromGUIValue :: GUIVALUE -> GUIVALUE #  | |
class (Show a, Read a) => GUIValue a where #
Minimal complete definition
Methods
toGUIValue :: a -> GUIVALUE #
maybeGUIValue :: GUIVALUE -> Maybe a #
fromGUIValue :: GUIVALUE -> a #
Instances
Constructors
| RawData String | 
Instances
| Read RawData | |
Defined in HTk.Kernel.GUIValue  | |
| Show RawData | |
| GUIValue RawData | |
Defined in HTk.Kernel.GUIValue Methods toGUIValue :: RawData -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe RawData # fromGUIValue :: GUIVALUE -> RawData #  | |
Constructors
| TkCommand String | 
Instances
| Read TkCommand | |
Defined in HTk.Kernel.GUIValue  | |
| Show TkCommand | |
| GUIValue TkCommand | |
Defined in HTk.Kernel.GUIValue Methods toGUIValue :: TkCommand -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe TkCommand # fromGUIValue :: GUIVALUE -> TkCommand #  | |
Constructors
| Distance Int | 
Instances
data GridPackOption #
Constructors
| Column Int | |
| Row Int | |
| GridPos (Int, Int) | |
| Sticky StickyKind | |
| Columnspan Int | |
| Rowspan Int | |
| GridPadX Int | |
| GridPadY Int | |
| GridIPadX Int | |
| GridIPadY Int | 
Instances
| Show GridPackOption | |
Defined in HTk.Kernel.GridPackOptions Methods showsPrec :: Int -> GridPackOption -> ShowS show :: GridPackOption -> String showList :: [GridPackOption] -> ShowS  | |
data StickyKind #
Instances
| Show StickyKind | |
Defined in HTk.Kernel.GridPackOptions Methods showsPrec :: Int -> StickyKind -> ShowS show :: StickyKind -> String showList :: [StickyKind] -> ShowS  | |
data PackOption #
Constructors
| Side SideSpec | |
| Fill FillSpec | |
| Expand Toggle | |
| IPadX Distance | |
| IPadY Distance | |
| PadX Distance | |
| PadY Distance | |
| Anchor Anchor | 
Instances
| Show PackOption | |
Defined in HTk.Kernel.PackOptions Methods showsPrec :: Int -> PackOption -> ShowS show :: PackOption -> String showList :: [PackOption] -> ShowS  | |
data AbstractWidget #
Constructors
| NONE | 
Instances
| Container AbstractWidget | |
Defined in HTk.Kernel.Packer  | |
| GUIObject AbstractWidget | |
Defined in HTk.Kernel.Packer Methods toGUIObject :: AbstractWidget -> GUIOBJECT cname :: AbstractWidget -> String cset :: GUIValue a => AbstractWidget -> ConfigID -> a -> IO AbstractWidget cget :: GUIValue a => AbstractWidget -> ConfigID -> IO a  | |
class GUIObject a => Container a #
Instances
| Container Box | |
Defined in HTk.Containers.Box  | |
| Container Frame | |
Defined in HTk.Containers.Frame  | |
| Container Toplevel | |
Defined in HTk.Containers.Toplevel  | |
| Container AbstractWidget | |
Defined in HTk.Kernel.Packer  | |
| Container LabelFrame | |
Defined in HTk.Tix.LabelFrame  | |
| Container NoteBookPage | |
Defined in HTk.Tix.NoteBook  | |
| Container Pane | |
Defined in HTk.Tix.PanedWindow  | |
| Container HTk | |
Defined in HTk.Toplevel.HTk  | |
| Container Canvas | |
Defined in HTk.Widgets.Canvas  | |
| Container Editor | |
Defined in HTk.Widgets.Editor  | |
Instances
| Enum Alignment | |
Defined in HTk.Kernel.Resources  | |
| Eq Alignment | |
| Ord Alignment | |
Defined in HTk.Kernel.Resources  | |
| Read Alignment | |
Defined in HTk.Kernel.Resources  | |
| Show Alignment | |
| GUIValue Alignment | |
Defined in HTk.Kernel.Resources Methods toGUIValue :: Alignment -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe Alignment # fromGUIValue :: GUIVALUE -> Alignment #  | |
Instances
| Enum Anchor | |
Defined in HTk.Kernel.Resources  | |
| Eq Anchor | |
| Ord Anchor | |
| Read Anchor | |
Defined in HTk.Kernel.Resources  | |
| Show Anchor | |
| GUIValue Anchor | |
Defined in HTk.Kernel.Resources Methods toGUIValue :: Anchor -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe Anchor # fromGUIValue :: GUIVALUE -> Anchor #  | |
type CreationConfig w = IO String #
data Flexibility #
Constructors
| JustLeft | |
| JustCenter | |
| JustRight | 
Instances
| Enum Justify | |
Defined in HTk.Kernel.Resources  | |
| Eq Justify | |
| Ord Justify | |
| Read Justify | |
Defined in HTk.Kernel.Resources  | |
| Show Justify | |
| GUIValue Justify | |
Defined in HTk.Kernel.Resources Methods toGUIValue :: Justify -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe Justify # fromGUIValue :: GUIVALUE -> Justify #  | |
data Orientation #
Constructors
| Horizontal | |
| Vertical | 
Instances
Instances
| Enum Relief | |
Defined in HTk.Kernel.Resources  | |
| Eq Relief | |
| Ord Relief | |
| Read Relief | |
Defined in HTk.Kernel.Resources  | |
| Show Relief | |
| GUIValue Relief | |
Defined in HTk.Kernel.Resources Methods toGUIValue :: Relief -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe Relief # fromGUIValue :: GUIVALUE -> Relief #  | |
Instances
| Enum State | |
| Eq State | |
| Ord State | |
| Read State | |
Defined in HTk.Kernel.Resources  | |
| Show State | |
| GUIValue State | |
Defined in HTk.Kernel.Resources Methods toGUIValue :: State -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe State # fromGUIValue :: GUIVALUE -> State #  | |
Instances
| Eq Toggle | |
| Ord Toggle | |
| Read Toggle | |
Defined in HTk.Kernel.Resources  | |
| Show Toggle | |
| GUIValue Toggle | |
Defined in HTk.Kernel.Resources Methods toGUIValue :: Toggle -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe Toggle # fromGUIValue :: GUIVALUE -> Toggle #  | |
class GUIObject w => HasVariable w where #
Minimal complete definition
Nothing
Methods
variable :: TkVariable v -> Config w #
Instances
| HasVariable MenuCheckButton | |
Defined in HTk.Menuitems.MenuCheckButton Methods variable :: TkVariable v -> Config MenuCheckButton #  | |
| HasVariable MenuRadioButton | |
Defined in HTk.Menuitems.MenuRadioButton Methods variable :: TkVariable v -> Config MenuRadioButton #  | |
| HasVariable (CheckButton a) | |
Defined in HTk.Widgets.CheckButton Methods variable :: TkVariable v -> Config (CheckButton a) #  | |
| HasVariable (Entry a) | |
Defined in HTk.Widgets.Entry Methods variable :: TkVariable v -> Config (Entry a) #  | |
| HasVariable (RadioButton a) | |
Defined in HTk.Widgets.RadioButton Methods variable :: TkVariable v -> Config (RadioButton a) #  | |
newtype GUIValue a => TkVariable a #
Constructors
| TkVariable ObjectID | 
class GUIObject w => HasTooltip w where #
Minimal complete definition
Nothing
Instances
Constructors
| WishEvent [WishEventModifier] WishEventType | 
Instances
| Eq WishEvent | |
| Ord WishEvent | |
Defined in HTk.Kernel.Wish  | |
| Show WishEvent | |
data WishEventModifier #
Constructors
| Control | |
| Shift | |
| Lock | |
| CommandKey | |
| Meta | |
| M | |
| Alt | |
| Mod1 | |
| Mod2 | |
| Mod3 | |
| Mod4 | |
| Mod5 | |
| Button1 | |
| Button2 | |
| Button3 | |
| Button4 | |
| Button5 | |
| Double | |
| Triple | 
Instances
| Eq WishEventModifier | |
Defined in HTk.Kernel.Wish Methods (==) :: WishEventModifier -> WishEventModifier -> Bool (/=) :: WishEventModifier -> WishEventModifier -> Bool  | |
| Ord WishEventModifier | |
Defined in HTk.Kernel.Wish Methods compare :: WishEventModifier -> WishEventModifier -> Ordering (<) :: WishEventModifier -> WishEventModifier -> Bool (<=) :: WishEventModifier -> WishEventModifier -> Bool (>) :: WishEventModifier -> WishEventModifier -> Bool (>=) :: WishEventModifier -> WishEventModifier -> Bool max :: WishEventModifier -> WishEventModifier -> WishEventModifier min :: WishEventModifier -> WishEventModifier -> WishEventModifier  | |
| Show WishEventModifier | |
Defined in HTk.Kernel.Wish Methods showsPrec :: Int -> WishEventModifier -> ShowS show :: WishEventModifier -> String showList :: [WishEventModifier] -> ShowS  | |
data WishEventType #
Constructors
| Activate | |
| ButtonPress (Maybe BNo) | |
| ButtonRelease (Maybe BNo) | |
| Circulate | |
| Colormap | |
| Configure | |
| Deactivate | |
| Destroy | |
| Enter | |
| Expose | |
| FocusIn | |
| FocusOut | |
| Gravity | |
| KeyPress (Maybe KeySym) | |
| KeyRelease (Maybe KeySym) | |
| Motion | |
| Leave | |
| Map | |
| Property | |
| Reparent | |
| Unmap | |
| Visibility | 
Instances
| Eq WishEventType | |
Defined in HTk.Kernel.Wish  | |
| Ord WishEventType | |
Defined in HTk.Kernel.Wish Methods compare :: WishEventType -> WishEventType -> Ordering (<) :: WishEventType -> WishEventType -> Bool (<=) :: WishEventType -> WishEventType -> Bool (>) :: WishEventType -> WishEventType -> Bool (>=) :: WishEventType -> WishEventType -> Bool max :: WishEventType -> WishEventType -> WishEventType min :: WishEventType -> WishEventType -> WishEventType  | |
| Show WishEventType | |
Defined in HTk.Kernel.Wish Methods showsPrec :: Int -> WishEventType -> ShowS show :: WishEventType -> String showList :: [WishEventType] -> ShowS  | |
class GUIObject w => HasMenu w where #
Minimal complete definition
Nothing
Instances
| (Window w, GUIObject w) => HasMenu w | |
Defined in HTk.Menuitems.Menu  | |
| HasMenu MenuCascade | |
Defined in HTk.Menuitems.MenuCascade Methods menu :: Menu -> Config MenuCascade #  | |
| HasMenu MenuButton | |
Defined in HTk.Widgets.MenuButton Methods menu :: Menu -> Config MenuButton #  | |
Constructors
| Menu GUIOBJECT (Ref Int) | 
Instances
| Eq Menu | |
| Destroyable Menu | |
Defined in HTk.Menuitems.Menu  | |
| Synchronized Menu | |
Defined in HTk.Menuitems.Menu Methods synchronize :: Menu -> IO b -> IO b #  | |
| Widget Menu | |
| HasBorder Menu | |
| HasColour Menu | |
| HasFont Menu | |
Defined in HTk.Menuitems.Menu  | |
| GUIObject Menu | |
data MenuCascade #
Instances
data MenuCheckButton #
Instances
data MenuCommand #
Instances
data MenuRadioButton #
Instances
data MenuSeparator #
Instances
data EmbeddedTextWin #
Instances
| Eq EmbeddedTextWin | |
Defined in HTk.Textitems.EmbeddedTextWin Methods (==) :: EmbeddedTextWin -> EmbeddedTextWin -> Bool (/=) :: EmbeddedTextWin -> EmbeddedTextWin -> Bool  | |
| Destroyable EmbeddedTextWin | |
Defined in HTk.Textitems.EmbeddedTextWin Methods destroy :: EmbeddedTextWin -> IO () #  | |
| Synchronized EmbeddedTextWin | |
Defined in HTk.Textitems.EmbeddedTextWin Methods synchronize :: EmbeddedTextWin -> IO b -> IO b #  | |
| GUIObject EmbeddedTextWin | |
Defined in HTk.Textitems.EmbeddedTextWin Methods toGUIObject :: EmbeddedTextWin -> GUIOBJECT cname :: EmbeddedTextWin -> String cset :: GUIValue a => EmbeddedTextWin -> ConfigID -> a -> IO EmbeddedTextWin cget :: GUIValue a => EmbeddedTextWin -> ConfigID -> IO a  | |
| HasIndex Editor EmbeddedTextWin BaseIndex | |
Defined in HTk.Textitems.EmbeddedTextWin Methods getBaseIndex :: Editor -> EmbeddedTextWin -> IO BaseIndex #  | |
Instances
| Enum Gravity | |
Defined in HTk.Textitems.Mark  | |
| Eq Gravity | |
| Ord Gravity | |
| Read Gravity | |
Defined in HTk.Textitems.Mark  | |
| Show Gravity | |
| GUIValue Gravity | |
Defined in HTk.Textitems.Mark Methods toGUIValue :: Gravity -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe Gravity # fromGUIValue :: GUIVALUE -> Gravity #  | |
Instances
| Eq TextTag | |
| Destroyable TextTag | |
Defined in HTk.Textitems.TextTag  | |
| Synchronized TextTag | |
Defined in HTk.Textitems.TextTag Methods synchronize :: TextTag -> IO b -> IO b #  | |
| HasBorder TextTag | |
| HasColour TextTag | |
| HasFont TextTag | |
Defined in HTk.Textitems.TextTag  | |
| HasJustify TextTag | |
Defined in HTk.Textitems.TextTag  | |
| HasLineSpacing TextTag | |
Defined in HTk.Textitems.TextTag  | |
| HasTabulators TextTag | |
| GUIObject TextTag | |
| HasIndex Editor (TextTag, First) BaseIndex | |
Defined in HTk.Textitems.TextTag  | |
| HasIndex Editor (TextTag, Last) BaseIndex | |
Defined in HTk.Textitems.TextTag  | |
data LabelFrame #
Instances
Constructors
| TopLabel | |
| LeftLabel | |
| RightLabel | |
| BottomLabel | |
| NoLabel | |
| AcrossTopLabel | 
Instances
| Read LabelSide | |
Defined in HTk.Tix.LabelFrame  | |
| Show LabelSide | |
| GUIValue LabelSide | |
Defined in HTk.Tix.LabelFrame Methods toGUIValue :: LabelSide -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe LabelSide # fromGUIValue :: GUIVALUE -> LabelSide #  | |
Instances
| Eq NoteBook | |
| Destroyable NoteBook | |
Defined in HTk.Tix.NoteBook  | |
| Synchronized NoteBook | |
Defined in HTk.Tix.NoteBook Methods synchronize :: NoteBook -> IO b -> IO b #  | |
| Widget NoteBook | |
| HasSize NoteBook | |
| GUIObject NoteBook | |
data NoteBookPage #
Instances
Instances
| Eq Pane | |
| Destroyable Pane | |
Defined in HTk.Tix.PanedWindow  | |
| Synchronized Pane | |
Defined in HTk.Tix.PanedWindow Methods synchronize :: Pane -> IO b -> IO b #  | |
| Widget Pane | |
| HasColour Pane | |
| Container Pane | |
Defined in HTk.Tix.PanedWindow  | |
| GUIObject Pane | |
data PanedWindow #
Instances
Instances
| Eq HTk | |
| Destroyable HTk | |
Defined in HTk.Toplevel.HTk  | |
| Synchronized HTk | |
Defined in HTk.Toplevel.HTk Methods synchronize :: HTk -> IO b -> IO b #  | |
| Window HTk | |
Defined in HTk.Toplevel.HTk Methods putWinOnTop :: HTk -> IO () # putWinAtBottom :: HTk -> IO () # screen :: Display -> Config HTk # getScreen :: HTk -> IO Display # getClassName :: HTk -> IO String # getWindowState :: HTk -> IO WindowState # aspectRatio :: AspectRatio -> Config HTk # getAspectRatio :: HTk -> IO AspectRatio # positionFrom :: Whom -> Config HTk # getPositionFrom :: HTk -> IO Whom # sizeFrom :: Whom -> Config HTk # getSizeFrom :: HTk -> IO Whom #  | |
| Container HTk | |
Defined in HTk.Toplevel.HTk  | |
| GUIObject HTk | |
| GUIValue v => HasValue HTk v | |
Instances
| Eq Button | |
| Destroyable Button | |
Defined in HTk.Widgets.Button  | |
| Synchronized Button | |
Defined in HTk.Widgets.Button Methods synchronize :: Button -> IO b -> IO b #  | |
| HasBitMap Button | |
Defined in HTk.Widgets.Button  | |
| HasPhoto Button | |
| Widget Button | |
| ButtonWidget Button | |
| HasAnchor Button | |
| HasBorder Button | |
| HasColour Button | |
| HasEnable Button | |
| HasFont Button | |
Defined in HTk.Widgets.Button  | |
| HasJustify Button | |
Defined in HTk.Widgets.Button  | |
| HasSize Button | |
| HasUnderline Button | |
Defined in HTk.Widgets.Button Methods underline :: Int -> Config Button # getUnderline :: Button -> IO Int # wraplength :: Int -> Config Button # getWraplength :: Button -> IO Int #  | |
| HasCommand Button | |
Defined in HTk.Widgets.Button  | |
| HasTooltip Button | |
Defined in HTk.Widgets.Button  | |
| GUIObject Button | |
| GUIValue v => HasText Button v | |
Instances
| Eq Canvas | |
| Destroyable Canvas | |
Defined in HTk.Widgets.Canvas  | |
| Synchronized Canvas | |
Defined in HTk.Widgets.Canvas Methods synchronize :: Canvas -> IO b -> IO b #  | |
| HasPostscript Canvas | |
Defined in HTk.Widgets.Canvas Methods postscript :: Canvas -> [CreationConfig PostScript] -> IO () #  | |
| Widget Canvas | |
| HasBorder Canvas | |
| HasColour Canvas | |
| HasEnable Canvas | |
| HasSize Canvas | |
| Container Canvas | |
Defined in HTk.Widgets.Canvas  | |
| HasTooltip Canvas | |
Defined in HTk.Widgets.Canvas  | |
| HasScroller Canvas | |
Defined in HTk.Widgets.Canvas Methods isWfOrientation :: Canvas -> Orientation -> Bool # scrollbar :: Orientation -> ScrollBar -> Config Canvas # moveto :: Orientation -> Canvas -> Fraction -> IO () # scroll :: Orientation -> Canvas -> Int -> ScrollUnit -> IO () #  | |
| GUIObject Canvas | |
| GUIObject c => HasBBox Canvas c | |
type ScrollRegion = (Position, Position) #
data CheckButton a #
Instances
data GUIValue a => ComboBox a #
Instances
| GUIValue a => Eq (ComboBox a) | |
| GUIValue a => Destroyable (ComboBox a) | |
Defined in HTk.Widgets.ComboBox  | |
| GUIValue a => Synchronized (ComboBox a) | |
Defined in HTk.Widgets.ComboBox Methods synchronize :: ComboBox a -> IO b -> IO b #  | |
| GUIValue a => Widget (ComboBox a) | |
| GUIValue a => HasAnchor (ComboBox a) | |
| GUIValue a => HasBorder (ComboBox a) | |
| GUIValue a => HasColour (ComboBox a) | |
| GUIValue a => HasEnable (ComboBox a) | |
| GUIValue a => HasSize (ComboBox a) | |
| GUIValue a => GUIObject (ComboBox a) | |
| (GUIValue a, GUIValue [a]) => HasValue (ComboBox a) [a] | |
Instances
class GUIObject w => HasLineSpacing w where #
Minimal complete definition
Nothing
Methods
spaceAbove :: Distance -> Config w #
getSpaceAbove :: w -> IO Distance #
spaceWrap :: Distance -> Config w #
getSpaceWrap :: w -> IO Distance #
spaceBelow :: Distance -> Config w #
getSpaceBelow :: w -> IO Distance #
Instances
| HasLineSpacing TextTag | |
Defined in HTk.Textitems.TextTag  | |
| HasLineSpacing Editor | |
Defined in HTk.Widgets.Editor  | |
class GUIObject w => HasTabulators w where #
Minimal complete definition
Nothing
Instances
data IndexModifier #
Constructors
| ForwardChars Int | |
| BackwardChars Int | |
| ForwardLines Int | |
| BackwardLines Int | |
| LineStart | |
| LineEnd | |
| WordStart | |
| WordEnd | 
Instances
| Show IndexModifier | |
Defined in HTk.Widgets.Editor Methods showsPrec :: Int -> IndexModifier -> ShowS show :: IndexModifier -> String showList :: [IndexModifier] -> ShowS  | |
| HasIndex Editor i BaseIndex => HasIndex Editor (i, [IndexModifier]) BaseIndex | |
Defined in HTk.Widgets.Editor Methods getBaseIndex :: Editor -> (i, [IndexModifier]) -> IO BaseIndex #  | |
| HasIndex Editor i BaseIndex => HasIndex Editor (i, IndexModifier) BaseIndex | |
Defined in HTk.Widgets.Editor Methods getBaseIndex :: Editor -> (i, IndexModifier) -> IO BaseIndex #  | |
newtype IndexModifiers #
Constructors
| IndexModifiers [IndexModifier] | 
Instances
| Show IndexModifiers | |
Defined in HTk.Widgets.Editor Methods showsPrec :: Int -> IndexModifiers -> ShowS show :: IndexModifiers -> String showList :: [IndexModifiers] -> ShowS  | |
data SearchDirection #
Instances
data SearchMode #
Instances
| Enum SearchMode | |
Defined in HTk.Widgets.Editor Methods succ :: SearchMode -> SearchMode pred :: SearchMode -> SearchMode toEnum :: Int -> SearchMode fromEnum :: SearchMode -> Int enumFrom :: SearchMode -> [SearchMode] enumFromThen :: SearchMode -> SearchMode -> [SearchMode] enumFromTo :: SearchMode -> SearchMode -> [SearchMode] enumFromThenTo :: SearchMode -> SearchMode -> SearchMode -> [SearchMode]  | |
| Eq SearchMode | |
Defined in HTk.Widgets.Editor  | |
| Ord SearchMode | |
Defined in HTk.Widgets.Editor Methods compare :: SearchMode -> SearchMode -> Ordering (<) :: SearchMode -> SearchMode -> Bool (<=) :: SearchMode -> SearchMode -> Bool (>) :: SearchMode -> SearchMode -> Bool (>=) :: SearchMode -> SearchMode -> Bool max :: SearchMode -> SearchMode -> SearchMode min :: SearchMode -> SearchMode -> SearchMode  | |
| Show SearchMode | |
Defined in HTk.Widgets.Editor Methods showsPrec :: Int -> SearchMode -> ShowS show :: SearchMode -> String showList :: [SearchMode] -> ShowS  | |
data SearchSwitch #
Constructors
| SearchSwitch | |
Fields 
  | |
Instances
| Show SearchSwitch | |
Defined in HTk.Widgets.Editor Methods showsPrec :: Int -> SearchSwitch -> ShowS show :: SearchSwitch -> String showList :: [SearchSwitch] -> ShowS  | |
Instances
| Enum WrapMode | |
Defined in HTk.Widgets.Editor  | |
| Eq WrapMode | |
| Ord WrapMode | |
Defined in HTk.Widgets.Editor  | |
| Read WrapMode | |
Defined in HTk.Widgets.Editor  | |
| Show WrapMode | |
| GUIValue WrapMode | |
Defined in HTk.Widgets.Editor Methods toGUIValue :: WrapMode -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe WrapMode # fromGUIValue :: GUIVALUE -> WrapMode #  | |
Instances
Instances
| Eq Label | |
| Destroyable Label | |
Defined in HTk.Widgets.Label  | |
| Synchronized Label | |
Defined in HTk.Widgets.Label Methods synchronize :: Label -> IO b -> IO b #  | |
| HasBitMap Label | |
Defined in HTk.Widgets.Label  | |
| HasPhoto Label | |
| Widget Label | |
| HasAnchor Label | |
| HasBorder Label | |
| HasColour Label | |
| HasFont Label | |
Defined in HTk.Widgets.Label  | |
| HasJustify Label | |
Defined in HTk.Widgets.Label  | |
| HasSize Label | |
| HasUnderline Label | |
Defined in HTk.Widgets.Label Methods underline :: Int -> Config Label # getUnderline :: Label -> IO Int # wraplength :: Int -> Config Label # getWraplength :: Label -> IO Int #  | |
| HasTooltip Label | |
Defined in HTk.Widgets.Label  | |
| GUIObject Label | |
| GUIValue b => HasText Label b | |
Instances
data Eq a => ListBoxElem a #
Constructors
| ListBoxElem a | 
Instances
| Eq a => Eq (ListBoxElem a) | |
Defined in HTk.Widgets.ListBox  | |
| (Eq a, GUIValue a, GUIValue [a]) => HasIndex (ListBox a) Int (ListBoxElem a) | |
Defined in HTk.Widgets.ListBox Methods getBaseIndex :: ListBox a -> Int -> IO (ListBoxElem a) #  | |
| (Eq a, GUIValue a) => HasIndex (ListBox [a]) (ListBoxElem a) Int | |
Defined in HTk.Widgets.ListBox Methods getBaseIndex :: ListBox [a] -> ListBoxElem a -> IO Int #  | |
data SelectMode #
Instances
data MenuButton #
Instances
Instances
| Eq Message | |
| Destroyable Message | |
Defined in HTk.Widgets.Message  | |
| Synchronized Message | |
Defined in HTk.Widgets.Message Methods synchronize :: Message -> IO b -> IO b #  | |
| Widget Message | |
| HasAnchor Message | |
| HasBorder Message | |
| HasColour Message | |
| HasFont Message | |
Defined in HTk.Widgets.Message  | |
| HasJustify Message | |
Defined in HTk.Widgets.Message  | |
| HasSize Message | |
| HasTooltip Message | |
Defined in HTk.Widgets.Message  | |
| GUIObject Message | |
| GUIValue b => HasText Message b | |
data OptionMenu a #
Instances
data RadioButton a #
Instances
Instances
| Eq (Scale a) | |
| Destroyable (Scale a) | |
Defined in HTk.Widgets.Scale  | |
| Synchronized (Scale a) | |
Defined in HTk.Widgets.Scale Methods synchronize :: Scale a -> IO b -> IO b #  | |
| HasSlider (Scale a) | |
Defined in HTk.Widgets.Scale Methods repeatInterval :: Int -> Config (Slider (Scale a)) # getRepeatInterval :: Slider (Scale a) -> IO Int # repeatDelay :: Int -> Config (Slider (Scale a)) # getRepeatDelay :: Slider (Scale a) -> IO Int #  | |
| Widget (Scale a) | |
| HasBorder (Scale a) | |
| HasColour (Scale a) | |
| HasEnable (Scale a) | |
| HasFont (Scale a) | |
Defined in HTk.Widgets.Scale  | |
| HasOrientation (Scale a) | |
Defined in HTk.Widgets.Scale  | |
| HasSize (Slider (Scale a)) | |
Defined in HTk.Widgets.Scale  | |
| HasSize (Scale a) | |
| HasTooltip (Scale a) | |
Defined in HTk.Widgets.Scale  | |
| GUIObject (Scale a) | |
| ScaleValue a => HasIncrement (Slider (Scale a)) a | |
Defined in HTk.Widgets.Scale  | |
| ScaleValue a => HasIncrement (Scale a) a | |
Defined in HTk.Widgets.Scale  | |
| GUIValue v => HasText (Scale a) v | |
class (Num a, GUIValue a) => ScaleValue a where #
Instances
| ScaleValue Double | |
Defined in HTk.Widgets.Scale  | |
class Widget w => HasScroller w where #
Minimal complete definition
Nothing
Methods
isWfOrientation :: w -> Orientation -> Bool #
scrollbar :: Orientation -> ScrollBar -> Config w #
moveto :: Orientation -> w -> Fraction -> IO () #
scroll :: Orientation -> w -> Int -> ScrollUnit -> IO () #
view :: Orientation -> w -> IO (Fraction, Fraction) #
Instances
Instances
| Eq ScrollBar | |
| Destroyable ScrollBar | |
Defined in HTk.Widgets.ScrollBar  | |
| HasSlider ScrollBar | |
Defined in HTk.Widgets.ScrollBar Methods repeatInterval :: Int -> Config (Slider ScrollBar) # getRepeatInterval :: Slider ScrollBar -> IO Int # repeatDelay :: Int -> Config (Slider ScrollBar) # getRepeatDelay :: Slider ScrollBar -> IO Int #  | |
| Widget ScrollBar | |
| HasBorder ScrollBar | |
| HasColour ScrollBar | |
| HasEnable ScrollBar | |
| HasOrientation ScrollBar | |
Defined in HTk.Widgets.ScrollBar  | |
| HasSize ScrollBar | |
| HasTooltip ScrollBar | |
Defined in HTk.Widgets.ScrollBar  | |
| GUIObject ScrollBar | |
data ScrollBarElem #
Constructors
| Arrow1 | |
| Trough1 | |
| ScrollBarSlider | |
| Trough2 | |
| Arrow2 | 
Instances
data ScrollUnit #
Instances
| Read ScrollUnit | |
Defined in HTk.Widgets.ScrollBar Methods readsPrec :: Int -> ReadS ScrollUnit readList :: ReadS [ScrollUnit] readPrec :: ReadPrec ScrollUnit readListPrec :: ReadPrec [ScrollUnit]  | |
| Show ScrollUnit | |
Defined in HTk.Widgets.ScrollBar Methods showsPrec :: Int -> ScrollUnit -> ShowS show :: ScrollUnit -> String showList :: [ScrollUnit] -> ShowS  | |
| GUIValue ScrollUnit | |
Defined in HTk.Widgets.ScrollBar Methods cdefault :: ScrollUnit # toGUIValue :: ScrollUnit -> GUIVALUE # maybeGUIValue :: GUIVALUE -> Maybe ScrollUnit # fromGUIValue :: GUIVALUE -> ScrollUnit #  | |
newtype MonadWithError (m :: Type -> Type) a #
Constructors
| MonadWithError (m (WithError a)) | 
Instances
| Monad m => Monad (MonadWithError m) | |
Defined in Util.Computation Methods (>>=) :: MonadWithError m a -> (a -> MonadWithError m b) -> MonadWithError m b (>>) :: MonadWithError m a -> MonadWithError m b -> MonadWithError m b return :: a -> MonadWithError m a  | |
| Monad m => Functor (MonadWithError m) | |
Defined in Util.Computation Methods fmap :: (a -> b) -> MonadWithError m a -> MonadWithError m b (<$) :: a -> MonadWithError m b -> MonadWithError m a  | |
| MonadFail m => MonadFail (MonadWithError m) | |
Defined in Util.Computation Methods fail :: String -> MonadWithError m a  | |
| Monad m => Applicative (MonadWithError m) | |
Defined in Util.Computation Methods pure :: a -> MonadWithError m a (<*>) :: MonadWithError m (a -> b) -> MonadWithError m a -> MonadWithError m b liftA2 :: (a -> b -> c) -> MonadWithError m a -> MonadWithError m b -> MonadWithError m c (*>) :: MonadWithError m a -> MonadWithError m b -> MonadWithError m b (<*) :: MonadWithError m a -> MonadWithError m b -> MonadWithError m a  | |
getScrollBars :: HasScroller a => ScrollBox a -> [ScrollBar] #
getScrolledWidget :: (Widget a, HasScroller a) => ScrollBox a -> a #
newScrollBox :: (Widget wid, HasScroller wid, Container par) => par -> (Frame -> IO wid) -> [Config (ScrollBox wid)] -> IO (ScrollBox wid, wid) #
Constructors
| ScrollBox | |
Fields 
  | |
Instances
| Eq (ScrollBox a) | |
| Destroyable (ScrollBox a) | |
Defined in HTk.Toolkit.ScrollBox  | |
| Synchronized (ScrollBox a) | |
Defined in HTk.Toolkit.ScrollBox Methods synchronize :: ScrollBox a -> IO b -> IO b #  | |
| (Widget a, HasScroller a) => Widget (ScrollBox a) | |
| HasBorder (ScrollBox a) | |
| (HasColour a, HasScroller a) => HasColour (ScrollBox a) | |
| HasSize (ScrollBox a) | |
| HasScroller a => HasScroller (ScrollBox a) | |
Defined in HTk.Toolkit.ScrollBox Methods isWfOrientation :: ScrollBox a -> Orientation -> Bool # scrollbar :: Orientation -> ScrollBar -> Config (ScrollBox a) # moveto :: Orientation -> ScrollBox a -> Fraction -> IO () # scroll :: Orientation -> ScrollBox a -> Int -> ScrollUnit -> IO () # view :: Orientation -> ScrollBox a -> IO (Fraction, Fraction) #  | |
| GUIObject (ScrollBox a) | |
doFormList :: String -> [(Form x, String)] -> IO (Event (WithError x), IO ()) #
doFormMust :: String -> Form value -> IO value #
editableTextForm :: [Config Editor] -> Form String #
editableTextForm0 :: [Config Editor] -> Form String #
guardFormIO :: (x -> IO Bool) -> String -> Form x -> Form x #
guardNothing :: String -> Form (Maybe x) -> Form x #
mapMakeFormEntry :: FormValue value2 => (value1 -> value2) -> (value2 -> value1) -> Frame -> value1 -> IO (EnteredForm value1) #
newFormEntry :: (FormLabel label, FormValue value) => label -> value -> Form value #
newFormMenu :: FormLabel label => label -> HTkMenu value -> Form (Maybe value) #
newFormOptionMenu :: GUIValue a => [a] -> Form a #
newFormOptionMenu2 :: (Eq a, GUIValue a) => [(a, b)] -> Form b #
data EmptyLabel #
Constructors
| EmptyLabel | 
Instances
| FormLabel EmptyLabel | |
Defined in HTk.Toolkit.SimpleForm Methods formLabel :: Frame -> EmptyLabel -> IO (IO ()) #  | |
Instances
| FormLabel String | |
Defined in HTk.Toolkit.SimpleForm  | |
| FormLabel Image | |
Defined in HTk.Toolkit.SimpleForm  | |
| FormLabel EmptyLabel | |
Defined in HTk.Toolkit.SimpleForm Methods formLabel :: Frame -> EmptyLabel -> IO (IO ()) #  | |
| FormLabel WrappedFormLabel | |
Defined in HTk.Toolkit.SimpleForm Methods formLabel :: Frame -> WrappedFormLabel -> IO (IO ()) #  | |
class FormTextField value where #
Instances
| (Num a, Show a, Read a) => FormTextField a | |
Defined in HTk.Toolkit.SimpleForm  | |
| FormTextField String | |
Defined in HTk.Toolkit.SimpleForm  | |
class FormTextFieldIO value where #
Instances
| FormTextField value => FormTextFieldIO value | |
Defined in HTk.Toolkit.SimpleForm  | |
| FormTextFieldIO value => FormTextFieldIO (Maybe value) | |
Defined in HTk.Toolkit.SimpleForm Methods makeFormStringIO :: Maybe value -> IO String # readFormStringIO :: String -> IO (WithError (Maybe value)) #  | |
Methods
makeFormEntry :: Frame -> value -> IO (EnteredForm value) #
Instances
| FormValue Bool | |
Defined in HTk.Toolkit.SimpleForm Methods makeFormEntry :: Frame -> Bool -> IO (EnteredForm Bool) #  | |
| FormValue () | |
Defined in HTk.Toolkit.SimpleForm Methods makeFormEntry :: Frame -> () -> IO (EnteredForm ()) #  | |
| FormTextFieldIO value => FormValue value | |
Defined in HTk.Toolkit.SimpleForm Methods makeFormEntry :: Frame -> value -> IO (EnteredForm value) #  | |
| FormTextFieldIO value => FormValue (Password value) | |
Defined in HTk.Toolkit.SimpleForm Methods makeFormEntry :: Frame -> Password value -> IO (EnteredForm (Password value)) #  | |
| (HasConfigRadioButton value, Bounded value, Enum value) => FormValue (Radio value) | |
Defined in HTk.Toolkit.SimpleForm Methods makeFormEntry :: Frame -> Radio value -> IO (EnteredForm (Radio value)) #  | |
class HasConfigRadioButton value where #
Methods
configRadioButton :: value -> Config (RadioButton Int) #
Constructors
| Password value | 
Instances
| FormTextFieldIO value => FormValue (Password value) | |
Defined in HTk.Toolkit.SimpleForm Methods makeFormEntry :: Frame -> Password value -> IO (EnteredForm (Password value)) #  | |
Instances
| (HasConfigRadioButton value, Bounded value, Enum value) => FormValue (Radio value) | |
Defined in HTk.Toolkit.SimpleForm Methods makeFormEntry :: Frame -> Radio value -> IO (EnteredForm (Radio value)) #  | |
| (Monad m, HasBinary x m) => HasBinary (Radio x) m | |
Defined in HTk.Toolkit.SimpleForm  | |
data WrappedFormLabel #
Constructors
| FormLabel label => WrappedFormLabel label | 
Instances
| FormLabel WrappedFormLabel | |
Defined in HTk.Toolkit.SimpleForm Methods formLabel :: Frame -> WrappedFormLabel -> IO (IO ()) #  | |
createTextDisplay :: String -> String -> [Config Editor] -> IO () #