{-# LINE 2 "./Graphics/UI/Gtk/Display/Statusbar.chs" #-}
-- -*-haskell-*-
-- GIMP Toolkit (GTK) Widget Statusbar
--
-- Author : Axel Simon, Andy Stewart
--
-- Created: 23 May 2001
--
-- Copyright (C) 1999-2005 Axel Simon
-- Copyright (C) 2010 Andy Stewart
--
-- 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)
--
-- Report messages of minor importance to the user
--
module Graphics.UI.Gtk.Display.Statusbar (
-- * Detail
--
-- | A 'Statusbar' is usually placed along the bottom of an application's main
-- 'Window'. It may provide a regular commentary of the application's status
-- (as is usually the case in a web browser, for example), or may be used to
-- simply output a message when the status changes, (when an upload is complete
-- in an FTP client, for example). It may also have a resize grip (a triangular
-- area in the lower right corner) which can be clicked on to resize the window
-- containing the statusbar.
--
-- Status bars in Gtk+ maintain a stack of messages. The message at the top
-- of the each bar's stack is the one that will currently be displayed.
--
-- Any messages added to a statusbar's stack must specify a /context_id/
-- that is used to uniquely identify the source of a message. This context_id
-- can be generated by 'statusbarGetContextId', given a message and the
-- statusbar that it will be added to. Note that messages are stored in a
-- stack, and when choosing which message to display, the stack structure is
-- adhered to, regardless of the context identifier of a message.
--
-- Status bars are created using 'statusbarNew'.
--
-- Messages are added to the bar's stack with 'statusbarPush'.
--
-- The message at the top of the stack can be removed using 'statusbarPop'.
-- A message can be removed from anywhere in the stack if its message_id was
-- recorded at the time it was added. This is done using 'statusbarRemove'.

-- * Class Hierarchy
-- |
-- @
-- | 'GObject'
-- | +----'Object'
-- | +----'Widget'
-- | +----'Container'
-- | +----'Box'
-- | +----'HBox'
-- | +----Statusbar
-- @

-- * Types
  Statusbar,
  StatusbarClass,
  castToStatusbar, gTypeStatusbar,
  toStatusbar,
  ContextId,
  MessageId,

-- * Constructors
  statusbarNew,

-- * Methods
  statusbarGetContextId,
  statusbarPush,
  statusbarPop,
  statusbarRemove,





  statusbarGetMessageArea,


  statusbarRemoveAll,


-- * Attributes




-- * Signals
  textPopped,
  textPushed,

-- * Deprecated






  ) where

import Control.Monad (liftM)

import System.Glib.FFI
import System.Glib.UTFString



import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Types
{-# LINE 124 "./Graphics/UI/Gtk/Display/Statusbar.chs" #-}
import Graphics.UI.Gtk.Signals
{-# LINE 125 "./Graphics/UI/Gtk/Display/Statusbar.chs" #-}


{-# LINE 127 "./Graphics/UI/Gtk/Display/Statusbar.chs" #-}

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

-- | Creates a new 'Statusbar' ready for messages.
--
statusbarNew :: IO Statusbar
statusbarNew =
  makeNewObject mkStatusbar $
  liftM (castPtr :: Ptr Widget -> Ptr Statusbar) $
  gtk_statusbar_new
{-# LINE 138 "./Graphics/UI/Gtk/Display/Statusbar.chs" #-}

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

type ContextId = (CUInt)
{-# LINE 143 "./Graphics/UI/Gtk/Display/Statusbar.chs" #-}

-- | Returns a new context identifier, given a description of the actual
-- context. This id can be used to later remove entries form the Statusbar.
--
statusbarGetContextId :: (StatusbarClass self, GlibString string) => self
 -> string -- ^ @contextDescription@ - textual description of what context the
                 -- new message is being used in.
 -> IO ContextId -- ^ returns an id that can be used to later remove entries
                 -- ^ from the Statusbar.
statusbarGetContextId self contextDescription =
  withUTFString contextDescription $ \contextDescriptionPtr ->
  (\(Statusbar arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_statusbar_get_context_id argPtr1 arg2)
{-# LINE 155 "./Graphics/UI/Gtk/Display/Statusbar.chs" #-}
    (toStatusbar self)
    contextDescriptionPtr

newtype MessageId = MessageId (CUInt)
{-# LINE 159 "./Graphics/UI/Gtk/Display/Statusbar.chs" #-}

-- | Pushes a new message onto the Statusbar's stack. It will
-- be displayed as long as it is on top of the stack.
--
statusbarPush :: (StatusbarClass self, GlibString string) => self
 -> ContextId -- ^ @contextId@ - the message's context id, as returned by
                 -- 'statusbarGetContextId'.
 -> string -- ^ @text@ - the message to add to the statusbar.
 -> IO MessageId -- ^ returns the message's new message id for use with
                 -- 'statusbarRemove'.
statusbarPush self contextId text =
  liftM MessageId $
  withUTFString text $ \textPtr ->
  (\(Statusbar arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_statusbar_push argPtr1 arg2 arg3)
{-# LINE 173 "./Graphics/UI/Gtk/Display/Statusbar.chs" #-}
    (toStatusbar self)
    contextId
    textPtr

-- | Removes the topmost message that has the correct context.
--
statusbarPop :: StatusbarClass self => self
 -> ContextId -- ^ @contextId@ - the context identifier used when the
                -- message was added.
 -> IO ()
statusbarPop self contextId =
  (\(Statusbar arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_statusbar_pop argPtr1 arg2)
{-# LINE 185 "./Graphics/UI/Gtk/Display/Statusbar.chs" #-}
    (toStatusbar self)
     contextId

-- | Forces the removal of a message from a statusbar's stack. The exact
-- @contextId@ and @messageId@ must be specified.
--
statusbarRemove :: StatusbarClass self => self
 -> ContextId -- ^ @contextId@ - a context identifier.
 -> MessageId -- ^ @messageId@ - a message identifier, as returned by
              -- 'statusbarPush'.
 -> IO ()
statusbarRemove self contextId (MessageId messageId) =
  (\(Statusbar arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_statusbar_remove argPtr1 arg2 arg3)
{-# LINE 198 "./Graphics/UI/Gtk/Display/Statusbar.chs" #-}
    (toStatusbar self)
    contextId
    messageId
{-# LINE 221 "./Graphics/UI/Gtk/Display/Statusbar.chs" #-}
-- | Retrieves the box containing the label widget.
statusbarGetMessageArea :: StatusbarClass self => self -> IO Box
statusbarGetMessageArea self =
  makeNewObject mkBox $
  liftM (castPtr :: Ptr Widget -> Ptr Box) $
  (\(Statusbar arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_statusbar_get_message_area argPtr1)
{-# LINE 227 "./Graphics/UI/Gtk/Display/Statusbar.chs" #-}
    (toStatusbar self)




-- | Forces the removal of all messages from a statusbar's stack with the exact @contextId@.
--
-- * Available since Gtk+ version 2.22
--
statusbarRemoveAll :: StatusbarClass self => self
                   -> Int -- ^ @contextId@ a context identifier
                   -> IO ()
statusbarRemoveAll self contextId =
  (\(Statusbar arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_statusbar_remove_all argPtr1 arg2)
{-# LINE 241 "./Graphics/UI/Gtk/Display/Statusbar.chs" #-}
    (toStatusbar self)
    (fromIntegral contextId)


--------------------
-- Attributes
{-# LINE 260 "./Graphics/UI/Gtk/Display/Statusbar.chs" #-}
--------------------
-- Signals

-- %hash c:4eb7 d:d0ef
-- | Is emitted whenever a new message gets pushed onto a statusbar's stack.
--
textPushed :: (StatusbarClass self, GlibString string) => Signal self (ContextId -> string -> IO ())
textPushed = Signal (\a self user -> connect_WORD_GLIBSTRING__NONE "text-pushed" a self (\w s -> user (fromIntegral w) s))

-- %hash c:2614 d:c1d2
-- | Is emitted whenever a new message is popped off a statusbar's stack.
--
textPopped :: (StatusbarClass self, GlibString string) => Signal self (ContextId -> string -> IO ())
textPopped = Signal (\a self user -> connect_WORD_GLIBSTRING__NONE "text-popped" a self (\w s -> user (fromIntegral w) s))

--------------------
-- Deprecated Signals

foreign import ccall unsafe "gtk_statusbar_new"
  gtk_statusbar_new :: (IO (Ptr Widget))

foreign import ccall unsafe "gtk_statusbar_get_context_id"
  gtk_statusbar_get_context_id :: ((Ptr Statusbar) -> ((Ptr CChar) -> (IO CUInt)))

foreign import ccall safe "gtk_statusbar_push"
  gtk_statusbar_push :: ((Ptr Statusbar) -> (CUInt -> ((Ptr CChar) -> (IO CUInt))))

foreign import ccall safe "gtk_statusbar_pop"
  gtk_statusbar_pop :: ((Ptr Statusbar) -> (CUInt -> (IO ())))

foreign import ccall safe "gtk_statusbar_remove"
  gtk_statusbar_remove :: ((Ptr Statusbar) -> (CUInt -> (CUInt -> (IO ()))))

foreign import ccall unsafe "gtk_statusbar_get_message_area"
  gtk_statusbar_get_message_area :: ((Ptr Statusbar) -> (IO (Ptr Widget)))

foreign import ccall safe "gtk_statusbar_remove_all"
  gtk_statusbar_remove_all :: ((Ptr Statusbar) -> (CUInt -> (IO ())))