Copyright | (c) 2024 Auth Global |
---|---|
License | Apache2 |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- nullBuffer :: ByteString
- type MutableSha256State# = MutableByteArray#
- type Sha256State# = ByteArray#
- type MutableSha256Ctx# = MutableByteArray#
- type Sha256Ctx# = ByteArray#
- newtype Sha256State = Sha256State {}
- newtype Sha256Ctx = Sha256Ctx {}
- sha256state_init :: Sha256State
- sha256state_feed :: ByteString -> Sha256State -> Sha256State
- sha256state_fromCtxInplace :: Sha256Ctx -> Sha256State
- sha256state_fromCtx :: Sha256Ctx -> Sha256State
- sha256state_runWith :: Word64 -> ByteString -> Sha256State -> Sha256Ctx
- sha256state_encode :: Sha256State -> HashString
- sha256state_decode :: HashString -> Sha256State
- c_sha256_init :: Ptr Word32
- c_sha256_init_ctx :: MutableSha256Ctx# RealWorld -> IO ()
- c_sha256_promote_to_ctx :: Sha256State# -> Word64 -> CString -> CSize -> MutableSha256Ctx# RealWorld -> IO ()
- c_sha256_update :: Sha256State# -> CString -> CSize -> MutableSha256State# RealWorld -> IO Word64
- c_sha256_update_ctx :: Sha256Ctx# -> CString -> CSize -> MutableSha256Ctx# RealWorld -> IO ()
- c_sha256_mutate_ctx :: MutableSha256Ctx# RealWorld -> CString -> CSize -> MutableSha256Ctx# RealWorld -> IO ()
- c_sha256_get_count :: Sha256State# -> Word64
- c_sha256_finalize_ctx_bits :: Sha256Ctx# -> CString -> Word64 -> Ptr Word8 -> IO ()
- c_sha256_finalize_ctx_bits_ba :: Sha256Ctx# -> CString -> Word64 -> MutableByteArray# RealWorld -> IO ()
- c_sha256_finalize_mutable_ctx_bits :: MutableSha256Ctx# RealWorld -> CString -> Word64 -> CString -> IO ()
- c_sha256_encode_state :: Sha256State# -> MutableByteArray# RealWorld -> IO ()
- c_sha256_decode_state :: ByteArray# -> MutableSha256State# RealWorld -> IO ()
- c_const_memcmp_uint32be :: ByteArray# -> ByteArray# -> Word32 -> CInt
- c_const_memcmp_ctx :: ByteArray# -> ByteArray# -> CInt
Documentation
type Sha256State# = ByteArray# Source #
type Sha256Ctx# = ByteArray# Source #
newtype Sha256State Source #
Instances
Eq Sha256State Source # | |
Defined in Crypto.Sha256.Subtle (==) :: Sha256State -> Sha256State -> Bool # (/=) :: Sha256State -> Sha256State -> Bool # | |
Ord Sha256State Source # | |
Defined in Crypto.Sha256.Subtle compare :: Sha256State -> Sha256State -> Ordering # (<) :: Sha256State -> Sha256State -> Bool # (<=) :: Sha256State -> Sha256State -> Bool # (>) :: Sha256State -> Sha256State -> Bool # (>=) :: Sha256State -> Sha256State -> Bool # max :: Sha256State -> Sha256State -> Sha256State # min :: Sha256State -> Sha256State -> Sha256State # |
sha256state_feed :: ByteString -> Sha256State -> Sha256State Source #
Note that this function only processes as many 64-byte blocks as possible, then discards the remainder of the input. Also note that this function does nothing to track the number of bytes that have been fed into the state, which will have to be done externally.
sha256state_fromCtxInplace :: Sha256Ctx -> Sha256State Source #
Cast a Sha256Ctx to a Sha256State, without (much, if any) copying. This has the disadvantage that the result will retain at least 8, and up to 71 unnecessary bytes, depending on the length of the buffer. 72 extra bytes will likely be possible once this binding supports mutable contexts and supports freezing mutable contexts into immutable contexts without copying.
sha256state_fromCtx :: Sha256Ctx -> Sha256State Source #
Cast a Sha256Ctx to a Sha256State. This copies the first 32 bytes of the Sha256Ctx structure, so the result is always as small as possible.
sha256state_runWith :: Word64 -> ByteString -> Sha256State -> Sha256Ctx Source #
c_sha256_init_ctx :: MutableSha256Ctx# RealWorld -> IO () Source #
c_sha256_promote_to_ctx Source #
:: Sha256State# |
|
-> Word64 |
|
-> CString | pointer to the constant data to process |
-> CSize | length of the data to process |
-> MutableSha256Ctx# RealWorld | output pointer |
-> IO () |
:: Sha256State# |
|
-> CString | pointer to the constant data to process |
-> CSize | length of the data to process |
-> MutableSha256State# RealWorld | output pointer |
-> IO Word64 | the new |
:: Sha256Ctx# |
|
-> CString | pointer to the constant data to process |
-> CSize | length of the data to process |
-> MutableSha256Ctx# RealWorld | output pointer |
-> IO () |
:: MutableSha256Ctx# RealWorld |
|
-> CString | pointer to the constant data to process |
-> CSize | length of the data to process |
-> MutableSha256Ctx# RealWorld | output pointer, can be same as the input context |
-> IO () |
c_sha256_finalize_ctx_bits :: Sha256Ctx# -> CString -> Word64 -> Ptr Word8 -> IO () Source #
c_sha256_finalize_ctx_bits_ba :: Sha256Ctx# -> CString -> Word64 -> MutableByteArray# RealWorld -> IO () Source #
c_sha256_finalize_mutable_ctx_bits :: MutableSha256Ctx# RealWorld -> CString -> Word64 -> CString -> IO () Source #
c_sha256_encode_state :: Sha256State# -> MutableByteArray# RealWorld -> IO () Source #
c_sha256_decode_state :: ByteArray# -> MutableSha256State# RealWorld -> IO () Source #
c_const_memcmp_uint32be :: ByteArray# -> ByteArray# -> Word32 -> CInt Source #
c_const_memcmp_ctx :: ByteArray# -> ByteArray# -> CInt Source #