Skip to content

Commit

Permalink
haskell side getPubKey
Browse files Browse the repository at this point in the history
  • Loading branch information
mlitchard committed May 17, 2022
1 parent eff14b6 commit fa53977
Show file tree
Hide file tree
Showing 3 changed files with 28 additions and 2 deletions.
1 change: 1 addition & 0 deletions rustbits/src/lib.rs
Original file line number Diff line number Diff line change
Expand Up @@ -154,6 +154,7 @@ pub fn put_ed_key_internal(
/// # Safety
///
/// To Do -mlitchard
#[no_mangle]
pub unsafe extern "C" fn get_public_key(kid: u16,result: *mut u8,testing_mock: bool) {
let connector = make_connector(testing_mock);
let client: Client = create_client(connector).expect("could not connect to YubiHSM");
Expand Down
14 changes: 14 additions & 0 deletions src/Lib.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,9 @@ foreign import ccall unsafe "sign_with_ed_key" sign_with_ed_key
foreign import ccall unsafe "hello_world" hello_world
:: IO ()

foreign import ccall unsafe "get_public_key" get_public_key
:: CUShort -> CString -> CBool -> IO ()

newtype Id = Id Word16 deriving (Eq, Show)
newtype Label = Label B.ByteString deriving (Eq, Show)
newtype Domains = Domains Word16 deriving (Eq, Show)
Expand Down Expand Up @@ -65,3 +68,14 @@ signWithEdKey (Id i) messageB isTesting =
sign_with_ed_key (CUShort i) msgptr (fromIntegral msglen) outputBuffer (CBool isTestingWord)

B.packCStringLen (outputBuffer, signatureSize)

getPubKey :: Id -> Bool -> IO B.ByteString
getPubKey (Id i) isTesting =
A.allocaBytes keySize $ \outputBuffer -> do
let isTestingWord :: Word8
isTestingWord = fromInteger (toInteger (fromEnum isTesting))
publicKeyB = B.empty
get_public_key (CUShort i) outputBuffer (CBool isTestingWord)
B.packCStringLen (outputBuffer, keySize)


15 changes: 13 additions & 2 deletions tests/Main.hs
Original file line number Diff line number Diff line change
@@ -1,22 +1,33 @@
{-# LANGUAGE ScopedTypeVariables #-}
import Control.Monad.IO.Class
import Control.Monad.IO.Class ()
import qualified Data.ByteString as B
import Data.Text (pack)
import Data.Text.Encoding (encodeUtf8)
import Test.HUnit hiding (Label)
import Test.HUnit ( assertBool, assertEqual, runTestTT, Test(..) )
import Lib
( Domains(Domains),
Label(Label),
Id(Id),
signature,
secretKey,
message,
putEdKey,
signWithEdKey )


testKeyID = 200;
main :: IO ()
main = do
_ <- runTestTT tests
return ()

tests :: Test
tests =
TestList [ TestLabel "test1" helloWorldTest
, TestLabel "putEdKey Test" putEdKeyTest
, TestLabel "signWithEdKey Test" signWithEdKeyTest]

helloWorldTest :: Test
helloWorldTest = TestCase $ do
assertEqual "hello world" True True

Expand Down

0 comments on commit fa53977

Please sign in to comment.