{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Represents a diff binary file.

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

module GI.Ggit.Structs.DiffBinaryFile
    ( 

-- * Exported types
    DiffBinaryFile(..)                      ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveDiffBinaryFileMethod             ,
#endif


-- ** getBinaryType #method:getBinaryType#

#if defined(ENABLE_OVERLOADING)
    DiffBinaryFileGetBinaryTypeMethodInfo   ,
#endif
    diffBinaryFileGetBinaryType             ,


-- ** getData #method:getData#

#if defined(ENABLE_OVERLOADING)
    DiffBinaryFileGetDataMethodInfo         ,
#endif
    diffBinaryFileGetData                   ,


-- ** getInflatedSize #method:getInflatedSize#

#if defined(ENABLE_OVERLOADING)
    DiffBinaryFileGetInflatedSizeMethodInfo ,
#endif
    diffBinaryFileGetInflatedSize           ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    DiffBinaryFileRefMethodInfo             ,
#endif
    diffBinaryFileRef                       ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    DiffBinaryFileUnrefMethodInfo           ,
#endif
    diffBinaryFileUnref                     ,




    ) 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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
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.Text as T
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 {-# SOURCE #-} qualified GI.Ggit.Enums as Ggit.Enums

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

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

foreign import ccall "ggit_diff_binary_file_get_type" c_ggit_diff_binary_file_get_type :: 
    IO GType

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

instance B.Types.TypedObject DiffBinaryFile where
    glibType :: IO GType
glibType = IO GType
c_ggit_diff_binary_file_get_type

instance B.Types.GBoxed DiffBinaryFile

-- | Convert 'DiffBinaryFile' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue DiffBinaryFile where
    toGValue :: DiffBinaryFile -> IO GValue
toGValue DiffBinaryFile
o = do
        GType
gtype <- IO GType
c_ggit_diff_binary_file_get_type
        DiffBinaryFile -> (Ptr DiffBinaryFile -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DiffBinaryFile
o (GType
-> (GValue -> Ptr DiffBinaryFile -> IO ())
-> Ptr DiffBinaryFile
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr DiffBinaryFile -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO DiffBinaryFile
fromGValue GValue
gv = do
        Ptr DiffBinaryFile
ptr <- GValue -> IO (Ptr DiffBinaryFile)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr DiffBinaryFile)
        (ManagedPtr DiffBinaryFile -> DiffBinaryFile)
-> Ptr DiffBinaryFile -> IO DiffBinaryFile
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr DiffBinaryFile -> DiffBinaryFile
DiffBinaryFile Ptr DiffBinaryFile
ptr
        
    


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DiffBinaryFile
type instance O.AttributeList DiffBinaryFile = DiffBinaryFileAttributeList
type DiffBinaryFileAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method DiffBinaryFile::get_binary_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "file"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "DiffBinaryFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiffBinaryFile."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Ggit" , name = "DiffBinaryType" })
-- throws : False
-- Skip return : False

foreign import ccall "ggit_diff_binary_file_get_binary_type" ggit_diff_binary_file_get_binary_type :: 
    Ptr DiffBinaryFile ->                   -- file : TInterface (Name {namespace = "Ggit", name = "DiffBinaryFile"})
    IO CUInt

-- | Gets the t'GI.Ggit.Enums.DiffBinaryType' for /@file@/.
diffBinaryFileGetBinaryType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DiffBinaryFile
    -- ^ /@file@/: a t'GI.Ggit.Structs.DiffBinaryFile.DiffBinaryFile'.
    -> m Ggit.Enums.DiffBinaryType
    -- ^ __Returns:__ the file\'s binary type.
diffBinaryFileGetBinaryType :: DiffBinaryFile -> m DiffBinaryType
diffBinaryFileGetBinaryType DiffBinaryFile
file = IO DiffBinaryType -> m DiffBinaryType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DiffBinaryType -> m DiffBinaryType)
-> IO DiffBinaryType -> m DiffBinaryType
forall a b. (a -> b) -> a -> b
$ do
    Ptr DiffBinaryFile
file' <- DiffBinaryFile -> IO (Ptr DiffBinaryFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DiffBinaryFile
file
    CUInt
result <- Ptr DiffBinaryFile -> IO CUInt
ggit_diff_binary_file_get_binary_type Ptr DiffBinaryFile
file'
    let result' :: DiffBinaryType
result' = (Int -> DiffBinaryType
forall a. Enum a => Int -> a
toEnum (Int -> DiffBinaryType)
-> (CUInt -> Int) -> CUInt -> DiffBinaryType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    DiffBinaryFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DiffBinaryFile
file
    DiffBinaryType -> IO DiffBinaryType
forall (m :: * -> *) a. Monad m => a -> m a
return DiffBinaryType
result'

#if defined(ENABLE_OVERLOADING)
data DiffBinaryFileGetBinaryTypeMethodInfo
instance (signature ~ (m Ggit.Enums.DiffBinaryType), MonadIO m) => O.MethodInfo DiffBinaryFileGetBinaryTypeMethodInfo DiffBinaryFile signature where
    overloadedMethod = diffBinaryFileGetBinaryType

#endif

-- method DiffBinaryFile::get_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "file"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "DiffBinaryFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiffBinaryFile."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "location to return size of byte data."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt8)
-- throws : False
-- Skip return : False

foreign import ccall "ggit_diff_binary_file_get_data" ggit_diff_binary_file_get_data :: 
    Ptr DiffBinaryFile ->                   -- file : TInterface (Name {namespace = "Ggit", name = "DiffBinaryFile"})
    Word64 ->                               -- size : TBasicType TUInt64
    IO Word8

-- | Get the binary data. This data should not be modified.
diffBinaryFileGetData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DiffBinaryFile
    -- ^ /@file@/: a t'GI.Ggit.Structs.DiffBinaryFile.DiffBinaryFile'.
    -> Word64
    -- ^ /@size@/: location to return size of byte data.
    -> m Word8
    -- ^ __Returns:__ a pointer to the binary data, or 'P.Nothing'.
diffBinaryFileGetData :: DiffBinaryFile -> Word64 -> m Word8
diffBinaryFileGetData DiffBinaryFile
file Word64
size = IO Word8 -> m Word8
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word8 -> m Word8) -> IO Word8 -> m Word8
forall a b. (a -> b) -> a -> b
$ do
    Ptr DiffBinaryFile
