{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Represents a blob object.

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

module GI.Ggit.Objects.Blob
    ( 

-- * Exported types
    Blob(..)                                ,
    IsBlob                                  ,
    toBlob                                  ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isBinary]("GI.Ggit.Objects.Blob#g:method:isBinary"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getId]("GI.Ggit.Objects.Object#g:method:getId"), [getOwner]("GI.Ggit.Objects.Object#g:method:getOwner"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRawContent]("GI.Ggit.Objects.Blob#g:method:getRawContent").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveBlobMethod                       ,
#endif

-- ** getRawContent #method:getRawContent#

#if defined(ENABLE_OVERLOADING)
    BlobGetRawContentMethodInfo             ,
#endif
    blobGetRawContent                       ,


-- ** isBinary #method:isBinary#

#if defined(ENABLE_OVERLOADING)
    BlobIsBinaryMethodInfo                  ,
#endif
    blobIsBinary                            ,




    ) 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.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

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Ggit.Objects.Native as Ggit.Native
import {-# SOURCE #-} qualified GI.Ggit.Objects.Object as Ggit.Object
import {-# SOURCE #-} qualified GI.Ggit.Objects.ObjectFactoryBase as Ggit.ObjectFactoryBase

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

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

foreign import ccall "ggit_blob_get_type"
    c_ggit_blob_get_type :: IO B.Types.GType

instance B.Types.TypedObject Blob where
    glibType :: IO GType
glibType = IO GType
c_ggit_blob_get_type

instance B.Types.GObject Blob

-- | Type class for types which can be safely cast to `Blob`, for instance with `toBlob`.
class (SP.GObject o, O.IsDescendantOf Blob o) => IsBlob o
instance (SP.GObject o, O.IsDescendantOf Blob o) => IsBlob o

instance O.HasParentTypes Blob
type instance O.ParentTypes Blob = '[Ggit.Object.Object, Ggit.Native.Native, Ggit.ObjectFactoryBase.ObjectFactoryBase, GObject.Object.Object]

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

-- | Convert 'Blob' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Blob) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ggit_blob_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Blob -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Blob
P.Nothing = Ptr GValue -> Ptr Blob -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Blob
forall a. Ptr a
FP.nullPtr :: FP.Ptr Blob)
    gvalueSet_ Ptr GValue
gv (P.Just Blob
obj) = Blob -> (Ptr Blob -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Blob
obj (Ptr GValue -> Ptr Blob -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Blob)
gvalueGet_ Ptr GValue
gv = do
        Ptr Blob
ptr <- Ptr GValue -> IO (Ptr Blob)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Blob)
        if Ptr Blob
ptr Ptr Blob -> Ptr Blob -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Blob
forall a. Ptr a
FP.nullPtr
        then Blob -> Maybe Blob
forall a. a -> Maybe a
P.Just (Blob -> Maybe Blob) -> IO Blob -> IO (Maybe Blob)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Blob -> Blob) -> Ptr Blob -> IO Blob
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Blob -> Blob
Blob Ptr Blob
ptr
        else Maybe Blob -> IO (Maybe Blob)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Blob
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveBlobMethod (t :: Symbol) (o :: *) :: * where
    ResolveBlobMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveBlobMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveBlobMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveBlobMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveBlobMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveBlobMethod "isBinary" o = BlobIsBinaryMethodInfo
    ResolveBlobMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveBlobMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveBlobMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveBlobMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveBlobMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveBlobMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveBlobMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveBlobMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveBlobMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveBlobMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveBlobMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveBlobMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveBlobMethod "getId" o = Ggit.Object.ObjectGetIdMethodInfo
    ResolveBlobMethod "getOwner" o = Ggit.Object.ObjectGetOwnerMethodInfo
    ResolveBlobMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveBlobMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveBlobMethod "getRawContent" o = BlobGetRawContentMethodInfo
    ResolveBlobMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveBlobMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveBlobMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveBlobMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveBlobMethod t Blob, O.OverloadedMethod info Blob p) => OL.IsLabel t (Blob -> 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 ~ ResolveBlobMethod t Blob, O.OverloadedMethod info Blob p, R.HasField t Blob p) => R.HasField t Blob p where
    getField = O.overloadedMethod @info

