{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An opaque structure representing a checksumming operation.
-- 
-- To create a new GChecksum, use 'GI.GLib.Structs.Checksum.checksumNew'. To free
-- a GChecksum, use 'GI.GLib.Structs.Checksum.checksumFree'.
-- 
-- /Since: 2.16/

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

module GI.GLib.Structs.Checksum
    ( 

-- * Exported types
    Checksum(..)                            ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [copy]("GI.GLib.Structs.Checksum#g:method:copy"), [free]("GI.GLib.Structs.Checksum#g:method:free"), [reset]("GI.GLib.Structs.Checksum#g:method:reset"), [update]("GI.GLib.Structs.Checksum#g:method:update").
-- 
-- ==== Getters
-- [getString]("GI.GLib.Structs.Checksum#g:method:getString").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveChecksumMethod                   ,
#endif

-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    ChecksumCopyMethodInfo                  ,
#endif
    checksumCopy                            ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    ChecksumFreeMethodInfo                  ,
#endif
    checksumFree                            ,


-- ** getString #method:getString#

#if defined(ENABLE_OVERLOADING)
    ChecksumGetStringMethodInfo             ,
#endif
    checksumGetString                       ,


-- ** new #method:new#

    checksumNew                             ,


-- ** reset #method:reset#

#if defined(ENABLE_OVERLOADING)
    ChecksumResetMethodInfo                 ,
#endif
    checksumReset                           ,


-- ** typeGetLength #method:typeGetLength#

    checksumTypeGetLength                   ,


-- ** update #method:update#

#if defined(ENABLE_OVERLOADING)
    ChecksumUpdateMethodInfo                ,
#endif
    checksumUpdate                          ,




    ) 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.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 {-# SOURCE #-} qualified GI.GLib.Enums as GLib.Enums

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

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

foreign import ccall "g_checksum_get_type" c_g_checksum_get_type :: 
    IO GType

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

instance B.Types.TypedObject Checksum where
    glibType :: IO GType
glibType = IO GType
c_g_checksum_get_type

instance B.Types.GBoxed Checksum

-- | Convert 'Checksum' 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 Checksum) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_checksum_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Checksum -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Checksum
P.Nothing = Ptr GValue -> Ptr Checksum -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Checksum
forall a. Ptr a
FP.nullPtr :: FP.Ptr Checksum)
    gvalueSet_ Ptr GValue
gv (P.Just Checksum
obj) = Checksum -> (Ptr Checksum -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Checksum
obj (Ptr GValue -> Ptr Checksum -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Checksum)
gvalueGet_ Ptr GValue
gv = do
        Ptr Checksum
ptr <- Ptr GValue -> IO (Ptr Checksum)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Checksum)
        if Ptr Checksum
ptr Ptr Checksum -> Ptr Checksum -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Checksum
forall a. Ptr a
FP.nullPtr
        then Checksum -> Maybe Checksum
forall a. a -> Maybe a
P.Just (Checksum -> Maybe Checksum) -> IO Checksum -> IO (Maybe Checksum)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Checksum -> Checksum) -> Ptr Checksum -> IO Checksum
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Checksum -> Checksum
Checksum Ptr Checksum
ptr
        else Maybe Checksum -> IO (Maybe Checksum)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Checksum
forall a. Maybe a
P.Nothing
        
    


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

-- method Checksum::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "checksum_type"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "ChecksumType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the desired type of checksum"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Checksum" })
-- throws : False
-- Skip return : False

foreign import ccall "g_checksum_new" g_checksum_new :: 
    CUInt ->                                -- checksum_type : TInterface (Name {namespace = "GLib", name = "ChecksumType"})
    IO (Ptr Checksum)

