fltkhs-0.5.4.4: FLTK bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.MenuItem

Contents

Synopsis

Documentation

newtype MenuItemIndex Source #

Constructors

MenuItemIndex Int 

newtype MenuItemName Source #

Constructors

MenuItemName Text 

Hierarchy

Functions

activate :: Ref MenuItem -> IO ()

active :: Ref MenuItem -> IO (Bool)

activevisible :: Ref MenuItem -> IO (Bool)

add:: (Parent a MenuItem) => Ref MenuItem -> Text -> Maybe Shortcut -> Maybe (Ref a -> IO ()) -> MenuItemFlags -> IO (MenuItemIndex)

checkbox :: Ref MenuItem -> IO (Bool)

clear :: Ref MenuItem -> IO ()

deactivate :: Ref MenuItem -> IO ()

destroy :: Ref MenuItem -> IO ()

doCallback :: Ref MenuItem -> Ref Widget -> IO ()

draw:: (Parent a MenuPrim) => Ref MenuItem -> Rectangle -> Ref a -> IO ()

drawWithT:: (Parent a MenuPrim) => Ref MenuItem -> Rectangle -> Ref a -> Int -> IO ()

findShortcut:: (Parent a MenuItem) => Ref MenuItem -> Maybe Int -> Bool -> IO (Maybe (Ref a))

getFirst :: Ref MenuItem -> IO (Maybe (Ref MenuItem))

getFlags :: Ref MenuItem -> IO (Maybe MenuItemFlags)

getLabel :: Ref MenuItem -> IO Text

getLabelcolor :: Ref MenuItem -> IO (Color)

getLabelfont :: Ref MenuItem -> IO (Font)

getLabelsize :: Ref MenuItem -> IO (FontSize)

getLabeltype :: Ref MenuItem -> IO (Labeltype)

getShortcut :: Ref MenuItem -> IO (Maybe ShortcutKeySequence)

getSize :: Ref MenuItem -> IO (Int)

getText :: Ref MenuItem -> IO Text

getValue :: Ref MenuItem -> IO (Int)

hide :: Ref MenuItem -> IO ()

insert:: (Parent a MenuItem) => Ref MenuItem -> Int -> Text -> Maybe ShortcutKeySequence -> (Ref a -> IO ()) -> MenuItemFlags -> IO (MenuItemIndex)

measure:: (Parent a MenuPrim) => Ref MenuItem -> Ref a -> IO (Size)

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

nextWithStep:: (Parent a MenuItem) => Ref MenuItem -> Int -> IO (Maybe (Ref a))

popup:: (Parent a MenuItem, Parent b MenuPrim, Parent c MenuItem) => Ref MenuItem -> Position -> Maybe Text -> Maybe (Ref a) -> Maybe (Ref b) -> IO (Maybe (Ref c))

pulldown:: (Parent a MenuPrim, Parent b MenuItem, Parent c MenuItem) => Ref MenuItem -> Rectangle -> Maybe (Ref a) -> Maybe (Ref b) -> Maybe (Ref c) -> Maybe Bool -> IO (Maybe (Ref MenuItem))

radio :: Ref MenuItem -> IO (Bool)

set :: Ref MenuItem -> IO ()

setCallback :: Ref MenuItem -> (Ref orig -> IO ()) -> IO ()

setFlags :: Ref MenuItem -> MenuItemFlags -> IO ()

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

setLabelWithLabeltype :: Ref MenuItem -> Labeltype -> Text -> IO ()

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

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

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

setLabeltype :: Ref MenuItem -> Labeltype -> IO ()

setShortcut :: Ref MenuItem -> ShortcutKeySequence -> IO ()

setonly :: Ref MenuItem -> IO ()

showWidget :: Ref MenuItem -> IO ()

submenu :: Ref MenuItem -> IO (Bool)

testShortcut:: (Parent a MenuItem) => Ref MenuItem -> IO (Maybe (Ref a))

visible :: Ref MenuItem -> IO (Bool)

Orphan instances

(~) * impl (IO Text) => Op (GetText ()) MenuItem orig impl Source # 

Methods

runOp :: GetText () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO Int) => Op (GetSize ()) MenuItem orig impl Source # 

Methods

runOp :: GetSize () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (Ref Widget -> IO ()) => Op (DoCallback ()) MenuItem orig impl Source # 

Methods

runOp :: DoCallback () -> orig -> Ref MenuItem -> impl Source #

(Parent a MenuItem, (~) * impl (Maybe Int -> Bool -> IO (Maybe (Ref a)))) => Op (FindShortcut ()) MenuItem orig impl Source # 

Methods

runOp :: FindShortcut () -> orig -> Ref MenuItem -> impl Source #

(Parent a MenuItem, (~) * impl (IO (Maybe (Ref a)))) => Op (TestShortcut ()) MenuItem orig impl Source # 

Methods

runOp :: TestShortcut () -> orig -> Ref MenuItem -> impl Source #

(Parent a MenuItem, Parent b MenuPrim, Parent c MenuItem, (~) * impl (Position -> Maybe Text -> Maybe (Ref a) -> Maybe (Ref b) -> IO (Maybe (Ref c)))) => Op (Popup ()) MenuItem orig impl Source # 

Methods

runOp :: Popup () -> orig -> Ref MenuItem -> impl Source #

(Parent a MenuPrim, Parent b MenuItem, Parent c MenuItem, (~) * impl (Rectangle -> Maybe (Ref a) -> Maybe (Ref b) -> Maybe (Ref c) -> Maybe Bool -> IO (Maybe (Ref MenuItem)))) => Op (Pulldown ()) MenuItem orig impl Source # 

