fltkhs-0.5.2.9: FLTK bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.MenuPrim

Contents

Synopsis

Documentation

Hierarchy

Functions

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

addName :: Ref MenuPrim -> Text -> IO ()

clear :: Ref MenuPrim -> IO ()

clearSubmenu :: Ref MenuPrim -> Int -> IO (Either OutOfRange ())

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

destroy :: Ref MenuPrim -> IO ()

findIndex :: Ref MenuPrim -> MenuItemLocator -> IO (Maybe Int)

getDownBox :: Ref MenuPrim -> IO (Boxtype)

getDownColor :: Ref MenuPrim -> IO (Color)

getMenu :: Ref MenuPrim -> IO [(Maybe (Ref MenuItem]))

getMode :: Ref MenuPrim -> Int -> IO (Maybe MenuItemFlags)

getSize :: Ref MenuPrim -> IO (Int)

getText :: Ref MenuPrim -> IO Text

getTextWithIndex :: Ref MenuPrim -> Int -> IO Text

getTextcolor :: Ref MenuPrim -> IO (Color)

getTextfont :: Ref MenuPrim -> IO (Font)

getTextsize :: Ref MenuPrim -> IO (FontSize)

getValue :: Ref MenuPrim -> IO (MenuItemIndex)

global :: Ref MenuPrim -> IO ()

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

handleSuper :: Ref MenuPrim -> Event -> IO (Either UnknownEvent ())

hide :: Ref MenuPrim -> IO ()

hideSuper :: Ref MenuPrim -> IO ()

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

itemPathname:: (Parent a MenuItem) => Ref MenuPrim -> Ref a -> IO (Maybe Text)

itemPathnameRecent :: Ref MenuPrim -> IO (Maybe String)

mvalue :: Ref MenuPrim -> IO (Maybe (Ref MenuItem))

picked:: (Parent a MenuItem, Parent b MenuItem) => Ref MenuPrim -> Ref a -> IO (Maybe (Ref b))

remove :: Ref MenuPrim -> Int -> IO ()

replace :: Ref MenuPrim -> Int -> Text -> IO ()

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

resizeSuper :: Ref MenuPrim -> Rectangle -> IO ()

setDownBox :: Ref MenuPrim -> Boxtype -> IO ()

setDownColor :: Ref MenuPrim -> Int -> IO ()

setMenu:: (Parent a MenuItem) => Ref MenuPrim -> [Ref a] -> IO ()

setMode :: Ref MenuPrim -> Int -> MenuItemFlags -> IO ()

setShortcut :: Ref MenuPrim -> Int -> ShortcutKeySequence -> IO ()

setSize :: Ref MenuPrim -> Int -> Int -> IO ()

setTextcolor :: Ref MenuPrim -> Color -> IO ()

setTextfont :: Ref MenuPrim -> Font -> IO ()

setTextsize :: Ref MenuPrim -> FontSize -> IO ()

setValue :: Ref MenuPrim -> MenuItemReference -> IO (Int)

showWidget :: Ref MenuPrim -> IO ()

showWidgetSuper :: Ref MenuPrim -> IO ()

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

Available in FLTK 1.3.4 only:
setonly:: (Parent a MenuItem) => Ref MenuPrim -> Ref a -> IO ()

Orphan instances

(~) * impl (Color -> IO ()) => Op (SetTextcolor ()) MenuPrim orig impl Source # 

Methods

runOp :: SetTextcolor () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (IO Color) => Op (GetTextcolor ()) MenuPrim orig impl Source # 

Methods

runOp :: GetTextcolor () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (FontSize -> IO ()) => Op (SetTextsize ()) MenuPrim orig impl Source # 

Methods

runOp :: SetTextsize () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (IO FontSize) => Op (GetTextsize ()) MenuPrim orig impl Source # 

Methods

runOp :: GetTextsize () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (Font -> IO ()) => Op (SetTextfont ()) MenuPrim orig impl Source # 

Methods

runOp :: SetTextfont () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (IO Font) => Op (GetTextfont ()) MenuPrim orig impl Source # 

Methods

runOp :: GetTextfont () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (Int -> IO Text) => Op (GetTextWithIndex ()) MenuPrim orig impl Source # 

Methods

