Skip to content

Commit

Permalink
Added Rust.hs and new tag a shah256 for cabal.project after updating …
Browse files Browse the repository at this point in the history
…my fork of KES-mmm
  • Loading branch information
TimSheard authored and angerman committed Jun 6, 2020
1 parent 88b59e2 commit bccd59d
Show file tree
Hide file tree
Showing 2 changed files with 114 additions and 2 deletions.
4 changes: 2 additions & 2 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,6 @@ source-repository-package
type: git
--location: https://github.com/input-output-hk/kes-mmm-sumed25519
location: https://github.com/TimSheard/kes-mmm-sumed25519
tag: 53c82e531712eec8787e34e550fb6487540e8d1c
--sha256: 0f36czh95x2xp3ncv3nxd3lcpanxzrylrbfi8xin6ddmcim12khx
tag: 0d2db3866551f76384f8684381f18ae1e7bbd016
--sha256: 1ckr4adhmyv7wyq47bhac7vmn9l1ckvwlsayw3j1in53lldib9rz
subdir: kes-mmm-sumed25519-hs
112 changes: 112 additions & 0 deletions cardano-crypto-class/src/Cardano/Crypto/KES/Rust.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,112 @@
{-# OPTIONS_GHC -fno-warn-orphans -Wno-unused-binds -Wno-unused-imports #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-} -- :set -XTypeApplications to set inside GHCi
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE PatternSynonyms #-}


module Rust(go) where


-- ==========================================================
-- import pointers and words to interface with C code

import Data.Word(Word8)
import Foreign(Ptr)
import Foreign.ForeignPtr(mallocForeignPtrBytes,ForeignPtr)
import Foreign.Storable(pokeElemOff)


-- ==========================================================
-- import the KES wrappers that are just C-calls

import qualified KES as CWrap -- (verify, generate, sign, t, update)


-- ===========================================================
-- import different kinds of Byte Strings and operations

import Data.ByteArray(ScrubbedBytes,convert,allocRet,withByteArray,copyByteArrayToPtr,pack)
import qualified Data.ByteString as BS
import Data.ByteString(ByteString,copy)


-- ===========================================================
-- Sizes and Types


pattern SIGNATURE_SIZE = 484
pattern SECRET_KEY_SIZE = 1220
pattern PUBLIC_KEY_SIZE = 32
pattern SEED_SIZE = 32

newtype PublicKey = PublicKey BS.ByteString deriving Show
newtype SecretKey = SecretKey ScrubbedBytes deriving Show
newtype Signature = Signature BS.ByteString deriving Show
newtype Seed = Seed { unSeed :: ScrubbedBytes } deriving Show




-- ============================================================
-- Higher level wrappers that call the C language wrappers

createSeed :: IO Seed
createSeed = do
(_,seed) <- allocRet SEED_SIZE $ \seed_ptr -> do
mapM_ (\i -> pokeElemOff seed_ptr i ((fromIntegral i) :: Word8)) [0..31]
pure $ Seed seed


generate :: Seed -> IO (PublicKey, SecretKey)
generate seed = do
withByteArray (unSeed seed) $ \seed_ptr -> do
(public, secret) <- allocRet SECRET_KEY_SIZE $ \secret -> do
(_,public) <- allocRet PUBLIC_KEY_SIZE $ \public_ptr -> do
CWrap.generate seed_ptr secret public_ptr
pure $ PublicKey public
pure (public, SecretKey secret)


verify :: PublicKey -> BS.ByteString -> Signature -> IO Bool
verify (PublicKey pub) message (Signature sig) = do
withByteArray pub $ \pub_ptr -> do
withByteArray message $ \msg_ptr -> do
withByteArray sig $ \sig_ptr -> do
pure $ CWrap.verify pub_ptr msg_ptr (fromIntegral $ BS.length message) sig_ptr


sign :: SecretKey -> BS.ByteString -> IO Signature
sign (SecretKey sec) message = do
withByteArray sec $ \sec_ptr -> do
withByteArray message $ \msg_ptr -> do
(_, sig) <- allocRet SIGNATURE_SIZE $ \sig_ptr -> do
CWrap.sign sec_ptr msg_ptr (fromIntegral $ BS.length message) sig_ptr
pure $ Signature sig


update :: SecretKey -> IO ()
update (SecretKey sec) = do
withByteArray sec $ \sec_ptr -> do
CWrap.update sec_ptr

compute_public :: SecretKey -> IO PublicKey
compute_public secret = do
withByteArray secret $ \ secret_ptr -> do
(_,public) <- allocRet PUBLIC_KEY_SIZE $ \public_ptr -> CWrap.compute_public secret_ptr public_ptr
pure public






go:: IO()
go = putStrLn "DONE"

0 comments on commit bccd59d

Please sign in to comment.