{-# 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" #-} -- 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(..), GCValues(..), pokeGCValues, newGCValues, widgetGetState, widgetGetSavedState, Allocation, Requisition(..), treeIterSize, textIterSize, inputError, dialogGetUpper, dialogGetActionArea, fileSelectionGetButtons, ResponseId(..), fromResponse, toResponse, {-# LINE 55 "Graphics/UI/Gtk/General/Structs.hsc" #-} NativeWindowId, toNativeWindowId, fromNativeWindowId, nativeWindowIdNone, {-# LINE 60 "Graphics/UI/Gtk/General/Structs.hsc" #-} drawableGetID, {-# LINE 62 "Graphics/UI/Gtk/General/Structs.hsc" #-} toolbarChildButton, toolbarChildToggleButton, toolbarChildRadioButton, {-# LINE 66 "Graphics/UI/Gtk/General/Structs.hsc" #-} IconSize(..), {-# LINE 68 "Graphics/UI/Gtk/General/Structs.hsc" #-} comboGetList, {-# LINE 70 "Graphics/UI/Gtk/General/Structs.hsc" #-} widgetGetDrawWindow, widgetGetSize, layoutGetDrawWindow, windowGetFrame, styleGetForeground, styleGetBackground, styleGetLight, styleGetMiddle, styleGetDark, styleGetText, styleGetBase, styleGetAntiAliasing, colorSelectionDialogGetColor, colorSelectionDialogGetOkButton, colorSelectionDialogGetCancelButton, colorSelectionDialogGetHelpButton, dragContextGetActions, dragContextSetActions, dragContextGetSuggestedAction, dragContextSetSuggestedAction, dragContextGetAction, dragContextSetAction, SortColumnId, treeSortableDefaultSortColumnId, tagInvalid, selectionPrimary, selectionSecondary, selectionClipboard, targetString, selectionTypeAtom, selectionTypeInteger, selectionTypeString, selectionDataGetType, 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 import Graphics.UI.Gtk.Gdk.Enums (Function, Fill, SubwindowMode, LineStyle, CapStyle, JoinStyle) 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 123 "Graphics/UI/Gtk/General/Structs.hsc" #-} {-# LINE 126 "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 132 "Graphics/UI/Gtk/General/Structs.hsc" #-} alignment _ = alignment (undefined:: Int32) {-# LINE 133 "Graphics/UI/Gtk/General/Structs.hsc" #-} peek ptr = do (x_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr {-# LINE 135 "Graphics/UI/Gtk/General/Structs.hsc" #-} (y_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr {-# LINE 136 "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 139 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr ((fromIntegral y)::Int32) {-# LINE 140 "Graphics/UI/Gtk/General/Structs.hsc" #-} instance Storable Rectangle where sizeOf _ = 16 {-# LINE 143 "Graphics/UI/Gtk/General/Structs.hsc" #-} alignment _ = alignment (undefined:: Int32) {-# LINE 144 "Graphics/UI/Gtk/General/Structs.hsc" #-} peek ptr = do (x_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr {-# LINE 146 "Graphics/UI/Gtk/General/Structs.hsc" #-} (y_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr {-# LINE 147 "Graphics/UI/Gtk/General/Structs.hsc" #-} (width_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr {-# LINE 148 "Graphics/UI/Gtk/General/Structs.hsc" #-} (height_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 12) ptr {-# LINE 149 "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 153 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr ((fromIntegral y)::Int32) {-# LINE 154 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr ((fromIntegral width)::Int32) {-# LINE 155 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 12) ptr ((fromIntegral height)::Int32) {-# LINE 156 "Graphics/UI/Gtk/General/Structs.hsc" #-} instance Storable Color where sizeOf _ = 12 {-# LINE 159 "Graphics/UI/Gtk/General/Structs.hsc" #-} alignment _ = alignment (undefined::Word32) {-# LINE 160 "Graphics/UI/Gtk/General/Structs.hsc" #-} peek ptr = do red <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr {-# LINE 162 "Graphics/UI/Gtk/General/Structs.hsc" #-} green <- (\hsc_ptr -> peekByteOff hsc_ptr 6) ptr {-# LINE 163 "Graphics/UI/Gtk/General/Structs.hsc" #-} blue <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr {-# LINE 164 "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 167 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr red {-# LINE 168 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 6) ptr green {-# LINE 169 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr blue {-# LINE 170 "Graphics/UI/Gtk/General/Structs.hsc" #-} cPtr <- gdkColormapGetSystem gdkColormapAllocColor cPtr ptr 0 1 return () type ColorMap = () foreign import ccall unsafe "gdk_colormap_get_system" gdkColormapGetSystem :: IO (Ptr ColorMap) foreign import ccall unsafe "gdk_colormap_alloc_color" gdkColormapAllocColor :: Ptr ColorMap -> Ptr Color -> CInt -> CInt -> IO CInt foreign import ccall unsafe "gdk_colormap_query_color" gdkColormapQueryColor :: Ptr ColorMap -> CULong -> Ptr Color -> IO () -- entry GC -- | Intermediate data structure for 'GC's. -- -- * If @graphicsExposure@ is set then copying portions into a -- drawable will generate an @\"exposure\"@ event, even if the -- destination area is not currently visible. -- data GCValues = GCValues { foreground :: Color, background :: Color, function :: Function, fill :: Fill, tile :: Maybe Pixmap, stipple :: Maybe Pixmap, clipMask :: Maybe Pixmap, subwindowMode :: SubwindowMode, tsXOrigin :: Int, tsYOrigin :: Int, clipXOrigin:: Int, clipYOrigin:: Int, graphicsExposure :: Bool, lineWidth :: Int, lineStyle :: LineStyle, capStyle :: CapStyle, joinStyle :: JoinStyle } instance Storable GCValues where sizeOf _ = 88 {-# LINE 215 "Graphics/UI/Gtk/General/Structs.hsc" #-} alignment _ = alignment (undefined::Color) peek ptr = do -- gdk_gc_get_values does not fill in the r,g,b members of the foreground -- and background colours (it only fills in the allocated pixel value), -- so we have to fill them in here: let foregroundPtr, backgroundPtr :: Ptr Color foregroundPtr = (\hsc_ptr -> hsc_ptr `plusPtr` 0) ptr {-# LINE 222 "Graphics/UI/Gtk/General/Structs.hsc" #-} backgroundPtr = (\hsc_ptr -> hsc_ptr `plusPtr` 12) ptr {-# LINE 223 "Graphics/UI/Gtk/General/Structs.hsc" #-} (foregroundPixelPtr :: CULong) <- (\hsc_ptr -> peekByteOff hsc_ptr 0) foregroundPtr {-# LINE 224 "Graphics/UI/Gtk/General/Structs.hsc" #-} (backgroundPixelPtr :: CULong) <- (\hsc_ptr -> peekByteOff hsc_ptr 0) backgroundPtr {-# LINE 225 "Graphics/UI/Gtk/General/Structs.hsc" #-} colormapPtr <- gdkColormapGetSystem gdkColormapQueryColor colormapPtr foregroundPixelPtr foregroundPtr gdkColormapQueryColor colormapPtr backgroundPixelPtr backgroundPtr foreground_ <- peek ((\hsc_ptr -> hsc_ptr `plusPtr` 0) ptr) {-# LINE 230 "Graphics/UI/Gtk/General/Structs.hsc" #-} background_ <- peek ((\hsc_ptr -> hsc_ptr `plusPtr` 12) ptr) {-# LINE 231 "Graphics/UI/Gtk/General/Structs.hsc" #-} (function_ :: Word32) <- (\hsc_ptr -> peekByteOff hsc_ptr 28) ptr {-# LINE 232 "Graphics/UI/Gtk/General/Structs.hsc" #-} (fill_ :: Word32) <- (\hsc_ptr -> peekByteOff hsc_ptr 32) ptr {-# LINE 233 "Graphics/UI/Gtk/General/Structs.hsc" #-} tile_ <- do pPtr <- (\hsc_ptr -> peekByteOff hsc_ptr 36) ptr {-# LINE 235 "Graphics/UI/Gtk/General/Structs.hsc" #-} if (pPtr==nullPtr) then return Nothing else liftM Just $ makeNewGObject mkPixmap $ return pPtr stipple_ <- do pPtr <- (\hsc_ptr -> peekByteOff hsc_ptr 40) ptr {-# LINE 239 "Graphics/UI/Gtk/General/Structs.hsc" #-} if (pPtr==nullPtr) then return Nothing else liftM Just $ makeNewGObject mkPixmap $ return pPtr clipMask_ <- do pPtr <- (\hsc_ptr -> peekByteOff hsc_ptr 44) ptr {-# LINE 243 "Graphics/UI/Gtk/General/Structs.hsc" #-} if (pPtr==nullPtr) then return Nothing else liftM Just $ makeNewGObject mkPixmap $ return pPtr (subwindow_ :: Word32) {-# LINE 246 "Graphics/UI/Gtk/General/Structs.hsc" #-} <- (\hsc_ptr -> peekByteOff hsc_ptr 48) ptr {-# LINE 247 "Graphics/UI/Gtk/General/Structs.hsc" #-} (tsXOrigin_ :: Int32) {-# LINE 248 "Graphics/UI/Gtk/General/Structs.hsc" #-} <- (\hsc_ptr -> peekByteOff hsc_ptr 52) ptr {-# LINE 249 "Graphics/UI/Gtk/General/Structs.hsc" #-} (tsYOrigin_ :: Int32) {-# LINE 250 "Graphics/UI/Gtk/General/Structs.hsc" #-} <- (\hsc_ptr -> peekByteOff hsc_ptr 56) ptr {-# LINE 251 "Graphics/UI/Gtk/General/Structs.hsc" #-} (clipXOrigin_:: Int32) {-# LINE 252 "Graphics/UI/Gtk/General/Structs.hsc" #-} <- (\hsc_ptr -> peekByteOff hsc_ptr 60) ptr {-# LINE 253 "Graphics/UI/Gtk/General/Structs.hsc" #-} (clipYOrigin_:: Int32) {-# LINE 254 "Graphics/UI/Gtk/General/Structs.hsc" #-} <- (\hsc_ptr -> peekByteOff hsc_ptr 64) ptr {-# LINE 255 "Graphics/UI/Gtk/General/Structs.hsc" #-} (graphics_ :: Int32) {-# LINE 256 "Graphics/UI/Gtk/General/Structs.hsc" #-} <- (\hsc_ptr -> peekByteOff hsc_ptr 68) ptr {-# LINE 257 "Graphics/UI/Gtk/General/Structs.hsc" #-} (lineWidth_ :: Int32) {-# LINE 258 "Graphics/UI/Gtk/General/Structs.hsc" #-} <- (\hsc_ptr -> peekByteOff hsc_ptr 72) ptr {-# LINE 259 "Graphics/UI/Gtk/General/Structs.hsc" #-} (lineStyle_ :: Word32) {-# LINE 260 "Graphics/UI/Gtk/General/Structs.hsc" #-} <- (\hsc_ptr -> peekByteOff hsc_ptr 76) ptr {-# LINE 261 "Graphics/UI/Gtk/General/Structs.hsc" #-} (capStyle_ :: Word32) {-# LINE 262 "Graphics/UI/Gtk/General/Structs.hsc" #-} <- (\hsc_ptr -> peekByteOff hsc_ptr 80) ptr {-# LINE 263 "Graphics/UI/Gtk/General/Structs.hsc" #-} (joinStyle_ :: Word32) {-# LINE 264 "Graphics/UI/Gtk/General/Structs.hsc" #-} <- (\hsc_ptr -> peekByteOff hsc_ptr 84) ptr {-# LINE 265 "Graphics/UI/Gtk/General/Structs.hsc" #-} return $ GCValues { foreground = foreground_, background = background_, function = (toEnum.fromIntegral) function_, fill = (toEnum.fromIntegral) fill_, tile = tile_, stipple = stipple_, clipMask = clipMask_, subwindowMode = (toEnum.fromIntegral) subwindow_, tsXOrigin = fromIntegral tsXOrigin_, tsYOrigin = fromIntegral tsYOrigin_, clipXOrigin= fromIntegral clipXOrigin_, clipYOrigin= fromIntegral clipYOrigin_, graphicsExposure = toBool graphics_, lineWidth = fromIntegral lineWidth_, lineStyle = (toEnum.fromIntegral) lineStyle_, capStyle = (toEnum.fromIntegral) capStyle_, joinStyle = (toEnum.fromIntegral) joinStyle_ } pokeGCValues :: Ptr GCValues -> GCValues -> IO CInt pokeGCValues ptr (GCValues { foreground = foreground_, background = background_, function = function_, fill = fill_, tile = tile_, stipple = stipple_, clipMask = clipMask_, subwindowMode = subwindow_, tsXOrigin = tsXOrigin_, tsYOrigin = tsYOrigin_, clipXOrigin= clipXOrigin_, clipYOrigin= clipYOrigin_, graphicsExposure = graphics_, lineWidth = lineWidth_, lineStyle = lineStyle_, capStyle = capStyle_, joinStyle = joinStyle_ }) = do r <- newIORef 0 add r 1 $ {-# LINE 307 "Graphics/UI/Gtk/General/Structs.hsc" #-} poke ((\hsc_ptr -> hsc_ptr `plusPtr` 0) ptr) foreground_ {-# LINE 308 "Graphics/UI/Gtk/General/Structs.hsc" #-} add r 2 $ {-# LINE 309 "Graphics/UI/Gtk/General/Structs.hsc" #-} poke ((\hsc_ptr -> hsc_ptr `plusPtr` 12) ptr) background_ {-# LINE 310 "Graphics/UI/Gtk/General/Structs.hsc" #-} add r 8 $ {-# LINE 311 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 28) ptr {-# LINE 312 "Graphics/UI/Gtk/General/Structs.hsc" #-} (fromIntegral (fromEnum function_):: Word32) {-# LINE 313 "Graphics/UI/Gtk/General/Structs.hsc" #-} add r 16 $ {-# LINE 314 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 32) ptr {-# LINE 315 "Graphics/UI/Gtk/General/Structs.hsc" #-} (fromIntegral (fromEnum fill_):: Word32) {-# LINE 316 "Graphics/UI/Gtk/General/Structs.hsc" #-} case tile_ of Nothing -> return () Just tile_ -> add r 32 $ {-# LINE 319 "Graphics/UI/Gtk/General/Structs.hsc" #-} withForeignPtr (unPixmap tile_) $ (\hsc_ptr -> pokeByteOff hsc_ptr 36) ptr {-# LINE 321 "Graphics/UI/Gtk/General/Structs.hsc" #-} case stipple_ of Nothing -> return () Just stipple_ -> add r 64 $ {-# LINE 324 "Graphics/UI/Gtk/General/Structs.hsc" #-} withForeignPtr (unPixmap stipple_) $ (\hsc_ptr -> pokeByteOff hsc_ptr 40) ptr {-# LINE 326 "Graphics/UI/Gtk/General/Structs.hsc" #-} case clipMask_ of Nothing -> return () Just clipMask_ -> add r 128 $ {-# LINE 329 "Graphics/UI/Gtk/General/Structs.hsc" #-} withForeignPtr (unPixmap clipMask_) $ (\hsc_ptr -> pokeByteOff hsc_ptr 44) ptr {-# LINE 331 "Graphics/UI/Gtk/General/Structs.hsc" #-} add r 256 $ {-# LINE 332 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 48) ptr {-# LINE 333 "Graphics/UI/Gtk/General/Structs.hsc" #-} (fromIntegral (fromEnum subwindow_):: Word32) {-# LINE 334 "Graphics/UI/Gtk/General/Structs.hsc" #-} add r 512 $ {-# LINE 335 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 52) ptr {-# LINE 336 "Graphics/UI/Gtk/General/Structs.hsc" #-} (fromIntegral tsXOrigin_:: Int32) {-# LINE 337 "Graphics/UI/Gtk/General/Structs.hsc" #-} add r 1024 $ {-# LINE 338 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 56) ptr {-# LINE 339 "Graphics/UI/Gtk/General/Structs.hsc" #-} (fromIntegral tsYOrigin_:: Int32) {-# LINE 340 "Graphics/UI/Gtk/General/Structs.hsc" #-} add r 2048 $ {-# LINE 341 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 60) ptr {-# LINE 342 "Graphics/UI/Gtk/General/Structs.hsc" #-} (fromIntegral clipXOrigin_:: Int32) {-# LINE 343 "Graphics/UI/Gtk/General/Structs.hsc" #-} add r 4096 $ {-# LINE 344 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 64) ptr {-# LINE 345 "Graphics/UI/Gtk/General/Structs.hsc" #-} (fromIntegral clipYOrigin_:: Int32) {-# LINE 346 "Graphics/UI/Gtk/General/Structs.hsc" #-} add r 8192 $ {-# LINE 347 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 68) ptr {-# LINE 348 "Graphics/UI/Gtk/General/Structs.hsc" #-} (fromBool graphics_:: Int32) {-# LINE 349 "Graphics/UI/Gtk/General/Structs.hsc" #-} add r 16384 $ {-# LINE 350 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 72) ptr {-# LINE 351 "Graphics/UI/Gtk/General/Structs.hsc" #-} (fromIntegral lineWidth_:: Int32) {-# LINE 352 "Graphics/UI/Gtk/General/Structs.hsc" #-} add r 32768 $ {-# LINE 353 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 76) ptr {-# LINE 354 "Graphics/UI/Gtk/General/Structs.hsc" #-} (fromIntegral (fromEnum lineStyle_):: Word32) {-# LINE 355 "Graphics/UI/Gtk/General/Structs.hsc" #-} add r 65536 $ {-# LINE 356 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 80) ptr {-# LINE 357 "Graphics/UI/Gtk/General/Structs.hsc" #-} (fromIntegral (fromEnum capStyle_):: Word32) {-# LINE 358 "Graphics/UI/Gtk/General/Structs.hsc" #-} add r 131072 $ {-# LINE 359 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 84) ptr {-# LINE 360 "Graphics/UI/Gtk/General/Structs.hsc" #-} (fromIntegral (fromEnum joinStyle_):: Word32) {-# LINE 361 "Graphics/UI/Gtk/General/Structs.hsc" #-} readIORef r where add :: IORef CInt -> CInt -> IO () -> IO () add r mVal act = handle (\(ErrorCall _) -> return ()) $ do act modifyIORef r (\val -> val+mVal) -- constant newGCValues An empty record of 'GCValues'. -- -- * Use this value instead of the constructor to avoid compiler wanings -- about uninitialized fields. -- newGCValues :: GCValues newGCValues = GCValues { foreground = undefined, background = undefined, function = undefined, fill = undefined, tile = Nothing, stipple = Nothing, clipMask = Nothing, subwindowMode = undefined, tsXOrigin = undefined, tsYOrigin = undefined, clipXOrigin= undefined, clipYOrigin= undefined, graphicsExposure = undefined, lineWidth = undefined, lineStyle = undefined, capStyle = undefined, joinStyle = undefined } -- Widget related methods -- | Retrieve the current state of the widget. -- -- * The state refers to different modes of user interaction, see -- 'StateType' for more information. -- widgetGetState :: WidgetClass w => w -> IO StateType widgetGetState w = liftM (\x -> toEnum (fromIntegral (x :: Word8))) $ {-# LINE 404 "Graphics/UI/Gtk/General/Structs.hsc" #-} withForeignPtr ((unWidget . toWidget) w) $ (\hsc_ptr -> peekByteOff hsc_ptr 18) {-# LINE 405 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- | Retrieve the current state of the widget. -- -- * If a widget is turned insensitive, the previous state is stored in -- a specific location. This function retrieves this previous state. -- widgetGetSavedState :: WidgetClass w => w -> IO StateType widgetGetSavedState w = liftM (\x -> toEnum (fromIntegral (x :: Word8))) $ {-# LINE 414 "Graphics/UI/Gtk/General/Structs.hsc" #-} withForeignPtr ((unWidget . toWidget) w) $ (\hsc_ptr -> peekByteOff hsc_ptr 19) {-# LINE 415 "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 435 "Graphics/UI/Gtk/General/Structs.hsc" #-} alignment _ = alignment (undefined::Int32) {-# LINE 436 "Graphics/UI/Gtk/General/Structs.hsc" #-} peek ptr = do (width_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr {-# LINE 438 "Graphics/UI/Gtk/General/Structs.hsc" #-} (height_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr {-# LINE 439 "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 442 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr ((fromIntegral height)::Int32) {-# LINE 443 "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 450 "Graphics/UI/Gtk/General/Structs.hsc" #-} inputError = -1 {-# LINE 451 "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 = 16 {-# LINE 457 "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 = 56 {-# LINE 464 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- Dialog related methods -- | Get the upper part of a dialog. -- -- * The upper part of a dialog window consists of a 'VBox'. -- Add the required widgets into this box. -- dialogGetUpper :: DialogClass dc => dc -> IO VBox dialogGetUpper dc = makeNewObject mkVBox $ liftM castPtr $ withForeignPtr ((unDialog.toDialog) dc) (\hsc_ptr -> peekByteOff hsc_ptr 148) {-# LINE 475 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- | Extract the action area of a dialog box. -- -- * This -- is useful to add some special widgets that cannot be added with -- dialogAddActionWidget. -- dialogGetActionArea :: DialogClass dc => dc -> IO HBox dialogGetActionArea dc = makeNewObject mkHBox $ liftM castPtr $ withForeignPtr ((unDialog.toDialog) dc) (\hsc_ptr -> peekByteOff hsc_ptr 152) {-# LINE 485 "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 573 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- | The identifer of a window of the underlying windowing system. -- {-# LINE 586 "Graphics/UI/Gtk/General/Structs.hsc" #-} newtype NativeWindowId = NativeWindowId Word32 deriving (Eq, Show) {-# LINE 587 "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 596 "Graphics/UI/Gtk/General/Structs.hsc" #-} {-# LINE 597 "Graphics/UI/Gtk/General/Structs.hsc" #-} {-# LINE 602 "Graphics/UI/Gtk/General/Structs.hsc" #-} foreign import ccall unsafe "gdk_x11_drawable_get_xid" gdk_x11_drawable_get_xid :: (Ptr Drawable) -> IO CInt {-# LINE 605 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- | Get 'NativeWindowId' of 'Drawable'. drawableGetID :: DrawableClass d => d -> IO NativeWindowId drawableGetID d = liftM toNativeWindowId $ (\(Drawable drawable) -> {-# LINE 620 "Graphics/UI/Gtk/General/Structs.hsc" #-} withForeignPtr drawable gdk_x11_drawable_get_xid {-# LINE 624 "Graphics/UI/Gtk/General/Structs.hsc" #-} ) (toDrawable d) {-# LINE 627 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- Static values for different Toolbar widgets. -- -- * c2hs and hsc should agree on types! -- toolbarChildButton, toolbarChildToggleButton, toolbarChildRadioButton :: CInt -- \#gtk2hs_type GtkToolbarChildType toolbarChildButton = 1 {-# LINE 634 "Graphics/UI/Gtk/General/Structs.hsc" #-} toolbarChildToggleButton = 2 {-# LINE 635 "Graphics/UI/Gtk/General/Structs.hsc" #-} toolbarChildRadioButton = 3 {-# LINE 636 "Graphics/UI/Gtk/General/Structs.hsc" #-} {-# LINE 637 "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 674 "Graphics/UI/Gtk/General/Structs.hsc" #-} toEnum 1 = IconSizeMenu {-# LINE 675 "Graphics/UI/Gtk/General/Structs.hsc" #-} toEnum 2 = IconSizeSmallToolbar {-# LINE 676 "Graphics/UI/Gtk/General/Structs.hsc" #-} toEnum 3 = IconSizeLargeToolbar {-# LINE 677 "Graphics/UI/Gtk/General/Structs.hsc" #-} toEnum 4 = IconSizeButton {-# LINE 678 "Graphics/UI/Gtk/General/Structs.hsc" #-} toEnum 5 = IconSizeDnd {-# LINE 679 "Graphics/UI/Gtk/General/Structs.hsc" #-} toEnum 6 = IconSizeDialog {-# LINE 680 "Graphics/UI/Gtk/General/Structs.hsc" #-} toEnum n = IconSizeUser n fromEnum IconSizeInvalid = 0 {-# LINE 682 "Graphics/UI/Gtk/General/Structs.hsc" #-} fromEnum IconSizeMenu = 1 {-# LINE 683 "Graphics/UI/Gtk/General/Structs.hsc" #-} fromEnum IconSizeSmallToolbar = 2 {-# LINE 684 "Graphics/UI/Gtk/General/Structs.hsc" #-} fromEnum IconSizeLargeToolbar = 3 {-# LINE 685 "Graphics/UI/Gtk/General/Structs.hsc" #-} fromEnum IconSizeButton = 4 {-# LINE 686 "Graphics/UI/Gtk/General/Structs.hsc" #-} fromEnum IconSizeDnd = 5 {-# LINE 687 "Graphics/UI/Gtk/General/Structs.hsc" #-} fromEnum IconSizeDialog = 6 {-# LINE 688 "Graphics/UI/Gtk/General/Structs.hsc" #-} fromEnum (IconSizeUser n) = n -- entry Widget Combo {-# LINE 693 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- | Extract the List container from a 'Combo' box. -- comboGetList :: Combo -> IO List comboGetList c = withForeignPtr (unCombo c) $ \cPtr -> makeNewObject mkList $ (\hsc_ptr -> peekByteOff hsc_ptr 92) cPtr {-# LINE 698 "Graphics/UI/Gtk/General/Structs.hsc" #-} {-# LINE 699 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- FileSelection related methods -- | Extract the buttons of a fileselection. -- fileSelectionGetButtons :: FileSelectionClass fsel => fsel -> IO (Button, Button) fileSelectionGetButtons fsel = do ok <- butPtrToButton (\hsc_ptr -> peekByteOff hsc_ptr 180) {-# LINE 709 "Graphics/UI/Gtk/General/Structs.hsc" #-} cancel <- butPtrToButton (\hsc_ptr -> peekByteOff hsc_ptr 184) {-# LINE 710 "Graphics/UI/Gtk/General/Structs.hsc" #-} return (ok,cancel) where butPtrToButton bp = makeNewObject mkButton $ liftM castPtr $ withForeignPtr ((unFileSelection . toFileSelection) fsel) bp -- DrawingArea related methods -- | Retrieves the 'DrawWindow' that the widget draws onto. -- -- This function thows an error if the widget has not yet been realized, since -- a widget does not allocate its window resources until just before it is -- displayed on the screen. You can use the -- 'Graphics.UI.Gtk.Abstract.Widget.onRealize' signal to give you the -- opportunity to use a widget's 'DrawWindow' as soon as it has been created -- but before the widget is displayed. -- widgetGetDrawWindow :: WidgetClass widget => widget -> IO DrawWindow widgetGetDrawWindow da = withForeignPtr (unWidget.toWidget $ da) $ \da' -> do drawWindowPtr <- (\hsc_ptr -> peekByteOff hsc_ptr 52) da' {-# LINE 730 "Graphics/UI/Gtk/General/Structs.hsc" #-} if drawWindowPtr == nullPtr then fail "widgetGetDrawWindow: no DrawWindow available (the widget is probably not realized)" else makeNewGObject mkDrawWindow (return $ castPtr drawWindowPtr) -- | Returns the current size. -- -- * This information may be out of date if the user is resizing the window. -- widgetGetSize :: WidgetClass widget => widget -> IO (Int, Int) widgetGetSize da = withForeignPtr (unWidget.toWidget $ da) $ \wPtr -> do (width :: Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 8) {-# LINE 741 "Graphics/UI/Gtk/General/Structs.hsc" #-} ((\hsc_ptr -> hsc_ptr `plusPtr` 36) wPtr) {-# LINE 742 "Graphics/UI/Gtk/General/Structs.hsc" #-} (height :: Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 12) {-# LINE 743 "Graphics/UI/Gtk/General/Structs.hsc" #-} ((\hsc_ptr -> hsc_ptr `plusPtr` 36) wPtr) {-# LINE 744 "Graphics/UI/Gtk/General/Structs.hsc" #-} return (fromIntegral width, fromIntegral height) -- Layout related methods -- | Retrieves the 'Drawable' part. -- layoutGetDrawWindow :: Layout -> IO DrawWindow layoutGetDrawWindow lay = makeNewGObject mkDrawWindow $ withForeignPtr (unLayout lay) $ \lay' -> liftM castPtr $ (\hsc_ptr -> peekByteOff hsc_ptr 88) lay' {-# LINE 754 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- Window related methods -- | Retrieves the frame 'DrawWindow' that contains a 'Window'. -- windowGetFrame :: WindowClass widget => widget -> IO (Maybe DrawWindow) windowGetFrame da = withForeignPtr (unWidget.toWidget $ da) $ \da' -> do drawWindowPtr <- (\hsc_ptr -> peekByteOff hsc_ptr 104) da' {-# LINE 763 "Graphics/UI/Gtk/General/Structs.hsc" #-} if drawWindowPtr == nullPtr then return Nothing else liftM Just $ makeNewGObject mkDrawWindow (return $ castPtr drawWindowPtr) -- 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` 12) stPtr) (fromEnum ty) {-# LINE 780 "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` 72) stPtr) (fromEnum ty) {-# LINE 792 "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` 132) stPtr) (fromEnum ty) {-# LINE 804 "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` 252) stPtr) (fromEnum ty) {-# LINE 816 "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` 192) stPtr) (fromEnum ty) {-# LINE 828 "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` 312) stPtr) (fromEnum ty) {-# LINE 840 "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` 372) stPtr) (fromEnum ty) {-# LINE 854 "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` 432) stPtr) (fromEnum ty) {-# LINE 870 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- | Retrieve the ColorSelection object contained within the dialog. colorSelectionDialogGetColor :: ColorSelectionDialog -> IO ColorSelection colorSelectionDialogGetColor cd = makeNewObject mkColorSelection $ liftM castPtr $ withForeignPtr (unColorSelectionDialog cd) (\hsc_ptr -> peekByteOff hsc_ptr 160) {-# LINE 877 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- | Retrieve the OK button widget contained within the dialog. colorSelectionDialogGetOkButton :: ColorSelectionDialog -> IO Button colorSelectionDialogGetOkButton cd = makeNewObject mkButton $ liftM castPtr $ withForeignPtr (unColorSelectionDialog cd) (\hsc_ptr -> peekByteOff hsc_ptr 164) {-# LINE 884 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- | Retrieve the Cancel button widget contained within the dialog. colorSelectionDialogGetCancelButton :: ColorSelectionDialog -> IO Button colorSelectionDialogGetCancelButton cd = makeNewObject mkButton $ liftM castPtr $ withForeignPtr (unColorSelectionDialog cd) (\hsc_ptr -> peekByteOff hsc_ptr 168) {-# LINE 891 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- | Retrieve the Help button widget contained within the dialog. colorSelectionDialogGetHelpButton :: ColorSelectionDialog -> IO Button colorSelectionDialogGetHelpButton cd = makeNewObject mkButton $ liftM castPtr $ withForeignPtr (unColorSelectionDialog cd) (\hsc_ptr -> peekByteOff hsc_ptr 172) {-# LINE 898 "Graphics/UI/Gtk/General/Structs.hsc" #-} dragContextGetActions :: DragContext -> IO Int dragContextGetActions dc = liftM (fromIntegral :: Int32 -> Int) $ {-# LINE 901 "Graphics/UI/Gtk/General/Structs.hsc" #-} withForeignPtr (unDragContext dc) (\hsc_ptr -> peekByteOff hsc_ptr 32) {-# LINE 902 "Graphics/UI/Gtk/General/Structs.hsc" #-} dragContextSetActions :: DragContext -> Int -> IO () dragContextSetActions dc val = withForeignPtr (unDragContext dc) $ \ptr -> (\hsc_ptr -> pokeByteOff hsc_ptr 32) ptr (fromIntegral val :: Int32) {-# LINE 906 "Graphics/UI/Gtk/General/Structs.hsc" #-} dragContextGetAction :: DragContext -> IO Int dragContextGetAction dc = liftM (fromIntegral :: Int32 -> Int) $ {-# LINE 909 "Graphics/UI/Gtk/General/Structs.hsc" #-} withForeignPtr (unDragContext dc) (\hsc_ptr -> peekByteOff hsc_ptr 40) {-# LINE 910 "Graphics/UI/Gtk/General/Structs.hsc" #-} dragContextSetAction :: DragContext -> Int -> IO () dragContextSetAction dc val = withForeignPtr (unDragContext dc) $ \ptr -> (\hsc_ptr -> pokeByteOff hsc_ptr 40) ptr (fromIntegral val :: Int32) {-# LINE 914 "Graphics/UI/Gtk/General/Structs.hsc" #-} dragContextGetSuggestedAction :: DragContext -> IO Int dragContextGetSuggestedAction dc = liftM (fromIntegral :: Int32 -> Int) $ {-# LINE 917 "Graphics/UI/Gtk/General/Structs.hsc" #-} withForeignPtr (unDragContext dc) (\hsc_ptr -> peekByteOff hsc_ptr 36) {-# LINE 918 "Graphics/UI/Gtk/General/Structs.hsc" #-} dragContextSetSuggestedAction :: DragContext -> Int -> IO () dragContextSetSuggestedAction dc val = withForeignPtr (unDragContext dc) $ \ptr -> (\hsc_ptr -> pokeByteOff hsc_ptr 36) ptr (fromIntegral val :: Int32) {-# LINE 922 "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 934 "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 942 "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 947 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- | The secondary selection. Rarely used. selectionSecondary :: SelectionTag selectionSecondary = intToAtom 2 {-# LINE 951 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- | The modern clipboard that is filled by copy or cut commands. selectionClipboard :: SelectionTag selectionClipboard = intToAtom 69 {-# LINE 955 "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 959 "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 964 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- | The type indicating that the associated data consists of integers. selectionTypeInteger :: SelectionTypeTag selectionTypeInteger = intToAtom 19 {-# LINE 968 "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 973 "Graphics/UI/Gtk/General/Structs.hsc" #-} -- | Extract the type field of SelectionData*. This should be in the -- Selection modules but c2hs chokes on the 'type' field. selectionDataGetType :: Ptr () -> IO SelectionTypeTag selectionDataGetType selPtr = liftM intToAtom $ (\hsc_ptr -> peekByteOff hsc_ptr 8) selPtr {-# LINE 979 "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 983 "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 1001 "Graphics/UI/Gtk/General/Structs.hsc" #-} foreign import ccall unsafe "g_free" g_free :: Ptr Int8 -> IO () {-# LINE 1004 "Graphics/UI/Gtk/General/Structs.hsc" #-} instance Storable TargetEntry where sizeOf _ = 12 {-# LINE 1007 "Graphics/UI/Gtk/General/Structs.hsc" #-} alignment _ = alignment (undefined::Word32) {-# LINE 1008 "Graphics/UI/Gtk/General/Structs.hsc" #-} peek ptr = undefined poke ptr (TargetEntry cPtr info) = do (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr cPtr {-# LINE 1011 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr (0::Word32) {-# LINE 1012 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr info {-# LINE 1013 "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 1033 "Graphics/UI/Gtk/General/Structs.hsc" #-} alignment _ = alignment (undefined::Int32) {-# LINE 1034 "Graphics/UI/Gtk/General/Structs.hsc" #-} peek ptr = do (keycode_ ::Word32) <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr {-# LINE 1036 "Graphics/UI/Gtk/General/Structs.hsc" #-} (group_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr {-# LINE 1037 "Graphics/UI/Gtk/General/Structs.hsc" #-} (level_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr {-# LINE 1038 "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 1041 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr ((fromIntegral group)::Int32) {-# LINE 1042 "Graphics/UI/Gtk/General/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr ((fromIntegral level)::Int32) {-# LINE 1043 "Graphics/UI/Gtk/General/Structs.hsc" #-}