fltkhs-0.8.0.3: FLTK bindings
Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.Base.Tree

Synopsis

Documentation

treeCustom Source #

Arguments

:: Rectangle

The bounds of this Tree

-> Maybe Text

The Tree label

-> Maybe (Ref Tree -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Tree)

Optional custom widget functions

-> IO (Ref Tree) 

Hierarchy

Functions

add :: Ref TreeBase -> Text -> IO (Maybe (Ref TreeItem))

addAt:: (Parent a TreeItem) => Ref TreeBase -> Text -> Ref a -> IO (Maybe (Ref TreeItem))

clear :: Ref TreeBase -> IO ()

clearChildren:: (Parent a TreeItem) => Ref TreeBase -> Ref a -> IO ()

close :: Ref TreeBase -> TreeItemLocator -> IO ()

closeAndCallback :: Ref TreeBase -> TreeItemLocator -> Bool -> IO ()

deselect :: Ref TreeBase -> TreeItemLocator -> IO (Either NoChange ())

deselectAll :: Ref TreeBase -> IO ()

deselectAllAndCallback :: Ref TreeBase -> Maybe (Ref TreeItem) -> Bool -> IO ()

deselectAndCallback :: Ref TreeBase -> TreeItemLocator -> Bool -> IO ()

destroy :: Ref TreeBase -> IO ()

display :: Ref TreeBase -> Ref TreeItem -> IO ()

displayed :: Ref TreeBase -> Ref TreeItem -> IO (Bool)

draw :: Ref TreeBase -> IO ()

findItem :: Ref TreeBase -> Text -> IO (Maybe (Ref TreeItem))

firstSelectedItem :: Ref TreeBase -> IO (Maybe (Ref TreeItem))

firstVisible :: Ref TreeBase -> IO (Maybe (Ref TreeItem))

getCallbackItem :: Ref TreeBase -> IO (Maybe (Ref TreeItem))

getCallbackReason :: Ref TreeBase -> IO (TreeReasonType)

getCloseicon :: Ref TreeBase -> IO (Maybe (Ref Image))

getConnectorcolor :: Ref TreeBase -> IO (Color)

getConnectorstyle :: Ref TreeBase -> IO (TreeConnector)

getConnectorwidth :: Ref TreeBase -> IO (Int)

getFirst :: Ref TreeBase -> IO (Maybe (Ref TreeItem))

getItemDrawMode :: Ref TreeBase -> IO ([TreeItemDrawMode)]

getItemFocus :: Ref TreeBase -> IO (Maybe (Ref TreeItem))

getItemLabelbgcolor :: Ref TreeBase -> IO (Color)

getItemLabelfgcolor :: Ref TreeBase -> IO (Color)

getItemLabelfont :: Ref TreeBase -> IO (Font)

getItemLabelsize :: Ref TreeBase -> IO (FontSize)

getItemReselectMode :: Ref TreeBase -> IO (TreeItemReselectMode)

getLabelmarginleft :: Ref TreeBase -> IO (Int)

getLast :: Ref TreeBase -> IO (Maybe (Ref TreeItem))

getLinespacing :: Ref TreeBase -> IO (Int)

getMarginbottom :: Ref TreeBase -> IO (Int)

getMarginleft :: Ref TreeBase -> IO (Int)

getMargintop :: Ref TreeBase -> IO (Int)

getOpenchildMarginbottom :: Ref TreeBase -> IO (Int)

getOpenicon :: Ref TreeBase -> IO (Maybe (Ref Image))

getScrollbarSize :: Ref TreeBase -> IO (Int)

getSelectbox :: Ref TreeBase -> IO (Boxtype)

getShowcollapse :: Ref TreeBase -> IO (Bool)

getShowroot :: Ref TreeBase -> IO (Bool)

getSortorder :: Ref TreeBase -> IO (TreeSort)

getUsericon :: Ref TreeBase -> IO (Maybe (Ref Image))

getUsericonmarginleft :: Ref TreeBase -> IO (Int)

getVposition :: Ref TreeBase -> IO (Int)

getWidgetmarginleft :: Ref TreeBase -> IO (Int)

handle :: Ref TreeBase -> Event -> IO (Either UnknownEvent ())

hide :: Ref TreeBase -> IO ()

insert:: (Parent a TreeItem) => Ref TreeBase -> Ref a -> Text -> AtIndex -> IO (Maybe (Ref a))

insertAbove:: (Parent a TreeItem) => Ref TreeBase -> Ref a -> Text -> IO (Maybe (Ref a))

isClose :: Ref TreeBase -> TreeItemLocator -> IO (Bool)

isOpen :: Ref TreeBase -> TreeItemLocator -> IO (Bool)

isScrollbar:: (Parent a WidgetBase) => Ref TreeBase -> Ref a -> IO (Bool)

isSelected :: Ref TreeBase -> TreeItemLocator -> IO (Bool)

isVscrollVisible :: Ref TreeBase -> IO (Bool)

itemClicked :: Ref TreeBase -> IO (Maybe (Ref TreeItem))

itemPathname:: (Parent a TreeItem) => Ref TreeBase -> Ref a -> IO (Maybe Text)

lastSelectedItem :: Ref TreeBase -> IO (Maybe (Ref TreeItem))

lastVisible :: Ref TreeBase -> IO (Maybe (Ref TreeItem))

next :: Ref TreeBase -> IO (Maybe (Ref TreeItem))

nextAfterItem :: Ref TreeBase -> Ref TreeItem -> IO (Maybe (Ref TreeItem))

nextItem :: Ref TreeBase -> Ref TreeItem -> Maybe SearchDirection -> Bool -> IO (Maybe (Ref TreeItem))

nextSelectedItem :: Ref TreeBase -> IO (Maybe (Ref TreeItem))

nextSelectedItemAfterItem :: Ref TreeBase -> Ref TreeItem -> Maybe SearchDirection -> IO (Maybe (Ref TreeItem))

open :: Ref TreeBase -> TreeItemLocator -> IO ()

openAndCallback :: Ref TreeBase -> TreeItemLocator -> Bool -> IO ()

openToggle :: Ref TreeBase -> Ref TreeItem -> IO ()

openToggleAndCallback :: Ref TreeBase -> Ref TreeItem -> Bool -> IO ()

prev :: Ref TreeBase -> IO (Maybe (Ref TreeItem))

prevBeforeItem :: Ref TreeBase -> Ref TreeItem -> IO (Maybe (Ref TreeItem))

recalcTree :: Ref TreeBase -> IO ()

remove :: Ref TreeBase -> Ref TreeItem -> IO (Either TreeItemNotFound ())

resize :: Ref TreeBase -> Rectangle -> IO ()

root :: Ref TreeBase -> IO (Maybe (Ref TreeItem))

rootLabel :: Ref TreeBase -> Text -> IO ()

select :: Ref TreeBase -> TreeItemLocator -> IO (Either NoChange ())

selectAll :: Ref TreeBase -> IO ()

selectAllAndCallback :: Ref TreeBase -> Maybe (Ref TreeItem) -> Bool -> IO ()

selectAndCallback :: Ref TreeBase -> TreeItemLocator -> Bool -> IO ()

selectOnly :: Ref TreeBase -> Ref TreeItem -> IO ()

selectOnlyAndCallback :: Ref TreeBase -> Ref TreeItem -> Bool -> IO ()

selectToggle :: Ref TreeBase -> Ref TreeItem -> IO ()

selectToggleAndCallback :: Ref TreeBase -> Ref TreeItem -> Bool -> IO ()

selectmode :: Ref TreeBase -> IO (TreeSelect)

setCallbackItem:: (Parent a TreeItem) => Ref TreeBase -> Ref a -> IO ()

setCallbackReason :: Ref TreeBase -> TreeReasonType -> IO ()

setCloseicon:: (Parent a Image) => Ref TreeBase -> Maybe( Ref a ) -> IO ()

setConnectorcolor :: Ref TreeBase -> Color -> IO ()

setConnectorstyle :: Ref TreeBase -> TreeConnector -> IO ()

setConnectorwidth :: Ref TreeBase -> Int -> IO ()

setItemDrawMode :: Ref TreeBase -> [TreeItemDrawMode] -> IO ()