-- | Creates a new t'GI.GLib.Structs.Checksum.Checksum', using the checksum algorithm /@checksumType@/.
-- If the /@checksumType@/ is not known, 'P.Nothing' is returned.
-- A t'GI.GLib.Structs.Checksum.Checksum' can be used to compute the checksum, or digest, of an
-- arbitrary binary blob, using different hashing algorithms.
-- 
-- A t'GI.GLib.Structs.Checksum.Checksum' works by feeding a binary blob through 'GI.GLib.Structs.Checksum.checksumUpdate'
-- until there is data to be checked; the digest can then be extracted
-- using 'GI.GLib.Structs.Checksum.checksumGetString', which will return the checksum as a
-- hexadecimal string; or @/g_checksum_get_digest()/@, which will return a
-- vector of raw bytes. Once either 'GI.GLib.Structs.Checksum.checksumGetString' or
-- @/g_checksum_get_digest()/@ have been called on a t'GI.GLib.Structs.Checksum.Checksum', the checksum
-- will be closed and it won\'t be possible to call 'GI.GLib.Structs.Checksum.checksumUpdate'
-- on it anymore.
-- 
-- /Since: 2.16/
checksumNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.Enums.ChecksumType
    -- ^ /@checksumType@/: the desired type of checksum
    -> m (Maybe Checksum)
    -- ^ __Returns:__ the newly created t'GI.GLib.Structs.Checksum.Checksum', or 'P.Nothing'.
    --   Use 'GI.GLib.Structs.Checksum.checksumFree' to free the memory allocated by it.
checksumNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ChecksumType -> m (Maybe Checksum)
checksumNew ChecksumType
checksumType = IO (Maybe Checksum) -> m (Maybe Checksum)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Checksum) -> m (Maybe Checksum))
-> IO (Maybe Checksum) -> m (Maybe Checksum)
forall a b. (a -> b) -> a -> b
$ do
    let checksumType' :: CUInt
checksumType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (ChecksumType -> Int) -> ChecksumType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ChecksumType -> Int
forall a. Enum a => a -> Int
fromEnum) ChecksumType
checksumType
    Ptr Checksum
result <- CUInt -> IO (Ptr Checksum)
g_checksum_new CUInt
checksumType'
    Maybe Checksum
maybeResult <- Ptr Checksum
-> (Ptr Checksum -> IO Checksum) -> IO (Maybe Checksum)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Checksum
result ((Ptr Checksum -> IO Checksum) -> IO (Maybe Checksum))
-> (Ptr Checksum -> IO Checksum) -> IO (Maybe Checksum)
forall a b. (a -> b) -> a -> b
$ \Ptr Checksum
result' -> do
        Checksum
result'' <- ((ManagedPtr Checksum -> Checksum) -> Ptr Checksum -> IO Checksum
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Checksum -> Checksum
Checksum) Ptr Checksum
result'
        Checksum -> IO Checksum
forall (m :: * -> *) a. Monad m => a -> m a
return Checksum
result''
    Maybe Checksum -> IO (Maybe Checksum)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Checksum
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method Checksum::copy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "checksum"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "Checksum" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GChecksum to copy"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Checksum" })
-- throws : False
-- Skip return : False

foreign import ccall "g_checksum_copy" g_checksum_copy :: 
    Ptr Checksum ->                         -- checksum : TInterface (Name {namespace = "GLib", name = "Checksum"})
    IO (Ptr Checksum)

-- | Copies a t'GI.GLib.Structs.Checksum.Checksum'. If /@checksum@/ has been closed, by calling
-- 'GI.GLib.Structs.Checksum.checksumGetString' or @/g_checksum_get_digest()/@, the copied
-- checksum will be closed as well.
-- 
-- /Since: 2.16/
checksumCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Checksum
    -- ^ /@checksum@/: the t'GI.GLib.Structs.Checksum.Checksum' to copy
    -> m Checksum
    -- ^ __Returns:__ the copy of the passed t'GI.GLib.Structs.Checksum.Checksum'. Use
    --   'GI.GLib.Structs.Checksum.checksumFree' when finished using it.
checksumCopy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Checksum -> m Checksum
checksumCopy Checksum
checksum = IO Checksum -> m Checksum
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Checksum -> m Checksum) -> IO Checksum -> m Checksum
forall a b. (a -> b) -> a -> b
$ do
    Ptr Checksum
checksum' <- Checksum -> IO (Ptr Checksum)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Checksum
checksum
    Ptr Checksum
result <- Ptr Checksum -> IO (Ptr Checksum)
g_checksum_copy Ptr Checksum
checksum'
    Text -> Ptr Checksum -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"checksumCopy" Ptr Checksum
result
    Checksum
