|
| 1 | +{-# LANGUAGE CApiFFI #-} |
| 2 | +{-# LANGUAGE CPP #-} |
| 3 | + |
| 4 | +module Cardano.Wasm.Internal.Api.Random (getRandomBytes) where |
| 5 | + |
| 6 | +#if !defined(wasm32_HOST_ARCH) |
| 7 | + |
| 8 | +import Data.ByteString (ByteString) |
| 9 | +import Crypto.Random.Entropy (getEntropy) |
| 10 | + |
| 11 | +getRandomBytes :: Word -> IO ByteString |
| 12 | +getRandomBytes n = getEntropy (fromIntegral n) |
| 13 | + |
| 14 | +#else |
| 15 | + |
| 16 | +import Control.Exception (throwIO) |
| 17 | +import Data.ByteString (ByteString, packCStringLen) |
| 18 | +import Data.Word (Word8) |
| 19 | +import System.IO.Error (mkIOError, userErrorType) |
| 20 | + |
| 21 | +import Foreign.C.Types (CInt (..), CSize (..)) |
| 22 | +import Foreign.Marshal.Alloc (allocaBytes) |
| 23 | +import Foreign.Ptr (Ptr, castPtr) |
| 24 | + |
| 25 | +-- | Import the 'random_get' function from wasi |
| 26 | +-- module provided by the WASI runtime. |
| 27 | +-- |
| 28 | +-- It takes a raw pointer to a u8 buffer (Ptr Word8) and the buffer's |
| 29 | +-- length (CSize) and returns a CInt representing the error code number. |
| 30 | +-- A return value of 0 means success. |
| 31 | +foreign import ccall "__wasi_random_get" |
| 32 | + wasi_random_get |
| 33 | + :: Ptr Word8 |
| 34 | + -- ^ Pointer to the buffer to fill |
| 35 | + -> CSize |
| 36 | + -- ^ Number of bytes to write |
| 37 | + -> IO CInt |
| 38 | + -- ^ Returns 0 on success, or an errno code |
| 39 | + |
| 40 | +-- | A safe Haskell wrapper around 'random_get' function from wasi. |
| 41 | +-- It requests the given number of cryptographically secure random |
| 42 | +-- bytes and returns them as a ByteString. |
| 43 | +getRandomBytes :: Word -> IO ByteString |
| 44 | +getRandomBytes n = |
| 45 | + allocaBytes (fromIntegral n) $ \ptr -> do |
| 46 | + -- Get pointer to allocated buffer |
| 47 | + errno <- wasi_random_get ptr (fromIntegral n) |
| 48 | + if errno == 0 |
| 49 | + -- If successful, pack the bytes from the pointer into a Haskell managed ByteString |
| 50 | + then packCStringLen (castPtr ptr, fromIntegral n) |
| 51 | + else -- Otherwise, we throw |
| 52 | + throwIO $ |
| 53 | + mkIOError |
| 54 | + userErrorType |
| 55 | + ("wasi_random_get failed with errno: " ++ show errno) |
| 56 | + Nothing |
| 57 | + Nothing |
| 58 | + |
| 59 | +#endif |
0 commit comments