#endif

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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Blob
type instance O.AttributeList Blob = BlobAttributeList
type BlobAttributeList = ('[ '("native", Ggit.Native.NativeNativePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Blob = BlobSignalList
type BlobSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method Blob::get_raw_content
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "blob"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Blob" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitBlob." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return value of the length of the data."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TUInt64
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "return value of the length of the data."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 1 (TBasicType TUInt8))
-- throws : False
-- Skip return : False

foreign import ccall "ggit_blob_get_raw_content" ggit_blob_get_raw_content :: 
    Ptr Blob ->                             -- blob : TInterface (Name {namespace = "Ggit", name = "Blob"})
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    IO (Ptr Word8)

-- | Gets a read-only buffer with the raw contents of /@blob@/.
-- 
-- A pointer to the raw contents of /@blob@/ is returned.
-- This pointer is owned internally by /@object@/ and must
-- not be free\'d. The pointer may be invalidated at a later
-- time.
blobGetRawContent ::
    (B.CallStack.HasCallStack, MonadIO m, IsBlob a) =>
    a
    -- ^ /@blob@/: a t'GI.Ggit.Objects.Blob.Blob'.
    -> m (Maybe ByteString)
    -- ^ __Returns:__ the blob content or
    --          'P.Nothing' if the blob does not have any content.
blobGetRawContent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBlob a) =>
a -> m (Maybe ByteString)
blobGetRawContent a
blob = IO (Maybe ByteString) -> m (Maybe ByteString)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ByteString) -> m (Maybe ByteString))
-> IO (Maybe ByteString) -> m (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Blob
blob' <- a -> IO (Ptr Blob)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
blob
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    Ptr Word8
result <- Ptr Blob -> Ptr Word64 -> IO (Ptr Word8)
ggit_blob_get_raw_content Ptr Blob
blob' Ptr Word64
length_
    Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
    Maybe ByteString
maybeResult <- Ptr Word8 -> (Ptr Word8 -> IO ByteString) -> IO (Maybe ByteString)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Word8
result ((Ptr Word8 -> IO ByteString) -> IO (Maybe ByteString))
-> (Ptr Word8 -> IO ByteString) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
result' -> do
        ByteString
result'' <- (Word64 -> Ptr Word8 -> IO ByteString
forall a. Integral a => a -> Ptr Word8 -> IO ByteString
unpackByteStringWithLength Word64
length_') Ptr Word8
result'
        ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
blob
    Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
    Maybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
maybeResult

#if defined(ENABLE_OVERLOADING)
data BlobGetRawContentMethodInfo
instance (signature ~ (m (Maybe ByteString)), MonadIO m, IsBlob a) => O.OverloadedMethod BlobGetRawContentMethodInfo a signature where
    overloadedMethod = blobGetRawContent

instance O.OverloadedMethodInfo BlobGetRawContentMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.Blob.blobGetRawContent",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-Blob.html#v:blobGetRawContent"
        })


#endif

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

foreign import ccall "ggit_blob_is_binary" ggit_blob_is_binary :: 
    Ptr Blob ->                             -- blob : TInterface (Name {namespace = "Ggit", name = "Blob"})
    IO CInt

-- | Check whether the blob is binary.
blobIsBinary ::
    (B.CallStack.HasCallStack, MonadIO m, IsBlob a) =>
    a
    -- ^ /@blob@/: a t'GI.Ggit.Objects.Blob.Blob'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the blob is binary, 'P.False' otherwise.
blobIsBinary :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBlob a) =>
a -> m Bool
blobIsBinary a
blob = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Blob
blob' <- a -> IO (Ptr Blob)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
blob
    CInt
result <- Ptr Blob -> IO CInt
ggit_blob_is_binary Ptr Blob
blob'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
blob
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data BlobIsBinaryMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsBlob a) => O.OverloadedMethod BlobIsBinaryMethodInfo a signature where
    overloadedMethod = blobIsBinary

instance O.OverloadedMethodInfo BlobIsBinaryMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.Blob.blobIsBinary",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-Blob.html#v:blobIsBinary"
        })


#endif