fltkhs-0.8.0.2: FLTK bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.TreeItem

Contents

Synopsis

Documentation

newtype TreeItemName Source #

Constructors

TreeItemName Text 

Hierarchy

Hierarchy

Functions

activate :: Ref TreeItem -> IO ()

activateWith :: Ref TreeItem -> Bool -> IO ()

add:: (Parent a TreeItem, Parent b TreePrefs) => Ref TreeItem -> Ref b -> TreeItemLocator -> IO (Maybe (Ref a))

addAt:: (Parent a TreeItem, Parent b TreePrefs) => Ref TreeItem -> Ref b -> [Text] -> Maybe (Ref a) -> IO (Maybe (Ref a))

child :: Ref TreeItem -> AtIndex -> IO (Maybe (Ref WidgetBase))

children :: Ref TreeItem -> IO (Int)

clearChildren :: Ref TreeItem -> IO ()

close :: Ref TreeItem -> IO ()

deparent :: Ref TreeItem -> AtIndex -> IO (Either UnknownError (Ref orig))

deselect :: Ref TreeItem -> IO ()

deselectAll :: Ref TreeItem -> IO (Int)

destroy :: Ref TreeItem -> IO ()

eventOnCollapseIcon:: (Parent a TreePrefs) => Ref TreeItem -> Ref a -> IO (Int)

eventOnLabel:: (Parent a TreePrefs) => Ref TreeItem -> Ref a -> IO (Int)

findChild :: Ref TreeItem -> TreeItemLocator -> IO (Maybe AtIndex)

findClicked:: (Parent a TreePrefs) => Ref TreeItem -> Ref a -> IO (Maybe (Ref TreeItem))

findInChildren :: Ref TreeItem -> [Text] -> IO (Maybe (Ref TreeItem))

findItem :: Ref TreeItem -> [Text] -> IO (Maybe (Ref TreeItem))

getDepth :: Ref TreeItem -> IO (Int)

getH :: Ref TreeItem -> IO Int

getLabel :: Ref TreeItem -> IO Text

getLabelbgcolor :: Ref TreeItem -> IO (Color)

getLabelcolor :: Ref TreeItem -> IO (Color)

getLabelfgcolor :: Ref TreeItem -> IO (Color)

getLabelfont :: Ref TreeItem -> IO (Font)

getLabelsize :: Ref TreeItem -> IO (FontSize)

getParent :: Ref TreeItem -> IO (Maybe (Ref TreeItem))

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

getW :: Ref TreeItem -> IO Int

getWidget :: Ref TreeItem -> IO (Maybe (Ref WidgetBase))

getX :: Ref TreeItem -> IO Int

getY :: Ref TreeItem -> IO Int

hasChildren :: Ref TreeItem -> IO (Bool)

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

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

isActive :: Ref TreeItem -> IO (Bool)

isClose :: Ref TreeItem -> IO (Bool)

isOpen :: Ref TreeItem -> IO (Bool)

isRoot :: Ref TreeItem -> IO (Bool)

isSelected :: Ref TreeItem -> IO (Bool)

isVisible :: Ref TreeItem -> IO (Bool)

labelH :: Ref TreeItem -> IO (Int)

labelW :: Ref TreeItem -> IO (Int)

labelX :: Ref TreeItem -> IO (Int)

labelY :: Ref TreeItem -> IO (Int)

move :: Ref TreeItem -> AtIndex -> AtIndex -> IO (Either OutOfRange ())

moveTo:: (Parent a TreeItem) => Ref TreeItem -> Ref a -> MoveType -> IO (Either MoveError ())

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

nextDisplayed:: (Parent a TreePrefs) => Ref TreeItem -> Ref a -> IO (Maybe (Ref TreeItem))

nextSibling :: Ref TreeItem -> IO (Maybe (Ref TreeItem))

open :: Ref TreeItem -> IO ()

openToggle :: Ref TreeItem -> IO ()

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

prevDisplayed:: (Parent a TreePrefs) => Ref TreeItem -> Ref a -> IO (Maybe (Ref TreeItem))

prevSibling :: Ref TreeItem -> IO (Maybe (Ref TreeItem))

