Skip to content

Commit

Permalink
Merge pull request #7 from kazu-yamamoto/cbits
Browse files Browse the repository at this point in the history
Fixing C symbol names
  • Loading branch information
kazu-yamamoto authored Jun 19, 2023
2 parents e5f315b + 2f06e88 commit ac6496f
Show file tree
Hide file tree
Showing 167 changed files with 3,134 additions and 3,134 deletions.
52 changes: 26 additions & 26 deletions Crypto/Cipher/AES/Primitive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -566,80 +566,80 @@ ccmFinish ctx ccm taglen = AuthTag $ B.take taglen computeTag
withCCMKeyAndCopySt ctx ccm (c_aes_ccm_finish (castPtr t)) >> return ()

------------------------------------------------------------------------
foreign import ccall "cryptonite_aes.h cryptonite_aes_initkey"
foreign import ccall "crypton_aes.h crypton_aes_initkey"
c_aes_init :: Ptr AES -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_encrypt_ecb"
foreign import ccall "crypton_aes.h crypton_aes_encrypt_ecb"
c_aes_encrypt_ecb :: CString -> Ptr AES -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_decrypt_ecb"
foreign import ccall "crypton_aes.h crypton_aes_decrypt_ecb"
c_aes_decrypt_ecb :: CString -> Ptr AES -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_encrypt_cbc"
foreign import ccall "crypton_aes.h crypton_aes_encrypt_cbc"
c_aes_encrypt_cbc :: CString -> Ptr AES -> Ptr Word8 -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_decrypt_cbc"
foreign import ccall "crypton_aes.h crypton_aes_decrypt_cbc"
c_aes_decrypt_cbc :: CString -> Ptr AES -> Ptr Word8 -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_encrypt_xts"
foreign import ccall "crypton_aes.h crypton_aes_encrypt_xts"
c_aes_encrypt_xts :: CString -> Ptr AES -> Ptr AES -> Ptr Word8 -> CUInt -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_decrypt_xts"
foreign import ccall "crypton_aes.h crypton_aes_decrypt_xts"
c_aes_decrypt_xts :: CString -> Ptr AES -> Ptr AES -> Ptr Word8 -> CUInt -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_gen_ctr"
foreign import ccall "crypton_aes.h crypton_aes_gen_ctr"
c_aes_gen_ctr :: CString -> Ptr AES -> Ptr Word8 -> CUInt -> IO ()

