{- | Copyright : Will Thompson, Iñaki García Etxebarria and Jonas Platte License : LGPL-2.1 Maintainer : Iñaki García Etxebarria (garetxe@gmail.com) A #GdkPixdata contains pixbuf information in a form suitable for serialization and streaming. -} module GI.GdkPixbuf.Structs.Pixdata ( -- * Exported types Pixdata(..) , newZeroPixdata , noPixdata , -- * Methods -- ** pixdataDeserialize PixdataDeserializeMethodInfo , pixdataDeserialize , -- ** pixdataSerialize PixdataSerializeMethodInfo , pixdataSerialize , -- ** pixdataToCsource PixdataToCsourceMethodInfo , pixdataToCsource , -- * Properties -- ** Height pixdataReadHeight , -- ** Length pixdataReadLength , -- ** Magic pixdataReadMagic , -- ** PixdataType pixdataReadPixdataType , -- ** PixelData pixdataReadPixelData , -- ** Rowstride pixdataReadRowstride , -- ** Width pixdataReadWidth , ) where import Prelude () import Data.GI.Base.ShortPrelude import qualified Data.Text as T import qualified Data.ByteString.Char8 as B import qualified Data.Map as Map import GI.GdkPixbuf.Types import GI.GdkPixbuf.Callbacks import qualified GI.GLib as GLib newtype Pixdata = Pixdata (ForeignPtr Pixdata) -- | Construct a `Pixdata` struct initialized to zero. newZeroPixdata :: MonadIO m => m Pixdata newZeroPixdata = liftIO $ callocBytes 32 >>= wrapPtr Pixdata noPixdata :: Maybe Pixdata noPixdata = Nothing pixdataReadMagic :: Pixdata -> IO Word32 pixdataReadMagic s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 0) :: IO Word32 return val pixdataReadLength :: Pixdata -> IO Int32 pixdataReadLength s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 4) :: IO Int32 return val pixdataReadPixdataType :: Pixdata -> IO Word32 pixdataReadPixdataType s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 8) :: IO Word32 return val pixdataReadRowstride :: Pixdata -> IO Word32 pixdataReadRowstride s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 12) :: IO Word32 return val pixdataReadWidth :: Pixdata -> IO Word32 pixdataReadWidth s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 16) :: IO Word32 return val pixdataReadHeight :: Pixdata -> IO Word32 pixdataReadHeight s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 20) :: IO Word32 return val pixdataReadPixelData :: Pixdata -> IO (Ptr Word8) pixdataReadPixelData s = withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 24) :: IO (Ptr Word8) return val -- method Pixdata::deserialize -- method type : OrdinaryMethod -- Args : [Arg {argCName = "_obj", argType = TInterface "GdkPixbuf" "Pixdata", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "stream_length", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "stream", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}] -- Lengths : [Arg {argCName = "stream_length", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}] -- returnType : TBasicType TBoolean -- throws : True -- Skip return : False foreign import ccall "gdk_pixdata_deserialize" gdk_pixdata_deserialize :: Ptr Pixdata -> -- _obj : TInterface "GdkPixbuf" "Pixdata" Word32 -> -- stream_length : TBasicType TUInt32 Ptr Word8 -> -- stream : TCArray False (-1) 1 (TBasicType TUInt8) Ptr (Ptr GError) -> -- error IO CInt {-# DEPRECATED pixdataDeserialize ["(Since version 2.32)","Use #GResource instead."]#-} pixdataDeserialize :: (MonadIO m) => Pixdata -- _obj -> ByteString -- stream -> m () -- result pixdataDeserialize _obj stream = liftIO $ do let streamLength = fromIntegral $ B.length stream let _obj' = unsafeManagedPtrGetPtr _obj stream' <- packByteString stream onException (do _ <- propagateGError $ gdk_pixdata_deserialize _obj' streamLength stream' touchManagedPtr _obj freeMem stream' return () ) (do freeMem stream' ) data PixdataDeserializeMethodInfo instance (signature ~ (ByteString -> m ()), MonadIO m) => MethodInfo PixdataDeserializeMethodInfo Pixdata signature where overloadedMethod _ = pixdataDeserialize -- method Pixdata::serialize -- method type : OrdinaryMethod -- Args : [Arg {argCName = "_obj", argType = TInterface "GdkPixbuf" "Pixdata", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "stream_length_p", argType = TBasicType TUInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}] -- Lengths : [Arg {argCName = "stream_length_p", argType = TBasicType TUInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferEverything}] -- returnType : TCArray False (-1) 1 (TBasicType TUInt8) -- throws : False -- Skip return : False foreign import ccall "gdk_pixdata_serialize" gdk_pixdata_serialize :: Ptr Pixdata -> -- _obj : TInterface "GdkPixbuf" "Pixdata" Ptr Word32 -> -- stream_length_p : TBasicType TUInt32 IO (Ptr Word8) {-# DEPRECATED pixdataSerialize ["(Since version 2.32)","Use #GResource instead."]#-} pixdataSerialize :: (MonadIO m) => Pixdata -- _obj -> m ByteString -- result pixdataSerialize _obj = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj streamLengthP <- allocMem :: IO (Ptr Word32) result <- gdk_pixdata_serialize _obj' streamLengthP streamLengthP' <- peek streamLengthP checkUnexpectedReturnNULL "gdk_pixdata_serialize" result result' <- (unpackByteStringWithLength streamLengthP') result freeMem result touchManagedPtr _obj freeMem streamLengthP return result' data PixdataSerializeMethodInfo instance (signature ~ (m ByteString), MonadIO m) => MethodInfo PixdataSerializeMethodInfo Pixdata signature where overloadedMethod _ = pixdataSerialize -- method Pixdata::to_csource -- method type : OrdinaryMethod -- Args : [Arg {argCName = "_obj", argType = TInterface "GdkPixbuf" "Pixdata", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "dump_type", argType = TInterface "GdkPixbuf" "PixdataDumpType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}] -- Lengths : [] -- returnType : TInterface "GLib" "String" -- throws : False -- Skip return : False foreign import ccall "gdk_pixdata_to_csource" gdk_pixdata_to_csource :: Ptr Pixdata -> -- _obj : TInterface "GdkPixbuf" "Pixdata" CString -> -- name : TBasicType TUTF8 CUInt -> -- dump_type : TInterface "GdkPixbuf" "PixdataDumpType" IO (Ptr GLib.String) {-# DEPRECATED pixdataToCsource ["(Since version 2.32)","Use #GResource instead."]#-} pixdataToCsource :: (MonadIO m) => Pixdata -- _obj -> T.Text -- name -> [PixdataDumpType] -- dumpType -> m GLib.String -- result pixdataToCsource _obj name dumpType = liftIO $ do let _obj' = unsafeManagedPtrGetPtr _obj name' <- textToCString name let dumpType' = gflagsToWord dumpType result <- gdk_pixdata_to_csource _obj' name' dumpType' checkUnexpectedReturnNULL "gdk_pixdata_to_csource" result result' <- (wrapBoxed GLib.String) result touchManagedPtr _obj freeMem name' return result' data PixdataToCsourceMethodInfo instance (signature ~ (T.Text -> [PixdataDumpType] -> m GLib.String), MonadIO m) => MethodInfo PixdataToCsourceMethodInfo Pixdata signature where overloadedMethod _ = pixdataToCsource type family ResolvePixdataMethod (t :: Symbol) (o :: *) :: * where ResolvePixdataMethod "deserialize" o = PixdataDeserializeMethodInfo ResolvePixdataMethod "serialize" o = PixdataSerializeMethodInfo ResolvePixdataMethod "toCsource" o = PixdataToCsourceMethodInfo ResolvePixdataMethod l o = MethodResolutionFailed l o instance (info ~ ResolvePixdataMethod t Pixdata, MethodInfo info Pixdata p) => IsLabelProxy t (Pixdata -> p) where fromLabelProxy _ = overloadedMethod (MethodProxy :: MethodProxy info) #if MIN_VERSION_base(4,9,0) instance (info ~ ResolvePixdataMethod t Pixdata, MethodInfo info Pixdata p) => IsLabel t (Pixdata -> p) where fromLabel _ = overloadedMethod (MethodProxy :: MethodProxy info) #endif