setItemFocus :: Ref TreeBase -> Ref TreeItem -> IO ()

setItemLabelbgcolor :: Ref TreeBase -> Color -> IO ()

setItemLabelfgcolor :: Ref TreeBase -> Color -> IO ()

setItemLabelfont :: Ref TreeBase -> Font -> IO ()

setItemLabelsize :: Ref TreeBase -> FontSize -> IO ()

setItemReselectMode :: Ref TreeBase -> TreeItemReselectMode -> IO ()

setLabelmarginleft :: Ref TreeBase -> Int -> IO ()

setLinespacing :: Ref TreeBase -> Int -> IO ()

setMarginbottom :: Ref TreeBase -> Int -> IO ()

setMarginleft :: Ref TreeBase -> Int -> IO ()

setMargintop :: Ref TreeBase -> Int -> IO ()

setOpenchildMarginbottom :: Ref TreeBase -> Int -> IO ()

setOpenicon:: (Parent a Image) => Ref TreeBase -> Maybe( Ref a ) -> IO ()

setScrollbarSize :: Ref TreeBase -> Int -> IO ()

setSelectbox :: Ref TreeBase -> Boxtype -> IO ()

setSelectmode :: Ref TreeBase -> TreeSelect -> IO ()

setShowcollapse :: Ref TreeBase -> Bool -> IO ()

setShowroot :: Ref TreeBase -> Bool -> IO ()

setSortorder :: Ref TreeBase -> TreeSort -> IO ()

setUsericon:: (Parent a Image) => Ref TreeBase -> Maybe( Ref a ) -> IO ()

setUsericonmarginleft :: Ref TreeBase -> Int -> IO ()

setVposition :: Ref TreeBase -> Int -> IO ()

setWidgetmarginleft :: Ref TreeBase -> Int -> IO ()

showItemBottom :: Ref TreeBase -> Ref TreeItem -> IO ()

showItemMiddle :: Ref TreeBase -> Ref TreeItem -> IO ()

showItemTop :: Ref TreeBase -> Ref TreeItem -> IO ()

showItemWithYoff :: Ref TreeBase -> Ref TreeItem -> Maybe Y -> IO ()

showSelf :: Ref TreeBase -> IO ()

showWidget :: Ref TreeBase -> IO ()

Orphan instances

