Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- compare :: ByteString -> ByteString -> Bool
- randomByteString :: Int -> IO ByteString
- bin2hex :: ByteString -> String
- safeSubtract :: (Ord a, Num a) => a -> a -> Maybe a
- cycleSucc :: (Bounded a, Enum a, Eq a) => a -> (Bool, a)
- nudgeBS :: ByteString -> ByteString
- orbit :: Eq a => (a -> a) -> a -> [a]
- pad :: Int -> ByteString -> ByteString
- unpad :: Int -> ByteString -> ByteString
- handleErrno :: CInt -> a -> Either String a
- unsafeDidSucceed :: IO CInt -> Bool
- withCStrings :: [String] -> ([CString] -> IO a) -> IO a
- withCStringLens :: [String] -> ([CStringLen] -> IO a) -> IO a
- constByteStrings :: [ByteString] -> ([CStringLen] -> IO b) -> IO b
- buildUnsafeByteString' :: Int -> (Ptr CChar -> IO b) -> IO (b, ByteString)
- buildUnsafeVariableByteString' :: Int -> (Ptr CChar -> IO b) -> IO (b, ByteString)
- buildUnsafeVariableByteString :: Int -> (Ptr CChar -> IO b) -> (b, ByteString)
- buildUnsafeByteString :: Int -> (Ptr CChar -> IO b) -> (b, ByteString)
- c_randombytes_buf :: Ptr CChar -> CInt -> IO ()
- hush :: Either s a -> Maybe a
- c_sodium_memcmp :: Ptr CChar -> Ptr CChar -> CInt -> IO CInt
- c_sodium_malloc :: CSize -> IO (Ptr a)
- c_sodium_free :: Ptr Word8 -> IO ()
- buildUnsafeScrubbedByteString' :: Int -> (Ptr CChar -> IO b) -> IO (b, ByteString)
- buildUnsafeScrubbedByteString :: Int -> (Ptr CChar -> IO b) -> (b, ByteString)
- c_sodium_bin2hex :: Ptr CChar -> CInt -> Ptr CChar -> CInt -> IO (Ptr CChar)
- uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
- uncurry5 :: (a -> b -> c -> d -> e -> f) -> (a, b, c, d, e) -> f
- (!&&!) :: Bool -> Bool -> Bool
- (!||!) :: Bool -> Bool -> Bool
- withCString :: String -> (CString -> IO a) -> IO a
- allocaBytes :: Int -> (Ptr a -> IO b) -> IO b
Documentation
compare :: ByteString -> ByteString -> Bool Source #
Constant-time comparison
randomByteString :: Int -> IO ByteString Source #
Build a sized random ByteString
using Sodium's bindings to
devurandom
.
bin2hex :: ByteString -> String Source #
safeSubtract :: (Ord a, Num a) => a -> a -> Maybe a Source #
Returns Nothing
if the subtraction would result in an
underflow or a negative number.
nudgeBS :: ByteString -> ByteString Source #
Treats a ByteString
as a little endian bitstring and increments
it.
orbit :: Eq a => (a -> a) -> a -> [a] Source #
Computes the orbit of a endomorphism... in a very brute force manner. Exists just for the below property.
length . orbit nudgeBS . S.pack . replicate 0 == (256^)
pad :: Int -> ByteString -> ByteString Source #
0-pad a ByteString
unpad :: Int -> ByteString -> ByteString Source #
Remove a 0-padding from a ByteString
withCStringLens :: [String] -> ([CStringLen] -> IO a) -> IO a Source #
constByteStrings :: [ByteString] -> ([CStringLen] -> IO b) -> IO b Source #
Convenience function for accessing constant C strings
buildUnsafeByteString' :: Int -> (Ptr CChar -> IO b) -> IO (b, ByteString) Source #
Slightly safer cousin to buildUnsafeByteString
that remains in the
IO
monad.
buildUnsafeVariableByteString' :: Int -> (Ptr CChar -> IO b) -> IO (b, ByteString) Source #
Sometimes we have to deal with variable-length strings
buildUnsafeVariableByteString :: Int -> (Ptr CChar -> IO b) -> (b, ByteString) Source #
buildUnsafeByteString :: Int -> (Ptr CChar -> IO b) -> (b, ByteString) Source #
Extremely unsafe function, use with utmost care! Builds a new
ByteString using a ccall which is given access to the raw underlying
pointer. Overwrites are UNCHECKED and unsafePerformIO
is used so
it's difficult to predict the timing of the ByteString
creation.
c_sodium_memcmp :: Ptr CChar -> Ptr CChar -> CInt -> IO CInt Source #
Constant time memory comparison
buildUnsafeScrubbedByteString' :: Int -> (Ptr CChar -> IO b) -> IO (b, ByteString) Source #
Not sure yet what to use this for
buildUnsafeScrubbedByteString :: Int -> (Ptr CChar -> IO b) -> (b, ByteString) Source #
Not sure yet what to use this for
c_sodium_bin2hex :: Ptr CChar -> CInt -> Ptr CChar -> CInt -> IO (Ptr CChar) Source #
bin2hex conversion for showing various binary types
withCString :: String -> (CString -> IO a) -> IO a #
Marshal a Haskell string into a NUL terminated C string using temporary storage.
- the Haskell string may not contain any NUL characters
- the memory is freed when the subcomputation terminates (either normally or via an exception), so the pointer to the temporary storage must not be used after this.
allocaBytes :: Int -> (Ptr a -> IO b) -> IO b #
executes the computation allocaBytes
n ff
, passing as argument
a pointer to a temporarily allocated block of memory of n
bytes.
The block of memory is sufficiently aligned for any of the basic
foreign types that fits into a memory block of the allocated size.
The memory is freed when f
terminates (either normally or via an
exception), so the pointer passed to f
must not be used after this.