runOp :: GetTextWithIndex () -> orig -> Ref MenuPrim -> impl Source #

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

Methods

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

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

Methods

runOp :: Mvalue () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (Int -> IO (Maybe MenuItemFlags)) => Op (GetMode ()) MenuPrim orig impl Source # 

Methods

runOp :: GetMode () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (Int -> MenuItemFlags -> IO ()) => Op (SetMode ()) MenuPrim orig impl Source # 

Methods

runOp :: SetMode () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (Int -> IO ()) => Op (Remove ()) MenuPrim orig impl Source # 

Methods

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

(~) * impl (Int -> Text -> IO ()) => Op (Replace ()) MenuPrim orig impl Source # 

Methods

runOp :: Replace () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (Text -> IO ()) => Op (AddName ()) MenuPrim orig impl Source # 

Methods

runOp :: AddName () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (Int -> IO (Either OutOfRange ())) => Op (ClearSubmenu ()) MenuPrim orig impl Source # 

Methods

runOp :: ClearSubmenu () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (Int -> Int -> IO ()) => Op (SetSize ()) MenuPrim orig impl Source # 

Methods

runOp :: SetSize () -> orig -> Ref MenuPrim -> impl Source #

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

Methods

runOp :: Copy () -> orig -> Ref MenuPrim -> impl Source #

(Parent a MenuItem, (~) * impl ([Ref a] -> IO ())) => Op (SetMenu ()) MenuPrim orig impl Source # 

Methods

runOp :: SetMenu () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (IO [Maybe (Ref MenuItem)]) => Op (GetMenu ()) MenuPrim orig impl Source # 

Methods

runOp :: GetMenu () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (IO ()) => Op (Global ()) MenuPrim orig impl Source # 

Methods

runOp :: Global () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (MenuItemLocator -> IO (Maybe Int)) => Op (FindIndex ()) MenuPrim orig impl Source # 

Methods

runOp :: FindIndex () -> orig -> Ref MenuPrim -> impl Source #

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

Methods

runOp :: Picked () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (IO (Maybe String)) => Op (ItemPathnameRecent ()) MenuPrim orig impl Source # 

Methods

runOp :: ItemPathnameRecent () -> orig -> Ref MenuPrim -> impl Source #

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

Methods

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

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

Methods

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

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

Methods

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

(~) * impl (Int -> IO ()) => Op (SetDownColor ()) MenuPrim orig impl Source # 

Methods

runOp :: SetDownColor () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (IO Color) => Op (GetDownColor ()) MenuPrim orig impl Source # 

Methods

runOp :: GetDownColor () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (Boxtype -> IO ()) => Op (SetDownBox ()) MenuPrim orig impl Source # 

Methods

runOp :: SetDownBox () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (IO Boxtype) => Op (GetDownBox ()) MenuPrim orig impl Source # 

Methods

runOp :: GetDownBox () -> orig -> Ref MenuPrim -> impl Source #

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

Methods

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

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

Methods

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

(~) * impl (MenuItemReference -> IO Int) => Op (SetValue ()) MenuPrim orig impl Source # 

Methods

runOp :: SetValue () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (IO MenuItemIndex) => Op (GetValue ()) MenuPrim orig impl Source # 

Methods

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

(~) * impl (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) MenuPrim orig impl Source # 

Methods

runOp :: HandleSuper () -> orig -> Ref MenuPrim -> impl Source #

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

Methods

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

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

Methods

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

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

Methods

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

(~) * impl (Rectangle -> IO ()) => Op (Resize ()) MenuPrim orig impl Source # 

Methods

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

(~) * impl (Rectangle -> IO ()) => Op (ResizeSuper ()) MenuPrim orig impl Source # 

Methods

runOp :: ResizeSuper () -> orig -> Ref MenuPrim -> impl Source #

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

Methods

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

(~) * impl (IO ()) => Op (HideSuper ()) MenuPrim orig impl Source # 

Methods

runOp :: HideSuper () -> orig -> Ref MenuPrim -> impl Source #

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

Methods

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

(~) * impl (IO ()) => Op (ShowWidgetSuper ()) MenuPrim orig impl Source # 

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref MenuPrim -> impl Source #

(~) * impl (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) MenuPrim orig impl Source # 

Methods

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

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

Methods

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