removeChild :: Ref TreeItem -> TreeItemLocator -> IO (Either UnknownError ())

reparent:: (Parent a TreeItem) => Ref TreeItem -> Ref a -> AtIndex -> IO (Either UnknownError ())

select :: Ref TreeItem -> IO ()

selectAll :: Ref TreeItem -> IO (Int)

selectSet :: Ref TreeItem -> Bool -> IO ()

selectToggle :: Ref TreeItem -> IO ()

setLabel :: Ref TreeItem -> Text -> IO ()

setLabelbgcolor :: Ref TreeItem -> Color -> IO ()

setLabelcolor :: Ref TreeItem -> Color -> IO ()

setLabelfgcolor :: Ref TreeItem -> Color -> IO ()

setLabelfont :: Ref TreeItem -> Font -> IO ()

setLabelsize :: Ref TreeItem -> FontSize -> IO ()

setParent:: (Parent a TreeItem) => Ref TreeItem -> Maybe (Ref a) -> IO ()

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

setWidget:: (Parent a WidgetBase) => Ref TreeItem -> Maybe ( Ref a ) -> IO ()

showSelf :: Ref TreeItem -> Maybe Text -> IO ()

swapChildren :: Ref TreeItem -> AtIndex -> AtIndex -> IO ()

swapChildrenByTreeItem:: (Parent a TreeItem) => Ref TreeItem -> Ref a -> Ref a -> IO (Either TreeItemNotFound ())

updatePrevNext :: Ref TreeItem -> AtIndex -> IO ()

visible :: Ref TreeItem -> IO (Bool)

visibleR :: Ref TreeItem -> IO (Bool)

Orphan instances