result' <- ((ManagedPtr Checksum -> Checksum) -> Ptr Checksum -> IO Checksum
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Checksum -> Checksum
Checksum) Ptr Checksum
result
    Checksum -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Checksum
checksum
    Checksum -> IO Checksum
forall (m :: * -> *) a. Monad m => a -> m a
return Checksum
result'

#if defined(ENABLE_OVERLOADING)
data ChecksumCopyMethodInfo
instance (signature ~ (m Checksum), MonadIO m) => O.OverloadedMethod ChecksumCopyMethodInfo Checksum signature where
    overloadedMethod = checksumCopy

instance O.OverloadedMethodInfo ChecksumCopyMethodInfo Checksum where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Checksum.checksumCopy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Checksum.html#v:checksumCopy"
        })


#endif

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

foreign import ccall "g_checksum_free" g_checksum_free :: 
    Ptr Checksum ->                         -- checksum : TInterface (Name {namespace = "GLib", name = "Checksum"})
    IO ()

-- | Frees the memory allocated for /@checksum@/.
-- 
-- /Since: 2.16/
checksumFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Checksum
    -- ^ /@checksum@/: a t'GI.GLib.Structs.Checksum.Checksum'
    -> m ()
checksumFree :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Checksum -> m ()
checksumFree Checksum
checksum = 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 Checksum
checksum' <- Checksum -> IO (Ptr Checksum)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Checksum
checksum
    Ptr Checksum -> IO ()
g_checksum_free Ptr Checksum
checksum'
    Checksum -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Checksum
checksum
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ChecksumFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod ChecksumFreeMethodInfo Checksum signature where
    overloadedMethod = checksumFree

instance O.OverloadedMethodInfo ChecksumFreeMethodInfo Checksum where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Checksum.checksumFree",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Checksum.html#v:checksumFree"
        })


#endif

-- method Checksum::get_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "checksum"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "Checksum" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GChecksum" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_checksum_get_string" g_checksum_get_string :: 
    Ptr Checksum ->                         -- checksum : TInterface (Name {namespace = "GLib", name = "Checksum"})
    IO CString

-- | Gets the digest as a hexadecimal string.
-- 
-- Once this function has been called the t'GI.GLib.Structs.Checksum.Checksum' can no longer be
-- updated with 'GI.GLib.Structs.Checksum.checksumUpdate'.
-- 
-- The hexadecimal characters will be lower case.
-- 
-- /Since: 2.16/
checksumGetString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Checksum
    -- ^ /@checksum@/: a t'GI.GLib.Structs.Checksum.Checksum'
    -> m T.Text
    -- ^ __Returns:__ the hexadecimal representation of the checksum. The
    --   returned string is owned by the checksum and should not be modified
    --   or freed.
checksumGetString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Checksum -> m Text
checksumGetString Checksum
checksum = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Checksum
checksum' <- Checksum -> IO (Ptr Checksum)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Checksum
checksum
    CString
result <- Ptr Checksum -> IO CString
g_checksum_get_string Ptr Checksum
checksum'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"checksumGetString" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    Checksum -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Checksum
checksum
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ChecksumGetStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod ChecksumGetStringMethodInfo Checksum signature where
    overloadedMethod = checksumGetString

instance O.OverloadedMethodInfo ChecksumGetStringMethodInfo Checksum where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Checksum.checksumGetString",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Checksum.html#v:checksumGetString"
        })


#endif

-- method Checksum::reset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "checksum"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "Checksum" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GChecksum to reset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_checksum_reset" g_checksum_reset :: 
    Ptr Checksum ->                         -- checksum : TInterface (Name {namespace = "GLib", name = "Checksum"})
    IO ()

-- | Resets the state of the /@checksum@/ back to its initial state.
-- 
-- /Since: 2.18/
checksumReset ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Checksum
    -- ^ /@checksum@/: the t'GI.GLib.Structs.Checksum.Checksum' to reset
    -> m ()
checksumReset :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Checksum -> m ()
checksumReset Checksum
checksum = 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 Checksum
checksum' <- Checksum -> IO (Ptr Checksum)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Checksum
checksum
    Ptr Checksum -> IO ()
g_checksum_reset Ptr Checksum
checksum'
    Checksum -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Checksum
