Skip to content

Commit 4690809

Browse files
authored
Merge pull request #980 from IntersectMBO/use-wasi-for-randomness
Replace JS snippet with WASI call for random byte generation
2 parents ab63048 + ff97c2b commit 4690809

File tree

4 files changed

+64
-35
lines changed

4 files changed

+64
-35
lines changed

cardano-wasm/cardano-wasm.cabal

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,14 +42,14 @@ executable cardano-wasm
4242
Cardano.Wasm.Internal.Api.GRPC
4343
Cardano.Wasm.Internal.Api.Info
4444
Cardano.Wasm.Internal.Api.InfoToTypeScript
45+
Cardano.Wasm.Internal.Api.Random
4546
Cardano.Wasm.Internal.Api.Tx
4647
Cardano.Wasm.Internal.Api.TypeScriptDefs
4748
Cardano.Wasm.Internal.Api.Wallet
4849
Cardano.Wasm.Internal.ExceptionHandling
4950
Cardano.Wasm.Internal.JavaScript.Bridge
5051
Cardano.Wasm.Internal.JavaScript.GRPC
5152
Cardano.Wasm.Internal.JavaScript.GRPCTypes
52-
Cardano.Wasm.Internal.JavaScript.Random
5353

5454
build-depends:
5555
aeson,
@@ -74,6 +74,9 @@ executable cardano-wasm
7474
base16-bytestring,
7575
ghc-experimental,
7676
utf8-string,
77+
else
78+
build-depends:
79+
crypton
7780

7881
test-suite cardano-wasm-golden
7982
type: exitcode-stdio-1.0
Lines changed: 59 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,59 @@
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

cardano-wasm/src/Cardano/Wasm/Internal/Api/Wallet.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,8 +38,8 @@ import Cardano.Api
3838
)
3939

4040
import Cardano.Crypto.Seed (mkSeedFromBytes)
41+
import Cardano.Wasm.Internal.Api.Random (getRandomBytes)
4142
import Cardano.Wasm.Internal.ExceptionHandling (rightOrError, toMonadFail)
42-
import Cardano.Wasm.Internal.JavaScript.Random (getRandomBytes)
4343

4444
import Data.Aeson ((.=))
4545
import Data.Aeson qualified as Aeson

cardano-wasm/src/Cardano/Wasm/Internal/JavaScript/Random.hs

Lines changed: 0 additions & 33 deletions
This file was deleted.

0 commit comments

Comments
 (0)