file' <- DiffBinaryFile -> IO (Ptr DiffBinaryFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DiffBinaryFile
file
    Word8
result <- Ptr DiffBinaryFile -> Word64 -> IO Word8
ggit_diff_binary_file_get_data Ptr DiffBinaryFile
file' Word64
size
    DiffBinaryFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DiffBinaryFile
file
    Word8 -> IO Word8
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
result

#if defined(ENABLE_OVERLOADING)
data DiffBinaryFileGetDataMethodInfo
instance (signature ~ (Word64 -> m Word8), MonadIO m) => O.MethodInfo DiffBinaryFileGetDataMethodInfo DiffBinaryFile signature where
    overloadedMethod = diffBinaryFileGetData

#endif

-- method DiffBinaryFile::get_inflated_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "file"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "DiffBinaryFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiffBinaryFile."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "ggit_diff_binary_file_get_inflated_size" ggit_diff_binary_file_get_inflated_size :: 
    Ptr DiffBinaryFile ->                   -- file : TInterface (Name {namespace = "Ggit", name = "DiffBinaryFile"})
    IO Word64

-- | Gets the length of the binary data after inflation.
diffBinaryFileGetInflatedSize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DiffBinaryFile
    -- ^ /@file@/: a t'GI.Ggit.Structs.DiffBinaryFile.DiffBinaryFile'.
    -> m Word64
    -- ^ __Returns:__ the length of the binary data after inflation.
diffBinaryFileGetInflatedSize :: DiffBinaryFile -> m Word64
diffBinaryFileGetInflatedSize DiffBinaryFile
file = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
    Ptr DiffBinaryFile
file' <- DiffBinaryFile -> IO (Ptr DiffBinaryFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DiffBinaryFile
file
    Word64
result <- Ptr DiffBinaryFile -> IO Word64
ggit_diff_binary_file_get_inflated_size Ptr DiffBinaryFile
file'
    DiffBinaryFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DiffBinaryFile
file
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data DiffBinaryFileGetInflatedSizeMethodInfo
instance (signature ~ (m Word64), MonadIO m) => O.MethodInfo DiffBinaryFileGetInflatedSizeMethodInfo DiffBinaryFile signature where
    overloadedMethod = diffBinaryFileGetInflatedSize

#endif

-- method DiffBinaryFile::ref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "file"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "DiffBinaryFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiff." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Ggit" , name = "DiffBinaryFile" })
-- throws : False
-- Skip return : False

