{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)

An opaque structure representing a checksumming operation.
To create a new GChecksum, use g_checksum_new(). To free
a GChecksum, use g_checksum_free().
-}

module GI.GLib.Structs.Checksum
    ( 

-- * Exported types
    Checksum(..)                            ,
    noChecksum                              ,


 -- * Methods
-- ** checksumCopy
    checksumCopy                            ,


-- ** checksumFree
    checksumFree                            ,


-- ** checksumGetString
    checksumGetString                       ,


-- ** checksumNew
    checksumNew                             ,


-- ** checksumReset
    checksumReset                           ,


-- ** checksumUpdate
    checksumUpdate                          ,




    ) 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.GLib.Types
import GI.GLib.Callbacks

newtype Checksum = Checksum (ForeignPtr Checksum)
foreign import ccall "g_checksum_get_type" c_g_checksum_get_type :: 
    IO GType

instance BoxedObject Checksum where
    boxedType _ = c_g_checksum_get_type

noChecksum :: Maybe Checksum
noChecksum = Nothing

-- method Checksum::new
-- method type : Constructor
-- Args : [Arg {argName = "checksum_type", argType = TInterface "GLib" "ChecksumType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "checksum_type", argType = TInterface "GLib" "ChecksumType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "Checksum"
-- throws : False
-- Skip return : False

foreign import ccall "g_checksum_new" g_checksum_new :: 
    CUInt ->                                -- checksum_type : TInterface "GLib" "ChecksumType"
    IO (Ptr Checksum)


checksumNew ::
    (MonadIO m) =>
    ChecksumType ->                         -- checksum_type
    m Checksum
checksumNew checksum_type = liftIO $ do
    let checksum_type' = (fromIntegral . fromEnum) checksum_type
    result <- g_checksum_new checksum_type'
    checkUnexpectedReturnNULL "g_checksum_new" result
    result' <- (wrapBoxed Checksum) result
    return result'

-- method Checksum::copy
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Checksum", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Checksum", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "Checksum"
-- throws : False
-- Skip return : False

foreign import ccall "g_checksum_copy" g_checksum_copy :: 
    Ptr Checksum ->                         -- _obj : TInterface "GLib" "Checksum"
    IO (Ptr Checksum)


checksumCopy ::
    (MonadIO m) =>
    Checksum ->                             -- _obj
    m Checksum
checksumCopy _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_checksum_copy _obj'
    checkUnexpectedReturnNULL "g_checksum_copy" result
    result' <- (wrapBoxed Checksum) result
    touchManagedPtr _obj
    return result'

-- method Checksum::free
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Checksum", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Checksum", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_checksum_free" g_checksum_free :: 
    Ptr Checksum ->                         -- _obj : TInterface "GLib" "Checksum"
    IO ()


checksumFree ::
    (MonadIO m) =>
    Checksum ->                             -- _obj
    m ()
checksumFree _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    g_checksum_free _obj'
    touchManagedPtr _obj
    return ()

-- method Checksum::get_string
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Checksum", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Checksum", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_checksum_get_string" g_checksum_get_string :: 
    Ptr Checksum ->                         -- _obj : TInterface "GLib" "Checksum"
    IO CString


checksumGetString ::
    (MonadIO m) =>
    Checksum ->                             -- _obj
    m T.Text
checksumGetString _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_checksum_get_string _obj'
    checkUnexpectedReturnNULL "g_checksum_get_string" result
    result' <- cstringToText result
    touchManagedPtr _obj
    return result'

-- method Checksum::reset
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Checksum", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Checksum", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_checksum_reset" g_checksum_reset :: 
    Ptr Checksum ->                         -- _obj : TInterface "GLib" "Checksum"
    IO ()


checksumReset ::
    (MonadIO m) =>
    Checksum ->                             -- _obj
    m ()
checksumReset _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    g_checksum_reset _obj'
    touchManagedPtr _obj
    return ()

-- method Checksum::update
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Checksum", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Checksum", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_checksum_update" g_checksum_update :: 
    Ptr Checksum ->                         -- _obj : TInterface "GLib" "Checksum"
    Ptr Word8 ->                            -- data : TCArray False (-1) 2 (TBasicType TUInt8)
    Int64 ->                                -- length : TBasicType TInt64
    IO ()


checksumUpdate ::
    (MonadIO m) =>
    Checksum ->                             -- _obj
    ByteString ->                           -- data
    m ()
checksumUpdate _obj data_ = liftIO $ do
    let length_ = fromIntegral $ B.length data_
    let _obj' = unsafeManagedPtrGetPtr _obj
    data_' <- packByteString data_
    g_checksum_update _obj' data_' length_
    touchManagedPtr _obj
    freeMem data_'
    return ()