{-# LINE 1 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LANGUAGE ScopedTypeVariables, TypeSynonymInstances, FlexibleInstances #-}
{-# LINE 2 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# OPTIONS_HADDOCK hide #-}
-- -*-haskell-*-


{-# LINE 6 "Graphics/UI/Gtk/General/Structs.hsc" #-}

{-# LINE 7 "Graphics/UI/Gtk/General/Structs.hsc" #-}

{-# LINE 8 "Graphics/UI/Gtk/General/Structs.hsc" #-}

{-# LINE 9 "Graphics/UI/Gtk/General/Structs.hsc" #-}

{-# LINE 10 "Graphics/UI/Gtk/General/Structs.hsc" #-}

{-# LINE 11 "Graphics/UI/Gtk/General/Structs.hsc" #-}
--  GIMP Toolkit (GTK) Structures
--
--  Author : Axel Simon
--
--  Created: 2 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.
--
-- #hide

-- |
-- Maintainer  : gtk2hs-users@lists.sourceforge.net
-- Stability   : provisional
-- Portability : portable (depends on GHC)
--
module Graphics.UI.Gtk.General.Structs (
  Point,
  Rectangle(..),
  Color(..),

{-# LINE 47 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  Allocation,
  Requisition(..),
  treeIterSize,
  textIterSize,
  inputError,

{-# LINE 57 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  ResponseId(..),
  fromResponse,
  toResponse,

{-# LINE 61 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  NativeWindowId,
  toNativeWindowId,
  fromNativeWindowId,
  nativeWindowIdNone,

{-# LINE 66 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  drawableGetID,

{-# LINE 74 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  IconSize(..),

{-# LINE 84 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  styleGetForeground,
  styleGetBackground,
  styleGetLight,
  styleGetMiddle,
  styleGetDark,
  styleGetText,
  styleGetBase,
  styleGetAntiAliasing,

{-# LINE 104 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  SortColumnId,
  treeSortableDefaultSortColumnId,
  tagInvalid,
  selectionPrimary,
  selectionSecondary,
  selectionClipboard,
  targetString,
  selectionTypeAtom,
  selectionTypeInteger,
  selectionTypeString,

{-# LINE 117 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  withTargetEntries,
  KeymapKey (..)
  ) where

import Control.Monad		(liftM)
import Data.IORef
import Control.Exception (handle, ErrorCall(..))

import System.Glib.FFI
import System.Glib.UTFString ( UTFCorrection, ofsToUTF )
import Graphics.UI.Gtk.Abstract.Object	(makeNewObject)
import System.Glib.GObject		(makeNewGObject)
import Graphics.UI.Gtk.Types

{-# LINE 134 "Graphics/UI/Gtk/General/Structs.hsc" #-}
import Graphics.UI.Gtk.General.Enums	(StateType)
import Graphics.UI.Gtk.General.DNDTypes (InfoId, Atom(Atom) , SelectionTag,
                                         TargetTag, SelectionTypeTag)
import Graphics.Rendering.Pango.Structs ( Color(..), Rectangle(..) )

{-# LINE 139 "Graphics/UI/Gtk/General/Structs.hsc" #-}

{-# LINE 142 "Graphics/UI/Gtk/General/Structs.hsc" #-}
-- | Represents the x and y coordinate of a point.
--
type Point = (Int, Int)
    
instance Storable Point where           
  sizeOf _ = 8
{-# LINE 148 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  alignment _ = alignment (undefined:: Int32)
{-# LINE 149 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  peek ptr = do
    (x_	     ::Int32)	<- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 151 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (y_	     ::Int32)	<- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 152 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    return $ (fromIntegral x_, fromIntegral y_) 
  poke ptr (x, y) = do
    (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr ((fromIntegral x)::Int32)
{-# LINE 155 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr ((fromIntegral y)::Int32)
{-# LINE 156 "Graphics/UI/Gtk/General/Structs.hsc" #-}

instance Storable Rectangle where
  sizeOf _ = 16
{-# LINE 159 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  alignment _ = alignment (undefined:: Int32)
{-# LINE 160 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  peek ptr = do
    (x_	     ::Int32)	<- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 162 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (y_	     ::Int32)	<- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 163 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (width_  ::Int32)	<- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 164 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (height_ ::Int32)	<- (\hsc_ptr -> peekByteOff hsc_ptr 12) ptr
{-# LINE 165 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    return $ Rectangle (fromIntegral x_) (fromIntegral y_) 
		       (fromIntegral width_) (fromIntegral height_)
  poke ptr (Rectangle x y width height) = do
    (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr ((fromIntegral x)::Int32)
{-# LINE 169 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr ((fromIntegral y)::Int32)
{-# LINE 170 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr ((fromIntegral width)::Int32)
{-# LINE 171 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 12) ptr ((fromIntegral height)::Int32)
{-# LINE 172 "Graphics/UI/Gtk/General/Structs.hsc" #-}

instance Storable Color where
  sizeOf _ = 12
{-# LINE 175 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  alignment _ = alignment (undefined::Word32)
{-# LINE 176 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  peek ptr = do
    red	   <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 178 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    green  <- (\hsc_ptr -> peekByteOff hsc_ptr 6) ptr
{-# LINE 179 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    blue   <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 180 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    return $ Color red green blue
  poke ptr (Color red green blue) = do
    (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr (0::Int32)
{-# LINE 183 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 4)   ptr red
{-# LINE 184 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 6) ptr green
{-# LINE 185 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 8)  ptr blue
{-# LINE 186 "Graphics/UI/Gtk/General/Structs.hsc" #-}

{-# LINE 190 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    return ()


{-# LINE 414 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- Widget related methods

{-# LINE 439 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | Allocation
--
-- * For Widget's 'Graphics.UI.Gtk.Abstract.Widget.sizeAllocate' signal.
--   The @x@ and @y@ values of the rectangle refer to the widgets position
--   relative to its parent window.
--
type Allocation = Rectangle


-- | Requisition
--
-- * For 'Graphics.UI.Gtk.Abstract.Widget.widgetSizeRequest'. The values
--   represent the desired width and height of the widget.
--
data Requisition = Requisition Int Int deriving (Eq,Show)

instance Storable Requisition where
  sizeOf _ = 8
{-# LINE 458 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  alignment _ = alignment (undefined::Int32)
{-# LINE 459 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  peek ptr = do
    (width_  ::Int32)	<- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 461 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (height_ ::Int32)	<- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 462 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    return $ Requisition (fromIntegral width_) (fromIntegral height_)
  poke ptr (Requisition width height) = do
    (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr ((fromIntegral width)::Int32)
{-# LINE 465 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr ((fromIntegral height)::Int32)
{-# LINE 466 "Graphics/UI/Gtk/General/Structs.hsc" #-}


-- SpinButton related mothods

-- If an invalid input has been put into a SpinButton the input function may
-- reject this value by returning this value.
inputError :: Int32
{-# LINE 473 "Graphics/UI/Gtk/General/Structs.hsc" #-}
inputError = -1
{-# LINE 474 "Graphics/UI/Gtk/General/Structs.hsc" #-}


-- The TreeIter struct is not used by itself. But we have to allocate space
-- for it in module TreeModel.
treeIterSize :: Int
treeIterSize = 32
{-# LINE 480 "Graphics/UI/Gtk/General/Structs.hsc" #-}


-- The TextIter struct can be a local variable in a C program. We have to
-- store it on the heap.
--
textIterSize :: Int
textIterSize = 80
{-# LINE 487 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- Dialog related methods

{-# LINE 509 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | Some constructors that can be used as response
-- numbers for dialogs.
--
data ResponseId

  -- | GTK returns this if a response widget has no @response_id@,
  --   or if the dialog gets programmatically hidden or destroyed.
  = ResponseNone

  -- | GTK won't return these unless you pass them in as
  --   the response for an action widget. They are for your convenience.
  | ResponseReject
  | ResponseAccept -- ^ (as above)

  -- | If the dialog is deleted.
  | ResponseDeleteEvent

  -- | \"Ok\" was pressed.
  --
  -- * This value is returned from the \"Ok\" stock dialog button.
  | ResponseOk

  -- | \"Cancel\" was pressed.
  --
  -- * These value is returned from the \"Cancel\" stock dialog button.
  | ResponseCancel

  -- | \"Close\" was pressed.
  --
  -- * This value is returned from the \"Close\" stock dialog button.
	| ResponseClose

  -- | \"Yes\" was pressed.
  --
  -- * This value is returned from the \"Yes\" stock dialog button.
  | ResponseYes

  -- | \"No\" was pressed.
  --
  -- * This value is returned from the \"No\" stock dialog button.
  | ResponseNo

  -- | \"Apply\" was pressed.
  --
  -- * This value is returned from the \"Apply\" stock dialog button.
	| ResponseApply

  -- |  \"Help\" was pressed.
  --
  -- * This value is returned from the \"Help\" stock dialog button.
  | ResponseHelp

  -- | A user-defined response
  --
  -- * This value is returned from a user defined button
  | ResponseUser Int
  deriving (Show, Eq)

fromResponse :: Integral a => ResponseId -> a
fromResponse ResponseNone = -1
fromResponse ResponseReject = -2
fromResponse ResponseAccept = -3
fromResponse ResponseDeleteEvent = -4
fromResponse ResponseOk = -5
fromResponse ResponseCancel = -6
fromResponse ResponseClose = -7
fromResponse ResponseYes = -8
fromResponse ResponseNo = -9
fromResponse ResponseApply = -10
fromResponse ResponseHelp = -11
fromResponse (ResponseUser i) = fromIntegral i

toResponse :: Integral a => a -> ResponseId
toResponse (-1) = ResponseNone
toResponse (-2) = ResponseReject
toResponse (-3) = ResponseAccept
toResponse (-4) = ResponseDeleteEvent
toResponse (-5) = ResponseOk
toResponse (-6) = ResponseCancel
toResponse (-7) = ResponseClose
toResponse (-8) = ResponseYes
toResponse (-9) = ResponseNo
toResponse (-10) = ResponseApply
toResponse (-11) = ResponseHelp
toResponse i = ResponseUser $ fromIntegral i


{-# LINE 597 "Graphics/UI/Gtk/General/Structs.hsc" #-}
-- | The identifer of a window of the underlying windowing system.
--

{-# LINE 620 "Graphics/UI/Gtk/General/Structs.hsc" #-}

{-# LINE 623 "Graphics/UI/Gtk/General/Structs.hsc" #-}
newtype NativeWindowId = NativeWindowId Word64 deriving (Eq, Show)
{-# LINE 624 "Graphics/UI/Gtk/General/Structs.hsc" #-}

{-# LINE 625 "Graphics/UI/Gtk/General/Structs.hsc" #-}
unNativeWindowId :: Integral a => NativeWindowId -> a
unNativeWindowId (NativeWindowId id) = fromIntegral id
toNativeWindowId :: Integral a => a -> NativeWindowId
toNativeWindowId = NativeWindowId . fromIntegral
fromNativeWindowId :: Integral a => NativeWindowId -> a
fromNativeWindowId = fromIntegral . unNativeWindowId
nativeWindowIdNone :: NativeWindowId
nativeWindowIdNone = NativeWindowId 0

{-# LINE 634 "Graphics/UI/Gtk/General/Structs.hsc" #-}

{-# LINE 635 "Graphics/UI/Gtk/General/Structs.hsc" #-}


{-# LINE 645 "Graphics/UI/Gtk/General/Structs.hsc" #-}

{-# LINE 646 "Graphics/UI/Gtk/General/Structs.hsc" #-}
foreign import ccall unsafe "gdk_x11_window_get_xid" 
  gdk_x11_drawable_get_xid :: (Ptr DrawWindow) -> IO CInt

{-# LINE 649 "Graphics/UI/Gtk/General/Structs.hsc" #-}

{-# LINE 650 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | Get 'NativeWindowId' of 'Drawable'.

{-# LINE 655 "Graphics/UI/Gtk/General/Structs.hsc" #-}
drawableGetID :: DrawWindowClass d => d -> IO NativeWindowId

{-# LINE 657 "Graphics/UI/Gtk/General/Structs.hsc" #-}
drawableGetID d =
  liftM toNativeWindowId $

{-# LINE 662 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  (\(DrawWindow drawable) ->

{-# LINE 664 "Graphics/UI/Gtk/General/Structs.hsc" #-}

{-# LINE 673 "Graphics/UI/Gtk/General/Structs.hsc" #-}
     withForeignPtr drawable gdk_x11_drawable_get_xid

{-# LINE 677 "Graphics/UI/Gtk/General/Structs.hsc" #-}

{-# LINE 680 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  ) (toDrawWindow d)

{-# LINE 682 "Graphics/UI/Gtk/General/Structs.hsc" #-}



{-# LINE 698 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | The size of an icon in pixels.
--
-- * This enumeration contains one case that is not exported and which
--   is used when new sizes are registered using
--   'Graphics.UI.Gtk.General.IconFactory.iconSizeRegister'.
--
-- * Applying 'show' to this type will reveal the name of the size
--   that is registered with Gtk+.
--
data IconSize
  -- | Don't scale but use any of the available sizes.
  = IconSizeInvalid

  -- | Icon size to use in next to menu items in drop-down menus.
  | IconSizeMenu

  -- | Icon size for small toolbars.
  | IconSizeSmallToolbar

  -- | Icon size for larger toolbars.
  | IconSizeLargeToolbar

  -- | Icon size for icons in buttons, next to the label.
  | IconSizeButton

  -- | Icon size for icons in drag-and-drop.
  | IconSizeDnd

  -- | Icon size for icons next to dialog text.
  | IconSizeDialog
  
  | IconSizeUser Int
  deriving (Eq)

instance Enum IconSize where
  toEnum 0 = IconSizeInvalid
{-# LINE 735 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  toEnum 1    = IconSizeMenu
{-# LINE 736 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  toEnum 2 = IconSizeSmallToolbar
{-# LINE 737 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  toEnum 3 = IconSizeLargeToolbar
{-# LINE 738 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  toEnum 4 = IconSizeButton
{-# LINE 739 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  toEnum 5 = IconSizeDnd
{-# LINE 740 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  toEnum 6 = IconSizeDialog
{-# LINE 741 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  toEnum n = IconSizeUser n
  fromEnum IconSizeInvalid = 0
{-# LINE 743 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  fromEnum IconSizeMenu = 1   
{-# LINE 744 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  fromEnum IconSizeSmallToolbar = 2
{-# LINE 745 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  fromEnum IconSizeLargeToolbar = 3
{-# LINE 746 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  fromEnum IconSizeButton = 4
{-# LINE 747 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  fromEnum IconSizeDnd = 5
{-# LINE 748 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  fromEnum IconSizeDialog = 6
{-# LINE 749 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  fromEnum (IconSizeUser n) = n
  
-- entry Widget Combo

{-# LINE 762 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- FileSelection related methods

{-# LINE 778 "Graphics/UI/Gtk/General/Structs.hsc" #-}


{-# LINE 836 "Graphics/UI/Gtk/General/Structs.hsc" #-}
-- Styles related methods

-- | Retrieve the the foreground color.
--
-- * The parameter @state@ determines for which widget
--   state (one of 'StateType') the 'Color' should be retrieved.
--   Use 'widgetGetState' to determine the current state of the
--   widget.
--
styleGetForeground :: Style -> StateType -> IO Color
styleGetForeground st ty =
  withForeignPtr (unStyle st) $ \stPtr -> do
    peekElemOff ((\hsc_ptr -> hsc_ptr `plusPtr` 24) stPtr) (fromEnum ty)
{-# LINE 849 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | Retrieve the background color.
--
-- * The parameter @state@ determines for which widget
--   state (one of 'StateType') the 'Color' should be retrieved.
--   Use 'widgetGetState' to determine the current state of the
--   widget.
--
styleGetBackground :: Style -> StateType -> IO Color
styleGetBackground st ty =
  withForeignPtr (unStyle st) $ \stPtr ->
    peekElemOff ((\hsc_ptr -> hsc_ptr `plusPtr` 84) stPtr) (fromEnum ty)
{-# LINE 861 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | Retrieve a light color.
--
-- * The parameter @state@ determines for which widget
--   state (one of 'StateType') the 'Color' should be retrieved.
--   Use 'widgetGetState' to determine the current state of the
--   widget.
--
styleGetLight :: Style -> StateType -> IO Color
styleGetLight st ty =
  withForeignPtr (unStyle st) $ \stPtr ->
    peekElemOff ((\hsc_ptr -> hsc_ptr `plusPtr` 144) stPtr) (fromEnum ty)
{-# LINE 873 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | Retrieve a middle color.
--
-- * The parameter @state@ determines for which widget
--   state (one of 'StateType') the 'Color' should be retrieved.
--   Use 'widgetGetState' to determine the current state of the
--   widget.
--
styleGetMiddle :: Style -> StateType -> IO Color
styleGetMiddle st ty =
  withForeignPtr (unStyle st) $ \stPtr ->
    peekElemOff ((\hsc_ptr -> hsc_ptr `plusPtr` 264) stPtr) (fromEnum ty)
{-# LINE 885 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | Retrieve a dark color.
--
-- * The parameter @state@ determines for which widget
--   state (one of 'StateType') the 'Color' should be retrieved.
--   Use 'widgetGetState' to determine the current state of the
--   widget.
--
styleGetDark :: Style -> StateType -> IO Color
styleGetDark st ty =
  withForeignPtr (unStyle st) $ \stPtr ->
    peekElemOff ((\hsc_ptr -> hsc_ptr `plusPtr` 204) stPtr) (fromEnum ty)
{-# LINE 897 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | Retrieve the text color.
--
-- * The parameter @state@ determines for which widget
--   state (one of 'StateType') the 'Color' should be retrieved.
--   Use 'widgetGetState' to determine the current state of the
--   widget.
--
styleGetText :: Style -> StateType -> IO Color
styleGetText st ty =
  withForeignPtr (unStyle st) $ \stPtr ->
    peekElemOff ((\hsc_ptr -> hsc_ptr `plusPtr` 324) stPtr) (fromEnum ty)
{-# LINE 909 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | Retrieve the base color.
--
-- * The base color is the standard text background of a widget.
--
-- * The parameter @state@ determines for which widget
--   state (one of 'StateType') the 'Color' should be retrieved.
--   Use 'widgetGetState' to determine the current state of the
--   widget.
--
styleGetBase :: Style -> StateType -> IO Color
styleGetBase st ty =
  withForeignPtr (unStyle st) $ \stPtr ->
    peekElemOff ((\hsc_ptr -> hsc_ptr `plusPtr` 384) stPtr) (fromEnum ty)
{-# LINE 923 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | Retrieve the color for drawing anti-aliased text.
--
-- * The anti-aliasing color is the color which is used when the rendering
--   of a character does not make it clear if a certain pixel shoud be set
--   or not. This color is between the text and the base color.
--
-- * The parameter @state@ determines for which widget
--   state (one of 'StateType') the 'Color' should be retrieved.
--   Use 'widgetGetState' to determine the current state of the
--   widget.
--
styleGetAntiAliasing :: Style -> StateType -> IO Color
styleGetAntiAliasing st ty =
  withForeignPtr (unStyle st) $ \stPtr ->
    peekElemOff ((\hsc_ptr -> hsc_ptr `plusPtr` 444) stPtr) (fromEnum ty)
{-# LINE 939 "Graphics/UI/Gtk/General/Structs.hsc" #-}


{-# LINE 1001 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | ID number of a sort column.
--
-- * A 'SortColumnId' is a logical number to which a sorting function can
--   be associated. The number does not have to coincide with any column
--   number.
type SortColumnId = Int

-- | A special 'SortColumnId' to indicated that the default sorting function is used.
--
treeSortableDefaultSortColumnId :: SortColumnId
treeSortableDefaultSortColumnId = -1
{-# LINE 1013 "Graphics/UI/Gtk/General/Structs.hsc" #-}

intToAtom :: Int -> Atom
intToAtom = Atom . plusPtr nullPtr

-- | An invalid 'TargetTag', 'SelectionTag', 'SelectionTypeTag' or 'PropertyTag'.
--
tagInvalid :: Atom
tagInvalid = intToAtom 0
{-# LINE 1021 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | The primary selection (the currently highlighted text in X11 that can
--   in many applications be pasted using the middle button).
selectionPrimary :: SelectionTag
selectionPrimary = intToAtom 1
{-# LINE 1026 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | The secondary selection. Rarely used.
selectionSecondary :: SelectionTag
selectionSecondary = intToAtom 2
{-# LINE 1030 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | The modern clipboard that is filled by copy or cut commands.
selectionClipboard :: SelectionTag
selectionClipboard = intToAtom 69
{-# LINE 1034 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | If this target is provided by a selection, then the data is a string.
targetString :: TargetTag
targetString = intToAtom 31
{-# LINE 1038 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | The type indicating that the associated data is itself a (list of)
-- 'Graphics.UI.Gtk.General.Selection.Atom's.
selectionTypeAtom :: SelectionTypeTag
selectionTypeAtom = intToAtom 4
{-# LINE 1043 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | The type indicating that the associated data consists of integers.
selectionTypeInteger :: SelectionTypeTag
selectionTypeInteger = intToAtom 19
{-# LINE 1047 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | The type indicating that the associated data is a string without further
-- information on its encoding.
selectionTypeString :: SelectionTypeTag
selectionTypeString = intToAtom 31
{-# LINE 1052 "Graphics/UI/Gtk/General/Structs.hsc" #-}


{-# LINE 1060 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- A type that identifies a target. This is needed to marshal arrays of
-- GtkTargetEntries.
data TargetEntry = TargetEntry (Ptr Int8) InfoId
{-# LINE 1064 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- brain damaged API: the whole selection API doesn't need GtkTargetEntry
-- structure, but stupid Clipboard has two functions that only provide this
-- interface. Thus, convert the efficient Atoms back into strings, have
-- the clipboard functions convert them back to string before we get a
-- chance to free the freshly allocated strings.

withTargetEntries :: [(TargetTag, InfoId)] -> (Int -> Ptr () -> IO a) -> IO a
withTargetEntries tags fun = do
  ptrsInfo <- mapM (\(Atom tag, info) -> gdk_atom_name tag >>= \strPtr ->
                     return (TargetEntry strPtr info)) tags
  let len = length tags
  res <- withArrayLen ptrsInfo (\len ptr -> fun len (castPtr ptr))
  mapM_ (\(TargetEntry ptr _) -> g_free ptr) ptrsInfo
  return res

foreign import ccall unsafe "gdk_atom_name"
  gdk_atom_name :: Ptr () -> IO (Ptr Int8)
{-# LINE 1082 "Graphics/UI/Gtk/General/Structs.hsc" #-}

foreign import ccall unsafe "g_free"
  g_free :: Ptr Int8 -> IO ()
{-# LINE 1085 "Graphics/UI/Gtk/General/Structs.hsc" #-}

instance Storable TargetEntry where
  sizeOf _ = 16
{-# LINE 1088 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  alignment _ = alignment (undefined::Word32)
{-# LINE 1089 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  peek ptr = undefined
  poke ptr (TargetEntry cPtr info) = do
    (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr cPtr
{-# LINE 1092 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr (0::Word32)
{-# LINE 1093 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 12) ptr info
{-# LINE 1094 "Graphics/UI/Gtk/General/Structs.hsc" #-}

-- | A 'KeymapKey' is a hardware key that can be mapped to a keyval.
data KeymapKey = KeymapKey {
       keycode   :: Int -- ^ @keycode@ the hardware keycode. This is an identifying number for a physical key.
      ,group     :: Int -- ^ @group@ indicates movement in a horizontal direction. 
                      -- Usually groups are used for two different languages. 
                      -- In group  0, a key might have two English characters, 
                      -- and in group 1 it might have two Hebrew characters. 
                      -- The Hebrew characters will be printed on the key next to the English characters. 
                      -- indicates which symbol on the key will be used, 
                      -- in a vertical direction. So on a standard US keyboard, the                         
      ,level     :: Int -- ^ @level@ key with the number "1" on it also has the exclamation 
                      -- point ("!") character on it. The level
                      -- indicates whether to use the "1" or the "!" symbol. The letter keys are considered to
                      -- have a lowercase letter at level 0, and an uppercase letter at level 1, though only
                      -- the uppercase letter is printed.
    } deriving (Eq, Show) 
               
instance Storable KeymapKey where
  sizeOf _ = 12
{-# LINE 1114 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  alignment _ = alignment (undefined::Int32)
{-# LINE 1115 "Graphics/UI/Gtk/General/Structs.hsc" #-}
  peek ptr = do
    (keycode_  ::Word32)	<- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 1117 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (group_  ::Int32)	<- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 1118 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (level_ ::Int32)	<- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 1119 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    return $ KeymapKey (fromIntegral keycode_) (fromIntegral group_) (fromIntegral level_)
  poke ptr (KeymapKey keycode group level) = do
    (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr ((fromIntegral keycode)::Word32)
{-# LINE 1122 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr ((fromIntegral group)::Int32)
{-# LINE 1123 "Graphics/UI/Gtk/General/Structs.hsc" #-}
    (\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr ((fromIntegral level)::Int32)
{-# LINE 1124 "Graphics/UI/Gtk/General/Structs.hsc" #-}