foreign import ccall unsafe "cryptonite_aes.h cryptonite_aes_gen_ctr_cont"
foreign import ccall unsafe "crypton_aes.h crypton_aes_gen_ctr_cont"
c_aes_gen_ctr_cont :: CString -> Ptr AES -> Ptr Word8 -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_encrypt_ctr"
foreign import ccall "crypton_aes.h crypton_aes_encrypt_ctr"
c_aes_encrypt_ctr :: CString -> Ptr AES -> Ptr Word8 -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_encrypt_c32"
foreign import ccall "crypton_aes.h crypton_aes_encrypt_c32"
c_aes_encrypt_c32 :: CString -> Ptr AES -> Ptr Word8 -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_gcm_init"
foreign import ccall "crypton_aes.h crypton_aes_gcm_init"
c_aes_gcm_init :: Ptr AESGCM -> Ptr AES -> Ptr Word8 -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_gcm_aad"
foreign import ccall "crypton_aes.h crypton_aes_gcm_aad"
c_aes_gcm_aad :: Ptr AESGCM -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_gcm_encrypt"
foreign import ccall "crypton_aes.h crypton_aes_gcm_encrypt"
c_aes_gcm_encrypt :: CString -> Ptr AESGCM -> Ptr AES -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_gcm_decrypt"
foreign import ccall "crypton_aes.h crypton_aes_gcm_decrypt"
c_aes_gcm_decrypt :: CString -> Ptr AESGCM -> Ptr AES -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_gcm_finish"
foreign import ccall "crypton_aes.h crypton_aes_gcm_finish"
c_aes_gcm_finish :: CString -> Ptr AESGCM -> Ptr AES -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_ocb_init"
foreign import ccall "crypton_aes.h crypton_aes_ocb_init"
c_aes_ocb_init :: Ptr AESOCB -> Ptr AES -> Ptr Word8 -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_ocb_aad"
foreign import ccall "crypton_aes.h crypton_aes_ocb_aad"
c_aes_ocb_aad :: Ptr AESOCB -> Ptr AES -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_ocb_encrypt"
foreign import ccall "crypton_aes.h crypton_aes_ocb_encrypt"
c_aes_ocb_encrypt :: CString -> Ptr AESOCB -> Ptr AES -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_ocb_decrypt"
foreign import ccall "crypton_aes.h crypton_aes_ocb_decrypt"
c_aes_ocb_decrypt :: CString -> Ptr AESOCB -> Ptr AES -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_ocb_finish"
foreign import ccall "crypton_aes.h crypton_aes_ocb_finish"
c_aes_ocb_finish :: CString -> Ptr AESOCB -> Ptr AES -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_ccm_init"
foreign import ccall "crypton_aes.h crypton_aes_ccm_init"
c_aes_ccm_init :: Ptr AESCCM -> Ptr AES -> Ptr Word8 -> CUInt -> CUInt -> CInt -> CInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_ccm_aad"
foreign import ccall "crypton_aes.h crypton_aes_ccm_aad"
c_aes_ccm_aad :: Ptr AESCCM -> Ptr AES -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_ccm_encrypt"
foreign import ccall "crypton_aes.h crypton_aes_ccm_encrypt"
c_aes_ccm_encrypt :: CString -> Ptr AESCCM -> Ptr AES -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_ccm_decrypt"
foreign import ccall "crypton_aes.h crypton_aes_ccm_decrypt"
c_aes_ccm_decrypt :: CString -> Ptr AESCCM -> Ptr AES -> CString -> CUInt -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_ccm_finish"
foreign import ccall "crypton_aes.h crypton_aes_ccm_finish"
c_aes_ccm_finish :: CString -> Ptr AESCCM -> Ptr AES -> IO ()
6 changes: 3 additions & 3 deletions Crypto/Cipher/AESGCMSIV.hs
Original file line number Diff line number Diff line change
Expand Up @@ -80,13 +80,13 @@ polyvalFinalize :: Polyval -> IO ScrubbedBytes
polyvalFinalize (Polyval ctx) = B.alloc 16 $ \dst ->
B.withByteArray ctx $ \pctx -> c_aes_polyval_finalize pctx dst

foreign import ccall unsafe "cryptonite_aes.h cryptonite_aes_polyval_init"
foreign import ccall unsafe "crypton_aes.h crypton_aes_polyval_init"
c_aes_polyval_init :: Ptr Polyval -> CString -> IO ()

foreign import ccall "cryptonite_aes.h cryptonite_aes_polyval_update"
foreign import ccall "crypton_aes.h crypton_aes_polyval_update"
c_aes_polyval_update :: Ptr Polyval -> CString -> CUInt -> IO ()

foreign import ccall unsafe "cryptonite_aes.h cryptonite_aes_polyval_finalize"
foreign import ccall unsafe "crypton_aes.h crypton_aes_polyval_finalize"
c_aes_polyval_finalize :: Ptr Polyval -> CString -> IO ()


Expand Down
30 changes: 15 additions & 15 deletions Crypto/Cipher/ChaCha.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ initialize nbRounds key nonce
stPtr <- B.alloc 132 $ \stPtr ->
B.withByteArray nonce $ \noncePtr ->
B.withByteArray key $ \keyPtr ->
ccryptonite_chacha_init stPtr nbRounds kLen keyPtr nonceLen noncePtr
ccrypton_chacha_init stPtr nbRounds kLen keyPtr nonceLen noncePtr
return $ State stPtr
where kLen = B.length key
nonceLen = B.length nonce
Expand All @@ -64,7 +64,7 @@ initializeSimple seed
| otherwise = unsafeDoIO $ do
stPtr <- B.alloc 64 $ \stPtr ->
B.withByteArray seed $ \seedPtr ->
ccryptonite_chacha_init_core stPtr 32 seedPtr 8 (seedPtr `plusPtr` 32)
ccrypton_chacha_init_core stPtr 32 seedPtr 8 (seedPtr `plusPtr` 32)
return $ StateSimple stPtr
where
sLen = B.length seed
Expand All @@ -81,7 +81,7 @@ combine prevSt@(State prevStMem) src
(out, st) <- B.copyRet prevStMem $ \ctx ->
B.alloc (B.length src) $ \dstPtr ->
B.withByteArray src $ \srcPtr ->
ccryptonite_chacha_combine dstPtr ctx srcPtr (fromIntegral $ B.length src)
ccrypton_chacha_combine dstPtr ctx srcPtr (fromIntegral $ B.length src)
return (out, State st)

-- | Generate a number of bytes from the ChaCha output directly
Expand All @@ -94,7 +94,7 @@ generate prevSt@(State prevStMem) len
| otherwise = unsafeDoIO $ do
(out, st) <- B.copyRet prevStMem $ \ctx ->
B.alloc len $ \dstPtr ->
ccryptonite_chacha_generate dstPtr ctx (fromIntegral len)
ccrypton_chacha_generate dstPtr ctx (fromIntegral len)
return (out, State st)

-- | similar to 'generate' but assume certains values
Expand All @@ -106,21 +106,21 @@ generateSimple (StateSimple prevSt) nbBytes = unsafeDoIO $ do
newSt <- B.copy prevSt (\_ -> return ())
output <- B.alloc nbBytes $ \dstPtr ->
B.withByteArray newSt $ \stPtr ->
ccryptonite_chacha_random 8 dstPtr stPtr (fromIntegral nbBytes)
ccrypton_chacha_random 8 dstPtr stPtr (fromIntegral nbBytes)
return (output, StateSimple newSt)

foreign import ccall "cryptonite_chacha_init_core"
ccryptonite_chacha_init_core :: Ptr StateSimple -> Int -> Ptr Word8 -> Int -> Ptr Word8 -> IO ()
foreign import ccall "crypton_chacha_init_core"
ccrypton_chacha_init_core :: Ptr StateSimple -> Int -> Ptr Word8 -> Int -> Ptr Word8 -> IO ()

foreign import ccall "cryptonite_chacha_init"
ccryptonite_chacha_init :: Ptr State -> Int -> Int -> Ptr Word8 -> Int -> Ptr Word8 -> IO ()
foreign import ccall "crypton_chacha_init"
ccrypton_chacha_init :: Ptr State -> Int -> Int -> Ptr Word8 -> Int -> Ptr Word8 -> IO ()

foreign import ccall "cryptonite_chacha_combine"
ccryptonite_chacha_combine :: Ptr Word8 -> Ptr State -> Ptr Word8 -> CUInt -> IO ()
foreign import ccall "crypton_chacha_combine"
ccrypton_chacha_combine :: Ptr Word8 -> Ptr State -> Ptr Word8 -> CUInt -> IO ()

foreign import ccall "cryptonite_chacha_generate"
ccryptonite_chacha_generate :: Ptr Word8 -> Ptr State -> CUInt -> IO ()
foreign import ccall "crypton_chacha_generate"
ccrypton_chacha_generate :: Ptr Word8 -> Ptr State -> CUInt -> IO ()

foreign import ccall "cryptonite_chacha_random"
ccryptonite_chacha_random :: Int -> Ptr Word8 -> Ptr StateSimple -> CUInt -> IO ()
foreign import ccall "crypton_chacha_random"
ccrypton_chacha_random :: Int -> Ptr Word8 -> Ptr StateSimple -> CUInt -> IO ()

4 changes: 2 additions & 2 deletions Crypto/Cipher/RC4.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,13 +39,13 @@ newtype State = State ScrubbedBytes
deriving (ByteArrayAccess,NFData)

-- | C Call for initializing the encryptor
foreign import ccall unsafe "cryptonite_rc4.h cryptonite_rc4_init"
foreign import ccall unsafe "crypton_rc4.h crypton_rc4_init"
c_rc4_init :: Ptr Word8 -- ^ The rc4 key
-> Word32 -- ^ The key length
-> Ptr State -- ^ The context
-> IO ()

foreign import ccall unsafe "cryptonite_rc4.h cryptonite_rc4_combine"
foreign import ccall unsafe "crypton_rc4.h crypton_rc4_combine"
c_rc4_combine :: Ptr State -- ^ Pointer to the permutation
-> Ptr Word8 -- ^ Pointer to the clear text
-> Word32 -- ^ Length of the clear text
Expand Down
18 changes: 9 additions & 9 deletions Crypto/Cipher/Salsa.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ initialize nbRounds key nonce
stPtr <- B.alloc 132 $ \stPtr ->
B.withByteArray nonce $ \noncePtr ->
B.withByteArray key $ \keyPtr ->
ccryptonite_salsa_init stPtr nbRounds kLen keyPtr nonceLen noncePtr
ccrypton_salsa_init stPtr nbRounds kLen keyPtr nonceLen noncePtr
return $ State stPtr
where kLen = B.length key
nonceLen = B.length nonce
Expand All @@ -57,7 +57,7 @@ combine prevSt@(State prevStMem) src
(out, st) <- B.copyRet prevStMem $ \ctx ->
B.alloc (B.length src) $ \dstPtr ->
B.withByteArray src $ \srcPtr -> do
ccryptonite_salsa_combine dstPtr ctx srcPtr (fromIntegral $ B.length src)
ccrypton_salsa_combine dstPtr ctx srcPtr (fromIntegral $ B.length src)
return (out, State st)

-- | Generate a number of bytes from the Salsa output directly
Expand All @@ -70,14 +70,14 @@ generate prevSt@(State prevStMem) len
| otherwise = unsafeDoIO $ do
(out, st) <- B.copyRet prevStMem $ \ctx ->
B.alloc len $ \dstPtr ->
ccryptonite_salsa_generate dstPtr ctx (fromIntegral len)
ccrypton_salsa_generate dstPtr ctx (fromIntegral len)
return (out, State st)

foreign import ccall "cryptonite_salsa_init"
ccryptonite_salsa_init :: Ptr State -> Int -> Int -> Ptr Word8 -> Int -> Ptr Word8 -> IO ()
foreign import ccall "crypton_salsa_init"
ccrypton_salsa_init :: Ptr State -> Int -> Int -> Ptr Word8 -> Int -> Ptr Word8 -> IO ()

foreign import ccall "cryptonite_salsa_combine"
ccryptonite_salsa_combine :: Ptr Word8 -> Ptr State -> Ptr Word8 -> CUInt -> IO ()
foreign import ccall "crypton_salsa_combine"
ccrypton_salsa_combine :: Ptr Word8 -> Ptr State -> Ptr Word8 -> CUInt -> IO ()

foreign import ccall "cryptonite_salsa_generate"
ccryptonite_salsa_generate :: Ptr Word8 -> Ptr State -> CUInt -> IO ()
foreign import ccall "crypton_salsa_generate"
ccrypton_salsa_generate :: Ptr Word8 -> Ptr State -> CUInt -> IO ()
12 changes: 6 additions & 6 deletions Crypto/Cipher/XSalsa.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ initialize nbRounds key nonce
stPtr <- B.alloc 132 $ \stPtr ->
B.withByteArray nonce $ \noncePtr ->
B.withByteArray key $ \keyPtr ->
ccryptonite_xsalsa_init stPtr nbRounds kLen keyPtr nonceLen noncePtr
ccrypton_xsalsa_init stPtr nbRounds kLen keyPtr nonceLen noncePtr
return $ State stPtr
where kLen = B.length key
nonceLen = B.length nonce
Expand All @@ -64,12 +64,12 @@ derive (State stPtr') nonce
| otherwise = unsafeDoIO $ do
stPtr <- B.copy stPtr' $ \stPtr ->
B.withByteArray nonce $ \noncePtr ->
ccryptonite_xsalsa_derive stPtr nonceLen noncePtr
ccrypton_xsalsa_derive stPtr nonceLen noncePtr
return $ State stPtr
where nonceLen = B.length nonce

foreign import ccall "cryptonite_xsalsa_init"
ccryptonite_xsalsa_init :: Ptr State -> Int -> Int -> Ptr Word8 -> Int -> Ptr Word8 -> IO ()
foreign import ccall "crypton_xsalsa_init"
ccrypton_xsalsa_init :: Ptr State -> Int -> Int -> Ptr Word8 -> Int -> Ptr Word8 -> IO ()

foreign import ccall "cryptonite_xsalsa_derive"
ccryptonite_xsalsa_derive :: Ptr State -> Int -> Ptr Word8 -> IO ()
foreign import ccall "crypton_xsalsa_derive"
ccrypton_xsalsa_derive :: Ptr State -> Int -> Ptr Word8 -> IO ()
32 changes: 16 additions & 16 deletions Crypto/ECC/Edwards25519.hs
Original file line number Diff line number Diff line change
Expand Up @@ -283,86 +283,86 @@ pointsMulVarTime (Scalar s1) (Scalar s2) (Point p) =
withByteArray p $ \pp ->
ed25519_base_double_scalarmul_vartime out ps1 pp ps2

foreign import ccall unsafe "cryptonite_ed25519_scalar_eq"
foreign import ccall unsafe "crypton_ed25519_scalar_eq"
ed25519_scalar_eq :: Ptr Scalar
-> Ptr Scalar
-> IO CInt

foreign import ccall unsafe "cryptonite_ed25519_scalar_encode"
foreign import ccall unsafe "crypton_ed25519_scalar_encode"
ed25519_scalar_encode :: Ptr Word8
-> Ptr Scalar
-> IO ()

foreign import ccall unsafe "cryptonite_ed25519_scalar_decode_long"
foreign import ccall unsafe "crypton_ed25519_scalar_decode_long"
ed25519_scalar_decode_long :: Ptr Scalar
-> Ptr Word8
-> CSize
-> IO ()

foreign import ccall unsafe "cryptonite_ed25519_scalar_add"
foreign import ccall unsafe "crypton_ed25519_scalar_add"
ed25519_scalar_add :: Ptr Scalar -- sum
-> Ptr Scalar -- a
-> Ptr Scalar -- b
-> IO ()

foreign import ccall unsafe "cryptonite_ed25519_scalar_mul"
foreign import ccall unsafe "crypton_ed25519_scalar_mul"
ed25519_scalar_mul :: Ptr Scalar -- out
-> Ptr Scalar -- a
-> Ptr Scalar -- b
-> IO ()

foreign import ccall unsafe "cryptonite_ed25519_point_encode"
foreign import ccall unsafe "crypton_ed25519_point_encode"
ed25519_point_encode :: Ptr Word8
-> Ptr Point
-> IO ()

foreign import ccall unsafe "cryptonite_ed25519_point_decode_vartime"
foreign import ccall unsafe "crypton_ed25519_point_decode_vartime"
ed25519_point_decode_vartime :: Ptr Point
-> Ptr Word8
-> IO CInt

foreign import ccall unsafe "cryptonite_ed25519_point_eq"
foreign import ccall unsafe "crypton_ed25519_point_eq"
ed25519_point_eq :: Ptr Point
-> Ptr Point
-> IO CInt

foreign import ccall "cryptonite_ed25519_point_has_prime_order"
foreign import ccall "crypton_ed25519_point_has_prime_order"
ed25519_point_has_prime_order :: Ptr Point
-> IO CInt

foreign import ccall unsafe "cryptonite_ed25519_point_negate"
foreign import ccall unsafe "crypton_ed25519_point_negate"
ed25519_point_negate :: Ptr Point -- minus_a
-> Ptr Point -- a
-> IO ()

foreign import ccall unsafe "cryptonite_ed25519_point_add"
foreign import ccall unsafe "crypton_ed25519_point_add"
ed25519_point_add :: Ptr Point -- sum
-> Ptr Point -- a
-> Ptr Point -- b
-> IO ()

foreign import ccall unsafe "cryptonite_ed25519_point_double"
foreign import ccall unsafe "crypton_ed25519_point_double"
ed25519_point_double :: Ptr Point -- two_a
-> Ptr Point -- a
-> IO ()

foreign import ccall unsafe "cryptonite_ed25519_point_mul_by_cofactor"
foreign import ccall unsafe "crypton_ed25519_point_mul_by_cofactor"
ed25519_point_mul_by_cofactor :: Ptr Point -- eight_a
-> Ptr Point -- a
-> IO ()

foreign import ccall "cryptonite_ed25519_point_base_scalarmul"
foreign import ccall "crypton_ed25519_point_base_scalarmul"
ed25519_point_base_scalarmul :: Ptr Point -- scaled
-> Ptr Scalar -- scalar
-> IO ()

foreign import ccall "cryptonite_ed25519_point_scalarmul"
foreign import ccall "crypton_ed25519_point_scalarmul"
ed25519_point_scalarmul :: Ptr Point -- scaled
-> Ptr Point -- base
-> Ptr Scalar -- scalar
-> IO ()

foreign import ccall "cryptonite_ed25519_base_double_scalarmul_vartime"
foreign import ccall "crypton_ed25519_base_double_scalarmul_vartime"
ed25519_base_double_scalarmul_vartime :: Ptr Point -- combo
-> Ptr Scalar -- scalar1
-> Ptr Point -- base2
Expand Down
Loading

0 comments on commit ac6496f

Please sign in to comment.