Merge pull request #167 from ocheron/eddsa-minimal

Improve Curve448 and add Ed448
This commit is contained in:
Vincent Hanquez 2017-06-19 13:49:07 +01:00 committed by GitHub
commit 1bcfa2e087
39 changed files with 5986 additions and 378 deletions

View File

@ -92,7 +92,10 @@ dhSecret bs
| B.length bs == 32 = CryptoPassed $ DhSecret $ B.copyAndFreeze bs (\_ -> return ())
| otherwise = CryptoFailed CryptoError_SharedSecretSizeInvalid
-- | Compute the Diffie Hellman secret from a public key and a secret key
-- | Compute the Diffie Hellman secret from a public key and a secret key.
--
-- This implementation may return an all-zero value as it does not check for
-- the condition.
dh :: PublicKey -> SecretKey -> DhSecret
dh (PublicKey pub) (SecretKey sec) = DhSecret <$>
B.allocAndFreeze 32 $ \result ->

View File

@ -7,6 +7,10 @@
--
-- Curve448 support
--
-- Internally uses Decaf point compression to omit the cofactor
-- and implementation by Mike Hamburg. Externally API and
-- data types are compatible with the encoding specified in RFC 7748.
--
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
module Crypto.PubKey.Curve448
@ -75,13 +79,16 @@ dhSecret bs
| B.length bs == x448_bytes = CryptoPassed $ DhSecret $ B.copyAndFreeze bs (\_ -> return ())
| otherwise = CryptoFailed CryptoError_SharedSecretSizeInvalid
-- | Compute the Diffie Hellman secret from a public key and a secret key
-- | Compute the Diffie Hellman secret from a public key and a secret key.
--
-- This implementation may return an all-zero value as it does not check for
-- the condition.
dh :: PublicKey -> SecretKey -> DhSecret
dh (PublicKey pub) (SecretKey sec) = DhSecret <$>
B.allocAndFreeze x448_bytes $ \result ->
withByteArray sec $ \psec ->
withByteArray pub $ \ppub ->
ccryptonite_ed448 result psec ppub
decaf_x448 result ppub psec
{-# NOINLINE dh #-}
-- | Create a public key from a secret key
@ -89,9 +96,7 @@ toPublic :: SecretKey -> PublicKey
toPublic (SecretKey sec) = PublicKey <$>
B.allocAndFreeze x448_bytes $ \result ->
withByteArray sec $ \psec ->
ccryptonite_ed448 result psec basePoint
where
basePoint = Ptr "\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#
decaf_x448_derive_public_key result psec
{-# NOINLINE toPublic #-}
-- | Generate a secret key.
@ -101,8 +106,13 @@ generateSecretKey = SecretKey <$> getRandomBytes x448_bytes
x448_bytes :: Int
x448_bytes = 448 `quot` 8
foreign import ccall "cryptonite_x448"
ccryptonite_ed448 :: Ptr Word8 -- ^ public
-> Ptr Word8 -- ^ secret
-> Ptr Word8 -- ^ basepoint
-> IO ()
foreign import ccall "cryptonite_decaf_x448"
decaf_x448 :: Ptr Word8 -- ^ public
-> Ptr Word8 -- ^ basepoint
-> Ptr Word8 -- ^ secret
-> IO ()
foreign import ccall "cryptonite_decaf_x448_derive_public_key"
decaf_x448_derive_public_key :: Ptr Word8 -- ^ public
-> Ptr Word8 -- ^ secret
-> IO ()

View File

@ -9,7 +9,6 @@
--
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Crypto.PubKey.Ed25519
( SecretKey
, PublicKey
@ -43,7 +42,7 @@ import Crypto.Random
-- | An Ed25519 Secret key
newtype SecretKey = SecretKey ScrubbedBytes
deriving (Eq,ByteArrayAccess,NFData)
deriving (Show,Eq,ByteArrayAccess,NFData)
-- | An Ed25519 public key
newtype PublicKey = PublicKey Bytes
@ -116,9 +115,7 @@ verify public message signatureVal = unsafeDoIO $
-- | Generate a secret key
generateSecretKey :: MonadRandom m => m SecretKey
generateSecretKey = do
ba :: ScrubbedBytes <- getRandomBytes secretKeySize
return (SecretKey $ B.copyAndFreeze ba (\_ -> return ()))
generateSecretKey = SecretKey <$> getRandomBytes secretKeySize
-- | A public key is 32 bytes
publicKeySize :: Int

View File

@ -1,20 +1,163 @@
-- |
-- Module : Crypto.PubKey.Ed448
-- License : BSD-style
-- Maintainer : John Galt <jgalt@centromere.net>
-- Maintainer : Olivier Chéron <olivier.cheron@gmail.com>
-- Stability : experimental
-- Portability : unknown
--
-- Ed448 support
--
-- /Functions and types exported here will be DEPRECATED in a future version./
-- For Diffie-Hellman over curve448 please use module "Crypto.PubKey.Curve448"
-- instead.
-- Internally uses Decaf point compression to omit the cofactor
-- and implementation by Mike Hamburg. Externally API and
-- data types are compatible with the encoding specified in RFC 8032.
--
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
module Crypto.PubKey.Ed448
( module Crypto.PubKey.Curve448
( SecretKey
, PublicKey
, Signature
-- * Size constants
, publicKeySize
, secretKeySize
, signatureSize
-- * Smart constructors
, signature
, publicKey
, secretKey
-- * methods
, toPublic
, sign
, verify
, generateSecretKey
) where
import Crypto.PubKey.Curve448
import Data.Word
import Foreign.C.Types
import Foreign.Ptr
import Crypto.Error
import Crypto.Internal.ByteArray (ByteArrayAccess, Bytes,
ScrubbedBytes, withByteArray)
import qualified Crypto.Internal.ByteArray as B
import Crypto.Internal.Compat
import Crypto.Internal.Imports
import Crypto.Random
-- | An Ed448 Secret key
newtype SecretKey = SecretKey ScrubbedBytes
deriving (Show,Eq,ByteArrayAccess,NFData)
-- | An Ed448 public key
newtype PublicKey = PublicKey Bytes
deriving (Show,Eq,ByteArrayAccess,NFData)
-- | An Ed448 signature
newtype Signature = Signature Bytes
deriving (Show,Eq,ByteArrayAccess,NFData)
-- | Try to build a public key from a bytearray
publicKey :: ByteArrayAccess ba => ba -> CryptoFailable PublicKey
publicKey bs
| B.length bs == publicKeySize =
CryptoPassed $ PublicKey $ B.copyAndFreeze bs (\_ -> return ())
| otherwise =
CryptoFailed $ CryptoError_PublicKeySizeInvalid
-- | Try to build a secret key from a bytearray
secretKey :: ByteArrayAccess ba => ba -> CryptoFailable SecretKey
secretKey bs
| B.length bs == secretKeySize = unsafeDoIO $ withByteArray bs initialize
| otherwise = CryptoFailed CryptoError_SecretKeyStructureInvalid
where
initialize inp = do
valid <- isValidPtr inp
if valid
then (CryptoPassed . SecretKey) <$> B.copy bs (\_ -> return ())
else return $ CryptoFailed CryptoError_SecretKeyStructureInvalid
isValidPtr _ =
return True
{-# NOINLINE secretKey #-}
-- | Try to build a signature from a bytearray
signature :: ByteArrayAccess ba => ba -> CryptoFailable Signature
signature bs
| B.length bs == signatureSize =
CryptoPassed $ Signature $ B.copyAndFreeze bs (\_ -> return ())
| otherwise =
CryptoFailed CryptoError_SecretKeyStructureInvalid
-- | Create a public key from a secret key
toPublic :: SecretKey -> PublicKey
toPublic (SecretKey sec) = PublicKey <$>
B.allocAndFreeze publicKeySize $ \result ->
withByteArray sec $ \psec ->
decaf_ed448_derive_public_key result psec
{-# NOINLINE toPublic #-}
-- | Sign a message using the key pair
sign :: ByteArrayAccess ba => SecretKey -> PublicKey -> ba -> Signature
sign secret public message =
Signature $ B.allocAndFreeze signatureSize $ \sig ->
withByteArray secret $ \sec ->
withByteArray public $ \pub ->
withByteArray message $ \msg ->
decaf_ed448_sign sig sec pub msg (fromIntegral msgLen) 0 no_context 0
where
!msgLen = B.length message
-- | Verify a message
verify :: ByteArrayAccess ba => PublicKey -> ba -> Signature -> Bool
verify public message signatureVal = unsafeDoIO $
withByteArray signatureVal $ \sig ->
withByteArray public $ \pub ->
withByteArray message $ \msg -> do
r <- decaf_ed448_verify sig pub msg (fromIntegral msgLen) 0 no_context 0
return (r /= 0)
where
!msgLen = B.length message
-- | Generate a secret key
generateSecretKey :: MonadRandom m => m SecretKey
generateSecretKey = SecretKey <$> getRandomBytes secretKeySize
-- | A public key is 57 bytes
publicKeySize :: Int
publicKeySize = 57
-- | A secret key is 57 bytes
secretKeySize :: Int
secretKeySize = 57
-- | A signature is 114 bytes
signatureSize :: Int
signatureSize = 114
no_context :: Ptr Word8
no_context = nullPtr -- not supported yet
foreign import ccall "cryptonite_decaf_ed448_derive_public_key"
decaf_ed448_derive_public_key :: Ptr PublicKey -- public key
-> Ptr SecretKey -- secret key
-> IO ()
foreign import ccall "cryptonite_decaf_ed448_sign"
decaf_ed448_sign :: Ptr Signature -- signature
-> Ptr SecretKey -- secret
-> Ptr PublicKey -- public
-> Ptr Word8 -- message
-> CSize -- message len
-> Word8 -- prehashed
-> Ptr Word8 -- context
-> Word8 -- context len
-> IO ()
foreign import ccall "cryptonite_decaf_ed448_verify"
decaf_ed448_verify :: Ptr Signature -- signature
-> Ptr PublicKey -- public
-> Ptr Word8 -- message
-> CSize -- message len
-> Word8 -- prehashed
-> Ptr Word8 -- context
-> Word8 -- context len
-> IO CInt

View File

@ -100,5 +100,7 @@ Links
* [Scrypt](http://www.tarsnap.com/scrypt.html)
* [Curve25519](http://cr.yp.to/ecdh.html)
* [Ed25519](http://ed25519.cr.yp.to/papers.html)
* [Ed448-Goldilocks](http://ed448goldilocks.sourceforge.net/)
* [EdDSA-test-vectors](http://www.ietf.org/rfc/rfc8032.txt)
* [AFIS](http://clemens.endorphin.org/cryptography)

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,354 @@
/** @warning: this file was automatically generated. */
#include "field.h"
#include <decaf.h>
#define API_NS(_id) cryptonite_decaf_448_##_id
const API_NS(point_t) API_NS(point_base) = {{
{FIELD_LITERAL(0x00fffffffffffffe,0x00ffffffffffffff,0x00ffffffffffffff,0x00ffffffffffffff,0x0000000000000003,0x0000000000000000,0x0000000000000000,0x0000000000000000)},
{FIELD_LITERAL(0x0081e6d37f752992,0x003078ead1c28721,0x00135cfd2394666c,0x0041149c50506061,0x0031d30e4f5490b3,0x00902014990dc141,0x0052341b04c1e328,0x0014237853c10a1b)},
{FIELD_LITERAL(0x00fffffffffffffb,0x00ffffffffffffff,0x00ffffffffffffff,0x00ffffffffffffff,0x00fffffffffffffe,0x00ffffffffffffff,0x00ffffffffffffff,0x00ffffffffffffff)},
{FIELD_LITERAL(0x008f205b70660415,0x00881c60cfd3824f,0x00377a638d08500d,0x008c66d5d4672615,0x00e52fa558e08e13,0x0087770ae1b6983d,0x004388f55a0aa7ff,0x00b4d9a785cf1a91)}
}};
const gf API_NS(precomputed_base_as_fe)[240]
VECTOR_ALIGNED = {
{FIELD_LITERAL(0x00e614a9f7278dc5,0x002e454ad04c5124,0x00d8f58cee1436f3,0x00c83ed46e4180ec,0x00a41e93274a38fa,0x00c1e7e53257771e,0x0043e0ff03c0392f,0x002c7c6405ce61df)},
{FIELD_LITERAL(0x0033c4f9dc990b33,0x00c291cb1ceb55c3,0x002ae3f58ade88b2,0x006b1f9f11395474,0x002ded6e4b27ff7c,0x0041012ed4aa10e1,0x003c22d20a36bae7,0x001f584eed472b19)},
{FIELD_LITERAL(0x00c3514779ee6f60,0x001574c873b20c2b,0x004cd6a46a5a5e65,0x0059a068aeb4204a,0x004c610458bc354d,0x00e94567479d02d2,0x00feaf77ed118e28,0x00f58a8bf115eeb5)},
{FIELD_LITERAL(0x0046110878fcb20f,0x00df43db21cc6f32,0x00ffdde9f4516644,0x00519917791686b9,0x00b72b441fd34473,0x008d45684cb1c72b,0x0015181370fc17a5,0x00a456d1307f74d3)},
{FIELD_LITERAL(0x001430f149b607dc,0x00e992ccd16715fc,0x00a62209b0a32a09,0x00b889cedc26b8e4,0x0059bf9a3ac109cf,0x006871bb3b7feac2,0x00f4a4d5fd9a0e6b,0x00b95db460cd69a5)},
{FIELD_LITERAL(0x0036304418bda702,0x007bc56861561558,0x00f344bc8e30416f,0x00a64537080f59d7,0x00b4c20077d00ace,0x00ee79620b26f8cc,0x00a6a558e0b5403d,0x008f1d2c766f3d19)},
{FIELD_LITERAL(0x00ef21c0297d3112,0x0073f89bd27c35b1,0x00ec44f9b1ff5e33,0x006bee51d878f1ee,0x001571a4b2aceddb,0x00cd0182d55131d1,0x0026761dbc1844be,0x00f01865af716474)},
{FIELD_LITERAL(0x0021dfef3f5fe8cc,0x0038c659ed1dbd68,0x0058ded9bcebe283,0x00077bbb094983ee,0x00b7b484e913d70c,0x0063e477a9506397,0x0000b996a6e01629,0x00ab68b41f75cd37)},
{FIELD_LITERAL(0x00a1fbd946403a4e,0x00be5a4e2d611b05,0x00ea4f210888bc6e,0x0043e9b0e0ae50fe,0x002abc4f6bd86845,0x00c3ed649c67f663,0x00d4eeb391a520e7,0x004b19cf1bfe7584)},
{FIELD_LITERAL(0x0099a75e6f22999e,0x001f16454c79f659,0x00d776a37fddc812,0x0095fdd63b6b0a78,0x00d232169366e947,0x002ea77dd21e9de7,0x00e8c46e85f97a90,0x00358758651f8cd9)},
{FIELD_LITERAL(0x002b6f5036a07bdf,0x004f6940af3e2646,0x00866028f8986799,0x00838b26ccb50415,0x0010557417f00b11,0x008a3b6bc447e96b,0x003de3d035e9e0c9,0x00188fca2b6d4011)},
{FIELD_LITERAL(0x001ca4038635312b,0x0078dc75c1e01c44,0x004340f00b3100a4,0x005e63e36bf6646e,0x008e1efd4b624688,0x00a61c2ffb1525e1,0x0072587505a75b81,0x00a8637140d96e78)},
{FIELD_LITERAL(0x004a7c41ffac8a41,0x005bf37075b1c20b,0x00c053b570a42408,0x002bb7e278d328e7,0x00b2378b63245100,0x003318bf2a1a368a,0x00f4e3e0bdbe02de,0x0058921e4b1e32f8)},
{FIELD_LITERAL(0x005e93d6fa1118a0,0x0062b43515d381e2,0x002c42864052e620,0x00af258bae6ccbd3,0x00954247094d654d,0x005db01f5b010810,0x009c8cf25efa8204,0x005f73ced3714ef7)},
{FIELD_LITERAL(0x0085f89aff2cf49d,0x00f591ee8480f6f0,0x00378ed518114265,0x00f04293e2a09008,0x00c58688db9140ed,0x00e9912696399ff1,0x0055bd1b96367413,0x0023a70cf830f999)},
{FIELD_LITERAL(0x001c83772944584e,0x00c1ba881e472bcc,0x00af2715a0aef13f,0x00bd0360d25610a6,0x00c42f8b3eebebde,0x00a9e474849788b1,0x00dcd1a1a2efec5c,0x009480d34c2818c0)},
{FIELD_LITERAL(0x00b4b6e09a565d74,0x0095efcf6175aa48,0x00498defe7ae7810,0x00309b684ed26470,0x007a8873a91d4e44,0x00ea4b3f857eb27a,0x00979b8619d25a9e,0x00721a2770eeb6e9)},
{FIELD_LITERAL(0x00b422f0f4be195f,0x00e88cfa83bfa2db,0x009fd60666ea4268,0x0095a458f5e801d0,0x00b9eee6882081f6,0x00b27edb37604948,0x00a7f67c4d44d8db,0x00df840ccf290c01)},
{FIELD_LITERAL(0x00c9fed0d47c9103,0x00ba73ed9294a043,0x005cbbc928e652e1,0x0068419e98ee8215,0x00f63de63786300b,0x009aa9bb6c19f8aa,0x0066c536b573213f,0x00d2b77a5b2f2450)},
{FIELD_LITERAL(0x00810236c68d5b74,0x00d0a1af1872a011,0x007f23ee29e3801a,0x009a55a678f8dba4,0x0065445dcff9be40,0x00f3978789a9abc5,0x00001f010d23f5e8,0x00ff80042934b0c5)},
{FIELD_LITERAL(0x00a6749f4b3f9745,0x003ab85f4180e502,0x006a7de9b530ed50,0x0050b5353b0441bf,0x00a093583ac6ede4,0x00c4918ad1406299,0x000f75cf2a353a2b,0x001c6644a0683a56)},
{FIELD_LITERAL(0x00e8694156c09bfe,0x00f6f3a5bd17ad96,0x0098dbed45edad12,0x00edfe2b84921821,0x0097884330199b67,0x004aab02685b3e9e,0x0068ac0bd2453c30,0x00167c1c1c87d8f5)},
{FIELD_LITERAL(0x008bba5fbf63f599,0x0059a3c960c7d63f,0x00ce2db75b08b7d9,0x0097e80cb2104171,0x009b68be26a140d0,0x002b9b9954e94c68,0x00023ca8fc411beb,0x00cbc4bcccbada07)},
{FIELD_LITERAL(0x0053c100e77b678d,0x000f115c400fa96f,0x005928d3de22afa2,0x00e47cd9bdbdbe96,0x00597ecfe84abf19,0x0058bb428e4c7a32,0x00dd582f76ecf584,0x00b1211365eccb79)},
{FIELD_LITERAL(0x00dbfb9a00a58e68,0x004468189350d82f,0x00b4b12407ee92c6,0x00e27a7908f73455,0x00f071170071b5ae,0x00221a5e6ba229dd,0x001903e3f6a81f83,0x00be36325402775f)},
{FIELD_LITERAL(0x004d298d6e691756,0x00775644dfce310b,0x00a861887823ea98,0x00cf0b6014fa6e6f,0x005f4e296380826f,0x00bf423392627f90,0x002893bfc8122f6a,0x00440dbc89bea228)},
{FIELD_LITERAL(0x00acbb4f40a4ab73,0x00d6a82f48fa3366,0x000a7958fc6faac2,0x008a4cdd60a7c33c,0x005e5587dd8b6f1a,0x00e40f63086a88e8,0x0030940cbbcda0ad,0x009a42e3dc35c130)},
{FIELD_LITERAL(0x00d37716cad825f1,0x00883870cba9552a,0x008ef785f5c762e3,0x006cb253e0469242,0x007b8f17fee9d967,0x00a43de6932b52b6,0x001aca9fe2af783c,0x008967778ff0b680)},
{FIELD_LITERAL(0x006400c4cdc6c9c3,0x001e8c978691083f,0x00ad74f01f68e0c5,0x00f7feb0372b5f6a,0x002f60d175ade13a,0x0098ec54a221a678,0x00fcfea8a71f244e,0x00dea6660e45ded2)},
{FIELD_LITERAL(0x002585b4aa8d6752,0x00e62da7615a2089,0x0010c1c741f39b68,0x00569bb1eced9f65,0x00ba6d09e4daa724,0x007d3e20aef281b9,0x00bd7f65aca3ffdc,0x00dea434a50288a8)},
{FIELD_LITERAL(0x007ba92a2489170f,0x00cd356354d31e9c,0x00a60d47406e5430,0x009c3d5fde8ed877,0x00079eaa50dd08d1,0x0024674d593ffa5f,0x005391be9596c53b,0x00856ca8d50acdd9)},
{FIELD_LITERAL(0x00d4620aa5e5bdec,0x002303c4b9b5d941,0x003b061f857ebb2a,0x00371f9e856d49fd,0x0071c36c5335051e,0x0040e4346a4d359f,0x00b31dbd959ec40c,0x00d99353a71bf6de)},
{FIELD_LITERAL(0x0078898adf0f21dd,0x006e09bfedd8604a,0x00efaf0e0f9bb666,0x00b0f685db8852c3,0x0094c86ec566b841,0x00e5c2879ba50dbe,0x00a87cd444cff758,0x00d3e26fd47f23df)},
{FIELD_LITERAL(0x00b82c07fb1854f8,0x0057f654a06fad9f,0x004c00383250cf92,0x008b91713d291af6,0x002f2521777859b9,0x00533111421f22c8,0x00643da86fab9794,0x00dc7fb0680e3d40)},
{FIELD_LITERAL(0x00e59ffd40e87788,0x006431e9755a50af,0x00a03ce700fb580a,0x00ad7e70aa3c9b9e,0x0078970a2b4db503,0x00c800451849637a,0x00e7e6a5b49e123f,0x00e1ed15f77bcb4d)},
{FIELD_LITERAL(0x00bc1d1d1af47f28,0x00ebc5501bbd81f0,0x00aa6b5513547aa4,0x0074ed33551343fe,0x00d2114f6ef7d43b,0x006335b41d518aeb,0x00ebd46919692fb8,0x0052d5d4e3fada95)},
{FIELD_LITERAL(0x00ebfc9f489799a4,0x00497535b6980688,0x00fef76499e6a51b,0x00018eedde7a18da,0x00f435d9e72b69c7,0x005ab0faa8281675,0x003232d06e290be8,0x005473ec8be0286c)},
{FIELD_LITERAL(0x00c6eb0d0ebb4874,0x00856a2274119097,0x00380bc7b29e3719,0x00b1ae149f0e424d,0x0009b41855b9de26,0x0098684013d0f53f,0x0082e8554c38a6ff,0x00e76c18c353743a)},
{FIELD_LITERAL(0x008da1194e1ab61f,0x008edb5f89688805,0x00f4970252f851bd,0x007a46f632b6ad20,0x006d2d1c37e9f90a,0x0060dd09353f665f,0x000a625a80d86657,0x000f93f6fedd0888)},
{FIELD_LITERAL(0x003b019b31992fb4,0x004f6a2ad1f64c28,0x008a744134e5c571,0x000ca33172f9af3f,0x00d478755a67bb8b,0x009d1f5c48abb223,0x004da4d6f12ee901,0x0084f09541f4140d)},
{FIELD_LITERAL(0x0031f412f5cacd43,0x00e5afb75dd20e94,0x001ce24b3452740e,0x00176d6dedf30ff1,0x0082e22e564fffca,0x001d56fbe007097f,0x0095b37c851a6918,0x008ec50ef97f8f4c)},
{FIELD_LITERAL(0x007e2b1c52251f57,0x00cbef37c9380033,0x0037ed652761bceb,0x00f1c2a5dc6dd232,0x0026e1b90d63ce0b,0x00938d732173a6b8,0x00d439aa45da993f,0x00d356b8deaccef7)},
{FIELD_LITERAL(0x00ed32377f56c67d,0x00c3b6a4de32e4a7,0x00481a36c0dd5d91,0x00bb557d20466ba7,0x00645f6d3200163e,0x005eb4c54df7c48c,0x00fd8e3d08f1e3b4,0x001156353f099147)},
{FIELD_LITERAL(0x00ae1b4c089b2756,0x00e686d2b916fb5f,0x007ac43ec2437dd8,0x00f7bfdf7e860ed2,0x0097dbcb8b786dc9,0x00ec7a90401c8b2f,0x00425ed017989bdb,0x00444bc9ca6d914d)},
{FIELD_LITERAL(0x00e5e7b83b53ab7f,0x004e4bed6ca44fc5,0x0008bd7a67c40d4d,0x009dbec74a4a2f0e,0x0077df3f4fc2c73f,0x0046b1af5e73ea8d,0x009f096cb7be8670,0x003ad0a29929141d)},
{FIELD_LITERAL(0x00991a1222e9b2e1,0x00be7583901d7dc7,0x00fd1d0c8169d3da,0x000fe0a94a68acf9,0x00b77bd05afc78a2,0x00a84f1697f87ebc,0x000097cfdb0c2ecb,0x007d51d70352ed1b)},
{FIELD_LITERAL(0x0025dc2a60643159,0x001f0d8ff85f95b4,0x00ed74a4bc598a73,0x00f30afe6f0574a9,0x0003788545d4d28c,0x009dc410ad120ac0,0x001950947e69961d,0x001ceb23cb0355b0)},
{FIELD_LITERAL(0x00ee2202ded9f1bd,0x002fa4fce658976d,0x00e7c15bc9716470,0x004f7ea99d500369,0x004b995a18318376,0x00246c4f8af91911,0x00cc77a07d09dbfe,0x007906f6f1364be6)},
{FIELD_LITERAL(0x003c97e6384da36e,0x00423d53eac81a09,0x00b70d68f3cdce35,0x00ee7959b354b92c,0x00f4e9718819c8ca,0x009349f12acbffe9,0x005aee7b62cb7da6,0x00d97764154ffc86)},
{FIELD_LITERAL(0x00d95d1c5fcb435a,0x0016d1ed6b5086f9,0x00792aa0b7e54d71,0x0067b65715f1925d,0x00a219755ec6176b,0x00bc3f026b12c28f,0x00700c897ffeb93e,0x0089b83f6ec50b46)},
{FIELD_LITERAL(0x00ad9cdb4544b923,0x00d11664c7284061,0x00815ae86b8f910b,0x005414fb2591c3c6,0x0094ba83e2d7ef9e,0x0001dbc16599386c,0x00c8721f0493911b,0x00c1be6b463c346c)},
{FIELD_LITERAL(0x0079680ce111ed3b,0x001a1ed82806122c,0x000c2e7466d15df3,0x002c407f6f7150fd,0x00c5e7c96b1b0ce3,0x009aa44626863ff9,0x00887b8b5b80be42,0x00b6023cec964825)},
{FIELD_LITERAL(0x00fed3cd80ca2292,0x0015b043a73ca613,0x000a9fd7bf9be227,0x003b5e03de2db983,0x005af72d46904ef7,0x00c0f1b5c49faa99,0x00dc86fc3bd305e1,0x00c92f08c1cb1797)},
{FIELD_LITERAL(0x001b571efb768f37,0x009d778487cf5cfd,0x00430e37327ebfd4,0x00a92447e5970a41,0x00eb13127c0edbac,0x00ec61e5aefeaf20,0x00447eebf57d2e5c,0x00f01433e550e558)},
{FIELD_LITERAL(0x0039dd7ce7fc6860,0x00d64f6425653da1,0x003e037c7f57d0af,0x0063477a06e2bcf2,0x001727dbb7ac67e6,0x0049589f5efafe2e,0x00fc0fef2e813d54,0x008baa5d087fb50d)},
{FIELD_LITERAL(0x00a7527958238159,0x0013ec9537a84cd6,0x001d7fee7d562525,0x00b9eefa6191d5e5,0x00dbc97db70bcb8a,0x00481affc7a4d395,0x006f73d3e70c31bb,0x00183f324ed96a61)},
{FIELD_LITERAL(0x00db04a6264ba838,0x00582b1f9fddc1b3,0x003ee72e4aaa027f,0x007d1de938cd0dd5,0x0032d5d66cf76afa,0x00c9c717c95c1ec2,0x00f27aa11764b8d6,0x00713a482b7ef36e)},
{FIELD_LITERAL(0x00ece96f95f2b66f,0x00ece7952813a27b,0x0026fc36592e489e,0x007157d1a2de0f66,0x00759dc111d86ddf,0x0012881e5780bb0f,0x00c8ccc83ad29496,0x0012b9bd1929eb71)},
{FIELD_LITERAL(0x001bf51f7d65cdfd,0x00d14cdafa16a97d,0x002c38e60fcd10e7,0x00a27446e393efbd,0x000b5d8946a71fdd,0x0063df2cde128f2f,0x006c8679569b1888,0x0059ffc4925d732d)},
{FIELD_LITERAL(0x00f05ea5df25a20f,0x00cb6224e5b932ce,0x00d3aed52e2718d9,0x00fb89ee0996ce72,0x006197045a6e1e80,0x00bcdf20057fc6f9,0x0059bf78b6ae5c2c,0x0049cacb87455db0)},
{FIELD_LITERAL(0x006a15bb20f75c0c,0x0079a144027a5d0c,0x00d19116ce0b4d70,0x0059b83bcb0b268e,0x005f58f63f16c127,0x0079958318ee2c37,0x00defbb063d07f82,0x00f1f0b931d2d446)},
{FIELD_LITERAL(0x009696510000d333,0x00ec2f788bc04826,0x000e4d02b1f67ba5,0x00659aa8dace08b6,0x00d7a38a3a3ae533,0x008856defa8c746b,0x004d7a4402d3da1a,0x00ea82e06229260f)},
{FIELD_LITERAL(0x0034a1b3c3ca2bdd,0x0072077a35bca880,0x0005af4e935c1b8e,0x00a5f1a71e8b7737,0x004d3133292cb2e5,0x000fe2a2dca1c916,0x0024d181b41935bb,0x00d9f54880ca0332)},
{FIELD_LITERAL(0x009ffd90abfeae96,0x00cba3c2b624a516,0x005ef08bcee46c91,0x00e6fde30afb6185,0x00f0b4db4f818ce4,0x006c54f45d2127f5,0x00040125035854c7,0x00372658a3287e13)},
{FIELD_LITERAL(0x006f6fd9baac61d5,0x002a7710a020a895,0x009de0db7fc03d4d,0x00cdedcb1875f40b,0x00050caf9b6b1e22,0x005e3a6654456ab0,0x00775fdf8c4423d4,0x0028701ea5738b5d)},
{FIELD_LITERAL(0x0028f8f04e414d54,0x0087037ba56c7694,0x00976b5b4d0ddb59,0x00a4227e6d462421,0x004c77c678b4c560,0x0006c9e74fb485a8,0x00c1c138a02d3981,0x0040a19403d6b6b5)},
{FIELD_LITERAL(0x0045e8dda9400888,0x002ff12e5fc05db7,0x00a7098d54afe69c,0x00cdbe846a500585,0x00879c1593ca1882,0x003f7a7fea76c8b0,0x002cd73dd0c8e0a1,0x00645d6ce96f51fe)},
{FIELD_LITERAL(0x00f19224ebba2aa5,0x0074f89d358e694d,0x00eea486597135ad,0x0081579a4555c7e1,0x0010b9b872930a9d,0x00f002e87a30ecc0,0x009b9d66b6de56e2,0x00a3c4f45e8004eb)},
{FIELD_LITERAL(0x00d4817c1edc2929,0x00c67cb908be637f,0x00bd6dd1aa6bfe9c,0x00a1803a9fe7795c,0x001770d311e2cefb,0x0018054eca0d1c88,0x004fa667b240f212,0x00f631f7f055a447)},
{FIELD_LITERAL(0x00f89335c2a59286,0x00a0f5c905d55141,0x00b41fb836ee9382,0x00e235d51730ca43,0x00a5cb37b5c0a69a,0x009b966ffe136c45,0x00cb2ea10bf80ed1,0x00fb2b370b40dc35)},
{FIELD_LITERAL(0x0085e78af7758979,0x00275a4ee1631a3a,0x00d26bc0ed78b683,0x004f8355ea21064f,0x00d618e1a32696e5,0x008d8d7b150e5680,0x00a74cd854b278d2,0x001dd62702203ea0)},
{FIELD_LITERAL(0x0029782e92b11745,0x008eadf422f96200,0x00217a39f2cdcaa2,0x00782d1ca9aefd0b,0x00321c6e47203654,0x001e72961020101a,0x00b562fa6e6ab16e,0x0005c92274af111a)},
{FIELD_LITERAL(0x006bc3d53011f470,0x00032d6e692b83e8,0x00059722f497cd0b,0x0009b4e6f0c497cc,0x0058a804b7cce6c0,0x002b71d3302bbd5d,0x00e2f82a36765fce,0x008dded99524c703)},
{FIELD_LITERAL(0x002e788749a865f7,0x006e4dc3116861ea,0x009f1428c37276e6,0x00e7d2e0fc1e1226,0x003aeebc6b6c45f6,0x0071a8073bf500c9,0x004b22ad986b530c,0x00f439e63c0d79d4)},
{FIELD_LITERAL(0x00b2fa76ac8b829b,0x008fe6bf01865590,0x0059df538e389f40,0x006acd49eeea748a,0x00ab81280b990cfe,0x00c34a54ac57bfe5,0x003889ce9731cedf,0x0081b71cc1b4654d)},
{FIELD_LITERAL(0x002f194eaafa46dc,0x008e38f57fe87613,0x00dc8e5ae25f4ab2,0x000a17809575e6bd,0x00d3ec7923ba366a,0x003a7e72e0ad75e3,0x0010024b88436e0a,0x00ed3c5444b64051)},
{FIELD_LITERAL(0x001b2fc57bf3c738,0x006a3f918993fb80,0x0026f7a14fdec288,0x0075a2cdccef08db,0x00d3ecbc9eecdbf1,0x0048c40f06e5bf7f,0x00d63e423009896b,0x000598bc99c056a8)},
{FIELD_LITERAL(0x007ce03ecbf50cbd,0x00369ba996b992ca,0x00896d4b33a5f7f0,0x00602b5b8536da60,0x00e1122082ba6d73,0x00c3fbb903ba0d74,0x00d3f8ec55c1daf8,0x006a8f96ca0f0be1)},
{FIELD_LITERAL(0x001fb73475c45509,0x00d2b2e5ea43345a,0x00cb3c3842077bd1,0x0029f90ad820946e,0x007c11b2380778aa,0x009e54ece62c1704,0x004bc60c41ca01c3,0x004525679a5a0b03)},
{FIELD_LITERAL(0x00766ae4190ec6d8,0x0065768cabc71380,0x00b902598416cdc2,0x00380021ad38df52,0x008f0b89d6551134,0x004254d4cc62c5a5,0x000d79f4484b9b94,0x00b516732ae3c50e)},
{FIELD_LITERAL(0x0039b0422412784c,0x00bf9fe2ee8ce055,0x0063ddb8a4906298,0x00db48625178a0ea,0x009e9012c0fd3c4e,0x00ff30c60950d2c4,0x003b9453f5565977,0x0054dc1d7ff25dfb)},
{FIELD_LITERAL(0x0017085f4a346148,0x00c7cf7a37f62272,0x001776e129bc5c30,0x009955134c9eef2a,0x001ba5bdf1df07be,0x00ec39497103a55c,0x006578354fda6cfb,0x005f02719d4f15ee)},
{FIELD_LITERAL(0x000b3a37617632b0,0x00597199fe1cfb6c,0x0042a7ccdfeafdd6,0x004cc9f15ebcea17,0x00f436e596a6b4a4,0x00168861142df0d8,0x000753edfec26af5,0x000c495d7e388116)},
{FIELD_LITERAL(0x00ad46264a269aa2,0x002b13845e4b9e3c,0x0006a20b68b0d7f4,0x00c271a35ee514ae,0x002b67e14a58f4d8,0x00f5065b099a60d6,0x00ba6737b90514bc,0x00b6265e7c5b898f)},
{FIELD_LITERAL(0x00b60167d9e7d065,0x00e60ba0d07381e8,0x003a4f17b725c2d4,0x006c19fe176b64fa,0x003b57b31af86ccb,0x0021047c286180fd,0x00bdc8fb00c6dbb6,0x00fe4a9f4bab4f3f)},
{FIELD_LITERAL(0x000a72d23dcb3f1f,0x00a3737f84011727,0x00f870c0fbbf4a47,0x00a7aadd04b5c9ca,0x000c7715c67bd072,0x00015a136afcd74e,0x0080d5caea499634,0x0026b448ec7514b7)},
{FIELD_LITERAL(0x0077003c5e9eee08,0x006eaa1bdba2f437,0x007ae297ddfa8d2a,0x00aa8531e1aeb2d6,0x00ce283cc626efdc,0x00efe2f51d153115,0x00db954c07c84995,0x002ade92c7e00acf)},
{FIELD_LITERAL(0x00a6295218dc136a,0x00563b3af0e9c012,0x00d3753b0145db1b,0x004550389c043dc1,0x00ea94ae27401bdf,0x002b0b949f2b7956,0x00c63f780ad8e23c,0x00e591c47d6bab15)},
{FIELD_LITERAL(0x0057e7ea35f36dae,0x00f47d7ad15de22e,0x00d757ea4b105115,0x008311457d579d7e,0x00b49b75b1edd4eb,0x0081c7ff742fd63a,0x00ddda3187433df6,0x00475727d55f9c66)},
{FIELD_LITERAL(0x00be93a7d4fa7149,0x00bef825a4d3396a,0x004c32daa951139b,0x003f4be7d981a85e,0x00e866d6ca8642d0,0x00b912bba6f1b2f8,0x00e28ba64c9cf5e1,0x0039504574996955)},
{FIELD_LITERAL(0x002419222c607674,0x00a7f23af89188b3,0x00ad127284e73d1c,0x008bba582fae1c51,0x00fc6aa7ca9ecab1,0x003df5319eb6c2ba,0x002a05af8a8b199a,0x004bf8354558407c)},
{FIELD_LITERAL(0x008d6009b26da3f8,0x00898e88ca06b1ca,0x00edb22b2ed7fe62,0x00fbc93516aabe80,0x008b4b470c42ce0d,0x00e0032ba7d0dcbb,0x00d76da3a956ecc8,0x007f20fe74e3852a)},
{FIELD_LITERAL(0x003182b5cf0f0340,0x002fd3d8d9d60fc2,0x00b73ffe08bff43d,0x00d3dec97fee6a72,0x00675aafc6e16949,0x00d27f499c6f0c86,0x00e0578789f3387a,0x00e52031ab49ec2a)},
{FIELD_LITERAL(0x006b7a0674f9f8de,0x00a742414e5c7cff,0x0041cbf3c6e13221,0x00e3a64fd207af24,0x0087c05f15fbe8d1,0x004c50936d9e8a33,0x001306ec21042b6d,0x00a4f4137d1141c2)},
{FIELD_LITERAL(0x001ed4dc71fa2523,0x005d0bff19bf9b5c,0x00c3801cee065a64,0x001ed0b504323fbf,0x0003ab9fdcbbc593,0x00df82070178b8d2,0x00a2bcaa9c251f85,0x00c628a3674bd02e)},
{FIELD_LITERAL(0x00f619046dea974f,0x004c39fedfde6ee7,0x00d593cb9f22afc5,0x00624e10ee9ab4ab,0x009c1b40f41869fd,0x0098f2cb44da6d46,0x002311d093becf31,0x004d97d1771880ab)},
{FIELD_LITERAL(0x00ddbe0750dd1add,0x004b3c7b885844b8,0x00363e7ecf12f1ae,0x0062e953e6438f9d,0x0023cc73b076afe9,0x00b09fa083b4da32,0x00c7c3d2456c541d,0x005b591ec6b694d4)},
{FIELD_LITERAL(0x000d5b4b3da135ab,0x00838f3e5064d81d,0x00d44eb50f6d94ed,0x0008931ab502ac6d,0x00debe01ca3d3586,0x0025c206775f0641,0x005ad4b6ae912763,0x007e2c318ad8f247)},
{FIELD_LITERAL(0x00d79a91e629d030,0x00ad5b50fc20eb72,0x00edd89a222eb1bd,0x000ddad6fb098ea8,0x00b8be69a49c90c4,0x009bbe2d69ecd346,0x00a1def906a95a48,0x00db8fd6a6d2cca3)},
{FIELD_LITERAL(0x00c41d1f9c1f1ac1,0x007b2df4e9f19146,0x00b469355fd5ba7a,0x00b5e1965afc852a,0x00388d5f1e2d8217,0x0022079e4c09ae93,0x0014268acd4ef518,0x00c1dd8d9640464c)},
{FIELD_LITERAL(0x003fe038eb92f894,0x000e6da1b72e8e32,0x003a1411bfcbe0fa,0x00b55d473164a9e4,0x00b9a775ac2df48d,0x0002ddf350659e21,0x00a279a69eb19cb3,0x00f844eab25cba44)},
{FIELD_LITERAL(0x00c7ad952112f3aa,0x00229739f81c017a,0x0008b9222b75a2a8,0x00bd0d6ad469c483,0x00e344297892a13c,0x00a1cbeb8f435a3d,0x0078e2be1f7a0bec,0x001ac54f670ba8cd)},
{FIELD_LITERAL(0x00adb2c1566e8b8f,0x0096c68a35771a9a,0x00869933356f334a,0x00ba9c93459f5962,0x009ec73fb6e8ca4b,0x003c3802c27202e1,0x0031f5b733e0c008,0x00f9058c19611fa9)},
{FIELD_LITERAL(0x004d51124797c831,0x008f5ae3750347ad,0x0070ced94c1a0c8e,0x00f6db2043898e64,0x000d00c9a5750cd0,0x000741ec59bad712,0x003c9d11aab37b7f,0x00a67ba169807714)},
{FIELD_LITERAL(0x00dc70fe7eb5cbde,0x003cda5bb49331d7,0x00dec9068514f18c,0x00f3537d975b501d,0x00dd02de725b8e4b,0x0062327200072106,0x0034607e7e266644,0x00ebc51a91215cb6)},
{FIELD_LITERAL(0x00a5187e6ee7341b,0x00e6d52e82d83b6e,0x00df3c41323094a7,0x00b3324f444e9de9,0x00689eb21a35bfe5,0x00f16363becd548d,0x00e187cc98e7f60f,0x00127d9062f0ccab)},
{FIELD_LITERAL(0x0000623bf87622c5,0x00a1966fdd069496,0x00c315b7b812f9fc,0x00bdf5efcd128b97,0x001d464f532e3e16,0x003cd94f081bfd7e,0x00ed9dae12ce4009,0x002756f5736eee70)},
{FIELD_LITERAL(0x00b528e4ce3d61bf,0x005a03531ed051d6,0x00bbda4aa68d7f12,0x001810a28e93ccb9,0x00ef4ac525bef536,0x006dcefdd9f9f364,0x006e3d9ed78d6381,0x00774bd6ff0713c4)},
{FIELD_LITERAL(0x00c13c5aae3ae341,0x009c6c9ed98373e7,0x00098f26864577a8,0x0015b886e9488b45,0x0037692c42aadba5,0x00b83170b8e7791c,0x001670952ece1b44,0x00fd932a39276da2)},
{FIELD_LITERAL(0x00f1e26e9762d4a8,0x00d9d74082183414,0x00ffec9bd57a0282,0x000919e128fd497a,0x00ab7ae7d00fe5f8,0x0054dc442851ff68,0x00c9ebeb3b861687,0x00507f7cab8b698f)},
{FIELD_LITERAL(0x007e5cda6410cc67,0x00ab7f000be9ef84,0x0031b09f82de4167,0x00c003f7b4be2064,0x00bc2f44effafd2d,0x0013ca0a8a45cd9e,0x0035e70988cff10c,0x001744f57d827ab7)},
{FIELD_LITERAL(0x009ae3b93a56c404,0x004a410b7a456699,0x00023a619355e6b2,0x009cdc7297387257,0x0055b94d4ae70d04,0x002cbd607f65b005,0x003208b489697166,0x00ea2aa058867370)},
{FIELD_LITERAL(0x00df76b3328ada72,0x002e20621604a7c2,0x00f910638a105b09,0x00ef4724d96ef2cd,0x00377d83d6b8a2f7,0x00b4f48805ade324,0x001cd5da8b152018,0x0045af671a20ca7f)},
{FIELD_LITERAL(0x000d62da6711c0cd,0x004b53ac7a27d523,0x0089cc150fb20e64,0x0055d2c2883154fe,0x00b5dcfd03448874,0x006d80dda2a505cb,0x00b57162afb80dc8,0x007ddb5162431acf)},
{FIELD_LITERAL(0x00c845923c084294,0x00072419a201bc25,0x0045f408b5f8e669,0x00e9d6a186b74dfe,0x00e19108c68fa075,0x0017b91d874177b7,0x002f0ca2c7912c5a,0x009400aa385a90a2)},
{FIELD_LITERAL(0x001cf640859b02f8,0x00758d1d5d5ce427,0x00763c784ef4604c,0x005fa81aee205270,0x00ac537bfdfc44cb,0x004b919bd342d670,0x00238508d9bf4b7a,0x00154888795644f3)},
{FIELD_LITERAL(0x008eeef4feb7de7b,0x003012ffbb0d4107,0x00cb0d6fe30b99d1,0x00c4b51d598067cb,0x003356469016b7ee,0x00addaf85188542f,0x004538bdd8de18c1,0x00999dd4f0c59d4f)},
{FIELD_LITERAL(0x0026ef1614e160af,0x00c023f9edfc9c76,0x00cff090da5f57ba,0x0076db7a66643ae9,0x0019462f8c646999,0x008fec00b3854b22,0x00d55041692a0a1c,0x0065db894215ca00)},
{FIELD_LITERAL(0x00f8ac5cf4705b6a,0x00867d82dcb457e3,0x007e13ab2ccc2ce9,0x009ee9a018d3930e,0x008370f8ecb42df8,0x002d9f019add263e,0x003302385b92d196,0x00a15654536e2c0c)},
{FIELD_LITERAL(0x0056dafc91f5bae3,0x00d5fc6f3c94933e,0x000d8fdf26f76b0b,0x00726f2ad342c280,0x001e2fec8c6d0c46,0x000fe83ea74ae570,0x00353cec2c128243,0x0046657e1c14bd2c)},
{FIELD_LITERAL(0x008cc9cd236315c0,0x0031d9c5b39fda54,0x00a5713ef37e1171,0x00293d5ae2886325,0x00c4aba3e05015e1,0x0003f35ef78e4fc6,0x0039d6bd3ac1527b,0x0019d7c3afb77106)},
{FIELD_LITERAL(0x00b54850275fe626,0x0053a3fd1ec71140,0x00e3d2d7dbe096fa,0x00e4ac7b595cce4c,0x0077bad449c0a494,0x00b7c98814afd5b3,0x0057226f58486cf9,0x00b1557154f0cc57)},
{FIELD_LITERAL(0x0084e9d6ce567a50,0x0052bf5d1f2558ec,0x00920d83bff60ee7,0x00afc160b1d17413,0x008ae58837d3e7d1,0x00fd676c8896dba4,0x00004e170540611a,0x00f7ccb8f91f6541)},
{FIELD_LITERAL(0x004246bfcecc627a,0x004ba431246c03a4,0x00bd1d101872d497,0x003b73d3f185ee16,0x001feb2e2678c0e3,0x00ff13c5a89dec76,0x00ed06042e771d8f,0x00a4fd2a897a83dd)},
{FIELD_LITERAL(0x00dbca4e98a7dcd9,0x00ee29cfc78bde99,0x00e4a3b6995f52e9,0x0045d70189ae8096,0x00fd2a8a3b9b0d1b,0x00af1793b107d8e1,0x00dbf92cbe4afa20,0x00da60f798e3681d)},
{FIELD_LITERAL(0x0065b5c41af29a68,0x0021ce9a03a5ef69,0x00b0c0a91cba4f38,0x0008408de2a54743,0x00bcec1b84f673ae,0x001b382a3f1e5244,0x00d1c1c24c9afae1,0x005b7f3d32956904)},
{FIELD_LITERAL(0x004ede34af2813f3,0x00d4a8e11c9e8216,0x004796d5041de8a5,0x00c4c6b4d21cc987,0x00e8a433ee07fa1e,0x0055720b5abcc5a1,0x008873ea9c74b080,0x005b3fec1ab65d48)},
{FIELD_LITERAL(0x00417fa30a7119ed,0x00af257758419751,0x00d358a487b463d4,0x0089703cc720b00d,0x00ce56314ff7f271,0x0064db171ade62c1,0x00640b36d4a22fed,0x00424eb88696d23f)},
{FIELD_LITERAL(0x00b81ad88248f13a,0x00f5f69399248294,0x004be9b33e8cfea6,0x00b56087c018df01,0x0057e8846bbb6242,0x006a5db00b65a660,0x00963e3a87daf343,0x00badfe6dec2140b)},
{FIELD_LITERAL(0x001bd59c09e982ea,0x00f72daeb937b289,0x0018b76dca908e0e,0x00edb498512384ad,0x00ce0243b6cc9538,0x00f96ff690cb4e70,0x007c77bf9f673c8d,0x005bf704c088a528)},
{FIELD_LITERAL(0x0021ce99e09ebda3,0x00fcbd9f91875ad0,0x009bbf6b7b7a0b5f,0x00388886a69b1940,0x00926a56d0f81f12,0x00e12903c3358d46,0x005dfce4e8e1ce9d,0x0044cfa94e2f7e23)},
{FIELD_LITERAL(0x006c2b9d7234cc41,0x006ad9c2ae2bda7d,0x00b64cdddba701f9,0x00180318c49ac580,0x00c35d14319f4c95,0x003a21dc65cd415b,0x009c474c28e04940,0x00c65114875e57c6)},
{FIELD_LITERAL(0x00fb22bb5fd3ce50,0x0017b48aada7ae54,0x00fd5c44ad19a536,0x000ccc4e4e55e45c,0x00fd637d45b4c3f5,0x0038914e023c37cf,0x00ac1881d6a8d898,0x00611ed8d3d943a8)},
{FIELD_LITERAL(0x007dc52da400336c,0x001fded1e15b9457,0x00902e00f5568e3a,0x00219bef40456d2d,0x005684161fb3dbc9,0x004a4e9be49a76ea,0x006e685ae88b78ff,0x0021c42f13042d3c)},
{FIELD_LITERAL(0x00a91dda62eec2d4,0x00a6b7e64d7b13e9,0x00384086b44c9969,0x008de118af683239,0x0008e416fb85d76c,0x0020945ebda9b120,0x0096a7f485e7b172,0x000fa91c7035f011)},
{FIELD_LITERAL(0x005e8694077a1535,0x008bef75f71c8f1d,0x000a7c1316423511,0x00906e1d70604320,0x003fc46c1a2ffbd6,0x00d1d5022e68f360,0x002515fba37bbf46,0x00ca16234e023b44)},
{FIELD_LITERAL(0x009df98566a18c6d,0x00cf3a200968f219,0x0044ba60da6d9086,0x00dbc9c0e344da03,0x000f9401c4466855,0x00d46a57c5b0a8d1,0x00875a635d7ac7c6,0x00ef4a933b7e0ae6)},
{FIELD_LITERAL(0x00878366a9e0b96f,0x0057a8573ea9e0d8,0x005ef206ddc3f601,0x0046756a9d1c4eab,0x00bccf478bb3c12c,0x001f97ed7f813a3b,0x001b309582460e1c,0x0026a4f760ecd5cb)},
{FIELD_LITERAL(0x00139078397030bd,0x000e3c447e859a00,0x0064a5b334c82393,0x00b8aabeb7358093,0x00020778bb9ae73b,0x0032ee94c7892a18,0x008215253cb41bda,0x005e2797593517ae)},
{FIELD_LITERAL(0x002922b39ca33eec,0x0090d12a5f3ab194,0x00ab60c02fb5f8ed,0x00188d292abba1cf,0x00e10edec9698f6e,0x0069a4d9934133c8,0x0024aac40e6d3d06,0x001702c2177661b0)},
{FIELD_LITERAL(0x007c89a5a07aa2b5,0x00ae492ecae4711d,0x00ee921ab74f0844,0x007842778fc5005f,0x006a4d33cb28022c,0x007b327e4ac0f437,0x007a9d0366acaf12,0x005c6544e6c9ae1c)},
{FIELD_LITERAL(0x0091868594265aa2,0x00797accae98ca6d,0x0008d8c5f0f8a184,0x00d1f4f1c2b2fe6e,0x0036783dfb48a006,0x008c165120503527,0x0025fd780058ce9b,0x0068beb007be7d27)},
{FIELD_LITERAL(0x0019e23f0474b114,0x00eb94c2ad3b437e,0x006ddb34683b75ac,0x00391f9209b564c6,0x00083b3bb3bff7aa,0x00eedcd0f6dceefc,0x00b50817f794fe01,0x0036474deaaa75c9)},
{FIELD_LITERAL(0x002f007755836f3d,0x004d39f2530acc6b,0x006b58d7b2699929,0x004126fdd3185e62,0x003aeaac0f32897c,0x003c0478f4edb66d,0x0072f43ac66a9364,0x0003730da744777a)},
{FIELD_LITERAL(0x0045fdc16487cda3,0x00b2d8e844cf2ed7,0x00612c50e88c1607,0x00a08aabc66c1672,0x006031fdcbb24d97,0x001b639525744b93,0x004409d62639ab17,0x00a1853d0347ab1d)},
{FIELD_LITERAL(0x003667bf998406f8,0x0000115c43a12975,0x001e662f3b20e8fd,0x0019ffa534cb24eb,0x00016be0dc8efb45,0x00ff76a8b26243f5,0x00ae20d241a541e3,0x0069bd6af13cd430)},
{FIELD_LITERAL(0x008a5e5a9140a3de,0x005c18d41653ac12,0x0010321e9d6e8f3d,0x00fbdda016e10aca,0x0077fb6038c20257,0x00b5438b7a81ed77,0x00db1dbcb9a8ce83,0x0026734c2c1aabc3)},
{FIELD_LITERAL(0x007e32c049b5c477,0x009d2bfdbd9bcfd8,0x00636e93045938c6,0x007fde4af7687298,0x0046a5184fafa5d3,0x0079b1e7f13a359b,0x00875adf1fb927d6,0x00333e21c61bcad2)},
{FIELD_LITERAL(0x00b4b53eab6bdb19,0x009b22d8b43711d0,0x00d948b9d961785d,0x00cb167b6f279ead,0x00191de3a678e1c9,0x00d9dd9511095c2e,0x00f284324cd43067,0x00ed74fa535151dd)},
{FIELD_LITERAL(0x00fb7feb08c27472,0x008a97b55f699c77,0x006d41820f923b83,0x006831432f0aa975,0x00a58ffb263b3955,0x004f13449a66db38,0x0026fccd22b6d583,0x00a803eb20eeb6c2)},
{FIELD_LITERAL(0x007df6cbb926830b,0x00d336058ae37865,0x007af47dac696423,0x0048d3011ec64ac8,0x006b87666e40049f,0x0036a2e0e51303d7,0x00ba319bd79dbc55,0x003e2737ecc94f53)},
{FIELD_LITERAL(0x0008ed8ea0ad95be,0x0041d324b9709645,0x00e25412257a19b4,0x0058df9f3423d8d2,0x00a9ab20def71304,0x009ae0dbf8ac4a81,0x00c9565977e4392a,0x003c9269444baf55)},
{FIELD_LITERAL(0x002d69008d9d8d26,0x00092f686d7030a8,0x001f19e95aa28fec,0x002150bab1261538,0x008c5a941210b26c,0x009330209036d1e6,0x0062e11ec8e58de7,0x0011c3d11bb9d27f)},
{FIELD_LITERAL(0x008132ae5c5d8cd1,0x00121d68324a1d9f,0x00d6be9dafcb8c76,0x00684d9070edf745,0x00519fbc96d7448e,0x00388182fdc1f27e,0x000235baed41f158,0x00bf6cf6f1a1796a)},
{FIELD_LITERAL(0x00437bce9bccdf9d,0x00e0c8e2f85dc0a3,0x00c91a7073995a19,0x00856ec9fe294559,0x009e4b33394b156e,0x00e245b0dc497e5c,0x006a54e687eeaeff,0x00f1cd1cd00fdb7c)},
{FIELD_LITERAL(0x00d523b4b2eb7de6,0x00cf7b525f2c56f5,0x00b9217554f0d1b1,0x00bad2cbd5984a02,0x002b4af0fe2b21dd,0x002492603f310486,0x0073e7b3795b9d32,0x001e837c89b2bd25)},
{FIELD_LITERAL(0x00ce382dc7993d92,0x00021153e938b4c8,0x00096f7567f48f51,0x0058f81ddfe4b0d5,0x00cc379a56b355c7,0x002c760770d3e819,0x00ee22d1d26e5a40,0x00de6d93d5b082d7)},
{FIELD_LITERAL(0x007b2743b9a1e01a,0x007847ffd42688c4,0x006c7844d610a316,0x00f0cb8b250aa4b0,0x00a19060143b3ae6,0x0014eb10b77cfd80,0x000170905729dd06,0x00063b5b9cd72477)},
{FIELD_LITERAL(0x00f56e5bd3ad1fa9,0x00e7a09488031815,0x00f7fc3ae69d094a,0x00ddad7a7d45a9c2,0x00bc07fbf167a928,0x007a5d6137e0479f,0x00a0659eeab60a00,0x003e068b1342b4f9)},
{FIELD_LITERAL(0x00ffc5c89d2b0cba,0x00d363d42e3e6fc3,0x0019a1a0118e2e8a,0x00f7baeff48882e1,0x001bd5af28c6b514,0x0055476ca2253cb2,0x00d8eb1977e2ddf3,0x00b173b1adb228a1)},
{FIELD_LITERAL(0x005b64c6fd65ec97,0x00c1fdd7f877bc7f,0x000d9cc6c89f841c,0x005c97b7f1aff9ad,0x0075e3c61475d47e,0x001ecb1ba8153011,0x00fe7f1c8d71d40d,0x003fa9757a229832)},
{FIELD_LITERAL(0x000d346622f528f8,0x001e1f7497a62227,0x00fff70d2f9af433,0x002812c6d079ea3c,0x006898af56b25d7f,0x00c17c44f1349645,0x00207172ea3eb539,0x000608e8bd6a263d)},
{FIELD_LITERAL(0x002389319450f9ba,0x003677f31aa1250a,0x0092c3db642f38cb,0x00f8b64c0dfc9773,0x00cd49fe3505b795,0x0068105a4090a510,0x00df0ba2072a8bb6,0x00eb396143afd8be)},
{FIELD_LITERAL(0x00f11cc8e0e70bcb,0x00e5dc689974e7dd,0x0014e409f9ee5870,0x00826e6689acbd63,0x008a6f4e3d895d88,0x00b26a8da41fd4ad,0x000fb7723f83efd7,0x009c749db0a5f6c3)},
{FIELD_LITERAL(0x005f2b1304db3200,0x0022507ff7459b86,0x000f4c1c92b4f0bb,0x00c8cb42c50e0eb9,0x004781d1038aad80,0x002dcf20aa2254af,0x00d9ecda851a93e2,0x0043f6b92eca6cb2)},
{FIELD_LITERAL(0x0067f8f0c4fe26c9,0x0079c4a3cc8f67b9,0x0082b1e62f23550d,0x00f2d409caefd7f5,0x0080e67dcdb26e81,0x0087ae993ea1f98a,0x00aa108becf61d03,0x001acf11efb608a3)},
{FIELD_LITERAL(0x00468711bd994651,0x0033108fa67561bf,0x0089d760192a54b4,0x00adc433de9f1871,0x000467d05f36e050,0x007847e0f0579f7f,0x00a2314ad320052d,0x00b3a93649f0b243)},
{FIELD_LITERAL(0x007dda014454af26,0x000c49fa1b22df7c,0x005cd4d7e761dc2d,0x002af81a1a14b368,0x00a5e57b1cfd7ddf,0x00f90ab3e3a0f738,0x005cb83734d7bc0f,0x00f608c16abb405a)},
{FIELD_LITERAL(0x00e828333c297f8b,0x009ef3cf8c3f7e1f,0x00ab45f8fff31cb9,0x00c8b4178cb0b013,0x00d0c50dd3260a3f,0x0097126ac257f5bc,0x0042376cc90c705a,0x001d96fdb4a1071e)},
{FIELD_LITERAL(0x006c59c9ae744185,0x009fc32f1b4282cd,0x004d6348ca59b1ac,0x00105376881be067,0x00af4096013147dc,0x004abfb5a5cb3124,0x000d2a7f8626c354,0x009c6ed568e07431)},
{FIELD_LITERAL(0x00abd2bb27611e57,0x00cf99bd1fbbd267,0x006f7ac78d478cc7,0x00dc9d340dd23fbb,0x00d3ddd520099c46,0x009836dbb6a03486,0x00f19de267c36883,0x0020885613349904)},
{FIELD_LITERAL(0x00832d02369b482c,0x00cba52ff0d93450,0x003fa9c908d554db,0x008d1e357b54122f,0x00abd91c2dc950c6,0x007eff1df4c0ec69,0x003f6aeb13fb2d31,0x00002d6179fc5b2c)},
{FIELD_LITERAL(0x002809e4bbf1814a,0x00b9e854f9fafb32,0x00d35e67c10f7a67,0x008f1bcb76e748cf,0x004224d9515687d2,0x005ba0b774e620c4,0x00b5e57db5d54119,0x00e15babe5683282)},
{FIELD_LITERAL(0x00b9361257e36376,0x0049f348e3709d03,0x00dd0a597c455aa7,0x00078ce603320668,0x00635f64ae3195dc,0x00a4ed450b508288,0x0075b9adb5e1cc1d,0x00fca588167741f2)},
{FIELD_LITERAL(0x00a9e7730a819691,0x00d9cc73c4992b70,0x00e299bde067de5a,0x008c314eb705192a,0x00e7226f17e8a3cc,0x0029dfd956e65a47,0x0053a8e839073b12,0x006f942b2ab1597e)},
{FIELD_LITERAL(0x00a7efe46a7dbe2f,0x002f66fd55014fe7,0x006a428afa1ff026,0x0056caaa9604ab72,0x0033f3bcd7fac8ae,0x00ccb1aa01c86764,0x00158d1edf13bf40,0x009848ee76fcf3b4)},
{FIELD_LITERAL(0x00e3c287f132a1c6,0x006b0db804233a01,0x002a387902ad889b,0x00490b258b0f24d5,0x007f0e0745232a02,0x000c95c8c52d1dc4,0x0007fb060bcbc40d,0x002e50bf139dc67d)},
{FIELD_LITERAL(0x0039343746531ebe,0x00c8509d835d429d,0x00e79eceff6b0018,0x004abfd31e8efce5,0x007bbfaaa1e20210,0x00e3be89c193e179,0x001c420f4c31d585,0x00f414a315bef5ae)},
{FIELD_LITERAL(0x0082aeace5f1b144,0x00f68b3108cf4dd3,0x00634af01dde3020,0x000beab5df5c2355,0x00e8b790d1b49b0b,0x00e48d15854e36f4,0x0040ab2d95f3db9f,0x002711c4ed9e899a)},
{FIELD_LITERAL(0x0083d695db66f207,0x002a2f8ada58aa77,0x002271eec16b4818,0x008443a70141f337,0x00d60ae50640352b,0x00816cee1385490c,0x006577b21e989cbc,0x00af2a0d2317b416)},
{FIELD_LITERAL(0x0098cddc8b39549a,0x006da37e3b05d22c,0x00ce633cfd4eb3cb,0x00fda288ef526acd,0x0025338878c5d30a,0x00f34438c4e5a1b4,0x00584efea7c310f1,0x0041a551f1b660ad)},
{FIELD_LITERAL(0x005fa020cca2450a,0x00491c29db6416d8,0x0037cefe3f9f9a85,0x003d405230647066,0x0049e835f0fdbe89,0x00feb78ac1a0815c,0x00828e4b32dc9724,0x00db84f2dc8d6fd4)},
{FIELD_LITERAL(0x002808570429bc85,0x009d78dbec40c8ac,0x0052b4434bc3a7b4,0x00801b6419fe281c,0x008839a68764540a,0x0014ba034f958be4,0x00a31dbb6ec068f7,0x0077bd9bfe8c9cd9)},
{FIELD_LITERAL(0x00a0b68ec1eb72d2,0x002c03235c0d45a0,0x00553627323fe8c5,0x006186e94b17af94,0x00a9906196e29f14,0x0025b3aee6567733,0x007e0dd840080517,0x0018eb5801a4ba93)},
{FIELD_LITERAL(0x007bf562ca768d7c,0x006c1f3a174e387c,0x00f024b447fee939,0x007e7af75f01143f,0x003adb70b4eed89d,0x00e43544021ad79a,0x0091f7f7042011f6,0x0093c1a1ee3a0ddc)},
{FIELD_LITERAL(0x0028018fe84095bf,0x0091c0f9db41f3bd,0x0000445dfaca7dba,0x000603d307e6bdc6,0x00726c4c840ea4b0,0x009220d1c741716a,0x00d4918640a03006,0x0054caa25bda1d21)},
{FIELD_LITERAL(0x003973d8938971d6,0x002aca26fa80c1f5,0x00108af1faa6b513,0x00daae275d7924e6,0x0053634ced721308,0x00d2355fe0bbd443,0x00357612b2d22095,0x00f9bb9dd4136cf3)},
{FIELD_LITERAL(0x00938f97e20be973,0x0099141a36aaf306,0x0057b0ca29e545a1,0x0085db571f9fbc13,0x008b333c554b4693,0x0043ab6ef3e241cb,0x0054fb20aa1e5c70,0x00be0ff852760adf)},
{FIELD_LITERAL(0x00d400ed30a1fc5a,0x00e424e0575e6307,0x0036e3986c07b2c6,0x0007960e4d145650,0x00a643ab823cdc93,0x0026e9ee292c7976,0x001f9d2555d3fdeb,0x0012c3fb833d437d)},
{FIELD_LITERAL(0x0062dd0fb31be374,0x00fcc96b84c8e727,0x003f64f1375e6ae3,0x0057d9b6dd1af004,0x00d6a167b1103c7b,0x00dd28f3180fb537,0x004ff27ad7167128,0x008934c33461f2ac)},
{FIELD_LITERAL(0x000050d70c32b31a,0x001939d576d437b3,0x00d709e598bf9fe6,0x00a885b34bd2ee9e,0x00dd4b5c08ab1a50,0x0091bebd50b55639,0x00cf79ff64acdbc6,0x006067a39d826336)},
{FIELD_LITERAL(0x009a4b8d486fffbc,0x00458102d00ef9b4,0x00f498293b3cfdf0,0x00ed2d7b960b1b92,0x00ce3cd6c68fc137,0x004b60f431eccf99,0x00081efbe9e7e2b8,0x00a36f0ae7981133)},
{FIELD_LITERAL(0x0006918f5dfce6dc,0x00d4bf1c793c57fb,0x0069a3f649435364,0x00e89a50e5b0cd6e,0x00b9f6a237e973af,0x006d4ed8b104e41d,0x00498946a3924cd2,0x00c136ec5ac9d4f7)},
{FIELD_LITERAL(0x0051207abd179101,0x00fc2a5c20d9c5da,0x00fb9d5f2701b6df,0x002dd040fdea82b8,0x00f163b0738442ff,0x00d9736bd68855b8,0x00e0d8e93005e61c,0x00df5a40b3988570)},
{FIELD_LITERAL(0x00ee563d6f53acc9,0x00d465d2b5959acc,0x006575973bba26c8,0x00c9e4d84f81a1a3,0x00c3fbc4e8aa468a,0x0048149930eeaa11,0x008850a6f611000d,0x006709f6788337f9)},
{FIELD_LITERAL(0x00b373076597455f,0x00e83f1af53ac0f5,0x0041f63c01dc6840,0x0097dea19b0c6f4b,0x007f9d63b4c1572c,0x00e692d492d0f5f0,0x00cbcb392e83b4ad,0x0069c0f39ed9b1a8)},
{FIELD_LITERAL(0x00ab13af436bf8f4,0x000bcf0a0dac8574,0x00d50c864f705045,0x00c40e611debc842,0x0085010489bd5caa,0x007c5050acec026f,0x00f67d943c8da6d1,0x00de1da0278074c6)},
{FIELD_LITERAL(0x0079efcffed8f836,0x00604423802b5504,0x0070a6e294aab7dd,0x0020f75be15e7521,0x0062827c19bd5414,0x006738e425c48700,0x00dd37618fde0ffa,0x00bb2d65c01e1c3b)},
{FIELD_LITERAL(0x00c903ee6d825540,0x00add6c4cf98473e,0x007636efed4227f1,0x00905124ae55e772,0x00e6b38fab12ed53,0x0045e132b863fe55,0x003974662edb366a,0x00b1787052be8208)},
{FIELD_LITERAL(0x00e748cd7b5c52f2,0x00ea9df883f89cc3,0x0018970df156b6c7,0x00c5a46c2a33a847,0x00cbde395e32aa09,0x0072474ebb423140,0x00fb00053086a23d,0x001dafcfe22d4e1f)},
{FIELD_LITERAL(0x0059eb4ff288a383,0x00283876be3388ab,0x00bdd22974a2543b,0x0059eef0fe982d74,0x0097a5cf63dad778,0x004bc6002aebc99f,0x00c9a91d6118c690,0x0038364612a527ab)},
{FIELD_LITERAL(0x00006e34a35d9fbc,0x00eee4e48b2f019a,0x006b344743003a5f,0x00541d514f04a7e3,0x00e81f9ee7647455,0x005e2b916c438f81,0x00116f8137b7eff0,0x009bd3decc7039d1)},
{FIELD_LITERAL(0x0040f7e7c5b37bf2,0x0064e4dc81181bba,0x00a8767ae2a366b6,0x001496b4f90546f2,0x002a28493f860441,0x0021f59513049a3a,0x00852d369a8b7ee3,0x00dd2e7d8b7d30a9)},
{FIELD_LITERAL(0x00fa2dd90bcbeef2,0x00507d774710de2a,0x00b585ad10e7e373,0x0041f487e4b4f921,0x00191c9d8212f81d,0x001bc55cbdd8d474,0x0017954bdba8827b,0x0004d6d3a991ca44)},
{FIELD_LITERAL(0x00e38abece3c82ab,0x005a51f18a2c7a86,0x009dafa2e86d592e,0x00495a62eb688678,0x00b79df74c0eb212,0x0023e8cc78b75982,0x005998cb91075e13,0x00735aa9ba61bc76)},
{FIELD_LITERAL(0x00334f5303ea1222,0x00dfb3dbeb0a5d3e,0x002940d9592335c1,0x00706a7a63e8938a,0x005a533558bc4caf,0x00558e33192022a9,0x00970d9faf74c133,0x002979fcb63493ca)},
{FIELD_LITERAL(0x00260857d22419d7,0x005e0387d77651f0,0x008e0025ed2eb499,0x00c830b135804c2a,0x0037f43dbd3a77f6,0x008a4073d2f7379c,0x0072be0ce503ad58,0x00e6869d130c78be)},
{FIELD_LITERAL(0x00bfc5fa1e4ea21f,0x00c21d7b6bb892e6,0x00cf043f3acf0291,0x00c13f2f849b3c90,0x00d1a97ebef10891,0x0061e130a445e7fe,0x0019513fdedbf22b,0x001d60c813bff841)},
{FIELD_LITERAL(0x006e9f475cccf2ee,0x00454b9cd506430c,0x00224a4fb79ee479,0x0062e3347ef0b5e2,0x0034fd2a3512232a,0x00b8b3cb0f457046,0x00eb20165daa38ec,0x00128eebc2d9c0f7)},
{FIELD_LITERAL(0x00e6a9e38030fdec,0x001c23597bc14288,0x0097156a46356df1,0x00642048f0daca6a,0x003970a6e7955fd4,0x00a511e335e3cfc6,0x0054865756c85e31,0x00465f1ab66a6190)},
{FIELD_LITERAL(0x003e4964fa8a8fc8,0x00f6a1cdbcf41689,0x00943cb18fe7fda7,0x00606dafbf34440a,0x005d37a86399c789,0x00e79a2a69417403,0x00fe34f7e68b8866,0x0011f448ed2df10e)},
{FIELD_LITERAL(0x00c79e0b6d97dfbd,0x00917c71fd2bc6e8,0x00db7529ccfb63d8,0x00be5be957f17866,0x00a9e11fdc2cdac1,0x007b91a8e1f44443,0x00a3065e4057d80f,0x004825f5b8d5f6d4)},
{FIELD_LITERAL(0x000e0a81033e033b,0x00aec986ee821eab,0x00d1a4a48379273c,0x00609b79a9e06304,0x00e9618b4fe8f307,0x006ffdfa50b50969,0x009530224887ac0c,0x0020e7b36f0cef97)},
{FIELD_LITERAL(0x00fd579ffb691713,0x00b76af4f81c412d,0x00f239de96110f82,0x00e965fb437f0306,0x00ca7e9436900921,0x00e487f1325fa24a,0x00633907de476380,0x00721c62ac5b8ea0)},
{FIELD_LITERAL(0x00b37396c3320791,0x00fc7b67175c5783,0x00c36d2cd73ecc38,0x0080ebcc0b328fc5,0x0043a5b22b35d35d,0x00466c9f1713c9da,0x0026ad346dcaa8da,0x007c684e701183a6)},
{FIELD_LITERAL(0x003f2ab1abd14b06,0x00b129a8e8e37230,0x0048bc5b083d5c64,0x0002606c12933a98,0x00cf8051ceec1a73,0x00a755a8836c3ce6,0x002dabaa90ca4cb9,0x00b6e5525ddfc0f2)},
{FIELD_LITERAL(0x00c4a1fb48635413,0x00b5dd54423ad59f,0x009ff5d53fd24a88,0x003c98d267fc06a7,0x002db7cb20013641,0x00bd1d6716e191f2,0x006dbc8b29094241,0x0044bbf233dafa2c)},
{FIELD_LITERAL(0x00dff3103786ff34,0x000144553b1f20c3,0x0095613baeb930e4,0x00098058275ea5d4,0x007cd1402b046756,0x0074d74e4d58aee3,0x005f93fc343ff69b,0x00873df17296b3b0)},
{FIELD_LITERAL(0x00aa7c72be0ace19,0x004095d22fc37e4d,0x00a7d85f9e3b7c61,0x00ff21d344c9553c,0x00d105d6268e8b86,0x000616d733758845,0x003ecb4ba7210610,0x006a75e7dddc03b7)},
{FIELD_LITERAL(0x007860d99db787cf,0x00fda8983018f4a8,0x008c8866bac4743c,0x00ef471f84c82a3f,0x00abea5976d3b8e7,0x00714882896cd015,0x00b49fae584ddac5,0x008e33a1a0b69c81)},
{FIELD_LITERAL(0x000a9ee23c06881f,0x002c727d3d871945,0x00f47d971512d24a,0x00671e816f9ef31a,0x00883af2cfaad673,0x00601f98583d6c9a,0x00b435f5adc79655,0x00ad87b71c04bff2)},
{FIELD_LITERAL(0x0084911d36175613,0x00dbaa24427629dd,0x009b6f30b1554fc7,0x0026da093cf7ea9e,0x00eac4cfb8218c7c,0x00c4bde074231490,0x0089e5b5afb62587,0x0067fcb73adfdbcc)},
{FIELD_LITERAL(0x00eebfd4e2312cc3,0x00474b2564e4fc8c,0x003303ef14b1da9b,0x003c93e0e66beb1d,0x0013619b0566925a,0x008817c24d901bf3,0x00b62bd8898d218b,0x0075a7716f1e88a2)},
{FIELD_LITERAL(0x007f8a43da97dd5c,0x00058539c800fc7b,0x0040f3cf5a28414a,0x00d68dd0d95283d6,0x004adce9da90146e,0x00befa41c7d4f908,0x007603bc2e3c3060,0x00bdf360ab3545db)},
{FIELD_LITERAL(0x00f6de725e1976f0,0x00d96f80a02fda8a,0x00b25412a0e629fa,0x00c540e7e78fdb62,0x004ad02fb7336d3a,0x004922ae1bea5a3a,0x0026147d42d4bfeb,0x00d379a5bc4b94bc)},
{FIELD_LITERAL(0x00c338b915d8fef0,0x00a893292045c39a,0x0028ab4f2eba6887,0x0060743cb519fd61,0x0006213964093ac0,0x007c0b7a43f6266d,0x008e3557c4fa5bda,0x002da976de7b8d9d)},
{FIELD_LITERAL(0x0070047189452f4c,0x00f7ad12e1ce78d5,0x00af1ba51ec44a8b,0x005f39f63e667cd6,0x00058eac4648425e,0x00d7fdab42bea03b,0x0028576a5688de15,0x00af973209e77c10)},
{FIELD_LITERAL(0x00b78d6075749232,0x0001dc47a33b2cdc,0x0018c7b2e91b24f1,0x00b5bdc68f9876bd,0x0013f489ccba2b44,0x003b8846066128de,0x003d6252c8884dcf,0x00e3ae84b9908209)},
{FIELD_LITERAL(0x00aa2261022d883f,0x00ebcca4548010ac,0x002528512e28a437,0x0070ca7676b66082,0x0084bda170f7c6d3,0x00581b4747c9b8bb,0x005c96a01061c7e2,0x00fb7c4a362b5273)},
{FIELD_LITERAL(0x006366c380f7b574,0x001c7d1f09ff0438,0x003e20a7301f5b22,0x00d3efb1916d28f6,0x0049f4f81060ce83,0x00c69d91ea43ced1,0x002b6f3e5cd269ed,0x005b0fb22ce9ec65)},
{FIELD_LITERAL(0x003cffdf14aed2fd,0x009f0d77d7c5b2d9,0x004812ec41321d9f,0x008a1448bddf0916,0x008fef86030175df,0x00e3d703200a76c7,0x00d1babb470b2094,0x009f3a43b0e5828c)},
{FIELD_LITERAL(0x00a94700032a093f,0x0076e96c225216e7,0x00a63a4316e45f91,0x007d8bbb4645d3b2,0x00340a6ff22793eb,0x006f935d4572aeb7,0x00b1fb69f00afa28,0x009e8f3423161ed3)},
{FIELD_LITERAL(0x00ae307cf069f701,0x005859f222dd618b,0x00212d6c46ec0b0d,0x00a0fe4642afb62d,0x00420d8e4a0a8903,0x00a80ff639bdf7b0,0x0019bee1490b5d8e,0x007439e4b9c27a86)},
{FIELD_LITERAL(0x00610b6394a312e8,0x005aaa19d96160f5,0x008190e286138c4a,0x006538796a5cd53b,0x00fe28804432a97c,0x007315e011f55112,0x000bd4157d5acb9d,0x00d1b95469350336)},
{FIELD_LITERAL(0x0060db815bc4786c,0x006fab25beedc434,0x00c610d06084797c,0x000c48f08537bec0,0x0031aba51c5b93da,0x007968fa6e01f347,0x0030070da52840c6,0x00c043c225a4837f)},
{FIELD_LITERAL(0x0051cfcc5885377a,0x00dce566cb1803ca,0x00430c7643f2c7d4,0x00dce1a1337bdcc0,0x0010d5bd7283c128,0x003b1b547f9b46fe,0x000f245e37e770ab,0x007b72511f022b37)},
{FIELD_LITERAL(0x00e4302ff9b6116c,0x0092314b81d5f02a,0x000d31425f30702f,0x004946262e04213c,0x007ead9d19b6f9ed,0x001080a31ce8989f,0x001b632f36672a74,0x00a03933d9645a83)},
{FIELD_LITERAL(0x004a2902926f8d3f,0x00ad79b42637ab75,0x0088f60b90f2d4e8,0x0030f54ef0e398c4,0x00021dc9bf99681e,0x007ebf66fde74ee3,0x004ade654386e9a4,0x00e7485066be4c27)},
{FIELD_LITERAL(0x008940211aa0d633,0x00addae28136571d,0x00d68fdbba20d673,0x003bc6129bc9e21a,0x000346cf184ebe9a,0x0068774d741ebc7f,0x0019d5e9e6966557,0x0003cbd7f981b651)},
{FIELD_LITERAL(0x00bba0ed9c67c41f,0x00b30c8e225ba195,0x008bb5762a5cef18,0x00e0df31b06fb7cc,0x0018b912141991d5,0x00f6ed54e093eac2,0x0009e288264dbbb3,0x00feb663299b89ef)}
};
const gf API_NS(precomputed_wnaf_as_fe)[96]
VECTOR_ALIGNED = {
{FIELD_LITERAL(0x00cfc32590115acd,0x0079f0e2a5c7af1b,0x00dd94605b8d7332,0x0097dd6c75f5f3f3,0x00d9c59e36156de9,0x00edfbfd6cde47d7,0x0095b97c9f67c39a,0x007d7b90f587debc)},
{FIELD_LITERAL(0x00cfc32590115acd,0x0079f0e2a5c7af1b,0x00dd94605b8d7332,0x0017dd6c75f5f3f3,0x00d9c59e36156de8,0x00edfbfd6cde47d7,0x0095b97c9f67c39a,0x00fd7b90f587debc)},
{FIELD_LITERAL(0x001071dd4d8ae672,0x004f14ebe5f4f174,0x00e0987625c34c73,0x0092d00712c6f8c1,0x009ef424965e980b,0x00a8e0cf9369764b,0x000aa81907b4d207,0x00d5002c74d37924)},
{FIELD_LITERAL(0x00f3c4efe62b8b17,0x001e6acc1b6add7b,0x003367ef45836df5,0x000efc2d87a6ba53,0x00405a96933964ca,0x00572c2ae16357c6,0x00a9dc34ba6a7946,0x00151831e32ad161)},
{FIELD_LITERAL(0x00315f0372d1774a,0x007de9ed2960e79d,0x008b3d7c4c198add,0x00a5e6a45fa57892,0x00f32201aa80115a,0x007fb9386a433a1a,0x00abf6960b291ee6,0x002d8069294ebc2a)},
{FIELD_LITERAL(0x00fa5e878ae22827,0x00d33c7bb3963bd0,0x0053401a101efac6,0x0063df0bcbce59a5,0x007bca269c8b584b,0x00611a8a9978842c,0x00bb96e8da12b8a8,0x00e17844d01d394d)},
{FIELD_LITERAL(0x00c107c50e9b4d0d,0x00f6b65a5fada2f2,0x000bb67e79353fae,0x0018853f610ed92d,0x008c51f4d36d6915,0x00e3e9c096dd1c12,0x009d6b9ea6cde415,0x00304864dd66f4c6)},
{FIELD_LITERAL(0x00f3123b214085fb,0x00d005bafffb8f53,0x00d1606987dfe6ea,0x00e825edf73b018d,0x0082aa733829a933,0x00c857d8d7830d76,0x00ebdb8d2cbbe7e6,0x0063de0e9930722e)},
{FIELD_LITERAL(0x004ffebce35619ab,0x00d281a1543365c5,0x00ad17eeb3d098b8,0x008653b06bb7806d,0x0040026e64a28b62,0x00d9e06d52ea19df,0x008e7c684856876a,0x003ebbc191443f3b)},
{FIELD_LITERAL(0x00c0a062813b8884,0x0054d18cc36e636b,0x00e4493fcadba51a,0x005cda5b6577c9cf,0x00cc165615c315cf,0x001bbd5e155f17bb,0x004dee92a4f18e47,0x003e95412929bfb8)},
{FIELD_LITERAL(0x0015326f3e1f5fb6,0x0076886ca4eb6041,0x00fb34645ee36c23,0x006042a4cb8f7bb2,0x00b43e736403dd2f,0x00a8986566e7c60c,0x0010ea48904bf6d1,0x008b5ae8c5ddafbe)},
{FIELD_LITERAL(0x003a9f4a12faee9a,0x00e6ba523a29af6b,0x001dde79a8ef06ef,0x0033ed4361647314,0x00b0556ae76eb1c9,0x00e8b892762bd092,0x004709c83705e374,0x0077382d86f79b47)},
{FIELD_LITERAL(0x006638c5cee4113d,0x005c100c7276ed52,0x00d10562e281768d,0x0008e851e1eb2ed9,0x00d7cc086a7af373,0x00993ed528eb7942,0x0051677625b7df14,0x0029fbbcf6aaa3f7)},
{FIELD_LITERAL(0x001081503e396419,0x007a2c7aa8870415,0x00d372a4baf3490a,0x00b18821a1e18013,0x00b83fa876c54211,0x00e4bcf47a2ae1e9,0x0069a384ba9bf3c3,0x00b784d44ee9d468)},
{FIELD_LITERAL(0x00b4e3ad7c2ea1be,0x009962715cf7008a,0x00fbc6fdcc089d5e,0x001e29847c349313,0x00c1145569b3874d,0x0094f50069a1499b,0x004cec2bb8f423c8,0x0077eb0034c34627)},
{FIELD_LITERAL(0x008f00d279b21a44,0x00a5c81149c8116a,0x00cc8be3da721e9f,0x001935a34e6770b9,0x00e315426d5db99d,0x00cf6a842aff01bf,0x00e3cc9d5016ed3a,0x00ae78776098742d)},
{FIELD_LITERAL(0x0068db473197248f,0x0089874a12ff90c2,0x00420b4763f5428c,0x00d668b71fb38392,0x0022279b6d3c3687,0x003a5801405cf566,0x00127b8ea4b4fd44,0x00ce6a975208fb79)},
{FIELD_LITERAL(0x00797ca039d44238,0x0063cae935b6ef5e,0x006a938e072ff87c,0x006a3870309cdca0,0x0003800945fa3ddc,0x0032274c0728b5ad,0x0053a51e9217da91,0x00162b41712b79db)},
{FIELD_LITERAL(0x000911f06768bdc6,0x00bd27650f82c5b0,0x007b948017bcb94a,0x0095de039572c65e,0x0053743dabe00d25,0x0092b1d5888cd8cd,0x0065c6496b33c0d0,0x007a3f55d5bfb370)},
{FIELD_LITERAL(0x003f31eebfa20d27,0x00b1c0c84d6c2849,0x00dbefe8d1e53924,0x00472400b407ebc2,0x00c584bf62a91498,0x00c1f095f2010650,0x007e3b1b2c9ba41e,0x003189f894ed89dc)},
{FIELD_LITERAL(0x004d9eefe5de7ab7,0x003e35169bdbd884,0x0079625f58822d97,0x0043f4f607137c15,0x0029efd80717d455,0x0055b37a66623198,0x00153cecd460c01e,0x000464f30e396a2d)},
{FIELD_LITERAL(0x0057b28375dc4b6e,0x00771e6557974d80,0x00fa6792bc187316,0x000d7fed0f9f92d7,0x00e821281efdb64b,0x00a12bf7b4dc5064,0x00464f56bfa9bb8d,0x00526fa933114e0b)},
{FIELD_LITERAL(0x00bcf86d6aaed0f2,0x00b95ff679e8a71f,0x00c11d7bd57f8c87,0x00cb3362ed671b05,0x0068bb14b2ce4c10,0x00505313699af32f,0x005376e4cec89e51,0x00179b292d918f75)},
{FIELD_LITERAL(0x00246e4ca8018aa1,0x005e55abb4eaca63,0x0050b6ce5fe6aa8b,0x008979edb01ee510,0x002e152c38461080,0x00550a03a7f073ea,0x0018d841eb811e13,0x00c39e3e1ea88479)},
{FIELD_LITERAL(0x007f1264364f8cc7,0x000315388ba2d9ad,0x007562aa0a0d3396,0x0069318d20cfe53a,0x000acdcd1868b277,0x008e8d738518c6b8,0x006faf89fda8f887,0x00347e30277c4e4d)},
{FIELD_LITERAL(0x0062c03567cddf30,0x0032ee53437ac23b,0x00e8a6fbf62d80e2,0x002de89967f7d7fd,0x0005fedae4d7c736,0x0022d685f264ae39,0x0028936d3fba7df5,0x00acb4383b936fcc)},
{FIELD_LITERAL(0x00afee55215c8c25,0x00c57a8713769fcb,0x000df59aca05928e,0x00aead2ce1a57830,0x00d453e3719735cd,0x004f1cdc24b3ec7e,0x000e2a69482a51da,0x00151ba7f6834b1f)},
{FIELD_LITERAL(0x003eaec329954173,0x00fec61feee76bb2,0x009b544347f7f444,0x004c4f7dfdb8cebd,0x0039d610da25dbfb,0x000f513ccef26480,0x00af4ddd8b8d2732,0x00093756dd2be04b)},
{FIELD_LITERAL(0x006df537f064f2de,0x0007f0808cbfedb9,0x00792c87b64aa829,0x00fd42b4ce848ad1,0x004d9b9c66c5bd43,0x00df8fbdd58c4ed6,0x00cbe5355fc7f34c,0x00abe6eb22995e4d)},
{FIELD_LITERAL(0x00ef8a330d9484e0,0x0044944dece8fbcc,0x0016b6e52d9d2586,0x00610b0b72d2c7b3,0x00766d88f8990f61,0x00ea7bc69494eefe,0x0050c07989360110,0x00db9fc3bfd96ee7)},
{FIELD_LITERAL(0x0069991db096c6b8,0x0008ebceed962ba0,0x00ef0053e2f37ae3,0x009917f3c8c9cb68,0x000e0b52fef39f4e,0x00ea378bf7b8f008,0x009ae2a16388995b,0x007ec77e628ee921)},
{FIELD_LITERAL(0x0062284cece6ad83,0x00e18536b7278c56,0x0005ab4b910698c5,0x009910472a4fd019,0x008ab4e2c6d75150,0x00fbd9d538d59094,0x0086482b65914fd9,0x00ced958acabfefd)},
{FIELD_LITERAL(0x00c6cb4ee3a8dac4,0x0010cf7120de0b91,0x001ab166385e9e67,0x007f2a8eca89b19c,0x008ae3d846b943da,0x0022c7631b161ed6,0x005e5d402e327b23,0x00d0518c1aeb64cd)},
{FIELD_LITERAL(0x000d45c95be55ebb,0x005f3dd26b911e70,0x00755171065eb066,0x00110b2864e644c9,0x00718a31c2d84e02,0x0059a255fc4d65d8,0x0026337c97b14eba,0x0061e127f33d128b)},
{FIELD_LITERAL(0x006ee9a82004b322,0x003eff4833aac2f9,0x00bb62f8a13b9833,0x008f9deff439b18f,0x00bc30790842de17,0x000bfe23b4868215,0x00addb504d09d19a,0x002e121c04a5bd41)},
{FIELD_LITERAL(0x004126ac2e668677,0x0046c12e8a5dbed7,0x0078e3a69c049c9a,0x0035d20dffeb5878,0x000a263e2f4cbcdc,0x00090a6bd7e724f5,0x00b33f6e0b6366f9,0x00175e7759f40060)},
{FIELD_LITERAL(0x0083b4b835838c18,0x00ac69ddefc68cb4,0x00749b220f1ba281,0x004052a50d7a193d,0x007138ee3a4e5e56,0x003099ccfedc8067,0x006e811c0e9aaed9,0x00bead0cc8101227)},
{FIELD_LITERAL(0x00cd3889dfcd0517,0x001bf78dcd1f43de,0x000898cbb491727a,0x00440c964893d55d,0x0075e0b9391ea8f2,0x00ec9732687fc960,0x008ca65c62f86bcf,0x00fc9b9aed6debcb)},
{FIELD_LITERAL(0x00f8381236cfa255,0x00f5999b0d8c8fe3,0x000918786a1dff4e,0x00a2fa46132db8c1,0x00eb0a0e8379a878,0x003802d2e990566a,0x00b6c65d27147f1f,0x00ddbb45f6bd3e66)},
{FIELD_LITERAL(0x000f68a71ee1c67a,0x00e96102429b052c,0x0017776482925329,0x00ca322a71577df6,0x004325b8a79280b5,0x00c322234d786f77,0x00e9258fe7816ab4,0x006aa915d16d5532)},
{FIELD_LITERAL(0x00cde18980fd9d30,0x00d1a82889350971,0x0040d36b7eb0fbc8,0x003cc6e695329dd0,0x00e24b3318e1d88e,0x00e212a22459111d,0x00879f754eaab372,0x00f9801f5489c9a4)},
{FIELD_LITERAL(0x007354e942e00768,0x004c7668d3208ac0,0x0015712e1b92023f,0x00b018106b3a760b,0x00d4751647fa130b,0x00da3f7276d78b5a,0x00dc6c71672bb3b3,0x0008a6ecb3540963)},
{FIELD_LITERAL(0x00e13a624c26a6f1,0x00e161c0e3c0e7d2,0x00ba563c13d354eb,0x00f7e67a8d51498c,0x0088c48bf9742e97,0x00edaca155c6abcb,0x00bb24561c4448b5,0x00d045b2c38b42f1)},
{FIELD_LITERAL(0x0093d57b9871b4c4,0x0085e6b5532e7970,0x0012fdda50bdb89e,0x0025f590d6c39b47,0x00ef9d53a39585e6,0x00cf0a88a575110b,0x00fd53552894850f,0x00bef47029c5a860)},
{FIELD_LITERAL(0x00bd40f701996dd3,0x00cce747044b6173,0x0028a6b9ffb55eb3,0x0009fea794bd40e3,0x0038b30e26ed0198,0x005434c968b4cf52,0x00814878df362d47,0x0060ab54842b207a)},
{FIELD_LITERAL(0x00bd19d97479e8ae,0x00f722fb96aff3e9,0x004ae4a83cc75c02,0x0033bb6827a30094,0x00d0ec294a83cb5a,0x007c9ad150cfeefa,0x0033cbbd6b336c57,0x009f0b2fd7ef1d8f)},
{FIELD_LITERAL(0x00246036b708c7d9,0x000574c8b9127116,0x00ecd349a550414d,0x003c900c0186da47,0x007c82512cac2d00,0x001399e41f99830b,0x00a414712d16fdfb,0x0028822961a9b698)},
{FIELD_LITERAL(0x00576abc9c32ae74,0x0052e8eedb433484,0x009a0b95b52551ff,0x00e4e5a4d5691aff,0x00bc01db07dccd79,0x00996692751e0d3c,0x003acf0cd9be9606,0x003f06d2f83095a8)},
{FIELD_LITERAL(0x0028c4051a1ff7bb,0x0040ba689904a0ad,0x009e4b0a5acec321,0x00bc6d2b3c46aaeb,0x00f2caae4ef88adb,0x00ff6677bf11a28e,0x0092191cbfbb7484,0x00dae55afb78a291)},
{FIELD_LITERAL(0x00c95aa397ea26bc,0x007372e21066c24c,0x00d1f1e17008ce70,0x00277c5b46d24ff5,0x00d0a187e51cc6f8,0x00e58d524dca3f92,0x000d1a618c916355,0x00e5b4a71cfce6eb)},
{FIELD_LITERAL(0x00c40cbcbd853cbd,0x00523f5879bd473a,0x00fc476ce8a57ceb,0x009e5cb521a8fc43,0x0015c157448e29cc,0x0041f2065e0e673d,0x00b9227183e9ca04,0x000eadc022da2a1a)},
{FIELD_LITERAL(0x00d6313aad8c08f2,0x008fbb11d8a39cbf,0x00bf09c856cfea1d,0x00cc7448724a5516,0x00eb6e4d59ecdeb7,0x005eda293019421c,0x00a0853a9e457996,0x00e2a1515c045530)},
{FIELD_LITERAL(0x009cc09c03622bf9,0x0018ec007f1fb5bc,0x009f39168f0d29de,0x005a83280f20e76e,0x000dbf95aaf9af43,0x004f9bd6f102397b,0x00e154febb2e86e9,0x0032ea079c3d6c54)},
{FIELD_LITERAL(0x00fab169ca1c41ce,0x00f1bc0ce1d78d41,0x002fa4e361cc67be,0x009053af427e0267,0x0032387ad15144f5,0x00b00ae64f9e66e4,0x006f6617ef82b37a,0x00d8c1db3c95b59e)},
{FIELD_LITERAL(0x0035175500c7799c,0x00a167c5ca225e38,0x00854efcf271c80b,0x001b76bf0a2fcd01,0x0095c90610cf4ccd,0x0064190fc6a738a8,0x0079dce31456ebff,0x00742f0847dc1855)},
{FIELD_LITERAL(0x00f8f4bbbe10d3b9,0x00105a4fd7fe5ef6,0x0040f473c119b520,0x0075981f4cbad167,0x00e6e94e0d05858a,0x00287e587009323c,0x00797d31a81a36e6,0x0033eef622def25c)},
{FIELD_LITERAL(0x003077e1410a5ba5,0x00b14158718390d3,0x006f256df630d95f,0x0021d4d1b388a47b,0x008e29fce3c3ea50,0x002616d810e8828f,0x0076b1173dc76902,0x001c4c4bfe1be552)},
{FIELD_LITERAL(0x00a2657cac024d24,0x00aa33dfb739670f,0x00093b53769a8de7,0x00adafcb28c0514d,0x00bca8890425c381,0x008f15acedcdc343,0x0085efa2bb2f9604,0x0092437292387955)},
{FIELD_LITERAL(0x00dfb010d979be8f,0x007e6d963a211f07,0x00404b8ec1368699,0x00d9cc6590cb2087,0x00e0d919b389e23c,0x001001c50cec349f,0x001e848fec709fe4,0x000e91e3326121a1)},
{FIELD_LITERAL(0x00e8300e632c6b13,0x00010847ef6dda78,0x0019b7c68f200ab7,0x00220c952978bd9b,0x0019e887adc0331c,0x006c5993f36c4db5,0x0002c98eeb248079,0x0089ad282231d922)},
{FIELD_LITERAL(0x0059811830606614,0x00a8ec4d8a0d0097,0x000e2ac957beaec2,0x007dc4a64fdb8ed1,0x0063b9462f2c7312,0x00324ea6a55d282b,0x007c8a4cbdc26507,0x00f54f4ae9268708)},
{FIELD_LITERAL(0x0026d312845ed7bc,0x0051563888e17918,0x00b99c696ccab084,0x0059d7244957f3b8,0x00c5f4faf8c8d6ab,0x00bdeeec54ba3f26,0x001aba0f7c9d5485,0x00d731f784b29269)},
{FIELD_LITERAL(0x00bd7234c3aef4f0,0x00a7a9f815db44b1,0x00c8c940e9fc9785,0x003b81a973b01c38,0x00c32ffd7d7b79f9,0x00bc5b783c46e6c6,0x00b003fb1ef6a5f9,0x005b36765c2b46e7)},
{FIELD_LITERAL(0x0030b09f9659a719,0x00ac35ad7a6bc959,0x009b466b281c1ee8,0x0034b96465f80acb,0x00304970c66162b7,0x000f2347253e3918,0x000d54980ac74c5a,0x00aaabb0e875468a)},
{FIELD_LITERAL(0x00578872f1bd6085,0x00b3fd4fa6efa597,0x00e99ac49f625c00,0x002aef842e5ed2d8,0x004b8f706588e353,0x00449c499dfcc096,0x008d0cdddbf18dea,0x00e6bba4a6396ddd)},
{FIELD_LITERAL(0x0066485d97a2ac73,0x001d0e768483ffe7,0x00c5253731b7251c,0x00f76d892a3af3f3,0x00e8d035f85298e7,0x0034e58d0abf961a,0x00b11bd0eccaba4c,0x0087a079aec9d0e9)},
{FIELD_LITERAL(0x00d38488bd2e2026,0x00d35414e79dc3fe,0x00faa0a1c1fbbbb9,0x0093df0c4b10ab45,0x0039ffebe1394c9f,0x00cab0bc80e5cd5c,0x00453b9db5cadf06,0x003b7c08cb56f96e)},
{FIELD_LITERAL(0x00b63453c7af61ee,0x00eadcbafa2bd320,0x0086b04f4a7bf0e3,0x00b69bc8cbbfba5a,0x00ce4926bb1b064e,0x004df8ce753e0a27,0x00ff37bf2580a3a2,0x00ad90c8c5a377eb)},
{FIELD_LITERAL(0x00ac58c82bdd6e72,0x0008035e278a79da,0x003c9fcc92524fb3,0x000c71c26ea75e47,0x009631c4be717b38,0x00a2e968135e9152,0x00074295ca131ec2,0x00877a203d4a5015)},
{FIELD_LITERAL(0x00a49896f002be26,0x00ad6b0d720ae906,0x005786d8dbed0346,0x00f6749d6592e372,0x000542c37faf79a4,0x003281a4f5c7863a,0x00eacdc7def0cbdc,0x00ca8353efe160bd)},
{FIELD_LITERAL(0x003c9e851d9f8893,0x004df23c1696dd28,0x005e587fddb98f95,0x00359afa5adbfdbb,0x00ddb949d26e687c,0x00ebc6efd285564c,0x001750eec619bdd3,0x0037772e4ad0d4fa)},
{FIELD_LITERAL(0x0076e84babbbb048,0x000a6db83681bbe4,0x0059dff597eaead2,0x00f65bdd79fe2dab,0x00e3fc9faa642c8a,0x008a9cc9dfc634c9,0x00428a4b728b1cd4,0x00e80aea53cb6617)},
{FIELD_LITERAL(0x002ab17fdf7d2bd3,0x005aa55f23183393,0x009b88469f8c0eb9,0x007d101b314bca6b,0x0056dd4345fd97b9,0x00880e62e548ae7d,0x003d44d8c87b91a6,0x00fb2811386e22cc)},
{FIELD_LITERAL(0x00eacd58001be3a5,0x0014e1231ca72940,0x0022453384987584,0x0075848f0c37be5c,0x000e6dc40d82c0b2,0x00f4d8ec1270878c,0x00550981d6fb86fd,0x00bb66b58f4c6892)},
{FIELD_LITERAL(0x00bba772e57e297f,0x004f56f68df71b07,0x00ded9facaf23a81,0x00d78e832d78eedc,0x0004f7c3eff02685,0x00ba5fa931f9c020,0x005a29fb4b2295be,0x00e2543f745b1dc9)},
{FIELD_LITERAL(0x00712177652580f9,0x00e9ee16e21d1eca,0x0002465ba75b8e46,0x00a9cb7b1fc8ef2e,0x00ce337e6da1cf8e,0x009d3684c507fffa,0x00058cc115d71214,0x0017dba81e144377)},
{FIELD_LITERAL(0x003b778e67285805,0x00dbb06704ba87b5,0x00ba6ee1ea5ea2fe,0x00e2cdc2c8b3f699,0x006983c6eae69a9c,0x00c6c8c542d0c398,0x00f2d3a9ebcedbdc,0x00be30ddeabbd31c)},
{FIELD_LITERAL(0x0095f20a016490a6,0x005f2b00b9fbf26d,0x00b583124906cdaf,0x002e2077aa473ca8,0x0018c5b9f7902fa6,0x00b704f5229201a6,0x00e1fc5d70e4b1c2,0x00578e366ccf7289)},
{FIELD_LITERAL(0x00932127be1d579d,0x00e6729f50f54904,0x00e70f6247f618af,0x00b1953989fe9d9c,0x0015032e9df69633,0x00d3687b35cb6e82,0x00ab0fff86869218,0x0026054a3a68ddfb)},
{FIELD_LITERAL(0x00cf244d2e899137,0x00a793f52ec7aaa1,0x002e5cb0616e3883,0x009cbf752f176feb,0x0029edce4fa090a3,0x00f6540a960a0275,0x00513985eef0e3bc,0x00ce2e586f6c7228)},
{FIELD_LITERAL(0x00b42f011dbc757c,0x004a8e19d4f07c42,0x00a6d7828318b7ff,0x0004c9ce49ba3c0f,0x005fe71688087b6a,0x006e1d8f9a3d84ed,0x0089693e7e8e9a1f,0x0073bf4183ba45c5)},
{FIELD_LITERAL(0x0029e8ce35530d30,0x00d20f389f61fe3a,0x00cf9e8ddf74e1d4,0x004bec01b04d4979,0x007d92c9f6fd5ddd,0x00c072fa91981808,0x009afda4fe8a1676,0x00c96522ee879a14)},
{FIELD_LITERAL(0x005f0cd9cd83497b,0x00e382f098d97f00,0x0073e37e004eed2e,0x000707fe98b12237,0x0016d92a2b73d561,0x00a42926ab390165,0x00b394db4b1cc8fc,0x002fa14a3f6efa33)},
{FIELD_LITERAL(0x0055076a513d05ee,0x00f076d43cec14ad,0x00a4e386b252faf4,0x00c0713b79b313eb,0x00507efa72f46f19,0x00141bc1e7c66844,0x005629ef060c19ea,0x0085327113d1772c)},
{FIELD_LITERAL(0x00ed490108514e35,0x006bed897e6b4958,0x0000f2cae0dc546c,0x008175eb3e5008e4,0x0093e3fe8f3aed42,0x00e9dbc15fd54d1a,0x00844979a4cfc0c1,0x00ea3194d64ea60b)},
{FIELD_LITERAL(0x00b64d054ec7ed5c,0x007b924cd329fbce,0x00fe8805a8737293,0x00fb82f1d52b43ae,0x004ea745c72e1a76,0x0095ba2552861c0c,0x00f66846c3547784,0x003b815bd05dc23c)},
{FIELD_LITERAL(0x00669e32fd197ef7,0x001dfca2c5e2f7c9,0x00a2ae0964a1e5e2,0x00b4334b15c91232,0x0096419585110d96,0x009c0b2262172a58,0x009d7c87cf6d35ca,0x008a5ce50d3cabf6)},
{FIELD_LITERAL(0x00888b9c1cf73530,0x00375346c6afecd2,0x00142240b35b74d3,0x00d952835f86a5f5,0x000665c2658eaf9a,0x00f29f43062b2033,0x00a19a58c5bc85f9,0x00e62ac95724a937)},
{FIELD_LITERAL(0x003bedc9ae9d1730,0x00fedd7c04cbc775,0x00c19abc4540c61d,0x00115294c57fb687,0x00663fceb174cd8f,0x001671f572b885b0,0x002d14694ed85978,0x00127282078a8e44)},
{FIELD_LITERAL(0x00e6d2822aa72eca,0x00d832957cdc0058,0x00dc60e5bed23e18,0x00b94b4c418b03a3,0x00df3b85d410a430,0x0055e81b70bc79d4,0x00081d9369cbd1a0,0x00f7fee3acf0c656)},
{FIELD_LITERAL(0x003baba41b5abffb,0x00661ee09fca8193,0x00e0c6c92e6aea59,0x00886c207bcbe591,0x00aef9e7798e8004,0x00164f599f4d707a,0x00bb1597a76d21f2,0x00fda82d5e025626)},
{FIELD_LITERAL(0x00552b53a9640f0e,0x005985236f4d88bf,0x00b7aaec965a8ae5,0x00cedada7b5ccf95,0x007b1ea2088f1902,0x0028445e38b4a7fa,0x0057f10ddc50efed,0x007637a3147bc5cb)},
{FIELD_LITERAL(0x008174fe4db53757,0x00930c4f4a35ecc8,0x000e9f82c1c95a8f,0x00c6480547d66e5e,0x00dce888f9a7bf39,0x006671a5022cb906,0x004823c19b5337a0,0x00455338b7fec529)},
{FIELD_LITERAL(0x005ac123fdc45964,0x00395057c2221d17,0x003c09c74cf84eb1,0x00b5ca859bbebf9d,0x001b26b274a7d235,0x00e8c63508e96a48,0x00edbce4d51d721e,0x00c49436797d6f83)},
{FIELD_LITERAL(0x0071595be88a7f40,0x00a05e6ac1c0fc87,0x00a01bf6538b29eb,0x00badcd80b881fb8,0x005bfe7af8049f8b,0x0084918e6ae35537,0x00ed4bd54759316e,0x007f135988d6b548)},
{FIELD_LITERAL(0x0075656c41e06629,0x0086059d83396637,0x004f304ecb457b37,0x00e3b4887db6be65,0x0020b54c263bb0be,0x0060a69193e561c3,0x00e6863f20dc8ce9,0x00afe16ac56e6478)}
};

View File

@ -0,0 +1,326 @@
/**
* @file ed448goldilocks/eddsa.c
* @author Mike Hamburg
*
* @copyright
* Copyright (c) 2015-2016 Cryptography Research, Inc. \n
* Released under the MIT License. See LICENSE.txt for license information.
*
* @cond internal
* @brief EdDSA routines.
*
* @warning This file was automatically generated in Python.
* Please do not edit it.
*/
#include "word.h"
#include <decaf/ed448.h>
#include <decaf/shake.h>
#include <decaf/sha512.h>
#include <string.h>
#define API_NAME "cryptonite_decaf_448"
#define API_NS(_id) cryptonite_decaf_448_##_id
#define hash_ctx_t cryptonite_decaf_shake256_ctx_t
#define hash_init cryptonite_decaf_shake256_init
#define hash_update cryptonite_decaf_shake256_update
#define hash_final cryptonite_decaf_shake256_final
#define hash_destroy cryptonite_decaf_shake256_destroy
#define hash_hash cryptonite_decaf_shake256_hash
#define NO_CONTEXT CRYPTONITE_DECAF_EDDSA_448_SUPPORTS_CONTEXTLESS_SIGS
#define EDDSA_USE_SIGMA_ISOGENY 0
#define COFACTOR 4
#if NO_CONTEXT
const uint8_t CRYPTONITE_NO_CONTEXT_POINTS_HERE = 0;
const uint8_t * const CRYPTONITE_DECAF_ED448_NO_CONTEXT = &CRYPTONITE_NO_CONTEXT_POINTS_HERE;
#endif
/* EDDSA_BASE_POINT_RATIO = 1 or 2
* Because EdDSA25519 is not on E_d but on the isogenous E_sigma_d,
* its base point is twice ours.
*/
#define EDDSA_BASE_POINT_RATIO (1+EDDSA_USE_SIGMA_ISOGENY)
static void clamp (
uint8_t secret_scalar_ser[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES]
) {
/* Blarg */
secret_scalar_ser[0] &= -COFACTOR;
uint8_t hibit = (1<<0)>>1;
if (hibit == 0) {
secret_scalar_ser[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES - 1] = 0;
secret_scalar_ser[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES - 2] |= 0x80;
} else {
secret_scalar_ser[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES - 1] &= hibit-1;
secret_scalar_ser[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES - 1] |= hibit;
}
}
static void hash_init_with_dom(
hash_ctx_t hash,
uint8_t prehashed,
uint8_t for_prehash,
const uint8_t *context,
uint8_t context_len
) {
hash_init(hash);
#if NO_CONTEXT
if (context_len == 0 && context == CRYPTONITE_DECAF_ED448_NO_CONTEXT) {
(void)prehashed;
(void)for_prehash;
(void)context;
(void)context_len;
return;
}
#endif
const char *dom_s = "SigEd448";
const uint8_t dom[2] = {2+word_is_zero(prehashed)+word_is_zero(for_prehash), context_len};
hash_update(hash,(const unsigned char *)dom_s, strlen(dom_s));
hash_update(hash,dom,2);
hash_update(hash,context,context_len);
}
void cryptonite_decaf_ed448_prehash_init (
hash_ctx_t hash
) {
hash_init(hash);
}
/* In this file because it uses the hash */
void cryptonite_decaf_ed448_convert_private_key_to_x448 (
uint8_t x[CRYPTONITE_DECAF_X448_PRIVATE_BYTES],
const uint8_t ed[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES]
) {
/* pass the private key through hash_hash function */
/* and keep the first CRYPTONITE_DECAF_X448_PRIVATE_BYTES bytes */
hash_hash(
x,
CRYPTONITE_DECAF_X448_PRIVATE_BYTES,
ed,
CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES
);
}
void cryptonite_decaf_ed448_derive_public_key (
uint8_t pubkey[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES],
const uint8_t privkey[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES]
) {
/* only this much used for keygen */
uint8_t secret_scalar_ser[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES];
hash_hash(
secret_scalar_ser,
sizeof(secret_scalar_ser),
privkey,
CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES
);
clamp(secret_scalar_ser);
API_NS(scalar_t) secret_scalar;
API_NS(scalar_decode_long)(secret_scalar, secret_scalar_ser, sizeof(secret_scalar_ser));
/* Since we are going to mul_by_cofactor during encoding, divide by it here.
* However, the EdDSA base point is not the same as the decaf base point if
* the sigma isogeny is in use: the EdDSA base point is on Etwist_d/(1-d) and
* the decaf base point is on Etwist_d, and when converted it effectively
* picks up a factor of 2 from the isogenies. So we might start at 2 instead of 1.
*/
for (unsigned int c = EDDSA_BASE_POINT_RATIO; c < COFACTOR; c <<= 1) {
API_NS(scalar_halve)(secret_scalar,secret_scalar);
}
API_NS(point_t) p;
API_NS(precomputed_scalarmul)(p,API_NS(precomputed_base),secret_scalar);
API_NS(point_mul_by_cofactor_and_encode_like_eddsa)(pubkey, p);
/* Cleanup */
API_NS(scalar_destroy)(secret_scalar);
API_NS(point_destroy)(p);
cryptonite_decaf_bzero(secret_scalar_ser, sizeof(secret_scalar_ser));
}
void cryptonite_decaf_ed448_sign (
uint8_t signature[CRYPTONITE_DECAF_EDDSA_448_SIGNATURE_BYTES],
const uint8_t privkey[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES],
const uint8_t pubkey[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES],
const uint8_t *message,
size_t message_len,
uint8_t prehashed,
const uint8_t *context,
uint8_t context_len
) {
API_NS(scalar_t) secret_scalar;
hash_ctx_t hash;
{
/* Schedule the secret key */
struct {
uint8_t secret_scalar_ser[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES];
uint8_t seed[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES];
} __attribute__((packed)) expanded;
hash_hash(
(uint8_t *)&expanded,
sizeof(expanded),
privkey,
CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES
);
clamp(expanded.secret_scalar_ser);
API_NS(scalar_decode_long)(secret_scalar, expanded.secret_scalar_ser, sizeof(expanded.secret_scalar_ser));
/* Hash to create the nonce */
hash_init_with_dom(hash,prehashed,0,context,context_len);
hash_update(hash,expanded.seed,sizeof(expanded.seed));
hash_update(hash,message,message_len);
cryptonite_decaf_bzero(&expanded, sizeof(expanded));
}
/* Decode the nonce */
API_NS(scalar_t) nonce_scalar;
{
uint8_t nonce[2*CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES];
hash_final(hash,nonce,sizeof(nonce));
API_NS(scalar_decode_long)(nonce_scalar, nonce, sizeof(nonce));
cryptonite_decaf_bzero(nonce, sizeof(nonce));
}
uint8_t nonce_point[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES] = {0};
{
/* Scalarmul to create the nonce-point */
API_NS(scalar_t) nonce_scalar_2;
API_NS(scalar_halve)(nonce_scalar_2,nonce_scalar);
for (unsigned int c = 2*EDDSA_BASE_POINT_RATIO; c < COFACTOR; c <<= 1) {
API_NS(scalar_halve)(nonce_scalar_2,nonce_scalar_2);
}
API_NS(point_t) p;
API_NS(precomputed_scalarmul)(p,API_NS(precomputed_base),nonce_scalar_2);
API_NS(point_mul_by_cofactor_and_encode_like_eddsa)(nonce_point, p);
API_NS(point_destroy)(p);
API_NS(scalar_destroy)(nonce_scalar_2);
}
API_NS(scalar_t) challenge_scalar;
{
/* Compute the challenge */
hash_init_with_dom(hash,prehashed,0,context,context_len);
hash_update(hash,nonce_point,sizeof(nonce_point));
hash_update(hash,pubkey,CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES);
hash_update(hash,message,message_len);
uint8_t challenge[2*CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES];
hash_final(hash,challenge,sizeof(challenge));
hash_destroy(hash);
API_NS(scalar_decode_long)(challenge_scalar,challenge,sizeof(challenge));
cryptonite_decaf_bzero(challenge,sizeof(challenge));
}
API_NS(scalar_mul)(challenge_scalar,challenge_scalar,secret_scalar);
API_NS(scalar_add)(challenge_scalar,challenge_scalar,nonce_scalar);
cryptonite_decaf_bzero(signature,CRYPTONITE_DECAF_EDDSA_448_SIGNATURE_BYTES);
memcpy(signature,nonce_point,sizeof(nonce_point));
API_NS(scalar_encode)(&signature[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES],challenge_scalar);
API_NS(scalar_destroy)(secret_scalar);
API_NS(scalar_destroy)(nonce_scalar);
API_NS(scalar_destroy)(challenge_scalar);
}
void cryptonite_decaf_ed448_sign_prehash (
uint8_t signature[CRYPTONITE_DECAF_EDDSA_448_SIGNATURE_BYTES],
const uint8_t privkey[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES],
const uint8_t pubkey[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES],
const cryptonite_decaf_ed448_prehash_ctx_t hash,
const uint8_t *context,
uint8_t context_len
) {
uint8_t hash_output[64]; /* MAGIC but true for all existing schemes */
{
cryptonite_decaf_ed448_prehash_ctx_t hash_too;
memcpy(hash_too,hash,sizeof(hash_too));
hash_final(hash_too,hash_output,sizeof(hash_output));
hash_destroy(hash_too);
}
cryptonite_decaf_ed448_sign(signature,privkey,pubkey,hash_output,sizeof(hash_output),1,context,context_len);
cryptonite_decaf_bzero(hash_output,sizeof(hash_output));
}
cryptonite_decaf_error_t cryptonite_decaf_ed448_verify (
const uint8_t signature[CRYPTONITE_DECAF_EDDSA_448_SIGNATURE_BYTES],
const uint8_t pubkey[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES],
const uint8_t *message,
size_t message_len,
uint8_t prehashed,
const uint8_t *context,
uint8_t context_len
) {
API_NS(point_t) pk_point, r_point;
cryptonite_decaf_error_t error = API_NS(point_decode_like_eddsa_and_ignore_cofactor)(pk_point,pubkey);
if (CRYPTONITE_DECAF_SUCCESS != error) { return error; }
error = API_NS(point_decode_like_eddsa_and_ignore_cofactor)(r_point,signature);
if (CRYPTONITE_DECAF_SUCCESS != error) { return error; }
API_NS(scalar_t) challenge_scalar;
{
/* Compute the challenge */
hash_ctx_t hash;
hash_init_with_dom(hash,prehashed,0,context,context_len);
hash_update(hash,signature,CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES);
hash_update(hash,pubkey,CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES);
hash_update(hash,message,message_len);
uint8_t challenge[2*CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES];
hash_final(hash,challenge,sizeof(challenge));
hash_destroy(hash);
API_NS(scalar_decode_long)(challenge_scalar,challenge,sizeof(challenge));
cryptonite_decaf_bzero(challenge,sizeof(challenge));
}
API_NS(scalar_sub)(challenge_scalar, API_NS(scalar_zero), challenge_scalar);
API_NS(scalar_t) response_scalar;
API_NS(scalar_decode_long)(
response_scalar,
&signature[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES],
CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES
);
#if EDDSA_BASE_POINT_RATIO == 2
API_NS(scalar_add)(response_scalar,response_scalar,response_scalar);
#endif
/* pk_point = -c(x(P)) + (cx + k)G = kG */
API_NS(base_double_scalarmul_non_secret)(
pk_point,
response_scalar,
pk_point,
challenge_scalar
);
return cryptonite_decaf_succeed_if(API_NS(point_eq(pk_point,r_point)));
}
cryptonite_decaf_error_t cryptonite_decaf_ed448_verify_prehash (
const uint8_t signature[CRYPTONITE_DECAF_EDDSA_448_SIGNATURE_BYTES],
const uint8_t pubkey[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES],
const cryptonite_decaf_ed448_prehash_ctx_t hash,
const uint8_t *context,
uint8_t context_len
) {
cryptonite_decaf_error_t ret;
uint8_t hash_output[64]; /* MAGIC but true for all existing schemes */
{
cryptonite_decaf_ed448_prehash_ctx_t hash_too;
memcpy(hash_too,hash,sizeof(hash_too));
hash_final(hash_too,hash_output,sizeof(hash_output));
hash_destroy(hash_too);
}
ret = cryptonite_decaf_ed448_verify(signature,pubkey,hash_output,sizeof(hash_output),1,context,context_len);
return ret;
}

View File

@ -0,0 +1,341 @@
/**
* @file ed448goldilocks/scalar.c
* @author Mike Hamburg
*
* @copyright
* Copyright (c) 2015-2016 Cryptography Research, Inc. \n
* Released under the MIT License. See LICENSE.txt for license information.
*
* @brief Decaf high-level functions.
*
* @warning This file was automatically generated in Python.
* Please do not edit it.
*/
#include "word.h"
#include "constant_time.h"
#include <decaf.h>
/* Template stuff */
#define API_NS(_id) cryptonite_decaf_448_##_id
#define SCALAR_BITS CRYPTONITE_DECAF_448_SCALAR_BITS
#define SCALAR_SER_BYTES CRYPTONITE_DECAF_448_SCALAR_BYTES
#define SCALAR_LIMBS CRYPTONITE_DECAF_448_SCALAR_LIMBS
#define scalar_t API_NS(scalar_t)
static const cryptonite_decaf_word_t MONTGOMERY_FACTOR = (cryptonite_decaf_word_t)0x3bd440fae918bc5ull;
static const scalar_t sc_p = {{{
SC_LIMB(0x2378c292ab5844f3), SC_LIMB(0x216cc2728dc58f55), SC_LIMB(0xc44edb49aed63690), SC_LIMB(0xffffffff7cca23e9), SC_LIMB(0xffffffffffffffff), SC_LIMB(0xffffffffffffffff), SC_LIMB(0x3fffffffffffffff)
}}}, sc_r2 = {{{
SC_LIMB(0xe3539257049b9b60), SC_LIMB(0x7af32c4bc1b195d9), SC_LIMB(0x0d66de2388ea1859), SC_LIMB(0xae17cf725ee4d838), SC_LIMB(0x1a9cc14ba3c47c44), SC_LIMB(0x2052bcb7e4d070af), SC_LIMB(0x3402a939f823b729)
}}};
/* End of template stuff */
#define WBITS CRYPTONITE_DECAF_WORD_BITS /* NB this may be different from ARCH_WORD_BITS */
const scalar_t API_NS(scalar_one) = {{{1}}}, API_NS(scalar_zero) = {{{0}}};
/** {extra,accum} - sub +? p
* Must have extra <= 1
*/
static CRYPTONITE_DECAF_NOINLINE void sc_subx(
scalar_t out,
const cryptonite_decaf_word_t accum[SCALAR_LIMBS],
const scalar_t sub,
const scalar_t p,
cryptonite_decaf_word_t extra
) {
cryptonite_decaf_dsword_t chain = 0;
unsigned int i;
for (i=0; i<SCALAR_LIMBS; i++) {
chain = (chain + accum[i]) - sub->limb[i];
out->limb[i] = chain;
chain >>= WBITS;
}
cryptonite_decaf_word_t borrow = chain+extra; /* = 0 or -1 */
chain = 0;
for (i=0; i<SCALAR_LIMBS; i++) {
chain = (chain + out->limb[i]) + (p->limb[i] & borrow);
out->limb[i] = chain;
chain >>= WBITS;
}
}
static CRYPTONITE_DECAF_NOINLINE void sc_montmul (
scalar_t out,
const scalar_t a,
const scalar_t b
) {
unsigned int i,j;
cryptonite_decaf_word_t accum[SCALAR_LIMBS+1] = {0};
cryptonite_decaf_word_t hi_carry = 0;
for (i=0; i<SCALAR_LIMBS; i++) {
cryptonite_decaf_word_t mand = a->limb[i];
const cryptonite_decaf_word_t *mier = b->limb;
cryptonite_decaf_dword_t chain = 0;
for (j=0; j<SCALAR_LIMBS; j++) {
chain += ((cryptonite_decaf_dword_t)mand)*mier[j] + accum[j];
accum[j] = chain;
chain >>= WBITS;
}
accum[j] = chain;
mand = accum[0] * MONTGOMERY_FACTOR;
chain = 0;
mier = sc_p->limb;
for (j=0; j<SCALAR_LIMBS; j++) {
chain += (cryptonite_decaf_dword_t)mand*mier[j] + accum[j];
if (j) accum[j-1] = chain;
chain >>= WBITS;
}
chain += accum[j];
chain += hi_carry;
accum[j-1] = chain;
hi_carry = chain >> WBITS;
}
sc_subx(out, accum, sc_p, sc_p, hi_carry);
}
void API_NS(scalar_mul) (
scalar_t out,
const scalar_t a,
const scalar_t b
) {
sc_montmul(out,a,b);
sc_montmul(out,out,sc_r2);
}
/* PERF: could implement this */
static CRYPTONITE_DECAF_INLINE void sc_montsqr (scalar_t out, const scalar_t a) {
sc_montmul(out,a,a);
}
cryptonite_decaf_error_t API_NS(scalar_invert) (
scalar_t out,
const scalar_t a
) {
/* Fermat's little theorem, sliding window.
* Sliding window is fine here because the modulus isn't secret.
*/
const int SCALAR_WINDOW_BITS = 3;
scalar_t precmp[1<<SCALAR_WINDOW_BITS];
const int LAST = (1<<SCALAR_WINDOW_BITS)-1;
/* Precompute precmp = [a^1,a^3,...] */
sc_montmul(precmp[0],a,sc_r2);
if (LAST > 0) sc_montmul(precmp[LAST],precmp[0],precmp[0]);
int i;
for (i=1; i<=LAST; i++) {
sc_montmul(precmp[i],precmp[i-1],precmp[LAST]);
}
/* Sliding window */
unsigned residue = 0, trailing = 0, started = 0;
for (i=SCALAR_BITS-1; i>=-SCALAR_WINDOW_BITS; i--) {
if (started) sc_montsqr(out,out);
cryptonite_decaf_word_t w = (i>=0) ? sc_p->limb[i/WBITS] : 0;
if (i >= 0 && i<WBITS) {
assert(w >= 2);
w-=2;
}
residue = (residue<<1) | ((w>>(i%WBITS))&1);
if (residue>>SCALAR_WINDOW_BITS != 0) {
assert(trailing == 0);
trailing = residue;
residue = 0;
}
if (trailing > 0 && (trailing & ((1<<SCALAR_WINDOW_BITS)-1)) == 0) {
if (started) {
sc_montmul(out,out,precmp[trailing>>(SCALAR_WINDOW_BITS+1)]);
} else {
API_NS(scalar_copy)(out,precmp[trailing>>(SCALAR_WINDOW_BITS+1)]);
started = 1;
}
trailing = 0;
}
trailing <<= 1;
}
assert(residue==0);
assert(trailing==0);
/* Demontgomerize */
sc_montmul(out,out,API_NS(scalar_one));
cryptonite_decaf_bzero(precmp, sizeof(precmp));
return cryptonite_decaf_succeed_if(~API_NS(scalar_eq)(out,API_NS(scalar_zero)));
}
void API_NS(scalar_sub) (
scalar_t out,
const scalar_t a,
const scalar_t b
) {
sc_subx(out, a->limb, b, sc_p, 0);
}
void API_NS(scalar_add) (
scalar_t out,
const scalar_t a,
const scalar_t b
) {
cryptonite_decaf_dword_t chain = 0;
unsigned int i;
for (i=0; i<SCALAR_LIMBS; i++) {
chain = (chain + a->limb[i]) + b->limb[i];
out->limb[i] = chain;
chain >>= WBITS;
}
sc_subx(out, out->limb, sc_p, sc_p, chain);
}
void
API_NS(scalar_set_unsigned) (
scalar_t out,
uint64_t w
) {
memset(out,0,sizeof(scalar_t));
unsigned int i = 0;
for (; i<sizeof(uint64_t)/sizeof(cryptonite_decaf_word_t); i++) {
out->limb[i] = w;
#if CRYPTONITE_DECAF_WORD_BITS < 64
w >>= 8*sizeof(cryptonite_decaf_word_t);
#endif
}
}
cryptonite_decaf_bool_t
API_NS(scalar_eq) (
const scalar_t a,
const scalar_t b
) {
cryptonite_decaf_word_t diff = 0;
unsigned int i;
for (i=0; i<SCALAR_LIMBS; i++) {
diff |= a->limb[i] ^ b->limb[i];
}
return mask_to_bool(word_is_zero(diff));
}
static CRYPTONITE_DECAF_INLINE void scalar_decode_short (
scalar_t s,
const unsigned char *ser,
unsigned int nbytes
) {
unsigned int i,j,k=0;
for (i=0; i<SCALAR_LIMBS; i++) {
cryptonite_decaf_word_t out = 0;
for (j=0; j<sizeof(cryptonite_decaf_word_t) && k<nbytes; j++,k++) {
out |= ((cryptonite_decaf_word_t)ser[k])<<(8*j);
}
s->limb[i] = out;
}
}
cryptonite_decaf_error_t API_NS(scalar_decode)(
scalar_t s,
const unsigned char ser[SCALAR_SER_BYTES]
) {
unsigned int i;
scalar_decode_short(s, ser, SCALAR_SER_BYTES);
cryptonite_decaf_dsword_t accum = 0;
for (i=0; i<SCALAR_LIMBS; i++) {
accum = (accum + s->limb[i] - sc_p->limb[i]) >> WBITS;
}
/* Here accum == 0 or -1 */
API_NS(scalar_mul)(s,s,API_NS(scalar_one)); /* ham-handed reduce */
return cryptonite_decaf_succeed_if(~word_is_zero(accum));
}
void API_NS(scalar_destroy) (
scalar_t scalar
) {
cryptonite_decaf_bzero(scalar, sizeof(scalar_t));
}
void API_NS(scalar_decode_long)(
scalar_t s,
const unsigned char *ser,
size_t ser_len
) {
if (ser_len == 0) {
API_NS(scalar_copy)(s, API_NS(scalar_zero));
return;
}
size_t i;
scalar_t t1, t2;
i = ser_len - (ser_len%SCALAR_SER_BYTES);
if (i==ser_len) i -= SCALAR_SER_BYTES;
scalar_decode_short(t1, &ser[i], ser_len-i);
if (ser_len == sizeof(scalar_t)) {
assert(i==0);
/* ham-handed reduce */
API_NS(scalar_mul)(s,t1,API_NS(scalar_one));
API_NS(scalar_destroy)(t1);
return;
}
while (i) {
i -= SCALAR_SER_BYTES;
sc_montmul(t1,t1,sc_r2);
ignore_result( API_NS(scalar_decode)(t2, ser+i) );
API_NS(scalar_add)(t1, t1, t2);
}
API_NS(scalar_copy)(s, t1);
API_NS(scalar_destroy)(t1);
API_NS(scalar_destroy)(t2);
}
void API_NS(scalar_encode)(
unsigned char ser[SCALAR_SER_BYTES],
const scalar_t s
) {
unsigned int i,j,k=0;
for (i=0; i<SCALAR_LIMBS; i++) {
for (j=0; j<sizeof(cryptonite_decaf_word_t); j++,k++) {
ser[k] = s->limb[i] >> (8*j);
}
}
}
void API_NS(scalar_cond_sel) (
scalar_t out,
const scalar_t a,
const scalar_t b,
cryptonite_decaf_bool_t pick_b
) {
constant_time_select(out,a,b,sizeof(scalar_t),bool_to_mask(pick_b),sizeof(out->limb[0]));
}
void API_NS(scalar_halve) (
scalar_t out,
const scalar_t a
) {
cryptonite_decaf_word_t mask = -(a->limb[0] & 1);
cryptonite_decaf_dword_t chain = 0;
unsigned int i;
for (i=0; i<SCALAR_LIMBS; i++) {
chain = (chain + a->limb[i]) + (sc_p->limb[i] & mask);
out->limb[i] = chain;
chain >>= CRYPTONITE_DECAF_WORD_BITS;
}
for (i=0; i<SCALAR_LIMBS-1; i++) {
out->limb[i] = out->limb[i]>>1 | out->limb[i+1]<<(WBITS-1);
}
out->limb[i] = out->limb[i]>>1 | chain<<(WBITS-1);
}

View File

@ -0,0 +1,22 @@
/* Copyright (c) 2016 Cryptography Research, Inc.
* Released under the MIT License. See LICENSE.txt for license information.
*/
#ifndef __ARCH_ARCH_32_ARCH_INTRINSICS_H__
#define __ARCH_ARCH_32_ARCH_INTRINSICS_H__
#define ARCH_WORD_BITS 32
static __inline__ __attribute((always_inline,unused))
uint32_t word_is_zero(uint32_t a) {
/* let's hope the compiler isn't clever enough to optimize this. */
return (((uint64_t)a)-1)>>32;
}
static __inline__ __attribute((always_inline,unused))
uint64_t widemul(uint32_t a, uint32_t b) {
return ((uint64_t)a) * b;
}
#endif /* __ARCH_ARM_32_ARCH_INTRINSICS_H__ */

View File

@ -0,0 +1,22 @@
/* Copyright (c) 2016 Cryptography Research, Inc.
* Released under the MIT License. See LICENSE.txt for license information.
*/
#ifndef __ARCH_REF64_ARCH_INTRINSICS_H__
#define __ARCH_REF64_ARCH_INTRINSICS_H__
#define ARCH_WORD_BITS 64
static __inline__ __attribute((always_inline,unused))
uint64_t word_is_zero(uint64_t a) {
/* let's hope the compiler isn't clever enough to optimize this. */
return (((__uint128_t)a)-1)>>64;
}
static __inline__ __attribute((always_inline,unused))
__uint128_t widemul(uint64_t a, uint64_t b) {
return ((__uint128_t)a) * b;
}
#endif /* ARCH_REF64_ARCH_INTRINSICS_H__ */

View File

@ -0,0 +1,362 @@
/**
* @file constant_time.h
* @copyright
* Copyright (c) 2014 Cryptography Research, Inc. \n
* Released under the MIT License. See LICENSE.txt for license information.
* @author Mike Hamburg
*
* @brief Constant-time routines.
*/
#ifndef __CONSTANT_TIME_H__
#define __CONSTANT_TIME_H__ 1
#include "word.h"
#include <string.h>
/*
* Constant-time operations on hopefully-compile-time-sized memory
* regions. Needed for flexibility / demagication: not all fields
* have sizes which are multiples of the vector width, necessitating
* a change from the Ed448 versions.
*
* These routines would be much simpler to define at the byte level,
* but if not vectorized they would be a significant fraction of the
* runtime. Eg on NEON-less ARM, constant_time_lookup is like 15% of
* signing time, vs 6% on Haswell with its fancy AVX2 vectors.
*
* If the compiler could do a good job of autovectorizing the code,
* we could just leave it with the byte definition. But that's unlikely
* on most deployed compilers, especially if you consider that pcmpeq[size]
* is much faster than moving a scalar to the vector unit (which is what
* a naive autovectorizer will do with constant_time_lookup on Intel).
*
* Instead, we're putting our trust in the loop unroller and unswitcher.
*/
/**
* Unaligned big (vector?) register.
*/
typedef struct {
big_register_t unaligned;
} __attribute__((packed)) unaligned_br_t;
/**
* Unaligned word register, for architectures where that matters.
*/
typedef struct {
word_t unaligned;
} __attribute__((packed)) unaligned_word_t;
/**
* @brief Constant-time conditional swap.
*
* If doswap, then swap elem_bytes between *a and *b.
*
* *a and *b must not alias. Also, they must be at least as aligned
* as their sizes, if the CPU cares about that sort of thing.
*/
static __inline__ void
__attribute__((unused,always_inline))
constant_time_cond_swap (
void *__restrict__ a_,
void *__restrict__ b_,
word_t elem_bytes,
mask_t doswap
) {
word_t k;
unsigned char *a = (unsigned char *)a_;
unsigned char *b = (unsigned char *)b_;
big_register_t br_mask = br_set_to_mask(doswap);
for (k=0; k<=elem_bytes-sizeof(big_register_t); k+=sizeof(big_register_t)) {
if (elem_bytes % sizeof(big_register_t)) {
/* unaligned */
big_register_t xor =
((unaligned_br_t*)(&a[k]))->unaligned
^ ((unaligned_br_t*)(&b[k]))->unaligned;
xor &= br_mask;
((unaligned_br_t*)(&a[k]))->unaligned ^= xor;
((unaligned_br_t*)(&b[k]))->unaligned ^= xor;
} else {
/* aligned */
big_register_t xor =
*((big_register_t*)(&a[k]))
^ *((big_register_t*)(&b[k]));
xor &= br_mask;
*((big_register_t*)(&a[k])) ^= xor;
*((big_register_t*)(&b[k])) ^= xor;
}
}
if (elem_bytes % sizeof(big_register_t) >= sizeof(word_t)) {
for (; k<=elem_bytes-sizeof(word_t); k+=sizeof(word_t)) {
if (elem_bytes % sizeof(word_t)) {
/* unaligned */
word_t xor =
((unaligned_word_t*)(&a[k]))->unaligned
^ ((unaligned_word_t*)(&b[k]))->unaligned;
xor &= doswap;
((unaligned_word_t*)(&a[k]))->unaligned ^= xor;
((unaligned_word_t*)(&b[k]))->unaligned ^= xor;
} else {
/* aligned */
word_t xor =
*((word_t*)(&a[k]))
^ *((word_t*)(&b[k]));
xor &= doswap;
*((word_t*)(&a[k])) ^= xor;
*((word_t*)(&b[k])) ^= xor;
}
}
}
if (elem_bytes % sizeof(word_t)) {
for (; k<elem_bytes; k+=1) {
unsigned char xor = a[k] ^ b[k];
xor &= doswap;
a[k] ^= xor;
b[k] ^= xor;
}
}
}
/**
* @brief Constant-time equivalent of memcpy(out, table + elem_bytes*idx, elem_bytes);
*
* The table must be at least as aligned as elem_bytes. The output must be word aligned,
* and if the input size is vector aligned it must also be vector aligned.
*
* The table and output must not alias.
*/
static __inline__ void
__attribute__((unused,always_inline))
constant_time_lookup (
void *__restrict__ out_,
const void *table_,
word_t elem_bytes,
word_t n_table,
word_t idx
) {
big_register_t big_one = br_set_to_mask(1), big_i = br_set_to_mask(idx);
/* Can't do pointer arithmetic on void* */
unsigned char *out = (unsigned char *)out_;
const unsigned char *table = (const unsigned char *)table_;
word_t j,k;
memset(out, 0, elem_bytes);
for (j=0; j<n_table; j++, big_i-=big_one) {
big_register_t br_mask = br_is_zero(big_i);
for (k=0; k<=elem_bytes-sizeof(big_register_t); k+=sizeof(big_register_t)) {
if (elem_bytes % sizeof(big_register_t)) {
/* unaligned */
((unaligned_br_t *)(out+k))->unaligned
|= br_mask & ((const unaligned_br_t*)(&table[k+j*elem_bytes]))->unaligned;
} else {
/* aligned */
*(big_register_t *)(out+k) |= br_mask & *(const big_register_t*)(&table[k+j*elem_bytes]);
}
}
word_t mask = word_is_zero(idx^j);
if (elem_bytes % sizeof(big_register_t) >= sizeof(word_t)) {
for (; k<=elem_bytes-sizeof(word_t); k+=sizeof(word_t)) {
if (elem_bytes % sizeof(word_t)) {
/* input unaligned, output aligned */
*(word_t *)(out+k) |= mask & ((const unaligned_word_t*)(&table[k+j*elem_bytes]))->unaligned;
} else {
/* aligned */
*(word_t *)(out+k) |= mask & *(const word_t*)(&table[k+j*elem_bytes]);
}
}
}
if (elem_bytes % sizeof(word_t)) {
for (; k<elem_bytes; k+=1) {
out[k] |= mask & table[k+j*elem_bytes];
}
}
}
}
/**
* @brief Constant-time equivalent of memcpy(table + elem_bytes*idx, in, elem_bytes);
*
* The table must be at least as aligned as elem_bytes. The input must be word aligned,
* and if the output size is vector aligned it must also be vector aligned.
*
* The table and input must not alias.
*/
static __inline__ void
__attribute__((unused,always_inline))
constant_time_insert (
void *__restrict__ table_,
const void *in_,
word_t elem_bytes,
word_t n_table,
word_t idx
) {
big_register_t big_one = br_set_to_mask(1), big_i = br_set_to_mask(idx);
/* Can't do pointer arithmetic on void* */
const unsigned char *in = (const unsigned char *)in_;
unsigned char *table = (unsigned char *)table_;
word_t j,k;
for (j=0; j<n_table; j++, big_i-=big_one) {
big_register_t br_mask = br_is_zero(big_i);
for (k=0; k<=elem_bytes-sizeof(big_register_t); k+=sizeof(big_register_t)) {
if (elem_bytes % sizeof(big_register_t)) {
/* unaligned */
((unaligned_br_t*)(&table[k+j*elem_bytes]))->unaligned
= ( ((unaligned_br_t*)(&table[k+j*elem_bytes]))->unaligned & ~br_mask )
| ( ((const unaligned_br_t *)(in+k))->unaligned & br_mask );
} else {
/* aligned */
*(big_register_t*)(&table[k+j*elem_bytes])
= ( *(big_register_t*)(&table[k+j*elem_bytes]) & ~br_mask )
| ( *(const big_register_t *)(in+k) & br_mask );
}
}
word_t mask = word_is_zero(idx^j);
if (elem_bytes % sizeof(big_register_t) >= sizeof(word_t)) {
for (; k<=elem_bytes-sizeof(word_t); k+=sizeof(word_t)) {
if (elem_bytes % sizeof(word_t)) {
/* output unaligned, input aligned */
((unaligned_word_t*)(&table[k+j*elem_bytes]))->unaligned
= ( ((unaligned_word_t*)(&table[k+j*elem_bytes]))->unaligned & ~mask )
| ( *(const word_t *)(in+k) & mask );
} else {
/* aligned */
*(word_t*)(&table[k+j*elem_bytes])
= ( *(word_t*)(&table[k+j*elem_bytes]) & ~mask )
| ( *(const word_t *)(in+k) & mask );
}
}
}
if (elem_bytes % sizeof(word_t)) {
for (; k<elem_bytes; k+=1) {
table[k+j*elem_bytes]
= ( table[k+j*elem_bytes] & ~mask )
| ( in[k] & mask );
}
}
}
}
/**
* @brief Constant-time a = b&mask.
*
* The input and output must be at least as aligned as elem_bytes.
*/
static __inline__ void
__attribute__((unused,always_inline))
constant_time_mask (
void * a_,
const void *b_,
word_t elem_bytes,
mask_t mask
) {
unsigned char *a = (unsigned char *)a_;
const unsigned char *b = (const unsigned char *)b_;
word_t k;
big_register_t br_mask = br_set_to_mask(mask);
for (k=0; k<=elem_bytes-sizeof(big_register_t); k+=sizeof(big_register_t)) {
if (elem_bytes % sizeof(big_register_t)) {
/* unaligned */
((unaligned_br_t*)(&a[k]))->unaligned = br_mask & ((const unaligned_br_t*)(&b[k]))->unaligned;
} else {
/* aligned */
*(big_register_t *)(a+k) = br_mask & *(const big_register_t*)(&b[k]);
}
}
if (elem_bytes % sizeof(big_register_t) >= sizeof(word_t)) {
for (; k<=elem_bytes-sizeof(word_t); k+=sizeof(word_t)) {
if (elem_bytes % sizeof(word_t)) {
/* unaligned */
((unaligned_word_t*)(&a[k]))->unaligned = mask & ((const unaligned_word_t*)(&b[k]))->unaligned;
} else {
/* aligned */
*(word_t *)(a+k) = mask & *(const word_t*)(&b[k]);
}
}
}
if (elem_bytes % sizeof(word_t)) {
for (; k<elem_bytes; k+=1) {
a[k] = mask & b[k];
}
}
}
/**
* @brief Constant-time a = mask ? bTrue : bFalse.
*
* The input and output must be at least as aligned as alignment_bytes
* or their size, whichever is smaller.
*
* Note that the output is not __restrict__, but if it overlaps either
* input, it must be equal and not partially overlap.
*/
static __inline__ void
__attribute__((unused,always_inline))
constant_time_select (
void *a_,
const void *bFalse_,
const void *bTrue_,
word_t elem_bytes,
mask_t mask,
size_t alignment_bytes
) {
unsigned char *a = (unsigned char *)a_;
const unsigned char *bTrue = (const unsigned char *)bTrue_;
const unsigned char *bFalse = (const unsigned char *)bFalse_;
alignment_bytes |= elem_bytes;
word_t k;
big_register_t br_mask = br_set_to_mask(mask);
for (k=0; k<=elem_bytes-sizeof(big_register_t); k+=sizeof(big_register_t)) {
if (alignment_bytes % sizeof(big_register_t)) {
/* unaligned */
((unaligned_br_t*)(&a[k]))->unaligned =
( br_mask & ((const unaligned_br_t*)(&bTrue [k]))->unaligned)
| (~br_mask & ((const unaligned_br_t*)(&bFalse[k]))->unaligned);
} else {
/* aligned */
*(big_register_t *)(a+k) =
( br_mask & *(const big_register_t*)(&bTrue [k]))
| (~br_mask & *(const big_register_t*)(&bFalse[k]));
}
}
if (elem_bytes % sizeof(big_register_t) >= sizeof(word_t)) {
for (; k<=elem_bytes-sizeof(word_t); k+=sizeof(word_t)) {
if (alignment_bytes % sizeof(word_t)) {
/* unaligned */
((unaligned_word_t*)(&a[k]))->unaligned =
( mask & ((const unaligned_word_t*)(&bTrue [k]))->unaligned)
| (~mask & ((const unaligned_word_t*)(&bFalse[k]))->unaligned);
} else {
/* aligned */
*(word_t *)(a+k) =
( mask & *(const word_t*)(&bTrue [k]))
| (~mask & *(const word_t*)(&bFalse[k]));
}
}
}
if (elem_bytes % sizeof(word_t)) {
for (; k<elem_bytes; k+=1) {
a[k] = ( mask & bTrue[k]) | (~mask & bFalse[k]);
}
}
}
#endif /* __CONSTANT_TIME_H__ */

View File

@ -0,0 +1,32 @@
/**
* @file decaf.h
* @author Mike Hamburg
*
* @copyright
* Copyright (c) 2015-2016 Cryptography Research, Inc. \n
* Released under the MIT License. See LICENSE.txt for license information.
*
* Master header for Decaf library.
*
* The Decaf library implements cryptographic operations on a elliptic curve
* groups of prime order p. It accomplishes this by using a twisted Edwards
* curve (isogenous to Ed448-Goldilocks or Ed25519) and wiping out the cofactor.
*
* The formulas are all complete and have no special cases. However, some
* functions can fail. For example, decoding functions can fail because not
* every string is the encoding of a valid group element.
*
* The formulas contain no data-dependent branches, timing or memory accesses,
* except for cryptonite_decaf_XXX_base_double_scalarmul_non_secret.
*
* @warning This file was automatically generated in Python.
* Please do not edit it.
*/
#ifndef __CRYPTONITE_DECAF_H__
#define __CRYPTONITE_DECAF_H__ 1
#include <decaf/point_255.h>
#include <decaf/point_448.h>
#endif /* __CRYPTONITE_DECAF_H__ */

View File

@ -0,0 +1,116 @@
/**
* @file decaf/common.h
* @author Mike Hamburg
*
* @copyright
* Copyright (c) 2015 Cryptography Research, Inc. \n
* Released under the MIT License. See LICENSE.txt for license information.
*
* @brief Common utility headers for Decaf library.
*/
#ifndef __CRYPTONITE_DECAF_COMMON_H__
#define __CRYPTONITE_DECAF_COMMON_H__ 1
#include <stdint.h>
#include <sys/types.h>
#ifdef __cplusplus
extern "C" {
#endif
/* Goldilocks' build flags default to hidden and stripping executables. */
/** @cond internal */
#if defined(DOXYGEN) && !defined(__attribute__)
#define __attribute__((x))
#endif
#define CRYPTONITE_DECAF_API_VIS __attribute__((visibility("default")))
#define CRYPTONITE_DECAF_NOINLINE __attribute__((noinline))
#define CRYPTONITE_DECAF_WARN_UNUSED __attribute__((warn_unused_result))
#define CRYPTONITE_DECAF_NONNULL __attribute__((nonnull))
#define CRYPTONITE_DECAF_INLINE inline __attribute__((always_inline,unused))
// Cribbed from libnotmuch
#if defined (__clang_major__) && __clang_major__ >= 3 \
|| defined (__GNUC__) && __GNUC__ >= 5 \
|| defined (__GNUC__) && __GNUC__ == 4 && __GNUC_MINOR__ >= 5
#define CRYPTONITE_DECAF_DEPRECATED(msg) __attribute__ ((deprecated(msg)))
#else
#define CRYPTONITE_DECAF_DEPRECATED(msg) __attribute__ ((deprecated))
#endif
/** @endcond */
/* Internal word types.
*
* Somewhat tricky. This could be decided separately per platform. However,
* the structs do need to be all the same size and alignment on a given
* platform to support dynamic linking, since even if you header was built
* with eg arch_neon, you might end up linking a library built with arch_arm32.
*/
#ifndef CRYPTONITE_DECAF_WORD_BITS
#if (defined(__ILP64__) || defined(__amd64__) || defined(__x86_64__) || (((__UINT_FAST32_MAX__)>>30)>>30))
#define CRYPTONITE_DECAF_WORD_BITS 64 /**< The number of bits in a word */
#else
#define CRYPTONITE_DECAF_WORD_BITS 32 /**< The number of bits in a word */
#endif
#endif
#if CRYPTONITE_DECAF_WORD_BITS == 64
typedef uint64_t cryptonite_decaf_word_t; /**< Word size for internal computations */
typedef int64_t cryptonite_decaf_sword_t; /**< Signed word size for internal computations */
typedef uint64_t cryptonite_decaf_bool_t; /**< "Boolean" type, will be set to all-zero or all-one (i.e. -1u) */
typedef __uint128_t cryptonite_decaf_dword_t; /**< Double-word size for internal computations */
typedef __int128_t cryptonite_decaf_dsword_t; /**< Signed double-word size for internal computations */
#elif CRYPTONITE_DECAF_WORD_BITS == 32 /**< The number of bits in a word */
typedef uint32_t cryptonite_decaf_word_t; /**< Word size for internal computations */
typedef int32_t cryptonite_decaf_sword_t; /**< Signed word size for internal computations */
typedef uint32_t cryptonite_decaf_bool_t; /**< "Boolean" type, will be set to all-zero or all-one (i.e. -1u) */
typedef uint64_t cryptonite_decaf_dword_t; /**< Double-word size for internal computations */
typedef int64_t cryptonite_decaf_dsword_t; /**< Signed double-word size for internal computations */
#else
#error "Only supporting CRYPTONITE_DECAF_WORD_BITS = 32 or 64 for now"
#endif
/** CRYPTONITE_DECAF_TRUE = -1 so that CRYPTONITE_DECAF_TRUE & x = x */
static const cryptonite_decaf_bool_t CRYPTONITE_DECAF_TRUE = -(cryptonite_decaf_bool_t)1;
/** CRYPTONITE_DECAF_FALSE = 0 so that CRYPTONITE_DECAF_FALSE & x = 0 */
static const cryptonite_decaf_bool_t CRYPTONITE_DECAF_FALSE = 0;
/** Another boolean type used to indicate success or failure. */
typedef enum {
CRYPTONITE_DECAF_SUCCESS = -1, /**< The operation succeeded. */
CRYPTONITE_DECAF_FAILURE = 0 /**< The operation failed. */
} cryptonite_decaf_error_t;
/** Return success if x is true */
static CRYPTONITE_DECAF_INLINE cryptonite_decaf_error_t
cryptonite_decaf_succeed_if(cryptonite_decaf_bool_t x) {
return (cryptonite_decaf_error_t)x;
}
/** Return CRYPTONITE_DECAF_TRUE iff x == CRYPTONITE_DECAF_SUCCESS */
static CRYPTONITE_DECAF_INLINE cryptonite_decaf_bool_t
cryptonite_decaf_successful(cryptonite_decaf_error_t e) {
cryptonite_decaf_dword_t w = ((cryptonite_decaf_word_t)e) ^ ((cryptonite_decaf_word_t)CRYPTONITE_DECAF_SUCCESS);
return (w-1)>>CRYPTONITE_DECAF_WORD_BITS;
}
/** Overwrite data with zeros. Uses memset_s if available. */
void cryptonite_decaf_bzero (
void *data,
size_t size
) CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_API_VIS;
/** Compare two buffers, returning CRYPTONITE_DECAF_TRUE if they are equal. */
cryptonite_decaf_bool_t cryptonite_decaf_memeq (
const void *data1,
const void *data2,
size_t size
) CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_WARN_UNUSED CRYPTONITE_DECAF_API_VIS;
#ifdef __cplusplus
} /* extern "C" */
#endif
#endif /* __CRYPTONITE_DECAF_COMMON_H__ */

View File

@ -0,0 +1,227 @@
/**
* @file decaf/ed448.h
* @author Mike Hamburg
*
* @copyright
* Copyright (c) 2015-2016 Cryptography Research, Inc. \n
* Released under the MIT License. See LICENSE.txt for license information.
*
* @brief A group of prime order p, based on Ed448-Goldilocks.
*
* @warning This file was automatically generated in Python.
* Please do not edit it.
*/
#ifndef __CRYPTONITE_DECAF_ED448_H__
#define __CRYPTONITE_DECAF_ED448_H__ 1
#include <decaf/point_448.h>
#include <decaf/shake.h>
#include <decaf/sha512.h>
#ifdef __cplusplus
extern "C" {
#endif
/** Number of bytes in an EdDSA public key. */
#define CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES 57
/** Number of bytes in an EdDSA private key. */
#define CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES
/** Number of bytes in an EdDSA private key. */
#define CRYPTONITE_DECAF_EDDSA_448_SIGNATURE_BYTES (CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES + CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES)
/** Does EdDSA support non-contextual signatures? */
#define CRYPTONITE_DECAF_EDDSA_448_SUPPORTS_CONTEXTLESS_SIGS 0
/** Prehash context renaming macros. */
#define cryptonite_decaf_ed448_prehash_ctx_s cryptonite_decaf_shake256_ctx_s
#define cryptonite_decaf_ed448_prehash_ctx_t cryptonite_decaf_shake256_ctx_t
#define cryptonite_decaf_ed448_prehash_update cryptonite_decaf_shake256_update
#define cryptonite_decaf_ed448_prehash_destroy cryptonite_decaf_shake256_destroy
/**
* @brief EdDSA key generation. This function uses a different (non-Decaf)
* encoding.
*
* @param [out] pubkey The public key.
* @param [in] privkey The private key.
*/
void cryptonite_decaf_ed448_derive_public_key (
uint8_t pubkey[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES],
const uint8_t privkey[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES]
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief EdDSA signing.
*
* @param [out] signature The signature.
* @param [in] privkey The private key.
* @param [in] pubkey The public key.
* @param [in] message The message to sign.
* @param [in] message_len The length of the message.
* @param [in] prehashed Nonzero if the message is actually the hash of something you want to sign.
* @param [in] context A "context" for this signature of up to 255 bytes.
* @param [in] context_len Length of the context.
*
* @warning For Ed25519, it is unsafe to use the same key for both prehashed and non-prehashed
* messages, at least without some very careful protocol-level disambiguation. For Ed448 it is
* safe. The C++ wrapper is designed to make it harder to screw this up, but this C code gives
* you no seat belt.
*/
void cryptonite_decaf_ed448_sign (
uint8_t signature[CRYPTONITE_DECAF_EDDSA_448_SIGNATURE_BYTES],
const uint8_t privkey[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES],
const uint8_t pubkey[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES],
const uint8_t *message,
size_t message_len,
uint8_t prehashed,
const uint8_t *context,
uint8_t context_len
) CRYPTONITE_DECAF_API_VIS __attribute__((nonnull(1,2,3))) CRYPTONITE_DECAF_NOINLINE;
/**
* @brief EdDSA signing with prehash.
*
* @param [out] signature The signature.
* @param [in] privkey The private key.
* @param [in] pubkey The public key.
* @param [in] hash The hash of the message. This object will not be modified by the call.
* @param [in] context A "context" for this signature of up to 255 bytes. Must be the same as what was used for the prehash.
* @param [in] context_len Length of the context.
*
* @warning For Ed25519, it is unsafe to use the same key for both prehashed and non-prehashed
* messages, at least without some very careful protocol-level disambiguation. For Ed448 it is
* safe. The C++ wrapper is designed to make it harder to screw this up, but this C code gives
* you no seat belt.
*/
void cryptonite_decaf_ed448_sign_prehash (
uint8_t signature[CRYPTONITE_DECAF_EDDSA_448_SIGNATURE_BYTES],
const uint8_t privkey[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES],
const uint8_t pubkey[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES],
const cryptonite_decaf_ed448_prehash_ctx_t hash,
const uint8_t *context,
uint8_t context_len
) CRYPTONITE_DECAF_API_VIS __attribute__((nonnull(1,2,3,4))) CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Prehash initialization, with contexts if supported.
*
* @param [out] hash The hash object to be initialized.
*/
void cryptonite_decaf_ed448_prehash_init (
cryptonite_decaf_ed448_prehash_ctx_t hash
) CRYPTONITE_DECAF_API_VIS __attribute__((nonnull(1))) CRYPTONITE_DECAF_NOINLINE;
/**
* @brief EdDSA signature verification.
*
* Uses the standard (i.e. less-strict) verification formula.
*
* @param [in] signature The signature.
* @param [in] pubkey The public key.
* @param [in] message The message to verify.
* @param [in] message_len The length of the message.
* @param [in] prehashed Nonzero if the message is actually the hash of something you want to verify.
* @param [in] context A "context" for this signature of up to 255 bytes.
* @param [in] context_len Length of the context.
*
* @warning For Ed25519, it is unsafe to use the same key for both prehashed and non-prehashed
* messages, at least without some very careful protocol-level disambiguation. For Ed448 it is
* safe. The C++ wrapper is designed to make it harder to screw this up, but this C code gives
* you no seat belt.
*/
cryptonite_decaf_error_t cryptonite_decaf_ed448_verify (
const uint8_t signature[CRYPTONITE_DECAF_EDDSA_448_SIGNATURE_BYTES],
const uint8_t pubkey[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES],
const uint8_t *message,
size_t message_len,
uint8_t prehashed,
const uint8_t *context,
uint8_t context_len
) CRYPTONITE_DECAF_API_VIS __attribute__((nonnull(1,2))) CRYPTONITE_DECAF_NOINLINE;
/**
* @brief EdDSA signature verification.
*
* Uses the standard (i.e. less-strict) verification formula.
*
* @param [in] signature The signature.
* @param [in] pubkey The public key.
* @param [in] hash The hash of the message. This object will not be modified by the call.
* @param [in] context A "context" for this signature of up to 255 bytes. Must be the same as what was used for the prehash.
* @param [in] context_len Length of the context.
*
* @warning For Ed25519, it is unsafe to use the same key for both prehashed and non-prehashed
* messages, at least without some very careful protocol-level disambiguation. For Ed448 it is
* safe. The C++ wrapper is designed to make it harder to screw this up, but this C code gives
* you no seat belt.
*/
cryptonite_decaf_error_t cryptonite_decaf_ed448_verify_prehash (
const uint8_t signature[CRYPTONITE_DECAF_EDDSA_448_SIGNATURE_BYTES],
const uint8_t pubkey[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES],
const cryptonite_decaf_ed448_prehash_ctx_t hash,
const uint8_t *context,
uint8_t context_len
) CRYPTONITE_DECAF_API_VIS __attribute__((nonnull(1,2))) CRYPTONITE_DECAF_NOINLINE;
/**
* @brief EdDSA point encoding. Used internally, exposed externally.
* Multiplies the point by the current cofactor first.
*
* @param [out] enc The encoded point.
* @param [in] p The point.
*/
void cryptonite_decaf_448_point_mul_by_cofactor_and_encode_like_eddsa (
uint8_t enc[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES],
const cryptonite_decaf_448_point_t p
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief EdDSA point decoding. Remember that while points on the
* EdDSA curves have cofactor information, Decaf ignores (quotients
* out) all cofactor information.
*
* @param [out] enc The encoded point.
* @param [in] p The point.
*/
cryptonite_decaf_error_t cryptonite_decaf_448_point_decode_like_eddsa_and_ignore_cofactor (
cryptonite_decaf_448_point_t p,
const uint8_t enc[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES]
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief EdDSA to ECDH public key conversion
* Deserialize the point to get y on Edwards curve,
* Convert it to u coordinate on Montgomery curve.
*
* @warning This function does not check that the public key being converted
* is a valid EdDSA public key (FUTURE?)
*
* @param[out] x The ECDH public key as in RFC7748(point on Montgomery curve)
* @param[in] ed The EdDSA public key(point on Edwards curve)
*/
void cryptonite_decaf_ed448_convert_public_key_to_x448 (
uint8_t x[CRYPTONITE_DECAF_X448_PUBLIC_BYTES],
const uint8_t ed[CRYPTONITE_DECAF_EDDSA_448_PUBLIC_BYTES]
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief EdDSA to ECDH private key conversion
* Using the appropriate hash function, hash the EdDSA private key
* and keep only the lower bytes to get the ECDH private key
*
* @param[out] x The ECDH private key as in RFC7748
* @param[in] ed The EdDSA private key
*/
void cryptonite_decaf_ed448_convert_private_key_to_x448 (
uint8_t x[CRYPTONITE_DECAF_X448_PRIVATE_BYTES],
const uint8_t ed[CRYPTONITE_DECAF_EDDSA_448_PRIVATE_BYTES]
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
#ifdef __cplusplus
} /* extern "C" */
#endif
#endif /* __CRYPTONITE_DECAF_ED448_H__ */

View File

@ -0,0 +1 @@
/* Not needed if 448-only */

View File

@ -0,0 +1,724 @@
/**
* @file decaf/point_448.h
* @author Mike Hamburg
*
* @copyright
* Copyright (c) 2015-2016 Cryptography Research, Inc. \n
* Released under the MIT License. See LICENSE.txt for license information.
*
* @brief A group of prime order p, based on Ed448-Goldilocks.
*
* @warning This file was automatically generated in Python.
* Please do not edit it.
*/
#ifndef __CRYPTONITE_DECAF_POINT_448_H__
#define __CRYPTONITE_DECAF_POINT_448_H__ 1
#include <decaf/common.h>
#ifdef __cplusplus
extern "C" {
#endif
/** @cond internal */
#define CRYPTONITE_DECAF_448_SCALAR_LIMBS ((446-1)/CRYPTONITE_DECAF_WORD_BITS+1)
/** @endcond */
/** The number of bits in a scalar */
#define CRYPTONITE_DECAF_448_SCALAR_BITS 446
/** @cond internal */
#ifndef __CRYPTONITE_DECAF_448_GF_DEFINED__
#define __CRYPTONITE_DECAF_448_GF_DEFINED__ 1
/** @brief Galois field element internal structure */
typedef struct cryptonite_gf_448_s {
cryptonite_decaf_word_t limb[512/CRYPTONITE_DECAF_WORD_BITS];
} __attribute__((aligned(16))) cryptonite_gf_448_s, cryptonite_gf_448_t[1];
#endif /* __CRYPTONITE_DECAF_448_GF_DEFINED__ */
/** @endcond */
/** Number of bytes in a serialized point. */
#define CRYPTONITE_DECAF_448_SER_BYTES 56
/** Number of bytes in an elligated point. For now set the same as SER_BYTES
* but could be different for other curves.
*/
#define CRYPTONITE_DECAF_448_HASH_BYTES 56
/** Number of bytes in a serialized scalar. */
#define CRYPTONITE_DECAF_448_SCALAR_BYTES 56
/** Number of bits in the "which" field of an elligator inverse */
#define CRYPTONITE_DECAF_448_INVERT_ELLIGATOR_WHICH_BITS 3
/** Number of bytes in an x448 public key */
#define CRYPTONITE_DECAF_X448_PUBLIC_BYTES 56
/** Number of bytes in an x448 private key */
#define CRYPTONITE_DECAF_X448_PRIVATE_BYTES 56
/** Twisted Edwards extended homogeneous coordinates */
typedef struct cryptonite_decaf_448_point_s {
/** @cond internal */
cryptonite_gf_448_t x,y,z,t;
/** @endcond */
} cryptonite_decaf_448_point_t[1];
/** Precomputed table based on a point. Can be trivial implementation. */
struct cryptonite_decaf_448_precomputed_s;
/** Precomputed table based on a point. Can be trivial implementation. */
typedef struct cryptonite_decaf_448_precomputed_s cryptonite_decaf_448_precomputed_s;
/** Size and alignment of precomputed point tables. */
extern const size_t cryptonite_decaf_448_sizeof_precomputed_s CRYPTONITE_DECAF_API_VIS, cryptonite_decaf_448_alignof_precomputed_s CRYPTONITE_DECAF_API_VIS;
/** Scalar is stored packed, because we don't need the speed. */
typedef struct cryptonite_decaf_448_scalar_s {
/** @cond internal */
cryptonite_decaf_word_t limb[CRYPTONITE_DECAF_448_SCALAR_LIMBS];
/** @endcond */
} cryptonite_decaf_448_scalar_t[1];
/** A scalar equal to 1. */
extern const cryptonite_decaf_448_scalar_t cryptonite_decaf_448_scalar_one CRYPTONITE_DECAF_API_VIS;
/** A scalar equal to 0. */
extern const cryptonite_decaf_448_scalar_t cryptonite_decaf_448_scalar_zero CRYPTONITE_DECAF_API_VIS;
/** The identity point on the curve. */
extern const cryptonite_decaf_448_point_t cryptonite_decaf_448_point_identity CRYPTONITE_DECAF_API_VIS;
/** An arbitrarily chosen base point on the curve. */
extern const cryptonite_decaf_448_point_t cryptonite_decaf_448_point_base CRYPTONITE_DECAF_API_VIS;
/** Precomputed table for the base point on the curve. */
extern const struct cryptonite_decaf_448_precomputed_s *cryptonite_decaf_448_precomputed_base CRYPTONITE_DECAF_API_VIS;
/**
* @brief Read a scalar from wire format or from bytes.
*
* @param [in] ser Serialized form of a scalar.
* @param [out] out Deserialized form.
*
* @retval CRYPTONITE_DECAF_SUCCESS The scalar was correctly encoded.
* @retval CRYPTONITE_DECAF_FAILURE The scalar was greater than the modulus,
* and has been reduced modulo that modulus.
*/
cryptonite_decaf_error_t cryptonite_decaf_448_scalar_decode (
cryptonite_decaf_448_scalar_t out,
const unsigned char ser[CRYPTONITE_DECAF_448_SCALAR_BYTES]
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_WARN_UNUSED CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Read a scalar from wire format or from bytes. Reduces mod
* scalar prime.
*
* @param [in] ser Serialized form of a scalar.
* @param [in] ser_len Length of serialized form.
* @param [out] out Deserialized form.
*/
void cryptonite_decaf_448_scalar_decode_long (
cryptonite_decaf_448_scalar_t out,
const unsigned char *ser,
size_t ser_len
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Serialize a scalar to wire format.
*
* @param [out] ser Serialized form of a scalar.
* @param [in] s Deserialized scalar.
*/
void cryptonite_decaf_448_scalar_encode (
unsigned char ser[CRYPTONITE_DECAF_448_SCALAR_BYTES],
const cryptonite_decaf_448_scalar_t s
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Add two scalars. The scalars may use the same memory.
* @param [in] a One scalar.
* @param [in] b Another scalar.
* @param [out] out a+b.
*/
void cryptonite_decaf_448_scalar_add (
cryptonite_decaf_448_scalar_t out,
const cryptonite_decaf_448_scalar_t a,
const cryptonite_decaf_448_scalar_t b
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Compare two scalars.
* @param [in] a One scalar.
* @param [in] b Another scalar.
* @retval CRYPTONITE_DECAF_TRUE The scalars are equal.
* @retval CRYPTONITE_DECAF_FALSE The scalars are not equal.
*/
cryptonite_decaf_bool_t cryptonite_decaf_448_scalar_eq (
const cryptonite_decaf_448_scalar_t a,
const cryptonite_decaf_448_scalar_t b
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_WARN_UNUSED CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Subtract two scalars. The scalars may use the same memory.
* @param [in] a One scalar.
* @param [in] b Another scalar.
* @param [out] out a-b.
*/
void cryptonite_decaf_448_scalar_sub (
cryptonite_decaf_448_scalar_t out,
const cryptonite_decaf_448_scalar_t a,
const cryptonite_decaf_448_scalar_t b
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Multiply two scalars. The scalars may use the same memory.
* @param [in] a One scalar.
* @param [in] b Another scalar.
* @param [out] out a*b.
*/
void cryptonite_decaf_448_scalar_mul (
cryptonite_decaf_448_scalar_t out,
const cryptonite_decaf_448_scalar_t a,
const cryptonite_decaf_448_scalar_t b
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Halve a scalar. The scalars may use the same memory.
* @param [in] a A scalar.
* @param [out] out a/2.
*/
void cryptonite_decaf_448_scalar_halve (
cryptonite_decaf_448_scalar_t out,
const cryptonite_decaf_448_scalar_t a
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Invert a scalar. When passed zero, return 0. The input and output may alias.
* @param [in] a A scalar.
* @param [out] out 1/a.
* @return CRYPTONITE_DECAF_SUCCESS The input is nonzero.
*/
cryptonite_decaf_error_t cryptonite_decaf_448_scalar_invert (
cryptonite_decaf_448_scalar_t out,
const cryptonite_decaf_448_scalar_t a
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_WARN_UNUSED CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Copy a scalar. The scalars may use the same memory, in which
* case this function does nothing.
* @param [in] a A scalar.
* @param [out] out Will become a copy of a.
*/
static inline void CRYPTONITE_DECAF_NONNULL cryptonite_decaf_448_scalar_copy (
cryptonite_decaf_448_scalar_t out,
const cryptonite_decaf_448_scalar_t a
) {
*out = *a;
}
/**
* @brief Set a scalar to an unsigned 64-bit integer.
* @param [in] a An integer.
* @param [out] out Will become equal to a.
*/
void cryptonite_decaf_448_scalar_set_unsigned (
cryptonite_decaf_448_scalar_t out,
uint64_t a
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL;
/**
* @brief Encode a point as a sequence of bytes.
*
* @param [out] ser The byte representation of the point.
* @param [in] pt The point to encode.
*/
void cryptonite_decaf_448_point_encode (
uint8_t ser[CRYPTONITE_DECAF_448_SER_BYTES],
const cryptonite_decaf_448_point_t pt
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Decode a point from a sequence of bytes.
*
* Every point has a unique encoding, so not every
* sequence of bytes is a valid encoding. If an invalid
* encoding is given, the output is undefined.
*
* @param [out] pt The decoded point.
* @param [in] ser The serialized version of the point.
* @param [in] allow_identity CRYPTONITE_DECAF_TRUE if the identity is a legal input.
* @retval CRYPTONITE_DECAF_SUCCESS The decoding succeeded.
* @retval CRYPTONITE_DECAF_FAILURE The decoding didn't succeed, because
* ser does not represent a point.
*/
cryptonite_decaf_error_t cryptonite_decaf_448_point_decode (
cryptonite_decaf_448_point_t pt,
const uint8_t ser[CRYPTONITE_DECAF_448_SER_BYTES],
cryptonite_decaf_bool_t allow_identity
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_WARN_UNUSED CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Copy a point. The input and output may alias,
* in which case this function does nothing.
*
* @param [out] a A copy of the point.
* @param [in] b Any point.
*/
static inline void CRYPTONITE_DECAF_NONNULL cryptonite_decaf_448_point_copy (
cryptonite_decaf_448_point_t a,
const cryptonite_decaf_448_point_t b
) {
*a=*b;
}
/**
* @brief Test whether two points are equal. If yes, return
* CRYPTONITE_DECAF_TRUE, else return CRYPTONITE_DECAF_FALSE.
*
* @param [in] a A point.
* @param [in] b Another point.
* @retval CRYPTONITE_DECAF_TRUE The points are equal.
* @retval CRYPTONITE_DECAF_FALSE The points are not equal.
*/
cryptonite_decaf_bool_t cryptonite_decaf_448_point_eq (
const cryptonite_decaf_448_point_t a,
const cryptonite_decaf_448_point_t b
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_WARN_UNUSED CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Add two points to produce a third point. The
* input points and output point can be pointers to the same
* memory.
*
* @param [out] sum The sum a+b.
* @param [in] a An addend.
* @param [in] b An addend.
*/
void cryptonite_decaf_448_point_add (
cryptonite_decaf_448_point_t sum,
const cryptonite_decaf_448_point_t a,
const cryptonite_decaf_448_point_t b
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL;
/**
* @brief Double a point. Equivalent to
* cryptonite_decaf_448_point_add(two_a,a,a), but potentially faster.
*
* @param [out] two_a The sum a+a.
* @param [in] a A point.
*/
void cryptonite_decaf_448_point_double (
cryptonite_decaf_448_point_t two_a,
const cryptonite_decaf_448_point_t a
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL;
/**
* @brief Subtract two points to produce a third point. The
* input points and output point can be pointers to the same
* memory.
*
* @param [out] diff The difference a-b.
* @param [in] a The minuend.
* @param [in] b The subtrahend.
*/
void cryptonite_decaf_448_point_sub (
cryptonite_decaf_448_point_t diff,
const cryptonite_decaf_448_point_t a,
const cryptonite_decaf_448_point_t b
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL;
/**
* @brief Negate a point to produce another point. The input
* and output points can use the same memory.
*
* @param [out] nega The negated input point
* @param [in] a The input point.
*/
void cryptonite_decaf_448_point_negate (
cryptonite_decaf_448_point_t nega,
const cryptonite_decaf_448_point_t a
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL;
/**
* @brief Multiply a base point by a scalar: scaled = scalar*base.
*
* @param [out] scaled The scaled point base*scalar
* @param [in] base The point to be scaled.
* @param [in] scalar The scalar to multiply by.
*/
void cryptonite_decaf_448_point_scalarmul (
cryptonite_decaf_448_point_t scaled,
const cryptonite_decaf_448_point_t base,
const cryptonite_decaf_448_scalar_t scalar
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Multiply a base point by a scalar: scaled = scalar*base.
* This function operates directly on serialized forms.
*
* @warning This function is experimental. It may not be supported
* long-term.
*
* @param [out] scaled The scaled point base*scalar
* @param [in] base The point to be scaled.
* @param [in] scalar The scalar to multiply by.
* @param [in] allow_identity Allow the input to be the identity.
* @param [in] short_circuit Allow a fast return if the input is illegal.
*
* @retval CRYPTONITE_DECAF_SUCCESS The scalarmul succeeded.
* @retval CRYPTONITE_DECAF_FAILURE The scalarmul didn't succeed, because
* base does not represent a point.
*/
cryptonite_decaf_error_t cryptonite_decaf_448_direct_scalarmul (
uint8_t scaled[CRYPTONITE_DECAF_448_SER_BYTES],
const uint8_t base[CRYPTONITE_DECAF_448_SER_BYTES],
const cryptonite_decaf_448_scalar_t scalar,
cryptonite_decaf_bool_t allow_identity,
cryptonite_decaf_bool_t short_circuit
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_WARN_UNUSED CRYPTONITE_DECAF_NOINLINE;
/**
* @brief RFC 7748 Diffie-Hellman scalarmul. This function uses a different
* (non-Decaf) encoding.
*
* @param [out] scaled The scaled point base*scalar
* @param [in] base The point to be scaled.
* @param [in] scalar The scalar to multiply by.
*
* @retval CRYPTONITE_DECAF_SUCCESS The scalarmul succeeded.
* @retval CRYPTONITE_DECAF_FAILURE The scalarmul didn't succeed, because the base
* point is in a small subgroup.
*/
cryptonite_decaf_error_t cryptonite_decaf_x448 (
uint8_t out[CRYPTONITE_DECAF_X448_PUBLIC_BYTES],
const uint8_t base[CRYPTONITE_DECAF_X448_PUBLIC_BYTES],
const uint8_t scalar[CRYPTONITE_DECAF_X448_PRIVATE_BYTES]
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_WARN_UNUSED CRYPTONITE_DECAF_NOINLINE;
/** The base point for X448 Diffie-Hellman */
extern const uint8_t cryptonite_decaf_x448_base_point[CRYPTONITE_DECAF_X448_PUBLIC_BYTES] CRYPTONITE_DECAF_API_VIS;
/**
* @brief RFC 7748 Diffie-Hellman base point scalarmul. This function uses
* a different (non-Decaf) encoding.
*
* @deprecated Renamed to cryptonite_decaf_x448_derive_public_key.
* I have no particular timeline for removing this name.
*
* @param [out] scaled The scaled point base*scalar
* @param [in] scalar The scalar to multiply by.
*/
void cryptonite_decaf_x448_generate_key (
uint8_t out[CRYPTONITE_DECAF_X448_PUBLIC_BYTES],
const uint8_t scalar[CRYPTONITE_DECAF_X448_PRIVATE_BYTES]
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE CRYPTONITE_DECAF_DEPRECATED("Renamed to cryptonite_decaf_x448_derive_public_key");
/**
* @brief RFC 7748 Diffie-Hellman base point scalarmul. This function uses
* a different (non-Decaf) encoding.
*
* Does exactly the same thing as cryptonite_decaf_x448_generate_key,
* but has a better name.
*
* @param [out] scaled The scaled point base*scalar
* @param [in] scalar The scalar to multiply by.
*/
void cryptonite_decaf_x448_derive_public_key (
uint8_t out[CRYPTONITE_DECAF_X448_PUBLIC_BYTES],
const uint8_t scalar[CRYPTONITE_DECAF_X448_PRIVATE_BYTES]
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/* FUTURE: uint8_t cryptonite_decaf_448_encode_like_curve448) */
/**
* @brief Precompute a table for fast scalar multiplication.
* Some implementations do not include precomputed points; for
* those implementations, this implementation simply copies the
* point.
*
* @param [out] a A precomputed table of multiples of the point.
* @param [in] b Any point.
*/
void cryptonite_decaf_448_precompute (
cryptonite_decaf_448_precomputed_s *a,
const cryptonite_decaf_448_point_t b
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Multiply a precomputed base point by a scalar:
* scaled = scalar*base.
* Some implementations do not include precomputed points; for
* those implementations, this function is the same as
* cryptonite_decaf_448_point_scalarmul
*
* @param [out] scaled The scaled point base*scalar
* @param [in] base The point to be scaled.
* @param [in] scalar The scalar to multiply by.
*/
void cryptonite_decaf_448_precomputed_scalarmul (
cryptonite_decaf_448_point_t scaled,
const cryptonite_decaf_448_precomputed_s *base,
const cryptonite_decaf_448_scalar_t scalar
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Multiply two base points by two scalars:
* scaled = scalar1*base1 + scalar2*base2.
*
* Equivalent to two calls to cryptonite_decaf_448_point_scalarmul, but may be
* faster.
*
* @param [out] combo The linear combination scalar1*base1 + scalar2*base2.
* @param [in] base1 A first point to be scaled.
* @param [in] scalar1 A first scalar to multiply by.
* @param [in] base2 A second point to be scaled.
* @param [in] scalar2 A second scalar to multiply by.
*/
void cryptonite_decaf_448_point_double_scalarmul (
cryptonite_decaf_448_point_t combo,
const cryptonite_decaf_448_point_t base1,
const cryptonite_decaf_448_scalar_t scalar1,
const cryptonite_decaf_448_point_t base2,
const cryptonite_decaf_448_scalar_t scalar2
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* Multiply one base point by two scalars:
*
* a1 = scalar1 * base
* a2 = scalar2 * base
*
* Equivalent to two calls to cryptonite_decaf_448_point_scalarmul, but may be
* faster.
*
* @param [out] a1 The first multiple. It may be the same as the input point.
* @param [out] a2 The second multiple. It may be the same as the input point.
* @param [in] base1 A point to be scaled.
* @param [in] scalar1 A first scalar to multiply by.
* @param [in] scalar2 A second scalar to multiply by.
*/
void cryptonite_decaf_448_point_dual_scalarmul (
cryptonite_decaf_448_point_t a1,
cryptonite_decaf_448_point_t a2,
const cryptonite_decaf_448_point_t base1,
const cryptonite_decaf_448_scalar_t scalar1,
const cryptonite_decaf_448_scalar_t scalar2
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Multiply two base points by two scalars:
* scaled = scalar1*cryptonite_decaf_448_point_base + scalar2*base2.
*
* Otherwise equivalent to cryptonite_decaf_448_point_double_scalarmul, but may be
* faster at the expense of being variable time.
*
* @param [out] combo The linear combination scalar1*base + scalar2*base2.
* @param [in] scalar1 A first scalar to multiply by.
* @param [in] base2 A second point to be scaled.
* @param [in] scalar2 A second scalar to multiply by.
*
* @warning: This function takes variable time, and may leak the scalars
* used. It is designed for signature verification.
*/
void cryptonite_decaf_448_base_double_scalarmul_non_secret (
cryptonite_decaf_448_point_t combo,
const cryptonite_decaf_448_scalar_t scalar1,
const cryptonite_decaf_448_point_t base2,
const cryptonite_decaf_448_scalar_t scalar2
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Constant-time decision between two points. If pick_b
* is zero, out = a; else out = b.
*
* @param [out] out The output. It may be the same as either input.
* @param [in] a Any point.
* @param [in] b Any point.
* @param [in] pick_b If nonzero, choose point b.
*/
void cryptonite_decaf_448_point_cond_sel (
cryptonite_decaf_448_point_t out,
const cryptonite_decaf_448_point_t a,
const cryptonite_decaf_448_point_t b,
cryptonite_decaf_word_t pick_b
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Constant-time decision between two scalars. If pick_b
* is zero, out = a; else out = b.
*
* @param [out] out The output. It may be the same as either input.
* @param [in] a Any scalar.
* @param [in] b Any scalar.
* @param [in] pick_b If nonzero, choose scalar b.
*/
void cryptonite_decaf_448_scalar_cond_sel (
cryptonite_decaf_448_scalar_t out,
const cryptonite_decaf_448_scalar_t a,
const cryptonite_decaf_448_scalar_t b,
cryptonite_decaf_word_t pick_b
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Test that a point is valid, for debugging purposes.
*
* @param [in] to_test The point to test.
* @retval CRYPTONITE_DECAF_TRUE The point is valid.
* @retval CRYPTONITE_DECAF_FALSE The point is invalid.
*/
cryptonite_decaf_bool_t cryptonite_decaf_448_point_valid (
const cryptonite_decaf_448_point_t to_test
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_WARN_UNUSED CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Torque a point, for debugging purposes. The output
* will be equal to the input.
*
* @param [out] q The point to torque.
* @param [in] p The point to torque.
*/
void cryptonite_decaf_448_point_debugging_torque (
cryptonite_decaf_448_point_t q,
const cryptonite_decaf_448_point_t p
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Projectively scale a point, for debugging purposes.
* The output will be equal to the input, and will be valid
* even if the factor is zero.
*
* @param [out] q The point to scale.
* @param [in] p The point to scale.
* @param [in] factor Serialized GF factor to scale.
*/
void cryptonite_decaf_448_point_debugging_pscale (
cryptonite_decaf_448_point_t q,
const cryptonite_decaf_448_point_t p,
const unsigned char factor[CRYPTONITE_DECAF_448_SER_BYTES]
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Almost-Elligator-like hash to curve.
*
* Call this function with the output of a hash to make a hash to the curve.
*
* This function runs Elligator2 on the cryptonite_decaf_448 Jacobi quartic model. It then
* uses the isogeny to put the result in twisted Edwards form. As a result,
* it is safe (cannot produce points of order 4), and would be compatible with
* hypothetical other implementations of Decaf using a Montgomery or untwisted
* Edwards model.
*
* Unlike Elligator, this function may be up to 4:1 on [0,(p-1)/2]:
* A factor of 2 due to the isogeny.
* A factor of 2 because we quotient out the 2-torsion.
*
* This makes it about 8:1 overall, or 16:1 overall on curves with cofactor 8.
*
* Negating the input (mod q) results in the same point. Inverting the input
* (mod q) results in the negative point. This is the same as Elligator.
*
* This function isn't quite indifferentiable from a random oracle.
* However, it is suitable for many protocols, including SPEKE and SPAKE2 EE.
* Furthermore, calling it twice with independent seeds and adding the results
* is indifferentiable from a random oracle.
*
* @param [in] hashed_data Output of some hash function.
* @param [out] pt The data hashed to the curve.
*/
void
cryptonite_decaf_448_point_from_hash_nonuniform (
cryptonite_decaf_448_point_t pt,
const unsigned char hashed_data[CRYPTONITE_DECAF_448_HASH_BYTES]
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Indifferentiable hash function encoding to curve.
*
* Equivalent to calling cryptonite_decaf_448_point_from_hash_nonuniform twice and adding.
*
* @param [in] hashed_data Output of some hash function.
* @param [out] pt The data hashed to the curve.
*/
void cryptonite_decaf_448_point_from_hash_uniform (
cryptonite_decaf_448_point_t pt,
const unsigned char hashed_data[2*CRYPTONITE_DECAF_448_HASH_BYTES]
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE;
/**
* @brief Inverse of elligator-like hash to curve.
*
* This function writes to the buffer, to make it so that
* cryptonite_decaf_448_point_from_hash_nonuniform(buffer) = pt if
* possible. Since there may be multiple preimages, the
* "which" parameter chooses between them. To ensure uniform
* inverse sampling, this function succeeds or fails
* independently for different "which" values.
*
* @param [out] recovered_hash Encoded data.
* @param [in] pt The point to encode.
* @param [in] which A value determining which inverse point
* to return.
*
* @retval CRYPTONITE_DECAF_SUCCESS The inverse succeeded.
* @retval CRYPTONITE_DECAF_FAILURE The inverse failed.
*/
cryptonite_decaf_error_t
cryptonite_decaf_448_invert_elligator_nonuniform (
unsigned char recovered_hash[CRYPTONITE_DECAF_448_HASH_BYTES],
const cryptonite_decaf_448_point_t pt,
uint32_t which
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE CRYPTONITE_DECAF_WARN_UNUSED;
/**
* @brief Inverse of elligator-like hash to curve.
*
* This function writes to the buffer, to make it so that
* cryptonite_decaf_448_point_from_hash_uniform(buffer) = pt if
* possible. Since there may be multiple preimages, the
* "which" parameter chooses between them. To ensure uniform
* inverse sampling, this function succeeds or fails
* independently for different "which" values.
*
* @param [out] recovered_hash Encoded data.
* @param [in] pt The point to encode.
* @param [in] which A value determining which inverse point
* to return.
*
* @retval CRYPTONITE_DECAF_SUCCESS The inverse succeeded.
* @retval CRYPTONITE_DECAF_FAILURE The inverse failed.
*/
cryptonite_decaf_error_t
cryptonite_decaf_448_invert_elligator_uniform (
unsigned char recovered_hash[2*CRYPTONITE_DECAF_448_HASH_BYTES],
const cryptonite_decaf_448_point_t pt,
uint32_t which
) CRYPTONITE_DECAF_API_VIS CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_NOINLINE CRYPTONITE_DECAF_WARN_UNUSED;
/**
* @brief Overwrite scalar with zeros.
*/
void cryptonite_decaf_448_scalar_destroy (
cryptonite_decaf_448_scalar_t scalar
) CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_API_VIS;
/**
* @brief Overwrite point with zeros.
*/
void cryptonite_decaf_448_point_destroy (
cryptonite_decaf_448_point_t point
) CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_API_VIS;
/**
* @brief Overwrite precomputed table with zeros.
*/
void cryptonite_decaf_448_precomputed_destroy (
cryptonite_decaf_448_precomputed_s *pre
) CRYPTONITE_DECAF_NONNULL CRYPTONITE_DECAF_API_VIS;
#ifdef __cplusplus
} /* extern "C" */
#endif
#endif /* __CRYPTONITE_DECAF_POINT_448_H__ */

View File

@ -0,0 +1 @@
/* Not needed if 448-only */

View File

@ -0,0 +1,96 @@
/*
* Copyright (C) 2006-2009 Vincent Hanquez <vincent@snarc.org>
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
* IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
* OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
* IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
* INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
* NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
* DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
* THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
* (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
* THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*/
#ifndef CRYPTONITE_DECAF_SHAKE_H
#define CRYPTONITE_DECAF_SHAKE_H
#include "cryptonite_sha3.h"
#include <decaf/common.h>
#define CHUNK_SIZE_32 0x80000000
typedef struct sha3_shake256_ctx
{
struct sha3_ctx sc[1];
uint8_t filler[136]; // 200 - 2*(256/8)
}
cryptonite_decaf_shake256_ctx_t[1];
static inline void cryptonite_decaf_shake256_init(cryptonite_decaf_shake256_ctx_t ctx)
{
cryptonite_sha3_init(ctx -> sc, 256);
}
static inline void cryptonite_decaf_shake256_update(cryptonite_decaf_shake256_ctx_t ctx, const uint8_t *in, size_t inlen)
{
#if __SIZE_MAX__ > UINT32_MAX
// split data over 4 GB in 2-GB chunks
while (inlen > UINT32_MAX) {
cryptonite_sha3_update(ctx -> sc, in, CHUNK_SIZE_32);
inlen -= CHUNK_SIZE_32;
in += CHUNK_SIZE_32;
}
#endif
cryptonite_sha3_update(ctx -> sc, in, (uint32_t) inlen);
}
static inline void cryptonite_decaf_shake256_output(cryptonite_decaf_shake256_ctx_t ctx, uint8_t *out, size_t outlen) {
#if __SIZE_MAX__ > UINT32_MAX
// split data over 4 GB in 2-GB chunks
while (outlen > UINT32_MAX) {
cryptonite_sha3_output(ctx -> sc, out, CHUNK_SIZE_32);
outlen -= CHUNK_SIZE_32;
out += CHUNK_SIZE_32;
}
#endif
cryptonite_sha3_output(ctx -> sc, out, (uint32_t) outlen);
}
static inline void cryptonite_decaf_shake256_final(cryptonite_decaf_shake256_ctx_t ctx, uint8_t *out, size_t outlen)
{
cryptonite_sha3_finalize_shake(ctx -> sc);
cryptonite_decaf_shake256_output(ctx, out, outlen);
cryptonite_decaf_shake256_init(ctx);
}
static inline void cryptonite_decaf_shake256_destroy(cryptonite_decaf_shake256_ctx_t ctx)
{
cryptonite_decaf_bzero(ctx, sizeof(*ctx));
}
static inline void cryptonite_decaf_shake256_hash(uint8_t *out, size_t outlen, const uint8_t *in, size_t inlen)
{
cryptonite_decaf_shake256_ctx_t ctx;
cryptonite_decaf_shake256_init(ctx);
cryptonite_decaf_shake256_update(ctx, in, inlen);
cryptonite_sha3_finalize_shake(ctx -> sc);
cryptonite_decaf_shake256_output(ctx, out, outlen);
cryptonite_decaf_shake256_destroy(ctx);
}
#endif

107
cbits/decaf/include/field.h Normal file
View File

@ -0,0 +1,107 @@
/**
* @file field.h
* @brief Generic gf header.
* @copyright
* Copyright (c) 2014 Cryptography Research, Inc. \n
* Released under the MIT License. See LICENSE.txt for license information.
* @author Mike Hamburg
*/
#ifndef __GF_H__
#define __GF_H__
#include "constant_time.h"
#include "f_field.h"
#include <string.h>
/** Square x, n times. */
static CRYPTONITE_DECAF_INLINE void cryptonite_gf_sqrn (
cryptonite_gf_s *__restrict__ y,
const gf x,
int n
) {
gf tmp;
assert(n>0);
if (n&1) {
cryptonite_gf_sqr(y,x);
n--;
} else {
cryptonite_gf_sqr(tmp,x);
cryptonite_gf_sqr(y,tmp);
n-=2;
}
for (; n; n-=2) {
cryptonite_gf_sqr(tmp,y);
cryptonite_gf_sqr(y,tmp);
}
}
#define cryptonite_gf_add_nr cryptonite_gf_add_RAW
/** Subtract mod p. Bias by 2 and don't reduce */
static inline void cryptonite_gf_sub_nr ( gf c, const gf a, const gf b ) {
cryptonite_gf_sub_RAW(c,a,b);
cryptonite_gf_bias(c, 2);
if (GF_HEADROOM < 3) cryptonite_gf_weak_reduce(c);
}
/** Subtract mod p. Bias by amt but don't reduce. */
static inline void cryptonite_gf_subx_nr ( gf c, const gf a, const gf b, int amt ) {
cryptonite_gf_sub_RAW(c,a,b);
cryptonite_gf_bias(c, amt);
if (GF_HEADROOM < amt+1) cryptonite_gf_weak_reduce(c);
}
/** Mul by signed int. Not constant-time WRT the sign of that int. */
static inline void cryptonite_gf_mulw(gf c, const gf a, int32_t w) {
if (w>0) {
cryptonite_gf_mulw_unsigned(c, a, w);
} else {
cryptonite_gf_mulw_unsigned(c, a, -w);
cryptonite_gf_sub(c,ZERO,c);
}
}
/** Constant time, x = is_z ? z : y */
static inline void cryptonite_gf_cond_sel(gf x, const gf y, const gf z, mask_t is_z) {
constant_time_select(x,y,z,sizeof(gf),is_z,0);
}
/** Constant time, if (neg) x=-x; */
static inline void cryptonite_gf_cond_neg(gf x, mask_t neg) {
gf y;
cryptonite_gf_sub(y,ZERO,x);
cryptonite_gf_cond_sel(x,x,y,neg);
}
/** Constant time, if (swap) (x,y) = (y,x); */
static inline void
cryptonite_gf_cond_swap(gf x, cryptonite_gf_s *__restrict__ y, mask_t swap) {
constant_time_cond_swap(x,y,sizeof(cryptonite_gf_s),swap);
}
static CRYPTONITE_DECAF_INLINE void cryptonite_gf_mul_qnr(cryptonite_gf_s *__restrict__ out, const gf x) {
#if P_MOD_8 == 5
/* r = QNR * r0^2 */
cryptonite_gf_mul(out,x,SQRT_MINUS_ONE);
#elif P_MOD_8 == 3 || P_MOD_8 == 7
cryptonite_gf_sub(out,ZERO,x);
#else
#error "Only supporting p=3,5,7 mod 8"
#endif
}
static CRYPTONITE_DECAF_INLINE void cryptonite_gf_div_qnr(cryptonite_gf_s *__restrict__ out, const gf x) {
#if P_MOD_8 == 5
/* r = QNR * r0^2 */
cryptonite_gf_mul(out,x,SQRT_MINUS_ONE);
cryptonite_gf_sub(out,ZERO,out);
#elif P_MOD_8 == 3 || P_MOD_8 == 7
cryptonite_gf_sub(out,ZERO,x);
#else
#error "Only supporting p=3,5,7 mod 8"
#endif
}
#endif // __GF_H__

View File

@ -0,0 +1,6 @@
/* portable_endian.h not used */
#if defined(__MINGW32__)
// does not exist on MinGW, but unused anyway
extern int posix_memalign(void **, size_t, size_t);
#endif

281
cbits/decaf/include/word.h Normal file
View File

@ -0,0 +1,281 @@
/* Copyright (c) 2014 Cryptography Research, Inc.
* Released under the MIT License. See LICENSE.txt for license information.
*/
#ifndef __WORD_H__
#define __WORD_H__
/* for posix_memalign */
#define _XOPEN_SOURCE 600
#define __STDC_WANT_LIB_EXT1__ 1 /* for memset_s */
#include <string.h>
#if defined(__sun) && defined(__SVR4)
extern int posix_memalign(void **, size_t, size_t);
#endif
#include <assert.h>
#include <stdint.h>
#include "arch_intrinsics.h"
#include <decaf/common.h>
#ifndef _BSD_SOURCE
#define _BSD_SOURCE 1
#endif
#ifndef _DEFAULT_SOURCE
#define _DEFAULT_SOURCE 1
#endif
#include "portable_endian.h"
#include <stdlib.h>
#include <sys/types.h>
#include <inttypes.h>
#if defined(__ARM_NEON__)
#include <arm_neon.h>
#elif defined(__SSE2__)
#if !defined(__GNUC__) || __clang__ || __GNUC__ >= 5 || (__GNUC__==4 && __GNUC_MINOR__ >= 4)
#include <immintrin.h>
#else
#include <emmintrin.h>
#endif
#endif
#if (ARCH_WORD_BITS == 64)
typedef uint64_t word_t, mask_t;
typedef __uint128_t dword_t;
typedef int32_t hsword_t;
typedef int64_t sword_t;
typedef __int128_t dsword_t;
#elif (ARCH_WORD_BITS == 32)
typedef uint32_t word_t, mask_t;
typedef uint64_t dword_t;
typedef int16_t hsword_t;
typedef int32_t sword_t;
typedef int64_t dsword_t;
#else
#error "For now, libdecaf only supports 32- and 64-bit architectures."
#endif
/* Scalar limbs are keyed off of the API word size instead of the arch word size. */
#if CRYPTONITE_DECAF_WORD_BITS == 64
#define SC_LIMB(x) (x##ull)
#elif CRYPTONITE_DECAF_WORD_BITS == 32
#define SC_LIMB(x) ((uint32_t)x##ull),(x##ull>>32)
#else
#error "For now, libdecaf only supports 32- and 64-bit architectures."
#endif
#ifdef __ARM_NEON__
typedef uint32x4_t vecmask_t;
#elif __clang__
typedef uint64_t uint64x2_t __attribute__((ext_vector_type(2)));
typedef int64_t int64x2_t __attribute__((ext_vector_type(2)));
typedef uint64_t uint64x4_t __attribute__((ext_vector_type(4)));
typedef int64_t int64x4_t __attribute__((ext_vector_type(4)));
typedef uint32_t uint32x4_t __attribute__((ext_vector_type(4)));
typedef int32_t int32x4_t __attribute__((ext_vector_type(4)));
typedef uint32_t uint32x2_t __attribute__((ext_vector_type(2)));
typedef int32_t int32x2_t __attribute__((ext_vector_type(2)));
typedef uint32_t uint32x8_t __attribute__((ext_vector_type(8)));
typedef int32_t int32x8_t __attribute__((ext_vector_type(8)));
typedef word_t vecmask_t __attribute__((ext_vector_type(4)));
#else /* GCC, hopefully? */
typedef uint64_t uint64x2_t __attribute__((vector_size(16)));
typedef int64_t int64x2_t __attribute__((vector_size(16)));
typedef uint64_t uint64x4_t __attribute__((vector_size(32)));
typedef int64_t int64x4_t __attribute__((vector_size(32)));
typedef uint32_t uint32x4_t __attribute__((vector_size(16)));
typedef int32_t int32x4_t __attribute__((vector_size(16)));
typedef uint32_t uint32x2_t __attribute__((vector_size(8)));
typedef int32_t int32x2_t __attribute__((vector_size(8)));
typedef uint32_t uint32x8_t __attribute__((vector_size(32)));
typedef int32_t int32x8_t __attribute__((vector_size(32)));
typedef word_t vecmask_t __attribute__((vector_size(32)));
#endif
#if __AVX2__
#define VECTOR_ALIGNED __attribute__((aligned(32)))
typedef uint32x8_t big_register_t;
typedef uint64x4_t uint64xn_t;
typedef uint32x8_t uint32xn_t;
static CRYPTONITE_DECAF_INLINE big_register_t
br_set_to_mask(mask_t x) {
uint32_t y = (uint32_t)x;
big_register_t ret = {y,y,y,y,y,y,y,y};
return ret;
}
#elif __SSE2__
#define VECTOR_ALIGNED __attribute__((aligned(16)))
typedef uint32x4_t big_register_t;
typedef uint64x2_t uint64xn_t;
typedef uint32x4_t uint32xn_t;
static CRYPTONITE_DECAF_INLINE big_register_t
br_set_to_mask(mask_t x) {
uint32_t y = x;
big_register_t ret = {y,y,y,y};
return ret;
}
#elif __ARM_NEON__
#define VECTOR_ALIGNED __attribute__((aligned(16)))
typedef uint32x4_t big_register_t;
typedef uint64x2_t uint64xn_t;
typedef uint32x4_t uint32xn_t;
static CRYPTONITE_DECAF_INLINE big_register_t
br_set_to_mask(mask_t x) {
return vdupq_n_u32(x);
}
#elif _WIN64 || __amd64__ || __X86_64__ || __aarch64__
#define VECTOR_ALIGNED __attribute__((aligned(8)))
typedef uint64_t big_register_t, uint64xn_t;
typedef uint32_t uint32xn_t;
static CRYPTONITE_DECAF_INLINE big_register_t
br_set_to_mask(mask_t x) {
return (big_register_t)x;
}
#else
#define VECTOR_ALIGNED __attribute__((aligned(4)))
typedef uint64_t uint64xn_t;
typedef uint32_t uint32xn_t;
typedef uint32_t big_register_t;
static CRYPTONITE_DECAF_INLINE big_register_t
br_set_to_mask(mask_t x) {
return (big_register_t)x;
}
#endif
typedef struct {
uint64xn_t unaligned;
} __attribute__((packed)) unaligned_uint64xn_t;
typedef struct {
uint32xn_t unaligned;
} __attribute__((packed)) unaligned_uint32xn_t;
#if __AVX2__
static CRYPTONITE_DECAF_INLINE big_register_t
br_is_zero(big_register_t x) {
return (big_register_t)(x == br_set_to_mask(0));
}
#elif __SSE2__
static CRYPTONITE_DECAF_INLINE big_register_t
br_is_zero(big_register_t x) {
return (big_register_t)_mm_cmpeq_epi32((__m128i)x, _mm_setzero_si128());
//return (big_register_t)(x == br_set_to_mask(0));
}
#elif __ARM_NEON__
static CRYPTONITE_DECAF_INLINE big_register_t
br_is_zero(big_register_t x) {
return vceqq_u32(x,x^x);
}
#else
#define br_is_zero word_is_zero
#endif
/**
* Really call memset, in a way that prevents the compiler from optimizing it out.
* @param p The object to zeroize.
* @param c The char to set it to (probably zero).
* @param s The size of the object.
*/
#if defined(__DARWIN_C_LEVEL) || defined(__STDC_LIB_EXT1__)
#define HAS_MEMSET_S
#endif
#if !defined(__STDC_WANT_LIB_EXT1__) || __STDC_WANT_LIB_EXT1__ != 1
#define NEED_MEMSET_S_EXTERN
#endif
#ifdef HAS_MEMSET_S
#ifdef NEED_MEMSET_S_EXTERN
extern int memset_s(void *, size_t, int, size_t);
#endif
static CRYPTONITE_DECAF_INLINE void
really_memset(void *p, char c, size_t s) {
memset_s(p, s, c, s);
}
#else
/* PERF: use words? */
static CRYPTONITE_DECAF_INLINE void
really_memset(void *p, char c, size_t s) {
volatile char *pv = (volatile char *)p;
size_t i;
for (i=0; i<s; i++) pv[i] = c;
}
#endif
/**
* Allocate memory which is sufficiently aligned to be used for the
* largest vector on the system (for now that's a big_register_t).
*
* Man malloc says that it does this, but at least for AVX2 on MacOS X,
* it's lying.
*
* @param size The size of the region to allocate.
* @return A suitable pointer, which can be free'd with free(),
* or NULL if no memory can be allocated.
*/
static CRYPTONITE_DECAF_INLINE void *
malloc_vector(size_t size) {
void *out = NULL;
int ret = posix_memalign(&out, sizeof(big_register_t), size);
if (ret) {
return NULL;
} else {
return out;
}
}
/* PERF: vectorize vs unroll */
#ifdef __clang__
#if 100*__clang_major__ + __clang_minor__ > 305
#define UNROLL _Pragma("clang loop unroll(full)")
#endif
#endif
#ifndef UNROLL
#define UNROLL
#endif
/* The plan on booleans:
*
* The external interface uses cryptonite_decaf_bool_t, but this might be a different
* size than our particular arch's word_t (and thus mask_t). Also, the caller
* isn't guaranteed to pass it as nonzero. So bool_to_mask converts word sizes
* and checks nonzero.
*
* On the flip side, mask_t is always -1 or 0, but it might be a different size
* than cryptonite_decaf_bool_t.
*
* On the third hand, we have success vs boolean types, but that's handled in
* common.h: it converts between cryptonite_decaf_bool_t and cryptonite_decaf_error_t.
*/
static CRYPTONITE_DECAF_INLINE cryptonite_decaf_bool_t mask_to_bool (mask_t m) {
return (cryptonite_decaf_sword_t)(sword_t)m;
}
static CRYPTONITE_DECAF_INLINE mask_t bool_to_mask (cryptonite_decaf_bool_t m) {
/* On most arches this will be optimized to a simple cast. */
mask_t ret = 0;
unsigned int limit = sizeof(cryptonite_decaf_bool_t)/sizeof(mask_t);
if (limit < 1) limit = 1;
for (unsigned int i=0; i<limit; i++) {
ret |= ~ word_is_zero(m >> (i*8*sizeof(word_t)));
}
return ret;
}
static CRYPTONITE_DECAF_INLINE void ignore_result ( cryptonite_decaf_bool_t boo ) {
(void)boo;
}
#endif /* __WORD_H__ */

View File

@ -0,0 +1,101 @@
/* Copyright (c) 2014 Cryptography Research, Inc.
* Released under the MIT License. See LICENSE.txt for license information.
*/
#include "f_field.h"
#if (defined(__OPTIMIZE__) && !defined(__OPTIMIZE_SIZE__) && !I_HATE_UNROLLED_LOOPS) \
|| defined(CRYPTONITE_DECAF_FORCE_UNROLL)
#define REPEAT8(_x) _x _x _x _x _x _x _x _x
#define FOR_LIMB(_i,_start,_end,_x) do { _i=_start; REPEAT8( if (_i<_end) { _x; } _i++;) } while (0)
#else
#define FOR_LIMB(_i,_start,_end,_x) do { for (_i=_start; _i<_end; _i++) _x; } while (0)
#endif
void cryptonite_gf_mul (cryptonite_gf_s *__restrict__ cs, const gf as, const gf bs) {
const uint32_t *a = as->limb, *b = bs->limb;
uint32_t *c = cs->limb;
uint64_t accum0 = 0, accum1 = 0, accum2 = 0;
uint32_t mask = (1<<28) - 1;
uint32_t aa[8], bb[8];
int i,j;
for (i=0; i<8; i++) {
aa[i] = a[i] + a[i+8];
bb[i] = b[i] + b[i+8];
}
FOR_LIMB(j,0,8,{
accum2 = 0;
FOR_LIMB (i,0,j+1,{
accum2 += widemul(a[j-i],b[i]);
accum1 += widemul(aa[j-i],bb[i]);
accum0 += widemul(a[8+j-i], b[8+i]);
});
accum1 -= accum2;
accum0 += accum2;
accum2 = 0;
FOR_LIMB (i,j+1,8,{
accum0 -= widemul(a[8+j-i], b[i]);
accum2 += widemul(aa[8+j-i], bb[i]);
accum1 += widemul(a[16+j-i], b[8+i]);
});
accum1 += accum2;
accum0 += accum2;
c[j] = ((uint32_t)(accum0)) & mask;
c[j+8] = ((uint32_t)(accum1)) & mask;
accum0 >>= 28;
accum1 >>= 28;
});
accum0 += accum1;
accum0 += c[8];
accum1 += c[0];
c[8] = ((uint32_t)(accum0)) & mask;
c[0] = ((uint32_t)(accum1)) & mask;
accum0 >>= 28;
accum1 >>= 28;
c[9] += ((uint32_t)(accum0));
c[1] += ((uint32_t)(accum1));
}
void cryptonite_gf_mulw_unsigned (cryptonite_gf_s *__restrict__ cs, const gf as, uint32_t b) {
assert(b<1<<28);
const uint32_t *a = as->limb;
uint32_t *c = cs->limb;
uint64_t accum0 = 0, accum8 = 0;
uint32_t mask = (1ull<<28)-1;
int i;
FOR_LIMB(i,0,8,{
accum0 += widemul(b, a[i]);
accum8 += widemul(b, a[i+8]);
c[i] = accum0 & mask; accum0 >>= 28;
c[i+8] = accum8 & mask; accum8 >>= 28;
});
accum0 += accum8 + c[8];
c[8] = accum0 & mask;
c[9] += accum0 >> 28;
accum8 += c[0];
c[0] = accum8 & mask;
c[1] += accum8 >> 28;
}
void cryptonite_gf_sqr (cryptonite_gf_s *__restrict__ cs, const gf as) {
cryptonite_gf_mul(cs,as,as); /* Performs better with a dedicated square */
}

View File

@ -0,0 +1,55 @@
/* Copyright (c) 2014-2016 Cryptography Research, Inc.
* Released under the MIT License. See LICENSE.txt for license information.
*/
#define GF_HEADROOM 2
#define LIMB(x) (x##ull)&((1ull<<28)-1), (x##ull)>>28
#define FIELD_LITERAL(a,b,c,d,e,f,g,h) \
{{LIMB(a),LIMB(b),LIMB(c),LIMB(d),LIMB(e),LIMB(f),LIMB(g),LIMB(h)}}
#define LIMB_PLACE_VALUE(i) 28
void cryptonite_gf_add_RAW (gf out, const gf a, const gf b) {
for (unsigned int i=0; i<sizeof(*out)/sizeof(uint32xn_t); i++) {
((uint32xn_t*)out)[i] = ((const uint32xn_t*)a)[i] + ((const uint32xn_t*)b)[i];
}
/*
unsigned int i;
for (i=0; i<sizeof(*out)/sizeof(out->limb[0]); i++) {
out->limb[i] = a->limb[i] + b->limb[i];
}
*/
}
void cryptonite_gf_sub_RAW (gf out, const gf a, const gf b) {
for (unsigned int i=0; i<sizeof(*out)/sizeof(uint32xn_t); i++) {
((uint32xn_t*)out)[i] = ((const uint32xn_t*)a)[i] - ((const uint32xn_t*)b)[i];
}
/*
unsigned int i;
for (i=0; i<sizeof(*out)/sizeof(out->limb[0]); i++) {
out->limb[i] = a->limb[i] - b->limb[i];
}
*/
}
void cryptonite_gf_bias (gf a, int amt) {
uint32_t co1 = ((1ull<<28)-1)*amt, co2 = co1-amt;
uint32x4_t lo = {co1,co1,co1,co1}, hi = {co2,co1,co1,co1};
uint32x4_t *aa = (uint32x4_t*) a;
aa[0] += lo;
aa[1] += lo;
aa[2] += hi;
aa[3] += lo;
}
void cryptonite_gf_weak_reduce (gf a) {
uint32_t mask = (1ull<<28) - 1;
uint32_t tmp = a->limb[15] >> 28;
a->limb[8] += tmp;
for (unsigned int i=15; i>0; i--) {
a->limb[i] = (a->limb[i] & mask) + (a->limb[i-1]>>28);
}
a->limb[0] = (a->limb[0] & mask) + tmp;
}

View File

@ -0,0 +1,302 @@
/* Copyright (c) 2014 Cryptography Research, Inc.
* Released under the MIT License. See LICENSE.txt for license information.
*/
#include "f_field.h"
void cryptonite_gf_mul (cryptonite_gf_s *__restrict__ cs, const gf as, const gf bs) {
const uint64_t *a = as->limb, *b = bs->limb;
uint64_t *c = cs->limb;
__uint128_t accum0 = 0, accum1 = 0, accum2;
uint64_t mask = (1ull<<56) - 1;
uint64_t aa[4], bb[4], bbb[4];
unsigned int i;
for (i=0; i<4; i++) {
aa[i] = a[i] + a[i+4];
bb[i] = b[i] + b[i+4];
bbb[i] = bb[i] + b[i+4];
}
int I_HATE_UNROLLED_LOOPS = 0;
if (I_HATE_UNROLLED_LOOPS) {
/* The compiler probably won't unroll this,
* so it's like 80% slower.
*/
for (i=0; i<4; i++) {
accum2 = 0;
unsigned int j;
for (j=0; j<=i; j++) {
accum2 += widemul(a[j], b[i-j]);
accum1 += widemul(aa[j], bb[i-j]);
accum0 += widemul(a[j+4], b[i-j+4]);
}
for (; j<4; j++) {
accum2 += widemul(a[j], b[i-j+8]);
accum1 += widemul(aa[j], bbb[i-j+4]);
accum0 += widemul(a[j+4], bb[i-j+4]);
}
accum1 -= accum2;
accum0 += accum2;
c[i] = ((uint64_t)(accum0)) & mask;
c[i+4] = ((uint64_t)(accum1)) & mask;
accum0 >>= 56;
accum1 >>= 56;
}
} else {
accum2 = widemul(a[0], b[0]);
accum1 += widemul(aa[0], bb[0]);
accum0 += widemul(a[4], b[4]);
accum2 += widemul(a[1], b[7]);
accum1 += widemul(aa[1], bbb[3]);
accum0 += widemul(a[5], bb[3]);
accum2 += widemul(a[2], b[6]);
accum1 += widemul(aa[2], bbb[2]);
accum0 += widemul(a[6], bb[2]);
accum2 += widemul(a[3], b[5]);
accum1 += widemul(aa[3], bbb[1]);
accum0 += widemul(a[7], bb[1]);
accum1 -= accum2;
accum0 += accum2;
c[0] = ((uint64_t)(accum0)) & mask;
c[4] = ((uint64_t)(accum1)) & mask;
accum0 >>= 56;
accum1 >>= 56;
accum2 = widemul(a[0], b[1]);
accum1 += widemul(aa[0], bb[1]);
accum0 += widemul(a[4], b[5]);
accum2 += widemul(a[1], b[0]);
accum1 += widemul(aa[1], bb[0]);
accum0 += widemul(a[5], b[4]);
accum2 += widemul(a[2], b[7]);
accum1 += widemul(aa[2], bbb[3]);
accum0 += widemul(a[6], bb[3]);
accum2 += widemul(a[3], b[6]);
accum1 += widemul(aa[3], bbb[2]);
accum0 += widemul(a[7], bb[2]);
accum1 -= accum2;
accum0 += accum2;
c[1] = ((uint64_t)(accum0)) & mask;
c[5] = ((uint64_t)(accum1)) & mask;
accum0 >>= 56;
accum1 >>= 56;
accum2 = widemul(a[0], b[2]);
accum1 += widemul(aa[0], bb[2]);
accum0 += widemul(a[4], b[6]);
accum2 += widemul(a[1], b[1]);
accum1 += widemul(aa[1], bb[1]);
accum0 += widemul(a[5], b[5]);
accum2 += widemul(a[2], b[0]);
accum1 += widemul(aa[2], bb[0]);
accum0 += widemul(a[6], b[4]);
accum2 += widemul(a[3], b[7]);
accum1 += widemul(aa[3], bbb[3]);
accum0 += widemul(a[7], bb[3]);
accum1 -= accum2;
accum0 += accum2;
c[2] = ((uint64_t)(accum0)) & mask;
c[6] = ((uint64_t)(accum1)) & mask;
accum0 >>= 56;
accum1 >>= 56;
accum2 = widemul(a[0], b[3]);
accum1 += widemul(aa[0], bb[3]);
accum0 += widemul(a[4], b[7]);
accum2 += widemul(a[1], b[2]);
accum1 += widemul(aa[1], bb[2]);
accum0 += widemul(a[5], b[6]);
accum2 += widemul(a[2], b[1]);
accum1 += widemul(aa[2], bb[1]);
accum0 += widemul(a[6], b[5]);
accum2 += widemul(a[3], b[0]);
accum1 += widemul(aa[3], bb[0]);
accum0 += widemul(a[7], b[4]);
accum1 -= accum2;
accum0 += accum2;
c[3] = ((uint64_t)(accum0)) & mask;
c[7] = ((uint64_t)(accum1)) & mask;
accum0 >>= 56;
accum1 >>= 56;
} /* !I_HATE_UNROLLED_LOOPS */
accum0 += accum1;
accum0 += c[4];
accum1 += c[0];
c[4] = ((uint64_t)(accum0)) & mask;
c[0] = ((uint64_t)(accum1)) & mask;
accum0 >>= 56;
accum1 >>= 56;
c[5] += ((uint64_t)(accum0));
c[1] += ((uint64_t)(accum1));
}
void cryptonite_gf_mulw_unsigned (cryptonite_gf_s *__restrict__ cs, const gf as, uint32_t b) {
const uint64_t *a = as->limb;
uint64_t *c = cs->limb;
__uint128_t accum0 = 0, accum4 = 0;
uint64_t mask = (1ull<<56) - 1;
int i;
for (i=0; i<4; i++) {
accum0 += widemul(b, a[i]);
accum4 += widemul(b, a[i+4]);
c[i] = accum0 & mask; accum0 >>= 56;
c[i+4] = accum4 & mask; accum4 >>= 56;
}
accum0 += accum4 + c[4];
c[4] = accum0 & mask;
c[5] += accum0 >> 56;
accum4 += c[0];
c[0] = accum4 & mask;
c[1] += accum4 >> 56;
}
void cryptonite_gf_sqr (cryptonite_gf_s *__restrict__ cs, const gf as) {
const uint64_t *a = as->limb;
uint64_t *c = cs->limb;
__uint128_t accum0 = 0, accum1 = 0, accum2;
uint64_t mask = (1ull<<56) - 1;
uint64_t aa[4];
/* For some reason clang doesn't vectorize this without prompting? */
unsigned int i;
for (i=0; i<4; i++) {
aa[i] = a[i] + a[i+4];
}
accum2 = widemul(a[0],a[3]);
accum0 = widemul(aa[0],aa[3]);
accum1 = widemul(a[4],a[7]);
accum2 += widemul(a[1], a[2]);
accum0 += widemul(aa[1], aa[2]);
accum1 += widemul(a[5], a[6]);
accum0 -= accum2;
accum1 += accum2;
c[3] = ((uint64_t)(accum1))<<1 & mask;
c[7] = ((uint64_t)(accum0))<<1 & mask;
accum0 >>= 55;
accum1 >>= 55;
accum0 += widemul(2*aa[1],aa[3]);
accum1 += widemul(2*a[5], a[7]);
accum0 += widemul(aa[2], aa[2]);
accum1 += accum0;
accum0 -= widemul(2*a[1], a[3]);
accum1 += widemul(a[6], a[6]);
accum2 = widemul(a[0],a[0]);
accum1 -= accum2;
accum0 += accum2;
accum0 -= widemul(a[2], a[2]);
accum1 += widemul(aa[0], aa[0]);
accum0 += widemul(a[4], a[4]);
c[0] = ((uint64_t)(accum0)) & mask;
c[4] = ((uint64_t)(accum1)) & mask;
accum0 >>= 56;
accum1 >>= 56;
accum2 = widemul(2*aa[2],aa[3]);
accum0 -= widemul(2*a[2], a[3]);
accum1 += widemul(2*a[6], a[7]);
accum1 += accum2;
accum0 += accum2;
accum2 = widemul(2*a[0],a[1]);
accum1 += widemul(2*aa[0], aa[1]);
accum0 += widemul(2*a[4], a[5]);
accum1 -= accum2;
accum0 += accum2;
c[1] = ((uint64_t)(accum0)) & mask;
c[5] = ((uint64_t)(accum1)) & mask;
accum0 >>= 56;
accum1 >>= 56;
accum2 = widemul(aa[3],aa[3]);
accum0 -= widemul(a[3], a[3]);
accum1 += widemul(a[7], a[7]);
accum1 += accum2;
accum0 += accum2;
accum2 = widemul(2*a[0],a[2]);
accum1 += widemul(2*aa[0], aa[2]);
accum0 += widemul(2*a[4], a[6]);
accum2 += widemul(a[1], a[1]);
accum1 += widemul(aa[1], aa[1]);
accum0 += widemul(a[5], a[5]);
accum1 -= accum2;
accum0 += accum2;
c[2] = ((uint64_t)(accum0)) & mask;
c[6] = ((uint64_t)(accum1)) & mask;
accum0 >>= 56;
accum1 >>= 56;
accum0 += c[3];
accum1 += c[7];
c[3] = ((uint64_t)(accum0)) & mask;
c[7] = ((uint64_t)(accum1)) & mask;
/* we could almost stop here, but it wouldn't be stable, so... */
accum0 >>= 56;
accum1 >>= 56;
c[4] += ((uint64_t)(accum0)) + ((uint64_t)(accum1));
c[0] += ((uint64_t)(accum1));
}

View File

@ -0,0 +1,38 @@
/* Copyright (c) 2014-2016 Cryptography Research, Inc.
* Released under the MIT License. See LICENSE.txt for license information.
*/
#define GF_HEADROOM 9999 /* Everything is reduced anyway */
#define FIELD_LITERAL(a,b,c,d,e,f,g,h) {{a,b,c,d,e,f,g,h}}
#define LIMB_PLACE_VALUE(i) 56
void cryptonite_gf_add_RAW (gf out, const gf a, const gf b) {
for (unsigned int i=0; i<8; i++) {
out->limb[i] = a->limb[i] + b->limb[i];
}
cryptonite_gf_weak_reduce(out);
}
void cryptonite_gf_sub_RAW (gf out, const gf a, const gf b) {
uint64_t co1 = ((1ull<<56)-1)*2, co2 = co1-2;
for (unsigned int i=0; i<8; i++) {
out->limb[i] = a->limb[i] - b->limb[i] + ((i==4) ? co2 : co1);
}
cryptonite_gf_weak_reduce(out);
}
void cryptonite_gf_bias (gf a, int amt) {
(void) a;
(void) amt;
}
void cryptonite_gf_weak_reduce (gf a) {
uint64_t mask = (1ull<<56) - 1;
uint64_t tmp = a->limb[7] >> 56;
a->limb[4] += tmp;
for (unsigned int i=7; i>0; i--) {
a->limb[i] = (a->limb[i] & mask) + (a->limb[i-1]>>56);
}
a->limb[0] = (a->limb[0] & mask) + tmp;
}

View File

@ -0,0 +1,46 @@
/**
* @cond internal
* @file f_arithmetic.c
* @copyright
* Copyright (c) 2014 Cryptography Research, Inc. \n
* Released under the MIT License. See LICENSE.txt for license information.
* @author Mike Hamburg
* @brief Field-specific arithmetic.
*/
#include "field.h"
mask_t cryptonite_gf_isr (
gf a,
const gf x
) {
gf L0, L1, L2;
cryptonite_gf_sqr (L1, x );
cryptonite_gf_mul (L2, x, L1 );
cryptonite_gf_sqr (L1, L2 );
cryptonite_gf_mul (L2, x, L1 );
cryptonite_gf_sqrn (L1, L2, 3 );
cryptonite_gf_mul (L0, L2, L1 );
cryptonite_gf_sqrn (L1, L0, 3 );
cryptonite_gf_mul (L0, L2, L1 );
cryptonite_gf_sqrn (L2, L0, 9 );
cryptonite_gf_mul (L1, L0, L2 );
cryptonite_gf_sqr (L0, L1 );
cryptonite_gf_mul (L2, x, L0 );
cryptonite_gf_sqrn (L0, L2, 18 );
cryptonite_gf_mul (L2, L1, L0 );
cryptonite_gf_sqrn (L0, L2, 37 );
cryptonite_gf_mul (L1, L2, L0 );
cryptonite_gf_sqrn (L0, L1, 37 );
cryptonite_gf_mul (L1, L2, L0 );
cryptonite_gf_sqrn (L0, L1, 111 );
cryptonite_gf_mul (L2, L1, L0 );
cryptonite_gf_sqr (L0, L2 );
cryptonite_gf_mul (L1, x, L0 );
cryptonite_gf_sqrn (L0, L1, 223 );
cryptonite_gf_mul (L1, L2, L0 );
cryptonite_gf_sqr (L2, L1);
cryptonite_gf_mul (L0, L2, x);
cryptonite_gf_copy(a,L1);
return cryptonite_gf_eq(L0,ONE);
}

108
cbits/decaf/p448/f_field.h Normal file
View File

@ -0,0 +1,108 @@
/**
* @file p448/f_field.h
* @author Mike Hamburg
*
* @copyright
* Copyright (c) 2015-2016 Cryptography Research, Inc. \n
* Released under the MIT License. See LICENSE.txt for license information.
*
* @brief Field-specific code for 2^448 - 2^224 - 1.
*
* @warning This file was automatically generated in Python.
* Please do not edit it.
*/
#ifndef __P448_F_FIELD_H__
#define __P448_F_FIELD_H__ 1
#include "constant_time.h"
#include <string.h>
#include <assert.h>
#include "word.h"
#define __CRYPTONITE_DECAF_448_GF_DEFINED__ 1
#define NLIMBS (64/sizeof(word_t))
#define X_SER_BYTES 56
#define SER_BYTES 56
typedef struct cryptonite_gf_448_s {
word_t limb[NLIMBS];
} __attribute__((aligned(16))) cryptonite_gf_448_s, cryptonite_gf_448_t[1];
#define GF_LIT_LIMB_BITS 56
#define GF_BITS 448
#define ZERO cryptonite_gf_448_ZERO
#define ONE cryptonite_gf_448_ONE
#define MODULUS cryptonite_gf_448_MODULUS
#define gf cryptonite_gf_448_t
#define cryptonite_gf_s cryptonite_gf_448_s
#define cryptonite_gf_eq cryptonite_gf_448_eq
#define cryptonite_gf_hibit cryptonite_gf_448_hibit
#define cryptonite_gf_copy cryptonite_gf_448_copy
#define cryptonite_gf_add cryptonite_gf_448_add
#define cryptonite_gf_sub cryptonite_gf_448_sub
#define cryptonite_gf_add_RAW cryptonite_gf_448_add_RAW
#define cryptonite_gf_sub_RAW cryptonite_gf_448_sub_RAW
#define cryptonite_gf_bias cryptonite_gf_448_bias
#define cryptonite_gf_weak_reduce cryptonite_gf_448_weak_reduce
#define cryptonite_gf_strong_reduce cryptonite_gf_448_strong_reduce
#define cryptonite_gf_mul cryptonite_gf_448_mul
#define cryptonite_gf_sqr cryptonite_gf_448_sqr
#define cryptonite_gf_mulw_unsigned cryptonite_gf_448_mulw_unsigned
#define cryptonite_gf_isr cryptonite_gf_448_isr
#define cryptonite_gf_serialize cryptonite_gf_448_serialize
#define cryptonite_gf_deserialize cryptonite_gf_448_deserialize
/* RFC 7748 support */
#define X_PUBLIC_BYTES X_SER_BYTES
#define X_PRIVATE_BYTES X_PUBLIC_BYTES
#define X_PRIVATE_BITS 448
#define SQRT_MINUS_ONE P448_SQRT_MINUS_ONE /* might not be defined */
#define INLINE_UNUSED __inline__ __attribute__((unused,always_inline))
#ifdef __cplusplus
extern "C" {
#endif
/* Defined below in f_impl.h */
static INLINE_UNUSED void cryptonite_gf_copy (gf out, const gf a) { *out = *a; }
static INLINE_UNUSED void cryptonite_gf_add_RAW (gf out, const gf a, const gf b);
static INLINE_UNUSED void cryptonite_gf_sub_RAW (gf out, const gf a, const gf b);
static INLINE_UNUSED void cryptonite_gf_bias (gf inout, int amount);
static INLINE_UNUSED void cryptonite_gf_weak_reduce (gf inout);
void cryptonite_gf_strong_reduce (gf inout);
void cryptonite_gf_add (gf out, const gf a, const gf b);
void cryptonite_gf_sub (gf out, const gf a, const gf b);
void cryptonite_gf_mul (cryptonite_gf_s *__restrict__ out, const gf a, const gf b);
void cryptonite_gf_mulw_unsigned (cryptonite_gf_s *__restrict__ out, const gf a, uint32_t b);
void cryptonite_gf_sqr (cryptonite_gf_s *__restrict__ out, const gf a);
mask_t cryptonite_gf_isr(gf a, const gf x); /** a^2 x = 1, QNR, or 0 if x=0. Return true if successful */
mask_t cryptonite_gf_eq (const gf x, const gf y);
mask_t cryptonite_gf_hibit (const gf x);
void cryptonite_gf_serialize (uint8_t *serial, const gf x,int with_highbit);
mask_t cryptonite_gf_deserialize (gf x, const uint8_t serial[SER_BYTES],int with_highbit);
#ifdef __cplusplus
} /* extern "C" */
#endif
#include "f_impl.h" /* Bring in the inline implementations */
#define P_MOD_8 7
#if P_MOD_8 == 5
extern const gf SQRT_MINUS_ONE;
#endif
#ifndef LIMBPERM
#define LIMBPERM(i) (i)
#endif
#define LIMB_MASK(i) (((1ull)<<LIMB_PLACE_VALUE(i))-1)
static const gf ZERO = {{{0}}}, ONE = {{{ [LIMBPERM(0)] = 1 }}};
#endif /* __P448_F_FIELD_H__ */

View File

@ -0,0 +1,133 @@
/**
* @file p448/f_generic.c
* @author Mike Hamburg
*
* @copyright
* Copyright (c) 2015-2016 Cryptography Research, Inc. \n
* Released under the MIT License. See LICENSE.txt for license information.
*
* @brief Generic arithmetic which has to be compiled per field.
*
* @warning This file was automatically generated in Python.
* Please do not edit it.
*/
#include "field.h"
static const gf MODULUS = {FIELD_LITERAL(
0xffffffffffffff, 0xffffffffffffff, 0xffffffffffffff, 0xffffffffffffff, 0xfffffffffffffe, 0xffffffffffffff, 0xffffffffffffff, 0xffffffffffffff
)};
#if P_MOD_8 == 5
const gf SQRT_MINUS_ONE = {FIELD_LITERAL(
/* NOPE */
)};
#endif
/** Serialize to wire format. */
void cryptonite_gf_serialize (uint8_t serial[SER_BYTES], const gf x, int with_hibit) {
gf red;
cryptonite_gf_copy(red, x);
cryptonite_gf_strong_reduce(red);
if (!with_hibit) { assert(cryptonite_gf_hibit(red) == 0); }
unsigned int j=0, fill=0;
dword_t buffer = 0;
UNROLL for (unsigned int i=0; i<(with_hibit ? X_SER_BYTES : SER_BYTES); i++) {
if (fill < 8 && j < NLIMBS) {
buffer |= ((dword_t)red->limb[LIMBPERM(j)]) << fill;
fill += LIMB_PLACE_VALUE(LIMBPERM(j));
j++;
}
serial[i] = buffer;
fill -= 8;
buffer >>= 8;
}
}
/** Return high bit of x = low bit of 2x mod p */
mask_t cryptonite_gf_hibit(const gf x) {
gf y;
cryptonite_gf_add(y,x,x);
cryptonite_gf_strong_reduce(y);
return -(y->limb[0]&1);
}
/** Deserialize from wire format; return -1 on success and 0 on failure. */
mask_t cryptonite_gf_deserialize (gf x, const uint8_t serial[SER_BYTES], int with_hibit) {
unsigned int j=0, fill=0;
dword_t buffer = 0;
dsword_t scarry = 0;
UNROLL for (unsigned int i=0; i<NLIMBS; i++) {
UNROLL while (fill < LIMB_PLACE_VALUE(LIMBPERM(i)) && j < (with_hibit ? X_SER_BYTES : SER_BYTES)) {
buffer |= ((dword_t)serial[j]) << fill;
fill += 8;
j++;
}
x->limb[LIMBPERM(i)] = (i<NLIMBS-1) ? buffer & LIMB_MASK(LIMBPERM(i)) : buffer;
fill -= LIMB_PLACE_VALUE(LIMBPERM(i));
buffer >>= LIMB_PLACE_VALUE(LIMBPERM(i));
scarry = (scarry + x->limb[LIMBPERM(i)] - MODULUS->limb[LIMBPERM(i)]) >> (8*sizeof(word_t));
}
mask_t succ = with_hibit ? -(mask_t)1 : ~cryptonite_gf_hibit(x);
return succ & word_is_zero(buffer) & ~word_is_zero(scarry);
}
/** Reduce to canonical form. */
void cryptonite_gf_strong_reduce (gf a) {
/* first, clear high */
cryptonite_gf_weak_reduce(a); /* Determined to have negligible perf impact. */
/* now the total is less than 2p */
/* compute total_value - p. No need to reduce mod p. */
dsword_t scarry = 0;
for (unsigned int i=0; i<NLIMBS; i++) {
scarry = scarry + a->limb[LIMBPERM(i)] - MODULUS->limb[LIMBPERM(i)];
a->limb[LIMBPERM(i)] = scarry & LIMB_MASK(LIMBPERM(i));
scarry >>= LIMB_PLACE_VALUE(LIMBPERM(i));
}
/* uncommon case: it was >= p, so now scarry = 0 and this = x
* common case: it was < p, so now scarry = -1 and this = x - p + 2^255
* so let's add back in p. will carry back off the top for 2^255.
*/
assert(word_is_zero(scarry) | word_is_zero(scarry+1));
word_t scarry_0 = scarry;
dword_t carry = 0;
/* add it back */
for (unsigned int i=0; i<NLIMBS; i++) {
carry = carry + a->limb[LIMBPERM(i)] + (scarry_0 & MODULUS->limb[LIMBPERM(i)]);
a->limb[LIMBPERM(i)] = carry & LIMB_MASK(LIMBPERM(i));
carry >>= LIMB_PLACE_VALUE(LIMBPERM(i));
}
assert(word_is_zero(carry + scarry_0));
}
/** Add two gf elements */
void cryptonite_gf_sub (gf d, const gf a, const gf b) {
cryptonite_gf_sub_RAW ( d, a, b );
cryptonite_gf_bias( d, 2 );
cryptonite_gf_weak_reduce ( d );
}
/** Subtract d = a-b */
void cryptonite_gf_add (gf d, const gf a, const gf b) {
cryptonite_gf_add_RAW ( d, a, b );
cryptonite_gf_weak_reduce ( d );
}
/** Compare a==b */
mask_t cryptonite_gf_eq(const gf a, const gf b) {
gf c;
cryptonite_gf_sub(c,a,b);
cryptonite_gf_strong_reduce(c);
mask_t ret=0;
for (unsigned int i=0; i<NLIMBS; i++) {
ret |= c->limb[LIMBPERM(i)];
}
return word_is_zero(ret);
}

22
cbits/decaf/tools/clean.sh Executable file
View File

@ -0,0 +1,22 @@
#!/bin/sh
# Usage: ./clean.sh
#
# Remove all files created by 'generate.sh'.
DEST_DIR="`dirname "$0"`"/..
rm "$DEST_DIR"/*.c
rm "$DEST_DIR"/include/constant_time.h
rm "$DEST_DIR"/include/field.h
rm "$DEST_DIR"/include/portable_endian.h
rm "$DEST_DIR"/include/word.h
rm "$DEST_DIR"/include/decaf.h
rm "$DEST_DIR"/include/decaf/common.h
rm "$DEST_DIR"/include/decaf/ed448.h
rm "$DEST_DIR"/include/decaf/point_255.h
rm "$DEST_DIR"/include/decaf/point_448.h
rm "$DEST_DIR"/include/decaf/sha512.h
rm -r "$DEST_DIR"/include/arch_*
rm -r "$DEST_DIR"/ed448goldilocks
rm -r "$DEST_DIR"/p448

121
cbits/decaf/tools/generate.sh Executable file
View File

@ -0,0 +1,121 @@
#!/bin/sh
# Usage: ./generate.sh /path/to/ed448goldilocks-code
#
# Generate all files from ed448goldilocks branch 'master'
# (available at <git://git.code.sf.net/p/ed448goldilocks/code>).
#
# Project is synced with upstream commit
# '0a6e96827595fa1a5a62d12ac83c3cc5dda6dd67', i.e. tag 'v0.9.2'.
#
# Notes about transformations applied:
#
# * only a subset of library files are used, cryptonite needing only x448
# and ed448. Some headers like point_255.h are still included but copied
# empty, as the definitions are not necessary. Only the simplest
# architectures arch_32 and arch_ref64 are used to get the best
# compatibility and generality over performance.
#
# * substitutions are performed in order to add a cryptonite_ prefix
# to all external symbols
#
# * code related to SHAKE is replaced by cryptonite code, referenced from
# a custom shake.h. As a consequence, portable_endian.h is not needed.
#
# * aligned(32) attributes used for stack alignment are replaced by
# aligned(16). This removes warnings on OpenBSD with GCC 4.2.1, and makes
# sure we get at least 16-byte alignment. 32-byte alignment is necessary
# only for AVX2 and arch_x86_64, which we don't have.
#
# * visibility("hidden") attributes are removed, as this is not supported
# on Windows/MinGW, and we have name mangling instead
#
# * function posix_memalign is defined in order to avoid a warning on
# Windows/MinGW. Hopefully it is not called. This definition is put
# inside portable_endian.h because this file is already included.
SRC_DIR="$1/src"
DEST_DIR="`dirname "$0"`"/..
ARCHITECTURES="arch_32 arch_ref64"
if [ ! -d "$SRC_DIR" ]; then
echo "$0: invalid source directory: $1" && exit 1
fi
convert() {
local FILE_NAME="`basename "$1"`"
local REPL
if [ "$FILE_NAME" = word.h ]; then
REPL='__attribute__((aligned(32)))'
else
REPL='__attribute__((aligned(16)))'
fi
sed <"$1" >"$2/$FILE_NAME" \
-e 's/ __attribute((visibility("hidden")))//g' \
-e 's/ __attribute__((visibility("hidden")))//g' \
-e 's/ __attribute__ ((visibility ("hidden")))//g' \
-e "s/__attribute__((aligned(32)))/$REPL/g" \
-e 's/decaf_/cryptonite_decaf_/g' \
-e 's/DECAF_/CRYPTONITE_DECAF_/g' \
-e 's/gf_/cryptonite_gf_/g' \
-e 's/keccakf/cryptonite_keccakf/g' \
-e 's/NO_CONTEXT_POINTS_HERE/CRYPTONITE_NO_CONTEXT_POINTS_HERE/g' \
-e 's/P25519_SQRT_MINUS_ONE/CRYPTONITE_P25519_SQRT_MINUS_ONE/g'
}
convert "$SRC_DIR"/utils.c "$DEST_DIR"
mkdir -p "$DEST_DIR"/include
convert "$SRC_DIR"/include/constant_time.h "$DEST_DIR"/include
convert "$SRC_DIR"/include/field.h "$DEST_DIR"/include
convert "$SRC_DIR"/include/word.h "$DEST_DIR"/include
for ARCH in $ARCHITECTURES; do
mkdir -p "$DEST_DIR"/include/$ARCH
convert "$SRC_DIR"/include/$ARCH/arch_intrinsics.h "$DEST_DIR"/include/$ARCH
done
mkdir -p "$DEST_DIR"/include/decaf
convert "$SRC_DIR"/GENERATED/include/decaf.h "$DEST_DIR"/include
convert "$SRC_DIR"/GENERATED/include/decaf/common.h "$DEST_DIR"/include/decaf
convert "$SRC_DIR"/GENERATED/include/decaf/ed448.h "$DEST_DIR"/include/decaf
convert "$SRC_DIR"/GENERATED/include/decaf/point_448.h "$DEST_DIR"/include/decaf
for CURVE in ed448goldilocks; do
mkdir -p "$DEST_DIR"/$CURVE
convert "$SRC_DIR"/GENERATED/c/$CURVE/decaf.c "$DEST_DIR"/$CURVE
convert "$SRC_DIR"/GENERATED/c/$CURVE/decaf_tables.c "$DEST_DIR"/$CURVE
convert "$SRC_DIR"/GENERATED/c/$CURVE/eddsa.c "$DEST_DIR"/$CURVE
convert "$SRC_DIR"/GENERATED/c/$CURVE/scalar.c "$DEST_DIR"/$CURVE
done
for FIELD in p448; do
mkdir -p "$DEST_DIR"/$FIELD
convert "$SRC_DIR"/$FIELD/f_arithmetic.c "$DEST_DIR"/$FIELD
convert "$SRC_DIR"/GENERATED/c/$FIELD/f_generic.c "$DEST_DIR"/$FIELD
convert "$SRC_DIR"/GENERATED/c/$FIELD/f_field.h "$DEST_DIR"/$FIELD
for ARCH in $ARCHITECTURES; do
mkdir -p "$DEST_DIR"/$FIELD/$ARCH
convert "$SRC_DIR"/$FIELD/$ARCH/f_impl.h "$DEST_DIR"/$FIELD/$ARCH
convert "$SRC_DIR"/$FIELD/$ARCH/f_impl.c "$DEST_DIR"/$FIELD/$ARCH
done
done
for FILE in point_255.h sha512.h; do
cat > "$DEST_DIR"/include/decaf/$FILE <<EOF
/* Not needed if 448-only */
EOF
done
cat >"$DEST_DIR"/include/portable_endian.h <<EOF
/* portable_endian.h not used */
#if defined(__MINGW32__)
// does not exist on MinGW, but unused anyway
extern int posix_memalign(void **, size_t, size_t);
#endif
EOF

43
cbits/decaf/utils.c Normal file
View File

@ -0,0 +1,43 @@
/* Copyright (c) 2015 Cryptography Research, Inc.
* Released under the MIT License. See LICENSE.txt for license information.
*/
/**
* @file utils.c
* @author Mike Hamburg
* @brief Decaf utility functions.
*/
#include <decaf/common.h>
void cryptonite_decaf_bzero (
void *s,
size_t size
) {
#ifdef __STDC_LIB_EXT1__
memset_s(s, size, 0, size);
#else
const size_t sw = sizeof(cryptonite_decaf_word_t);
volatile uint8_t *destroy = (volatile uint8_t *)s;
for (; size && ((uintptr_t)destroy)%sw; size--, destroy++)
*destroy = 0;
for (; size >= sw; size -= sw, destroy += sw)
*(volatile cryptonite_decaf_word_t *)destroy = 0;
for (; size; size--, destroy++)
*destroy = 0;
#endif
}
cryptonite_decaf_bool_t cryptonite_decaf_memeq (
const void *data1_,
const void *data2_,
size_t size
) {
const unsigned char *data1 = (const unsigned char *)data1_;
const unsigned char *data2 = (const unsigned char *)data2_;
unsigned char ret = 0;
for (; size; size--, data1++, data2++) {
ret |= *data1 ^ *data2;
}
return (((cryptonite_decaf_dword_t)ret) - 1) >> 8;
}

View File

@ -1,311 +0,0 @@
/* Copyright (c) 2015 Cryptography Research, Inc.
* Released under the MIT License. See LICENSE.txt for license information.
*/
/**
* @file decaf.c
* @author Mike Hamburg
* @brief Decaf high-level functions.
*/
#include <stdint.h>
#include "x448.h"
#ifdef ARCH_X86_64
#define WBITS 64
#else
#define WBITS 32
#endif
#define LBITS (WBITS * 7 / 8)
#define X448_LIMBS (448/LBITS)
#if WBITS == 64
typedef uint64_t decaf_word_t;
typedef int64_t decaf_sword_t;
typedef __uint128_t decaf_dword_t;
typedef __int128_t decaf_sdword_t;
#elif WBITS == 32
typedef uint32_t decaf_word_t;
typedef int32_t decaf_sword_t;
typedef uint64_t decaf_dword_t;
typedef int64_t decaf_sdword_t;
#else
#error "WBITS must be 32 or 64"
#endif
typedef struct { decaf_word_t limb[X448_LIMBS]; } gf_s, gf[1];
static const unsigned char X448_BASE_POINT[X448_BYTES] = {5};
static const gf ZERO = {{{0}}}, ONE = {{{1}}};
#define LMASK ((((decaf_word_t)1)<<LBITS)-1)
#if WBITS == 64
static const gf P = {{{ LMASK, LMASK, LMASK, LMASK, LMASK-1, LMASK, LMASK, LMASK }}};
#else
static const gf P = {{{ LMASK, LMASK, LMASK, LMASK, LMASK, LMASK, LMASK, LMASK,
LMASK-1, LMASK, LMASK, LMASK, LMASK, LMASK, LMASK, LMASK }}};
#endif
static const int EDWARDS_D = -39081;
#if (defined(__OPTIMIZE__) && !defined(__OPTIMIZE_SIZE__)) || defined(DECAF_FORCE_UNROLL)
#if X448_LIMBS==8
#define FOR_LIMB_U(i,op) { unsigned int i=0; \
op;i++; op;i++; op;i++; op;i++; op;i++; op;i++; op;i++; op;i++; \
}
#elif X448_LIMBS==16
#define FOR_LIMB_U(i,op) { unsigned int i=0; \
op;i++; op;i++; op;i++; op;i++; op;i++; op;i++; op;i++; op;i++; \
op;i++; op;i++; op;i++; op;i++; op;i++; op;i++; op;i++; op;i++; \
}
#else
#define FOR_LIMB_U(i,op) { unsigned int i=0; for (i=0; i<X448_LIMBS; i++) { op; }}
#endif
#else
#define FOR_LIMB_U(i,op) { unsigned int i=0; for (i=0; i<X448_LIMBS; i++) { op; }}
#endif
#define FOR_LIMB(i,op) { unsigned int i=0; for (i=0; i<X448_LIMBS; i++) { op; }}
/** Copy x = y */
static void gf_cpy(gf x, const gf y) {
FOR_LIMB_U(i, x->limb[i] = y->limb[i]);
}
/** Mostly-unoptimized multiply (PERF), but at least it's unrolled. */
static void
gf_mul (gf c, const gf a, const gf b) {
gf aa;
gf_cpy(aa,a);
decaf_dword_t accum[X448_LIMBS] = {0};
FOR_LIMB_U(i, {
FOR_LIMB_U(j,{ accum[(i+j)%X448_LIMBS] += (decaf_dword_t)b->limb[i] * aa->limb[j]; });
aa->limb[(X448_LIMBS-1-i)^(X448_LIMBS/2)] += aa->limb[X448_LIMBS-1-i];
});
accum[X448_LIMBS-1] += accum[X448_LIMBS-2] >> LBITS;
accum[X448_LIMBS-2] &= LMASK;
accum[X448_LIMBS/2] += accum[X448_LIMBS-1] >> LBITS;
FOR_LIMB_U(j,{
accum[j] += accum[(j-1)%X448_LIMBS] >> LBITS;
accum[(j-1)%X448_LIMBS] &= LMASK;
});
FOR_LIMB_U(j, c->limb[j] = accum[j] );
}
/** No dedicated square (PERF) */
#define gf_sqr(c,a) gf_mul(c,a,a)
/** Inverse square root using addition chain. */
static void
gf_isqrt(gf y, const gf x) {
int i;
#define STEP(s,m,n) gf_mul(s,m,c); gf_cpy(c,s); for (i=0;i<n;i++) gf_sqr(c,c);
gf a, b, c;
gf_sqr ( c, x );
STEP(b,x,1);
STEP(b,x,3);
STEP(a,b,3);
STEP(a,b,9);
STEP(b,a,1);
STEP(a,x,18);
STEP(a,b,37);
STEP(b,a,37);
STEP(b,a,111);
STEP(a,b,1);
STEP(b,x,223);
gf_mul(y,a,c);
}
static void
gf_inv(gf y, const gf x) {
gf z,w;
gf_sqr(z,x); /* x^2 */
gf_isqrt(w,z); /* +- 1/sqrt(x^2) = +- 1/x */
gf_sqr(z,w); /* 1/x^2 */
gf_mul(w,x,z); /* 1/x */
gf_cpy(y,w);
}
/** Weak reduce mod p. */
static void
gf_reduce(gf x) {
x->limb[X448_LIMBS/2] += x->limb[X448_LIMBS-1] >> LBITS;
FOR_LIMB_U(j,{
x->limb[j] += x->limb[(j-1)%X448_LIMBS] >> LBITS;
x->limb[(j-1)%X448_LIMBS] &= LMASK;
});
}
/** Add mod p. Conservatively always weak-reduce. (PERF) */
static void
gf_add ( gf x, const gf y, const gf z ) {
FOR_LIMB_U(i, x->limb[i] = y->limb[i] + z->limb[i] );
gf_reduce(x);
}
/** Subtract mod p. Conservatively always weak-reduce. (PERF) */
static void
gf_sub ( gf x, const gf y, const gf z ) {
FOR_LIMB_U(i, x->limb[i] = y->limb[i] - z->limb[i] + 2*P->limb[i] );
gf_reduce(x);
}
/** Constant time, if (swap) (x,y) = (y,x); */
static void
cond_swap(gf x, gf_s *__restrict__ y, decaf_word_t swap) {
FOR_LIMB_U(i, {
decaf_word_t s = (x->limb[i] ^ y->limb[i]) & swap;
x->limb[i] ^= s;
y->limb[i] ^= s;
});
}
/**
* Mul by signed int. Not constant-time WRT the sign of that int.
* Just uses a full mul (PERF)
*/
static inline void
gf_mlw(gf a, const gf b, int w) {
if (w>0) {
gf ww = {{{w}}};
gf_mul(a,b,ww);
} else {
gf ww = {{{-w}}};
gf_mul(a,b,ww);
gf_sub(a,ZERO,a);
}
}
/** Canonicalize */
static void gf_canon ( gf a ) {
gf_reduce(a);
/* subtract p with borrow */
decaf_sdword_t carry = 0;
FOR_LIMB(i, {
carry = carry + a->limb[i] - P->limb[i];
a->limb[i] = carry & LMASK;
carry >>= LBITS;
});
decaf_word_t addback = carry;
carry = 0;
/* add it back */
FOR_LIMB(i, {
carry = carry + a->limb[i] + (P->limb[i] & addback);
a->limb[i] = carry & LMASK;
carry >>= LBITS;
});
}
/* Deserialize */
static decaf_word_t
gf_deser(gf s, const unsigned char ser[X448_BYTES]) {
unsigned int i, k=0, bits=0;
decaf_dword_t buf=0;
for (i=0; i<X448_BYTES; i++) {
buf |= (decaf_dword_t)ser[i]<<bits;
for (bits += 8; (bits>=LBITS || i==X448_BYTES-1) && k<X448_LIMBS; bits-=LBITS, buf>>=LBITS) {
s->limb[k++] = buf & LMASK;
}
}
decaf_sdword_t accum = 0;
FOR_LIMB(i, accum = (accum + s->limb[i] - P->limb[i]) >> WBITS );
return accum;
}
/* Serialize */
static void
gf_ser(uint8_t ser[X448_BYTES], gf a) {
gf_canon(a);
int k=0, bits=0;
decaf_dword_t buf=0;
FOR_LIMB(i, {
buf |= (decaf_dword_t)a->limb[i]<<bits;
for (bits += LBITS; (bits>=8 || i==X448_LIMBS-1) && k<X448_BYTES; bits-=8, buf>>=8) {
ser[k++]=buf;
}
});
}
int __attribute__((visibility("default"))) cryptonite_x448 (
unsigned char out[X448_BYTES],
const unsigned char scalar[X448_BYTES],
const unsigned char base[X448_BYTES]
) {
gf x1, x2, z2, x3, z3, t1, t2;
gf_deser(x1,base);
gf_cpy(x2,ONE);
gf_cpy(z2,ZERO);
gf_cpy(x3,x1);
gf_cpy(z3,ONE);
int t;
decaf_word_t swap = 0;
for (t = 448-1; t>=0; t--) {
uint8_t sb = scalar[t/8];
/* Scalar conditioning */
if (t/8==0) sb &= 0xFC;
else if (t/8 == X448_BYTES-1) sb |= 0x80;
decaf_word_t k_t = (sb>>(t%8)) & 1;
k_t = -k_t; /* set to all 0s or all 1s */
swap ^= k_t;
cond_swap(x2,x3,swap);
cond_swap(z2,z3,swap);
swap = k_t;
gf_add(t1,x2,z2); /* A = x2 + z2 */
gf_sub(t2,x2,z2); /* B = x2 - z2 */
gf_sub(z2,x3,z3); /* D = x3 - z3 */
gf_mul(x2,t1,z2); /* DA */
gf_add(z2,z3,x3); /* C = x3 + z3 */
gf_mul(x3,t2,z2); /* CB */
gf_sub(z3,x2,x3); /* DA-CB */
gf_sqr(z2,z3); /* (DA-CB)^2 */
gf_mul(z3,x1,z2); /* z3 = x1(DA-CB)^2 */
gf_add(z2,x2,x3); /* (DA+CB) */
gf_sqr(x3,z2); /* x3 = (DA+CB)^2 */
gf_sqr(z2,t1); /* AA = A^2 */
gf_sqr(t1,t2); /* BB = B^2 */
gf_mul(x2,z2,t1); /* x2 = AA*BB */
gf_sub(t2,z2,t1); /* E = AA-BB */
gf_mlw(t1,t2,-EDWARDS_D); /* E*-d = a24*E */
gf_add(t1,t1,z2); /* AA + a24*E */
gf_mul(z2,t2,t1); /* z2 = E(AA+a24*E) */
}
/* Finish */
cond_swap(x2,x3,swap);
cond_swap(z2,z3,swap);
gf_inv(z2,z2);
gf_mul(x1,x2,z2);
gf_ser(out,x1);
decaf_sword_t nz = 0;
for (t=0; t<X448_BYTES; t++) {
nz |= out[t];
}
nz = (nz-1)>>8; /* 0 = succ, -1 = fail */
/* return value: 0 = succ, -1 = fail */
return nz;
}
int __attribute__((visibility("default")))
cryptonite_x448_base (
unsigned char out[X448_BYTES],
const unsigned char scalar[X448_BYTES]
) {
return cryptonite_x448(out,scalar,X448_BASE_POINT);
}

View File

@ -1,25 +0,0 @@
#define X448_BYTES (448/8)
/* The base point (5) */
//extern const unsigned char X448_BASE_POINT[X448_BYTES];
/* Returns 0 on success, -1 on failure */
int __attribute__((visibility("default")))
cryptonite_x448 (
unsigned char out[X448_BYTES],
const unsigned char scalar[X448_BYTES],
const unsigned char base[X448_BYTES]
);
/* Returns 0 on success, -1 on failure
*
* Same as x448(out,scalar,X448_BASE_POINT), except that
* an implementation may optimize it.
*/
int __attribute__((visibility("default")))
cryptonite_x448_base (
unsigned char out[X448_BYTES],
const unsigned char scalar[X448_BYTES]
);

View File

@ -10,7 +10,7 @@ Description:
.
* MAC: HMAC, Poly1305
.
* Asymmetric crypto: DSA, RSA, DH, ECDH, ECDSA, ECC, Curve25519, Curve448, Ed25519
* Asymmetric crypto: DSA, RSA, DH, ECDH, ECDSA, ECC, Curve25519, Curve448, Ed25519, Ed448
.
* Key Derivation Function: PBKDF2, Scrypt, HKDF, Argon2
.
@ -40,7 +40,13 @@ extra-doc-files: README.md CHANGELOG.md
extra-source-files: cbits/*.h
cbits/aes/*.h
cbits/ed25519/*.h
cbits/ed448/*.h
cbits/decaf/include/*.h
cbits/decaf/include/decaf/*.h
cbits/decaf/include/arch_32/*.h
cbits/decaf/include/arch_ref64/*.h
cbits/decaf/p448/arch_32/*.h
cbits/decaf/p448/arch_ref64/*.h
cbits/decaf/p448/*.h
cbits/p256/*.h
cbits/blake2/ref/*.h
cbits/blake2/sse/*.h
@ -234,7 +240,6 @@ Library
, cbits/cryptonite_rc4.c
, cbits/cryptonite_cpu.c
, cbits/ed25519/ed25519.c
, cbits/ed448/x448.c
, cbits/p256/p256.c
, cbits/p256/p256_ec.c
, cbits/cryptonite_blake2s.c
@ -256,7 +261,35 @@ Library
, cbits/cryptonite_whirlpool.c
, cbits/cryptonite_scrypt.c
, cbits/cryptonite_pbkdf2.c
include-dirs: cbits cbits/ed25519
include-dirs: cbits
, cbits/ed25519
, cbits/decaf/include
, cbits/decaf/p448
if arch(x86_64)
C-sources: cbits/decaf/p448/arch_ref64/f_impl.c
, cbits/decaf/p448/f_generic.c
, cbits/decaf/p448/f_arithmetic.c
, cbits/decaf/utils.c
, cbits/decaf/ed448goldilocks/scalar.c
, cbits/decaf/ed448goldilocks/decaf_tables.c
, cbits/decaf/ed448goldilocks/decaf.c
, cbits/decaf/ed448goldilocks/eddsa.c
include-dirs: cbits/decaf/include/arch_ref64
, cbits/decaf/p448/arch_ref64
else
C-sources: cbits/decaf/p448/arch_32/f_impl.c
, cbits/decaf/p448/f_generic.c
, cbits/decaf/p448/f_arithmetic.c
, cbits/decaf/utils.c
, cbits/decaf/ed448goldilocks/scalar.c
, cbits/decaf/ed448goldilocks/decaf_tables.c
, cbits/decaf/ed448goldilocks/decaf.c
, cbits/decaf/ed448goldilocks/eddsa.c
include-dirs: cbits/decaf/include/arch_32
, cbits/decaf/p448/arch_32
if arch(x86_64)
C-sources: cbits/curve25519/curve25519-donna-c64.c
@ -352,6 +385,7 @@ Test-Suite test-cryptonite
KAT_Curve448
KAT_DES
KAT_Ed25519
KAT_Ed448
KAT_CMAC
KAT_HKDF
KAT_HMAC

View File

@ -16,6 +16,8 @@ katTests :: [TestTree]
katTests =
[ testCase "0" (aliceMultBob @=? B.convert (Curve25519.dh alicePublic bobPrivate))
, testCase "1" (aliceMultBob @=? B.convert (Curve25519.dh bobPublic alicePrivate))
, testCase "2" (alicePublic @=? Curve25519.toPublic alicePrivate)
, testCase "3" (bobPublic @=? Curve25519.toPublic bobPrivate)
]
tests = testGroup "Curve25519"

View File

@ -13,27 +13,60 @@ data Vec = Vec
, vecSig :: ByteString
} deriving (Show,Eq)
vec1 = Vec
{ vecSec = "\x4c\xcd\x08\x9b\x28\xff\x96\xda\x9d\xb6\xc3\x46\xec\x11\x4e\x0f\x5b\x8a\x31\x9f\x35\xab\xa6\x24\xda\x8c\xf6\xed\x4f\xb8\xa6\xfb"
, vecPub = "\x3d\x40\x17\xc3\xe8\x43\x89\x5a\x92\xb7\x0a\xa7\x4d\x1b\x7e\xbc\x9c\x98\x2c\xcf\x2e\xc4\x96\x8c\xc0\xcd\x55\xf1\x2a\xf4\x66\x0c"
, vecMsg = "\x72"
, vecSig = "\x92\xa0\x09\xa9\xf0\xd4\xca\xb8\x72\x0e\x82\x0b\x5f\x64\x25\x40\xa2\xb2\x7b\x54\x16\x50\x3f\x8f\xb3\x76\x22\x23\xeb\xdb\x69\xda\x08\x5a\xc1\xe4\x3e\x15\x99\x6e\x45\x8f\x36\x13\xd0\xf1\x1d\x8c\x38\x7b\x2e\xae\xb4\x30\x2a\xee\xb0\x0d\x29\x16\x12\xbb\x0c\x00"
}
testVec :: String -> Vec -> [TestTree]
testVec s vec =
[ testCase (s ++ " gen publickey") (pub @=? Ed25519.toPublic sec)
, testCase (s ++ " gen secretkey") (Ed25519.generateSecretKey *> pure ())
, testCase (s ++ " gen signature") (sig @=? Ed25519.sign sec pub (vecMsg vec))
vectors =
[ Vec
{ vecSec = "\x9d\x61\xb1\x9d\xef\xfd\x5a\x60\xba\x84\x4a\xf4\x92\xec\x2c\xc4\x44\x49\xc5\x69\x7b\x32\x69\x19\x70\x3b\xac\x03\x1c\xae\x7f\x60"
, vecPub = "\xd7\x5a\x98\x01\x82\xb1\x0a\xb7\xd5\x4b\xfe\xd3\xc9\x64\x07\x3a\x0e\xe1\x72\xf3\xda\xa6\x23\x25\xaf\x02\x1a\x68\xf7\x07\x51\x1a"
, vecMsg = ""
, vecSig = "\xe5\x56\x43\x00\xc3\x60\xac\x72\x90\x86\xe2\xcc\x80\x6e\x82\x8a\x84\x87\x7f\x1e\xb8\xe5\xd9\x74\xd8\x73\xe0\x65\x22\x49\x01\x55\x5f\xb8\x82\x15\x90\xa3\x3b\xac\xc6\x1e\x39\x70\x1c\xf9\xb4\x6b\xd2\x5b\xf5\xf0\x59\x5b\xbe\x24\x65\x51\x41\x43\x8e\x7a\x10\x0b"
}
, Vec
{ vecSec = "\x4c\xcd\x08\x9b\x28\xff\x96\xda\x9d\xb6\xc3\x46\xec\x11\x4e\x0f\x5b\x8a\x31\x9f\x35\xab\xa6\x24\xda\x8c\xf6\xed\x4f\xb8\xa6\xfb"
, vecPub = "\x3d\x40\x17\xc3\xe8\x43\x89\x5a\x92\xb7\x0a\xa7\x4d\x1b\x7e\xbc\x9c\x98\x2c\xcf\x2e\xc4\x96\x8c\xc0\xcd\x55\xf1\x2a\xf4\x66\x0c"
, vecMsg = "\x72"
, vecSig = "\x92\xa0\x09\xa9\xf0\xd4\xca\xb8\x72\x0e\x82\x0b\x5f\x64\x25\x40\xa2\xb2\x7b\x54\x16\x50\x3f\x8f\xb3\x76\x22\x23\xeb\xdb\x69\xda\x08\x5a\xc1\xe4\x3e\x15\x99\x6e\x45\x8f\x36\x13\xd0\xf1\x1d\x8c\x38\x7b\x2e\xae\xb4\x30\x2a\xee\xb0\x0d\x29\x16\x12\xbb\x0c\x00"
}
, Vec
{ vecSec = "\xc5\xaa\x8d\xf4\x3f\x9f\x83\x7b\xed\xb7\x44\x2f\x31\xdc\xb7\xb1\x66\xd3\x85\x35\x07\x6f\x09\x4b\x85\xce\x3a\x2e\x0b\x44\x58\xf7"
, vecPub = "\xfc\x51\xcd\x8e\x62\x18\xa1\xa3\x8d\xa4\x7e\xd0\x02\x30\xf0\x58\x08\x16\xed\x13\xba\x33\x03\xac\x5d\xeb\x91\x15\x48\x90\x80\x25"
, vecMsg = "\xaf\x82"
, vecSig = "\x62\x91\xd6\x57\xde\xec\x24\x02\x48\x27\xe6\x9c\x3a\xbe\x01\xa3\x0c\xe5\x48\xa2\x84\x74\x3a\x44\x5e\x36\x80\xd7\xdb\x5a\xc3\xac\x18\xff\x9b\x53\x8d\x16\xf2\x90\xae\x67\xf7\x60\x98\x4d\xc6\x59\x4a\x7c\x15\xe9\x71\x6e\xd2\x8d\xc0\x27\xbe\xce\xea\x1e\xc4\x0a"
}
, Vec
{ vecSec = "\xf5\xe5\x76\x7c\xf1\x53\x31\x95\x17\x63\x0f\x22\x68\x76\xb8\x6c\x81\x60\xcc\x58\x3b\xc0\x13\x74\x4c\x6b\xf2\x55\xf5\xcc\x0e\xe5"
, vecPub = "\x27\x81\x17\xfc\x14\x4c\x72\x34\x0f\x67\xd0\xf2\x31\x6e\x83\x86\xce\xff\xbf\x2b\x24\x28\xc9\xc5\x1f\xef\x7c\x59\x7f\x1d\x42\x6e"
, vecMsg = "\x08\xb8\xb2\xb7\x33\x42\x42\x43\x76\x0f\xe4\x26\xa4\xb5\x49\x08\x63\x21\x10\xa6\x6c\x2f\x65\x91\xea\xbd\x33\x45\xe3\xe4\xeb\x98\xfa\x6e\x26\x4b\xf0\x9e\xfe\x12\xee\x50\xf8\xf5\x4e\x9f\x77\xb1\xe3\x55\xf6\xc5\x05\x44\xe2\x3f\xb1\x43\x3d\xdf\x73\xbe\x84\xd8\x79\xde\x7c\x00\x46\xdc\x49\x96\xd9\xe7\x73\xf4\xbc\x9e\xfe\x57\x38\x82\x9a\xdb\x26\xc8\x1b\x37\xc9\x3a\x1b\x27\x0b\x20\x32\x9d\x65\x86\x75\xfc\x6e\xa5\x34\xe0\x81\x0a\x44\x32\x82\x6b\xf5\x8c\x94\x1e\xfb\x65\xd5\x7a\x33\x8b\xbd\x2e\x26\x64\x0f\x89\xff\xbc\x1a\x85\x8e\xfc\xb8\x55\x0e\xe3\xa5\xe1\x99\x8b\xd1\x77\xe9\x3a\x73\x63\xc3\x44\xfe\x6b\x19\x9e\xe5\xd0\x2e\x82\xd5\x22\xc4\xfe\xba\x15\x45\x2f\x80\x28\x8a\x82\x1a\x57\x91\x16\xec\x6d\xad\x2b\x3b\x31\x0d\xa9\x03\x40\x1a\xa6\x21\x00\xab\x5d\x1a\x36\x55\x3e\x06\x20\x3b\x33\x89\x0c\xc9\xb8\x32\xf7\x9e\xf8\x05\x60\xcc\xb9\xa3\x9c\xe7\x67\x96\x7e\xd6\x28\xc6\xad\x57\x3c\xb1\x16\xdb\xef\xef\xd7\x54\x99\xda\x96\xbd\x68\xa8\xa9\x7b\x92\x8a\x8b\xbc\x10\x3b\x66\x21\xfc\xde\x2b\xec\xa1\x23\x1d\x20\x6b\xe6\xcd\x9e\xc7\xaf\xf6\xf6\xc9\x4f\xcd\x72\x04\xed\x34\x55\xc6\x8c\x83\xf4\xa4\x1d\xa4\xaf\x2b\x74\xef\x5c\x53\xf1\xd8\xac\x70\xbd\xcb\x7e\xd1\x85\xce\x81\xbd\x84\x35\x9d\x44\x25\x4d\x95\x62\x9e\x98\x55\xa9\x4a\x7c\x19\x58\xd1\xf8\xad\xa5\xd0\x53\x2e\xd8\xa5\xaa\x3f\xb2\xd1\x7b\xa7\x0e\xb6\x24\x8e\x59\x4e\x1a\x22\x97\xac\xbb\xb3\x9d\x50\x2f\x1a\x8c\x6e\xb6\xf1\xce\x22\xb3\xde\x1a\x1f\x40\xcc\x24\x55\x41\x19\xa8\x31\xa9\xaa\xd6\x07\x9c\xad\x88\x42\x5d\xe6\xbd\xe1\xa9\x18\x7e\xbb\x60\x92\xcf\x67\xbf\x2b\x13\xfd\x65\xf2\x70\x88\xd7\x8b\x7e\x88\x3c\x87\x59\xd2\xc4\xf5\xc6\x5a\xdb\x75\x53\x87\x8a\xd5\x75\xf9\xfa\xd8\x78\xe8\x0a\x0c\x9b\xa6\x3b\xcb\xcc\x27\x32\xe6\x94\x85\xbb\xc9\xc9\x0b\xfb\xd6\x24\x81\xd9\x08\x9b\xec\xcf\x80\xcf\xe2\xdf\x16\xa2\xcf\x65\xbd\x92\xdd\x59\x7b\x07\x07\xe0\x91\x7a\xf4\x8b\xbb\x75\xfe\xd4\x13\xd2\x38\xf5\x55\x5a\x7a\x56\x9d\x80\xc3\x41\x4a\x8d\x08\x59\xdc\x65\xa4\x61\x28\xba\xb2\x7a\xf8\x7a\x71\x31\x4f\x31\x8c\x78\x2b\x23\xeb\xfe\x80\x8b\x82\xb0\xce\x26\x40\x1d\x2e\x22\xf0\x4d\x83\xd1\x25\x5d\xc5\x1a\xdd\xd3\xb7\x5a\x2b\x1a\xe0\x78\x45\x04\xdf\x54\x3a\xf8\x96\x9b\xe3\xea\x70\x82\xff\x7f\xc9\x88\x8c\x14\x4d\xa2\xaf\x58\x42\x9e\xc9\x60\x31\xdb\xca\xd3\xda\xd9\xaf\x0d\xcb\xaa\xaf\x26\x8c\xb8\xfc\xff\xea\xd9\x4f\x3c\x7c\xa4\x95\xe0\x56\xa9\xb4\x7a\xcd\xb7\x51\xfb\x73\xe6\x66\xc6\xc6\x55\xad\xe8\x29\x72\x97\xd0\x7a\xd1\xba\x5e\x43\xf1\xbc\xa3\x23\x01\x65\x13\x39\xe2\x29\x04\xcc\x8c\x42\xf5\x8c\x30\xc0\x4a\xaf\xdb\x03\x8d\xda\x08\x47\xdd\x98\x8d\xcd\xa6\xf3\xbf\xd1\x5c\x4b\x4c\x45\x25\x00\x4a\xa0\x6e\xef\xf8\xca\x61\x78\x3a\xac\xec\x57\xfb\x3d\x1f\x92\xb0\xfe\x2f\xd1\xa8\x5f\x67\x24\x51\x7b\x65\xe6\x14\xad\x68\x08\xd6\xf6\xee\x34\xdf\xf7\x31\x0f\xdc\x82\xae\xbf\xd9\x04\xb0\x1e\x1d\xc5\x4b\x29\x27\x09\x4b\x2d\xb6\x8d\x6f\x90\x3b\x68\x40\x1a\xde\xbf\x5a\x7e\x08\xd7\x8f\xf4\xef\x5d\x63\x65\x3a\x65\x04\x0c\xf9\xbf\xd4\xac\xa7\x98\x4a\x74\xd3\x71\x45\x98\x67\x80\xfc\x0b\x16\xac\x45\x16\x49\xde\x61\x88\xa7\xdb\xdf\x19\x1f\x64\xb5\xfc\x5e\x2a\xb4\x7b\x57\xf7\xf7\x27\x6c\xd4\x19\xc1\x7a\x3c\xa8\xe1\xb9\x39\xae\x49\xe4\x88\xac\xba\x6b\x96\x56\x10\xb5\x48\x01\x09\xc8\xb1\x7b\x80\xe1\xb7\xb7\x50\xdf\xc7\x59\x8d\x5d\x50\x11\xfd\x2d\xcc\x56\x00\xa3\x2e\xf5\xb5\x2a\x1e\xcc\x82\x0e\x30\x8a\xa3\x42\x72\x1a\xac\x09\x43\xbf\x66\x86\xb6\x4b\x25\x79\x37\x65\x04\xcc\xc4\x93\xd9\x7e\x6a\xed\x3f\xb0\xf9\xcd\x71\xa4\x3d\xd4\x97\xf0\x1f\x17\xc0\xe2\xcb\x37\x97\xaa\x2a\x2f\x25\x66\x56\x16\x8e\x6c\x49\x6a\xfc\x5f\xb9\x32\x46\xf6\xb1\x11\x63\x98\xa3\x46\xf1\xa6\x41\xf3\xb0\x41\xe9\x89\xf7\x91\x4f\x90\xcc\x2c\x7f\xff\x35\x78\x76\xe5\x06\xb5\x0d\x33\x4b\xa7\x7c\x22\x5b\xc3\x07\xba\x53\x71\x52\xf3\xf1\x61\x0e\x4e\xaf\xe5\x95\xf6\xd9\xd9\x0d\x11\xfa\xa9\x33\xa1\x5e\xf1\x36\x95\x46\x86\x8a\x7f\x3a\x45\xa9\x67\x68\xd4\x0f\xd9\xd0\x34\x12\xc0\x91\xc6\x31\x5c\xf4\xfd\xe7\xcb\x68\x60\x69\x37\x38\x0d\xb2\xea\xaa\x70\x7b\x4c\x41\x85\xc3\x2e\xdd\xcd\xd3\x06\x70\x5e\x4d\xc1\xff\xc8\x72\xee\xee\x47\x5a\x64\xdf\xac\x86\xab\xa4\x1c\x06\x18\x98\x3f\x87\x41\xc5\xef\x68\xd3\xa1\x01\xe8\xa3\xb8\xca\xc6\x0c\x90\x5c\x15\xfc\x91\x08\x40\xb9\x4c\x00\xa0\xb9\xd0"
, vecSig = "\x0a\xab\x4c\x90\x05\x01\xb3\xe2\x4d\x7c\xdf\x46\x63\x32\x6a\x3a\x87\xdf\x5e\x48\x43\xb2\xcb\xdb\x67\xcb\xf6\xe4\x60\xfe\xc3\x50\xaa\x53\x71\xb1\x50\x8f\x9f\x45\x28\xec\xea\x23\xc4\x36\xd9\x4b\x5e\x8f\xcd\x4f\x68\x1e\x30\xa6\xac\x00\xa9\x70\x4a\x18\x8a\x03"
}
, Vec
{ vecSec = "\x83\x3f\xe6\x24\x09\x23\x7b\x9d\x62\xec\x77\x58\x75\x20\x91\x1e\x9a\x75\x9c\xec\x1d\x19\x75\x5b\x7d\xa9\x01\xb9\x6d\xca\x3d\x42"
, vecPub = "\xec\x17\x2b\x93\xad\x5e\x56\x3b\xf4\x93\x2c\x70\xe1\x24\x50\x34\xc3\x54\x67\xef\x2e\xfd\x4d\x64\xeb\xf8\x19\x68\x34\x67\xe2\xbf"
, vecMsg = "\xdd\xaf\x35\xa1\x93\x61\x7a\xba\xcc\x41\x73\x49\xae\x20\x41\x31\x12\xe6\xfa\x4e\x89\xa9\x7e\xa2\x0a\x9e\xee\xe6\x4b\x55\xd3\x9a\x21\x92\x99\x2a\x27\x4f\xc1\xa8\x36\xba\x3c\x23\xa3\xfe\xeb\xbd\x45\x4d\x44\x23\x64\x3c\xe8\x0e\x2a\x9a\xc9\x4f\xa5\x4c\xa4\x9f"
, vecSig = "\xdc\x2a\x44\x59\xe7\x36\x96\x33\xa5\x2b\x1b\xf2\x77\x83\x9a\x00\x20\x10\x09\xa3\xef\xbf\x3e\xcb\x69\xbe\xa2\x18\x6c\x26\xb5\x89\x09\x35\x1f\xc9\xac\x90\xb3\xec\xfd\xfb\xc7\xc6\x64\x31\xe0\x30\x3d\xca\x17\x9c\x13\x8a\xc1\x7a\xd9\xbe\xf1\x17\x73\x31\xa7\x04"
}
]
doPublicKeyTest (i, vec) = testCase (show i) (pub @=? Ed25519.toPublic sec)
where
!pub = throwCryptoError $ Ed25519.publicKey (vecPub vec)
!sec = throwCryptoError $ Ed25519.secretKey (vecSec vec)
doSignatureTest (i, vec) = testCase (show i) (sig @=? Ed25519.sign sec pub (vecMsg vec))
where
!sig = throwCryptoError $ Ed25519.signature (vecSig vec)
!pub = throwCryptoError $ Ed25519.publicKey (vecPub vec)
!sec = throwCryptoError $ Ed25519.secretKey (vecSec vec)
katTests :: [TestTree]
katTests = testVec "vec 1" vec1
doVerifyTest (i, vec) = testCase (show i) (True @=? Ed25519.verify pub (vecMsg vec) sig)
where
!sig = throwCryptoError $ Ed25519.signature (vecSig vec)
!pub = throwCryptoError $ Ed25519.publicKey (vecPub vec)
tests = testGroup "Ed25519"
[ testGroup "KATs" katTests
[ testCase "gen secretkey" (Ed25519.generateSecretKey *> pure ())
, testGroup "gen publickey" $ map doPublicKeyTest (zip [katZero..] vectors)
, testGroup "gen signature" $ map doSignatureTest (zip [katZero..] vectors)
, testGroup "verify sig" $ map doVerifyTest (zip [katZero..] vectors)
]

90
tests/KAT_Ed448.hs Normal file
View File

@ -0,0 +1,90 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE BangPatterns #-}
module KAT_Ed448 ( tests ) where
import Crypto.Error
import qualified Crypto.PubKey.Ed448 as Ed448
import Imports
data Vec = Vec
{ vecSec :: ByteString
, vecPub :: ByteString
, vecMsg :: ByteString
, vecSig :: ByteString
} deriving (Show,Eq)
vectors =
[ Vec
{ vecSec = "\x6c\x82\xa5\x62\xcb\x80\x8d\x10\xd6\x32\xbe\x89\xc8\x51\x3e\xbf\x6c\x92\x9f\x34\xdd\xfa\x8c\x9f\x63\xc9\x96\x0e\xf6\xe3\x48\xa3\x52\x8c\x8a\x3f\xcc\x2f\x04\x4e\x39\xa3\xfc\x5b\x94\x49\x2f\x8f\x03\x2e\x75\x49\xa2\x00\x98\xf9\x5b"
, vecPub = "\x5f\xd7\x44\x9b\x59\xb4\x61\xfd\x2c\xe7\x87\xec\x61\x6a\xd4\x6a\x1d\xa1\x34\x24\x85\xa7\x0e\x1f\x8a\x0e\xa7\x5d\x80\xe9\x67\x78\xed\xf1\x24\x76\x9b\x46\xc7\x06\x1b\xd6\x78\x3d\xf1\xe5\x0f\x6c\xd1\xfa\x1a\xbe\xaf\xe8\x25\x61\x80"
, vecMsg = ""
, vecSig = "\x53\x3a\x37\xf6\xbb\xe4\x57\x25\x1f\x02\x3c\x0d\x88\xf9\x76\xae\x2d\xfb\x50\x4a\x84\x3e\x34\xd2\x07\x4f\xd8\x23\xd4\x1a\x59\x1f\x2b\x23\x3f\x03\x4f\x62\x82\x81\xf2\xfd\x7a\x22\xdd\xd4\x7d\x78\x28\xc5\x9b\xd0\xa2\x1b\xfd\x39\x80\xff\x0d\x20\x28\xd4\xb1\x8a\x9d\xf6\x3e\x00\x6c\x5d\x1c\x2d\x34\x5b\x92\x5d\x8d\xc0\x0b\x41\x04\x85\x2d\xb9\x9a\xc5\xc7\xcd\xda\x85\x30\xa1\x13\xa0\xf4\xdb\xb6\x11\x49\xf0\x5a\x73\x63\x26\x8c\x71\xd9\x58\x08\xff\x2e\x65\x26\x00"
}
, Vec
{ vecSec = "\xc4\xea\xb0\x5d\x35\x70\x07\xc6\x32\xf3\xdb\xb4\x84\x89\x92\x4d\x55\x2b\x08\xfe\x0c\x35\x3a\x0d\x4a\x1f\x00\xac\xda\x2c\x46\x3a\xfb\xea\x67\xc5\xe8\xd2\x87\x7c\x5e\x3b\xc3\x97\xa6\x59\x94\x9e\xf8\x02\x1e\x95\x4e\x0a\x12\x27\x4e"
, vecPub = "\x43\xba\x28\xf4\x30\xcd\xff\x45\x6a\xe5\x31\x54\x5f\x7e\xcd\x0a\xc8\x34\xa5\x5d\x93\x58\xc0\x37\x2b\xfa\x0c\x6c\x67\x98\xc0\x86\x6a\xea\x01\xeb\x00\x74\x28\x02\xb8\x43\x8e\xa4\xcb\x82\x16\x9c\x23\x51\x60\x62\x7b\x4c\x3a\x94\x80"
, vecMsg = "\x03"
, vecSig = "\x26\xb8\xf9\x17\x27\xbd\x62\x89\x7a\xf1\x5e\x41\xeb\x43\xc3\x77\xef\xb9\xc6\x10\xd4\x8f\x23\x35\xcb\x0b\xd0\x08\x78\x10\xf4\x35\x25\x41\xb1\x43\xc4\xb9\x81\xb7\xe1\x8f\x62\xde\x8c\xcd\xf6\x33\xfc\x1b\xf0\x37\xab\x7c\xd7\x79\x80\x5e\x0d\xbc\xc0\xaa\xe1\xcb\xce\xe1\xaf\xb2\xe0\x27\xdf\x36\xbc\x04\xdc\xec\xbf\x15\x43\x36\xc1\x9f\x0a\xf7\xe0\xa6\x47\x29\x05\xe7\x99\xf1\x95\x3d\x2a\x0f\xf3\x34\x8a\xb2\x1a\xa4\xad\xaf\xd1\xd2\x34\x44\x1c\xf8\x07\xc0\x3a\x00"
}
, Vec
{ vecSec = "\xcd\x23\xd2\x4f\x71\x42\x74\xe7\x44\x34\x32\x37\xb9\x32\x90\xf5\x11\xf6\x42\x5f\x98\xe6\x44\x59\xff\x20\x3e\x89\x85\x08\x3f\xfd\xf6\x05\x00\x55\x3a\xbc\x0e\x05\xcd\x02\x18\x4b\xdb\x89\xc4\xcc\xd6\x7e\x18\x79\x51\x26\x7e\xb3\x28"
, vecPub = "\xdc\xea\x9e\x78\xf3\x5a\x1b\xf3\x49\x9a\x83\x1b\x10\xb8\x6c\x90\xaa\xc0\x1c\xd8\x4b\x67\xa0\x10\x9b\x55\xa3\x6e\x93\x28\xb1\xe3\x65\xfc\xe1\x61\xd7\x1c\xe7\x13\x1a\x54\x3e\xa4\xcb\x5f\x7e\x9f\x1d\x8b\x00\x69\x64\x47\x00\x14\x00"
, vecMsg = "\x0c\x3e\x54\x40\x74\xec\x63\xb0\x26\x5e\x0c"
, vecSig = "\x1f\x0a\x88\x88\xce\x25\xe8\xd4\x58\xa2\x11\x30\x87\x9b\x84\x0a\x90\x89\xd9\x99\xaa\xba\x03\x9e\xaf\x3e\x3a\xfa\x09\x0a\x09\xd3\x89\xdb\xa8\x2c\x4f\xf2\xae\x8a\xc5\xcd\xfb\x7c\x55\xe9\x4d\x5d\x96\x1a\x29\xfe\x01\x09\x94\x1e\x00\xb8\xdb\xde\xea\x6d\x3b\x05\x10\x68\xdf\x72\x54\xc0\xcd\xc1\x29\xcb\xe6\x2d\xb2\xdc\x95\x7d\xbb\x47\xb5\x1f\xd3\xf2\x13\xfb\x86\x98\xf0\x64\x77\x42\x50\xa5\x02\x89\x61\xc9\xbf\x8f\xfd\x97\x3f\xe5\xd5\xc2\x06\x49\x2b\x14\x0e\x00"
}
, Vec
{ vecSec = "\x25\x8c\xdd\x4a\xda\x32\xed\x9c\x9f\xf5\x4e\x63\x75\x6a\xe5\x82\xfb\x8f\xab\x2a\xc7\x21\xf2\xc8\xe6\x76\xa7\x27\x68\x51\x3d\x93\x9f\x63\xdd\xdb\x55\x60\x91\x33\xf2\x9a\xdf\x86\xec\x99\x29\xdc\xcb\x52\xc1\xc5\xfd\x2f\xf7\xe2\x1b"
, vecPub = "\x3b\xa1\x6d\xa0\xc6\xf2\xcc\x1f\x30\x18\x77\x40\x75\x6f\x5e\x79\x8d\x6b\xc5\xfc\x01\x5d\x7c\x63\xcc\x95\x10\xee\x3f\xd4\x4a\xdc\x24\xd8\xe9\x68\xb6\xe4\x6e\x6f\x94\xd1\x9b\x94\x53\x61\x72\x6b\xd7\x5e\x14\x9e\xf0\x98\x17\xf5\x80"
, vecMsg = "\x64\xa6\x5f\x3c\xde\xdc\xdd\x66\x81\x1e\x29\x15"
, vecSig = "\x7e\xee\xab\x7c\x4e\x50\xfb\x79\x9b\x41\x8e\xe5\xe3\x19\x7f\xf6\xbf\x15\xd4\x3a\x14\xc3\x43\x89\xb5\x9d\xd1\xa7\xb1\xb8\x5b\x4a\xe9\x04\x38\xac\xa6\x34\xbe\xa4\x5e\x3a\x26\x95\xf1\x27\x0f\x07\xfd\xcd\xf7\xc6\x2b\x8e\xfe\xaf\x00\xb4\x5c\x2c\x96\xba\x45\x7e\xb1\xa8\xbf\x07\x5a\x3d\xb2\x8e\x5c\x24\xf6\xb9\x23\xed\x4a\xd7\x47\xc3\xc9\xe0\x3c\x70\x79\xef\xb8\x7c\xb1\x10\xd3\xa9\x98\x61\xe7\x20\x03\xcb\xae\x6d\x6b\x8b\x82\x7e\x4e\x6c\x14\x30\x64\xff\x3c\x00"
}
, Vec
{ vecSec = "\x7e\xf4\xe8\x45\x44\x23\x67\x52\xfb\xb5\x6b\x8f\x31\xa2\x3a\x10\xe4\x28\x14\xf5\xf5\x5c\xa0\x37\xcd\xcc\x11\xc6\x4c\x9a\x3b\x29\x49\xc1\xbb\x60\x70\x03\x14\x61\x17\x32\xa6\xc2\xfe\xa9\x8e\xeb\xc0\x26\x6a\x11\xa9\x39\x70\x10\x0e"
, vecPub = "\xb3\xda\x07\x9b\x0a\xa4\x93\xa5\x77\x20\x29\xf0\x46\x7b\xae\xbe\xe5\xa8\x11\x2d\x9d\x3a\x22\x53\x23\x61\xda\x29\x4f\x7b\xb3\x81\x5c\x5d\xc5\x9e\x17\x6b\x4d\x9f\x38\x1c\xa0\x93\x8e\x13\xc6\xc0\x7b\x17\x4b\xe6\x5d\xfa\x57\x8e\x80"
, vecMsg = "\x64\xa6\x5f\x3c\xde\xdc\xdd\x66\x81\x1e\x29\x15\xe7"
, vecSig = "\x6a\x12\x06\x6f\x55\x33\x1b\x6c\x22\xac\xd5\xd5\xbf\xc5\xd7\x12\x28\xfb\xda\x80\xae\x8d\xec\x26\xbd\xd3\x06\x74\x3c\x50\x27\xcb\x48\x90\x81\x0c\x16\x2c\x02\x74\x68\x67\x5e\xcf\x64\x5a\x83\x17\x6c\x0d\x73\x23\xa2\xcc\xde\x2d\x80\xef\xe5\xa1\x26\x8e\x8a\xca\x1d\x6f\xbc\x19\x4d\x3f\x77\xc4\x49\x86\xeb\x4a\xb4\x17\x79\x19\xad\x8b\xec\x33\xeb\x47\xbb\xb5\xfc\x6e\x28\x19\x6f\xd1\xca\xf5\x6b\x4e\x7e\x0b\xa5\x51\x92\x34\xd0\x47\x15\x5a\xc7\x27\xa1\x05\x31\x00"
}
, Vec
{ vecSec = "\xd6\x5d\xf3\x41\xad\x13\xe0\x08\x56\x76\x88\xba\xed\xda\x8e\x9d\xcd\xc1\x7d\xc0\x24\x97\x4e\xa5\xb4\x22\x7b\x65\x30\xe3\x39\xbf\xf2\x1f\x99\xe6\x8c\xa6\x96\x8f\x3c\xca\x6d\xfe\x0f\xb9\xf4\xfa\xb4\xfa\x13\x5d\x55\x42\xea\x3f\x01"
, vecPub = "\xdf\x97\x05\xf5\x8e\xdb\xab\x80\x2c\x7f\x83\x63\xcf\xe5\x56\x0a\xb1\xc6\x13\x2c\x20\xa9\xf1\xdd\x16\x34\x83\xa2\x6f\x8a\xc5\x3a\x39\xd6\x80\x8b\xf4\xa1\xdf\xbd\x26\x1b\x09\x9b\xb0\x3b\x3f\xb5\x09\x06\xcb\x28\xbd\x8a\x08\x1f\x00"
, vecMsg = "\xbd\x0f\x6a\x37\x47\xcd\x56\x1b\xdd\xdf\x46\x40\xa3\x32\x46\x1a\x4a\x30\xa1\x2a\x43\x4c\xd0\xbf\x40\xd7\x66\xd9\xc6\xd4\x58\xe5\x51\x22\x04\xa3\x0c\x17\xd1\xf5\x0b\x50\x79\x63\x1f\x64\xeb\x31\x12\x18\x2d\xa3\x00\x58\x35\x46\x11\x13\x71\x8d\x1a\x5e\xf9\x44"
, vecSig = "\x55\x4b\xc2\x48\x08\x60\xb4\x9e\xab\x85\x32\xd2\xa5\x33\xb7\xd5\x78\xef\x47\x3e\xeb\x58\xc9\x8b\xb2\xd0\xe1\xce\x48\x8a\x98\xb1\x8d\xfd\xe9\xb9\xb9\x07\x75\xe6\x7f\x47\xd4\xa1\xc3\x48\x20\x58\xef\xc9\xf4\x0d\x2c\xa0\x33\xa0\x80\x1b\x63\xd4\x5b\x3b\x72\x2e\xf5\x52\xba\xd3\xb4\xcc\xb6\x67\xda\x35\x01\x92\xb6\x1c\x50\x8c\xf7\xb6\xb5\xad\xad\xc2\xc8\xd9\xa4\x46\xef\x00\x3f\xb0\x5c\xba\x5f\x30\xe8\x8e\x36\xec\x27\x03\xb3\x49\xca\x22\x9c\x26\x70\x83\x39\x00"
}
, Vec
{ vecSec = "\x2e\xc5\xfe\x3c\x17\x04\x5a\xbd\xb1\x36\xa5\xe6\xa9\x13\xe3\x2a\xb7\x5a\xe6\x8b\x53\xd2\xfc\x14\x9b\x77\xe5\x04\x13\x2d\x37\x56\x9b\x7e\x76\x6b\xa7\x4a\x19\xbd\x61\x62\x34\x3a\x21\xc8\x59\x0a\xa9\xce\xbc\xa9\x01\x4c\x63\x6d\xf5"
, vecPub = "\x79\x75\x6f\x01\x4d\xcf\xe2\x07\x9f\x5d\xd9\xe7\x18\xbe\x41\x71\xe2\xef\x24\x86\xa0\x8f\x25\x18\x6f\x6b\xff\x43\xa9\x93\x6b\x9b\xfe\x12\x40\x2b\x08\xae\x65\x79\x8a\x3d\x81\xe2\x2e\x9e\xc8\x0e\x76\x90\x86\x2e\xf3\xd4\xed\x3a\x00"
, vecMsg = "\x15\x77\x75\x32\xb0\xbd\xd0\xd1\x38\x9f\x63\x6c\x5f\x6b\x9b\xa7\x34\xc9\x0a\xf5\x72\x87\x7e\x2d\x27\x2d\xd0\x78\xaa\x1e\x56\x7c\xfa\x80\xe1\x29\x28\xbb\x54\x23\x30\xe8\x40\x9f\x31\x74\x50\x41\x07\xec\xd5\xef\xac\x61\xae\x75\x04\xda\xbe\x2a\x60\x2e\xde\x89\xe5\xcc\xa6\x25\x7a\x7c\x77\xe2\x7a\x70\x2b\x3a\xe3\x9f\xc7\x69\xfc\x54\xf2\x39\x5a\xe6\xa1\x17\x8c\xab\x47\x38\xe5\x43\x07\x2f\xc1\xc1\x77\xfe\x71\xe9\x2e\x25\xbf\x03\xe4\xec\xb7\x2f\x47\xb6\x4d\x04\x65\xaa\xea\x4c\x7f\xad\x37\x25\x36\xc8\xba\x51\x6a\x60\x39\xc3\xc2\xa3\x9f\x0e\x4d\x83\x2b\xe4\x32\xdf\xa9\xa7\x06\xa6\xe5\xc7\xe1\x9f\x39\x79\x64\xca\x42\x58\x00\x2f\x7c\x05\x41\xb5\x90\x31\x6d\xbc\x56\x22\xb6\xb2\xa6\xfe\x7a\x4a\xbf\xfd\x96\x10\x5e\xca\x76\xea\x7b\x98\x81\x6a\xf0\x74\x8c\x10\xdf\x04\x8c\xe0\x12\xd9\x01\x01\x5a\x51\xf1\x89\xf3\x88\x81\x45\xc0\x36\x50\xaa\x23\xce\x89\x4c\x3b\xd8\x89\xe0\x30\xd5\x65\x07\x1c\x59\xf4\x09\xa9\x98\x1b\x51\x87\x8f\xd6\xfc\x11\x06\x24\xdc\xbc\xde\x0b\xf7\xa6\x9c\xcc\xe3\x8f\xab\xdf\x86\xf3\xbe\xf6\x04\x48\x19\xde\x11"
, vecSig = "\xc6\x50\xdd\xbb\x06\x01\xc1\x9c\xa1\x14\x39\xe1\x64\x0d\xd9\x31\xf4\x3c\x51\x8e\xa5\xbe\xa7\x0d\x3d\xcd\xe5\xf4\x19\x1f\xe5\x3f\x00\xcf\x96\x65\x46\xb7\x2b\xcc\x7d\x58\xbe\x2b\x9b\xad\xef\x28\x74\x39\x54\xe3\xa4\x4a\x23\xf8\x80\xe8\xd4\xf1\xcf\xce\x2d\x7a\x61\x45\x2d\x26\xda\x05\x89\x6f\x0a\x50\xda\x66\xa2\x39\xa8\xa1\x88\xb6\xd8\x25\xb3\x30\x5a\xd7\x7b\x73\xfb\xac\x08\x36\xec\xc6\x09\x87\xfd\x08\x52\x7c\x1a\x8e\x80\xd5\x82\x3e\x65\xca\xfe\x2a\x3d\x00"
}
, Vec
{ vecSec = "\x87\x2d\x09\x37\x80\xf5\xd3\x73\x0d\xf7\xc2\x12\x66\x4b\x37\xb8\xa0\xf2\x4f\x56\x81\x0d\xaa\x83\x82\xcd\x4f\xa3\xf7\x76\x34\xec\x44\xdc\x54\xf1\xc2\xed\x9b\xea\x86\xfa\xfb\x76\x32\xd8\xbe\x19\x9e\xa1\x65\xf5\xad\x55\xdd\x9c\xe8"
, vecPub = "\xa8\x1b\x2e\x8a\x70\xa5\xac\x94\xff\xdb\xcc\x9b\xad\xfc\x3f\xeb\x08\x01\xf2\x58\x57\x8b\xb1\x14\xad\x44\xec\xe1\xec\x0e\x79\x9d\xa0\x8e\xff\xb8\x1c\x5d\x68\x5c\x0c\x56\xf6\x4e\xec\xae\xf8\xcd\xf1\x1c\xc3\x87\x37\x83\x8c\xf4\x00"
, vecMsg = "\x6d\xdf\x80\x2e\x1a\xae\x49\x86\x93\x5f\x7f\x98\x1b\xa3\xf0\x35\x1d\x62\x73\xc0\xa0\xc2\x2c\x9c\x0e\x83\x39\x16\x8e\x67\x54\x12\xa3\xde\xbf\xaf\x43\x5e\xd6\x51\x55\x80\x07\xdb\x43\x84\xb6\x50\xfc\xc0\x7e\x3b\x58\x6a\x27\xa4\xf7\xa0\x0a\xc8\xa6\xfe\xc2\xcd\x86\xae\x4b\xf1\x57\x0c\x41\xe6\xa4\x0c\x93\x1d\xb2\x7b\x2f\xaa\x15\xa8\xce\xdd\x52\xcf\xf7\x36\x2c\x4e\x6e\x23\xda\xec\x0f\xbc\x3a\x79\xb6\x80\x6e\x31\x6e\xfc\xc7\xb6\x81\x19\xbf\x46\xbc\x76\xa2\x60\x67\xa5\x3f\x29\x6d\xaf\xdb\xdc\x11\xc7\x7f\x77\x77\xe9\x72\x66\x0c\xf4\xb6\xa9\xb3\x69\xa6\x66\x5f\x02\xe0\xcc\x9b\x6e\xdf\xad\x13\x6b\x4f\xab\xe7\x23\xd2\x81\x3d\xb3\x13\x6c\xfd\xe9\xb6\xd0\x44\x32\x2f\xee\x29\x47\x95\x2e\x03\x1b\x73\xab\x5c\x60\x33\x49\xb3\x07\xbd\xc2\x7b\xc6\xcb\x8b\x8b\xbd\x7b\xd3\x23\x21\x9b\x80\x33\xa5\x81\xb5\x9e\xad\xeb\xb0\x9b\x3c\x4f\x3d\x22\x77\xd4\xf0\x34\x36\x24\xac\xc8\x17\x80\x47\x28\xb2\x5a\xb7\x97\x17\x2b\x4c\x5c\x21\xa2\x2f\x9c\x78\x39\xd6\x43\x00\x23\x2e\xb6\x6e\x53\xf3\x1c\x72\x3f\xa3\x7f\xe3\x87\xc7\xd3\xe5\x0b\xdf\x98\x13\xa3\x0e\x5b\xb1\x2c\xf4\xcd\x93\x0c\x40\xcf\xb4\xe1\xfc\x62\x25\x92\xa4\x95\x88\x79\x44\x94\xd5\x6d\x24\xea\x4b\x40\xc8\x9f\xc0\x59\x6c\xc9\xeb\xb9\x61\xc8\xcb\x10\xad\xde\x97\x6a\x5d\x60\x2b\x1c\x3f\x85\xb9\xb9\xa0\x01\xed\x3c\x6a\x4d\x3b\x14\x37\xf5\x20\x96\xcd\x19\x56\xd0\x42\xa5\x97\xd5\x61\xa5\x96\xec\xd3\xd1\x73\x5a\x8d\x57\x0e\xa0\xec\x27\x22\x5a\x2c\x4a\xaf\xf2\x63\x06\xd1\x52\x6c\x1a\xf3\xca\x6d\x9c\xf5\xa2\xc9\x8f\x47\xe1\xc4\x6d\xb9\xa3\x32\x34\xcf\xd4\xd8\x1f\x2c\x98\x53\x8a\x09\xeb\xe7\x69\x98\xd0\xd8\xfd\x25\x99\x7c\x7d\x25\x5c\x6d\x66\xec\xe6\xfa\x56\xf1\x11\x44\x95\x0f\x02\x77\x95\xe6\x53\x00\x8f\x4b\xd7\xca\x2d\xee\x85\xd8\xe9\x0f\x3d\xc3\x15\x13\x0c\xe2\xa0\x03\x75\xa3\x18\xc7\xc3\xd9\x7b\xe2\xc8\xce\x5b\x6d\xb4\x1a\x62\x54\xff\x26\x4f\xa6\x15\x5b\xae\xe3\xb0\x77\x3c\x0f\x49\x7c\x57\x3f\x19\xbb\x4f\x42\x40\x28\x1f\x0b\x1f\x4f\x7b\xe8\x57\xa4\xe5\x9d\x41\x6c\x06\xb4\xc5\x0f\xa0\x9e\x18\x10\xdd\xc6\xb1\x46\x7b\xae\xac\x5a\x36\x68\xd1\x1b\x6e\xca\xa9\x01\x44\x00\x16\xf3\x89\xf8\x0a\xcc\x4d\xb9\x77\x02\x5e\x7f\x59\x24\x38\x8c\x7e\x34\x0a\x73\x2e\x55\x44\x40\xe7\x65\x70\xf8\xdd\x71\xb7\xd6\x40\xb3\x45\x0d\x1f\xd5\xf0\x41\x0a\x18\xf9\xa3\x49\x4f\x70\x7c\x71\x7b\x79\xb4\xbf\x75\xc9\x84\x00\xb0\x96\xb2\x16\x53\xb5\xd2\x17\xcf\x35\x65\xc9\x59\x74\x56\xf7\x07\x03\x49\x7a\x07\x87\x63\x82\x9b\xc0\x1b\xb1\xcb\xc8\xfa\x04\xea\xdc\x9a\x6e\x3f\x66\x99\x58\x7a\x9e\x75\xc9\x4e\x5b\xab\x00\x36\xe0\xb2\xe7\x11\x39\x2c\xff\x00\x47\xd0\xd6\xb0\x5b\xd2\xa5\x88\xbc\x10\x97\x18\x95\x42\x59\xf1\xd8\x66\x78\xa5\x79\xa3\x12\x0f\x19\xcf\xb2\x96\x3f\x17\x7a\xeb\x70\xf2\xd4\x84\x48\x26\x26\x2e\x51\xb8\x02\x71\x27\x20\x68\xef\x5b\x38\x56\xfa\x85\x35\xaa\x2a\x88\xb2\xd4\x1f\x2a\x0e\x2f\xda\x76\x24\xc2\x85\x02\x72\xac\x4a\x2f\x56\x1f\x8f\x2f\x7a\x31\x8b\xfd\x5c\xaf\x96\x96\x14\x9e\x4a\xc8\x24\xad\x34\x60\x53\x8f\xdc\x25\x42\x1b\xee\xc2\xcc\x68\x18\x16\x2d\x06\xbb\xed\x0c\x40\xa3\x87\x19\x23\x49\xdb\x67\xa1\x18\xba\xda\x6c\xd5\xab\x01\x40\xee\x27\x32\x04\xf6\x28\xaa\xd1\xc1\x35\xf7\x70\x27\x9a\x65\x1e\x24\xd8\xc1\x4d\x75\xa6\x05\x9d\x76\xb9\x6a\x6f\xd8\x57\xde\xf5\xe0\xb3\x54\xb2\x7a\xb9\x37\xa5\x81\x5d\x16\xb5\xfa\xe4\x07\xff\x18\x22\x2c\x6d\x1e\xd2\x63\xbe\x68\xc9\x5f\x32\xd9\x08\xbd\x89\x5c\xd7\x62\x07\xae\x72\x64\x87\x56\x7f\x9a\x67\xda\xd7\x9a\xbe\xc3\x16\xf6\x83\xb1\x7f\x2d\x02\xbf\x07\xe0\xac\x8b\x5b\xc6\x16\x2c\xf9\x46\x97\xb3\xc2\x7c\xd1\xfe\xa4\x9b\x27\xf2\x3b\xa2\x90\x18\x71\x96\x25\x06\x52\x0c\x39\x2d\xa8\xb6\xad\x0d\x99\xf7\x01\x3f\xbc\x06\xc2\xc1\x7a\x56\x95\x00\xc8\xa7\x69\x64\x81\xc1\xcd\x33\xe9\xb1\x4e\x40\xb8\x2e\x79\xa5\xf5\xdb\x82\x57\x1b\xa9\x7b\xae\x3a\xd3\xe0\x47\x95\x15\xbb\x0e\x2b\x0f\x3b\xfc\xd1\xfd\x33\x03\x4e\xfc\x62\x45\xed\xdd\x7e\xe2\x08\x6d\xda\xe2\x60\x0d\x8c\xa7\x3e\x21\x4e\x8c\x2b\x0b\xdb\x2b\x04\x7c\x6a\x46\x4a\x56\x2e\xd7\x7b\x73\xd2\xd8\x41\xc4\xb3\x49\x73\x55\x12\x57\x71\x3b\x75\x36\x32\xef\xba\x34\x81\x69\xab\xc9\x0a\x68\xf4\x26\x11\xa4\x01\x26\xd7\xcb\x21\xb5\x86\x95\x56\x81\x86\xf7\xe5\x69\xd2\xff\x0f\x9e\x74\x5d\x04\x87\xdd\x2e\xb9\x97\xca\xfc\x5a\xbf\x9d\xd1\x02\xe6\x2f\xf6\x6c\xba\x87"
, vecSig = "\xe3\x01\x34\x5a\x41\xa3\x9a\x4d\x72\xff\xf8\xdf\x69\xc9\x80\x75\xa0\xcc\x08\x2b\x80\x2f\xc9\xb2\xb6\xbc\x50\x3f\x92\x6b\x65\xbd\xdf\x7f\x4c\x8f\x1c\xb4\x9f\x63\x96\xaf\xc8\xa7\x0a\xbe\x6d\x8a\xef\x0d\xb4\x78\xd4\xc6\xb2\x97\x00\x76\xc6\xa0\x48\x4f\xe7\x6d\x76\xb3\xa9\x76\x25\xd7\x9f\x1c\xe2\x40\xe7\xc5\x76\x75\x0d\x29\x55\x28\x28\x6f\x71\x9b\x41\x3d\xe9\xad\xa3\xe8\xeb\x78\xed\x57\x36\x03\xce\x30\xd8\xbb\x76\x17\x85\xdc\x30\xdb\xc3\x20\x86\x9e\x1a\x00"
}
]
doPublicKeyTest (i, vec) = testCase (show i) (pub @=? Ed448.toPublic sec)
where
!pub = throwCryptoError $ Ed448.publicKey (vecPub vec)
!sec = throwCryptoError $ Ed448.secretKey (vecSec vec)
doSignatureTest (i, vec) = testCase (show i) (sig @=? Ed448.sign sec pub (vecMsg vec))
where
!sig = throwCryptoError $ Ed448.signature (vecSig vec)
!pub = throwCryptoError $ Ed448.publicKey (vecPub vec)
!sec = throwCryptoError $ Ed448.secretKey (vecSec vec)
doVerifyTest (i, vec) = testCase (show i) (True @=? Ed448.verify pub (vecMsg vec) sig)
where
!sig = throwCryptoError $ Ed448.signature (vecSig vec)
!pub = throwCryptoError $ Ed448.publicKey (vecPub vec)
tests = testGroup "Ed448"
[ testCase "gen secretkey" (Ed448.generateSecretKey *> pure ())
, testGroup "gen publickey" $ map doPublicKeyTest (zip [katZero..] vectors)
, testGroup "gen signature" $ map doSignatureTest (zip [katZero..] vectors)
, testGroup "verify sig" $ map doVerifyTest (zip [katZero..] vectors)
]

View File

@ -22,6 +22,7 @@ import qualified KAT_PBKDF2
import qualified KAT_Curve25519
import qualified KAT_Curve448
import qualified KAT_Ed25519
import qualified KAT_Ed448
import qualified KAT_OTP
import qualified KAT_PubKey
import qualified KAT_Scrypt
@ -53,6 +54,7 @@ tests = testGroup "cryptonite"
, KAT_Curve25519.tests
, KAT_Curve448.tests
, KAT_Ed25519.tests
, KAT_Ed448.tests
, KAT_PubKey.tests
, KAT_OTP.tests
, testGroup "KDF"