foreign import ccall "ggit_diff_binary_file_ref" ggit_diff_binary_file_ref :: 
    Ptr DiffBinaryFile ->                   -- file : TInterface (Name {namespace = "Ggit", name = "DiffBinaryFile"})
    IO (Ptr DiffBinaryFile)

-- | Atomically increments the reference count of /@file@/ by one.
-- This function is MT-safe and may be called from any thread.
diffBinaryFileRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DiffBinaryFile
    -- ^ /@file@/: a t'GI.Ggit.Objects.Diff.Diff'.
    -> m DiffBinaryFile
    -- ^ __Returns:__ a t'GI.Ggit.Structs.DiffBinaryFile.DiffBinaryFile'.
diffBinaryFileRef :: DiffBinaryFile -> m DiffBinaryFile
diffBinaryFileRef DiffBinaryFile
file = IO DiffBinaryFile -> m DiffBinaryFile
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DiffBinaryFile -> m DiffBinaryFile)
-> IO DiffBinaryFile -> m DiffBinaryFile
forall a b. (a -> b) -> a -> b
$ do
    Ptr DiffBinaryFile
file' <- DiffBinaryFile -> IO (Ptr DiffBinaryFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DiffBinaryFile
file
    Ptr DiffBinaryFile
result <- Ptr DiffBinaryFile -> IO (Ptr DiffBinaryFile)
ggit_diff_binary_file_ref Ptr DiffBinaryFile
file'
    Text -> Ptr DiffBinaryFile -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"diffBinaryFileRef" Ptr DiffBinaryFile
result
    DiffBinaryFile
result' <- ((ManagedPtr DiffBinaryFile -> DiffBinaryFile)
-> Ptr DiffBinaryFile -> IO DiffBinaryFile
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr DiffBinaryFile -> DiffBinaryFile
DiffBinaryFile) Ptr DiffBinaryFile
result
    DiffBinaryFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DiffBinaryFile
file
    DiffBinaryFile -> IO DiffBinaryFile
forall (m :: * -> *) a. Monad m => a -> m a
return DiffBinaryFile
result'

#if defined(ENABLE_OVERLOADING)
data DiffBinaryFileRefMethodInfo
instance (signature ~ (m DiffBinaryFile), MonadIO m) => O.MethodInfo DiffBinaryFileRefMethodInfo DiffBinaryFile signature where
    overloadedMethod = diffBinaryFileRef

#endif

-- method DiffBinaryFile::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "file"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "DiffBinaryFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiffBinaryFile."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_diff_binary_file_unref" ggit_diff_binary_file_unref :: 
    Ptr DiffBinaryFile ->                   -- file : TInterface (Name {namespace = "Ggit", name = "DiffBinaryFile"})
    IO ()

-- | Atomically decrements the reference count of /@file@/ by one.
-- If the reference count drops to 0, /@file@/ is freed.
diffBinaryFileUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    DiffBinaryFile
    -- ^ /@file@/: a t'GI.Ggit.Structs.DiffBinaryFile.DiffBinaryFile'.
    -> m ()
diffBinaryFileUnref :: DiffBinaryFile -> m ()
diffBinaryFileUnref DiffBinaryFile
file = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DiffBinaryFile
file' <- DiffBinaryFile -> IO (Ptr DiffBinaryFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DiffBinaryFile
file
    Ptr DiffBinaryFile -> IO ()
ggit_diff_binary_file_unref Ptr DiffBinaryFile
file'
    DiffBinaryFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DiffBinaryFile
file
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DiffBinaryFileUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo DiffBinaryFileUnrefMethodInfo DiffBinaryFile signature where
    overloadedMethod = diffBinaryFileUnref

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveDiffBinaryFileMethod (t :: Symbol) (o :: *) :: * where
    ResolveDiffBinaryFileMethod "ref" o = DiffBinaryFileRefMethodInfo
    ResolveDiffBinaryFileMethod "unref" o = DiffBinaryFileUnrefMethodInfo
    ResolveDiffBinaryFileMethod "getBinaryType" o = DiffBinaryFileGetBinaryTypeMethodInfo
    ResolveDiffBinaryFileMethod "getData" o = DiffBinaryFileGetDataMethodInfo
    ResolveDiffBinaryFileMethod "getInflatedSize" o = DiffBinaryFileGetInflatedSizeMethodInfo
    ResolveDiffBinaryFileMethod l o = O.MethodResolutionFailed l o

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

#endif