impl ~ IO [TreeItemDrawMode] => Op (GetItemDrawMode ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetItemDrawMode () -> orig -> Ref TreeBase -> impl Source #

impl ~ ([TreeItemDrawMode] -> IO ()) => Op (SetItemDrawMode ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetItemDrawMode () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO TreeItemReselectMode => Op (GetItemReselectMode ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetItemReselectMode () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeItemReselectMode -> IO ()) => Op (SetItemReselectMode ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetItemReselectMode () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Int => Op (GetWidgetmarginleft ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetWidgetmarginleft () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Int -> IO ()) => Op (SetWidgetmarginleft ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetWidgetmarginleft () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Int => Op (GetMarginbottom ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetMarginbottom () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Int -> IO ()) => Op (SetMarginbottom ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetMarginbottom () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO () => Op (RecalcTree ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: RecalcTree () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO TreeReasonType => Op (GetCallbackReason ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetCallbackReason () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeReasonType -> IO ()) => Op (SetCallbackReason ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetCallbackReason () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (GetCallbackItem ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetCallbackItem () -> orig -> Ref TreeBase -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> IO ())) => Op (SetCallbackItem ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetCallbackItem () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Bool => Op (IsVscrollVisible ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: IsVscrollVisible () -> orig -> Ref TreeBase -> impl Source #

(Parent a WidgetBase, impl ~ (Ref a -> IO Bool)) => Op (IsScrollbar ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: IsScrollbar () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Int -> IO ()) => Op (SetVposition ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetVposition () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Int => Op (GetVposition ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetVposition () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (Display ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Display () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (ShowItemBottom ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: ShowItemBottom () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (ShowItemMiddle ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: ShowItemMiddle () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (ShowItemTop ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: ShowItemTop () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> Maybe Y -> IO ()) => Op (ShowItemWithYoff ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: ShowItemWithYoff () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO TreeSelect => Op (Selectmode ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Selectmode () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Color => Op (GetItemLabelfgcolor ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetItemLabelfgcolor () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Font -> IO ()) => Op (SetItemLabelfont ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetItemLabelfont () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (GetItemFocus ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetItemFocus () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (SetItemFocus ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetItemFocus () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Maybe (Ref TreeItem) -> Bool -> IO ()) => Op (DeselectAllAndCallback ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: DeselectAllAndCallback () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Maybe (Ref TreeItem) -> Bool -> IO ()) => Op (SelectAllAndCallback ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SelectAllAndCallback () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> Bool -> IO ()) => Op (SelectToggleAndCallback ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SelectToggleAndCallback () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeItemLocator -> Bool -> IO ()) => Op (SelectAndCallback ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SelectAndCallback () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeItemLocator -> Bool -> IO ()) => Op (CloseAndCallback ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: CloseAndCallback () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> Bool -> IO ()) => Op (OpenToggleAndCallback ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: OpenToggleAndCallback () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeItemLocator -> Bool -> IO ()) => Op (OpenAndCallback ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: OpenAndCallback () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> Maybe SearchDirection -> IO (Maybe (Ref TreeItem))) => Op (NextSelectedItemAfterItem ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: NextSelectedItemAfterItem () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (NextSelectedItem ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: NextSelectedItem () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (LastSelectedItem ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: LastSelectedItem () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (FirstSelectedItem ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: FirstSelectedItem () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (LastVisible ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: LastVisible () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (GetLast ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetLast () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> IO (Maybe (Ref TreeItem))) => Op (PrevBeforeItem ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: PrevBeforeItem () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> Maybe SearchDirection -> Bool -> IO (Maybe (Ref TreeItem))) => Op (NextItem ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: NextItem () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> IO (Maybe (Ref TreeItem))) => Op (NextAfterItem ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: NextAfterItem () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (FirstVisible ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: FirstVisible () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (ItemClicked ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: ItemClicked () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (Root ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Root () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Text -> IO ()) => Op (RootLabel ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: RootLabel () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO () => Op (DeselectAll ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: DeselectAll () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO () => Op (SelectAll ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SelectAll () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (SelectToggle ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SelectToggle () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (OpenToggle ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: OpenToggle () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeItemLocator -> IO Bool) => Op (IsClose ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: IsClose () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeItemLocator -> IO Bool) => Op (IsOpen ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: IsOpen () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeItemLocator -> IO ()) => Op (Close ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Close () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeItemLocator -> IO ()) => Op (Open ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Open () -> orig -> Ref TreeBase -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> Text -> IO (Maybe (Ref a)))) => Op (InsertAbove ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: InsertAbove () -> orig -> Ref TreeBase -> impl Source #

(Parent a TreeItem, impl ~ (Text -> Ref a -> IO (Maybe (Ref TreeItem)))) => Op (AddAt ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: AddAt () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Text -> IO (Maybe (Ref TreeItem))) => Op (FindItem ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: FindItem () -> orig -> Ref TreeBase -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> IO ())) => Op (ClearChildren ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: ClearChildren () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO () => Op (ShowSelf ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: ShowSelf () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeSelect -> IO ()) => Op (SetSelectmode ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetSelectmode () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetShowroot ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetShowroot () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Bool => Op (GetShowroot ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetShowroot () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Boxtype -> IO ()) => Op (SetSelectbox ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetSelectbox () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Boxtype => Op (GetSelectbox ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetSelectbox () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeSort -> IO ()) => Op (SetSortorder ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetSortorder () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO TreeSort => Op (GetSortorder ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetSortorder () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetShowcollapse ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetShowcollapse () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Bool => Op (GetShowcollapse ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetShowcollapse () -> orig -> Ref TreeBase -> impl Source #

(Parent a Image, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetUsericon ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetUsericon () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref Image)) => Op (GetUsericon ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetUsericon () -> orig -> Ref TreeBase -> impl Source #

(Parent a Image, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetCloseicon ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetCloseicon () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref Image)) => Op (GetCloseicon ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetCloseicon () -> orig -> Ref TreeBase -> impl Source #

(Parent a Image, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetOpenicon ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetOpenicon () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref Image)) => Op (GetOpenicon ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetOpenicon () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Int -> IO ()) => Op (SetConnectorwidth ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetConnectorwidth () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Int => Op (GetConnectorwidth ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetConnectorwidth () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeConnector -> IO ()) => Op (SetConnectorstyle ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetConnectorstyle () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO TreeConnector => Op (GetConnectorstyle ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetConnectorstyle () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Color -> IO ()) => Op (SetConnectorcolor ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetConnectorcolor () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Color => Op (GetConnectorcolor ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetConnectorcolor () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Int -> IO ()) => Op (SetLinespacing ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetLinespacing () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Int => Op (GetLinespacing ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetLinespacing () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Int -> IO ()) => Op (SetLabelmarginleft ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetLabelmarginleft () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Int => Op (GetLabelmarginleft ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetLabelmarginleft () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Int -> IO ()) => Op (SetUsericonmarginleft ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetUsericonmarginleft () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Int => Op (GetUsericonmarginleft ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetUsericonmarginleft () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Int -> IO ()) => Op (SetOpenchildMarginbottom ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetOpenchildMarginbottom () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Int => Op (GetOpenchildMarginbottom ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetOpenchildMarginbottom () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Int -> IO ()) => Op (SetMargintop ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetMargintop () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Int => Op (GetMargintop ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetMargintop () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Int -> IO ()) => Op (SetMarginleft ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetMarginleft () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Int => Op (GetMarginleft ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetMarginleft () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Color -> IO ()) => Op (SetItemLabelbgcolor ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetItemLabelbgcolor () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Color => Op (GetItemLabelbgcolor ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetItemLabelbgcolor () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Color -> IO ()) => Op (SetItemLabelfgcolor ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetItemLabelfgcolor () -> orig -> Ref TreeBase -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetItemLabelsize ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetItemLabelsize () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO FontSize => Op (GetItemLabelsize ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetItemLabelsize () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Font => Op (GetItemLabelfont ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetItemLabelfont () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Int -> IO ()) => Op (SetScrollbarSize ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SetScrollbarSize () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO Int => Op (GetScrollbarSize ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetScrollbarSize () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeItemLocator -> Bool -> IO ()) => Op (DeselectAndCallback ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: DeselectAndCallback () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeItemLocator -> IO (Either NoChange ())) => Op (Deselect ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Deselect () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> Bool -> IO ()) => Op (SelectOnlyAndCallback ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SelectOnlyAndCallback () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (SelectOnly ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: SelectOnly () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> IO Bool) => Op (Displayed ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Displayed () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeItemLocator -> IO (Either NoChange ())) => Op (Select ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Select () -> orig -> Ref TreeBase -> impl Source #

impl ~ (TreeItemLocator -> IO Bool) => Op (IsSelected ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: IsSelected () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (Prev ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Prev () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Ref TreeItem -> IO (Either TreeItemNotFound ())) => Op (Remove ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Remove () -> orig -> Ref TreeBase -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> IO (Maybe Text))) => Op (ItemPathname ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: ItemPathname () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO () => Op (Draw ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Draw () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (GetFirst ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: GetFirst () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (Next ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Next () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO () => Op (Clear ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Clear () -> orig -> Ref TreeBase -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> Text -> AtIndex -> IO (Maybe (Ref a)))) => Op (Insert ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Insert () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Text -> IO (Maybe (Ref TreeItem))) => Op (Add ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Add () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Resize () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO () => Op (Hide ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Hide () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO () => Op (ShowWidget ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: ShowWidget () -> orig -> Ref TreeBase -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Handle () -> orig -> Ref TreeBase -> impl Source #

impl ~ IO () => Op (Destroy ()) TreeBase orig impl Source # 
Instance details

Methods

runOp :: Destroy () -> orig -> Ref TreeBase -> impl Source #