{-# LANGUAGE FlexibleContexts #-} module Crypto.Secp256k1.Internal.Util where import Crypto.Secp256k1.Internal.ForeignTypes (Seed32) import Data.Base16.Types (assertBase16, extractBase16) import Data.ByteString (ByteString) import qualified Data.ByteString as BS import Data.ByteString.Base16 (decodeBase16, encodeBase16, isBase16) import qualified Data.ByteString.Unsafe as BU import Data.String.Conversions (ConvertibleStrings, cs) import Foreign (Ptr, castPtr) import Foreign.C (CSize (..)) import System.Entropy (getEntropy) decodeHex :: (ConvertibleStrings a ByteString) => a -> Maybe ByteString decodeHex :: forall a. ConvertibleStrings a ByteString => a -> Maybe ByteString decodeHex a str = if ByteString -> Bool isBase16 (ByteString -> Bool) -> ByteString -> Bool forall a b. (a -> b) -> a -> b $ a -> ByteString forall a b. ConvertibleStrings a b => a -> b cs a str then ByteString -> Maybe ByteString forall a. a -> Maybe a Just (ByteString -> Maybe ByteString) -> (Base16 ByteString -> ByteString) -> Base16 ByteString -> Maybe ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Base16 ByteString -> ByteString decodeBase16 (Base16 ByteString -> Maybe ByteString) -> Base16 ByteString -> Maybe ByteString forall a b. (a -> b) -> a -> b $ ByteString -> Base16 ByteString forall a. a -> Base16 a assertBase16 (ByteString -> Base16 ByteString) -> ByteString -> Base16 ByteString forall a b. (a -> b) -> a -> b $ a -> ByteString forall a b. ConvertibleStrings a b => a -> b cs a str else Maybe ByteString forall a. Maybe a Nothing showsHex :: ByteString -> ShowS showsHex :: ByteString -> ShowS showsHex = Text -> ShowS forall a. Show a => a -> ShowS shows (Text -> ShowS) -> (ByteString -> Text) -> ByteString -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Base16 Text -> Text forall a. Base16 a -> a extractBase16 (Base16 Text -> Text) -> (ByteString -> Base16 Text) -> ByteString -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> Base16 Text encodeBase16 unsafeUseByteString :: ByteString -> ((Ptr a, CSize) -> IO b) -> IO b unsafeUseByteString :: forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b unsafeUseByteString ByteString bs (Ptr a, CSize) -> IO b f = ByteString -> (CStringLen -> IO b) -> IO b forall a. ByteString -> (CStringLen -> IO a) -> IO a BU.unsafeUseAsCStringLen ByteString bs ((CStringLen -> IO b) -> IO b) -> (CStringLen -> IO b) -> IO b forall a b. (a -> b) -> a -> b $ \(Ptr CChar b, Int l) -> (Ptr a, CSize) -> IO b f (Ptr CChar -> Ptr a forall a b. Ptr a -> Ptr b castPtr Ptr CChar b, Int -> CSize forall a b. (Integral a, Num b) => a -> b fromIntegral Int l) useByteString :: ByteString -> ((Ptr a, CSize) -> IO b) -> IO b useByteString :: forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b useByteString ByteString bs (Ptr a, CSize) -> IO b f = ByteString -> (CStringLen -> IO b) -> IO b forall a. ByteString -> (CStringLen -> IO a) -> IO a BS.useAsCStringLen ByteString bs ((CStringLen -> IO b) -> IO b) -> (CStringLen -> IO b) -> IO b forall a b. (a -> b) -> a -> b $ \(Ptr CChar b, Int l) -> (Ptr a, CSize) -> IO b f (Ptr CChar -> Ptr a forall a b. Ptr a -> Ptr b castPtr Ptr CChar b, Int -> CSize forall a b. (Integral a, Num b) => a -> b fromIntegral Int l) unsafePackByteString :: (Ptr a, CSize) -> IO ByteString unsafePackByteString :: forall a. (Ptr a, CSize) -> IO ByteString unsafePackByteString (Ptr a b, CSize l) = CStringLen -> IO ByteString BU.unsafePackMallocCStringLen (Ptr a -> Ptr CChar forall a b. Ptr a -> Ptr b castPtr Ptr a b, CSize -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral CSize l) packByteString :: (Ptr a, CSize) -> IO ByteString packByteString :: forall a. (Ptr a, CSize) -> IO ByteString packByteString (Ptr a b, CSize l) = CStringLen -> IO ByteString BS.packCStringLen (Ptr a -> Ptr CChar forall a b. Ptr a -> Ptr b castPtr Ptr a b, CSize -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral CSize l) withRandomSeed :: (Ptr Seed32 -> IO a) -> IO a withRandomSeed :: forall a. (Ptr Seed32 -> IO a) -> IO a withRandomSeed Ptr Seed32 -> IO a go = do ByteString bs <- Int -> IO ByteString getEntropy Int 32 ByteString -> ((Ptr Seed32, CSize) -> IO a) -> IO a forall a b. ByteString -> ((Ptr a, CSize) -> IO b) -> IO b useByteString ByteString bs (((Ptr Seed32, CSize) -> IO a) -> IO a) -> ((Ptr Seed32, CSize) -> IO a) -> IO a forall a b. (a -> b) -> a -> b $ Ptr Seed32 -> IO a go (Ptr Seed32 -> IO a) -> ((Ptr Seed32, CSize) -> Ptr Seed32) -> (Ptr Seed32, CSize) -> IO a forall b c a. (b -> c) -> (a -> b) -> a -> c . (Ptr Seed32, CSize) -> Ptr Seed32 forall a b. (a, b) -> a fst