diff --git a/3way.cpp b/3way.cpp index 60bd0e13..bd610536 100644 --- a/3way.cpp +++ b/3way.cpp @@ -36,14 +36,14 @@ static inline word32 reverseBits(word32 a) a2 = t; \ } -#define pi_gamma_pi(a0, a1, a2) \ -{ \ - word32 b0, b2; \ - b2 = rotlFixed(a2, 1U); \ - b0 = rotlFixed(a0, 22U); \ - a0 = rotlFixed(b0 ^ (a1|(~b2)), 1U); \ - a2 = rotlFixed(b2 ^ (b0|(~a1)), 22U);\ - a1 ^= (b2|(~b0)); \ +#define pi_gamma_pi(a0, a1, a2) \ +{ \ + word32 b0, b2; \ + b2 = rotlConstant<1>(a2); \ + b0 = rotlConstant<22>(a0); \ + a0 = rotlConstant<1>(b0 ^ (a1|(~b2))); \ + a2 = rotlConstant<22>(b2 ^ (b0|(~a1))); \ + a1 ^= (b2|(~b0)); \ } // thanks to Paulo Barreto for this optimized theta() @@ -51,7 +51,7 @@ static inline word32 reverseBits(word32 a) { \ word32 b0, b1, c; \ c = a0 ^ a1 ^ a2; \ - c = rotlFixed(c, 16U) ^ rotlFixed(c, 8U); \ + c = rotlConstant<16>(c) ^ rotlConstant<8>(c); \ b0 = (a0 << 24) ^ (a2 >> 8) ^ (a1 << 8) ^ (a0 >> 24); \ b1 = (a1 << 24) ^ (a0 >> 8) ^ (a2 << 8) ^ (a1 >> 24); \ a0 ^= c ^ b0; \ diff --git a/aria.cpp b/aria.cpp index b2985656..a08f7850 100644 --- a/aria.cpp +++ b/aria.cpp @@ -65,7 +65,7 @@ inline byte ARIA_BRF(const word32 x, const int y) { #define ARIA_P(T0,T1,T2,T3) { \ (T1) = (((T1)<< 8)&0xff00ff00) ^ (((T1)>> 8)&0x00ff00ff); \ - (T2) = rotrFixed((T2),16); \ + (T2) = rotrConstant<16>(T2); \ (T3) = ByteReverse((T3)); \ } diff --git a/camellia.cpp b/camellia.cpp index be666fd1..07bd38da 100644 --- a/camellia.cpp +++ b/camellia.cpp @@ -29,20 +29,20 @@ NAMESPACE_BEGIN(CryptoPP) #define SLOW_ROUND(lh, ll, rh, rl, kh, kl) { \ word32 zr = ll ^ kl; \ word32 zl = lh ^ kh; \ - zr= rotlFixed(s1[GETBYTE(zr, 3)], 1) | \ - (rotrFixed(s1[GETBYTE(zr, 2)], 1) << 24) | \ - (s1[rotlFixed(CRYPTOPP_GET_BYTE_AS_BYTE(zr, 1),1)] << 16) | \ + zr= rotlConstant<1>(s1[GETBYTE(zr, 3)]) | \ + (rotrConstant<1>(s1[GETBYTE(zr, 2)]) << 24) | \ + (s1[rotlConstant<1>(CRYPTOPP_GET_BYTE_AS_BYTE(zr, 1))] << 16) | \ (s1[GETBYTE(zr, 0)] << 8); \ zl= (s1[GETBYTE(zl, 3)] << 24) | \ - (rotlFixed(s1[GETBYTE(zl, 2)], 1) << 16) | \ - (rotrFixed(s1[GETBYTE(zl, 1)], 1) << 8) | \ - s1[rotlFixed(CRYPTOPP_GET_BYTE_AS_BYTE(zl, 0), 1)]; \ + (rotlConstant<1>(s1[GETBYTE(zl, 2)]) << 16) | \ + (rotrConstant<1>(s1[GETBYTE(zl, 1)]) << 8) | \ + s1[rotlConstant<1>(CRYPTOPP_GET_BYTE_AS_BYTE(zl, 0))]; \ zl ^= zr; \ - zr = zl ^ rotlFixed(zr, 8); \ - zl = zr ^ rotrFixed(zl, 8); \ - rh ^= rotlFixed(zr, 16); \ + zr = zl ^ rotlConstant<8>(zr); \ + zl = zr ^ rotrConstant<8>(zl); \ + rh ^= rotlConstant<16>(zr); \ rh ^= zl; \ - rl ^= rotlFixed(zl, 8); \ + rl ^= rotlConstant<8>(zl); \ } // normal round - same output as above but using larger tables for faster speed @@ -54,7 +54,7 @@ NAMESPACE_BEGIN(CryptoPP) d ^= u; \ rh ^= d; \ rl ^= d; \ - rl ^= rotrFixed(u, 8);} + rl ^= rotrConstant<8>(u);} #define DOUBLE_ROUND(lh, ll, rh, rl, k0, k1, k2, k3) \ ROUND(lh, ll, rh, rl, k0, k1) \ @@ -202,10 +202,10 @@ void Camellia::Base::ProcessAndXorBlock(const byte *inBlock, const byte *xorBloc #define KS(i, j) ks[i*4 + EFI(j/2)*2 + EFI(j%2)] #define FL(klh, kll, krh, krl) \ - ll ^= rotlFixed(lh & klh, 1); \ + ll ^= rotlConstant<1>(lh & klh);\ lh ^= (ll | kll); \ rh ^= (rl | krl); \ - rl ^= rotlFixed(rh & krh, 1); + rl ^= rotlConstant<1>(rh & krh); word32 lh, ll, rh, rl; typedef BlockGetAndPut Block; diff --git a/chacha.cpp b/chacha.cpp index 4aeed40b..a63998be 100644 --- a/chacha.cpp +++ b/chacha.cpp @@ -12,10 +12,10 @@ NAMESPACE_BEGIN(CryptoPP) #define CHACHA_QUARTER_ROUND(a,b,c,d) \ - a += b; d ^= a; d = rotlFixed(d,16); \ - c += d; b ^= c; b = rotlFixed(b,12); \ - a += b; d ^= a; d = rotlFixed(d, 8); \ - c += d; b ^= c; b = rotlFixed(b, 7); + a += b; d ^= a; d = rotlConstant<16,word32>(d); \ + c += d; b ^= c; b = rotlConstant<12,word32>(b); \ + a += b; d ^= a; d = rotlConstant<8,word32>(d); \ + c += d; b ^= c; b = rotlConstant<7,word32>(b); #if defined(CRYPTOPP_DEBUG) && !defined(CRYPTOPP_DOXYGEN_PROCESSING) void ChaCha_TestInstantiations() diff --git a/des.cpp b/des.cpp index 7807e752..144897eb 100644 --- a/des.cpp +++ b/des.cpp @@ -77,21 +77,21 @@ static inline void IPERM(word32 &left, word32 &right) { word32 work; - right = rotlFixed(right, 4U); + right = rotlConstant<4>(right); work = (left ^ right) & 0xf0f0f0f0; left ^= work; - right = rotrFixed(right^work, 20U); + right = rotrConstant<20>(right^work); work = (left ^ right) & 0xffff0000; left ^= work; - right = rotrFixed(right^work, 18U); + right = rotrConstant<18>(right^work); work = (left ^ right) & 0x33333333; left ^= work; - right = rotrFixed(right^work, 6U); + right = rotrConstant<6>(right^work); work = (left ^ right) & 0x00ff00ff; left ^= work; - right = rotlFixed(right^work, 9U); + right = rotlConstant<9>(right^work); work = (left ^ right) & 0xaaaaaaaa; - left = rotlFixed(left^work, 1U); + left = rotlConstant<1>(left^work); right ^= work; } @@ -99,22 +99,22 @@ static inline void FPERM(word32 &left, word32 &right) { word32 work; - right = rotrFixed(right, 1U); + right = rotrConstant<1>(right); work = (left ^ right) & 0xaaaaaaaa; right ^= work; - left = rotrFixed(left^work, 9U); + left = rotrConstant<9>(left^work); work = (left ^ right) & 0x00ff00ff; right ^= work; - left = rotlFixed(left^work, 6U); + left = rotlConstant<6>(left^work); work = (left ^ right) & 0x33333333; right ^= work; - left = rotlFixed(left^work, 18U); + left = rotlConstant<18>(left^work); work = (left ^ right) & 0xffff0000; right ^= work; - left = rotlFixed(left^work, 20U); + left = rotlConstant<20>(left^work); work = (left ^ right) & 0xf0f0f0f0; right ^= work; - left = rotrFixed(left^work, 4U); + left = rotrConstant<4>(left^work); } void DES::Base::UncheckedSetKey(const byte *userKey, unsigned int length, const NameValuePairs &) @@ -340,7 +340,7 @@ void RawDES::RawProcessBlock(word32 &l_, word32 &r_) const for (unsigned i=0; i<8; i++) { - word32 work = rotrFixed(r, 4U) ^ kptr[4*i+0]; + word32 work = rotrConstant<4>(r) ^ kptr[4 * i + 0]; l ^= Spbox[6][(work) & 0x3f] ^ Spbox[4][(work >> 8) & 0x3f] ^ Spbox[2][(work >> 16) & 0x3f] @@ -351,7 +351,7 @@ void RawDES::RawProcessBlock(word32 &l_, word32 &r_) const ^ Spbox[3][(work >> 16) & 0x3f] ^ Spbox[1][(work >> 24) & 0x3f]; - work = rotrFixed(l, 4U) ^ kptr[4*i+2]; + work = rotrConstant<4>(l) ^ kptr[4 * i + 2]; r ^= Spbox[6][(work) & 0x3f] ^ Spbox[4][(work >> 8) & 0x3f] ^ Spbox[2][(work >> 16) & 0x3f] diff --git a/gf2_32.cpp b/gf2_32.cpp index ab4169ca..51d10a49 100644 --- a/gf2_32.cpp +++ b/gf2_32.cpp @@ -23,12 +23,12 @@ GF2_32::Element GF2_32::Multiply(Element a, Element b) const } #if CRYPTOPP_FAST_ROTATE(32) - b = rotrFixed(b, 30U); + b = rotrConstant<30>(b); word32 result = table[b&2]; for (int i=29; i>=0; --i) { - b = rotlFixed(b, 1U); + b = rotlConstant<1>(b); result = (result<<1) ^ table[(b&2) + (result>>31)]; } diff --git a/keccak.cpp b/keccak.cpp index b9abd396..cc1771cf 100644 --- a/keccak.cpp +++ b/keccak.cpp @@ -61,22 +61,22 @@ static void KeccakF1600(word64 *state) BCu = Abu^Agu^Aku^Amu^Asu; //thetaRhoPiChiIotaPrepareTheta(round , A, E) - Da = BCu^rotlFixed(BCe, 1); - De = BCa^rotlFixed(BCi, 1); - Di = BCe^rotlFixed(BCo, 1); - Do = BCi^rotlFixed(BCu, 1); - Du = BCo^rotlFixed(BCa, 1); + Da = BCu^rotlConstant<1>(BCe); + De = BCa^rotlConstant<1>(BCi); + Di = BCe^rotlConstant<1>(BCo); + Do = BCi^rotlConstant<1>(BCu); + Du = BCo^rotlConstant<1>(BCa); Aba ^= Da; BCa = Aba; Age ^= De; - BCe = rotlFixed(Age, 44); + BCe = rotlConstant<44>(Age); Aki ^= Di; - BCi = rotlFixed(Aki, 43); + BCi = rotlConstant<43>(Aki); Amo ^= Do; - BCo = rotlFixed(Amo, 21); + BCo = rotlConstant<21>(Amo); Asu ^= Du; - BCu = rotlFixed(Asu, 14); + BCu = rotlConstant<14>(Asu); Eba = BCa ^((~BCe)& BCi ); Eba ^= (word64)KeccakF_RoundConstants[round]; Ebe = BCe ^((~BCi)& BCo ); @@ -85,15 +85,15 @@ static void KeccakF1600(word64 *state) Ebu = BCu ^((~BCa)& BCe ); Abo ^= Do; - BCa = rotlFixed(Abo, 28); + BCa = rotlConstant<28>(Abo); Agu ^= Du; - BCe = rotlFixed(Agu, 20); + BCe = rotlConstant<20>(Agu); Aka ^= Da; - BCi = rotlFixed(Aka, 3); + BCi = rotlConstant<3>(Aka); Ame ^= De; - BCo = rotlFixed(Ame, 45); + BCo = rotlConstant<45>(Ame); Asi ^= Di; - BCu = rotlFixed(Asi, 61); + BCu = rotlConstant<61>(Asi); Ega = BCa ^((~BCe)& BCi ); Ege = BCe ^((~BCi)& BCo ); Egi = BCi ^((~BCo)& BCu ); @@ -101,15 +101,15 @@ static void KeccakF1600(word64 *state) Egu = BCu ^((~BCa)& BCe ); Abe ^= De; - BCa = rotlFixed(Abe, 1); + BCa = rotlConstant<1>(Abe); Agi ^= Di; - BCe = rotlFixed(Agi, 6); + BCe = rotlConstant<6>(Agi); Ako ^= Do; - BCi = rotlFixed(Ako, 25); + BCi = rotlConstant<25>(Ako); Amu ^= Du; - BCo = rotlFixed(Amu, 8); + BCo = rotlConstant<8>(Amu); Asa ^= Da; - BCu = rotlFixed(Asa, 18); + BCu = rotlConstant<18>(Asa); Eka = BCa ^((~BCe)& BCi ); Eke = BCe ^((~BCi)& BCo ); Eki = BCi ^((~BCo)& BCu ); @@ -117,15 +117,15 @@ static void KeccakF1600(word64 *state) Eku = BCu ^((~BCa)& BCe ); Abu ^= Du; - BCa = rotlFixed(Abu, 27); + BCa = rotlConstant<27>(Abu); Aga ^= Da; - BCe = rotlFixed(Aga, 36); + BCe = rotlConstant<36>(Aga); Ake ^= De; - BCi = rotlFixed(Ake, 10); + BCi = rotlConstant<10>(Ake); Ami ^= Di; - BCo = rotlFixed(Ami, 15); + BCo = rotlConstant<15>(Ami); Aso ^= Do; - BCu = rotlFixed(Aso, 56); + BCu = rotlConstant<56>(Aso); Ema = BCa ^((~BCe)& BCi ); Eme = BCe ^((~BCi)& BCo ); Emi = BCi ^((~BCo)& BCu ); @@ -133,15 +133,15 @@ static void KeccakF1600(word64 *state) Emu = BCu ^((~BCa)& BCe ); Abi ^= Di; - BCa = rotlFixed(Abi, 62); + BCa = rotlConstant<62>(Abi); Ago ^= Do; - BCe = rotlFixed(Ago, 55); + BCe = rotlConstant<55>(Ago); Aku ^= Du; - BCi = rotlFixed(Aku, 39); + BCi = rotlConstant<39>(Aku); Ama ^= Da; - BCo = rotlFixed(Ama, 41); + BCo = rotlConstant<41>(Ama); Ase ^= De; - BCu = rotlFixed(Ase, 2); + BCu = rotlConstant<2>(Ase); Esa = BCa ^((~BCe)& BCi ); Ese = BCe ^((~BCi)& BCo ); Esi = BCi ^((~BCo)& BCu ); @@ -156,22 +156,22 @@ static void KeccakF1600(word64 *state) BCu = Ebu^Egu^Eku^Emu^Esu; //thetaRhoPiChiIotaPrepareTheta(round+1, E, A) - Da = BCu^rotlFixed(BCe, 1); - De = BCa^rotlFixed(BCi, 1); - Di = BCe^rotlFixed(BCo, 1); - Do = BCi^rotlFixed(BCu, 1); - Du = BCo^rotlFixed(BCa, 1); + Da = BCu^rotlConstant<1>(BCe); + De = BCa^rotlConstant<1>(BCi); + Di = BCe^rotlConstant<1>(BCo); + Do = BCi^rotlConstant<1>(BCu); + Du = BCo^rotlConstant<1>(BCa); Eba ^= Da; BCa = Eba; Ege ^= De; - BCe = rotlFixed(Ege, 44); + BCe = rotlConstant<44>(Ege); Eki ^= Di; - BCi = rotlFixed(Eki, 43); + BCi = rotlConstant<43>(Eki); Emo ^= Do; - BCo = rotlFixed(Emo, 21); + BCo = rotlConstant<21>(Emo); Esu ^= Du; - BCu = rotlFixed(Esu, 14); + BCu = rotlConstant<14>(Esu); Aba = BCa ^((~BCe)& BCi ); Aba ^= (word64)KeccakF_RoundConstants[round+1]; Abe = BCe ^((~BCi)& BCo ); @@ -180,15 +180,15 @@ static void KeccakF1600(word64 *state) Abu = BCu ^((~BCa)& BCe ); Ebo ^= Do; - BCa = rotlFixed(Ebo, 28); + BCa = rotlConstant<28>(Ebo); Egu ^= Du; - BCe = rotlFixed(Egu, 20); + BCe = rotlConstant<20>(Egu); Eka ^= Da; - BCi = rotlFixed(Eka, 3); + BCi = rotlConstant<3>(Eka); Eme ^= De; - BCo = rotlFixed(Eme, 45); + BCo = rotlConstant<45>(Eme); Esi ^= Di; - BCu = rotlFixed(Esi, 61); + BCu = rotlConstant<61>(Esi); Aga = BCa ^((~BCe)& BCi ); Age = BCe ^((~BCi)& BCo ); Agi = BCi ^((~BCo)& BCu ); @@ -196,15 +196,15 @@ static void KeccakF1600(word64 *state) Agu = BCu ^((~BCa)& BCe ); Ebe ^= De; - BCa = rotlFixed(Ebe, 1); + BCa = rotlConstant<1>(Ebe); Egi ^= Di; - BCe = rotlFixed(Egi, 6); + BCe = rotlConstant<6>(Egi); Eko ^= Do; - BCi = rotlFixed(Eko, 25); + BCi = rotlConstant<25>(Eko); Emu ^= Du; - BCo = rotlFixed(Emu, 8); + BCo = rotlConstant<8>(Emu); Esa ^= Da; - BCu = rotlFixed(Esa, 18); + BCu = rotlConstant<18>(Esa); Aka = BCa ^((~BCe)& BCi ); Ake = BCe ^((~BCi)& BCo ); Aki = BCi ^((~BCo)& BCu ); @@ -212,15 +212,15 @@ static void KeccakF1600(word64 *state) Aku = BCu ^((~BCa)& BCe ); Ebu ^= Du; - BCa = rotlFixed(Ebu, 27); + BCa = rotlConstant<27>(Ebu); Ega ^= Da; - BCe = rotlFixed(Ega, 36); + BCe = rotlConstant<36>(Ega); Eke ^= De; - BCi = rotlFixed(Eke, 10); + BCi = rotlConstant<10>(Eke); Emi ^= Di; - BCo = rotlFixed(Emi, 15); + BCo = rotlConstant<15>(Emi); Eso ^= Do; - BCu = rotlFixed(Eso, 56); + BCu = rotlConstant<56>(Eso); Ama = BCa ^((~BCe)& BCi ); Ame = BCe ^((~BCi)& BCo ); Ami = BCi ^((~BCo)& BCu ); @@ -228,15 +228,15 @@ static void KeccakF1600(word64 *state) Amu = BCu ^((~BCa)& BCe ); Ebi ^= Di; - BCa = rotlFixed(Ebi, 62); + BCa = rotlConstant<62>(Ebi); Ego ^= Do; - BCe = rotlFixed(Ego, 55); + BCe = rotlConstant<55>(Ego); Eku ^= Du; - BCi = rotlFixed(Eku, 39); + BCi = rotlConstant<39>(Eku); Ema ^= Da; - BCo = rotlFixed(Ema, 41); + BCo = rotlConstant<41>(Ema); Ese ^= De; - BCu = rotlFixed(Ese, 2); + BCu = rotlConstant<2>(Ese); Asa = BCa ^((~BCe)& BCi ); Ase = BCe ^((~BCi)& BCo ); Asi = BCi ^((~BCo)& BCu ); diff --git a/mars.cpp b/mars.cpp index 9fff388b..a8d69439 100644 --- a/mars.cpp +++ b/mars.cpp @@ -22,12 +22,12 @@ void MARS::Base::UncheckedSetKey(const byte *userKey, unsigned int length, const unsigned int i; // Do linear transformation for (i=0; i<15; i++) - T[i] = T[i] ^ rotlFixed(T[(i+8)%15] ^ T[(i+13)%15], 3) ^ (4*i+j); + T[i] = T[i] ^ rotlConstant<3>(T[(i + 8) % 15] ^ T[(i + 13) % 15]) ^ (4 * i + j); // Do four rounds of stirring for (unsigned int k=0; k<4; k++) for (i=0; i<15; i++) - T[i] = rotlFixed(T[i] + Sbox[T[(i+14)%15]%512], 9); + T[i] = rotlConstant<9>(T[i] + Sbox[T[(i + 14) % 15] % 512]); // Store next 10 key words into K[] for (i=0; i<10; i++) @@ -67,7 +67,7 @@ void MARS::Enc::ProcessAndXorBlock(const byte *inBlock, const byte *xorBlock, by { b = (b ^ S0(a)) + S1(a>>8); c += S0(a>>16); - a = rotrFixed(a, 24); + a = rotrConstant<24>(a); d ^= S1(a); a += (i%4==0) ? d : 0; a += (i%4==1) ? b : 0; @@ -76,11 +76,11 @@ void MARS::Enc::ProcessAndXorBlock(const byte *inBlock, const byte *xorBlock, by for (i=0; i<16; i++) { - t = rotlFixed(a, 13); - r = rotlFixed(t * k[2*i+5], 10); + t = rotlConstant<13>(a); + r = rotlConstant<10>(t * k[2 * i + 5]); m = a + k[2*i+4]; - l = rotlMod((S(m) ^ rotrFixed(r, 5) ^ r), r); - c += rotlMod(m, rotrFixed(r, 5)); + l = rotlMod((S(m) ^ rotrConstant<5>(r) ^ r), r); + c += rotlMod(m, rotrConstant<5>(r)); (i<8 ? b : d) += l; (i<8 ? d : b) ^= r; a = b; b = c; c = d; d = t; @@ -92,7 +92,7 @@ void MARS::Enc::ProcessAndXorBlock(const byte *inBlock, const byte *xorBlock, by a -= (i%4==3) ? b : 0; b ^= S1(a); c -= S0(a>>24); - t = rotlFixed(a, 24); + t = rotlConstant<24>(a); d = (d - S1(a>>16)) ^ S0(t); a = b; b = c; c = d; d = t; } @@ -116,7 +116,7 @@ void MARS::Dec::ProcessAndXorBlock(const byte *inBlock, const byte *xorBlock, by { b = (b ^ S0(a)) + S1(a>>8); c += S0(a>>16); - a = rotrFixed(a, 24); + a = rotrConstant<24>(a); d ^= S1(a); a += (i%4==0) ? d : 0; a += (i%4==1) ? b : 0; @@ -125,11 +125,11 @@ void MARS::Dec::ProcessAndXorBlock(const byte *inBlock, const byte *xorBlock, by for (i=0; i<16; i++) { - t = rotrFixed(a, 13); - r = rotlFixed(a * k[35-2*i], 10); + t = rotrConstant<13>(a); + r = rotlConstant<10>(a * k[35 - 2 * i]); m = t + k[34-2*i]; - l = rotlMod((S(m) ^ rotrFixed(r, 5) ^ r), r); - c -= rotlMod(m, rotrFixed(r, 5)); + l = rotlMod((S(m) ^ rotrConstant<5>(r) ^ r), r); + c -= rotlMod(m, rotrConstant<5>(r)); (i<8 ? b : d) -= l; (i<8 ? d : b) ^= r; a = b; b = c; c = d; d = t; @@ -141,7 +141,7 @@ void MARS::Dec::ProcessAndXorBlock(const byte *inBlock, const byte *xorBlock, by a -= (i%4==3) ? b : 0; b ^= S1(a); c -= S0(a>>24); - t = rotlFixed(a, 24); + t = rotlConstant<24>(a); d = (d - S1(a>>16)) ^ S0(t); a = b; b = c; c = d; d = t; } diff --git a/md4.cpp b/md4.cpp index 713d2143..f14588cc 100644 --- a/md4.cpp +++ b/md4.cpp @@ -44,7 +44,7 @@ void MD4::Transform (word32 *digest, const word32 *in) C=digest[2]; D=digest[3]; -#define function(a,b,c,d,k,s) a=rotlFixed(a+F(b,c,d)+in[k],s); +#define function(a,b,c,d,k,s) a=rotlVariable(a+F(b,c,d)+in[k],s); function(A,B,C,D, 0, 3); function(D,A,B,C, 1, 7); function(C,D,A,B, 2,11); @@ -63,7 +63,7 @@ void MD4::Transform (word32 *digest, const word32 *in) function(B,C,D,A,15,19); #undef function -#define function(a,b,c,d,k,s) a=rotlFixed(a+G(b,c,d)+in[k]+0x5a827999,s); +#define function(a,b,c,d,k,s) a=rotlVariable(a+G(b,c,d)+in[k]+0x5a827999,s); function(A,B,C,D, 0, 3); function(D,A,B,C, 4, 5); function(C,D,A,B, 8, 9); @@ -82,7 +82,7 @@ void MD4::Transform (word32 *digest, const word32 *in) function(B,C,D,A,15,13); #undef function -#define function(a,b,c,d,k,s) a=rotlFixed(a+H(b,c,d)+in[k]+0x6ed9eba1,s); +#define function(a,b,c,d,k,s) a=rotlVariable(a+H(b,c,d)+in[k]+0x6ed9eba1,s); function(A,B,C,D, 0, 3); function(D,A,B,C, 8, 9); function(C,D,A,B, 4,11); diff --git a/rc2.cpp b/rc2.cpp index a4e0079f..1469cc59 100644 --- a/rc2.cpp +++ b/rc2.cpp @@ -61,16 +61,16 @@ void RC2::Enc::ProcessAndXorBlock(const byte *inBlock, const byte *xorBlock, byt for (int i = 0; i < 16; i++) { R0 += (R1 & ~R3) + (R2 & R3) + K[4*i+0]; - R0 = rotlFixed(R0, 1); + R0 = rotlConstant<1>(R0); R1 += (R2 & ~R0) + (R3 & R0) + K[4*i+1]; - R1 = rotlFixed(R1, 2); + R1 = rotlConstant<2>(R1); R2 += (R3 & ~R1) + (R0 & R1) + K[4*i+2]; - R2 = rotlFixed(R2, 3); + R2 = rotlConstant<3>(R2); R3 += (R0 & ~R2) + (R1 & R2) + K[4*i+3]; - R3 = rotlFixed(R3, 5); + R3 = rotlConstant<5>(R3); if (i == 4 || i == 10) { @@ -99,16 +99,16 @@ void RC2::Dec::ProcessAndXorBlock(const byte *inBlock, const byte *xorBlock, byt R0 = word16(R0 - K[R3 & 63]); } - R3 = rotrFixed(R3, 5); + R3 = rotrConstant<5>(R3); R3 = word16(R3 - ((R0 & ~R2) + (R1 & R2) + K[4*i+3])); - R2 = rotrFixed(R2, 3); + R2 = rotrConstant<3>(R2); R2 = word16(R2 - ((R3 & ~R1) + (R0 & R1) + K[4*i+2])); - R1 = rotrFixed(R1, 2); + R1 = rotrConstant<2>(R1); R1 = word16(R1 - ((R2 & ~R0) + (R3 & R0) + K[4*i+1])); - R0 = rotrFixed(R0, 1); + R0 = rotrConstant<1>(R0); R0 = word16(R0 - ((R1 & ~R3) + (R2 & R3) + K[4*i+0])); } diff --git a/rc5.cpp b/rc5.cpp index f17667f2..262c9aec 100644 --- a/rc5.cpp +++ b/rc5.cpp @@ -32,7 +32,7 @@ void RC5::Base::UncheckedSetKey(const byte *k, unsigned int keylen, const NameVa for (unsigned h=0; h < n; h++) { - a = sTable[h % sTable.size()] = rotlFixed((sTable[h % sTable.size()] + a + b), 3); + a = sTable[h % sTable.size()] = rotlConstant<3>((sTable[h % sTable.size()] + a + b)); b = l[h % c] = rotlMod((l[h % c] + a + b), (a+b)); } } diff --git a/rc6.cpp b/rc6.cpp index b5cd8448..6301cb74 100644 --- a/rc6.cpp +++ b/rc6.cpp @@ -33,7 +33,7 @@ void RC6::Base::UncheckedSetKey(const byte *k, unsigned int keylen, const NameVa for (unsigned h=0; h < n; h++) { - a = sTable[h % sTable.size()] = rotlFixed((sTable[h % sTable.size()] + a + b), 3); + a = sTable[h % sTable.size()] = rotlConstant<3>((sTable[h % sTable.size()] + a + b)); b = l[h % c] = rotlMod((l[h % c] + a + b), (a+b)); } } @@ -52,8 +52,8 @@ void RC6::Enc::ProcessAndXorBlock(const byte *inBlock, const byte *xorBlock, byt for(unsigned i=0; i(b*(2*b+1)); + u = rotlConstant<5>(d*(2*d+1)); a = rotlMod(a^t,u) + sptr[0]; c = rotlMod(c^u,t) + sptr[1]; t = a; a = b; b = c; c = d; d = t; @@ -81,8 +81,8 @@ void RC6::Dec::ProcessAndXorBlock(const byte *inBlock, const byte *xorBlock, byt { sptr -= 2; t = a; a = d; d = c; c = b; b = t; - u = rotlFixed(d*(2*d+1), 5); - t = rotlFixed(b*(2*b+1), 5); + u = rotlConstant<5>(d*(2 * d + 1)); + t = rotlConstant<5>(b*(2 * b + 1)); c = rotrMod(c-sptr[1], t) ^ u; a = rotrMod(a-sptr[0], u) ^ t; } diff --git a/rijndael.cpp b/rijndael.cpp index 55bf6510..9074cec9 100644 --- a/rijndael.cpp +++ b/rijndael.cpp @@ -253,7 +253,7 @@ void Rijndael::Base::FillEncTable() for (int j=0; j<4; j++) { Te[i+j*256] = y; - y = rotrFixed(y, 8); + y = rotrConstant<8>(y); } #endif } @@ -276,7 +276,7 @@ void Rijndael::Base::FillDecTable() for (int j=0; j<4; j++) { Td[i+j*256] = y; - y = rotrFixed(y, 8); + y = rotrConstant<8>(y); } #endif } diff --git a/ripemd.cpp b/ripemd.cpp index a9d62391..163b2803 100644 --- a/ripemd.cpp +++ b/ripemd.cpp @@ -31,8 +31,8 @@ NAMESPACE_BEGIN(CryptoPP) // for 160 and 320 #define Subround(f, a, b, c, d, e, x, s, k) \ a += f(b, c, d) + x + k;\ - a = rotlFixed((word32)a, s) + e;\ - c = rotlFixed((word32)c, 10U) + a = rotlVariable((word32)a, s) + e;\ + c = rotlConstant<10>((word32)c) void RIPEMD160::InitState(HashWordType *state) { @@ -459,7 +459,7 @@ void RIPEMD320::Transform (word32 *digest, const word32 *X) // for 128 and 256 #define Subround(f, a, b, c, d, x, s, k) \ a += f(b, c, d) + x + k;\ - a = rotlFixed((word32)a, s); + a = rotlVariable((word32)a, s); void RIPEMD128::InitState(HashWordType *state) { diff --git a/safer.cpp b/safer.cpp index 583f8b3b..83f41517 100644 --- a/safer.cpp +++ b/safer.cpp @@ -74,7 +74,7 @@ void SAFER::Base::UncheckedSetKey(const byte *userkey_1, unsigned int length, co kb[BLOCKSIZE] = 0; for (j = 0; j < BLOCKSIZE; j++) { - ka[BLOCKSIZE] ^= ka[j] = rotlFixed(userkey_1[j], 5U); + ka[BLOCKSIZE] ^= ka[j] = rotlConstant<5>(userkey_1[j]); kb[BLOCKSIZE] ^= kb[j] = *key++ = userkey_2[j]; } @@ -82,8 +82,8 @@ void SAFER::Base::UncheckedSetKey(const byte *userkey_1, unsigned int length, co { for (j = 0; j < BLOCKSIZE + 1; j++) { - ka[j] = rotlFixed(ka[j], 6U); - kb[j] = rotlFixed(kb[j], 6U); + ka[j] = rotlConstant<6>(ka[j]); + kb[j] = rotlConstant<6>(kb[j]); } for (j = 0; j < BLOCKSIZE; j++) if (strengthened) diff --git a/salsa.cpp b/salsa.cpp index e0f7a085..e42a73bd 100644 --- a/salsa.cpp +++ b/salsa.cpp @@ -525,10 +525,10 @@ Salsa20_OperateKeystream ENDP for (int i=m_rounds; i>0; i-=2) { #define QUARTER_ROUND(a, b, c, d) \ - b = b ^ rotlFixed(a + d, 7); \ - c = c ^ rotlFixed(b + a, 9); \ - d = d ^ rotlFixed(c + b, 13); \ - a = a ^ rotlFixed(d + c, 18); + b = b ^ rotlConstant<7>(a + d); \ + c = c ^ rotlConstant<9>(b + a); \ + d = d ^ rotlConstant<13>(c + b); \ + a = a ^ rotlConstant<18>(d + c); QUARTER_ROUND(x0, x4, x8, x12) QUARTER_ROUND(x1, x5, x9, x13) diff --git a/seal.cpp b/seal.cpp index fef2656c..fea047e7 100644 --- a/seal.cpp +++ b/seal.cpp @@ -101,84 +101,84 @@ void SEAL_Policy::OperateKeystream(KeystreamOperation operation, byte *output #define Ttab(x) *(word32 *)(void*)((byte *)m_T.begin()+x) a = m_outsideCounter ^ m_R[4*m_insideCounter]; - b = rotrFixed(m_outsideCounter, 8U) ^ m_R[4*m_insideCounter+1]; - c = rotrFixed(m_outsideCounter, 16U) ^ m_R[4*m_insideCounter+2]; - d = rotrFixed(m_outsideCounter, 24U) ^ m_R[4*m_insideCounter+3]; + b = rotrConstant<8>(m_outsideCounter) ^ m_R[4*m_insideCounter+1]; + c = rotrConstant<16>(m_outsideCounter) ^ m_R[4 * m_insideCounter + 2]; + d = rotrConstant<24>(m_outsideCounter) ^ m_R[4 * m_insideCounter + 3]; for (unsigned int j=0; j<2; j++) { p = a & 0x7fc; b += Ttab(p); - a = rotrFixed(a, 9U); + a = rotrConstant<9>(a); p = b & 0x7fc; c += Ttab(p); - b = rotrFixed(b, 9U); + b = rotrConstant<9>(b); p = c & 0x7fc; d += Ttab(p); - c = rotrFixed(c, 9U); + c = rotrConstant<9>(c); p = d & 0x7fc; a += Ttab(p); - d = rotrFixed(d, 9U); + d = rotrConstant<9>(d); } n1 = d, n2 = b, n3 = a, n4 = c; p = a & 0x7fc; b += Ttab(p); - a = rotrFixed(a, 9U); + a = rotrConstant<9>(a); p = b & 0x7fc; c += Ttab(p); - b = rotrFixed(b, 9U); + b = rotrConstant<9>(b); p = c & 0x7fc; d += Ttab(p); - c = rotrFixed(c, 9U); + c = rotrConstant<9>(c); p = d & 0x7fc; a += Ttab(p); - d = rotrFixed(d, 9U); + d = rotrConstant<9>(d); // generate 8192 bits for (unsigned int i=0; i<64; i++) { p = a & 0x7fc; - a = rotrFixed(a, 9U); + a = rotrConstant<9>(a); b += Ttab(p); b ^= a; q = b & 0x7fc; - b = rotrFixed(b, 9U); + b = rotrConstant<9>(b); c ^= Ttab(q); c += b; p = (p+c) & 0x7fc; - c = rotrFixed(c, 9U); + c = rotrConstant<9>(c); d += Ttab(p); d ^= c; q = (q+d) & 0x7fc; - d = rotrFixed(d, 9U); + d = rotrConstant<9>(d); a ^= Ttab(q); a += d; p = (p+a) & 0x7fc; b ^= Ttab(p); - a = rotrFixed(a, 9U); + a = rotrConstant<9>(a); q = (q+b) & 0x7fc; c += Ttab(q); - b = rotrFixed(b, 9U); + b = rotrConstant<9>(b); p = (p+c) & 0x7fc; d ^= Ttab(p); - c = rotrFixed(c, 9U); + c = rotrConstant<9>(c); q = (q+d) & 0x7fc; - d = rotrFixed(d, 9U); + d = rotrConstant<9>(d); a += Ttab(q); #define SEAL_OUTPUT(x) \ diff --git a/seed.cpp b/seed.cpp index 75410c01..a610b3e6 100644 --- a/seed.cpp +++ b/seed.cpp @@ -75,9 +75,9 @@ void SEED::Base::UncheckedSetKey(const byte *userKey, unsigned int length, const k[1] = G(t1); k+=kInc; if (i&1) - key23 = rotlFixed(key23, 8); + key23 = rotlConstant<8,word64>(key23); else - key01 = rotrFixed(key01, 8); + key01 = rotrConstant<8,word64>(key01); } } diff --git a/serpent.cpp b/serpent.cpp index 80a59499..351186ce 100644 --- a/serpent.cpp +++ b/serpent.cpp @@ -20,9 +20,9 @@ void Serpent_KeySchedule(word32 *k, unsigned int rounds, const byte *userKey, si word32 t = k0[7]; unsigned int i; for (i = 0; i < 8; ++i) - k[i] = k0[i] = t = rotlFixed(k0[i] ^ k0[(i+3)%8] ^ k0[(i+5)%8] ^ t ^ 0x9e3779b9 ^ i, 11); + k[i] = k0[i] = t = rotlConstant<11>(k0[i] ^ k0[(i + 3) % 8] ^ k0[(i + 5) % 8] ^ t ^ 0x9e3779b9 ^ i); for (i = 8; i < 4*(rounds+1); ++i) - k[i] = t = rotlFixed(k[i-8] ^ k[i-5] ^ k[i-3] ^ t ^ 0x9e3779b9 ^ i, 11); + k[i] = t = rotlConstant<11>(k[i-8] ^ k[i-5] ^ k[i-3] ^ t ^ 0x9e3779b9 ^ i); k -= 20; word32 a,b,c,d,e; diff --git a/serpentp.h b/serpentp.h index a38b39a7..b0053c17 100644 --- a/serpentp.h +++ b/serpentp.h @@ -4,24 +4,24 @@ NAMESPACE_BEGIN(CryptoPP) // linear transformation #define LT(i,a,b,c,d,e) {\ - a = rotlFixed(a, 13); \ - c = rotlFixed(c, 3); \ - d = rotlFixed(d ^ c ^ (a << 3), 7); \ - b = rotlFixed(b ^ a ^ c, 1); \ - a = rotlFixed(a ^ b ^ d, 5); \ - c = rotlFixed(c ^ d ^ (b << 7), 22);} + a = rotlConstant<13>(a); \ + c = rotlConstant<3>(c); \ + d = rotlConstant<7>(d ^ c ^ (a << 3)); \ + b = rotlConstant<1>(b ^ a ^ c); \ + a = rotlConstant<5>(a ^ b ^ d); \ + c = rotlConstant<22>(c ^ d ^ (b << 7));} // inverse linear transformation #define ILT(i,a,b,c,d,e) {\ - c = rotrFixed(c, 22); \ - a = rotrFixed(a, 5); \ + c = rotrConstant<22>(c); \ + a = rotrConstant<5>(a); \ c ^= d ^ (b << 7); \ a ^= b ^ d; \ - b = rotrFixed(b, 1); \ - d = rotrFixed(d, 7) ^ c ^ (a << 3); \ + b = rotrConstant<1>(b); \ + d = rotrConstant<7>(d) ^ c ^ (a << 3); \ b ^= a ^ c; \ - c = rotrFixed(c, 3); \ - a = rotrFixed(a, 13);} + c = rotrConstant<3>(c); \ + a = rotrConstant<13>(a);} // order of output from S-box functions #define beforeS0(f) f(0,a,b,c,d,e) diff --git a/sha.cpp b/sha.cpp index d1c8d454..06e1a640 100644 --- a/sha.cpp +++ b/sha.cpp @@ -82,7 +82,7 @@ extern void SHA512_HashMultipleBlocks_POWER8(word64 *state, const word64 *data, ANONYMOUS_NAMESPACE_BEGIN #define blk0(i) (W[i] = data[i]) -#define blk1(i) (W[i&15] = rotlFixed(W[(i+13)&15]^W[(i+8)&15]^W[(i+2)&15]^W[i&15],1)) +#define blk1(i) (W[i&15] = rotlConstant<1>(W[(i+13)&15]^W[(i+8)&15]^W[(i+2)&15]^W[i&15])) #define f1(x,y,z) (z^(x&(y^z))) #define f2(x,y,z) (x^y^z) @@ -90,11 +90,11 @@ ANONYMOUS_NAMESPACE_BEGIN #define f4(x,y,z) (x^y^z) /* (R0+R1), R2, R3, R4 are the different operations used in SHA1 */ -#define R0(v,w,x,y,z,i) z+=f1(w,x,y)+blk0(i)+0x5A827999+rotlFixed(v,5);w=rotlFixed(w,30); -#define R1(v,w,x,y,z,i) z+=f1(w,x,y)+blk1(i)+0x5A827999+rotlFixed(v,5);w=rotlFixed(w,30); -#define R2(v,w,x,y,z,i) z+=f2(w,x,y)+blk1(i)+0x6ED9EBA1+rotlFixed(v,5);w=rotlFixed(w,30); -#define R3(v,w,x,y,z,i) z+=f3(w,x,y)+blk1(i)+0x8F1BBCDC+rotlFixed(v,5);w=rotlFixed(w,30); -#define R4(v,w,x,y,z,i) z+=f4(w,x,y)+blk1(i)+0xCA62C1D6+rotlFixed(v,5);w=rotlFixed(w,30); +#define R0(v,w,x,y,z,i) z+=f1(w,x,y)+blk0(i)+0x5A827999+rotlConstant<5>(v);w=rotlConstant<30>(w); +#define R1(v,w,x,y,z,i) z+=f1(w,x,y)+blk1(i)+0x5A827999+rotlConstant<5>(v);w=rotlConstant<30>(w); +#define R2(v,w,x,y,z,i) z+=f2(w,x,y)+blk1(i)+0x6ED9EBA1+rotlConstant<5>(v);w=rotlConstant<30>(w); +#define R3(v,w,x,y,z,i) z+=f3(w,x,y)+blk1(i)+0x8F1BBCDC+rotlConstant<5>(v);w=rotlConstant<30>(w); +#define R4(v,w,x,y,z,i) z+=f4(w,x,y)+blk1(i)+0xCA62C1D6+rotlConstant<5>(v);w=rotlConstant<30>(w); void SHA1_HashBlock_CXX(word32 *state, const word32 *data) { @@ -271,10 +271,10 @@ ANONYMOUS_NAMESPACE_BEGIN d(i)+=h(i);h(i)+=S0(a(i))+Maj(a(i),b(i),c(i)) // for SHA256 -#define s0(x) (rotrFixed(x,7)^rotrFixed(x,18)^(x>>3)) -#define s1(x) (rotrFixed(x,17)^rotrFixed(x,19)^(x>>10)) -#define S0(x) (rotrFixed(x,2)^rotrFixed(x,13)^rotrFixed(x,22)) -#define S1(x) (rotrFixed(x,6)^rotrFixed(x,11)^rotrFixed(x,25)) +#define s0(x) (rotrConstant<7>(x)^rotrConstant<18>(x)^(x>>3)) +#define s1(x) (rotrConstant<17>(x)^rotrConstant<19>(x)^(x>>10)) +#define S0(x) (rotrConstant<2>(x)^rotrConstant<13>(x)^rotrConstant<22>(x)) +#define S1(x) (rotrConstant<6>(x)^rotrConstant<11>(x)^rotrConstant<25>(x)) void SHA256_HashBlock_CXX(word32 *state, const word32 *data) { @@ -1099,10 +1099,10 @@ ANONYMOUS_NAMESPACE_BEGIN #define Ch(x,y,z) (z^(x&(y^z))) #define Maj(x,y,z) (y^((x^y)&(y^z))) -#define s0(x) (rotrFixed(x,1)^rotrFixed(x,8)^(x>>7)) -#define s1(x) (rotrFixed(x,19)^rotrFixed(x,61)^(x>>6)) -#define S0(x) (rotrFixed(x,28)^rotrFixed(x,34)^rotrFixed(x,39)) -#define S1(x) (rotrFixed(x,14)^rotrFixed(x,18)^rotrFixed(x,41)) +#define s0(x) (rotrConstant<1>(x)^rotrConstant<8>(x)^(x>>7)) +#define s1(x) (rotrConstant<19>(x)^rotrConstant<61>(x)^(x>>6)) +#define S0(x) (rotrConstant<28>(x)^rotrConstant<34>(x)^rotrConstant<39>(x)) +#define S1(x) (rotrConstant<14>(x)^rotrConstant<18>(x)^rotrConstant<41>(x)) #define R(i) h(i)+=S1(e(i))+Ch(e(i),f(i),g(i))+SHA512_K[i+j]+\ (j?blk2(i):blk0(i));d(i)+=h(i);h(i)+=S0(a(i))+Maj(a(i),b(i),c(i)); diff --git a/sha3.cpp b/sha3.cpp index 6cfcaa67..ec3b04e3 100644 --- a/sha3.cpp +++ b/sha3.cpp @@ -61,22 +61,22 @@ static void KeccakF1600(word64 *state) BCu = Abu^Agu^Aku^Amu^Asu; //thetaRhoPiChiIotaPrepareTheta(round , A, E) - Da = BCu^rotlFixed(BCe, 1); - De = BCa^rotlFixed(BCi, 1); - Di = BCe^rotlFixed(BCo, 1); - Do = BCi^rotlFixed(BCu, 1); - Du = BCo^rotlFixed(BCa, 1); + Da = BCu^rotlConstant<1>(BCe); + De = BCa^rotlConstant<1>(BCi); + Di = BCe^rotlConstant<1>(BCo); + Do = BCi^rotlConstant<1>(BCu); + Du = BCo^rotlConstant<1>(BCa); Aba ^= Da; BCa = Aba; Age ^= De; - BCe = rotlFixed(Age, 44); + BCe = rotlConstant<44>(Age); Aki ^= Di; - BCi = rotlFixed(Aki, 43); + BCi = rotlConstant<43>(Aki); Amo ^= Do; - BCo = rotlFixed(Amo, 21); + BCo = rotlConstant<21>(Amo); Asu ^= Du; - BCu = rotlFixed(Asu, 14); + BCu = rotlConstant<14>(Asu); Eba = BCa ^((~BCe)& BCi ); Eba ^= (word64)KeccakF_RoundConstants[round]; Ebe = BCe ^((~BCi)& BCo ); @@ -85,15 +85,15 @@ static void KeccakF1600(word64 *state) Ebu = BCu ^((~BCa)& BCe ); Abo ^= Do; - BCa = rotlFixed(Abo, 28); + BCa = rotlConstant<28>(Abo); Agu ^= Du; - BCe = rotlFixed(Agu, 20); + BCe = rotlConstant<20>(Agu); Aka ^= Da; - BCi = rotlFixed(Aka, 3); + BCi = rotlConstant<3>(Aka); Ame ^= De; - BCo = rotlFixed(Ame, 45); + BCo = rotlConstant<45>(Ame); Asi ^= Di; - BCu = rotlFixed(Asi, 61); + BCu = rotlConstant<61>(Asi); Ega = BCa ^((~BCe)& BCi ); Ege = BCe ^((~BCi)& BCo ); Egi = BCi ^((~BCo)& BCu ); @@ -101,15 +101,15 @@ static void KeccakF1600(word64 *state) Egu = BCu ^((~BCa)& BCe ); Abe ^= De; - BCa = rotlFixed(Abe, 1); + BCa = rotlConstant<1>(Abe); Agi ^= Di; - BCe = rotlFixed(Agi, 6); + BCe = rotlConstant<6>(Agi); Ako ^= Do; - BCi = rotlFixed(Ako, 25); + BCi = rotlConstant<25>(Ako); Amu ^= Du; - BCo = rotlFixed(Amu, 8); + BCo = rotlConstant<8>(Amu); Asa ^= Da; - BCu = rotlFixed(Asa, 18); + BCu = rotlConstant<18>(Asa); Eka = BCa ^((~BCe)& BCi ); Eke = BCe ^((~BCi)& BCo ); Eki = BCi ^((~BCo)& BCu ); @@ -117,15 +117,15 @@ static void KeccakF1600(word64 *state) Eku = BCu ^((~BCa)& BCe ); Abu ^= Du; - BCa = rotlFixed(Abu, 27); + BCa = rotlConstant<27>(Abu); Aga ^= Da; - BCe = rotlFixed(Aga, 36); + BCe = rotlConstant<36>(Aga); Ake ^= De; - BCi = rotlFixed(Ake, 10); + BCi = rotlConstant<10>(Ake); Ami ^= Di; - BCo = rotlFixed(Ami, 15); + BCo = rotlConstant<15>(Ami); Aso ^= Do; - BCu = rotlFixed(Aso, 56); + BCu = rotlConstant<56>(Aso); Ema = BCa ^((~BCe)& BCi ); Eme = BCe ^((~BCi)& BCo ); Emi = BCi ^((~BCo)& BCu ); @@ -133,15 +133,15 @@ static void KeccakF1600(word64 *state) Emu = BCu ^((~BCa)& BCe ); Abi ^= Di; - BCa = rotlFixed(Abi, 62); + BCa = rotlConstant<62>(Abi); Ago ^= Do; - BCe = rotlFixed(Ago, 55); + BCe = rotlConstant<55>(Ago); Aku ^= Du; - BCi = rotlFixed(Aku, 39); + BCi = rotlConstant<39>(Aku); Ama ^= Da; - BCo = rotlFixed(Ama, 41); + BCo = rotlConstant<41>(Ama); Ase ^= De; - BCu = rotlFixed(Ase, 2); + BCu = rotlConstant<2>(Ase); Esa = BCa ^((~BCe)& BCi ); Ese = BCe ^((~BCi)& BCo ); Esi = BCi ^((~BCo)& BCu ); @@ -156,22 +156,22 @@ static void KeccakF1600(word64 *state) BCu = Ebu^Egu^Eku^Emu^Esu; //thetaRhoPiChiIotaPrepareTheta(round+1, E, A) - Da = BCu^rotlFixed(BCe, 1); - De = BCa^rotlFixed(BCi, 1); - Di = BCe^rotlFixed(BCo, 1); - Do = BCi^rotlFixed(BCu, 1); - Du = BCo^rotlFixed(BCa, 1); + Da = BCu^rotlConstant<1>(BCe); + De = BCa^rotlConstant<1>(BCi); + Di = BCe^rotlConstant<1>(BCo); + Do = BCi^rotlConstant<1>(BCu); + Du = BCo^rotlConstant<1>(BCa); Eba ^= Da; BCa = Eba; Ege ^= De; - BCe = rotlFixed(Ege, 44); + BCe = rotlConstant<44>(Ege); Eki ^= Di; - BCi = rotlFixed(Eki, 43); + BCi = rotlConstant<43>(Eki); Emo ^= Do; - BCo = rotlFixed(Emo, 21); + BCo = rotlConstant<21>(Emo); Esu ^= Du; - BCu = rotlFixed(Esu, 14); + BCu = rotlConstant<14>(Esu); Aba = BCa ^((~BCe)& BCi ); Aba ^= (word64)KeccakF_RoundConstants[round+1]; Abe = BCe ^((~BCi)& BCo ); @@ -180,15 +180,15 @@ static void KeccakF1600(word64 *state) Abu = BCu ^((~BCa)& BCe ); Ebo ^= Do; - BCa = rotlFixed(Ebo, 28); + BCa = rotlConstant<28>(Ebo); Egu ^= Du; - BCe = rotlFixed(Egu, 20); + BCe = rotlConstant<20>(Egu); Eka ^= Da; - BCi = rotlFixed(Eka, 3); + BCi = rotlConstant<3>(Eka); Eme ^= De; - BCo = rotlFixed(Eme, 45); + BCo = rotlConstant<45>(Eme); Esi ^= Di; - BCu = rotlFixed(Esi, 61); + BCu = rotlConstant<61>(Esi); Aga = BCa ^((~BCe)& BCi ); Age = BCe ^((~BCi)& BCo ); Agi = BCi ^((~BCo)& BCu ); @@ -196,15 +196,15 @@ static void KeccakF1600(word64 *state) Agu = BCu ^((~BCa)& BCe ); Ebe ^= De; - BCa = rotlFixed(Ebe, 1); + BCa = rotlConstant<1>(Ebe); Egi ^= Di; - BCe = rotlFixed(Egi, 6); + BCe = rotlConstant<6>(Egi); Eko ^= Do; - BCi = rotlFixed(Eko, 25); + BCi = rotlConstant<25>(Eko); Emu ^= Du; - BCo = rotlFixed(Emu, 8); + BCo = rotlConstant<8>(Emu); Esa ^= Da; - BCu = rotlFixed(Esa, 18); + BCu = rotlConstant<18>(Esa); Aka = BCa ^((~BCe)& BCi ); Ake = BCe ^((~BCi)& BCo ); Aki = BCi ^((~BCo)& BCu ); @@ -212,15 +212,15 @@ static void KeccakF1600(word64 *state) Aku = BCu ^((~BCa)& BCe ); Ebu ^= Du; - BCa = rotlFixed(Ebu, 27); + BCa = rotlConstant<27>(Ebu); Ega ^= Da; - BCe = rotlFixed(Ega, 36); + BCe = rotlConstant<36>(Ega); Eke ^= De; - BCi = rotlFixed(Eke, 10); + BCi = rotlConstant<10>(Eke); Emi ^= Di; - BCo = rotlFixed(Emi, 15); + BCo = rotlConstant<15>(Emi); Eso ^= Do; - BCu = rotlFixed(Eso, 56); + BCu = rotlConstant<56>(Eso); Ama = BCa ^((~BCe)& BCi ); Ame = BCe ^((~BCi)& BCo ); Ami = BCi ^((~BCo)& BCu ); @@ -228,15 +228,15 @@ static void KeccakF1600(word64 *state) Amu = BCu ^((~BCa)& BCe ); Ebi ^= Di; - BCa = rotlFixed(Ebi, 62); + BCa = rotlConstant<62>(Ebi); Ego ^= Do; - BCe = rotlFixed(Ego, 55); + BCe = rotlConstant<55>(Ego); Eku ^= Du; - BCi = rotlFixed(Eku, 39); + BCi = rotlConstant<39>(Eku); Ema ^= Da; - BCo = rotlFixed(Ema, 41); + BCo = rotlConstant<41>(Ema); Ese ^= De; - BCu = rotlFixed(Ese, 2); + BCu = rotlConstant<2>(Ese); Asa = BCa ^((~BCe)& BCi ); Ase = BCe ^((~BCi)& BCo ); Asi = BCi ^((~BCo)& BCu ); diff --git a/shacal2.cpp b/shacal2.cpp index 2e77dd6f..6cad11ef 100644 --- a/shacal2.cpp +++ b/shacal2.cpp @@ -22,10 +22,10 @@ NAMESPACE_BEGIN(CryptoPP) // SHACAL-2 function and round definitions -#define S0(x) (rotrFixed(x,2)^rotrFixed(x,13)^rotrFixed(x,22)) -#define S1(x) (rotrFixed(x,6)^rotrFixed(x,11)^rotrFixed(x,25)) -#define s0(x) (rotrFixed(x,7)^rotrFixed(x,18)^(x>>3)) -#define s1(x) (rotrFixed(x,17)^rotrFixed(x,19)^(x>>10)) +#define S0(x) (rotrConstant<2>(x)^rotrConstant<13>(x)^rotrConstant<22>(x)) +#define S1(x) (rotrConstant<6>(x)^rotrConstant<11>(x)^rotrConstant<25>(x)) +#define s0(x) (rotrConstant<7>(x)^rotrConstant<18>(x)^(x>>3)) +#define s1(x) (rotrConstant<17>(x)^rotrConstant<19>(x)^(x>>10)) #define Ch(x,y,z) (z^(x&(y^z))) #define Maj(x,y,z) ((x&y)|(z&(x|y))) diff --git a/simon.cpp b/simon.cpp index c1bee040..a9ea38d7 100644 --- a/simon.cpp +++ b/simon.cpp @@ -10,8 +10,8 @@ ANONYMOUS_NAMESPACE_BEGIN using CryptoPP::word32; using CryptoPP::word64; -using CryptoPP::rotlFixed; -using CryptoPP::rotrFixed; +using CryptoPP::rotlConstant; +using CryptoPP::rotrConstant; //! \brief Round transformation helper //! \tparam W word type @@ -19,7 +19,7 @@ using CryptoPP::rotrFixed; template inline W f(const W v) { - return (rotlFixed(v, 1) & rotlFixed(v, 8)) ^ rotlFixed(v, 2); + return (rotlConstant<1>(v) & rotlConstant<8>(v)) ^ rotlConstant<2>(v); } //! \brief Round transformation @@ -103,7 +103,7 @@ inline void SPECK64_ExpandKey_42R3K(word32 key[42], const word32 k[3]) key[0] = k[2]; key[1] = k[1]; key[2] = k[0]; for (size_t i = 3; i<42; ++i) { - key[i] = c ^ (z & 1) ^ key[i-3] ^ rotrFixed(key[i-1], 3) ^ rotrFixed(key[i-1], 4); + key[i] = c ^ (z & 1) ^ key[i - 3] ^ rotrConstant<3>(key[i - 1]) ^ rotrConstant<4>(key[i - 1]); z >>= 1; } } @@ -121,7 +121,7 @@ inline void SPECK64_ExpandKey_44R4K(word32 key[44], const word32 k[4]) key[0] = k[3]; key[1] = k[2]; key[2] = k[1]; key[3] = k[0]; for (size_t i = 4; i<44; ++i) { - key[i] = c ^ (z & 1) ^ key[i-4] ^ rotrFixed(key[i-1], 3) ^ key[i-3] ^ rotrFixed(key[i-1], 4) ^ rotrFixed(key[i-3], 1); + key[i] = c ^ (z & 1) ^ key[i - 4] ^ rotrConstant<3>(key[i - 1]) ^ key[i - 3] ^ rotrConstant<4>(key[i - 1]) ^ rotrConstant<1>(key[i - 3]); z >>= 1; } } @@ -139,12 +139,12 @@ inline void SIMON128_ExpandKey_68R2K(word64 key[68], const word64 k[2]) key[0] = k[1]; key[1] = k[0]; for (size_t i=2; i<66; ++i) { - key[i] = c^(z&1)^key[i-2]^rotrFixed(key[i-1],3)^rotrFixed(key[i-1],4); + key[i] = c ^ (z & 1) ^ key[i - 2] ^ rotrConstant<3>(key[i - 1]) ^ rotrConstant<4>(key[i - 1]); z>>=1; } - key[66] = c^1^key[64]^rotrFixed(key[65],3)^rotrFixed(key[65],4); - key[67] = c^key[65]^rotrFixed(key[66],3)^rotrFixed(key[66],4); + key[66] = c ^ 1 ^ key[64] ^ rotrConstant<3>(key[65]) ^ rotrConstant<4>(key[65]); + key[67] = c^key[65] ^ rotrConstant<3>(key[66]) ^ rotrConstant<4>(key[66]); } //! \brief Subkey generation function @@ -160,12 +160,12 @@ inline void SIMON128_ExpandKey_69R3K(word64 key[69], const word64 k[3]) key[0]=k[2]; key[1]=k[1]; key[2]=k[0]; for (size_t i=3; i<67; ++i) { - key[i] = c^(z&1)^key[i-3]^rotrFixed(key[i-1],3)^rotrFixed(key[i-1],4); + key[i] = c ^ (z & 1) ^ key[i - 3] ^ rotrConstant<3>(key[i - 1]) ^ rotrConstant<4>(key[i - 1]); z>>=1; } - key[67] = c^key[64]^rotrFixed(key[66],3)^rotrFixed(key[66],4); - key[68] = c^1^key[65]^rotrFixed(key[67],3)^rotrFixed(key[67],4); + key[67] = c^key[64] ^ rotrConstant<3>(key[66]) ^ rotrConstant<4>(key[66]); + key[68] = c ^ 1 ^ key[65] ^ rotrConstant<3>(key[67]) ^ rotrConstant<4>(key[67]); } //! \brief Subkey generation function @@ -181,14 +181,14 @@ inline void SIMON128_ExpandKey_72R4K(word64 key[72], const word64 k[4]) key[0]=k[3]; key[1]=k[2]; key[2]=k[1]; key[3]=k[0]; for (size_t i=4; i<68; ++i) { - key[i] = c^(z&1)^key[i-4]^rotrFixed(key[i-1],3)^key[i-3]^rotrFixed(key[i-1],4)^rotrFixed(key[i-3],1); + key[i] = c ^ (z & 1) ^ key[i - 4] ^ rotrConstant<3>(key[i - 1]) ^ key[i - 3] ^ rotrConstant<4>(key[i - 1]) ^ rotrConstant<1>(key[i - 3]); z>>=1; } - key[68] = c^key[64]^rotrFixed(key[67],3)^key[65]^rotrFixed(key[67],4)^rotrFixed(key[65],1); - key[69] = c^1^key[65]^rotrFixed(key[68],3)^key[66]^rotrFixed(key[68],4)^rotrFixed(key[66],1); - key[70] = c^key[66]^rotrFixed(key[69],3)^key[67]^rotrFixed(key[69],4)^rotrFixed(key[67],1); - key[71] = c^key[67]^rotrFixed(key[70],3)^key[68]^rotrFixed(key[70],4)^rotrFixed(key[68],1); + key[68] = c^key[64] ^ rotrConstant<3>(key[67]) ^ key[65] ^ rotrConstant<4>(key[67]) ^ rotrConstant<1>(key[65]); + key[69] = c ^ 1 ^ key[65] ^ rotrConstant<3>(key[68]) ^ key[66] ^ rotrConstant<4>(key[68]) ^ rotrConstant<1>(key[66]); + key[70] = c^key[66] ^ rotrConstant<3>(key[69]) ^ key[67] ^ rotrConstant<4>(key[69]) ^ rotrConstant<1>(key[67]); + key[71] = c^key[67] ^ rotrConstant<3>(key[70]) ^ key[68] ^ rotrConstant<4>(key[70]) ^ rotrConstant<1>(key[68]); } ANONYMOUS_NAMESPACE_END diff --git a/siphash.h b/siphash.h index f8418c51..5f36cd39 100644 --- a/siphash.h +++ b/siphash.h @@ -90,19 +90,19 @@ protected: inline void SIPROUND() { m_v[0] += m_v[1]; - m_v[1] = rotlFixed(m_v[1], 13U); + m_v[1] = rotlConstant<13>(m_v[1]); m_v[1] ^= m_v[0]; - m_v[0] = rotlFixed(m_v[0], 32U); + m_v[0] = rotlConstant<32>(m_v[0]); m_v[2] += m_v[3]; - m_v[3] = rotlFixed(m_v[3], 16U); + m_v[3] = rotlConstant<16>(m_v[3]); m_v[3] ^= m_v[2]; m_v[0] += m_v[3]; - m_v[3] = rotlFixed(m_v[3], 21U); + m_v[3] = rotlConstant<21>(m_v[3]); m_v[3] ^= m_v[0]; m_v[2] += m_v[1]; - m_v[1] = rotlFixed(m_v[1], 17U); + m_v[1] = rotlConstant<17>(m_v[1]); m_v[1] ^= m_v[2]; - m_v[2] = rotlFixed(m_v[2], 32U); + m_v[2] = rotlConstant<32>(m_v[2]); } private: diff --git a/sosemanuk.cpp b/sosemanuk.cpp index 0ff37d0c..276ebb2d 100644 --- a/sosemanuk.cpp +++ b/sosemanuk.cpp @@ -85,7 +85,7 @@ void SosemanukPolicy::CipherResynchronize(byte *keystreamBuffer, const byte *iv, #define XMUX(c, x, y) (x ^ (y & (0 - (c & 1)))) m_state[11] += XMUX(m_state[10], m_state[1], m_state[8]); - m_state[10] = rotlFixed(m_state[10] * 0x54655307, 7); + m_state[10] = rotlConstant<7>(m_state[10] * 0x54655307); } extern "C" { @@ -626,7 +626,7 @@ void SosemanukPolicy::OperateKeystream(KeystreamOperation operation, byte *outpu #ifndef CRYPTOPP_GENERATE_X64_MASM { #if (CRYPTOPP_BOOL_X86 || CRYPTOPP_BOOL_X32 || CRYPTOPP_BOOL_X64) && !defined(CRYPTOPP_DISABLE_SOSEMANUK_ASM) -#define MUL_A(x) (x = rotlFixed(x, 8), x ^ s_sosemanukMulTables[byte(x)]) +#define MUL_A(x) (x = (rotlConstant<7>(x)), x ^ s_sosemanukMulTables[byte(x)]) #else #define MUL_A(x) (((x) << 8) ^ s_sosemanukMulTables[(x) >> 24]) #endif diff --git a/square.cpp b/square.cpp index 0b960323..4065a7f3 100644 --- a/square.cpp +++ b/square.cpp @@ -58,7 +58,7 @@ void Square::Base::UncheckedSetKey(const byte *userKey, unsigned int length, con /* apply the key evolution function */ for (int i = 1; i < ROUNDS+1; i++) { - roundkeys(i, 0) = roundkeys(i-1, 0) ^ rotlFixed(roundkeys(i-1, 3), 8U) ^ offset[i-1]; + roundkeys(i, 0) = roundkeys(i-1, 0) ^ rotlConstant<8>(roundkeys(i-1, 3)) ^ offset[i-1]; roundkeys(i, 1) = roundkeys(i-1, 1) ^ roundkeys(i, 0); roundkeys(i, 2) = roundkeys(i-1, 2) ^ roundkeys(i, 1); roundkeys(i, 3) = roundkeys(i-1, 3) ^ roundkeys(i, 2); diff --git a/threefish.cpp b/threefish.cpp index 8fff615b..ff74566e 100644 --- a/threefish.cpp +++ b/threefish.cpp @@ -12,24 +12,16 @@ ANONYMOUS_NAMESPACE_BEGIN -#if defined(__clang__) -# define rotatel64(x,y) rotlVariable(x,y) -# define rotater64(x,y) rotrVariable(x,y) -#else -# define rotatel64(x,y) rotlFixed(x,y) -# define rotater64(x,y) rotrFixed(x,y) -#endif - #define G256(G0, G1, G2, G3, C0, C1) \ G0 += G1; \ - G1 = rotatel64(G1, C0) ^ G0; \ + G1 = rotlVariable(G1, C0) ^ G0; \ G2 += G3; \ - G3 = rotatel64(G3, C1) ^ G2; + G3 = rotlVariable(G3, C1) ^ G2; #define IG256(G0, G1, G2, G3, C0, C1) \ - G3 = rotater64(G3 ^ G2, C1); \ + G3 = rotrVariable(G3 ^ G2, C1); \ G2 -= G3; \ - G1 = rotater64(G1 ^ G0, C0); \ + G1 = rotrVariable(G1 ^ G0, C0); \ G0 -= G1; \ #define KS256(r) \ @@ -69,24 +61,24 @@ ANONYMOUS_NAMESPACE_BEGIN IKS256(r - 1); #define IG512(G0, G1, G2, G3, G4, G5, G6, G7, C0, C1, C2, C3) \ - G7 = rotater64(G7 ^ G6, C3); \ + G7 = rotrVariable(G7 ^ G6, C3); \ G6 -= G7; \ - G5 = rotater64(G5 ^ G4, C2); \ + G5 = rotrVariable(G5 ^ G4, C2); \ G4 -= G5; \ - G3 = rotater64(G3 ^ G2, C1); \ + G3 = rotrVariable(G3 ^ G2, C1); \ G2 -= G3; \ - G1 = rotater64(G1 ^ G0, C0); \ + G1 = rotrVariable(G1 ^ G0, C0); \ G0 -= G1; #define G512(G0, G1, G2, G3, G4, G5, G6, G7, C0, C1, C2, C3) \ G0 += G1; \ - G1 = rotatel64(G1, C0) ^ G0; \ + G1 = rotlVariable(G1, C0) ^ G0; \ G2 += G3; \ - G3 = rotatel64(G3, C1) ^ G2; \ + G3 = rotlVariable(G3, C1) ^ G2; \ G4 += G5; \ - G5 = rotatel64(G5, C2) ^ G4; \ + G5 = rotlVariable(G5, C2) ^ G4; \ G6 += G7; \ - G7 = rotatel64(G7, C3) ^ G6; + G7 = rotlVariable(G7, C3) ^ G6; #define IKS512(r) \ G0 -= m_rkey[(r + 1) % 9]; \ @@ -133,40 +125,40 @@ ANONYMOUS_NAMESPACE_BEGIN KS512(r + 1) #define IG1024(G0, G1, G2, G3, G4, G5, G6, G7, G8, G9, G10, G11, G12, G13, G14, G15, C1, C2, C3, C4, C5, C6, C7, C8) \ - G15 = rotater64(G15 ^ G14, C8); \ + G15 = rotrVariable(G15 ^ G14, C8); \ G14 -= G15; \ - G13 = rotater64(G13 ^ G12, C7); \ + G13 = rotrVariable(G13 ^ G12, C7); \ G12 -= G13; \ - G11 = rotater64(G11 ^ G10, C6); \ + G11 = rotrVariable(G11 ^ G10, C6); \ G10 -= G11; \ - G9 = rotater64(G9 ^ G8, C5); \ + G9 = rotrVariable(G9 ^ G8, C5); \ G8 -= G9; \ - G7 = rotater64(G7 ^ G6, C4); \ + G7 = rotrVariable(G7 ^ G6, C4); \ G6 -= G7; \ - G5 = rotater64(G5 ^ G4, C3); \ + G5 = rotrVariable(G5 ^ G4, C3); \ G4 -= G5; \ - G3 = rotater64(G3 ^ G2, C2); \ + G3 = rotrVariable(G3 ^ G2, C2); \ G2 -= G3; \ - G1 = rotater64(G1 ^ G0, C1); \ + G1 = rotrVariable(G1 ^ G0, C1); \ G0 -= G1; #define G1024(G0, G1, G2, G3, G4, G5, G6, G7, G8, G9, G10, G11, G12, G13, G14, G15, C1, C2, C3, C4, C5, C6, C7, C8) \ G0 += G1; \ - G1 = rotatel64(G1, C1) ^ G0; \ + G1 = rotlVariable(G1, C1) ^ G0; \ G2 += G3; \ - G3 = rotatel64(G3, C2) ^ G2; \ + G3 = rotlVariable(G3, C2) ^ G2; \ G4 += G5; \ - G5 = rotatel64(G5, C3) ^ G4; \ + G5 = rotlVariable(G5, C3) ^ G4; \ G6 += G7; \ - G7 = rotatel64(G7, C4) ^ G6; \ + G7 = rotlVariable(G7, C4) ^ G6; \ G8 += G9; \ - G9 = rotatel64(G9, C5) ^ G8; \ + G9 = rotlVariable(G9, C5) ^ G8; \ G10 += G11; \ - G11 = rotatel64(G11, C6) ^ G10; \ + G11 = rotlVariable(G11, C6) ^ G10; \ G12 += G13; \ - G13 = rotatel64(G13, C7) ^ G12; \ + G13 = rotlVariable(G13, C7) ^ G12; \ G14 += G15; \ - G15 = rotatel64(G15, C8) ^ G14; + G15 = rotlVariable(G15, C8) ^ G14; #define IKS1024(r) \ G0 -= m_rkey[(r + 1) % 17]; \ diff --git a/ttmac.cpp b/ttmac.cpp index 98954370..7bcb9855 100644 --- a/ttmac.cpp +++ b/ttmac.cpp @@ -99,8 +99,8 @@ void TTMAC_Base::Transform(word32 *digest, const word32 *X, bool last) { #define Subround(f, a, b, c, d, e, x, s, k) \ a += f(b, c, d) + x + k;\ - a = rotlFixed((word32)a, s) + e;\ - c = rotlFixed((word32)c, 10U) + a = rotlVariable((word32)a, s) + e;\ + c = rotlVariable((word32)c, 10U) word32 a1, b1, c1, d1, e1, a2, b2, c2, d2, e2; word32 *trackA, *trackB; diff --git a/twofish.cpp b/twofish.cpp index d7104cbd..1097eba5 100644 --- a/twofish.cpp +++ b/twofish.cpp @@ -64,9 +64,9 @@ void Twofish::Base::UncheckedSetKey(const byte *userKey, unsigned int keylength, for (i=0; i<40; i+=2) { word32 a = h(i, key, len); - word32 b = rotlFixed(h(i+1, key+1, len), 8); + word32 b = rotlConstant<8>(h(i + 1, key + 1, len)); m_k[i] = a+b; - m_k[i+1] = rotlFixed(a+2*b, 9); + m_k[i + 1] = rotlConstant<9>(a + 2 * b); } SecBlock svec(2*len); @@ -89,8 +89,8 @@ void Twofish::Base::UncheckedSetKey(const byte *userKey, unsigned int keylength, x = G1 (a); y = G2 (b); \ x += y; y += x + k[2 * (n) + 1]; \ (c) ^= x + k[2 * (n)]; \ - (c) = rotrFixed(c, 1); \ - (d) = rotlFixed(d, 1) ^ y + (c) = rotrConstant<1>(c); \ + (d) = rotlConstant<1>(d) ^ y #define ENCCYCLE(n) \ ENCROUND (2 * (n), a, b, c, d); \ @@ -100,8 +100,8 @@ void Twofish::Base::UncheckedSetKey(const byte *userKey, unsigned int keylength, x = G1 (a); y = G2 (b); \ x += y; y += x; \ (d) ^= y + k[2 * (n) + 1]; \ - (d) = rotrFixed(d, 1); \ - (c) = rotlFixed(c, 1); \ + (d) = rotrConstant<1>(d); \ + (c) = rotlConstant<1>(c); \ (c) ^= (x + k[2 * (n)]) #define DECCYCLE(n) \ diff --git a/whrlpool.cpp b/whrlpool.cpp index 49b030e4..9fb28bda 100644 --- a/whrlpool.cpp +++ b/whrlpool.cpp @@ -621,16 +621,16 @@ void Whirlpool::Transform(word64 *digest, const word64 *block) #define KSH(op, i, a, b, c, d) \ t = (word32)(k[(i+4)%8]>>32);\ - w##a = Whirlpool_C[3*256 + (byte)t] ^ (op ? w##a : rotrFixed(w##a, 32));\ + w##a = Whirlpool_C[3*256 + (byte)t] ^ (op ? w##a : rotrConstant<32>(w##a));\ if (op==2) k[a] = w##a;\ t >>= 8;\ - w##b = Whirlpool_C[2*256 + (byte)t] ^ (op ? w##b : rotrFixed(w##b, 32));\ + w##b = Whirlpool_C[2*256 + (byte)t] ^ (op ? w##b : rotrConstant<32>(w##b));\ if (op==2) k[b] = w##b;\ t >>= 8;\ - w##c = Whirlpool_C[1*256 + (byte)t] ^ (op ? w##c : rotrFixed(w##c, 32));\ + w##c = Whirlpool_C[1*256 + (byte)t] ^ (op ? w##c : rotrConstant<32>(w##c));\ if (op==2) k[c] = w##c;\ t >>= 8;\ - w##d = Whirlpool_C[0*256 + t] ^ (op ? w##d : rotrFixed(w##d, 32));\ + w##d = Whirlpool_C[0*256 + t] ^ (op ? w##d : rotrConstant<32>(w##d));\ if (op==2) k[d] = w##d;\ #define TSL(op, i, a, b, c, d) \ @@ -644,7 +644,7 @@ void Whirlpool::Transform(word64 *digest, const word64 *block) w##d = Whirlpool_C[0*256 + t] ^ (op ? w##d : 0); #define TSH_OP(op, a, b) \ - w##a = Whirlpool_C[b*256 + (byte)t] ^ (op ? w##a : rotrFixed(w##a, 32) ^ k[a]);\ + w##a = Whirlpool_C[b*256 + (byte)t] ^ (op ? w##a : rotrConstant<32>(w##a) ^ k[a]);\ if (op==2) s[a] = w##a;\ if (op==3) digest[a] ^= w##a;\