Methods

runOp :: Pulldown () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (MenuItemFlags -> IO ()) => Op (SetFlags ()) MenuItem orig impl Source # 

Methods

runOp :: SetFlags () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO (Maybe MenuItemFlags)) => Op (GetFlags ()) MenuItem orig impl Source # 

Methods

runOp :: GetFlags () -> orig -> Ref MenuItem -> impl Source #

(Parent a MenuPrim, (~) * impl (Rectangle -> Ref a -> IO ())) => Op (Draw ()) MenuItem orig impl Source # 

Methods

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

(Parent a MenuPrim, (~) * impl (Rectangle -> Ref a -> Int -> IO ())) => Op (DrawWithT ()) MenuItem orig impl Source # 

Methods

runOp :: DrawWithT () -> orig -> Ref MenuItem -> impl Source #

(Parent a MenuPrim, (~) * impl (Ref a -> IO Size)) => Op (Measure ()) MenuItem orig impl Source # 

Methods

runOp :: Measure () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO Bool) => Op (Activevisible ()) MenuItem orig impl Source # 

Methods

runOp :: Activevisible () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO Bool) => Op (Visible ()) MenuItem orig impl Source # 

Methods

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

(~) * impl (IO Bool) => Op (Radio ()) MenuItem orig impl Source # 

Methods

runOp :: Radio () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO Bool) => Op (Checkbox ()) MenuItem orig impl Source # 

Methods

runOp :: Checkbox () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO Bool) => Op (Submenu ()) MenuItem orig impl Source # 

Methods

runOp :: Submenu () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (Labeltype -> Text -> IO ()) => Op (SetLabelWithLabeltype ()) MenuItem orig impl Source # 

Methods

runOp :: SetLabelWithLabeltype () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO (Maybe (Ref MenuItem))) => Op (GetFirst ()) MenuItem orig impl Source # 

Methods

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

(~) * impl (IO (Maybe (Ref MenuItem))) => Op (Next ()) MenuItem orig impl Source # 

Methods

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

(Parent a MenuItem, (~) * impl (Int -> IO (Maybe (Ref a)))) => Op (NextWithStep ()) MenuItem orig impl Source # 

Methods

runOp :: NextWithStep () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) MenuItem orig impl Source # 

Methods

runOp :: SetShortcut () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO (Maybe ShortcutKeySequence)) => Op (GetShortcut ()) MenuItem orig impl Source # 

Methods

runOp :: GetShortcut () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO ()) => Op (Setonly ()) MenuItem orig impl Source # 

Methods

runOp :: Setonly () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO ()) => Op (Set ()) MenuItem orig impl Source # 

Methods

runOp :: Set () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO Int) => Op (GetValue ()) MenuItem orig impl Source # 

Methods

runOp :: GetValue () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO ()) => Op (Clear ()) MenuItem orig impl Source # 

Methods

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

(Parent a MenuItem, (~) * impl (Int -> Text -> Maybe ShortcutKeySequence -> (Ref a -> IO ()) -> MenuItemFlags -> IO MenuItemIndex)) => Op (Insert ()) MenuItem orig impl Source # 

Methods

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

(Parent a MenuItem, (~) * impl (Text -> Maybe Shortcut -> Maybe (Ref a -> IO ()) -> MenuItemFlags -> IO MenuItemIndex)) => Op (Add ()) MenuItem orig impl Source # 

Methods

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

(~) * impl ((Ref orig -> IO ()) -> IO ()) => Op (SetCallback ()) MenuItem orig impl Source # 

Methods

runOp :: SetCallback () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO ()) => Op (Deactivate ()) MenuItem orig impl Source # 

Methods

runOp :: Deactivate () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO ()) => Op (Activate ()) MenuItem orig impl Source # 

Methods

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

(~) * impl (IO Bool) => Op (Active ()) MenuItem orig impl Source # 

Methods

runOp :: Active () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO ()) => Op (Hide ()) MenuItem orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (ShowWidget ()) MenuItem orig impl Source # 

Methods

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

(~) * impl (FontSize -> IO ()) => Op (SetLabelsize ()) MenuItem orig impl Source # 

Methods

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

(~) * impl (IO FontSize) => Op (GetLabelsize ()) MenuItem orig impl Source # 

Methods

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

(~) * impl (Font -> IO ()) => Op (SetLabelfont ()) MenuItem orig impl Source # 

Methods

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

(~) * impl (IO Font) => Op (GetLabelfont ()) MenuItem orig impl Source # 

Methods

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

(~) * impl (Color -> IO ()) => Op (SetLabelcolor ()) MenuItem orig impl Source # 

Methods

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

(~) * impl (IO Color) => Op (GetLabelcolor ()) MenuItem orig impl Source # 

Methods

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

(~) * impl (Labeltype -> IO ()) => Op (SetLabeltype ()) MenuItem orig impl Source # 

Methods

runOp :: SetLabeltype () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (IO Labeltype) => Op (GetLabeltype ()) MenuItem orig impl Source # 

Methods

runOp :: GetLabeltype () -> orig -> Ref MenuItem -> impl Source #

(~) * impl (Text -> IO ()) => Op (SetLabel ()) MenuItem orig impl Source # 

Methods

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

(~) * impl (IO Text) => Op (GetLabel ()) MenuItem orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (Destroy ()) MenuItem orig impl Source # 

Methods

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