{-# LINE 1 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LANGUAGE ScopedTypeVariables, TypeSynonymInstances, FlexibleInstances #-}
{-# OPTIONS_HADDOCK hide #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# LINE 12 "Graphics/UI/Gtk/General/Structs.hsc" #-}
module Graphics.UI.Gtk.General.Structs (
Point,
Rectangle(..),
Color(..),
{-# LINE 44 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 45 "Graphics/UI/Gtk/General/Structs.hsc" #-}
GCValues(..),
pokeGCValues,
newGCValues,
widgetGetState,
widgetGetSavedState,
{-# LINE 51 "Graphics/UI/Gtk/General/Structs.hsc" #-}
Allocation,
Requisition(..),
treeIterSize,
textIterSize,
inputError,
{-# LINE 57 "Graphics/UI/Gtk/General/Structs.hsc" #-}
dialogGetUpper,
dialogGetActionArea,
fileSelectionGetButtons,
{-# LINE 61 "Graphics/UI/Gtk/General/Structs.hsc" #-}
ResponseId(..),
fromResponse,
toResponse,
{-# LINE 65 "Graphics/UI/Gtk/General/Structs.hsc" #-}
NativeWindowId,
toNativeWindowId,
fromNativeWindowId,
nativeWindowIdNone,
{-# LINE 70 "Graphics/UI/Gtk/General/Structs.hsc" #-}
drawableGetID,
{-# LINE 72 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 73 "Graphics/UI/Gtk/General/Structs.hsc" #-}
toolbarChildButton,
toolbarChildToggleButton,
toolbarChildRadioButton,
{-# LINE 77 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 78 "Graphics/UI/Gtk/General/Structs.hsc" #-}
IconSize(..),
{-# LINE 80 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 81 "Graphics/UI/Gtk/General/Structs.hsc" #-}
comboGetList,
{-# LINE 83 "Graphics/UI/Gtk/General/Structs.hsc" #-}
widgetGetDrawWindow,
widgetGetSize,
windowGetFrame,
{-# LINE 87 "Graphics/UI/Gtk/General/Structs.hsc" #-}
styleGetForeground,
styleGetBackground,
styleGetLight,
styleGetMiddle,
styleGetDark,
styleGetText,
styleGetBase,
styleGetAntiAliasing,
{-# LINE 96 "Graphics/UI/Gtk/General/Structs.hsc" #-}
colorSelectionDialogGetColor,
colorSelectionDialogGetOkButton,
colorSelectionDialogGetCancelButton,
colorSelectionDialogGetHelpButton,
dragContextGetActions,
dragContextSetActions,
dragContextGetSuggestedAction,
dragContextSetSuggestedAction,
dragContextGetAction,
dragContextSetAction,
{-# LINE 107 "Graphics/UI/Gtk/General/Structs.hsc" #-}
SortColumnId,
treeSortableDefaultSortColumnId,
tagInvalid,
selectionPrimary,
selectionSecondary,
selectionClipboard,
targetString,
selectionTypeAtom,
selectionTypeInteger,
selectionTypeString,
{-# LINE 118 "Graphics/UI/Gtk/General/Structs.hsc" #-}
selectionDataGetType,
{-# LINE 120 "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.Gdk.Enums (Function, Fill, SubwindowMode,
LineStyle, CapStyle, JoinStyle)
{-# LINE 137 "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 142 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 145 "Graphics/UI/Gtk/General/Structs.hsc" #-}
type Point = (Int, Int)
instance Storable Point where
sizeOf :: Point -> Int
sizeOf Point
_ = Int
8
{-# LINE 151 "Graphics/UI/Gtk/General/Structs.hsc" #-}
alignment _ = alignment (undefined:: Int32)
{-# LINE 152 "Graphics/UI/Gtk/General/Structs.hsc" #-}
peek ptr = do
(x_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 154 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(y_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 155 "Graphics/UI/Gtk/General/Structs.hsc" #-}
return $ (fromIntegral x_, fromIntegral y_)
poke :: Ptr Point -> Point -> IO ()
poke Ptr Point
ptr (Int
x, Int
y) = do
(\Ptr Point
hsc_ptr -> Ptr Point -> Int -> Int32 -> IO ()
forall b. Ptr b -> Int -> Int32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Point
hsc_ptr Int
0) Ptr Point
ptr ((Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x)::Int32)
{-# LINE 158 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr ((fromIntegral y)::Int32)
{-# LINE 159 "Graphics/UI/Gtk/General/Structs.hsc" #-}
instance Storable Rectangle where
sizeOf :: Rectangle -> Int
sizeOf Rectangle
_ = Int
16
{-# LINE 162 "Graphics/UI/Gtk/General/Structs.hsc" #-}
alignment _ = alignment (undefined:: Int32)
{-# LINE 163 "Graphics/UI/Gtk/General/Structs.hsc" #-}
peek ptr = do
(x_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 165 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(y_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 166 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(width_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 167 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(height_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 12) ptr
{-# LINE 168 "Graphics/UI/Gtk/General/Structs.hsc" #-}
return $ Rectangle (fromIntegral x_) (fromIntegral y_)
(fromIntegral width_) (fromIntegral height_)
poke :: Ptr Rectangle -> Rectangle -> IO ()
poke Ptr Rectangle
ptr (Rectangle Int
x Int
y Int
width Int
height) = do
(\Ptr Rectangle
hsc_ptr -> Ptr Rectangle -> Int -> Int32 -> IO ()
forall b. Ptr b -> Int -> Int32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Rectangle
hsc_ptr Int
0) Ptr Rectangle
ptr ((Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x)::Int32)
{-# LINE 172 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr ((fromIntegral y)::Int32)
{-# LINE 173 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr ((fromIntegral width)::Int32)
{-# LINE 174 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 12) ptr ((fromIntegral height)::Int32)
{-# LINE 175 "Graphics/UI/Gtk/General/Structs.hsc" #-}
instance Storable Color where
sizeOf :: Color -> Int
sizeOf Color
_ = Int
12
{-# LINE 178 "Graphics/UI/Gtk/General/Structs.hsc" #-}
alignment _ = alignment (undefined::Word32)
{-# LINE 179 "Graphics/UI/Gtk/General/Structs.hsc" #-}
peek ptr = do
red <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 181 "Graphics/UI/Gtk/General/Structs.hsc" #-}
green <- (\hsc_ptr -> peekByteOff hsc_ptr 6) ptr
{-# LINE 182 "Graphics/UI/Gtk/General/Structs.hsc" #-}
blue <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 183 "Graphics/UI/Gtk/General/Structs.hsc" #-}
return $ Color red green blue
poke :: Ptr Color -> Color -> IO ()
poke Ptr Color
ptr (Color Word16
red Word16
green Word16
blue) = do
(\Ptr Color
hsc_ptr -> Ptr Color -> Int -> Int32 -> IO ()
forall b. Ptr b -> Int -> Int32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Color
hsc_ptr Int
0) Ptr Color
ptr (Int32
0::Int32)
{-# LINE 186 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr red
{-# LINE 187 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 6) ptr green
{-# LINE 188 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr blue
{-# LINE 189 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 190 "Graphics/UI/Gtk/General/Structs.hsc" #-}
cPtr <- gdkColormapGetSystem
Ptr () -> Ptr Color -> CInt -> CInt -> IO CInt
gdkColormapAllocColor Ptr ()
cPtr Ptr Color
ptr CInt
0 CInt
1
{-# LINE 193 "Graphics/UI/Gtk/General/Structs.hsc" #-}
return ()
{-# LINE 214 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 216 "Graphics/UI/Gtk/General/Structs.hsc" #-}
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 ()
data GCValues = GCValues {
GCValues -> Color
foreground :: Color,
GCValues -> Color
background :: Color,
GCValues -> Function
function :: Function,
GCValues -> Fill
fill :: Fill,
GCValues -> Maybe Pixmap
tile :: Maybe Pixmap,
GCValues -> Maybe Pixmap
stipple :: Maybe Pixmap,
GCValues -> Maybe Pixmap
clipMask :: Maybe Pixmap,
GCValues -> SubwindowMode
subwindowMode :: SubwindowMode,
GCValues -> Int
tsXOrigin :: Int,
GCValues -> Int
tsYOrigin :: Int,
GCValues -> Int
clipXOrigin:: Int,
GCValues -> Int
clipYOrigin:: Int,
GCValues -> Bool
graphicsExposure :: Bool,
GCValues -> Int
lineWidth :: Int,
GCValues -> LineStyle
lineStyle :: LineStyle,
GCValues -> CapStyle
capStyle :: CapStyle,
GCValues -> JoinStyle
joinStyle :: JoinStyle
}
instance Storable GCValues where
sizeOf :: GCValues -> Int
sizeOf GCValues
_ = Int
104
{-# LINE 257 "Graphics/UI/Gtk/General/Structs.hsc" #-}
alignment _ = alignment (undefined::Color)
peek :: Ptr GCValues -> IO GCValues
peek Ptr GCValues
ptr = do
let foregroundPtr, backgroundPtr :: Ptr Color
foregroundPtr :: Ptr Color
foregroundPtr = (\Ptr GCValues
hsc_ptr -> Ptr GCValues
hsc_ptr Ptr GCValues -> Int -> Ptr Color
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) Ptr GCValues
ptr
{-# LINE 264 "Graphics/UI/Gtk/General/Structs.hsc" #-}
backgroundPtr :: Ptr Color
backgroundPtr = (\Ptr GCValues
hsc_ptr -> Ptr GCValues
hsc_ptr Ptr GCValues -> Int -> Ptr Color
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) Ptr GCValues
ptr
{-# LINE 265 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(foregroundPixelPtr :: CULong) <- (\hsc_ptr -> peekByteOff hsc_ptr 0) foregroundPtr
{-# LINE 266 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(backgroundPixelPtr :: CULong) <- (\hsc_ptr -> peekByteOff hsc_ptr 0) backgroundPtr
{-# LINE 267 "Graphics/UI/Gtk/General/Structs.hsc" #-}
colormapPtr <- gdkColormapGetSystem
Ptr () -> CULong -> Ptr Color -> IO ()
gdkColormapQueryColor Ptr ()
colormapPtr CULong
foregroundPixelPtr Ptr Color
foregroundPtr
Ptr () -> CULong -> Ptr Color -> IO ()
gdkColormapQueryColor Ptr ()
colormapPtr CULong
backgroundPixelPtr Ptr Color
backgroundPtr
Color
foreground_ <- Ptr Color -> IO Color
forall a. Storable a => Ptr a -> IO a
peek ((\Ptr GCValues
hsc_ptr -> Ptr GCValues
hsc_ptr Ptr GCValues -> Int -> Ptr Color
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) Ptr GCValues
ptr)
{-# LINE 272 "Graphics/UI/Gtk/General/Structs.hsc" #-}
background_ <- peek ((\hsc_ptr -> hsc_ptr `plusPtr` 12) ptr)
{-# LINE 273 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(function_ :: Word32) <- (\hsc_ptr -> peekByteOff hsc_ptr 32) ptr
{-# LINE 274 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(fill_ :: Word32) <- (\hsc_ptr -> peekByteOff hsc_ptr 36) ptr
{-# LINE 275 "Graphics/UI/Gtk/General/Structs.hsc" #-}
tile_ <- do
pPtr <- (\hsc_ptr -> peekByteOff hsc_ptr 40) ptr
{-# LINE 277 "Graphics/UI/Gtk/General/Structs.hsc" #-}
if (pPtr==nullPtr) then return Nothing else
liftM Just $ makeNewGObject mkPixmap $ return pPtr
Maybe Pixmap
stipple_ <- do
Ptr Pixmap
pPtr <- (\Ptr GCValues
hsc_ptr -> Ptr GCValues -> Int -> IO (Ptr Pixmap)
forall b. Ptr b -> Int -> IO (Ptr Pixmap)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr GCValues
hsc_ptr Int
48) Ptr GCValues
ptr
{-# LINE 281 "Graphics/UI/Gtk/General/Structs.hsc" #-}
if (Ptr Pixmap
pPtrPtr Pixmap -> Ptr Pixmap -> Bool
forall a. Eq a => a -> a -> Bool
==Ptr Pixmap
forall a. Ptr a
nullPtr) then Maybe Pixmap -> IO (Maybe Pixmap)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixmap
forall a. Maybe a
Nothing else
(Pixmap -> Maybe Pixmap) -> IO Pixmap -> IO (Maybe Pixmap)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Pixmap -> Maybe Pixmap
forall a. a -> Maybe a
Just (IO Pixmap -> IO (Maybe Pixmap)) -> IO Pixmap -> IO (Maybe Pixmap)
forall a b. (a -> b) -> a -> b
$ (ForeignPtr Pixmap -> Pixmap, FinalizerPtr Pixmap)
-> IO (Ptr Pixmap) -> IO Pixmap
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewGObject (ForeignPtr Pixmap -> Pixmap, FinalizerPtr Pixmap)
forall {a}. (ForeignPtr Pixmap -> Pixmap, FinalizerPtr a)
mkPixmap (IO (Ptr Pixmap) -> IO Pixmap) -> IO (Ptr Pixmap) -> IO Pixmap
forall a b. (a -> b) -> a -> b
$ Ptr Pixmap -> IO (Ptr Pixmap)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Pixmap
pPtr
Maybe Pixmap
clipMask_ <- do
Ptr Pixmap
pPtr <- (\Ptr GCValues
hsc_ptr -> Ptr GCValues -> Int -> IO (Ptr Pixmap)
forall b. Ptr b -> Int -> IO (Ptr Pixmap)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr GCValues
hsc_ptr Int
56) Ptr GCValues
ptr
{-# LINE 285 "Graphics/UI/Gtk/General/Structs.hsc" #-}
if (Ptr Pixmap
pPtrPtr Pixmap -> Ptr Pixmap -> Bool
forall a. Eq a => a -> a -> Bool
==Ptr Pixmap
forall a. Ptr a
nullPtr) then Maybe Pixmap -> IO (Maybe Pixmap)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixmap
forall a. Maybe a
Nothing else
(Pixmap -> Maybe Pixmap) -> IO Pixmap -> IO (Maybe Pixmap)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Pixmap -> Maybe Pixmap
forall a. a -> Maybe a
Just (IO Pixmap -> IO (Maybe Pixmap)) -> IO Pixmap -> IO (Maybe Pixmap)
forall a b. (a -> b) -> a -> b
$ (ForeignPtr Pixmap -> Pixmap, FinalizerPtr Pixmap)
-> IO (Ptr Pixmap) -> IO Pixmap
forall obj.
GObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewGObject (ForeignPtr Pixmap -> Pixmap, FinalizerPtr Pixmap)
forall {a}. (ForeignPtr Pixmap -> Pixmap, FinalizerPtr a)
mkPixmap (IO (Ptr Pixmap) -> IO Pixmap) -> IO (Ptr Pixmap) -> IO Pixmap
forall a b. (a -> b) -> a -> b
$ Ptr Pixmap -> IO (Ptr Pixmap)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Pixmap
pPtr
(Word32
subwindow_ :: Word32)
{-# LINE 288 "Graphics/UI/Gtk/General/Structs.hsc" #-}
<- (\Ptr GCValues
hsc_ptr -> Ptr GCValues -> Int -> IO Word32
forall b. Ptr b -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr GCValues
hsc_ptr Int
64) Ptr GCValues
ptr
{-# LINE 289 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(tsXOrigin_ :: Int32)
{-# LINE 290 "Graphics/UI/Gtk/General/Structs.hsc" #-}
<- (\hsc_ptr -> peekByteOff hsc_ptr 68) ptr
{-# LINE 291 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(tsYOrigin_ :: Int32)
{-# LINE 292 "Graphics/UI/Gtk/General/Structs.hsc" #-}
<- (\hsc_ptr -> peekByteOff hsc_ptr 72) ptr
{-# LINE 293 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(clipXOrigin_:: Int32)
{-# LINE 294 "Graphics/UI/Gtk/General/Structs.hsc" #-}
<- (\hsc_ptr -> peekByteOff hsc_ptr 76) ptr
{-# LINE 295 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(clipYOrigin_:: Int32)
{-# LINE 296 "Graphics/UI/Gtk/General/Structs.hsc" #-}
<- (\hsc_ptr -> peekByteOff hsc_ptr 80) ptr
{-# LINE 297 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(graphics_ :: Int32)
{-# LINE 298 "Graphics/UI/Gtk/General/Structs.hsc" #-}
<- (\hsc_ptr -> peekByteOff hsc_ptr 84) ptr
{-# LINE 299 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(lineWidth_ :: Int32)
{-# LINE 300 "Graphics/UI/Gtk/General/Structs.hsc" #-}
<- (\hsc_ptr -> peekByteOff hsc_ptr 88) ptr
{-# LINE 301 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(lineStyle_ :: Word32)
{-# LINE 302 "Graphics/UI/Gtk/General/Structs.hsc" #-}
<- (\hsc_ptr -> peekByteOff hsc_ptr 92) ptr
{-# LINE 303 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(capStyle_ :: Word32)
{-# LINE 304 "Graphics/UI/Gtk/General/Structs.hsc" #-}
<- (\hsc_ptr -> peekByteOff hsc_ptr 96) ptr
{-# LINE 305 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(joinStyle_ :: Word32)
{-# LINE 306 "Graphics/UI/Gtk/General/Structs.hsc" #-}
<- (\hsc_ptr -> peekByteOff hsc_ptr 100) ptr
{-# LINE 307 "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_
}
poke :: Ptr GCValues -> GCValues -> IO ()
poke = [Char] -> Ptr GCValues -> GCValues -> IO ()
forall a. HasCallStack => [Char] -> a
error [Char]
"GCValues poke undefined (not sure why)"
pokeGCValues :: Ptr GCValues -> GCValues -> IO CInt
pokeGCValues :: Ptr GCValues -> GCValues -> IO CInt
pokeGCValues Ptr GCValues
ptr (GCValues {
foreground :: GCValues -> Color
foreground = Color
foreground_,
background :: GCValues -> Color
background = Color
background_,
function :: GCValues -> Function
function = Function
function_,
fill :: GCValues -> Fill
fill = Fill
fill_,
tile :: GCValues -> Maybe Pixmap
tile = Maybe Pixmap
tile_,
stipple :: GCValues -> Maybe Pixmap
stipple = Maybe Pixmap
stipple_,
clipMask :: GCValues -> Maybe Pixmap
clipMask = Maybe Pixmap
clipMask_,
subwindowMode :: GCValues -> SubwindowMode
subwindowMode = SubwindowMode
subwindow_,
tsXOrigin :: GCValues -> Int
tsXOrigin = Int
tsXOrigin_,
tsYOrigin :: GCValues -> Int
tsYOrigin = Int
tsYOrigin_,
clipXOrigin :: GCValues -> Int
clipXOrigin= Int
clipXOrigin_,
clipYOrigin :: GCValues -> Int
clipYOrigin= Int
clipYOrigin_,
graphicsExposure :: GCValues -> Bool
graphicsExposure = Bool
graphics_,
lineWidth :: GCValues -> Int
lineWidth = Int
lineWidth_,
lineStyle :: GCValues -> LineStyle
lineStyle = LineStyle
lineStyle_,
capStyle :: GCValues -> CapStyle
capStyle = CapStyle
capStyle_,
joinStyle :: GCValues -> JoinStyle
joinStyle = JoinStyle
joinStyle_
}) = do
IORef CInt
r <- CInt -> IO (IORef CInt)
forall a. a -> IO (IORef a)
newIORef CInt
0
IORef CInt -> CInt -> IO () -> IO ()
add IORef CInt
r CInt
1 (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
{-# LINE 350 "Graphics/UI/Gtk/General/Structs.hsc" #-}
poke ((\hsc_ptr -> hsc_ptr `plusPtr` 0) ptr) foreground_
{-# LINE 351 "Graphics/UI/Gtk/General/Structs.hsc" #-}
add r 2 $
{-# LINE 352 "Graphics/UI/Gtk/General/Structs.hsc" #-}
poke ((\hsc_ptr -> hsc_ptr `plusPtr` 12) ptr) background_
{-# LINE 353 "Graphics/UI/Gtk/General/Structs.hsc" #-}
add r 8 $
{-# LINE 354 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 32) ptr
{-# LINE 355 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(fromIntegral (fromEnum function_):: Word32)
{-# LINE 356 "Graphics/UI/Gtk/General/Structs.hsc" #-}
add r 16 $
{-# LINE 357 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 36) ptr
{-# LINE 358 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(fromIntegral (fromEnum fill_):: Word32)
{-# LINE 359 "Graphics/UI/Gtk/General/Structs.hsc" #-}
case tile_ of
Nothing -> return ()
Just tile_ -> add r 32 $
{-# LINE 362 "Graphics/UI/Gtk/General/Structs.hsc" #-}
withForeignPtr (unPixmap tile_) $
(\hsc_ptr -> pokeByteOff hsc_ptr 40) ptr
{-# LINE 364 "Graphics/UI/Gtk/General/Structs.hsc" #-}
case stipple_ of
Nothing -> return ()
Just stipple_ -> add r 64 $
{-# LINE 367 "Graphics/UI/Gtk/General/Structs.hsc" #-}
withForeignPtr (unPixmap stipple_) $
(\hsc_ptr -> pokeByteOff hsc_ptr 48) ptr
{-# LINE 369 "Graphics/UI/Gtk/General/Structs.hsc" #-}
case clipMask_ of
Nothing -> return ()
Just clipMask_ -> add r 128 $
{-# LINE 372 "Graphics/UI/Gtk/General/Structs.hsc" #-}
withForeignPtr (unPixmap clipMask_) $
(\hsc_ptr -> pokeByteOff hsc_ptr 56) ptr
{-# LINE 374 "Graphics/UI/Gtk/General/Structs.hsc" #-}
add r 256 $
{-# LINE 375 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 64) ptr
{-# LINE 376 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(fromIntegral (fromEnum subwindow_):: Word32)
{-# LINE 377 "Graphics/UI/Gtk/General/Structs.hsc" #-}
add r 512 $
{-# LINE 378 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 68) ptr
{-# LINE 379 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(fromIntegral tsXOrigin_:: Int32)
{-# LINE 380 "Graphics/UI/Gtk/General/Structs.hsc" #-}
add r 1024 $
{-# LINE 381 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 72) ptr
{-# LINE 382 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(fromIntegral tsYOrigin_:: Int32)
{-# LINE 383 "Graphics/UI/Gtk/General/Structs.hsc" #-}
add r 2048 $
{-# LINE 384 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 76) ptr
{-# LINE 385 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(fromIntegral clipXOrigin_:: Int32)
{-# LINE 386 "Graphics/UI/Gtk/General/Structs.hsc" #-}
add r 4096 $
{-# LINE 387 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 80) ptr
{-# LINE 388 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(fromIntegral clipYOrigin_:: Int32)
{-# LINE 389 "Graphics/UI/Gtk/General/Structs.hsc" #-}
add r 8192 $
{-# LINE 390 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 84) ptr
{-# LINE 391 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(fromBool graphics_:: Int32)
{-# LINE 392 "Graphics/UI/Gtk/General/Structs.hsc" #-}
add r 16384 $
{-# LINE 393 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 88) ptr
{-# LINE 394 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(fromIntegral lineWidth_:: Int32)
{-# LINE 395 "Graphics/UI/Gtk/General/Structs.hsc" #-}
add r 32768 $
{-# LINE 396 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 92) ptr
{-# LINE 397 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(fromIntegral (fromEnum lineStyle_):: Word32)
{-# LINE 398 "Graphics/UI/Gtk/General/Structs.hsc" #-}
add r 65536 $
{-# LINE 399 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 96) ptr
{-# LINE 400 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(fromIntegral (fromEnum capStyle_):: Word32)
{-# LINE 401 "Graphics/UI/Gtk/General/Structs.hsc" #-}
add r 131072 $
{-# LINE 402 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 100) ptr
{-# LINE 403 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(fromIntegral (fromEnum joinStyle_):: Word32)
{-# LINE 404 "Graphics/UI/Gtk/General/Structs.hsc" #-}
readIORef r
where
add :: IORef CInt -> CInt -> IO () -> IO ()
add :: IORef CInt -> CInt -> IO () -> IO ()
add IORef CInt
r CInt
mVal IO ()
act = (ErrorCall -> IO ()) -> IO () -> IO ()
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle (\(ErrorCall [Char]
_) -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
IO ()
act
IORef CInt -> (CInt -> CInt) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef IORef CInt
r (\CInt
val -> CInt
valCInt -> CInt -> CInt
forall a. Num a => a -> a -> a
+CInt
mVal)
newGCValues :: GCValues
newGCValues :: GCValues
newGCValues = GCValues {
foreground :: Color
foreground = Color
forall a. HasCallStack => a
undefined,
background :: Color
background = Color
forall a. HasCallStack => a
undefined,
function :: Function
function = Function
forall a. HasCallStack => a
undefined,
fill :: Fill
fill = Fill
forall a. HasCallStack => a
undefined,
tile :: Maybe Pixmap
tile = Maybe Pixmap
forall a. Maybe a
Nothing,
stipple :: Maybe Pixmap
stipple = Maybe Pixmap
forall a. Maybe a
Nothing,
clipMask :: Maybe Pixmap
clipMask = Maybe Pixmap
forall a. Maybe a
Nothing,
subwindowMode :: SubwindowMode
subwindowMode = SubwindowMode
forall a. HasCallStack => a
undefined,
tsXOrigin :: Int
tsXOrigin = Int
forall a. HasCallStack => a
undefined,
tsYOrigin :: Int
tsYOrigin = Int
forall a. HasCallStack => a
undefined,
clipXOrigin :: Int
clipXOrigin= Int
forall a. HasCallStack => a
undefined,
clipYOrigin :: Int
clipYOrigin= Int
forall a. HasCallStack => a
undefined,
graphicsExposure :: Bool
graphicsExposure = Bool
forall a. HasCallStack => a
undefined,
lineWidth :: Int
lineWidth = Int
forall a. HasCallStack => a
undefined,
lineStyle :: LineStyle
lineStyle = LineStyle
forall a. HasCallStack => a
undefined,
capStyle :: CapStyle
capStyle = CapStyle
forall a. HasCallStack => a
undefined,
joinStyle :: JoinStyle
joinStyle = JoinStyle
forall a. HasCallStack => a
undefined
}
{-# LINE 438 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 441 "Graphics/UI/Gtk/General/Structs.hsc" #-}
widgetGetState :: WidgetClass w => w -> IO StateType
widgetGetState :: forall w. WidgetClass w => w -> IO StateType
widgetGetState w
w =
(Word8 -> StateType) -> IO Word8 -> IO StateType
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (\Word8
x -> Int -> StateType
forall a. Enum a => Int -> a
toEnum (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8
x :: Word8))) (IO Word8 -> IO StateType) -> IO Word8 -> IO StateType
forall a b. (a -> b) -> a -> b
$
{-# LINE 450 "Graphics/UI/Gtk/General/Structs.hsc" #-}
withForeignPtr ((unWidget . toWidget) w) $ (\hsc_ptr -> peekByteOff hsc_ptr 34)
{-# LINE 451 "Graphics/UI/Gtk/General/Structs.hsc" #-}
widgetGetSavedState :: WidgetClass w => w -> IO StateType
widgetGetSavedState :: forall w. WidgetClass w => w -> IO StateType
widgetGetSavedState w
w =
(Word8 -> StateType) -> IO Word8 -> IO StateType
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (\Word8
x -> Int -> StateType
forall a. Enum a => Int -> a
toEnum (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8
x :: Word8))) (IO Word8 -> IO StateType) -> IO Word8 -> IO StateType
forall a b. (a -> b) -> a -> b
$
{-# LINE 461 "Graphics/UI/Gtk/General/Structs.hsc" #-}
withForeignPtr ((unWidget . toWidget) w) $ (\hsc_ptr -> peekByteOff hsc_ptr 35)
{-# LINE 462 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 463 "Graphics/UI/Gtk/General/Structs.hsc" #-}
type Allocation = Rectangle
data Requisition = Requisition Int Int deriving (Requisition -> Requisition -> Bool
(Requisition -> Requisition -> Bool)
-> (Requisition -> Requisition -> Bool) -> Eq Requisition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Requisition -> Requisition -> Bool
== :: Requisition -> Requisition -> Bool
$c/= :: Requisition -> Requisition -> Bool
/= :: Requisition -> Requisition -> Bool
Eq,Int -> Requisition -> ShowS
[Requisition] -> ShowS
Requisition -> [Char]
(Int -> Requisition -> ShowS)
-> (Requisition -> [Char])
-> ([Requisition] -> ShowS)
-> Show Requisition
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Requisition -> ShowS
showsPrec :: Int -> Requisition -> ShowS
$cshow :: Requisition -> [Char]
show :: Requisition -> [Char]
$cshowList :: [Requisition] -> ShowS
showList :: [Requisition] -> ShowS
Show)
instance Storable Requisition where
sizeOf :: Requisition -> Int
sizeOf Requisition
_ = Int
8
{-# LINE 482 "Graphics/UI/Gtk/General/Structs.hsc" #-}
alignment _ = alignment (undefined::Int32)
{-# LINE 483 "Graphics/UI/Gtk/General/Structs.hsc" #-}
peek ptr = do
(width_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 485 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(height_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 486 "Graphics/UI/Gtk/General/Structs.hsc" #-}
return $ Requisition (fromIntegral width_) (fromIntegral height_)
poke :: Ptr Requisition -> Requisition -> IO ()
poke Ptr Requisition
ptr (Requisition Int
width Int
height) = do
(\Ptr Requisition
hsc_ptr -> Ptr Requisition -> Int -> Int32 -> IO ()
forall b. Ptr b -> Int -> Int32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Requisition
hsc_ptr Int
0) Ptr Requisition
ptr ((Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
width)::Int32)
{-# LINE 489 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr ((fromIntegral height)::Int32)
{-# LINE 490 "Graphics/UI/Gtk/General/Structs.hsc" #-}
inputError :: Int32
{-# LINE 497 "Graphics/UI/Gtk/General/Structs.hsc" #-}
inputError = -1
{-# LINE 498 "Graphics/UI/Gtk/General/Structs.hsc" #-}
treeIterSize :: Int
treeIterSize :: Int
treeIterSize = Int
32
{-# LINE 504 "Graphics/UI/Gtk/General/Structs.hsc" #-}
textIterSize :: Int
textIterSize :: Int
textIterSize = Int
80
{-# LINE 511 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 514 "Graphics/UI/Gtk/General/Structs.hsc" #-}
dialogGetUpper :: DialogClass dc => dc -> IO VBox
dialogGetUpper :: forall dc. DialogClass dc => dc -> IO VBox
dialogGetUpper dc
dc = (ForeignPtr VBox -> VBox, FinalizerPtr VBox)
-> IO (Ptr VBox) -> IO VBox
forall obj.
ObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewObject (ForeignPtr VBox -> VBox, FinalizerPtr VBox)
forall {a}. (ForeignPtr VBox -> VBox, FinalizerPtr a)
mkVBox (IO (Ptr VBox) -> IO VBox) -> IO (Ptr VBox) -> IO VBox
forall a b. (a -> b) -> a -> b
$ (Ptr Any -> Ptr VBox) -> IO (Ptr Any) -> IO (Ptr VBox)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Ptr Any -> Ptr VBox
forall a b. Ptr a -> Ptr b
castPtr (IO (Ptr Any) -> IO (Ptr VBox)) -> IO (Ptr Any) -> IO (Ptr VBox)
forall a b. (a -> b) -> a -> b
$
ForeignPtr Dialog -> (Ptr Dialog -> IO (Ptr Any)) -> IO (Ptr Any)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ((Dialog -> ForeignPtr Dialog
unDialog(Dialog -> ForeignPtr Dialog)
-> (dc -> Dialog) -> dc -> ForeignPtr Dialog
forall b c a. (b -> c) -> (a -> b) -> a -> c
.dc -> Dialog
forall o. DialogClass o => o -> Dialog
toDialog) dc
dc) (\Ptr Dialog
hsc_ptr -> Ptr Dialog -> Int -> IO (Ptr Any)
forall b. Ptr b -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Dialog
hsc_ptr Int
240)
{-# LINE 522 "Graphics/UI/Gtk/General/Structs.hsc" #-}
dialogGetActionArea :: DialogClass dc => dc -> IO HBox
dialogGetActionArea :: forall dc. DialogClass dc => dc -> IO HBox
dialogGetActionArea dc
dc = (ForeignPtr HBox -> HBox, FinalizerPtr HBox)
-> IO (Ptr HBox) -> IO HBox
forall obj.
ObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewObject (ForeignPtr HBox -> HBox, FinalizerPtr HBox)
forall {a}. (ForeignPtr HBox -> HBox, FinalizerPtr a)
mkHBox (IO (Ptr HBox) -> IO HBox) -> IO (Ptr HBox) -> IO HBox
forall a b. (a -> b) -> a -> b
$ (Ptr Any -> Ptr HBox) -> IO (Ptr Any) -> IO (Ptr HBox)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Ptr Any -> Ptr HBox
forall a b. Ptr a -> Ptr b
castPtr (IO (Ptr Any) -> IO (Ptr HBox)) -> IO (Ptr Any) -> IO (Ptr HBox)
forall a b. (a -> b) -> a -> b
$
ForeignPtr Dialog -> (Ptr Dialog -> IO (Ptr Any)) -> IO (Ptr Any)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ((Dialog -> ForeignPtr Dialog
unDialog(Dialog -> ForeignPtr Dialog)
-> (dc -> Dialog) -> dc -> ForeignPtr Dialog
forall b c a. (b -> c) -> (a -> b) -> a -> c
.dc -> Dialog
forall o. DialogClass o => o -> Dialog
toDialog) dc
dc) (\Ptr Dialog
hsc_ptr -> Ptr Dialog -> Int -> IO (Ptr Any)
forall b. Ptr b -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Dialog
hsc_ptr Int
248)
{-# LINE 532 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 533 "Graphics/UI/Gtk/General/Structs.hsc" #-}
data ResponseId
= ResponseNone
| ResponseReject
| ResponseAccept
| ResponseDeleteEvent
| ResponseOk
| ResponseCancel
| ResponseClose
| ResponseYes
| ResponseNo
| ResponseApply
| ResponseHelp
| ResponseUser Int
deriving (Int -> ResponseId -> ShowS
[ResponseId] -> ShowS
ResponseId -> [Char]
(Int -> ResponseId -> ShowS)
-> (ResponseId -> [Char])
-> ([ResponseId] -> ShowS)
-> Show ResponseId
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseId -> ShowS
showsPrec :: Int -> ResponseId -> ShowS
$cshow :: ResponseId -> [Char]
show :: ResponseId -> [Char]
$cshowList :: [ResponseId] -> ShowS
showList :: [ResponseId] -> ShowS
Show, ResponseId -> ResponseId -> Bool
(ResponseId -> ResponseId -> Bool)
-> (ResponseId -> ResponseId -> Bool) -> Eq ResponseId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseId -> ResponseId -> Bool
== :: ResponseId -> ResponseId -> Bool
$c/= :: ResponseId -> ResponseId -> Bool
/= :: ResponseId -> ResponseId -> Bool
Eq)
fromResponse :: Integral a => ResponseId -> a
fromResponse :: forall a. Integral a => ResponseId -> a
fromResponse ResponseId
ResponseNone = -a
1
fromResponse ResponseId
ResponseReject = -a
2
fromResponse ResponseId
ResponseAccept = -a
3
fromResponse ResponseId
ResponseDeleteEvent = -a
4
fromResponse ResponseId
ResponseOk = -a
5
fromResponse ResponseId
ResponseCancel = -a
6
fromResponse ResponseId
ResponseClose = -a
7
fromResponse ResponseId
ResponseYes = -a
8
fromResponse ResponseId
ResponseNo = -a
9
fromResponse ResponseId
ResponseApply = -a
10
fromResponse ResponseId
ResponseHelp = -a
11
fromResponse (ResponseUser Int
i) = Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i
toResponse :: Integral a => a -> ResponseId
toResponse :: forall a. Integral a => a -> ResponseId
toResponse (-1) = ResponseId
ResponseNone
toResponse (-2) = ResponseId
ResponseReject
toResponse (-3) = ResponseId
ResponseAccept
toResponse (-4) = ResponseId
ResponseDeleteEvent
toResponse (-5) = ResponseId
ResponseOk
toResponse (-6) = ResponseId
ResponseCancel
toResponse (-7) = ResponseId
ResponseClose
toResponse (-8) = ResponseId
ResponseYes
toResponse (-9) = ResponseId
ResponseNo
toResponse (-10) = ResponseId
ResponseApply
toResponse (-11) = ResponseId
ResponseHelp
toResponse a
i = Int -> ResponseId
ResponseUser (Int -> ResponseId) -> Int -> ResponseId
forall a b. (a -> b) -> a -> b
$ a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i
{-# LINE 621 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 645 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 646 "Graphics/UI/Gtk/General/Structs.hsc" #-}
newtype NativeWindowId = NativeWindowId Word32 deriving (Eq, Show)
{-# LINE 647 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 650 "Graphics/UI/Gtk/General/Structs.hsc" #-}
unNativeWindowId :: Integral a => NativeWindowId -> a
unNativeWindowId :: forall a. Integral a => NativeWindowId -> a
unNativeWindowId (NativeWindowId Word32
id) = Word32 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
id
toNativeWindowId :: Integral a => a -> NativeWindowId
toNativeWindowId :: forall a. Integral a => a -> NativeWindowId
toNativeWindowId = Word32 -> NativeWindowId
NativeWindowId (Word32 -> NativeWindowId) -> (a -> Word32) -> a -> NativeWindowId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral
fromNativeWindowId :: Integral a => NativeWindowId -> a
fromNativeWindowId :: forall a. Integral a => NativeWindowId -> a
fromNativeWindowId = Integer -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> a)
-> (NativeWindowId -> Integer) -> NativeWindowId -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NativeWindowId -> Integer
forall a. Integral a => NativeWindowId -> a
unNativeWindowId
nativeWindowIdNone :: NativeWindowId
nativeWindowIdNone :: NativeWindowId
nativeWindowIdNone = Word32 -> NativeWindowId
NativeWindowId Word32
0
{-# LINE 659 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 660 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 662 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 666 "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 669 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 675 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 678 "Graphics/UI/Gtk/General/Structs.hsc" #-}
drawableGetID :: DrawableClass d => d -> IO NativeWindowId
{-# LINE 682 "Graphics/UI/Gtk/General/Structs.hsc" #-}
drawableGetID :: forall d. DrawableClass d => d -> IO NativeWindowId
drawableGetID d
d =
(CInt -> NativeWindowId) -> IO CInt -> IO NativeWindowId
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM CInt -> NativeWindowId
forall a. Integral a => a -> NativeWindowId
toNativeWindowId (IO CInt -> IO NativeWindowId) -> IO CInt -> IO NativeWindowId
forall a b. (a -> b) -> a -> b
$
{-# LINE 685 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\(Drawable drawable) ->
{-# LINE 689 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 698 "Graphics/UI/Gtk/General/Structs.hsc" #-}
withForeignPtr drawable gdk_x11_drawable_get_xid
{-# LINE 702 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 703 "Graphics/UI/Gtk/General/Structs.hsc" #-}
) (toDrawable d)
{-# LINE 707 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 710 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 711 "Graphics/UI/Gtk/General/Structs.hsc" #-}
toolbarChildButton, toolbarChildToggleButton, toolbarChildRadioButton ::
CInt
toolbarChildButton :: CInt
toolbarChildButton = CInt
1
{-# LINE 719 "Graphics/UI/Gtk/General/Structs.hsc" #-}
toolbarChildToggleButton = 2
{-# LINE 720 "Graphics/UI/Gtk/General/Structs.hsc" #-}
toolbarChildRadioButton = 3
{-# LINE 721 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 722 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 723 "Graphics/UI/Gtk/General/Structs.hsc" #-}
data IconSize
= IconSizeInvalid
|
| IconSizeSmallToolbar
| IconSizeLargeToolbar
| IconSizeButton
| IconSizeDnd
| IconSizeDialog
| IconSizeUser Int
deriving (IconSize -> IconSize -> Bool
(IconSize -> IconSize -> Bool)
-> (IconSize -> IconSize -> Bool) -> Eq IconSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IconSize -> IconSize -> Bool
== :: IconSize -> IconSize -> Bool
$c/= :: IconSize -> IconSize -> Bool
/= :: IconSize -> IconSize -> Bool
Eq)
instance Enum IconSize where
toEnum :: Int -> IconSize
toEnum Int
0 = IconSize
IconSizeInvalid
{-# LINE 760 "Graphics/UI/Gtk/General/Structs.hsc" #-}
toEnum 1 = IconSizeMenu
{-# LINE 761 "Graphics/UI/Gtk/General/Structs.hsc" #-}
toEnum 2 = IconSizeSmallToolbar
{-# LINE 762 "Graphics/UI/Gtk/General/Structs.hsc" #-}
toEnum 3 = IconSizeLargeToolbar
{-# LINE 763 "Graphics/UI/Gtk/General/Structs.hsc" #-}
toEnum 4 = IconSizeButton
{-# LINE 764 "Graphics/UI/Gtk/General/Structs.hsc" #-}
toEnum 5 = IconSizeDnd
{-# LINE 765 "Graphics/UI/Gtk/General/Structs.hsc" #-}
toEnum 6 = IconSizeDialog
{-# LINE 766 "Graphics/UI/Gtk/General/Structs.hsc" #-}
toEnum n = IconSizeUser n
fromEnum :: IconSize -> Int
fromEnum IconSize
IconSizeInvalid = Int
0
{-# LINE 768 "Graphics/UI/Gtk/General/Structs.hsc" #-}
fromEnum IconSizeMenu = 1
{-# LINE 769 "Graphics/UI/Gtk/General/Structs.hsc" #-}
fromEnum IconSizeSmallToolbar = 2
{-# LINE 770 "Graphics/UI/Gtk/General/Structs.hsc" #-}
fromEnum IconSizeLargeToolbar = 3
{-# LINE 771 "Graphics/UI/Gtk/General/Structs.hsc" #-}
fromEnum IconSizeButton = 4
{-# LINE 772 "Graphics/UI/Gtk/General/Structs.hsc" #-}
fromEnum IconSizeDnd = 5
{-# LINE 773 "Graphics/UI/Gtk/General/Structs.hsc" #-}
fromEnum IconSizeDialog = 6
{-# LINE 774 "Graphics/UI/Gtk/General/Structs.hsc" #-}
fromEnum (IconSizeUser n) = n
{-# LINE 778 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 779 "Graphics/UI/Gtk/General/Structs.hsc" #-}
comboGetList :: Combo -> IO List
comboGetList :: Combo -> IO List
comboGetList Combo
c = ForeignPtr Combo -> (Ptr Combo -> IO List) -> IO List
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (Combo -> ForeignPtr Combo
unCombo Combo
c) ((Ptr Combo -> IO List) -> IO List)
-> (Ptr Combo -> IO List) -> IO List
forall a b. (a -> b) -> a -> b
$ \Ptr Combo
cPtr ->
(ForeignPtr List -> List, FinalizerPtr List)
-> IO (Ptr List) -> IO List
forall obj.
ObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewObject (ForeignPtr List -> List, FinalizerPtr List)
forall {a}. (ForeignPtr List -> List, FinalizerPtr a)
mkList (IO (Ptr List) -> IO List) -> IO (Ptr List) -> IO List
forall a b. (a -> b) -> a -> b
$ (\Ptr Combo
hsc_ptr -> Ptr Combo -> Int -> IO (Ptr List)
forall b. Ptr b -> Int -> IO (Ptr List)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Combo
hsc_ptr Int
160) Ptr Combo
cPtr
{-# LINE 785 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 786 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 787 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 790 "Graphics/UI/Gtk/General/Structs.hsc" #-}
fileSelectionGetButtons :: FileSelectionClass fsel => fsel ->
IO (Button, Button)
fileSelectionGetButtons :: forall fsel. FileSelectionClass fsel => fsel -> IO (Button, Button)
fileSelectionGetButtons fsel
fsel =
do
Button
ok <- (Ptr FileSelection -> IO (Ptr Any)) -> IO Button
forall {a}. (Ptr FileSelection -> IO (Ptr a)) -> IO Button
butPtrToButton (\Ptr FileSelection
hsc_ptr -> Ptr FileSelection -> Int -> IO (Ptr Any)
forall b. Ptr b -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr FileSelection
hsc_ptr Int
304)
{-# LINE 797 "Graphics/UI/Gtk/General/Structs.hsc" #-}
cancel <- butPtrToButton (\hsc_ptr -> peekByteOff hsc_ptr 312)
{-# LINE 798 "Graphics/UI/Gtk/General/Structs.hsc" #-}
return (ok,cancel)
where
butPtrToButton :: (Ptr FileSelection -> IO (Ptr a)) -> IO Button
butPtrToButton Ptr FileSelection -> IO (Ptr a)
bp = (ForeignPtr Button -> Button, FinalizerPtr Button)
-> IO (Ptr Button) -> IO Button
forall obj.
ObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewObject (ForeignPtr Button -> Button, FinalizerPtr Button)
forall {a}. (ForeignPtr Button -> Button, FinalizerPtr a)
mkButton (IO (Ptr Button) -> IO Button) -> IO (Ptr Button) -> IO Button
forall a b. (a -> b) -> a -> b
$ (Ptr a -> Ptr Button) -> IO (Ptr a) -> IO (Ptr Button)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Ptr a -> Ptr Button
forall a b. Ptr a -> Ptr b
castPtr (IO (Ptr a) -> IO (Ptr Button)) -> IO (Ptr a) -> IO (Ptr Button)
forall a b. (a -> b) -> a -> b
$
ForeignPtr FileSelection
-> (Ptr FileSelection -> IO (Ptr a)) -> IO (Ptr a)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ((FileSelection -> ForeignPtr FileSelection
unFileSelection (FileSelection -> ForeignPtr FileSelection)
-> (fsel -> FileSelection) -> fsel -> ForeignPtr FileSelection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. fsel -> FileSelection
forall o. FileSelectionClass o => o -> FileSelection
toFileSelection) fsel
fsel) Ptr FileSelection -> IO (Ptr a)
bp
{-# LINE 803 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 805 "Graphics/UI/Gtk/General/Structs.hsc" #-}
widgetGetDrawWindow :: WidgetClass widget => widget -> IO DrawWindow
widgetGetDrawWindow :: forall widget. WidgetClass widget => widget -> IO DrawWindow
widgetGetDrawWindow widget
da =
ForeignPtr Widget -> (Ptr Widget -> IO DrawWindow) -> IO DrawWindow
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (Widget -> ForeignPtr Widget
unWidget(Widget -> ForeignPtr Widget)
-> (widget -> Widget) -> widget -> ForeignPtr Widget
forall b c a. (b -> c) -> (a -> b) -> a -> c
.widget -> Widget
forall o. WidgetClass o => o -> Widget
toWidget (widget -> ForeignPtr Widget) -> widget -> ForeignPtr Widget
forall a b. (a -> b) -> a -> b
$ widget
da) ((Ptr Widget -> IO DrawWindow) -> IO DrawWindow)
-> (Ptr Widget -> IO DrawWindow) -> IO DrawWindow
forall a b. (a -> b) -> a -> b
$ \Ptr Widget
da' -> do
Ptr Any
drawWindowPtr <- (\Ptr Widget
hsc_ptr -> Ptr Widget -> Int -> IO (Ptr Any)
forall b. Ptr b -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Widget
hsc_ptr Int
80) Ptr Widget
da'
{-# LINE 821 "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)
widgetGetSize :: WidgetClass widget => widget -> IO (Int, Int)
widgetGetSize :: forall widget. WidgetClass widget => widget -> IO Point
widgetGetSize widget
da = ForeignPtr Widget -> (Ptr Widget -> IO Point) -> IO Point
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (Widget -> ForeignPtr Widget
unWidget(Widget -> ForeignPtr Widget)
-> (widget -> Widget) -> widget -> ForeignPtr Widget
forall b c a. (b -> c) -> (a -> b) -> a -> c
.widget -> Widget
forall o. WidgetClass o => o -> Widget
toWidget (widget -> ForeignPtr Widget) -> widget -> ForeignPtr Widget
forall a b. (a -> b) -> a -> b
$ widget
da) ((Ptr Widget -> IO Point) -> IO Point)
-> (Ptr Widget -> IO Point) -> IO Point
forall a b. (a -> b) -> a -> b
$ \Ptr Widget
wPtr -> do
(Int32
width :: Int32) <- (\Ptr Any
hsc_ptr -> Ptr Any -> Int -> IO Int32
forall b. Ptr b -> Int -> IO Int32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Any
hsc_ptr Int
8)
{-# LINE 833 "Graphics/UI/Gtk/General/Structs.hsc" #-}
((\Ptr Widget
hsc_ptr -> Ptr Widget
hsc_ptr Ptr Widget -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) Ptr Widget
wPtr)
{-# LINE 834 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(height :: Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 12)
{-# LINE 835 "Graphics/UI/Gtk/General/Structs.hsc" #-}
((\hsc_ptr -> hsc_ptr `plusPtr` 64) wPtr)
{-# LINE 836 "Graphics/UI/Gtk/General/Structs.hsc" #-}
return (fromIntegral width, fromIntegral height)
windowGetFrame :: WindowClass widget => widget -> IO (Maybe DrawWindow)
windowGetFrame :: forall widget.
WindowClass widget =>
widget -> IO (Maybe DrawWindow)
windowGetFrame widget
da =
ForeignPtr Widget
-> (Ptr Widget -> IO (Maybe DrawWindow)) -> IO (Maybe DrawWindow)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (Widget -> ForeignPtr Widget
unWidget(Widget -> ForeignPtr Widget)
-> (widget -> Widget) -> widget -> ForeignPtr Widget
forall b c a. (b -> c) -> (a -> b) -> a -> c
.widget -> Widget
forall o. WidgetClass o => o -> Widget
toWidget (widget -> ForeignPtr Widget) -> widget -> ForeignPtr Widget
forall a b. (a -> b) -> a -> b
$ widget
da) ((Ptr Widget -> IO (Maybe DrawWindow)) -> IO (Maybe DrawWindow))
-> (Ptr Widget -> IO (Maybe DrawWindow)) -> IO (Maybe DrawWindow)
forall a b. (a -> b) -> a -> b
$ \Ptr Widget
da' -> do
Ptr Any
drawWindowPtr <- (\Ptr Widget
hsc_ptr -> Ptr Widget -> Int -> IO (Ptr Any)
forall b. Ptr b -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Widget
hsc_ptr Int
184) Ptr Widget
da'
{-# LINE 847 "Graphics/UI/Gtk/General/Structs.hsc" #-}
if drawWindowPtr == nullPtr
then return Nothing
else liftM Just $ makeNewGObject mkDrawWindow (return $ castPtr drawWindowPtr)
{-# LINE 851 "Graphics/UI/Gtk/General/Structs.hsc" #-}
styleGetForeground :: Style -> StateType -> IO Color
styleGetForeground :: Style -> StateType -> IO Color
styleGetForeground Style
st StateType
ty =
ForeignPtr Style -> (Ptr Style -> IO Color) -> IO Color
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (Style -> ForeignPtr Style
unStyle Style
st) ((Ptr Style -> IO Color) -> IO Color)
-> (Ptr Style -> IO Color) -> IO Color
forall a b. (a -> b) -> a -> b
$ \Ptr Style
stPtr -> do
Ptr Color -> Int -> IO Color
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff ((\Ptr Style
hsc_ptr -> Ptr Style
hsc_ptr Ptr Style -> Int -> Ptr Color
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) Ptr Style
stPtr) (StateType -> Int
forall a. Enum a => a -> Int
fromEnum StateType
ty)
{-# LINE 864 "Graphics/UI/Gtk/General/Structs.hsc" #-}
styleGetBackground :: Style -> StateType -> IO Color
styleGetBackground :: Style -> StateType -> IO Color
styleGetBackground Style
st StateType
ty =
ForeignPtr Style -> (Ptr Style -> IO Color) -> IO Color
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (Style -> ForeignPtr Style
unStyle Style
st) ((Ptr Style -> IO Color) -> IO Color)
-> (Ptr Style -> IO Color) -> IO Color
forall a b. (a -> b) -> a -> b
$ \Ptr Style
stPtr ->
Ptr Color -> Int -> IO Color
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff ((\Ptr Style
hsc_ptr -> Ptr Style
hsc_ptr Ptr Style -> Int -> Ptr Color
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84) Ptr Style
stPtr) (StateType -> Int
forall a. Enum a => a -> Int
fromEnum StateType
ty)
{-# LINE 876 "Graphics/UI/Gtk/General/Structs.hsc" #-}
styleGetLight :: Style -> StateType -> IO Color
styleGetLight :: Style -> StateType -> IO Color
styleGetLight Style
st StateType
ty =
ForeignPtr Style -> (Ptr Style -> IO Color) -> IO Color
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (Style -> ForeignPtr Style
unStyle Style
st) ((Ptr Style -> IO Color) -> IO Color)
-> (Ptr Style -> IO Color) -> IO Color
forall a b. (a -> b) -> a -> b
$ \Ptr Style
stPtr ->
Ptr Color -> Int -> IO Color
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff ((\Ptr Style
hsc_ptr -> Ptr Style
hsc_ptr Ptr Style -> Int -> Ptr Color
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
144) Ptr Style
stPtr) (StateType -> Int
forall a. Enum a => a -> Int
fromEnum StateType
ty)
{-# LINE 888 "Graphics/UI/Gtk/General/Structs.hsc" #-}
styleGetMiddle :: Style -> StateType -> IO Color
styleGetMiddle :: Style -> StateType -> IO Color
styleGetMiddle Style
st StateType
ty =
ForeignPtr Style -> (Ptr Style -> IO Color) -> IO Color
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (Style -> ForeignPtr Style
unStyle Style
st) ((Ptr Style -> IO Color) -> IO Color)
-> (Ptr Style -> IO Color) -> IO Color
forall a b. (a -> b) -> a -> b
$ \Ptr Style
stPtr ->
Ptr Color -> Int -> IO Color
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff ((\Ptr Style
hsc_ptr -> Ptr Style
hsc_ptr Ptr Style -> Int -> Ptr Color
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
264) Ptr Style
stPtr) (StateType -> Int
forall a. Enum a => a -> Int
fromEnum StateType
ty)
{-# LINE 900 "Graphics/UI/Gtk/General/Structs.hsc" #-}
styleGetDark :: Style -> StateType -> IO Color
styleGetDark :: Style -> StateType -> IO Color
styleGetDark Style
st StateType
ty =
ForeignPtr Style -> (Ptr Style -> IO Color) -> IO Color
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (Style -> ForeignPtr Style
unStyle Style
st) ((Ptr Style -> IO Color) -> IO Color)
-> (Ptr Style -> IO Color) -> IO Color
forall a b. (a -> b) -> a -> b
$ \Ptr Style
stPtr ->
Ptr Color -> Int -> IO Color
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff ((\Ptr Style
hsc_ptr -> Ptr Style
hsc_ptr Ptr Style -> Int -> Ptr Color
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
204) Ptr Style
stPtr) (StateType -> Int
forall a. Enum a => a -> Int
fromEnum StateType
ty)
{-# LINE 912 "Graphics/UI/Gtk/General/Structs.hsc" #-}
styleGetText :: Style -> StateType -> IO Color
styleGetText :: Style -> StateType -> IO Color
styleGetText Style
st StateType
ty =
ForeignPtr Style -> (Ptr Style -> IO Color) -> IO Color
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (Style -> ForeignPtr Style
unStyle Style
st) ((Ptr Style -> IO Color) -> IO Color)
-> (Ptr Style -> IO Color) -> IO Color
forall a b. (a -> b) -> a -> b
$ \Ptr Style
stPtr ->
Ptr Color -> Int -> IO Color
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff ((\Ptr Style
hsc_ptr -> Ptr Style
hsc_ptr Ptr Style -> Int -> Ptr Color
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
324) Ptr Style
stPtr) (StateType -> Int
forall a. Enum a => a -> Int
fromEnum StateType
ty)
{-# LINE 924 "Graphics/UI/Gtk/General/Structs.hsc" #-}
styleGetBase :: Style -> StateType -> IO Color
styleGetBase :: Style -> StateType -> IO Color
styleGetBase Style
st StateType
ty =
ForeignPtr Style -> (Ptr Style -> IO Color) -> IO Color
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (Style -> ForeignPtr Style
unStyle Style
st) ((Ptr Style -> IO Color) -> IO Color)
-> (Ptr Style -> IO Color) -> IO Color
forall a b. (a -> b) -> a -> b
$ \Ptr Style
stPtr ->
Ptr Color -> Int -> IO Color
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff ((\Ptr Style
hsc_ptr -> Ptr Style
hsc_ptr Ptr Style -> Int -> Ptr Color
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
384) Ptr Style
stPtr) (StateType -> Int
forall a. Enum a => a -> Int
fromEnum StateType
ty)
{-# LINE 938 "Graphics/UI/Gtk/General/Structs.hsc" #-}
styleGetAntiAliasing :: Style -> StateType -> IO Color
styleGetAntiAliasing :: Style -> StateType -> IO Color
styleGetAntiAliasing Style
st StateType
ty =
ForeignPtr Style -> (Ptr Style -> IO Color) -> IO Color
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (Style -> ForeignPtr Style
unStyle Style
st) ((Ptr Style -> IO Color) -> IO Color)
-> (Ptr Style -> IO Color) -> IO Color
forall a b. (a -> b) -> a -> b
$ \Ptr Style
stPtr ->
Ptr Color -> Int -> IO Color
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff ((\Ptr Style
hsc_ptr -> Ptr Style
hsc_ptr Ptr Style -> Int -> Ptr Color
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
444) Ptr Style
stPtr) (StateType -> Int
forall a. Enum a => a -> Int
fromEnum StateType
ty)
{-# LINE 954 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 956 "Graphics/UI/Gtk/General/Structs.hsc" #-}
colorSelectionDialogGetColor :: ColorSelectionDialog -> IO ColorSelection
colorSelectionDialogGetColor :: ColorSelectionDialog -> IO ColorSelection
colorSelectionDialogGetColor ColorSelectionDialog
cd =
(ForeignPtr ColorSelection -> ColorSelection,
FinalizerPtr ColorSelection)
-> IO (Ptr ColorSelection) -> IO ColorSelection
forall obj.
ObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewObject (ForeignPtr ColorSelection -> ColorSelection,
FinalizerPtr ColorSelection)
forall {a}.
(ForeignPtr ColorSelection -> ColorSelection, FinalizerPtr a)
mkColorSelection (IO (Ptr ColorSelection) -> IO ColorSelection)
-> IO (Ptr ColorSelection) -> IO ColorSelection
forall a b. (a -> b) -> a -> b
$ (Ptr Any -> Ptr ColorSelection)
-> IO (Ptr Any) -> IO (Ptr ColorSelection)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Ptr Any -> Ptr ColorSelection
forall a b. Ptr a -> Ptr b
castPtr (IO (Ptr Any) -> IO (Ptr ColorSelection))
-> IO (Ptr Any) -> IO (Ptr ColorSelection)
forall a b. (a -> b) -> a -> b
$
ForeignPtr ColorSelectionDialog
-> (Ptr ColorSelectionDialog -> IO (Ptr Any)) -> IO (Ptr Any)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (ColorSelectionDialog -> ForeignPtr ColorSelectionDialog
unColorSelectionDialog ColorSelectionDialog
cd)
(\Ptr ColorSelectionDialog
hsc_ptr -> Ptr ColorSelectionDialog -> Int -> IO (Ptr Any)
forall b. Ptr b -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr ColorSelectionDialog
hsc_ptr Int
264)
{-# LINE 964 "Graphics/UI/Gtk/General/Structs.hsc" #-}
colorSelectionDialogGetOkButton :: ColorSelectionDialog -> IO Button
colorSelectionDialogGetOkButton :: ColorSelectionDialog -> IO Button
colorSelectionDialogGetOkButton ColorSelectionDialog
cd =
(ForeignPtr Button -> Button, FinalizerPtr Button)
-> IO (Ptr Button) -> IO Button
forall obj.
ObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewObject (ForeignPtr Button -> Button, FinalizerPtr Button)
forall {a}. (ForeignPtr Button -> Button, FinalizerPtr a)
mkButton (IO (Ptr Button) -> IO Button) -> IO (Ptr Button) -> IO Button
forall a b. (a -> b) -> a -> b
$ (Ptr Any -> Ptr Button) -> IO (Ptr Any) -> IO (Ptr Button)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Ptr Any -> Ptr Button
forall a b. Ptr a -> Ptr b
castPtr (IO (Ptr Any) -> IO (Ptr Button))
-> IO (Ptr Any) -> IO (Ptr Button)
forall a b. (a -> b) -> a -> b
$
ForeignPtr ColorSelectionDialog
-> (Ptr ColorSelectionDialog -> IO (Ptr Any)) -> IO (Ptr Any)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (ColorSelectionDialog -> ForeignPtr ColorSelectionDialog
unColorSelectionDialog ColorSelectionDialog
cd)
(\Ptr ColorSelectionDialog
hsc_ptr -> Ptr ColorSelectionDialog -> Int -> IO (Ptr Any)
forall b. Ptr b -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr ColorSelectionDialog
hsc_ptr Int
272)
{-# LINE 973 "Graphics/UI/Gtk/General/Structs.hsc" #-}
colorSelectionDialogGetCancelButton :: ColorSelectionDialog -> IO Button
colorSelectionDialogGetCancelButton :: ColorSelectionDialog -> IO Button
colorSelectionDialogGetCancelButton ColorSelectionDialog
cd =
(ForeignPtr Button -> Button, FinalizerPtr Button)
-> IO (Ptr Button) -> IO Button
forall obj.
ObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewObject (ForeignPtr Button -> Button, FinalizerPtr Button)
forall {a}. (ForeignPtr Button -> Button, FinalizerPtr a)
mkButton (IO (Ptr Button) -> IO Button) -> IO (Ptr Button) -> IO Button
forall a b. (a -> b) -> a -> b
$ (Ptr Any -> Ptr Button) -> IO (Ptr Any) -> IO (Ptr Button)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Ptr Any -> Ptr Button
forall a b. Ptr a -> Ptr b
castPtr (IO (Ptr Any) -> IO (Ptr Button))
-> IO (Ptr Any) -> IO (Ptr Button)
forall a b. (a -> b) -> a -> b
$
ForeignPtr ColorSelectionDialog
-> (Ptr ColorSelectionDialog -> IO (Ptr Any)) -> IO (Ptr Any)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (ColorSelectionDialog -> ForeignPtr ColorSelectionDialog
unColorSelectionDialog ColorSelectionDialog
cd)
(\Ptr ColorSelectionDialog
hsc_ptr -> Ptr ColorSelectionDialog -> Int -> IO (Ptr Any)
forall b. Ptr b -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr ColorSelectionDialog
hsc_ptr Int
280)
{-# LINE 982 "Graphics/UI/Gtk/General/Structs.hsc" #-}
colorSelectionDialogGetHelpButton :: ColorSelectionDialog -> IO Button
colorSelectionDialogGetHelpButton :: ColorSelectionDialog -> IO Button
colorSelectionDialogGetHelpButton ColorSelectionDialog
cd =
(ForeignPtr Button -> Button, FinalizerPtr Button)
-> IO (Ptr Button) -> IO Button
forall obj.
ObjectClass obj =>
(ForeignPtr obj -> obj, FinalizerPtr obj) -> IO (Ptr obj) -> IO obj
makeNewObject (ForeignPtr Button -> Button, FinalizerPtr Button)
forall {a}. (ForeignPtr Button -> Button, FinalizerPtr a)
mkButton (IO (Ptr Button) -> IO Button) -> IO (Ptr Button) -> IO Button
forall a b. (a -> b) -> a -> b
$ (Ptr Any -> Ptr Button) -> IO (Ptr Any) -> IO (Ptr Button)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Ptr Any -> Ptr Button
forall a b. Ptr a -> Ptr b
castPtr (IO (Ptr Any) -> IO (Ptr Button))
-> IO (Ptr Any) -> IO (Ptr Button)
forall a b. (a -> b) -> a -> b
$
ForeignPtr ColorSelectionDialog
-> (Ptr ColorSelectionDialog -> IO (Ptr Any)) -> IO (Ptr Any)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (ColorSelectionDialog -> ForeignPtr ColorSelectionDialog
unColorSelectionDialog ColorSelectionDialog
cd)
(\Ptr ColorSelectionDialog
hsc_ptr -> Ptr ColorSelectionDialog -> Int -> IO (Ptr Any)
forall b. Ptr b -> Int -> IO (Ptr Any)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr ColorSelectionDialog
hsc_ptr Int
288)
{-# LINE 991 "Graphics/UI/Gtk/General/Structs.hsc" #-}
dragContextGetActions :: DragContext -> IO Int
dragContextGetActions :: DragContext -> IO Int
dragContextGetActions DragContext
dc = (Int32 -> Int) -> IO Int32 -> IO Int
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral :: Int32 -> Int) (IO Int32 -> IO Int) -> IO Int32 -> IO Int
forall a b. (a -> b) -> a -> b
$
{-# LINE 994 "Graphics/UI/Gtk/General/Structs.hsc" #-}
withForeignPtr (unDragContext dc) (\hsc_ptr -> peekByteOff hsc_ptr 56)
{-# LINE 995 "Graphics/UI/Gtk/General/Structs.hsc" #-}
dragContextSetActions :: DragContext -> Int -> IO ()
dragContextSetActions :: DragContext -> Int -> IO ()
dragContextSetActions DragContext
dc Int
val = ForeignPtr DragContext -> (Ptr DragContext -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (DragContext -> ForeignPtr DragContext
unDragContext DragContext
dc) ((Ptr DragContext -> IO ()) -> IO ())
-> (Ptr DragContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DragContext
ptr ->
(\Ptr DragContext
hsc_ptr -> Ptr DragContext -> Int -> Int32 -> IO ()
forall b. Ptr b -> Int -> Int32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr DragContext
hsc_ptr Int
56) Ptr DragContext
ptr (Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
val :: Int32)
{-# LINE 999 "Graphics/UI/Gtk/General/Structs.hsc" #-}
dragContextGetAction :: DragContext -> IO Int
dragContextGetAction :: DragContext -> IO Int
dragContextGetAction DragContext
dc = (Int32 -> Int) -> IO Int32 -> IO Int
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral :: Int32 -> Int) (IO Int32 -> IO Int) -> IO Int32 -> IO Int
forall a b. (a -> b) -> a -> b
$
{-# LINE 1002 "Graphics/UI/Gtk/General/Structs.hsc" #-}
withForeignPtr (unDragContext dc) (\hsc_ptr -> peekByteOff hsc_ptr 64)
{-# LINE 1003 "Graphics/UI/Gtk/General/Structs.hsc" #-}
dragContextSetAction :: DragContext -> Int -> IO ()
dragContextSetAction :: DragContext -> Int -> IO ()
dragContextSetAction DragContext
dc Int
val = ForeignPtr DragContext -> (Ptr DragContext -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (DragContext -> ForeignPtr DragContext
unDragContext DragContext
dc) ((Ptr DragContext -> IO ()) -> IO ())
-> (Ptr DragContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DragContext
ptr ->
(\Ptr DragContext
hsc_ptr -> Ptr DragContext -> Int -> Int32 -> IO ()
forall b. Ptr b -> Int -> Int32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr DragContext
hsc_ptr Int
64) Ptr DragContext
ptr (Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
val :: Int32)
{-# LINE 1007 "Graphics/UI/Gtk/General/Structs.hsc" #-}
dragContextGetSuggestedAction :: DragContext -> IO Int
dragContextGetSuggestedAction :: DragContext -> IO Int
dragContextGetSuggestedAction DragContext
dc = (Int32 -> Int) -> IO Int32 -> IO Int
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral :: Int32 -> Int) (IO Int32 -> IO Int) -> IO Int32 -> IO Int
forall a b. (a -> b) -> a -> b
$
{-# LINE 1010 "Graphics/UI/Gtk/General/Structs.hsc" #-}
withForeignPtr (unDragContext dc) (\hsc_ptr -> peekByteOff hsc_ptr 60)
{-# LINE 1011 "Graphics/UI/Gtk/General/Structs.hsc" #-}
dragContextSetSuggestedAction :: DragContext -> Int -> IO ()
dragContextSetSuggestedAction :: DragContext -> Int -> IO ()
dragContextSetSuggestedAction DragContext
dc Int
val = ForeignPtr DragContext -> (Ptr DragContext -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (DragContext -> ForeignPtr DragContext
unDragContext DragContext
dc) ((Ptr DragContext -> IO ()) -> IO ())
-> (Ptr DragContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DragContext
ptr ->
(\Ptr DragContext
hsc_ptr -> Ptr DragContext -> Int -> Int32 -> IO ()
forall b. Ptr b -> Int -> Int32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr DragContext
hsc_ptr Int
60) Ptr DragContext
ptr (Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
val :: Int32)
{-# LINE 1015 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 1016 "Graphics/UI/Gtk/General/Structs.hsc" #-}
type SortColumnId = Int
treeSortableDefaultSortColumnId :: SortColumnId
treeSortableDefaultSortColumnId :: Int
treeSortableDefaultSortColumnId = -Int
1
{-# LINE 1028 "Graphics/UI/Gtk/General/Structs.hsc" #-}
intToAtom :: Int -> Atom
intToAtom :: Int -> Atom
intToAtom = Ptr () -> Atom
Atom (Ptr () -> Atom) -> (Int -> Ptr ()) -> Int -> Atom
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Any -> Int -> Ptr ()
forall a b. Ptr a -> Int -> Ptr b
plusPtr Ptr Any
forall a. Ptr a
nullPtr
tagInvalid :: Atom
tagInvalid :: Atom
tagInvalid = Int -> Atom
intToAtom Int
0
{-# LINE 1036 "Graphics/UI/Gtk/General/Structs.hsc" #-}
selectionPrimary :: SelectionTag
selectionPrimary :: Atom
selectionPrimary = Int -> Atom
intToAtom Int
1
{-# LINE 1041 "Graphics/UI/Gtk/General/Structs.hsc" #-}
selectionSecondary :: SelectionTag
selectionSecondary :: Atom
selectionSecondary = Int -> Atom
intToAtom Int
2
{-# LINE 1045 "Graphics/UI/Gtk/General/Structs.hsc" #-}
selectionClipboard :: SelectionTag
selectionClipboard :: Atom
selectionClipboard = Int -> Atom
intToAtom Int
69
{-# LINE 1049 "Graphics/UI/Gtk/General/Structs.hsc" #-}
targetString :: TargetTag
targetString :: Atom
targetString = Int -> Atom
intToAtom Int
31
{-# LINE 1053 "Graphics/UI/Gtk/General/Structs.hsc" #-}
selectionTypeAtom :: SelectionTypeTag
selectionTypeAtom :: Atom
selectionTypeAtom = Int -> Atom
intToAtom Int
4
{-# LINE 1058 "Graphics/UI/Gtk/General/Structs.hsc" #-}
selectionTypeInteger :: SelectionTypeTag
selectionTypeInteger :: Atom
selectionTypeInteger = Int -> Atom
intToAtom Int
19
{-# LINE 1062 "Graphics/UI/Gtk/General/Structs.hsc" #-}
selectionTypeString :: SelectionTypeTag
selectionTypeString :: Atom
selectionTypeString = Int -> Atom
intToAtom Int
31
{-# LINE 1067 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 1069 "Graphics/UI/Gtk/General/Structs.hsc" #-}
selectionDataGetType :: Ptr () -> IO SelectionTypeTag
selectionDataGetType :: Ptr () -> IO Atom
selectionDataGetType Ptr ()
selPtr =
(Int -> Atom) -> IO Int -> IO Atom
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Int -> Atom
intToAtom (IO Int -> IO Atom) -> IO Int -> IO Atom
forall a b. (a -> b) -> a -> b
$ (\Ptr ()
hsc_ptr -> Ptr () -> Int -> IO Int
forall b. Ptr b -> Int -> IO Int
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr ()
hsc_ptr Int
16) Ptr ()
selPtr
{-# LINE 1074 "Graphics/UI/Gtk/General/Structs.hsc" #-}
{-# LINE 1075 "Graphics/UI/Gtk/General/Structs.hsc" #-}
data TargetEntry = TargetEntry (Ptr Int8) InfoId
{-# LINE 1079 "Graphics/UI/Gtk/General/Structs.hsc" #-}
withTargetEntries :: [(TargetTag, InfoId)] -> (Int -> Ptr () -> IO a) -> IO a
withTargetEntries :: forall a. [(Atom, InfoId)] -> (Int -> Ptr () -> IO a) -> IO a
withTargetEntries [(Atom, InfoId)]
tags Int -> Ptr () -> IO a
fun = do
[TargetEntry]
ptrsInfo <- ((Atom, InfoId) -> IO TargetEntry)
-> [(Atom, InfoId)] -> IO [TargetEntry]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\(Atom Ptr ()
tag, InfoId
info) -> Ptr () -> IO (Ptr Int8)
gdk_atom_name Ptr ()
tag IO (Ptr Int8) -> (Ptr Int8 -> IO TargetEntry) -> IO TargetEntry
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Ptr Int8
strPtr ->
TargetEntry -> IO TargetEntry
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Int8 -> InfoId -> TargetEntry
TargetEntry Ptr Int8
strPtr InfoId
info)) [(Atom, InfoId)]
tags
a
res <- [TargetEntry] -> (Int -> Ptr TargetEntry -> IO a) -> IO a
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [TargetEntry]
ptrsInfo (\Int
len Ptr TargetEntry
ptr -> Int -> Ptr () -> IO a
fun Int
len (Ptr TargetEntry -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr Ptr TargetEntry
ptr))
(TargetEntry -> IO ()) -> [TargetEntry] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(TargetEntry Ptr Int8
ptr InfoId
_) -> Ptr Int8 -> IO ()
g_free Ptr Int8
ptr) [TargetEntry]
ptrsInfo
a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
res
foreign import ccall unsafe "gdk_atom_name"
gdk_atom_name :: Ptr () -> IO (Ptr Int8)
{-# LINE 1096 "Graphics/UI/Gtk/General/Structs.hsc" #-}
foreign import ccall unsafe "g_free"
g_free :: Ptr Int8 -> IO ()
{-# LINE 1099 "Graphics/UI/Gtk/General/Structs.hsc" #-}
instance Storable TargetEntry where
sizeOf :: TargetEntry -> Int
sizeOf TargetEntry
_ = Int
16
{-# LINE 1102 "Graphics/UI/Gtk/General/Structs.hsc" #-}
alignment _ = alignment (undefined::Word32)
{-# LINE 1103 "Graphics/UI/Gtk/General/Structs.hsc" #-}
peek ptr = undefined
poke :: Ptr TargetEntry -> TargetEntry -> IO ()
poke Ptr TargetEntry
ptr (TargetEntry Ptr Int8
cPtr InfoId
info) = do
(\Ptr TargetEntry
hsc_ptr -> Ptr TargetEntry -> Int -> Ptr Int8 -> IO ()
forall b. Ptr b -> Int -> Ptr Int8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr TargetEntry
hsc_ptr Int
0) Ptr TargetEntry
ptr Ptr Int8
cPtr
{-# LINE 1106 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr (0::Word32)
{-# LINE 1107 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 12) ptr info
{-# LINE 1108 "Graphics/UI/Gtk/General/Structs.hsc" #-}
data KeymapKey = KeymapKey {
KeymapKey -> Int
keycode :: Int
,KeymapKey -> Int
group :: Int
,KeymapKey -> Int
level :: Int
} deriving (KeymapKey -> KeymapKey -> Bool
(KeymapKey -> KeymapKey -> Bool)
-> (KeymapKey -> KeymapKey -> Bool) -> Eq KeymapKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KeymapKey -> KeymapKey -> Bool
== :: KeymapKey -> KeymapKey -> Bool
$c/= :: KeymapKey -> KeymapKey -> Bool
/= :: KeymapKey -> KeymapKey -> Bool
Eq, Int -> KeymapKey -> ShowS
[KeymapKey] -> ShowS
KeymapKey -> [Char]
(Int -> KeymapKey -> ShowS)
-> (KeymapKey -> [Char])
-> ([KeymapKey] -> ShowS)
-> Show KeymapKey
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KeymapKey -> ShowS
showsPrec :: Int -> KeymapKey -> ShowS
$cshow :: KeymapKey -> [Char]
show :: KeymapKey -> [Char]
$cshowList :: [KeymapKey] -> ShowS
showList :: [KeymapKey] -> ShowS
Show)
instance Storable KeymapKey where
sizeOf :: KeymapKey -> Int
sizeOf KeymapKey
_ = Int
12
{-# LINE 1128 "Graphics/UI/Gtk/General/Structs.hsc" #-}
alignment _ = alignment (undefined::Int32)
{-# LINE 1129 "Graphics/UI/Gtk/General/Structs.hsc" #-}
peek ptr = do
(keycode_ ::Word32) <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr
{-# LINE 1131 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(group_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr
{-# LINE 1132 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(level_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr
{-# LINE 1133 "Graphics/UI/Gtk/General/Structs.hsc" #-}
return $ KeymapKey (fromIntegral keycode_) (fromIntegral group_) (fromIntegral level_)
poke :: Ptr KeymapKey -> KeymapKey -> IO ()
poke Ptr KeymapKey
ptr (KeymapKey Int
keycode Int
group Int
level) = do
(\Ptr KeymapKey
hsc_ptr -> Ptr KeymapKey -> Int -> Word32 -> IO ()
forall b. Ptr b -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr KeymapKey
hsc_ptr Int
0) Ptr KeymapKey
ptr ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
keycode)::Word32)
{-# LINE 1136 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr ((fromIntegral group)::Int32)
{-# LINE 1137 "Graphics/UI/Gtk/General/Structs.hsc" #-}
(\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr ((fromIntegral level)::Int32)
{-# LINE 1138 "Graphics/UI/Gtk/General/Structs.hsc" #-}