{-# LINE 2 "./Graphics/UI/Gtk/Display/AccelLabel.chs" #-}
-- -*-haskell-*-
-- GIMP Toolkit (GTK) Widget AccelLabel
--
-- Author : Axel Simon
--
-- Created: 23 May 2001
--
-- Copyright (C) 1999-2005 Axel Simon
--
-- This library is free software; you can redistribute it and/or
-- modify it under the terms of the GNU Lesser General Public
-- License as published by the Free Software Foundation; either
-- version 2.1 of the License, or (at your option) any later version.
--
-- This library is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
-- Lesser General Public License for more details.
--
-- |
-- Maintainer : gtk2hs-users@lists.sourceforge.net
-- Stability : provisional
-- Portability : portable (depends on GHC)
--
-- A label which displays an accelerator key on the right of the text
--
module Graphics.UI.Gtk.Display.AccelLabel (
-- * Detail
--
-- | The 'AccelLabel' widget is a subclass of 'Label' that also displays an
-- accelerator key on the right of the label text, e.g. \'Ctl+S\'. It is
-- commonly used in menus to show the keyboard short-cuts for commands.
--
-- The accelerator key to display is not set explicitly. Instead, the
-- 'AccelLabel' displays the accelerators which have been added to a particular
-- widget. This widget is set by calling 'accelLabelSetAccelWidget'.
--
-- For example, a 'MenuItem' widget may have an accelerator added to emit
-- the \"activate\" signal when the \'Ctl+S\' key combination is pressed. A
-- 'AccelLabel' is created and added to the 'MenuItem', and
-- 'accelLabelSetAccelWidget' is called with the 'MenuItem' as the second
-- argument. The 'AccelLabel' will now display \'Ctl+S\' after its label.
--
-- Note that creating a 'MenuItem' with
-- 'Graphics.UI.Gtk.MenuComboToolbar.MenuItem.menuItemNewWithLabel' (or one of
-- the similar functions for 'CheckMenuItem' and 'RadioMenuItem') automatically
-- adds a 'AccelLabel' to the 'MenuItem' and calls 'accelLabelSetAccelWidget'
-- to set it up for you.
--
-- An 'AccelLabel' will only display accelerators which have
-- 'Graphics.UI.Gtk.Abstract.Widget.AccelVisible'
-- set (see 'Graphics.UI.Gtk.Abstract.Widget.AccelFlags').
-- A 'AccelLabel' can display multiple accelerators and
-- even signal names, though it is almost always used to display just one
-- accelerator key.

-- * Class Hierarchy
-- |
-- @
-- | 'GObject'
-- | +----'Object'
-- | +----'Widget'
-- | +----'Misc'
-- | +----'Label'
-- | +----AccelLabel
-- @

-- * Types
  AccelLabel,
  AccelLabelClass,
  castToAccelLabel, gTypeAccelLabel,
  toAccelLabel,

-- * Constructors
  accelLabelNew,

-- * Methods
  accelLabelSetAccelWidget,
  accelLabelGetAccelWidget,

-- * Attributes
  accelLabelAccelWidget,
  ) where

import Control.Monad (liftM)

import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.Attributes
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Types
{-# LINE 93 "./Graphics/UI/Gtk/Display/AccelLabel.chs" #-}


{-# LINE 95 "./Graphics/UI/Gtk/Display/AccelLabel.chs" #-}

--------------------
-- Constructors

-- | Creates a new 'AccelLabel'.
--
accelLabelNew :: GlibString string
 => string -- ^ @string@ - the label string.
 -> IO AccelLabel
accelLabelNew :: forall string. GlibString string => string -> IO AccelLabel
accelLabelNew string
string =
  (ForeignPtr AccelLabel -> AccelLabel, FinalizerPtr AccelLabel)
-> IO (Ptr AccelLabel) -> IO AccelLabel
forall obj.
ObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewObject (ForeignPtr AccelLabel -> AccelLabel, FinalizerPtr AccelLabel)
forall {a}. (ForeignPtr AccelLabel -> AccelLabel, FinalizerPtr a)
mkAccelLabel (IO (Ptr AccelLabel) -> IO AccelLabel)
-> IO (Ptr AccelLabel) -> IO AccelLabel
forall a b. (a -> b) -> a -> b
$
  (Ptr Widget -> Ptr AccelLabel)
-> IO (Ptr Widget) -> IO (Ptr AccelLabel)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Ptr Widget -> Ptr AccelLabel
forall a b. Ptr a -> Ptr b
castPtr :: Ptr Widget -> Ptr AccelLabel) (IO (Ptr Widget) -> IO (Ptr AccelLabel))
-> IO (Ptr Widget) -> IO (Ptr AccelLabel)
forall a b. (a -> b) -> a -> b
$
  string -> (CString -> IO (Ptr Widget)) -> IO (Ptr Widget)
forall a. string -> (CString -> IO a) -> IO a
forall s a. GlibString s => s -> (CString -> IO a) -> IO a
withUTFString string
string ((CString -> IO (Ptr Widget)) -> IO (Ptr Widget))
-> (CString -> IO (Ptr Widget)) -> IO (Ptr Widget)
forall a b. (a -> b) -> a -> b
$ \CString
stringPtr ->
  CString -> IO (Ptr Widget)
gtk_accel_label_new
{-# LINE 109 "./Graphics/UI/Gtk/Display/AccelLabel.chs" #-}
    stringPtr

--------------------
-- Methods

-- | Sets the widget to be monitored by this accelerator label.
--
accelLabelSetAccelWidget :: (AccelLabelClass self, WidgetClass accelWidget) => self
 -> accelWidget -- ^ @accelWidget@ - the widget to be monitored.
 -> IO ()
accelLabelSetAccelWidget :: forall self accelWidget.
(AccelLabelClass self, WidgetClass accelWidget) =>
self -> accelWidget -> IO ()
accelLabelSetAccelWidget self
self accelWidget
accelWidget =
  (\(AccelLabel ForeignPtr AccelLabel
arg1) (Widget ForeignPtr Widget
arg2) -> ForeignPtr AccelLabel -> (Ptr AccelLabel -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AccelLabel
arg1 ((Ptr AccelLabel -> IO ()) -> IO ())
-> (Ptr AccelLabel -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AccelLabel
argPtr1 ->ForeignPtr Widget -> (Ptr Widget -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Widget
arg2 ((Ptr Widget -> IO ()) -> IO ()) -> (Ptr Widget -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Widget
argPtr2 ->Ptr AccelLabel -> Ptr Widget -> IO ()
gtk_accel_label_set_accel_widget Ptr AccelLabel
argPtr1 Ptr Widget
argPtr2)
{-# LINE 121 "./Graphics/UI/Gtk/Display/AccelLabel.chs" #-}
    (toAccelLabel self)
    (accelWidget -> Widget
forall o. WidgetClass o => o -> Widget
toWidget accelWidget
accelWidget)

-- | Fetches the widget monitored by this accelerator label. See
-- 'accelLabelSetAccelWidget'.
--
accelLabelGetAccelWidget :: AccelLabelClass self => self
 -> IO (Maybe Widget) -- ^ returns the object monitored by the accelerator
                      -- label, or @Nothing@.
accelLabelGetAccelWidget :: forall self. AccelLabelClass self => self -> IO (Maybe Widget)
accelLabelGetAccelWidget self
self =
  (IO (Ptr Widget) -> IO Widget)
-> IO (Ptr Widget) -> IO (Maybe Widget)
forall a. (IO (Ptr a) -> IO a) -> IO (Ptr a) -> IO (Maybe a)
maybeNull ((ForeignPtr Widget -> Widget, FinalizerPtr Widget)
-> IO (Ptr Widget) -> IO Widget
forall obj.
ObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewObject (ForeignPtr Widget -> Widget, FinalizerPtr Widget)
forall {a}. (ForeignPtr Widget -> Widget, FinalizerPtr a)
mkWidget) (IO (Ptr Widget) -> IO (Maybe Widget))
-> IO (Ptr Widget) -> IO (Maybe Widget)
forall a b. (a -> b) -> a -> b
$
  (\(AccelLabel ForeignPtr AccelLabel
arg1) -> ForeignPtr AccelLabel
-> (Ptr AccelLabel -> IO (Ptr Widget)) -> IO (Ptr Widget)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr AccelLabel
arg1 ((Ptr AccelLabel -> IO (Ptr Widget)) -> IO (Ptr Widget))
-> (Ptr AccelLabel -> IO (Ptr Widget)) -> IO (Ptr Widget)
forall a b. (a -> b) -> a -> b
$ \Ptr AccelLabel
argPtr1 ->Ptr AccelLabel -> IO (Ptr Widget)
gtk_accel_label_get_accel_widget Ptr AccelLabel
argPtr1)
{-# LINE 133 "./Graphics/UI/Gtk/Display/AccelLabel.chs" #-}
    (toAccelLabel self)

--------------------
-- Attributes

-- | The widget to be monitored for accelerator changes.
--
accelLabelAccelWidget :: (AccelLabelClass self, WidgetClass accelWidget) => ReadWriteAttr self (Maybe Widget) accelWidget
accelLabelAccelWidget :: forall self accelWidget.
(AccelLabelClass self, WidgetClass accelWidget) =>
ReadWriteAttr self (Maybe Widget) accelWidget
accelLabelAccelWidget = (self -> IO (Maybe Widget))
-> (self -> accelWidget -> IO ())
-> ReadWriteAttr self (Maybe Widget) accelWidget
forall o a b.
(o -> IO a) -> (o -> b -> IO ()) -> ReadWriteAttr o a b
newAttr
  self -> IO (Maybe Widget)
forall self. AccelLabelClass self => self -> IO (Maybe Widget)
accelLabelGetAccelWidget
  self -> accelWidget -> IO ()
forall self accelWidget.
(AccelLabelClass self, WidgetClass accelWidget) =>
self -> accelWidget -> IO ()
accelLabelSetAccelWidget

foreign import ccall unsafe "gtk_accel_label_new"
  gtk_accel_label_new :: ((Ptr CChar) -> (IO (Ptr Widget)))

foreign import ccall safe "gtk_accel_label_set_accel_widget"
  gtk_accel_label_set_accel_widget :: ((Ptr AccelLabel) -> ((Ptr Widget) -> (IO ())))

foreign import ccall unsafe "gtk_accel_label_get_accel_widget"
  gtk_accel_label_get_accel_widget :: ((Ptr AccelLabel) -> (IO (Ptr Widget)))