{-# LINE 1 "implementation/entropy/getrandom/Entropy.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface         #-}
module Entropy( getEntropy, entropySource ) where
import Foreign.C             ( CLong(..) )
import Raaz.Core.Prelude
import Raaz.Core.Types
import Raaz.Core.Types.Internal
entropySource :: String
entropySource :: String
entropySource = String
"getrandom(linux)"
foreign import ccall unsafe
  "syscall"
  c_syscall :: CLong
            -> Ptr Word8    
            -> BYTES Int    
            -> Int          
            -> IO (BYTES Int)
sysGETRANDOM :: CLong
sysGETRANDOM :: CLong
sysGETRANDOM = CLong
318
{-# LINE 31 "implementation/entropy/getrandom/Entropy.hsc" #-}
getEntropy :: BYTES Int -> Ptr Word8 -> IO (BYTES Int)
getEntropy :: BYTES Int -> Ptr Word8 -> IO (BYTES Int)
getEntropy BYTES Int
l Ptr Word8
ptr = CLong -> Ptr Word8 -> BYTES Int -> Int -> IO (BYTES Int)
c_syscall CLong
sysGETRANDOM Ptr Word8
ptr BYTES Int
l Int
0