impl ~ IO Int => Op (LabelH ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: LabelH () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Int => Op (LabelW ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: LabelW () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Int => Op (LabelY ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: LabelY () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Int => Op (LabelX ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: LabelX () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Bool => Op (IsRoot ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: IsRoot () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreePrefs, impl ~ (Ref a -> IO Int)) => Op (EventOnLabel ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: EventOnLabel () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreePrefs, impl ~ (Ref a -> IO Int)) => Op (EventOnCollapseIcon ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: EventOnCollapseIcon () -> orig -> Ref TreeItem -> impl Source #

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

Methods

runOp :: FindClicked () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Bool => Op (VisibleR ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: VisibleR () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Bool => Op (IsVisible ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: IsVisible () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Bool => Op (IsActive ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: IsActive () -> orig -> Ref TreeItem -> impl Source #

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

Methods

runOp :: ActivateWith () -> orig -> Ref TreeItem -> impl Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

runOp :: SelectSet () -> orig -> Ref TreeItem -> impl Source #

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

Methods

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

impl ~ IO Bool => Op (IsClose ()) TreeItem orig impl Source # 
Instance details

Methods

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

impl ~ IO Bool => Op (IsOpen ()) TreeItem orig impl Source # 
Instance details

Methods

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

impl ~ IO () => Op (Close ()) TreeItem orig impl Source # 
Instance details

Methods

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

impl ~ IO () => Op (Open ()) TreeItem orig impl Source # 
Instance details

Methods

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

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

Methods

runOp :: PrevDisplayed () -> orig -> Ref TreeItem -> impl Source #

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

Methods

runOp :: NextDisplayed () -> orig -> Ref TreeItem -> impl Source #

impl ~ (AtIndex -> IO ()) => Op (UpdatePrevNext ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: UpdatePrevNext () -> orig -> Ref TreeItem -> impl Source #

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

Methods

runOp :: PrevSibling () -> orig -> Ref TreeItem -> impl Source #

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

Methods

runOp :: NextSibling () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Int => Op (GetDepth ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: GetDepth () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> MoveType -> IO (Either MoveError ()))) => Op (MoveTo ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: MoveTo () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> AtIndex -> IO (Either UnknownError ()))) => Op (Reparent ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: Reparent () -> orig -> Ref TreeItem -> impl Source #

impl ~ (AtIndex -> IO (Either UnknownError (Ref orig))) => Op (Deparent ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: Deparent () -> orig -> Ref TreeItem -> impl Source #

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

Methods

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

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

Methods

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

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

Methods

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

impl ~ ([Text] -> IO (Maybe (Ref TreeItem))) => Op (FindInChildren ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: FindInChildren () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> Ref a -> IO (Either TreeItemNotFound ()))) => Op (SwapChildrenByTreeItem ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: SwapChildrenByTreeItem () -> orig -> Ref TreeItem -> impl Source #

impl ~ (AtIndex -> AtIndex -> IO ()) => Op (SwapChildren ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: SwapChildren () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO () => Op (ClearChildren ()) TreeItem orig impl Source # 
Instance details

Methods

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

impl ~ (TreeItemLocator -> IO (Either UnknownError ())) => Op (RemoveChild ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: RemoveChild () -> orig -> Ref TreeItem -> impl Source #

impl ~ (TreeItemLocator -> IO (Maybe AtIndex)) => Op (FindChild ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: FindChild () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Bool => Op (HasChildren ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: HasChildren () -> orig -> Ref TreeItem -> impl Source #

impl ~ (AtIndex -> IO (Maybe (Ref WidgetBase))) => Op (Child ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: Child () -> orig -> Ref TreeItem -> impl Source #

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

Methods

runOp :: GetWidget () -> orig -> Ref TreeItem -> impl Source #

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

Methods

runOp :: SetWidget () -> orig -> Ref TreeItem -> impl Source #

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

Methods

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

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

Methods

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

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

Methods

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

impl ~ (Color -> IO ()) => Op (SetLabelbgcolor ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: SetLabelbgcolor () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Color => Op (GetLabelbgcolor ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: GetLabelbgcolor () -> orig -> Ref TreeItem -> impl Source #

impl ~ (Color -> IO ()) => Op (SetLabelfgcolor ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: SetLabelfgcolor () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Color => Op (GetLabelfgcolor ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: GetLabelfgcolor () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO () => Op (Deselect ()) TreeItem orig impl Source # 
Instance details

Methods

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

impl ~ IO () => Op (Select ()) TreeItem orig impl Source # 
Instance details

Methods

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

impl ~ (AtIndex -> AtIndex -> IO (Either OutOfRange ())) => Op (Move ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: Move () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Bool => Op (IsSelected ()) TreeItem orig impl Source # 
Instance details

Methods

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

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

Methods

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

impl ~ IO Bool => Op (Visible ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: Visible () -> orig -> Ref TreeItem -> impl Source #

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

Methods

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

impl ~ IO Int => Op (Children ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: Children () -> orig -> Ref TreeItem -> impl Source #

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

Methods

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

(Parent a TreeItem, Parent b TreePrefs, impl ~ (Ref b -> TreeItemLocator -> IO (Maybe (Ref a)))) => Op (Add ()) TreeItem orig impl Source # 
Instance details

Methods

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

impl ~ IO () => Op (Activate ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: Activate () -> orig -> Ref TreeItem -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetLabelsize ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: SetLabelsize () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO FontSize => Op (GetLabelsize ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: GetLabelsize () -> orig -> Ref TreeItem -> impl Source #

impl ~ (Font -> IO ()) => Op (SetLabelfont ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: SetLabelfont () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Font => Op (GetLabelfont ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: GetLabelfont () -> orig -> Ref TreeItem -> impl Source #

impl ~ (Color -> IO ()) => Op (SetLabelcolor ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: SetLabelcolor () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Color => Op (GetLabelcolor ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: GetLabelcolor () -> orig -> Ref TreeItem -> impl Source #

impl ~ (Text -> IO ()) => Op (SetLabel ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: SetLabel () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Text => Op (GetLabel ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: GetLabel () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Int => Op (GetH ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: GetH () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Int => Op (GetW ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: GetW () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Int => Op (GetY ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: GetY () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Int => Op (GetX ()) TreeItem orig impl Source # 
Instance details

Methods

runOp :: GetX () -> orig -> Ref TreeItem -> impl Source #

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

Methods

runOp :: SetParent () -> orig -> Ref TreeItem -> impl Source #

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

Methods

runOp :: GetParent () -> orig -> Ref TreeItem -> impl Source #

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

Methods

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