{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-unused-imports #-} -- Generated code. {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# LANGUAGE ForeignFunctionInterface, ConstraintKinds, TypeFamilies, MultiParamTypeClasses, KindSignatures, FlexibleInstances, UndecidableInstances, DataKinds, OverloadedStrings, NegativeLiterals, FlexibleContexts #-} module GI.GdkPixbufAttributes where import Prelude () import Data.GI.Base.ShortPrelude import Data.Char import Data.Int import Data.Word import qualified Data.ByteString.Char8 as B import Data.ByteString.Char8 (ByteString) import qualified Data.Map as Map import Foreign.C import Foreign.Ptr import Foreign.ForeignPtr import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr) import Foreign.Storable (peek, poke, sizeOf) import Control.Applicative ((<$>)) import Control.Exception (onException) import Control.Monad.IO.Class import qualified Data.Text as T import Data.GI.Base.Attributes hiding (get, set) import Data.GI.Base.BasicTypes import Data.GI.Base.BasicConversions import Data.GI.Base.Closure import Data.GI.Base.GError import Data.GI.Base.GHashTable import Data.GI.Base.GParamSpec import Data.GI.Base.GVariant import Data.GI.Base.GValue import Data.GI.Base.ManagedPtr import Data.GI.Base.Overloading import Data.GI.Base.Properties hiding (new) import Data.GI.Base.Signals (SignalConnectMode(..), connectSignalFunPtr, SignalHandlerId) import Data.GI.Base.Utils import qualified GI.GLib as GLib import qualified GI.GLibAttributes as GLibA import GI.GdkPixbuf -- VVV Prop "bits-per-sample" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getPixbufBitsPerSample :: (MonadIO m, PixbufK o) => o -> m Int32 getPixbufBitsPerSample obj = liftIO $ getObjectPropertyCInt obj "bits-per-sample" constructPixbufBitsPerSample :: Int32 -> IO ([Char], GValue) constructPixbufBitsPerSample val = constructObjectPropertyCInt "bits-per-sample" val data PixbufBitsPerSamplePropertyInfo instance AttrInfo PixbufBitsPerSamplePropertyInfo where type AttrAllowedOps PixbufBitsPerSamplePropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint PixbufBitsPerSamplePropertyInfo = (~) Int32 type AttrBaseTypeConstraint PixbufBitsPerSamplePropertyInfo = PixbufK type AttrGetType PixbufBitsPerSamplePropertyInfo = Int32 type AttrLabel PixbufBitsPerSamplePropertyInfo = "Pixbuf::bits-per-sample" attrGet _ = getPixbufBitsPerSample attrSet _ = undefined attrConstruct _ = constructPixbufBitsPerSample -- VVV Prop "colorspace" -- Type: TInterface "GdkPixbuf" "Colorspace" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getPixbufColorspace :: (MonadIO m, PixbufK o) => o -> m Colorspace getPixbufColorspace obj = liftIO $ getObjectPropertyEnum obj "colorspace" constructPixbufColorspace :: Colorspace -> IO ([Char], GValue) constructPixbufColorspace val = constructObjectPropertyEnum "colorspace" val data PixbufColorspacePropertyInfo instance AttrInfo PixbufColorspacePropertyInfo where type AttrAllowedOps PixbufColorspacePropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint PixbufColorspacePropertyInfo = (~) Colorspace type AttrBaseTypeConstraint PixbufColorspacePropertyInfo = PixbufK type AttrGetType PixbufColorspacePropertyInfo = Colorspace type AttrLabel PixbufColorspacePropertyInfo = "Pixbuf::colorspace" attrGet _ = getPixbufColorspace attrSet _ = undefined attrConstruct _ = constructPixbufColorspace -- VVV Prop "has-alpha" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getPixbufHasAlpha :: (MonadIO m, PixbufK o) => o -> m Bool getPixbufHasAlpha obj = liftIO $ getObjectPropertyBool obj "has-alpha" constructPixbufHasAlpha :: Bool -> IO ([Char], GValue) constructPixbufHasAlpha val = constructObjectPropertyBool "has-alpha" val data PixbufHasAlphaPropertyInfo instance AttrInfo PixbufHasAlphaPropertyInfo where type AttrAllowedOps PixbufHasAlphaPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint PixbufHasAlphaPropertyInfo = (~) Bool type AttrBaseTypeConstraint PixbufHasAlphaPropertyInfo = PixbufK type AttrGetType PixbufHasAlphaPropertyInfo = Bool type AttrLabel PixbufHasAlphaPropertyInfo = "Pixbuf::has-alpha" attrGet _ = getPixbufHasAlpha attrSet _ = undefined attrConstruct _ = constructPixbufHasAlpha -- VVV Prop "height" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getPixbufHeight :: (MonadIO m, PixbufK o) => o -> m Int32 getPixbufHeight obj = liftIO $ getObjectPropertyCInt obj "height" constructPixbufHeight :: Int32 -> IO ([Char], GValue) constructPixbufHeight val = constructObjectPropertyCInt "height" val data PixbufHeightPropertyInfo instance AttrInfo PixbufHeightPropertyInfo where type AttrAllowedOps PixbufHeightPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint PixbufHeightPropertyInfo = (~) Int32 type AttrBaseTypeConstraint PixbufHeightPropertyInfo = PixbufK type AttrGetType PixbufHeightPropertyInfo = Int32 type AttrLabel PixbufHeightPropertyInfo = "Pixbuf::height" attrGet _ = getPixbufHeight attrSet _ = undefined attrConstruct _ = constructPixbufHeight -- VVV Prop "n-channels" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getPixbufNChannels :: (MonadIO m, PixbufK o) => o -> m Int32 getPixbufNChannels obj = liftIO $ getObjectPropertyCInt obj "n-channels" constructPixbufNChannels :: Int32 -> IO ([Char], GValue) constructPixbufNChannels val = constructObjectPropertyCInt "n-channels" val data PixbufNChannelsPropertyInfo instance AttrInfo PixbufNChannelsPropertyInfo where type AttrAllowedOps PixbufNChannelsPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint PixbufNChannelsPropertyInfo = (~) Int32 type AttrBaseTypeConstraint PixbufNChannelsPropertyInfo = PixbufK type AttrGetType PixbufNChannelsPropertyInfo = Int32 type AttrLabel PixbufNChannelsPropertyInfo = "Pixbuf::n-channels" attrGet _ = getPixbufNChannels attrSet _ = undefined attrConstruct _ = constructPixbufNChannels -- VVV Prop "pixel-bytes" -- Type: TInterface "GLib" "Bytes" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getPixbufPixelBytes :: (MonadIO m, PixbufK o) => o -> m GLib.Bytes getPixbufPixelBytes obj = liftIO $ getObjectPropertyBoxed obj "pixel-bytes" GLib.Bytes constructPixbufPixelBytes :: GLib.Bytes -> IO ([Char], GValue) constructPixbufPixelBytes val = constructObjectPropertyBoxed "pixel-bytes" val data PixbufPixelBytesPropertyInfo instance AttrInfo PixbufPixelBytesPropertyInfo where type AttrAllowedOps PixbufPixelBytesPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint PixbufPixelBytesPropertyInfo = (~) GLib.Bytes type AttrBaseTypeConstraint PixbufPixelBytesPropertyInfo = PixbufK type AttrGetType PixbufPixelBytesPropertyInfo = GLib.Bytes type AttrLabel PixbufPixelBytesPropertyInfo = "Pixbuf::pixel-bytes" attrGet _ = getPixbufPixelBytes attrSet _ = undefined attrConstruct _ = constructPixbufPixelBytes -- VVV Prop "pixels" -- Type: TBasicType TVoid -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getPixbufPixels :: (MonadIO m, PixbufK o) => o -> m (Ptr ()) getPixbufPixels obj = liftIO $ getObjectPropertyPtr obj "pixels" constructPixbufPixels :: (Ptr ()) -> IO ([Char], GValue) constructPixbufPixels val = constructObjectPropertyPtr "pixels" val data PixbufPixelsPropertyInfo instance AttrInfo PixbufPixelsPropertyInfo where type AttrAllowedOps PixbufPixelsPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint PixbufPixelsPropertyInfo = (~) (Ptr ()) type AttrBaseTypeConstraint PixbufPixelsPropertyInfo = PixbufK type AttrGetType PixbufPixelsPropertyInfo = (Ptr ()) type AttrLabel PixbufPixelsPropertyInfo = "Pixbuf::pixels" attrGet _ = getPixbufPixels attrSet _ = undefined attrConstruct _ = constructPixbufPixels -- VVV Prop "rowstride" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getPixbufRowstride :: (MonadIO m, PixbufK o) => o -> m Int32 getPixbufRowstride obj = liftIO $ getObjectPropertyCInt obj "rowstride" constructPixbufRowstride :: Int32 -> IO ([Char], GValue) constructPixbufRowstride val = constructObjectPropertyCInt "rowstride" val data PixbufRowstridePropertyInfo instance AttrInfo PixbufRowstridePropertyInfo where type AttrAllowedOps PixbufRowstridePropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint PixbufRowstridePropertyInfo = (~) Int32 type AttrBaseTypeConstraint PixbufRowstridePropertyInfo = PixbufK type AttrGetType PixbufRowstridePropertyInfo = Int32 type AttrLabel PixbufRowstridePropertyInfo = "Pixbuf::rowstride" attrGet _ = getPixbufRowstride attrSet _ = undefined attrConstruct _ = constructPixbufRowstride -- VVV Prop "width" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getPixbufWidth :: (MonadIO m, PixbufK o) => o -> m Int32 getPixbufWidth obj = liftIO $ getObjectPropertyCInt obj "width" constructPixbufWidth :: Int32 -> IO ([Char], GValue) constructPixbufWidth val = constructObjectPropertyCInt "width" val data PixbufWidthPropertyInfo instance AttrInfo PixbufWidthPropertyInfo where type AttrAllowedOps PixbufWidthPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint PixbufWidthPropertyInfo = (~) Int32 type AttrBaseTypeConstraint PixbufWidthPropertyInfo = PixbufK type AttrGetType PixbufWidthPropertyInfo = Int32 type AttrLabel PixbufWidthPropertyInfo = "Pixbuf::width" attrGet _ = getPixbufWidth attrSet _ = undefined attrConstruct _ = constructPixbufWidth type instance AttributeList Pixbuf = '[ '("bits-per-sample", PixbufBitsPerSamplePropertyInfo), '("colorspace", PixbufColorspacePropertyInfo), '("has-alpha", PixbufHasAlphaPropertyInfo), '("height", PixbufHeightPropertyInfo), '("n-channels", PixbufNChannelsPropertyInfo), '("pixel-bytes", PixbufPixelBytesPropertyInfo), '("pixels", PixbufPixelsPropertyInfo), '("rowstride", PixbufRowstridePropertyInfo), '("width", PixbufWidthPropertyInfo)] type instance AttributeList PixbufAnimation = '[ ] type instance AttributeList PixbufAnimationIter = '[ ] type instance AttributeList PixbufLoader = '[ ] -- VVV Prop "loop" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getPixbufSimpleAnimLoop :: (MonadIO m, PixbufSimpleAnimK o) => o -> m Bool getPixbufSimpleAnimLoop obj = liftIO $ getObjectPropertyBool obj "loop" setPixbufSimpleAnimLoop :: (MonadIO m, PixbufSimpleAnimK o) => o -> Bool -> m () setPixbufSimpleAnimLoop obj val = liftIO $ setObjectPropertyBool obj "loop" val constructPixbufSimpleAnimLoop :: Bool -> IO ([Char], GValue) constructPixbufSimpleAnimLoop val = constructObjectPropertyBool "loop" val data PixbufSimpleAnimLoopPropertyInfo instance AttrInfo PixbufSimpleAnimLoopPropertyInfo where type AttrAllowedOps PixbufSimpleAnimLoopPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint PixbufSimpleAnimLoopPropertyInfo = (~) Bool type AttrBaseTypeConstraint PixbufSimpleAnimLoopPropertyInfo = PixbufSimpleAnimK type AttrGetType PixbufSimpleAnimLoopPropertyInfo = Bool type AttrLabel PixbufSimpleAnimLoopPropertyInfo = "PixbufSimpleAnim::loop" attrGet _ = getPixbufSimpleAnimLoop attrSet _ = setPixbufSimpleAnimLoop attrConstruct _ = constructPixbufSimpleAnimLoop type instance AttributeList PixbufSimpleAnim = '[ '("loop", PixbufSimpleAnimLoopPropertyInfo)] type instance AttributeList PixbufSimpleAnimIter = '[ ]