{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GLib.Structs.Hmac
(
Hmac(..) ,
noHmac ,
#if defined(ENABLE_OVERLOADING)
ResolveHmacMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
HmacGetDigestMethodInfo ,
#endif
hmacGetDigest ,
#if defined(ENABLE_OVERLOADING)
HmacGetStringMethodInfo ,
#endif
hmacGetString ,
#if defined(ENABLE_OVERLOADING)
HmacUnrefMethodInfo ,
#endif
hmacUnref ,
#if defined(ENABLE_OVERLOADING)
HmacUpdateMethodInfo ,
#endif
hmacUpdate ,
) 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.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 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
newtype Hmac = Hmac (ManagedPtr Hmac)
deriving (Hmac -> Hmac -> Bool
(Hmac -> Hmac -> Bool) -> (Hmac -> Hmac -> Bool) -> Eq Hmac
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hmac -> Hmac -> Bool
$c/= :: Hmac -> Hmac -> Bool
== :: Hmac -> Hmac -> Bool
$c== :: Hmac -> Hmac -> Bool
Eq)
instance WrappedPtr Hmac where
wrappedPtrCalloc :: IO (Ptr Hmac)
wrappedPtrCalloc = Ptr Hmac -> IO (Ptr Hmac)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Hmac
forall a. Ptr a
nullPtr
wrappedPtrCopy :: Hmac -> IO Hmac
wrappedPtrCopy = Hmac -> IO Hmac
forall (m :: * -> *) a. Monad m => a -> m a
return
wrappedPtrFree :: Maybe (GDestroyNotify Hmac)
wrappedPtrFree = Maybe (GDestroyNotify Hmac)
forall a. Maybe a
Nothing
noHmac :: Maybe Hmac
noHmac :: Maybe Hmac
noHmac = Maybe Hmac
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Hmac
type instance O.AttributeList Hmac = HmacAttributeList
type HmacAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "g_hmac_get_digest" g_hmac_get_digest ::
Ptr Hmac ->
Ptr Word8 ->
Ptr Word64 ->
IO ()
hmacGetDigest ::
(B.CallStack.HasCallStack, MonadIO m) =>
Hmac
-> ByteString
-> m ()
hmacGetDigest :: Hmac -> ByteString -> m ()
hmacGetDigest hmac :: Hmac
hmac buffer :: ByteString
buffer = 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 digestLen :: Word64
digestLen = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
buffer
Ptr Hmac
hmac' <- Hmac -> IO (Ptr Hmac)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Hmac
hmac
Ptr Word8
buffer' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
buffer
Ptr Word64
digestLen' <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word64
digestLen' Word64
digestLen
Ptr Hmac -> Ptr Word8 -> Ptr Word64 -> IO ()
g_hmac_get_digest Ptr Hmac
hmac' Ptr Word8
buffer' Ptr Word64
digestLen'
Word64
digestLen'' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
digestLen'
Hmac -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Hmac
hmac
Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
buffer'
Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
digestLen'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data HmacGetDigestMethodInfo
instance (signature ~ (ByteString -> m ()), MonadIO m) => O.MethodInfo HmacGetDigestMethodInfo Hmac signature where
overloadedMethod = hmacGetDigest
#endif
foreign import ccall "g_hmac_get_string" g_hmac_get_string ::
Ptr Hmac ->
IO CString
hmacGetString ::
(B.CallStack.HasCallStack, MonadIO m) =>
Hmac
-> m T.Text
hmacGetString :: Hmac -> m Text
hmacGetString hmac :: Hmac
hmac = 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 Hmac
hmac' <- Hmac -> IO (Ptr Hmac)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Hmac
hmac
CString
result <- Ptr Hmac -> IO CString
g_hmac_get_string Ptr Hmac
hmac'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "hmacGetString" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
Hmac -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Hmac
hmac
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data HmacGetStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo HmacGetStringMethodInfo Hmac signature where
overloadedMethod = hmacGetString
#endif
foreign import ccall "g_hmac_unref" g_hmac_unref ::
Ptr Hmac ->
IO ()
hmacUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
Hmac
-> m ()
hmacUnref :: Hmac -> m ()
hmacUnref hmac :: Hmac
hmac = 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 Hmac
hmac' <- Hmac -> IO (Ptr Hmac)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Hmac
hmac
Ptr Hmac -> IO ()
g_hmac_unref Ptr Hmac
hmac'
Hmac -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Hmac
hmac
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data HmacUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo HmacUnrefMethodInfo Hmac signature where
overloadedMethod = hmacUnref
#endif
foreign import ccall "g_hmac_update" g_hmac_update ::
Ptr Hmac ->
Ptr Word8 ->
Int64 ->
IO ()
hmacUpdate ::
(B.CallStack.HasCallStack, MonadIO m) =>
Hmac
-> ByteString
-> m ()
hmacUpdate :: Hmac -> ByteString -> m ()
hmacUpdate hmac :: Hmac
hmac data_ :: 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 Hmac
hmac' <- Hmac -> IO (Ptr Hmac)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Hmac
hmac
Ptr Word8
data_' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
data_
Ptr Hmac -> Ptr Word8 -> Int64 -> IO ()
g_hmac_update Ptr Hmac
hmac' Ptr Word8
data_' Int64
length_
Hmac -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Hmac
hmac
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 HmacUpdateMethodInfo
instance (signature ~ (ByteString -> m ()), MonadIO m) => O.MethodInfo HmacUpdateMethodInfo Hmac signature where
overloadedMethod = hmacUpdate
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveHmacMethod (t :: Symbol) (o :: *) :: * where
ResolveHmacMethod "unref" o = HmacUnrefMethodInfo
ResolveHmacMethod "update" o = HmacUpdateMethodInfo
ResolveHmacMethod "getDigest" o = HmacGetDigestMethodInfo
ResolveHmacMethod "getString" o = HmacGetStringMethodInfo
ResolveHmacMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveHmacMethod t Hmac, O.MethodInfo info Hmac p) => OL.IsLabel t (Hmac -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif