{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Cogl.Objects.Bitmap
    ( 

-- * Exported types
    Bitmap(..)                              ,
    IsBitmap                                ,
    toBitmap                                ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveBitmapMethod                     ,
#endif

-- ** getSizeFromFile #method:getSizeFromFile#

    bitmapGetSizeFromFile                   ,


-- ** newFromFile #method:newFromFile#

    bitmapNewFromFile                       ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R


-- | Memory-managed wrapper type.
newtype Bitmap = Bitmap (SP.ManagedPtr Bitmap)
    deriving (Bitmap -> Bitmap -> Bool
(Bitmap -> Bitmap -> Bool)
-> (Bitmap -> Bitmap -> Bool) -> Eq Bitmap
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Bitmap -> Bitmap -> Bool
== :: Bitmap -> Bitmap -> Bool
$c/= :: Bitmap -> Bitmap -> Bool
/= :: Bitmap -> Bitmap -> Bool
Eq)

instance SP.ManagedPtrNewtype Bitmap where
    toManagedPtr :: Bitmap -> ManagedPtr Bitmap
toManagedPtr (Bitmap ManagedPtr Bitmap
p) = ManagedPtr Bitmap
p

foreign import ccall "cogl_bitmap_get_gtype"
    c_cogl_bitmap_get_gtype :: IO B.Types.GType

instance B.Types.TypedObject Bitmap where
    glibType :: IO GType
glibType = IO GType
c_cogl_bitmap_get_gtype

-- | Type class for types which can be safely cast to `Bitmap`, for instance with `toBitmap`.
class (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf Bitmap o) => IsBitmap o
instance (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf Bitmap o) => IsBitmap o

instance O.HasParentTypes Bitmap
type instance O.ParentTypes Bitmap = '[]

-- | Cast to `Bitmap`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toBitmap :: (MIO.MonadIO m, IsBitmap o) => o -> m Bitmap
toBitmap :: forall (m :: * -> *) o. (MonadIO m, IsBitmap o) => o -> m Bitmap
toBitmap = IO Bitmap -> m Bitmap
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bitmap -> m Bitmap) -> (o -> IO Bitmap) -> o -> m Bitmap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Bitmap -> Bitmap) -> o -> IO Bitmap
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Bitmap -> Bitmap
Bitmap

--- XXX Missing getter and/or setter, so no GValue instance could be generated.
#if defined(ENABLE_OVERLOADING)
type family ResolveBitmapMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveBitmapMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveBitmapMethod t Bitmap, O.OverloadedMethod info Bitmap p) => OL.IsLabel t (Bitmap -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveBitmapMethod t Bitmap, O.OverloadedMethod info Bitmap p, R.HasField t Bitmap p) => R.HasField t Bitmap p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveBitmapMethod t Bitmap, O.OverloadedMethodInfo info Bitmap) => OL.IsLabel t (O.MethodProxy info Bitmap) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance BoxedPtr Bitmap where
    boxedPtrCopy :: Bitmap -> IO Bitmap
boxedPtrCopy = Bitmap -> IO Bitmap
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: Bitmap -> IO ()
boxedPtrFree = \Bitmap
_x -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()


-- method Bitmap::new_from_file
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "filename"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the file to load." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Cogl" , name = "Bitmap" })
-- throws : True
-- Skip return : False

foreign import ccall "cogl_bitmap_new_from_file" cogl_bitmap_new_from_file :: 
    CString ->                              -- filename : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Bitmap)

-- | Loads an image file from disk. This function can be safely called from
-- within a thread.
-- 
-- /Since: 1.0/
bitmapNewFromFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@filename@/: the file to load.
    -> m Bitmap
    -- ^ __Returns:__ a t'GI.Cogl.Objects.Bitmap.Bitmap' to the new loaded
    --               image data, or 'P.Nothing' if loading the image failed. /(Can throw 'Data.GI.Base.GError.GError')/
bitmapNewFromFile :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Text -> m Bitmap
bitmapNewFromFile Text
filename = IO Bitmap -> m Bitmap
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bitmap -> m Bitmap) -> IO Bitmap -> m Bitmap
forall a b. (a -> b) -> a -> b
$ do
    CString
filename' <- Text -> IO CString
textToCString Text
filename
    IO Bitmap -> IO () -> IO Bitmap
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Bitmap
result <- (Ptr (Ptr GError) -> IO (Ptr Bitmap)) -> IO (Ptr Bitmap)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Bitmap)) -> IO (Ptr Bitmap))
-> (Ptr (Ptr GError) -> IO (Ptr Bitmap)) -> IO (Ptr Bitmap)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr Bitmap)
cogl_bitmap_new_from_file CString
filename'
        Text -> Ptr Bitmap -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bitmapNewFromFile" Ptr Bitmap
result
        Bitmap
result' <- ((ManagedPtr Bitmap -> Bitmap) -> Ptr Bitmap -> IO Bitmap
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Bitmap -> Bitmap
Bitmap) Ptr Bitmap
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
        Bitmap -> IO Bitmap
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bitmap
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Bitmap::get_size_from_file
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "filename"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the file to check" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the bitmap width, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the bitmap height, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "cogl_bitmap_get_size_from_file" cogl_bitmap_get_size_from_file :: 
    CString ->                              -- filename : TBasicType TUTF8
    Ptr Int32 ->                            -- width : TBasicType TInt
    Ptr Int32 ->                            -- height : TBasicType TInt
    IO Int32

-- | Parses an image file enough to extract the width and height
-- of the bitmap.
-- 
-- /Since: 1.0/
bitmapGetSizeFromFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@filename@/: the file to check
    -> m ((Int32, Int32, Int32))
    -- ^ __Returns:__ 'P.True' if the image was successfully parsed
bitmapGetSizeFromFile :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m (Int32, Int32, Int32)
bitmapGetSizeFromFile Text
filename = IO (Int32, Int32, Int32) -> m (Int32, Int32, Int32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32, Int32) -> m (Int32, Int32, Int32))
-> IO (Int32, Int32, Int32) -> m (Int32, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    CString
filename' <- Text -> IO CString
textToCString Text
filename
    Ptr Int32
width <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
height <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Int32
result <- CString -> Ptr Int32 -> Ptr Int32 -> IO Int32
cogl_bitmap_get_size_from_file CString
filename' Ptr Int32
width Ptr Int32
height
    Int32
width' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
width
    Int32
height' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
height
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
width
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
height
    (Int32, Int32, Int32) -> IO (Int32, Int32, Int32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
result, Int32
width', Int32
height')

#if defined(ENABLE_OVERLOADING)
#endif