checksum
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ChecksumResetMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod ChecksumResetMethodInfo Checksum signature where
    overloadedMethod = checksumReset

instance O.OverloadedMethodInfo ChecksumResetMethodInfo Checksum where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Checksum.checksumReset",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Checksum.html#v:checksumReset"
        })


#endif

-- method Checksum::update
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "checksum"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "Checksum" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GChecksum" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TCArray False (-1) 2 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "buffer used to compute the checksum"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "size of the buffer, or -1 if it is a null-terminated string."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "size of the buffer, or -1 if it is a null-terminated string."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_checksum_update" g_checksum_update :: 
    Ptr Checksum ->                         -- checksum : TInterface (Name {namespace = "GLib", name = "Checksum"})
    Ptr Word8 ->                            -- data : TCArray False (-1) 2 (TBasicType TUInt8)
    Int64 ->                                -- length : TBasicType TInt64
    IO ()

-- | Feeds /@data@/ into an existing t'GI.GLib.Structs.Checksum.Checksum'. The checksum must still be
-- open, that is 'GI.GLib.Structs.Checksum.checksumGetString' or @/g_checksum_get_digest()/@ must
-- not have been called on /@checksum@/.
-- 
-- /Since: 2.16/
checksumUpdate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Checksum
    -- ^ /@checksum@/: a t'GI.GLib.Structs.Checksum.Checksum'
    -> ByteString
    -- ^ /@data@/: buffer used to compute the checksum
    -> m ()
checksumUpdate :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Checksum -> ByteString -> m ()
checksumUpdate Checksum
checksum ByteString
data_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    let length_ :: Int64
length_ = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int64) -> Int -> Int64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
data_
    Ptr Checksum
checksum' <- Checksum -> IO (Ptr Checksum)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Checksum
checksum
    Ptr Word8
data_' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
data_
    Ptr Checksum -> Ptr Word8 -> Int64 -> IO ()
g_checksum_update Ptr Checksum
checksum' Ptr Word8
data_' Int64
length_
    Checksum -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Checksum
checksum
    Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
data_'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ChecksumUpdateMethodInfo
instance (signature ~ (ByteString -> m ()), MonadIO m) => O.OverloadedMethod ChecksumUpdateMethodInfo Checksum signature where
    overloadedMethod = checksumUpdate

instance O.OverloadedMethodInfo ChecksumUpdateMethodInfo Checksum where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Checksum.checksumUpdate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-Checksum.html#v:checksumUpdate"
        })


#endif

-- method Checksum::type_get_length
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "checksum_type"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "ChecksumType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GChecksumType" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt64)
-- throws : False
-- Skip return : False

foreign import ccall "g_checksum_type_get_length" g_checksum_type_get_length :: 
    CUInt ->                                -- checksum_type : TInterface (Name {namespace = "GLib", name = "ChecksumType"})
    IO Int64

-- | Gets the length in bytes of digests of type /@checksumType@/
-- 
-- /Since: 2.16/
checksumTypeGetLength ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.Enums.ChecksumType
    -- ^ /@checksumType@/: a t'GI.GLib.Enums.ChecksumType'
    -> m Int64
    -- ^ __Returns:__ the checksum length, or -1 if /@checksumType@/ is
    -- not supported.
checksumTypeGetLength :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ChecksumType -> m Int64
checksumTypeGetLength ChecksumType
checksumType = IO Int64 -> m Int64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
    let checksumType' :: CUInt
checksumType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (ChecksumType -> Int) -> ChecksumType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ChecksumType -> Int
forall a. Enum a => a -> Int
fromEnum) ChecksumType
checksumType
    Int64
result <- CUInt -> IO Int64
g_checksum_type_get_length CUInt
checksumType'
    Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveChecksumMethod (t :: Symbol) (o :: *) :: * where
    ResolveChecksumMethod "copy" o = ChecksumCopyMethodInfo
    ResolveChecksumMethod "free" o = ChecksumFreeMethodInfo
    ResolveChecksumMethod "reset" o = ChecksumResetMethodInfo
    ResolveChecksumMethod "update" o = ChecksumUpdateMethodInfo
    ResolveChecksumMethod "getString" o = ChecksumGetStringMethodInfo
    ResolveChecksumMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif