1*5c591343SA. Cody Schuffelen /* Microsoft Reference Implementation for TPM 2.0
2*5c591343SA. Cody Schuffelen *
3*5c591343SA. Cody Schuffelen * The copyright in this software is being made available under the BSD License,
4*5c591343SA. Cody Schuffelen * included below. This software may be subject to other third party and
5*5c591343SA. Cody Schuffelen * contributor rights, including patent rights, and no such rights are granted
6*5c591343SA. Cody Schuffelen * under this license.
7*5c591343SA. Cody Schuffelen *
8*5c591343SA. Cody Schuffelen * Copyright (c) Microsoft Corporation
9*5c591343SA. Cody Schuffelen *
10*5c591343SA. Cody Schuffelen * All rights reserved.
11*5c591343SA. Cody Schuffelen *
12*5c591343SA. Cody Schuffelen * BSD License
13*5c591343SA. Cody Schuffelen *
14*5c591343SA. Cody Schuffelen * Redistribution and use in source and binary forms, with or without modification,
15*5c591343SA. Cody Schuffelen * are permitted provided that the following conditions are met:
16*5c591343SA. Cody Schuffelen *
17*5c591343SA. Cody Schuffelen * Redistributions of source code must retain the above copyright notice, this list
18*5c591343SA. Cody Schuffelen * of conditions and the following disclaimer.
19*5c591343SA. Cody Schuffelen *
20*5c591343SA. Cody Schuffelen * Redistributions in binary form must reproduce the above copyright notice, this
21*5c591343SA. Cody Schuffelen * list of conditions and the following disclaimer in the documentation and/or
22*5c591343SA. Cody Schuffelen * other materials provided with the distribution.
23*5c591343SA. Cody Schuffelen *
24*5c591343SA. Cody Schuffelen * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS ""AS IS""
25*5c591343SA. Cody Schuffelen * AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
26*5c591343SA. Cody Schuffelen * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
27*5c591343SA. Cody Schuffelen * DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR
28*5c591343SA. Cody Schuffelen * ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
29*5c591343SA. Cody Schuffelen * (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
30*5c591343SA. Cody Schuffelen * LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON
31*5c591343SA. Cody Schuffelen * ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
32*5c591343SA. Cody Schuffelen * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
33*5c591343SA. Cody Schuffelen * SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
34*5c591343SA. Cody Schuffelen */
35*5c591343SA. Cody Schuffelen //** Introduction
36*5c591343SA. Cody Schuffelen //
37*5c591343SA. Cody Schuffelen // This file contains implementation of cryptographic primitives for RSA.
38*5c591343SA. Cody Schuffelen // Vendors may replace the implementation in this file with their own library
39*5c591343SA. Cody Schuffelen // functions.
40*5c591343SA. Cody Schuffelen
41*5c591343SA. Cody Schuffelen //** Includes
42*5c591343SA. Cody Schuffelen // Need this define to get the 'private' defines for this function
43*5c591343SA. Cody Schuffelen #define CRYPT_RSA_C
44*5c591343SA. Cody Schuffelen #include "Tpm.h"
45*5c591343SA. Cody Schuffelen
46*5c591343SA. Cody Schuffelen #if ALG_RSA
47*5c591343SA. Cody Schuffelen
48*5c591343SA. Cody Schuffelen //** Obligatory Initialization Functions
49*5c591343SA. Cody Schuffelen
50*5c591343SA. Cody Schuffelen //*** CryptRsaInit()
51*5c591343SA. Cody Schuffelen // Function called at _TPM_Init().
52*5c591343SA. Cody Schuffelen BOOL
CryptRsaInit(void)53*5c591343SA. Cody Schuffelen CryptRsaInit(
54*5c591343SA. Cody Schuffelen void
55*5c591343SA. Cody Schuffelen )
56*5c591343SA. Cody Schuffelen {
57*5c591343SA. Cody Schuffelen return TRUE;
58*5c591343SA. Cody Schuffelen }
59*5c591343SA. Cody Schuffelen
60*5c591343SA. Cody Schuffelen //*** CryptRsaStartup()
61*5c591343SA. Cody Schuffelen // Function called at TPM2_Startup()
62*5c591343SA. Cody Schuffelen BOOL
CryptRsaStartup(void)63*5c591343SA. Cody Schuffelen CryptRsaStartup(
64*5c591343SA. Cody Schuffelen void
65*5c591343SA. Cody Schuffelen )
66*5c591343SA. Cody Schuffelen {
67*5c591343SA. Cody Schuffelen return TRUE;
68*5c591343SA. Cody Schuffelen }
69*5c591343SA. Cody Schuffelen
70*5c591343SA. Cody Schuffelen //** Internal Functions
71*5c591343SA. Cody Schuffelen
72*5c591343SA. Cody Schuffelen //*** RsaInitializeExponent()
73*5c591343SA. Cody Schuffelen // This function initializes the bignum data structure that holds the private
74*5c591343SA. Cody Schuffelen // exponent. This function returns the pointer to the private exponent value so that
75*5c591343SA. Cody Schuffelen // it can be used in an initializer for a data declaration.
76*5c591343SA. Cody Schuffelen static privateExponent *
RsaInitializeExponent(privateExponent * Z)77*5c591343SA. Cody Schuffelen RsaInitializeExponent(
78*5c591343SA. Cody Schuffelen privateExponent *Z
79*5c591343SA. Cody Schuffelen )
80*5c591343SA. Cody Schuffelen {
81*5c591343SA. Cody Schuffelen bigNum *bn = (bigNum *)&Z->P;
82*5c591343SA. Cody Schuffelen int i;
83*5c591343SA. Cody Schuffelen //
84*5c591343SA. Cody Schuffelen for(i = 0; i < 5; i++)
85*5c591343SA. Cody Schuffelen {
86*5c591343SA. Cody Schuffelen bn[i] = (bigNum)&Z->entries[i];
87*5c591343SA. Cody Schuffelen BnInit(bn[i], BYTES_TO_CRYPT_WORDS(sizeof(Z->entries[0].d)));
88*5c591343SA. Cody Schuffelen }
89*5c591343SA. Cody Schuffelen return Z;
90*5c591343SA. Cody Schuffelen }
91*5c591343SA. Cody Schuffelen
92*5c591343SA. Cody Schuffelen //*** MakePgreaterThanQ()
93*5c591343SA. Cody Schuffelen // This function swaps the pointers for P and Q if Q happens to be larger than Q.
94*5c591343SA. Cody Schuffelen static void
MakePgreaterThanQ(privateExponent * Z)95*5c591343SA. Cody Schuffelen MakePgreaterThanQ(
96*5c591343SA. Cody Schuffelen privateExponent *Z
97*5c591343SA. Cody Schuffelen )
98*5c591343SA. Cody Schuffelen {
99*5c591343SA. Cody Schuffelen if(BnUnsignedCmp(Z->P, Z->Q) < 0)
100*5c591343SA. Cody Schuffelen {
101*5c591343SA. Cody Schuffelen bigNum bnT = Z->P;
102*5c591343SA. Cody Schuffelen Z->P = Z->Q;
103*5c591343SA. Cody Schuffelen Z->Q = bnT;
104*5c591343SA. Cody Schuffelen }
105*5c591343SA. Cody Schuffelen }
106*5c591343SA. Cody Schuffelen
107*5c591343SA. Cody Schuffelen //*** PackExponent()
108*5c591343SA. Cody Schuffelen // This function takes the bignum private exponent and converts it into TPM2B form.
109*5c591343SA. Cody Schuffelen // In this form, the size field contains the overall size of the packed data. The
110*5c591343SA. Cody Schuffelen // buffer contains 5, equal sized values in P, Q, dP, dQ, qInv order. For example, if
111*5c591343SA. Cody Schuffelen // a key has a 2Kb public key, then the packed private key will contain 5, 1Kb values.
112*5c591343SA. Cody Schuffelen // This form makes it relatively easy to load and save the values without changing
113*5c591343SA. Cody Schuffelen // the normal unmarshaling to do anything more than allow a larger TPM2B for the
114*5c591343SA. Cody Schuffelen // private key. Also, when exporting the value, all that is needed is to change the
115*5c591343SA. Cody Schuffelen // size field of the private key in order to save just the P value.
116*5c591343SA. Cody Schuffelen // Return Type: BOOL
117*5c591343SA. Cody Schuffelen // TRUE(1) success
118*5c591343SA. Cody Schuffelen // FALSE(0) failure // The data is too big to fit
119*5c591343SA. Cody Schuffelen static BOOL
PackExponent(TPM2B_PRIVATE_KEY_RSA * packed,privateExponent * Z)120*5c591343SA. Cody Schuffelen PackExponent(
121*5c591343SA. Cody Schuffelen TPM2B_PRIVATE_KEY_RSA *packed,
122*5c591343SA. Cody Schuffelen privateExponent *Z
123*5c591343SA. Cody Schuffelen )
124*5c591343SA. Cody Schuffelen {
125*5c591343SA. Cody Schuffelen int i;
126*5c591343SA. Cody Schuffelen UINT16 primeSize = (UINT16)BITS_TO_BYTES(BnMsb(Z->P));
127*5c591343SA. Cody Schuffelen UINT16 pS = primeSize;
128*5c591343SA. Cody Schuffelen //
129*5c591343SA. Cody Schuffelen pAssert((primeSize * 5) <= sizeof(packed->t.buffer));
130*5c591343SA. Cody Schuffelen packed->t.size = (primeSize * 5) + RSA_prime_flag;
131*5c591343SA. Cody Schuffelen for(i = 0; i < 5; i++)
132*5c591343SA. Cody Schuffelen if(!BnToBytes((bigNum)&Z->entries[i], &packed->t.buffer[primeSize * i], &pS))
133*5c591343SA. Cody Schuffelen return FALSE;
134*5c591343SA. Cody Schuffelen if(pS != primeSize)
135*5c591343SA. Cody Schuffelen return FALSE;
136*5c591343SA. Cody Schuffelen return TRUE;
137*5c591343SA. Cody Schuffelen }
138*5c591343SA. Cody Schuffelen
139*5c591343SA. Cody Schuffelen //*** UnpackExponent()
140*5c591343SA. Cody Schuffelen // This function unpacks the private exponent from its TPM2B form into its bignum
141*5c591343SA. Cody Schuffelen // form.
142*5c591343SA. Cody Schuffelen // Return Type: BOOL
143*5c591343SA. Cody Schuffelen // TRUE(1) success
144*5c591343SA. Cody Schuffelen // FALSE(0) TPM2B is not the correct size
145*5c591343SA. Cody Schuffelen static BOOL
UnpackExponent(TPM2B_PRIVATE_KEY_RSA * b,privateExponent * Z)146*5c591343SA. Cody Schuffelen UnpackExponent(
147*5c591343SA. Cody Schuffelen TPM2B_PRIVATE_KEY_RSA *b,
148*5c591343SA. Cody Schuffelen privateExponent *Z
149*5c591343SA. Cody Schuffelen )
150*5c591343SA. Cody Schuffelen {
151*5c591343SA. Cody Schuffelen UINT16 primeSize = b->t.size & ~RSA_prime_flag;
152*5c591343SA. Cody Schuffelen int i;
153*5c591343SA. Cody Schuffelen bigNum *bn = &Z->P;
154*5c591343SA. Cody Schuffelen //
155*5c591343SA. Cody Schuffelen VERIFY(b->t.size & RSA_prime_flag);
156*5c591343SA. Cody Schuffelen RsaInitializeExponent(Z);
157*5c591343SA. Cody Schuffelen VERIFY((primeSize % 5) == 0);
158*5c591343SA. Cody Schuffelen primeSize /= 5;
159*5c591343SA. Cody Schuffelen for(i = 0; i < 5; i++)
160*5c591343SA. Cody Schuffelen VERIFY(BnFromBytes(bn[i], &b->t.buffer[primeSize * i], primeSize)
161*5c591343SA. Cody Schuffelen != NULL);
162*5c591343SA. Cody Schuffelen MakePgreaterThanQ(Z);
163*5c591343SA. Cody Schuffelen return TRUE;
164*5c591343SA. Cody Schuffelen Error:
165*5c591343SA. Cody Schuffelen return FALSE;
166*5c591343SA. Cody Schuffelen }
167*5c591343SA. Cody Schuffelen
168*5c591343SA. Cody Schuffelen //*** ComputePrivateExponent()
169*5c591343SA. Cody Schuffelen // This function computes the private exponent from the primes.
170*5c591343SA. Cody Schuffelen // Return Type: BOOL
171*5c591343SA. Cody Schuffelen // TRUE(1) success
172*5c591343SA. Cody Schuffelen // FALSE(0) failure
173*5c591343SA. Cody Schuffelen static BOOL
ComputePrivateExponent(bigNum pubExp,privateExponent * Z)174*5c591343SA. Cody Schuffelen ComputePrivateExponent(
175*5c591343SA. Cody Schuffelen bigNum pubExp, // IN: the public exponent
176*5c591343SA. Cody Schuffelen privateExponent *Z // IN/OUT: on input, has primes P and Q. On
177*5c591343SA. Cody Schuffelen // output, has P, Q, dP, dQ, and pInv
178*5c591343SA. Cody Schuffelen )
179*5c591343SA. Cody Schuffelen {
180*5c591343SA. Cody Schuffelen BOOL pOK;
181*5c591343SA. Cody Schuffelen BOOL qOK;
182*5c591343SA. Cody Schuffelen BN_PRIME(pT);
183*5c591343SA. Cody Schuffelen //
184*5c591343SA. Cody Schuffelen // make p the larger value so that m2 is always less than p
185*5c591343SA. Cody Schuffelen MakePgreaterThanQ(Z);
186*5c591343SA. Cody Schuffelen
187*5c591343SA. Cody Schuffelen //dP = (1/e) mod (p-1)
188*5c591343SA. Cody Schuffelen pOK = BnSubWord(pT, Z->P, 1);
189*5c591343SA. Cody Schuffelen pOK = pOK && BnModInverse(Z->dP, pubExp, pT);
190*5c591343SA. Cody Schuffelen //dQ = (1/e) mod (q-1)
191*5c591343SA. Cody Schuffelen qOK = BnSubWord(pT, Z->Q, 1);
192*5c591343SA. Cody Schuffelen qOK = qOK && BnModInverse(Z->dQ, pubExp, pT);
193*5c591343SA. Cody Schuffelen // qInv = (1/q) mod p
194*5c591343SA. Cody Schuffelen if(pOK && qOK)
195*5c591343SA. Cody Schuffelen pOK = qOK = BnModInverse(Z->qInv, Z->Q, Z->P);
196*5c591343SA. Cody Schuffelen if(!pOK)
197*5c591343SA. Cody Schuffelen BnSetWord(Z->P, 0);
198*5c591343SA. Cody Schuffelen if(!qOK)
199*5c591343SA. Cody Schuffelen BnSetWord(Z->Q, 0);
200*5c591343SA. Cody Schuffelen return pOK && qOK;
201*5c591343SA. Cody Schuffelen }
202*5c591343SA. Cody Schuffelen
203*5c591343SA. Cody Schuffelen //*** RsaPrivateKeyOp()
204*5c591343SA. Cody Schuffelen // This function is called to do the exponentiation with the private key. Compile
205*5c591343SA. Cody Schuffelen // options allow use of the simple (but slow) private exponent, or the more complex
206*5c591343SA. Cody Schuffelen // but faster CRT method.
207*5c591343SA. Cody Schuffelen // Return Type: BOOL
208*5c591343SA. Cody Schuffelen // TRUE(1) success
209*5c591343SA. Cody Schuffelen // FALSE(0) failure
210*5c591343SA. Cody Schuffelen static BOOL
RsaPrivateKeyOp(bigNum inOut,privateExponent * Z)211*5c591343SA. Cody Schuffelen RsaPrivateKeyOp(
212*5c591343SA. Cody Schuffelen bigNum inOut, // IN/OUT: number to be exponentiated
213*5c591343SA. Cody Schuffelen privateExponent *Z
214*5c591343SA. Cody Schuffelen )
215*5c591343SA. Cody Schuffelen {
216*5c591343SA. Cody Schuffelen BN_RSA(M1);
217*5c591343SA. Cody Schuffelen BN_RSA(M2);
218*5c591343SA. Cody Schuffelen BN_RSA(M);
219*5c591343SA. Cody Schuffelen BN_RSA(H);
220*5c591343SA. Cody Schuffelen //
221*5c591343SA. Cody Schuffelen MakePgreaterThanQ(Z);
222*5c591343SA. Cody Schuffelen // m1 = cdP mod p
223*5c591343SA. Cody Schuffelen VERIFY(BnModExp(M1, inOut, Z->dP, Z->P));
224*5c591343SA. Cody Schuffelen // m2 = cdQ mod q
225*5c591343SA. Cody Schuffelen VERIFY(BnModExp(M2, inOut, Z->dQ, Z->Q));
226*5c591343SA. Cody Schuffelen // h = qInv * (m1 - m2) mod p = qInv * (m1 + P - m2) mod P because Q < P
227*5c591343SA. Cody Schuffelen // so m2 < P
228*5c591343SA. Cody Schuffelen VERIFY(BnSub(H, Z->P, M2));
229*5c591343SA. Cody Schuffelen VERIFY(BnAdd(H, H, M1));
230*5c591343SA. Cody Schuffelen VERIFY(BnModMult(H, H, Z->qInv, Z->P));
231*5c591343SA. Cody Schuffelen // m = m2 + h * q
232*5c591343SA. Cody Schuffelen VERIFY(BnMult(M, H, Z->Q));
233*5c591343SA. Cody Schuffelen VERIFY(BnAdd(inOut, M2, M));
234*5c591343SA. Cody Schuffelen return TRUE;
235*5c591343SA. Cody Schuffelen Error:
236*5c591343SA. Cody Schuffelen return FALSE;
237*5c591343SA. Cody Schuffelen }
238*5c591343SA. Cody Schuffelen
239*5c591343SA. Cody Schuffelen //*** RSAEP()
240*5c591343SA. Cody Schuffelen // This function performs the RSAEP operation defined in PKCS#1v2.1. It is
241*5c591343SA. Cody Schuffelen // an exponentiation of a value ('m') with the public exponent ('e'), modulo
242*5c591343SA. Cody Schuffelen // the public ('n').
243*5c591343SA. Cody Schuffelen //
244*5c591343SA. Cody Schuffelen // Return Type: TPM_RC
245*5c591343SA. Cody Schuffelen // TPM_RC_VALUE number to exponentiate is larger than the modulus
246*5c591343SA. Cody Schuffelen //
247*5c591343SA. Cody Schuffelen static TPM_RC
RSAEP(TPM2B * dInOut,OBJECT * key)248*5c591343SA. Cody Schuffelen RSAEP(
249*5c591343SA. Cody Schuffelen TPM2B *dInOut, // IN: size of the encrypted block and the size of
250*5c591343SA. Cody Schuffelen // the encrypted value. It must be the size of
251*5c591343SA. Cody Schuffelen // the modulus.
252*5c591343SA. Cody Schuffelen // OUT: the encrypted data. Will receive the
253*5c591343SA. Cody Schuffelen // decrypted value
254*5c591343SA. Cody Schuffelen OBJECT *key // IN: the key to use
255*5c591343SA. Cody Schuffelen )
256*5c591343SA. Cody Schuffelen {
257*5c591343SA. Cody Schuffelen TPM2B_TYPE(4BYTES, 4);
258*5c591343SA. Cody Schuffelen TPM2B_4BYTES e2B;
259*5c591343SA. Cody Schuffelen UINT32 e = key->publicArea.parameters.rsaDetail.exponent;
260*5c591343SA. Cody Schuffelen //
261*5c591343SA. Cody Schuffelen if(e == 0)
262*5c591343SA. Cody Schuffelen e = RSA_DEFAULT_PUBLIC_EXPONENT;
263*5c591343SA. Cody Schuffelen UINT32_TO_BYTE_ARRAY(e, e2B.t.buffer);
264*5c591343SA. Cody Schuffelen e2B.t.size = 4;
265*5c591343SA. Cody Schuffelen return ModExpB(dInOut->size, dInOut->buffer, dInOut->size, dInOut->buffer,
266*5c591343SA. Cody Schuffelen e2B.t.size, e2B.t.buffer, key->publicArea.unique.rsa.t.size,
267*5c591343SA. Cody Schuffelen key->publicArea.unique.rsa.t.buffer);
268*5c591343SA. Cody Schuffelen }
269*5c591343SA. Cody Schuffelen
270*5c591343SA. Cody Schuffelen //*** RSADP()
271*5c591343SA. Cody Schuffelen // This function performs the RSADP operation defined in PKCS#1v2.1. It is
272*5c591343SA. Cody Schuffelen // an exponentiation of a value ('c') with the private exponent ('d'), modulo
273*5c591343SA. Cody Schuffelen // the public modulus ('n'). The decryption is in place.
274*5c591343SA. Cody Schuffelen //
275*5c591343SA. Cody Schuffelen // This function also checks the size of the private key. If the size indicates
276*5c591343SA. Cody Schuffelen // that only a prime value is present, the key is converted to being a private
277*5c591343SA. Cody Schuffelen // exponent.
278*5c591343SA. Cody Schuffelen //
279*5c591343SA. Cody Schuffelen // Return Type: TPM_RC
280*5c591343SA. Cody Schuffelen // TPM_RC_SIZE the value to decrypt is larger than the modulus
281*5c591343SA. Cody Schuffelen //
282*5c591343SA. Cody Schuffelen static TPM_RC
RSADP(TPM2B * inOut,OBJECT * key)283*5c591343SA. Cody Schuffelen RSADP(
284*5c591343SA. Cody Schuffelen TPM2B *inOut, // IN/OUT: the value to encrypt
285*5c591343SA. Cody Schuffelen OBJECT *key // IN: the key
286*5c591343SA. Cody Schuffelen )
287*5c591343SA. Cody Schuffelen {
288*5c591343SA. Cody Schuffelen BN_RSA_INITIALIZED(bnM, inOut);
289*5c591343SA. Cody Schuffelen NEW_PRIVATE_EXPONENT(Z);
290*5c591343SA. Cody Schuffelen if(UnsignedCompareB(inOut->size, inOut->buffer,
291*5c591343SA. Cody Schuffelen key->publicArea.unique.rsa.t.size,
292*5c591343SA. Cody Schuffelen key->publicArea.unique.rsa.t.buffer) >= 0)
293*5c591343SA. Cody Schuffelen return TPM_RC_SIZE;
294*5c591343SA. Cody Schuffelen // private key operation requires that private exponent be loaded
295*5c591343SA. Cody Schuffelen // During self-test, this might not be the case so load it up if it hasn't
296*5c591343SA. Cody Schuffelen // already done
297*5c591343SA. Cody Schuffelen // been done
298*5c591343SA. Cody Schuffelen if((key->sensitive.sensitive.rsa.t.size & RSA_prime_flag) == 0)
299*5c591343SA. Cody Schuffelen {
300*5c591343SA. Cody Schuffelen if(CryptRsaLoadPrivateExponent(&key->publicArea, &key->sensitive)
301*5c591343SA. Cody Schuffelen != TPM_RC_SUCCESS)
302*5c591343SA. Cody Schuffelen return TPM_RC_BINDING;
303*5c591343SA. Cody Schuffelen }
304*5c591343SA. Cody Schuffelen VERIFY(UnpackExponent(&key->sensitive.sensitive.rsa, Z));
305*5c591343SA. Cody Schuffelen VERIFY(RsaPrivateKeyOp(bnM, Z));
306*5c591343SA. Cody Schuffelen VERIFY(BnTo2B(bnM, inOut, inOut->size));
307*5c591343SA. Cody Schuffelen return TPM_RC_SUCCESS;
308*5c591343SA. Cody Schuffelen Error:
309*5c591343SA. Cody Schuffelen return TPM_RC_FAILURE;
310*5c591343SA. Cody Schuffelen }
311*5c591343SA. Cody Schuffelen
312*5c591343SA. Cody Schuffelen //*** OaepEncode()
313*5c591343SA. Cody Schuffelen // This function performs OAEP padding. The size of the buffer to receive the
314*5c591343SA. Cody Schuffelen // OAEP padded data must equal the size of the modulus
315*5c591343SA. Cody Schuffelen //
316*5c591343SA. Cody Schuffelen // Return Type: TPM_RC
317*5c591343SA. Cody Schuffelen // TPM_RC_VALUE 'hashAlg' is not valid or message size is too large
318*5c591343SA. Cody Schuffelen //
319*5c591343SA. Cody Schuffelen static TPM_RC
OaepEncode(TPM2B * padded,TPM_ALG_ID hashAlg,const TPM2B * label,TPM2B * message,RAND_STATE * rand)320*5c591343SA. Cody Schuffelen OaepEncode(
321*5c591343SA. Cody Schuffelen TPM2B *padded, // OUT: the pad data
322*5c591343SA. Cody Schuffelen TPM_ALG_ID hashAlg, // IN: algorithm to use for padding
323*5c591343SA. Cody Schuffelen const TPM2B *label, // IN: null-terminated string (may be NULL)
324*5c591343SA. Cody Schuffelen TPM2B *message, // IN: the message being padded
325*5c591343SA. Cody Schuffelen RAND_STATE *rand // IN: the random number generator to use
326*5c591343SA. Cody Schuffelen )
327*5c591343SA. Cody Schuffelen {
328*5c591343SA. Cody Schuffelen INT32 padLen;
329*5c591343SA. Cody Schuffelen INT32 dbSize;
330*5c591343SA. Cody Schuffelen INT32 i;
331*5c591343SA. Cody Schuffelen BYTE mySeed[MAX_DIGEST_SIZE];
332*5c591343SA. Cody Schuffelen BYTE *seed = mySeed;
333*5c591343SA. Cody Schuffelen UINT16 hLen = CryptHashGetDigestSize(hashAlg);
334*5c591343SA. Cody Schuffelen BYTE mask[MAX_RSA_KEY_BYTES];
335*5c591343SA. Cody Schuffelen BYTE *pp;
336*5c591343SA. Cody Schuffelen BYTE *pm;
337*5c591343SA. Cody Schuffelen TPM_RC retVal = TPM_RC_SUCCESS;
338*5c591343SA. Cody Schuffelen
339*5c591343SA. Cody Schuffelen pAssert(padded != NULL && message != NULL);
340*5c591343SA. Cody Schuffelen
341*5c591343SA. Cody Schuffelen // A value of zero is not allowed because the KDF can't produce a result
342*5c591343SA. Cody Schuffelen // if the digest size is zero.
343*5c591343SA. Cody Schuffelen if(hLen == 0)
344*5c591343SA. Cody Schuffelen return TPM_RC_VALUE;
345*5c591343SA. Cody Schuffelen
346*5c591343SA. Cody Schuffelen // Basic size checks
347*5c591343SA. Cody Schuffelen // make sure digest isn't too big for key size
348*5c591343SA. Cody Schuffelen if(padded->size < (2 * hLen) + 2)
349*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_HASH);
350*5c591343SA. Cody Schuffelen
351*5c591343SA. Cody Schuffelen // and that message will fit messageSize <= k - 2hLen - 2
352*5c591343SA. Cody Schuffelen if(message->size > (padded->size - (2 * hLen) - 2))
353*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_VALUE);
354*5c591343SA. Cody Schuffelen
355*5c591343SA. Cody Schuffelen // Hash L even if it is null
356*5c591343SA. Cody Schuffelen // Offset into padded leaving room for masked seed and byte of zero
357*5c591343SA. Cody Schuffelen pp = &padded->buffer[hLen + 1];
358*5c591343SA. Cody Schuffelen if(CryptHashBlock(hashAlg, label->size, (BYTE *)label->buffer,
359*5c591343SA. Cody Schuffelen hLen, pp) != hLen)
360*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_FAILURE);
361*5c591343SA. Cody Schuffelen
362*5c591343SA. Cody Schuffelen // concatenate PS of k mLen 2hLen 2
363*5c591343SA. Cody Schuffelen padLen = padded->size - message->size - (2 * hLen) - 2;
364*5c591343SA. Cody Schuffelen MemorySet(&pp[hLen], 0, padLen);
365*5c591343SA. Cody Schuffelen pp[hLen + padLen] = 0x01;
366*5c591343SA. Cody Schuffelen padLen += 1;
367*5c591343SA. Cody Schuffelen memcpy(&pp[hLen + padLen], message->buffer, message->size);
368*5c591343SA. Cody Schuffelen
369*5c591343SA. Cody Schuffelen // The total size of db = hLen + pad + mSize;
370*5c591343SA. Cody Schuffelen dbSize = hLen + padLen + message->size;
371*5c591343SA. Cody Schuffelen
372*5c591343SA. Cody Schuffelen // If testing, then use the provided seed. Otherwise, use values
373*5c591343SA. Cody Schuffelen // from the RNG
374*5c591343SA. Cody Schuffelen CryptRandomGenerate(hLen, mySeed);
375*5c591343SA. Cody Schuffelen DRBG_Generate(rand, mySeed, (UINT16)hLen);
376*5c591343SA. Cody Schuffelen if(g_inFailureMode)
377*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_FAILURE);
378*5c591343SA. Cody Schuffelen // mask = MGF1 (seed, nSize hLen 1)
379*5c591343SA. Cody Schuffelen CryptMGF_KDF(dbSize, mask, hashAlg, hLen, seed, 0);
380*5c591343SA. Cody Schuffelen
381*5c591343SA. Cody Schuffelen // Create the masked db
382*5c591343SA. Cody Schuffelen pm = mask;
383*5c591343SA. Cody Schuffelen for(i = dbSize; i > 0; i--)
384*5c591343SA. Cody Schuffelen *pp++ ^= *pm++;
385*5c591343SA. Cody Schuffelen pp = &padded->buffer[hLen + 1];
386*5c591343SA. Cody Schuffelen
387*5c591343SA. Cody Schuffelen // Run the masked data through MGF1
388*5c591343SA. Cody Schuffelen if(CryptMGF_KDF(hLen, &padded->buffer[1], hashAlg, dbSize, pp, 0) != (unsigned)hLen)
389*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_VALUE);
390*5c591343SA. Cody Schuffelen // Now XOR the seed to create masked seed
391*5c591343SA. Cody Schuffelen pp = &padded->buffer[1];
392*5c591343SA. Cody Schuffelen pm = seed;
393*5c591343SA. Cody Schuffelen for(i = hLen; i > 0; i--)
394*5c591343SA. Cody Schuffelen *pp++ ^= *pm++;
395*5c591343SA. Cody Schuffelen // Set the first byte to zero
396*5c591343SA. Cody Schuffelen padded->buffer[0] = 0x00;
397*5c591343SA. Cody Schuffelen Exit:
398*5c591343SA. Cody Schuffelen return retVal;
399*5c591343SA. Cody Schuffelen }
400*5c591343SA. Cody Schuffelen
401*5c591343SA. Cody Schuffelen //*** OaepDecode()
402*5c591343SA. Cody Schuffelen // This function performs OAEP padding checking. The size of the buffer to receive
403*5c591343SA. Cody Schuffelen // the recovered data. If the padding is not valid, the 'dSize' size is set to zero
404*5c591343SA. Cody Schuffelen // and the function returns TPM_RC_VALUE.
405*5c591343SA. Cody Schuffelen //
406*5c591343SA. Cody Schuffelen // The 'dSize' parameter is used as an input to indicate the size available in the
407*5c591343SA. Cody Schuffelen // buffer.
408*5c591343SA. Cody Schuffelen
409*5c591343SA. Cody Schuffelen // If insufficient space is available, the size is not changed and the return code
410*5c591343SA. Cody Schuffelen // is TPM_RC_VALUE.
411*5c591343SA. Cody Schuffelen //
412*5c591343SA. Cody Schuffelen // Return Type: TPM_RC
413*5c591343SA. Cody Schuffelen // TPM_RC_VALUE the value to decode was larger than the modulus, or
414*5c591343SA. Cody Schuffelen // the padding is wrong or the buffer to receive the
415*5c591343SA. Cody Schuffelen // results is too small
416*5c591343SA. Cody Schuffelen //
417*5c591343SA. Cody Schuffelen //
418*5c591343SA. Cody Schuffelen static TPM_RC
OaepDecode(TPM2B * dataOut,TPM_ALG_ID hashAlg,const TPM2B * label,TPM2B * padded)419*5c591343SA. Cody Schuffelen OaepDecode(
420*5c591343SA. Cody Schuffelen TPM2B *dataOut, // OUT: the recovered data
421*5c591343SA. Cody Schuffelen TPM_ALG_ID hashAlg, // IN: algorithm to use for padding
422*5c591343SA. Cody Schuffelen const TPM2B *label, // IN: null-terminated string (may be NULL)
423*5c591343SA. Cody Schuffelen TPM2B *padded // IN: the padded data
424*5c591343SA. Cody Schuffelen )
425*5c591343SA. Cody Schuffelen {
426*5c591343SA. Cody Schuffelen UINT32 i;
427*5c591343SA. Cody Schuffelen BYTE seedMask[MAX_DIGEST_SIZE];
428*5c591343SA. Cody Schuffelen UINT32 hLen = CryptHashGetDigestSize(hashAlg);
429*5c591343SA. Cody Schuffelen
430*5c591343SA. Cody Schuffelen BYTE mask[MAX_RSA_KEY_BYTES];
431*5c591343SA. Cody Schuffelen BYTE *pp;
432*5c591343SA. Cody Schuffelen BYTE *pm;
433*5c591343SA. Cody Schuffelen TPM_RC retVal = TPM_RC_SUCCESS;
434*5c591343SA. Cody Schuffelen
435*5c591343SA. Cody Schuffelen // Strange size (anything smaller can't be an OAEP padded block)
436*5c591343SA. Cody Schuffelen // Also check for no leading 0
437*5c591343SA. Cody Schuffelen if((padded->size < (unsigned)((2 * hLen) + 2)) || (padded->buffer[0] != 0))
438*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_VALUE);
439*5c591343SA. Cody Schuffelen // Use the hash size to determine what to put through MGF1 in order
440*5c591343SA. Cody Schuffelen // to recover the seedMask
441*5c591343SA. Cody Schuffelen CryptMGF_KDF(hLen, seedMask, hashAlg, padded->size - hLen - 1,
442*5c591343SA. Cody Schuffelen &padded->buffer[hLen + 1], 0);
443*5c591343SA. Cody Schuffelen
444*5c591343SA. Cody Schuffelen // Recover the seed into seedMask
445*5c591343SA. Cody Schuffelen pAssert(hLen <= sizeof(seedMask));
446*5c591343SA. Cody Schuffelen pp = &padded->buffer[1];
447*5c591343SA. Cody Schuffelen pm = seedMask;
448*5c591343SA. Cody Schuffelen for(i = hLen; i > 0; i--)
449*5c591343SA. Cody Schuffelen *pm++ ^= *pp++;
450*5c591343SA. Cody Schuffelen
451*5c591343SA. Cody Schuffelen // Use the seed to generate the data mask
452*5c591343SA. Cody Schuffelen CryptMGF_KDF(padded->size - hLen - 1, mask, hashAlg, hLen, seedMask, 0);
453*5c591343SA. Cody Schuffelen
454*5c591343SA. Cody Schuffelen // Use the mask generated from seed to recover the padded data
455*5c591343SA. Cody Schuffelen pp = &padded->buffer[hLen + 1];
456*5c591343SA. Cody Schuffelen pm = mask;
457*5c591343SA. Cody Schuffelen for(i = (padded->size - hLen - 1); i > 0; i--)
458*5c591343SA. Cody Schuffelen *pm++ ^= *pp++;
459*5c591343SA. Cody Schuffelen
460*5c591343SA. Cody Schuffelen // Make sure that the recovered data has the hash of the label
461*5c591343SA. Cody Schuffelen // Put trial value in the seed mask
462*5c591343SA. Cody Schuffelen if((CryptHashBlock(hashAlg, label->size, (BYTE *)label->buffer,
463*5c591343SA. Cody Schuffelen hLen, seedMask)) != hLen)
464*5c591343SA. Cody Schuffelen FAIL(FATAL_ERROR_INTERNAL);
465*5c591343SA. Cody Schuffelen if(memcmp(seedMask, mask, hLen) != 0)
466*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_VALUE);
467*5c591343SA. Cody Schuffelen
468*5c591343SA. Cody Schuffelen // find the start of the data
469*5c591343SA. Cody Schuffelen pm = &mask[hLen];
470*5c591343SA. Cody Schuffelen for(i = (UINT32)padded->size - (2 * hLen) - 1; i > 0; i--)
471*5c591343SA. Cody Schuffelen {
472*5c591343SA. Cody Schuffelen if(*pm++ != 0)
473*5c591343SA. Cody Schuffelen break;
474*5c591343SA. Cody Schuffelen }
475*5c591343SA. Cody Schuffelen // If we ran out of data or didn't end with 0x01, then return an error
476*5c591343SA. Cody Schuffelen if(i == 0 || pm[-1] != 0x01)
477*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_VALUE);
478*5c591343SA. Cody Schuffelen
479*5c591343SA. Cody Schuffelen // pm should be pointing at the first part of the data
480*5c591343SA. Cody Schuffelen // and i is one greater than the number of bytes to move
481*5c591343SA. Cody Schuffelen i--;
482*5c591343SA. Cody Schuffelen if(i > dataOut->size)
483*5c591343SA. Cody Schuffelen // Special exit to preserve the size of the output buffer
484*5c591343SA. Cody Schuffelen return TPM_RC_VALUE;
485*5c591343SA. Cody Schuffelen memcpy(dataOut->buffer, pm, i);
486*5c591343SA. Cody Schuffelen dataOut->size = (UINT16)i;
487*5c591343SA. Cody Schuffelen Exit:
488*5c591343SA. Cody Schuffelen if(retVal != TPM_RC_SUCCESS)
489*5c591343SA. Cody Schuffelen dataOut->size = 0;
490*5c591343SA. Cody Schuffelen return retVal;
491*5c591343SA. Cody Schuffelen }
492*5c591343SA. Cody Schuffelen
493*5c591343SA. Cody Schuffelen //*** PKCS1v1_5Encode()
494*5c591343SA. Cody Schuffelen // This function performs the encoding for RSAES-PKCS1-V1_5-ENCRYPT as defined in
495*5c591343SA. Cody Schuffelen // PKCS#1V2.1
496*5c591343SA. Cody Schuffelen // Return Type: TPM_RC
497*5c591343SA. Cody Schuffelen // TPM_RC_VALUE message size is too large
498*5c591343SA. Cody Schuffelen //
499*5c591343SA. Cody Schuffelen static TPM_RC
RSAES_PKCS1v1_5Encode(TPM2B * padded,TPM2B * message,RAND_STATE * rand)500*5c591343SA. Cody Schuffelen RSAES_PKCS1v1_5Encode(
501*5c591343SA. Cody Schuffelen TPM2B *padded, // OUT: the pad data
502*5c591343SA. Cody Schuffelen TPM2B *message, // IN: the message being padded
503*5c591343SA. Cody Schuffelen RAND_STATE *rand
504*5c591343SA. Cody Schuffelen )
505*5c591343SA. Cody Schuffelen {
506*5c591343SA. Cody Schuffelen UINT32 ps = padded->size - message->size - 3;
507*5c591343SA. Cody Schuffelen //
508*5c591343SA. Cody Schuffelen if(message->size > padded->size - 11)
509*5c591343SA. Cody Schuffelen return TPM_RC_VALUE;
510*5c591343SA. Cody Schuffelen // move the message to the end of the buffer
511*5c591343SA. Cody Schuffelen memcpy(&padded->buffer[padded->size - message->size], message->buffer,
512*5c591343SA. Cody Schuffelen message->size);
513*5c591343SA. Cody Schuffelen // Set the first byte to 0x00 and the second to 0x02
514*5c591343SA. Cody Schuffelen padded->buffer[0] = 0;
515*5c591343SA. Cody Schuffelen padded->buffer[1] = 2;
516*5c591343SA. Cody Schuffelen
517*5c591343SA. Cody Schuffelen // Fill with random bytes
518*5c591343SA. Cody Schuffelen DRBG_Generate(rand, &padded->buffer[2], (UINT16)ps);
519*5c591343SA. Cody Schuffelen if(g_inFailureMode)
520*5c591343SA. Cody Schuffelen return TPM_RC_FAILURE;
521*5c591343SA. Cody Schuffelen
522*5c591343SA. Cody Schuffelen // Set the delimiter for the random field to 0
523*5c591343SA. Cody Schuffelen padded->buffer[2 + ps] = 0;
524*5c591343SA. Cody Schuffelen
525*5c591343SA. Cody Schuffelen // Now, the only messy part. Make sure that all the 'ps' bytes are non-zero
526*5c591343SA. Cody Schuffelen // In this implementation, use the value of the current index
527*5c591343SA. Cody Schuffelen for(ps++; ps > 1; ps--)
528*5c591343SA. Cody Schuffelen {
529*5c591343SA. Cody Schuffelen if(padded->buffer[ps] == 0)
530*5c591343SA. Cody Schuffelen padded->buffer[ps] = 0x55; // In the < 0.5% of the cases that the
531*5c591343SA. Cody Schuffelen // random value is 0, just pick a value to
532*5c591343SA. Cody Schuffelen // put into the spot.
533*5c591343SA. Cody Schuffelen }
534*5c591343SA. Cody Schuffelen return TPM_RC_SUCCESS;
535*5c591343SA. Cody Schuffelen }
536*5c591343SA. Cody Schuffelen
537*5c591343SA. Cody Schuffelen //*** RSAES_Decode()
538*5c591343SA. Cody Schuffelen // This function performs the decoding for RSAES-PKCS1-V1_5-ENCRYPT as defined in
539*5c591343SA. Cody Schuffelen // PKCS#1V2.1
540*5c591343SA. Cody Schuffelen //
541*5c591343SA. Cody Schuffelen // Return Type: TPM_RC
542*5c591343SA. Cody Schuffelen // TPM_RC_FAIL decoding error or results would no fit into provided buffer
543*5c591343SA. Cody Schuffelen //
544*5c591343SA. Cody Schuffelen static TPM_RC
RSAES_Decode(TPM2B * message,TPM2B * coded)545*5c591343SA. Cody Schuffelen RSAES_Decode(
546*5c591343SA. Cody Schuffelen TPM2B *message, // OUT: the recovered message
547*5c591343SA. Cody Schuffelen TPM2B *coded // IN: the encoded message
548*5c591343SA. Cody Schuffelen )
549*5c591343SA. Cody Schuffelen {
550*5c591343SA. Cody Schuffelen BOOL fail = FALSE;
551*5c591343SA. Cody Schuffelen UINT16 pSize;
552*5c591343SA. Cody Schuffelen
553*5c591343SA. Cody Schuffelen fail = (coded->size < 11);
554*5c591343SA. Cody Schuffelen fail = (coded->buffer[0] != 0x00) | fail;
555*5c591343SA. Cody Schuffelen fail = (coded->buffer[1] != 0x02) | fail;
556*5c591343SA. Cody Schuffelen for(pSize = 2; pSize < coded->size; pSize++)
557*5c591343SA. Cody Schuffelen {
558*5c591343SA. Cody Schuffelen if(coded->buffer[pSize] == 0)
559*5c591343SA. Cody Schuffelen break;
560*5c591343SA. Cody Schuffelen }
561*5c591343SA. Cody Schuffelen pSize++;
562*5c591343SA. Cody Schuffelen
563*5c591343SA. Cody Schuffelen // Make sure that pSize has not gone over the end and that there are at least 8
564*5c591343SA. Cody Schuffelen // bytes of pad data.
565*5c591343SA. Cody Schuffelen fail = (pSize > coded->size) | fail;
566*5c591343SA. Cody Schuffelen fail = ((pSize - 2) <= 8) | fail;
567*5c591343SA. Cody Schuffelen if((message->size < (UINT16)(coded->size - pSize)) || fail)
568*5c591343SA. Cody Schuffelen return TPM_RC_VALUE;
569*5c591343SA. Cody Schuffelen message->size = coded->size - pSize;
570*5c591343SA. Cody Schuffelen memcpy(message->buffer, &coded->buffer[pSize], coded->size - pSize);
571*5c591343SA. Cody Schuffelen return TPM_RC_SUCCESS;
572*5c591343SA. Cody Schuffelen }
573*5c591343SA. Cody Schuffelen
574*5c591343SA. Cody Schuffelen //*** CryptRsaPssSaltSize()
575*5c591343SA. Cody Schuffelen // This function computes the salt size used in PSS. It is broken out so that
576*5c591343SA. Cody Schuffelen // the X509 code can get the same value that is used by the encoding function in this
577*5c591343SA. Cody Schuffelen // module.
578*5c591343SA. Cody Schuffelen INT16
CryptRsaPssSaltSize(INT16 hashSize,INT16 outSize)579*5c591343SA. Cody Schuffelen CryptRsaPssSaltSize(
580*5c591343SA. Cody Schuffelen INT16 hashSize,
581*5c591343SA. Cody Schuffelen INT16 outSize
582*5c591343SA. Cody Schuffelen )
583*5c591343SA. Cody Schuffelen {
584*5c591343SA. Cody Schuffelen INT16 saltSize;
585*5c591343SA. Cody Schuffelen //
586*5c591343SA. Cody Schuffelen // (Mask Length) = (outSize - hashSize - 1);
587*5c591343SA. Cody Schuffelen // Max saltSize is (Mask Length) - 1
588*5c591343SA. Cody Schuffelen saltSize = (outSize - hashSize - 1) - 1;
589*5c591343SA. Cody Schuffelen // Use the maximum salt size allowed by FIPS 186-4
590*5c591343SA. Cody Schuffelen if(saltSize > hashSize)
591*5c591343SA. Cody Schuffelen saltSize = hashSize;
592*5c591343SA. Cody Schuffelen else if(saltSize < 0)
593*5c591343SA. Cody Schuffelen saltSize = 0;
594*5c591343SA. Cody Schuffelen return saltSize;
595*5c591343SA. Cody Schuffelen }
596*5c591343SA. Cody Schuffelen
597*5c591343SA. Cody Schuffelen //*** PssEncode()
598*5c591343SA. Cody Schuffelen // This function creates an encoded block of data that is the size of modulus.
599*5c591343SA. Cody Schuffelen // The function uses the maximum salt size that will fit in the encoded block.
600*5c591343SA. Cody Schuffelen //
601*5c591343SA. Cody Schuffelen // Returns TPM_RC_SUCCESS or goes into failure mode.
602*5c591343SA. Cody Schuffelen static TPM_RC
PssEncode(TPM2B * out,TPM_ALG_ID hashAlg,TPM2B * digest,RAND_STATE * rand)603*5c591343SA. Cody Schuffelen PssEncode(
604*5c591343SA. Cody Schuffelen TPM2B *out, // OUT: the encoded buffer
605*5c591343SA. Cody Schuffelen TPM_ALG_ID hashAlg, // IN: hash algorithm for the encoding
606*5c591343SA. Cody Schuffelen TPM2B *digest, // IN: the digest
607*5c591343SA. Cody Schuffelen RAND_STATE *rand // IN: random number source
608*5c591343SA. Cody Schuffelen )
609*5c591343SA. Cody Schuffelen {
610*5c591343SA. Cody Schuffelen UINT32 hLen = CryptHashGetDigestSize(hashAlg);
611*5c591343SA. Cody Schuffelen BYTE salt[MAX_RSA_KEY_BYTES - 1];
612*5c591343SA. Cody Schuffelen UINT16 saltSize;
613*5c591343SA. Cody Schuffelen BYTE *ps = salt;
614*5c591343SA. Cody Schuffelen BYTE *pOut;
615*5c591343SA. Cody Schuffelen UINT16 mLen;
616*5c591343SA. Cody Schuffelen HASH_STATE hashState;
617*5c591343SA. Cody Schuffelen
618*5c591343SA. Cody Schuffelen // These are fatal errors indicating bad TPM firmware
619*5c591343SA. Cody Schuffelen pAssert(out != NULL && hLen > 0 && digest != NULL);
620*5c591343SA. Cody Schuffelen
621*5c591343SA. Cody Schuffelen // Get the size of the mask
622*5c591343SA. Cody Schuffelen mLen = (UINT16)(out->size - hLen - 1);
623*5c591343SA. Cody Schuffelen
624*5c591343SA. Cody Schuffelen // Set the salt size
625*5c591343SA. Cody Schuffelen saltSize = CryptRsaPssSaltSize((INT16)hLen, (INT16)out->size);
626*5c591343SA. Cody Schuffelen
627*5c591343SA. Cody Schuffelen //using eOut for scratch space
628*5c591343SA. Cody Schuffelen // Set the first 8 bytes to zero
629*5c591343SA. Cody Schuffelen pOut = out->buffer;
630*5c591343SA. Cody Schuffelen memset(pOut, 0, 8);
631*5c591343SA. Cody Schuffelen
632*5c591343SA. Cody Schuffelen // Get set the salt
633*5c591343SA. Cody Schuffelen DRBG_Generate(rand, salt, saltSize);
634*5c591343SA. Cody Schuffelen if(g_inFailureMode)
635*5c591343SA. Cody Schuffelen return TPM_RC_FAILURE;
636*5c591343SA. Cody Schuffelen
637*5c591343SA. Cody Schuffelen // Create the hash of the pad || input hash || salt
638*5c591343SA. Cody Schuffelen CryptHashStart(&hashState, hashAlg);
639*5c591343SA. Cody Schuffelen CryptDigestUpdate(&hashState, 8, pOut);
640*5c591343SA. Cody Schuffelen CryptDigestUpdate2B(&hashState, digest);
641*5c591343SA. Cody Schuffelen CryptDigestUpdate(&hashState, saltSize, salt);
642*5c591343SA. Cody Schuffelen CryptHashEnd(&hashState, hLen, &pOut[out->size - hLen - 1]);
643*5c591343SA. Cody Schuffelen
644*5c591343SA. Cody Schuffelen // Create a mask
645*5c591343SA. Cody Schuffelen if(CryptMGF_KDF(mLen, pOut, hashAlg, hLen, &pOut[mLen], 0) != mLen)
646*5c591343SA. Cody Schuffelen FAIL(FATAL_ERROR_INTERNAL);
647*5c591343SA. Cody Schuffelen
648*5c591343SA. Cody Schuffelen // Since this implementation uses key sizes that are all even multiples of
649*5c591343SA. Cody Schuffelen // 8, just need to make sure that the most significant bit is CLEAR
650*5c591343SA. Cody Schuffelen *pOut &= 0x7f;
651*5c591343SA. Cody Schuffelen
652*5c591343SA. Cody Schuffelen // Before we mess up the pOut value, set the last byte to 0xbc
653*5c591343SA. Cody Schuffelen pOut[out->size - 1] = 0xbc;
654*5c591343SA. Cody Schuffelen
655*5c591343SA. Cody Schuffelen // XOR a byte of 0x01 at the position just before where the salt will be XOR'ed
656*5c591343SA. Cody Schuffelen pOut = &pOut[mLen - saltSize - 1];
657*5c591343SA. Cody Schuffelen *pOut++ ^= 0x01;
658*5c591343SA. Cody Schuffelen
659*5c591343SA. Cody Schuffelen // XOR the salt data into the buffer
660*5c591343SA. Cody Schuffelen for(; saltSize > 0; saltSize--)
661*5c591343SA. Cody Schuffelen *pOut++ ^= *ps++;
662*5c591343SA. Cody Schuffelen
663*5c591343SA. Cody Schuffelen // and we are done
664*5c591343SA. Cody Schuffelen return TPM_RC_SUCCESS;
665*5c591343SA. Cody Schuffelen }
666*5c591343SA. Cody Schuffelen
667*5c591343SA. Cody Schuffelen //*** PssDecode()
668*5c591343SA. Cody Schuffelen // This function checks that the PSS encoded block was built from the
669*5c591343SA. Cody Schuffelen // provided digest. If the check is successful, TPM_RC_SUCCESS is returned.
670*5c591343SA. Cody Schuffelen // Any other value indicates an error.
671*5c591343SA. Cody Schuffelen //
672*5c591343SA. Cody Schuffelen // This implementation of PSS decoding is intended for the reference TPM
673*5c591343SA. Cody Schuffelen // implementation and is not at all generalized. It is used to check
674*5c591343SA. Cody Schuffelen // signatures over hashes and assumptions are made about the sizes of values.
675*5c591343SA. Cody Schuffelen // Those assumptions are enforce by this implementation.
676*5c591343SA. Cody Schuffelen // This implementation does allow for a variable size salt value to have been
677*5c591343SA. Cody Schuffelen // used by the creator of the signature.
678*5c591343SA. Cody Schuffelen //
679*5c591343SA. Cody Schuffelen // Return Type: TPM_RC
680*5c591343SA. Cody Schuffelen // TPM_RC_SCHEME 'hashAlg' is not a supported hash algorithm
681*5c591343SA. Cody Schuffelen // TPM_RC_VALUE decode operation failed
682*5c591343SA. Cody Schuffelen //
683*5c591343SA. Cody Schuffelen static TPM_RC
PssDecode(TPM_ALG_ID hashAlg,TPM2B * dIn,TPM2B * eIn)684*5c591343SA. Cody Schuffelen PssDecode(
685*5c591343SA. Cody Schuffelen TPM_ALG_ID hashAlg, // IN: hash algorithm to use for the encoding
686*5c591343SA. Cody Schuffelen TPM2B *dIn, // In: the digest to compare
687*5c591343SA. Cody Schuffelen TPM2B *eIn // IN: the encoded data
688*5c591343SA. Cody Schuffelen )
689*5c591343SA. Cody Schuffelen {
690*5c591343SA. Cody Schuffelen UINT32 hLen = CryptHashGetDigestSize(hashAlg);
691*5c591343SA. Cody Schuffelen BYTE mask[MAX_RSA_KEY_BYTES];
692*5c591343SA. Cody Schuffelen BYTE *pm = mask;
693*5c591343SA. Cody Schuffelen BYTE *pe;
694*5c591343SA. Cody Schuffelen BYTE pad[8] = {0};
695*5c591343SA. Cody Schuffelen UINT32 i;
696*5c591343SA. Cody Schuffelen UINT32 mLen;
697*5c591343SA. Cody Schuffelen BYTE fail;
698*5c591343SA. Cody Schuffelen TPM_RC retVal = TPM_RC_SUCCESS;
699*5c591343SA. Cody Schuffelen HASH_STATE hashState;
700*5c591343SA. Cody Schuffelen
701*5c591343SA. Cody Schuffelen // These errors are indicative of failures due to programmer error
702*5c591343SA. Cody Schuffelen pAssert(dIn != NULL && eIn != NULL);
703*5c591343SA. Cody Schuffelen pe = eIn->buffer;
704*5c591343SA. Cody Schuffelen
705*5c591343SA. Cody Schuffelen // check the hash scheme
706*5c591343SA. Cody Schuffelen if(hLen == 0)
707*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_SCHEME);
708*5c591343SA. Cody Schuffelen
709*5c591343SA. Cody Schuffelen // most significant bit must be zero
710*5c591343SA. Cody Schuffelen fail = pe[0] & 0x80;
711*5c591343SA. Cody Schuffelen
712*5c591343SA. Cody Schuffelen // last byte must be 0xbc
713*5c591343SA. Cody Schuffelen fail |= pe[eIn->size - 1] ^ 0xbc;
714*5c591343SA. Cody Schuffelen
715*5c591343SA. Cody Schuffelen // Use the hLen bytes at the end of the buffer to generate a mask
716*5c591343SA. Cody Schuffelen // Doesn't start at the end which is a flag byte
717*5c591343SA. Cody Schuffelen mLen = eIn->size - hLen - 1;
718*5c591343SA. Cody Schuffelen CryptMGF_KDF(mLen, mask, hashAlg, hLen, &pe[mLen], 0);
719*5c591343SA. Cody Schuffelen
720*5c591343SA. Cody Schuffelen // Clear the MSO of the mask to make it consistent with the encoding.
721*5c591343SA. Cody Schuffelen mask[0] &= 0x7F;
722*5c591343SA. Cody Schuffelen
723*5c591343SA. Cody Schuffelen pAssert(mLen <= sizeof(mask));
724*5c591343SA. Cody Schuffelen // XOR the data into the mask to recover the salt. This sequence
725*5c591343SA. Cody Schuffelen // advances eIn so that it will end up pointing to the seed data
726*5c591343SA. Cody Schuffelen // which is the hash of the signature data
727*5c591343SA. Cody Schuffelen for(i = mLen; i > 0; i--)
728*5c591343SA. Cody Schuffelen *pm++ ^= *pe++;
729*5c591343SA. Cody Schuffelen
730*5c591343SA. Cody Schuffelen // Find the first byte of 0x01 after a string of all 0x00
731*5c591343SA. Cody Schuffelen for(pm = mask, i = mLen; i > 0; i--)
732*5c591343SA. Cody Schuffelen {
733*5c591343SA. Cody Schuffelen if(*pm == 0x01)
734*5c591343SA. Cody Schuffelen break;
735*5c591343SA. Cody Schuffelen else
736*5c591343SA. Cody Schuffelen fail |= *pm++;
737*5c591343SA. Cody Schuffelen }
738*5c591343SA. Cody Schuffelen // i should not be zero
739*5c591343SA. Cody Schuffelen fail |= (i == 0);
740*5c591343SA. Cody Schuffelen
741*5c591343SA. Cody Schuffelen // if we have failed, will continue using the entire mask as the salt value so
742*5c591343SA. Cody Schuffelen // that the timing attacks will not disclose anything (I don't think that this
743*5c591343SA. Cody Schuffelen // is a problem for TPM applications but, usually, we don't fail so this
744*5c591343SA. Cody Schuffelen // doesn't cost anything).
745*5c591343SA. Cody Schuffelen if(fail)
746*5c591343SA. Cody Schuffelen {
747*5c591343SA. Cody Schuffelen i = mLen;
748*5c591343SA. Cody Schuffelen pm = mask;
749*5c591343SA. Cody Schuffelen }
750*5c591343SA. Cody Schuffelen else
751*5c591343SA. Cody Schuffelen {
752*5c591343SA. Cody Schuffelen pm++;
753*5c591343SA. Cody Schuffelen i--;
754*5c591343SA. Cody Schuffelen }
755*5c591343SA. Cody Schuffelen // i contains the salt size and pm points to the salt. Going to use the input
756*5c591343SA. Cody Schuffelen // hash and the seed to recreate the hash in the lower portion of eIn.
757*5c591343SA. Cody Schuffelen CryptHashStart(&hashState, hashAlg);
758*5c591343SA. Cody Schuffelen
759*5c591343SA. Cody Schuffelen // add the pad of 8 zeros
760*5c591343SA. Cody Schuffelen CryptDigestUpdate(&hashState, 8, pad);
761*5c591343SA. Cody Schuffelen
762*5c591343SA. Cody Schuffelen // add the provided digest value
763*5c591343SA. Cody Schuffelen CryptDigestUpdate(&hashState, dIn->size, dIn->buffer);
764*5c591343SA. Cody Schuffelen
765*5c591343SA. Cody Schuffelen // and the salt
766*5c591343SA. Cody Schuffelen CryptDigestUpdate(&hashState, i, pm);
767*5c591343SA. Cody Schuffelen
768*5c591343SA. Cody Schuffelen // get the result
769*5c591343SA. Cody Schuffelen fail |= (CryptHashEnd(&hashState, hLen, mask) != hLen);
770*5c591343SA. Cody Schuffelen
771*5c591343SA. Cody Schuffelen // Compare all bytes
772*5c591343SA. Cody Schuffelen for(pm = mask; hLen > 0; hLen--)
773*5c591343SA. Cody Schuffelen // don't use fail = because that could skip the increment and compare
774*5c591343SA. Cody Schuffelen // operations after the first failure and that gives away timing
775*5c591343SA. Cody Schuffelen // information.
776*5c591343SA. Cody Schuffelen fail |= *pm++ ^ *pe++;
777*5c591343SA. Cody Schuffelen
778*5c591343SA. Cody Schuffelen retVal = (fail != 0) ? TPM_RC_VALUE : TPM_RC_SUCCESS;
779*5c591343SA. Cody Schuffelen Exit:
780*5c591343SA. Cody Schuffelen return retVal;
781*5c591343SA. Cody Schuffelen }
782*5c591343SA. Cody Schuffelen
783*5c591343SA. Cody Schuffelen //*** MakeDerTag()
784*5c591343SA. Cody Schuffelen // Construct the DER value that is used in RSASSA
785*5c591343SA. Cody Schuffelen // Return Type: INT16
786*5c591343SA. Cody Schuffelen // > 0 size of value
787*5c591343SA. Cody Schuffelen // <= 0 no hash exists
788*5c591343SA. Cody Schuffelen INT16
MakeDerTag(TPM_ALG_ID hashAlg,INT16 sizeOfBuffer,BYTE * buffer)789*5c591343SA. Cody Schuffelen MakeDerTag(
790*5c591343SA. Cody Schuffelen TPM_ALG_ID hashAlg,
791*5c591343SA. Cody Schuffelen INT16 sizeOfBuffer,
792*5c591343SA. Cody Schuffelen BYTE *buffer
793*5c591343SA. Cody Schuffelen )
794*5c591343SA. Cody Schuffelen {
795*5c591343SA. Cody Schuffelen // 0x30, 0x31, // SEQUENCE (2 elements) 1st
796*5c591343SA. Cody Schuffelen // 0x30, 0x0D, // SEQUENCE (2 elements)
797*5c591343SA. Cody Schuffelen // 0x06, 0x09, // HASH OID
798*5c591343SA. Cody Schuffelen // 0x60, 0x86, 0x48, 0x01, 0x65, 0x03, 0x04, 0x02, 0x01,
799*5c591343SA. Cody Schuffelen // 0x05, 0x00, // NULL
800*5c591343SA. Cody Schuffelen // 0x04, 0x20 // OCTET STRING
801*5c591343SA. Cody Schuffelen HASH_DEF *info = CryptGetHashDef(hashAlg);
802*5c591343SA. Cody Schuffelen INT16 oidSize;
803*5c591343SA. Cody Schuffelen // If no OID, can't do encode
804*5c591343SA. Cody Schuffelen VERIFY(info != NULL);
805*5c591343SA. Cody Schuffelen oidSize = 2 + (info->OID)[1];
806*5c591343SA. Cody Schuffelen // make sure this fits in the buffer
807*5c591343SA. Cody Schuffelen VERIFY(sizeOfBuffer >= (oidSize + 8));
808*5c591343SA. Cody Schuffelen *buffer++ = 0x30; // 1st SEQUENCE
809*5c591343SA. Cody Schuffelen // Size of the 1st SEQUENCE is 6 bytes + size of the hash OID + size of the
810*5c591343SA. Cody Schuffelen // digest size
811*5c591343SA. Cody Schuffelen *buffer++ = (BYTE)(6 + oidSize + info->digestSize); //
812*5c591343SA. Cody Schuffelen *buffer++ = 0x30; // 2nd SEQUENCE
813*5c591343SA. Cody Schuffelen // size is 4 bytes of overhead plus the side of the OID
814*5c591343SA. Cody Schuffelen *buffer++ = (BYTE)(2 + oidSize);
815*5c591343SA. Cody Schuffelen MemoryCopy(buffer, info->OID, oidSize);
816*5c591343SA. Cody Schuffelen buffer += oidSize;
817*5c591343SA. Cody Schuffelen *buffer++ = 0x05; // Add a NULL
818*5c591343SA. Cody Schuffelen *buffer++ = 0x00;
819*5c591343SA. Cody Schuffelen
820*5c591343SA. Cody Schuffelen *buffer++ = 0x04;
821*5c591343SA. Cody Schuffelen *buffer++ = (BYTE)(info->digestSize);
822*5c591343SA. Cody Schuffelen return oidSize + 8;
823*5c591343SA. Cody Schuffelen Error:
824*5c591343SA. Cody Schuffelen return 0;
825*5c591343SA. Cody Schuffelen
826*5c591343SA. Cody Schuffelen }
827*5c591343SA. Cody Schuffelen
828*5c591343SA. Cody Schuffelen //*** RSASSA_Encode()
829*5c591343SA. Cody Schuffelen // Encode a message using PKCS1v1.5 method.
830*5c591343SA. Cody Schuffelen //
831*5c591343SA. Cody Schuffelen // Return Type: TPM_RC
832*5c591343SA. Cody Schuffelen // TPM_RC_SCHEME 'hashAlg' is not a supported hash algorithm
833*5c591343SA. Cody Schuffelen // TPM_RC_SIZE 'eOutSize' is not large enough
834*5c591343SA. Cody Schuffelen // TPM_RC_VALUE 'hInSize' does not match the digest size of hashAlg
835*5c591343SA. Cody Schuffelen static TPM_RC
RSASSA_Encode(TPM2B * pOut,TPM_ALG_ID hashAlg,TPM2B * hIn)836*5c591343SA. Cody Schuffelen RSASSA_Encode(
837*5c591343SA. Cody Schuffelen TPM2B *pOut, // IN:OUT on in, the size of the public key
838*5c591343SA. Cody Schuffelen // on out, the encoded area
839*5c591343SA. Cody Schuffelen TPM_ALG_ID hashAlg, // IN: hash algorithm for PKCS1v1_5
840*5c591343SA. Cody Schuffelen TPM2B *hIn // IN: digest value to encode
841*5c591343SA. Cody Schuffelen )
842*5c591343SA. Cody Schuffelen {
843*5c591343SA. Cody Schuffelen BYTE DER[20];
844*5c591343SA. Cody Schuffelen BYTE *der = DER;
845*5c591343SA. Cody Schuffelen INT32 derSize = MakeDerTag(hashAlg, sizeof(DER), DER);
846*5c591343SA. Cody Schuffelen BYTE *eOut;
847*5c591343SA. Cody Schuffelen INT32 fillSize;
848*5c591343SA. Cody Schuffelen TPM_RC retVal = TPM_RC_SUCCESS;
849*5c591343SA. Cody Schuffelen
850*5c591343SA. Cody Schuffelen // Can't use this scheme if the algorithm doesn't have a DER string defined.
851*5c591343SA. Cody Schuffelen if(derSize == 0)
852*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_SCHEME);
853*5c591343SA. Cody Schuffelen
854*5c591343SA. Cody Schuffelen // If the digest size of 'hashAl' doesn't match the input digest size, then
855*5c591343SA. Cody Schuffelen // the DER will misidentify the digest so return an error
856*5c591343SA. Cody Schuffelen if(CryptHashGetDigestSize(hashAlg) != hIn->size)
857*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_VALUE);
858*5c591343SA. Cody Schuffelen fillSize = pOut->size - derSize - hIn->size - 3;
859*5c591343SA. Cody Schuffelen eOut = pOut->buffer;
860*5c591343SA. Cody Schuffelen
861*5c591343SA. Cody Schuffelen // Make sure that this combination will fit in the provided space
862*5c591343SA. Cody Schuffelen if(fillSize < 8)
863*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_SIZE);
864*5c591343SA. Cody Schuffelen
865*5c591343SA. Cody Schuffelen // Start filling
866*5c591343SA. Cody Schuffelen *eOut++ = 0; // initial byte of zero
867*5c591343SA. Cody Schuffelen *eOut++ = 1; // byte of 0x01
868*5c591343SA. Cody Schuffelen for(; fillSize > 0; fillSize--)
869*5c591343SA. Cody Schuffelen *eOut++ = 0xff; // bunch of 0xff
870*5c591343SA. Cody Schuffelen *eOut++ = 0; // another 0
871*5c591343SA. Cody Schuffelen for(; derSize > 0; derSize--)
872*5c591343SA. Cody Schuffelen *eOut++ = *der++; // copy the DER
873*5c591343SA. Cody Schuffelen der = hIn->buffer;
874*5c591343SA. Cody Schuffelen for(fillSize = hIn->size; fillSize > 0; fillSize--)
875*5c591343SA. Cody Schuffelen *eOut++ = *der++; // copy the hash
876*5c591343SA. Cody Schuffelen Exit:
877*5c591343SA. Cody Schuffelen return retVal;
878*5c591343SA. Cody Schuffelen }
879*5c591343SA. Cody Schuffelen
880*5c591343SA. Cody Schuffelen //*** RSASSA_Decode()
881*5c591343SA. Cody Schuffelen // This function performs the RSASSA decoding of a signature.
882*5c591343SA. Cody Schuffelen //
883*5c591343SA. Cody Schuffelen // Return Type: TPM_RC
884*5c591343SA. Cody Schuffelen // TPM_RC_VALUE decode unsuccessful
885*5c591343SA. Cody Schuffelen // TPM_RC_SCHEME 'haslAlg' is not supported
886*5c591343SA. Cody Schuffelen //
887*5c591343SA. Cody Schuffelen static TPM_RC
RSASSA_Decode(TPM_ALG_ID hashAlg,TPM2B * hIn,TPM2B * eIn)888*5c591343SA. Cody Schuffelen RSASSA_Decode(
889*5c591343SA. Cody Schuffelen TPM_ALG_ID hashAlg, // IN: hash algorithm to use for the encoding
890*5c591343SA. Cody Schuffelen TPM2B *hIn, // In: the digest to compare
891*5c591343SA. Cody Schuffelen TPM2B *eIn // IN: the encoded data
892*5c591343SA. Cody Schuffelen )
893*5c591343SA. Cody Schuffelen {
894*5c591343SA. Cody Schuffelen BYTE fail;
895*5c591343SA. Cody Schuffelen BYTE DER[20];
896*5c591343SA. Cody Schuffelen BYTE *der = DER;
897*5c591343SA. Cody Schuffelen INT32 derSize = MakeDerTag(hashAlg, sizeof(DER), DER);
898*5c591343SA. Cody Schuffelen BYTE *pe;
899*5c591343SA. Cody Schuffelen INT32 hashSize = CryptHashGetDigestSize(hashAlg);
900*5c591343SA. Cody Schuffelen INT32 fillSize;
901*5c591343SA. Cody Schuffelen TPM_RC retVal;
902*5c591343SA. Cody Schuffelen BYTE *digest;
903*5c591343SA. Cody Schuffelen UINT16 digestSize;
904*5c591343SA. Cody Schuffelen
905*5c591343SA. Cody Schuffelen pAssert(hIn != NULL && eIn != NULL);
906*5c591343SA. Cody Schuffelen pe = eIn->buffer;
907*5c591343SA. Cody Schuffelen
908*5c591343SA. Cody Schuffelen // Can't use this scheme if the algorithm doesn't have a DER string
909*5c591343SA. Cody Schuffelen // defined or if the provided hash isn't the right size
910*5c591343SA. Cody Schuffelen if(derSize == 0 || (unsigned)hashSize != hIn->size)
911*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_SCHEME);
912*5c591343SA. Cody Schuffelen
913*5c591343SA. Cody Schuffelen // Make sure that this combination will fit in the provided space
914*5c591343SA. Cody Schuffelen // Since no data movement takes place, can just walk though this
915*5c591343SA. Cody Schuffelen // and accept nearly random values. This can only be called from
916*5c591343SA. Cody Schuffelen // CryptValidateSignature() so eInSize is known to be in range.
917*5c591343SA. Cody Schuffelen fillSize = eIn->size - derSize - hashSize - 3;
918*5c591343SA. Cody Schuffelen
919*5c591343SA. Cody Schuffelen // Start checking (fail will become non-zero if any of the bytes do not have
920*5c591343SA. Cody Schuffelen // the expected value.
921*5c591343SA. Cody Schuffelen fail = *pe++; // initial byte of zero
922*5c591343SA. Cody Schuffelen fail |= *pe++ ^ 1; // byte of 0x01
923*5c591343SA. Cody Schuffelen for(; fillSize > 0; fillSize--)
924*5c591343SA. Cody Schuffelen fail |= *pe++ ^ 0xff; // bunch of 0xff
925*5c591343SA. Cody Schuffelen fail |= *pe++; // another 0
926*5c591343SA. Cody Schuffelen for(; derSize > 0; derSize--)
927*5c591343SA. Cody Schuffelen fail |= *pe++ ^ *der++; // match the DER
928*5c591343SA. Cody Schuffelen digestSize = hIn->size;
929*5c591343SA. Cody Schuffelen digest = hIn->buffer;
930*5c591343SA. Cody Schuffelen for(; digestSize > 0; digestSize--)
931*5c591343SA. Cody Schuffelen fail |= *pe++ ^ *digest++; // match the hash
932*5c591343SA. Cody Schuffelen retVal = (fail != 0) ? TPM_RC_VALUE : TPM_RC_SUCCESS;
933*5c591343SA. Cody Schuffelen Exit:
934*5c591343SA. Cody Schuffelen return retVal;
935*5c591343SA. Cody Schuffelen }
936*5c591343SA. Cody Schuffelen
937*5c591343SA. Cody Schuffelen //** Externally Accessible Functions
938*5c591343SA. Cody Schuffelen
939*5c591343SA. Cody Schuffelen //*** CryptRsaSelectScheme()
940*5c591343SA. Cody Schuffelen // This function is used by TPM2_RSA_Decrypt and TPM2_RSA_Encrypt. It sets up
941*5c591343SA. Cody Schuffelen // the rules to select a scheme between input and object default.
942*5c591343SA. Cody Schuffelen // This function assume the RSA object is loaded.
943*5c591343SA. Cody Schuffelen // If a default scheme is defined in object, the default scheme should be chosen,
944*5c591343SA. Cody Schuffelen // otherwise, the input scheme should be chosen.
945*5c591343SA. Cody Schuffelen // In the case that both the object and 'scheme' are not TPM_ALG_NULL, then
946*5c591343SA. Cody Schuffelen // if the schemes are the same, the input scheme will be chosen.
947*5c591343SA. Cody Schuffelen // if the scheme are not compatible, a NULL pointer will be returned.
948*5c591343SA. Cody Schuffelen //
949*5c591343SA. Cody Schuffelen // The return pointer may point to a TPM_ALG_NULL scheme.
950*5c591343SA. Cody Schuffelen TPMT_RSA_DECRYPT*
CryptRsaSelectScheme(TPMI_DH_OBJECT rsaHandle,TPMT_RSA_DECRYPT * scheme)951*5c591343SA. Cody Schuffelen CryptRsaSelectScheme(
952*5c591343SA. Cody Schuffelen TPMI_DH_OBJECT rsaHandle, // IN: handle of an RSA key
953*5c591343SA. Cody Schuffelen TPMT_RSA_DECRYPT *scheme // IN: a sign or decrypt scheme
954*5c591343SA. Cody Schuffelen )
955*5c591343SA. Cody Schuffelen {
956*5c591343SA. Cody Schuffelen OBJECT *rsaObject;
957*5c591343SA. Cody Schuffelen TPMT_ASYM_SCHEME *keyScheme;
958*5c591343SA. Cody Schuffelen TPMT_RSA_DECRYPT *retVal = NULL;
959*5c591343SA. Cody Schuffelen
960*5c591343SA. Cody Schuffelen // Get sign object pointer
961*5c591343SA. Cody Schuffelen rsaObject = HandleToObject(rsaHandle);
962*5c591343SA. Cody Schuffelen keyScheme = &rsaObject->publicArea.parameters.asymDetail.scheme;
963*5c591343SA. Cody Schuffelen
964*5c591343SA. Cody Schuffelen // if the default scheme of the object is TPM_ALG_NULL, then select the
965*5c591343SA. Cody Schuffelen // input scheme
966*5c591343SA. Cody Schuffelen if(keyScheme->scheme == TPM_ALG_NULL)
967*5c591343SA. Cody Schuffelen {
968*5c591343SA. Cody Schuffelen retVal = scheme;
969*5c591343SA. Cody Schuffelen }
970*5c591343SA. Cody Schuffelen // if the object scheme is not TPM_ALG_NULL and the input scheme is
971*5c591343SA. Cody Schuffelen // TPM_ALG_NULL, then select the default scheme of the object.
972*5c591343SA. Cody Schuffelen else if(scheme->scheme == TPM_ALG_NULL)
973*5c591343SA. Cody Schuffelen {
974*5c591343SA. Cody Schuffelen // if input scheme is NULL
975*5c591343SA. Cody Schuffelen retVal = (TPMT_RSA_DECRYPT *)keyScheme;
976*5c591343SA. Cody Schuffelen }
977*5c591343SA. Cody Schuffelen // get here if both the object scheme and the input scheme are
978*5c591343SA. Cody Schuffelen // not TPM_ALG_NULL. Need to insure that they are the same.
979*5c591343SA. Cody Schuffelen // IMPLEMENTATION NOTE: This could cause problems if future versions have
980*5c591343SA. Cody Schuffelen // schemes that have more values than just a hash algorithm. A new function
981*5c591343SA. Cody Schuffelen // (IsSchemeSame()) might be needed then.
982*5c591343SA. Cody Schuffelen else if(keyScheme->scheme == scheme->scheme
983*5c591343SA. Cody Schuffelen && keyScheme->details.anySig.hashAlg == scheme->details.anySig.hashAlg)
984*5c591343SA. Cody Schuffelen {
985*5c591343SA. Cody Schuffelen retVal = scheme;
986*5c591343SA. Cody Schuffelen }
987*5c591343SA. Cody Schuffelen // two different, incompatible schemes specified will return NULL
988*5c591343SA. Cody Schuffelen return retVal;
989*5c591343SA. Cody Schuffelen }
990*5c591343SA. Cody Schuffelen
991*5c591343SA. Cody Schuffelen //*** CryptRsaLoadPrivateExponent()
992*5c591343SA. Cody Schuffelen // This function is called to generate the private exponent of an RSA key.
993*5c591343SA. Cody Schuffelen // Return Type: TPM_RC
994*5c591343SA. Cody Schuffelen // TPM_RC_BINDING public and private parts of 'rsaKey' are not matched
995*5c591343SA. Cody Schuffelen TPM_RC
CryptRsaLoadPrivateExponent(TPMT_PUBLIC * publicArea,TPMT_SENSITIVE * sensitive)996*5c591343SA. Cody Schuffelen CryptRsaLoadPrivateExponent(
997*5c591343SA. Cody Schuffelen TPMT_PUBLIC *publicArea,
998*5c591343SA. Cody Schuffelen TPMT_SENSITIVE *sensitive
999*5c591343SA. Cody Schuffelen )
1000*5c591343SA. Cody Schuffelen {
1001*5c591343SA. Cody Schuffelen //
1002*5c591343SA. Cody Schuffelen if((sensitive->sensitive.rsa.t.size & RSA_prime_flag) == 0)
1003*5c591343SA. Cody Schuffelen {
1004*5c591343SA. Cody Schuffelen if((sensitive->sensitive.rsa.t.size * 2) == publicArea->unique.rsa.t.size)
1005*5c591343SA. Cody Schuffelen {
1006*5c591343SA. Cody Schuffelen NEW_PRIVATE_EXPONENT(Z);
1007*5c591343SA. Cody Schuffelen BN_RSA_INITIALIZED(bnN, &publicArea->unique.rsa);
1008*5c591343SA. Cody Schuffelen BN_RSA(bnQr);
1009*5c591343SA. Cody Schuffelen BN_VAR(bnE, RADIX_BITS);
1010*5c591343SA. Cody Schuffelen
1011*5c591343SA. Cody Schuffelen TEST(TPM_ALG_NULL);
1012*5c591343SA. Cody Schuffelen
1013*5c591343SA. Cody Schuffelen VERIFY((sensitive->sensitive.rsa.t.size * 2)
1014*5c591343SA. Cody Schuffelen == publicArea->unique.rsa.t.size);
1015*5c591343SA. Cody Schuffelen // Initialize the exponent
1016*5c591343SA. Cody Schuffelen BnSetWord(bnE, publicArea->parameters.rsaDetail.exponent);
1017*5c591343SA. Cody Schuffelen if(BnEqualZero(bnE))
1018*5c591343SA. Cody Schuffelen BnSetWord(bnE, RSA_DEFAULT_PUBLIC_EXPONENT);
1019*5c591343SA. Cody Schuffelen // Convert first prime to 2B
1020*5c591343SA. Cody Schuffelen VERIFY(BnFrom2B(Z->P, &sensitive->sensitive.rsa.b) != NULL);
1021*5c591343SA. Cody Schuffelen
1022*5c591343SA. Cody Schuffelen // Find the second prime by division. This uses 'bQ' rather than Z->Q
1023*5c591343SA. Cody Schuffelen // because the division could make the quotient larger than a prime during
1024*5c591343SA. Cody Schuffelen // some intermediate step.
1025*5c591343SA. Cody Schuffelen VERIFY(BnDiv(Z->Q, bnQr, bnN, Z->P));
1026*5c591343SA. Cody Schuffelen VERIFY(BnEqualZero(bnQr));
1027*5c591343SA. Cody Schuffelen // Compute the private exponent and return it if found
1028*5c591343SA. Cody Schuffelen VERIFY(ComputePrivateExponent(bnE, Z));
1029*5c591343SA. Cody Schuffelen VERIFY(PackExponent(&sensitive->sensitive.rsa, Z));
1030*5c591343SA. Cody Schuffelen }
1031*5c591343SA. Cody Schuffelen else
1032*5c591343SA. Cody Schuffelen VERIFY(((sensitive->sensitive.rsa.t.size / 5) * 2)
1033*5c591343SA. Cody Schuffelen == publicArea->unique.rsa.t.size);
1034*5c591343SA. Cody Schuffelen sensitive->sensitive.rsa.t.size |= RSA_prime_flag;
1035*5c591343SA. Cody Schuffelen }
1036*5c591343SA. Cody Schuffelen return TPM_RC_SUCCESS;
1037*5c591343SA. Cody Schuffelen Error:
1038*5c591343SA. Cody Schuffelen return TPM_RC_BINDING;
1039*5c591343SA. Cody Schuffelen }
1040*5c591343SA. Cody Schuffelen
1041*5c591343SA. Cody Schuffelen //*** CryptRsaEncrypt()
1042*5c591343SA. Cody Schuffelen // This is the entry point for encryption using RSA. Encryption is
1043*5c591343SA. Cody Schuffelen // use of the public exponent. The padding parameter determines what
1044*5c591343SA. Cody Schuffelen // padding will be used.
1045*5c591343SA. Cody Schuffelen //
1046*5c591343SA. Cody Schuffelen // The 'cOutSize' parameter must be at least as large as the size of the key.
1047*5c591343SA. Cody Schuffelen //
1048*5c591343SA. Cody Schuffelen // If the padding is RSA_PAD_NONE, 'dIn' is treated as a number. It must be
1049*5c591343SA. Cody Schuffelen // lower in value than the key modulus.
1050*5c591343SA. Cody Schuffelen // NOTE: If dIn has fewer bytes than cOut, then we don't add low-order zeros to
1051*5c591343SA. Cody Schuffelen // dIn to make it the size of the RSA key for the call to RSAEP. This is
1052*5c591343SA. Cody Schuffelen // because the high order bytes of dIn might have a numeric value that is
1053*5c591343SA. Cody Schuffelen // greater than the value of the key modulus. If this had low-order zeros
1054*5c591343SA. Cody Schuffelen // added, it would have a numeric value larger than the modulus even though
1055*5c591343SA. Cody Schuffelen // it started out with a lower numeric value.
1056*5c591343SA. Cody Schuffelen //
1057*5c591343SA. Cody Schuffelen // Return Type: TPM_RC
1058*5c591343SA. Cody Schuffelen // TPM_RC_VALUE 'cOutSize' is too small (must be the size
1059*5c591343SA. Cody Schuffelen // of the modulus)
1060*5c591343SA. Cody Schuffelen // TPM_RC_SCHEME 'padType' is not a supported scheme
1061*5c591343SA. Cody Schuffelen //
1062*5c591343SA. Cody Schuffelen LIB_EXPORT TPM_RC
CryptRsaEncrypt(TPM2B_PUBLIC_KEY_RSA * cOut,TPM2B * dIn,OBJECT * key,TPMT_RSA_DECRYPT * scheme,const TPM2B * label,RAND_STATE * rand)1063*5c591343SA. Cody Schuffelen CryptRsaEncrypt(
1064*5c591343SA. Cody Schuffelen TPM2B_PUBLIC_KEY_RSA *cOut, // OUT: the encrypted data
1065*5c591343SA. Cody Schuffelen TPM2B *dIn, // IN: the data to encrypt
1066*5c591343SA. Cody Schuffelen OBJECT *key, // IN: the key used for encryption
1067*5c591343SA. Cody Schuffelen TPMT_RSA_DECRYPT *scheme, // IN: the type of padding and hash
1068*5c591343SA. Cody Schuffelen // if needed
1069*5c591343SA. Cody Schuffelen const TPM2B *label, // IN: in case it is needed
1070*5c591343SA. Cody Schuffelen RAND_STATE *rand // IN: random number generator
1071*5c591343SA. Cody Schuffelen // state (mostly for testing)
1072*5c591343SA. Cody Schuffelen )
1073*5c591343SA. Cody Schuffelen {
1074*5c591343SA. Cody Schuffelen TPM_RC retVal = TPM_RC_SUCCESS;
1075*5c591343SA. Cody Schuffelen TPM2B_PUBLIC_KEY_RSA dataIn;
1076*5c591343SA. Cody Schuffelen //
1077*5c591343SA. Cody Schuffelen // if the input and output buffers are the same, copy the input to a scratch
1078*5c591343SA. Cody Schuffelen // buffer so that things don't get messed up.
1079*5c591343SA. Cody Schuffelen if(dIn == &cOut->b)
1080*5c591343SA. Cody Schuffelen {
1081*5c591343SA. Cody Schuffelen MemoryCopy2B(&dataIn.b, dIn, sizeof(dataIn.t.buffer));
1082*5c591343SA. Cody Schuffelen dIn = &dataIn.b;
1083*5c591343SA. Cody Schuffelen }
1084*5c591343SA. Cody Schuffelen // All encryption schemes return the same size of data
1085*5c591343SA. Cody Schuffelen cOut->t.size = key->publicArea.unique.rsa.t.size;
1086*5c591343SA. Cody Schuffelen TEST(scheme->scheme);
1087*5c591343SA. Cody Schuffelen
1088*5c591343SA. Cody Schuffelen switch(scheme->scheme)
1089*5c591343SA. Cody Schuffelen {
1090*5c591343SA. Cody Schuffelen case TPM_ALG_NULL: // 'raw' encryption
1091*5c591343SA. Cody Schuffelen {
1092*5c591343SA. Cody Schuffelen INT32 i;
1093*5c591343SA. Cody Schuffelen INT32 dSize = dIn->size;
1094*5c591343SA. Cody Schuffelen // dIn can have more bytes than cOut as long as the extra bytes
1095*5c591343SA. Cody Schuffelen // are zero. Note: the more significant bytes of a number in a byte
1096*5c591343SA. Cody Schuffelen // buffer are the bytes at the start of the array.
1097*5c591343SA. Cody Schuffelen for(i = 0; (i < dSize) && (dIn->buffer[i] == 0); i++);
1098*5c591343SA. Cody Schuffelen dSize -= i;
1099*5c591343SA. Cody Schuffelen if(dSize > cOut->t.size)
1100*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_VALUE);
1101*5c591343SA. Cody Schuffelen // Pad cOut with zeros if dIn is smaller
1102*5c591343SA. Cody Schuffelen memset(cOut->t.buffer, 0, cOut->t.size - dSize);
1103*5c591343SA. Cody Schuffelen // And copy the rest of the value
1104*5c591343SA. Cody Schuffelen memcpy(&cOut->t.buffer[cOut->t.size - dSize], &dIn->buffer[i], dSize);
1105*5c591343SA. Cody Schuffelen
1106*5c591343SA. Cody Schuffelen // If the size of dIn is the same as cOut dIn could be larger than
1107*5c591343SA. Cody Schuffelen // the modulus. If it is, then RSAEP() will catch it.
1108*5c591343SA. Cody Schuffelen }
1109*5c591343SA. Cody Schuffelen break;
1110*5c591343SA. Cody Schuffelen case TPM_ALG_RSAES:
1111*5c591343SA. Cody Schuffelen retVal = RSAES_PKCS1v1_5Encode(&cOut->b, dIn, rand);
1112*5c591343SA. Cody Schuffelen break;
1113*5c591343SA. Cody Schuffelen case TPM_ALG_OAEP:
1114*5c591343SA. Cody Schuffelen retVal = OaepEncode(&cOut->b, scheme->details.oaep.hashAlg, label, dIn,
1115*5c591343SA. Cody Schuffelen rand);
1116*5c591343SA. Cody Schuffelen break;
1117*5c591343SA. Cody Schuffelen default:
1118*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_SCHEME);
1119*5c591343SA. Cody Schuffelen break;
1120*5c591343SA. Cody Schuffelen }
1121*5c591343SA. Cody Schuffelen // All the schemes that do padding will come here for the encryption step
1122*5c591343SA. Cody Schuffelen // Check that the Encoding worked
1123*5c591343SA. Cody Schuffelen if(retVal == TPM_RC_SUCCESS)
1124*5c591343SA. Cody Schuffelen // Padding OK so do the encryption
1125*5c591343SA. Cody Schuffelen retVal = RSAEP(&cOut->b, key);
1126*5c591343SA. Cody Schuffelen Exit:
1127*5c591343SA. Cody Schuffelen return retVal;
1128*5c591343SA. Cody Schuffelen }
1129*5c591343SA. Cody Schuffelen
1130*5c591343SA. Cody Schuffelen //*** CryptRsaDecrypt()
1131*5c591343SA. Cody Schuffelen // This is the entry point for decryption using RSA. Decryption is
1132*5c591343SA. Cody Schuffelen // use of the private exponent. The 'padType' parameter determines what
1133*5c591343SA. Cody Schuffelen // padding was used.
1134*5c591343SA. Cody Schuffelen //
1135*5c591343SA. Cody Schuffelen // Return Type: TPM_RC
1136*5c591343SA. Cody Schuffelen // TPM_RC_SIZE 'cInSize' is not the same as the size of the public
1137*5c591343SA. Cody Schuffelen // modulus of 'key'; or numeric value of the encrypted
1138*5c591343SA. Cody Schuffelen // data is greater than the modulus
1139*5c591343SA. Cody Schuffelen // TPM_RC_VALUE 'dOutSize' is not large enough for the result
1140*5c591343SA. Cody Schuffelen // TPM_RC_SCHEME 'padType' is not supported
1141*5c591343SA. Cody Schuffelen //
1142*5c591343SA. Cody Schuffelen LIB_EXPORT TPM_RC
CryptRsaDecrypt(TPM2B * dOut,TPM2B * cIn,OBJECT * key,TPMT_RSA_DECRYPT * scheme,const TPM2B * label)1143*5c591343SA. Cody Schuffelen CryptRsaDecrypt(
1144*5c591343SA. Cody Schuffelen TPM2B *dOut, // OUT: the decrypted data
1145*5c591343SA. Cody Schuffelen TPM2B *cIn, // IN: the data to decrypt
1146*5c591343SA. Cody Schuffelen OBJECT *key, // IN: the key to use for decryption
1147*5c591343SA. Cody Schuffelen TPMT_RSA_DECRYPT *scheme, // IN: the padding scheme
1148*5c591343SA. Cody Schuffelen const TPM2B *label // IN: in case it is needed for the scheme
1149*5c591343SA. Cody Schuffelen )
1150*5c591343SA. Cody Schuffelen {
1151*5c591343SA. Cody Schuffelen TPM_RC retVal;
1152*5c591343SA. Cody Schuffelen
1153*5c591343SA. Cody Schuffelen // Make sure that the necessary parameters are provided
1154*5c591343SA. Cody Schuffelen pAssert(cIn != NULL && dOut != NULL && key != NULL);
1155*5c591343SA. Cody Schuffelen
1156*5c591343SA. Cody Schuffelen // Size is checked to make sure that the encrypted value is the right size
1157*5c591343SA. Cody Schuffelen if(cIn->size != key->publicArea.unique.rsa.t.size)
1158*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_SIZE);
1159*5c591343SA. Cody Schuffelen
1160*5c591343SA. Cody Schuffelen TEST(scheme->scheme);
1161*5c591343SA. Cody Schuffelen
1162*5c591343SA. Cody Schuffelen // For others that do padding, do the decryption in place and then
1163*5c591343SA. Cody Schuffelen // go handle the decoding.
1164*5c591343SA. Cody Schuffelen retVal = RSADP(cIn, key);
1165*5c591343SA. Cody Schuffelen if(retVal == TPM_RC_SUCCESS)
1166*5c591343SA. Cody Schuffelen {
1167*5c591343SA. Cody Schuffelen // Remove padding
1168*5c591343SA. Cody Schuffelen switch(scheme->scheme)
1169*5c591343SA. Cody Schuffelen {
1170*5c591343SA. Cody Schuffelen case TPM_ALG_NULL:
1171*5c591343SA. Cody Schuffelen if(dOut->size < cIn->size)
1172*5c591343SA. Cody Schuffelen return TPM_RC_VALUE;
1173*5c591343SA. Cody Schuffelen MemoryCopy2B(dOut, cIn, dOut->size);
1174*5c591343SA. Cody Schuffelen break;
1175*5c591343SA. Cody Schuffelen case TPM_ALG_RSAES:
1176*5c591343SA. Cody Schuffelen retVal = RSAES_Decode(dOut, cIn);
1177*5c591343SA. Cody Schuffelen break;
1178*5c591343SA. Cody Schuffelen case TPM_ALG_OAEP:
1179*5c591343SA. Cody Schuffelen retVal = OaepDecode(dOut, scheme->details.oaep.hashAlg, label, cIn);
1180*5c591343SA. Cody Schuffelen break;
1181*5c591343SA. Cody Schuffelen default:
1182*5c591343SA. Cody Schuffelen retVal = TPM_RC_SCHEME;
1183*5c591343SA. Cody Schuffelen break;
1184*5c591343SA. Cody Schuffelen }
1185*5c591343SA. Cody Schuffelen }
1186*5c591343SA. Cody Schuffelen Exit:
1187*5c591343SA. Cody Schuffelen return retVal;
1188*5c591343SA. Cody Schuffelen }
1189*5c591343SA. Cody Schuffelen
1190*5c591343SA. Cody Schuffelen //*** CryptRsaSign()
1191*5c591343SA. Cody Schuffelen // This function is used to generate an RSA signature of the type indicated in
1192*5c591343SA. Cody Schuffelen // 'scheme'.
1193*5c591343SA. Cody Schuffelen //
1194*5c591343SA. Cody Schuffelen // Return Type: TPM_RC
1195*5c591343SA. Cody Schuffelen // TPM_RC_SCHEME 'scheme' or 'hashAlg' are not supported
1196*5c591343SA. Cody Schuffelen // TPM_RC_VALUE 'hInSize' does not match 'hashAlg' (for RSASSA)
1197*5c591343SA. Cody Schuffelen //
1198*5c591343SA. Cody Schuffelen LIB_EXPORT TPM_RC
CryptRsaSign(TPMT_SIGNATURE * sigOut,OBJECT * key,TPM2B_DIGEST * hIn,RAND_STATE * rand)1199*5c591343SA. Cody Schuffelen CryptRsaSign(
1200*5c591343SA. Cody Schuffelen TPMT_SIGNATURE *sigOut,
1201*5c591343SA. Cody Schuffelen OBJECT *key, // IN: key to use
1202*5c591343SA. Cody Schuffelen TPM2B_DIGEST *hIn, // IN: the digest to sign
1203*5c591343SA. Cody Schuffelen RAND_STATE *rand // IN: the random number generator
1204*5c591343SA. Cody Schuffelen // to use (mostly for testing)
1205*5c591343SA. Cody Schuffelen )
1206*5c591343SA. Cody Schuffelen {
1207*5c591343SA. Cody Schuffelen TPM_RC retVal = TPM_RC_SUCCESS;
1208*5c591343SA. Cody Schuffelen UINT16 modSize;
1209*5c591343SA. Cody Schuffelen
1210*5c591343SA. Cody Schuffelen // parameter checks
1211*5c591343SA. Cody Schuffelen pAssert(sigOut != NULL && key != NULL && hIn != NULL);
1212*5c591343SA. Cody Schuffelen
1213*5c591343SA. Cody Schuffelen modSize = key->publicArea.unique.rsa.t.size;
1214*5c591343SA. Cody Schuffelen
1215*5c591343SA. Cody Schuffelen // for all non-null signatures, the size is the size of the key modulus
1216*5c591343SA. Cody Schuffelen sigOut->signature.rsapss.sig.t.size = modSize;
1217*5c591343SA. Cody Schuffelen
1218*5c591343SA. Cody Schuffelen TEST(sigOut->sigAlg);
1219*5c591343SA. Cody Schuffelen
1220*5c591343SA. Cody Schuffelen switch(sigOut->sigAlg)
1221*5c591343SA. Cody Schuffelen {
1222*5c591343SA. Cody Schuffelen case TPM_ALG_NULL:
1223*5c591343SA. Cody Schuffelen sigOut->signature.rsapss.sig.t.size = 0;
1224*5c591343SA. Cody Schuffelen return TPM_RC_SUCCESS;
1225*5c591343SA. Cody Schuffelen case TPM_ALG_RSAPSS:
1226*5c591343SA. Cody Schuffelen retVal = PssEncode(&sigOut->signature.rsapss.sig.b,
1227*5c591343SA. Cody Schuffelen sigOut->signature.rsapss.hash, &hIn->b, rand);
1228*5c591343SA. Cody Schuffelen break;
1229*5c591343SA. Cody Schuffelen case TPM_ALG_RSASSA:
1230*5c591343SA. Cody Schuffelen retVal = RSASSA_Encode(&sigOut->signature.rsassa.sig.b,
1231*5c591343SA. Cody Schuffelen sigOut->signature.rsassa.hash, &hIn->b);
1232*5c591343SA. Cody Schuffelen break;
1233*5c591343SA. Cody Schuffelen default:
1234*5c591343SA. Cody Schuffelen retVal = TPM_RC_SCHEME;
1235*5c591343SA. Cody Schuffelen }
1236*5c591343SA. Cody Schuffelen if(retVal == TPM_RC_SUCCESS)
1237*5c591343SA. Cody Schuffelen {
1238*5c591343SA. Cody Schuffelen // Do the encryption using the private key
1239*5c591343SA. Cody Schuffelen retVal = RSADP(&sigOut->signature.rsapss.sig.b, key);
1240*5c591343SA. Cody Schuffelen }
1241*5c591343SA. Cody Schuffelen return retVal;
1242*5c591343SA. Cody Schuffelen }
1243*5c591343SA. Cody Schuffelen
1244*5c591343SA. Cody Schuffelen //*** CryptRsaValidateSignature()
1245*5c591343SA. Cody Schuffelen // This function is used to validate an RSA signature. If the signature is valid
1246*5c591343SA. Cody Schuffelen // TPM_RC_SUCCESS is returned. If the signature is not valid, TPM_RC_SIGNATURE is
1247*5c591343SA. Cody Schuffelen // returned. Other return codes indicate either parameter problems or fatal errors.
1248*5c591343SA. Cody Schuffelen //
1249*5c591343SA. Cody Schuffelen // Return Type: TPM_RC
1250*5c591343SA. Cody Schuffelen // TPM_RC_SIGNATURE the signature does not check
1251*5c591343SA. Cody Schuffelen // TPM_RC_SCHEME unsupported scheme or hash algorithm
1252*5c591343SA. Cody Schuffelen //
1253*5c591343SA. Cody Schuffelen LIB_EXPORT TPM_RC
CryptRsaValidateSignature(TPMT_SIGNATURE * sig,OBJECT * key,TPM2B_DIGEST * digest)1254*5c591343SA. Cody Schuffelen CryptRsaValidateSignature(
1255*5c591343SA. Cody Schuffelen TPMT_SIGNATURE *sig, // IN: signature
1256*5c591343SA. Cody Schuffelen OBJECT *key, // IN: public modulus
1257*5c591343SA. Cody Schuffelen TPM2B_DIGEST *digest // IN: The digest being validated
1258*5c591343SA. Cody Schuffelen )
1259*5c591343SA. Cody Schuffelen {
1260*5c591343SA. Cody Schuffelen TPM_RC retVal;
1261*5c591343SA. Cody Schuffelen //
1262*5c591343SA. Cody Schuffelen // Fatal programming errors
1263*5c591343SA. Cody Schuffelen pAssert(key != NULL && sig != NULL && digest != NULL);
1264*5c591343SA. Cody Schuffelen switch(sig->sigAlg)
1265*5c591343SA. Cody Schuffelen {
1266*5c591343SA. Cody Schuffelen case TPM_ALG_RSAPSS:
1267*5c591343SA. Cody Schuffelen case TPM_ALG_RSASSA:
1268*5c591343SA. Cody Schuffelen break;
1269*5c591343SA. Cody Schuffelen default:
1270*5c591343SA. Cody Schuffelen return TPM_RC_SCHEME;
1271*5c591343SA. Cody Schuffelen }
1272*5c591343SA. Cody Schuffelen
1273*5c591343SA. Cody Schuffelen // Errors that might be caused by calling parameters
1274*5c591343SA. Cody Schuffelen if(sig->signature.rsassa.sig.t.size != key->publicArea.unique.rsa.t.size)
1275*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_SIGNATURE);
1276*5c591343SA. Cody Schuffelen
1277*5c591343SA. Cody Schuffelen TEST(sig->sigAlg);
1278*5c591343SA. Cody Schuffelen
1279*5c591343SA. Cody Schuffelen // Decrypt the block
1280*5c591343SA. Cody Schuffelen retVal = RSAEP(&sig->signature.rsassa.sig.b, key);
1281*5c591343SA. Cody Schuffelen if(retVal == TPM_RC_SUCCESS)
1282*5c591343SA. Cody Schuffelen {
1283*5c591343SA. Cody Schuffelen switch(sig->sigAlg)
1284*5c591343SA. Cody Schuffelen {
1285*5c591343SA. Cody Schuffelen case TPM_ALG_RSAPSS:
1286*5c591343SA. Cody Schuffelen retVal = PssDecode(sig->signature.any.hashAlg, &digest->b,
1287*5c591343SA. Cody Schuffelen &sig->signature.rsassa.sig.b);
1288*5c591343SA. Cody Schuffelen break;
1289*5c591343SA. Cody Schuffelen case TPM_ALG_RSASSA:
1290*5c591343SA. Cody Schuffelen retVal = RSASSA_Decode(sig->signature.any.hashAlg, &digest->b,
1291*5c591343SA. Cody Schuffelen &sig->signature.rsassa.sig.b);
1292*5c591343SA. Cody Schuffelen break;
1293*5c591343SA. Cody Schuffelen default:
1294*5c591343SA. Cody Schuffelen return TPM_RC_SCHEME;
1295*5c591343SA. Cody Schuffelen }
1296*5c591343SA. Cody Schuffelen }
1297*5c591343SA. Cody Schuffelen Exit:
1298*5c591343SA. Cody Schuffelen return (retVal != TPM_RC_SUCCESS) ? TPM_RC_SIGNATURE : TPM_RC_SUCCESS;
1299*5c591343SA. Cody Schuffelen }
1300*5c591343SA. Cody Schuffelen
1301*5c591343SA. Cody Schuffelen #if SIMULATION && USE_RSA_KEY_CACHE
1302*5c591343SA. Cody Schuffelen extern int s_rsaKeyCacheEnabled;
1303*5c591343SA. Cody Schuffelen int GetCachedRsaKey(TPMT_PUBLIC *publicArea, TPMT_SENSITIVE *sensitive,
1304*5c591343SA. Cody Schuffelen RAND_STATE *rand);
1305*5c591343SA. Cody Schuffelen #define GET_CACHED_KEY(publicArea, sensitive, rand) \
1306*5c591343SA. Cody Schuffelen (s_rsaKeyCacheEnabled && GetCachedRsaKey(publicArea, sensitive, rand))
1307*5c591343SA. Cody Schuffelen #else
1308*5c591343SA. Cody Schuffelen #define GET_CACHED_KEY(key, rand)
1309*5c591343SA. Cody Schuffelen #endif
1310*5c591343SA. Cody Schuffelen
1311*5c591343SA. Cody Schuffelen //*** CryptRsaGenerateKey()
1312*5c591343SA. Cody Schuffelen // Generate an RSA key from a provided seed
1313*5c591343SA. Cody Schuffelen /*(See part 1 specification)
1314*5c591343SA. Cody Schuffelen // The formulation is:
1315*5c591343SA. Cody Schuffelen // KDFa(hash, seed, label, Name, Counter, bits)
1316*5c591343SA. Cody Schuffelen // Where:
1317*5c591343SA. Cody Schuffelen // hash the nameAlg from the public template
1318*5c591343SA. Cody Schuffelen // seed a seed (will be a primary seed for a primary key)
1319*5c591343SA. Cody Schuffelen // label a distinguishing label including vendor ID and
1320*5c591343SA. Cody Schuffelen // vendor-assigned part number for the TPM.
1321*5c591343SA. Cody Schuffelen // Name the nameAlg from the template and the hash of the template
1322*5c591343SA. Cody Schuffelen // using nameAlg.
1323*5c591343SA. Cody Schuffelen // Counter a 32-bit integer that is incremented each time the KDF is
1324*5c591343SA. Cody Schuffelen // called in order to produce a specific key. This value
1325*5c591343SA. Cody Schuffelen // can be a 32-bit integer in host format and does not need
1326*5c591343SA. Cody Schuffelen // to be put in canonical form.
1327*5c591343SA. Cody Schuffelen // bits the number of bits needed for the key.
1328*5c591343SA. Cody Schuffelen // The following process is implemented to find a RSA key pair:
1329*5c591343SA. Cody Schuffelen // 1. pick a random number with enough bits from KDFa as a prime candidate
1330*5c591343SA. Cody Schuffelen // 2. set the first two significant bits and the least significant bit of the
1331*5c591343SA. Cody Schuffelen // prime candidate
1332*5c591343SA. Cody Schuffelen // 3. check if the number is a prime. if not, pick another random number
1333*5c591343SA. Cody Schuffelen // 4. Make sure the difference between the two primes are more than 2^104.
1334*5c591343SA. Cody Schuffelen // Otherwise, restart the process for the second prime
1335*5c591343SA. Cody Schuffelen // 5. If the counter has reached its maximum but we still can not find a valid
1336*5c591343SA. Cody Schuffelen // RSA key pair, return an internal error. This is an artificial bound.
1337*5c591343SA. Cody Schuffelen // Other implementation may choose a smaller number to indicate how many
1338*5c591343SA. Cody Schuffelen // times they are willing to try.
1339*5c591343SA. Cody Schuffelen */
1340*5c591343SA. Cody Schuffelen // Return Type: TPM_RC
1341*5c591343SA. Cody Schuffelen // TPM_RC_CANCELED operation was canceled
1342*5c591343SA. Cody Schuffelen // TPM_RC_RANGE public exponent is not supported
1343*5c591343SA. Cody Schuffelen // TPM_RC_VALUE could not find a prime using the provided parameters
1344*5c591343SA. Cody Schuffelen LIB_EXPORT TPM_RC
CryptRsaGenerateKey(TPMT_PUBLIC * publicArea,TPMT_SENSITIVE * sensitive,RAND_STATE * rand)1345*5c591343SA. Cody Schuffelen CryptRsaGenerateKey(
1346*5c591343SA. Cody Schuffelen TPMT_PUBLIC *publicArea,
1347*5c591343SA. Cody Schuffelen TPMT_SENSITIVE *sensitive,
1348*5c591343SA. Cody Schuffelen RAND_STATE *rand // IN: if not NULL, the deterministic
1349*5c591343SA. Cody Schuffelen // RNG state
1350*5c591343SA. Cody Schuffelen )
1351*5c591343SA. Cody Schuffelen {
1352*5c591343SA. Cody Schuffelen UINT32 i;
1353*5c591343SA. Cody Schuffelen BN_RSA(bnD);
1354*5c591343SA. Cody Schuffelen BN_RSA(bnN);
1355*5c591343SA. Cody Schuffelen BN_WORD(bnPubExp);
1356*5c591343SA. Cody Schuffelen UINT32 e = publicArea->parameters.rsaDetail.exponent;
1357*5c591343SA. Cody Schuffelen int keySizeInBits;
1358*5c591343SA. Cody Schuffelen TPM_RC retVal = TPM_RC_NO_RESULT;
1359*5c591343SA. Cody Schuffelen NEW_PRIVATE_EXPONENT(Z);
1360*5c591343SA. Cody Schuffelen //
1361*5c591343SA. Cody Schuffelen
1362*5c591343SA. Cody Schuffelen // Need to make sure that the caller did not specify an exponent that is
1363*5c591343SA. Cody Schuffelen // not supported
1364*5c591343SA. Cody Schuffelen e = publicArea->parameters.rsaDetail.exponent;
1365*5c591343SA. Cody Schuffelen if(e == 0)
1366*5c591343SA. Cody Schuffelen e = RSA_DEFAULT_PUBLIC_EXPONENT;
1367*5c591343SA. Cody Schuffelen else
1368*5c591343SA. Cody Schuffelen {
1369*5c591343SA. Cody Schuffelen if(e < 65537)
1370*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_RANGE);
1371*5c591343SA. Cody Schuffelen // Check that e is prime
1372*5c591343SA. Cody Schuffelen if(!IsPrimeInt(e))
1373*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_RANGE);
1374*5c591343SA. Cody Schuffelen }
1375*5c591343SA. Cody Schuffelen BnSetWord(bnPubExp, e);
1376*5c591343SA. Cody Schuffelen
1377*5c591343SA. Cody Schuffelen // check for supported key size.
1378*5c591343SA. Cody Schuffelen keySizeInBits = publicArea->parameters.rsaDetail.keyBits;
1379*5c591343SA. Cody Schuffelen if(((keySizeInBits % 1024) != 0)
1380*5c591343SA. Cody Schuffelen || (keySizeInBits > MAX_RSA_KEY_BITS) // this might be redundant, but...
1381*5c591343SA. Cody Schuffelen || (keySizeInBits == 0))
1382*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_VALUE);
1383*5c591343SA. Cody Schuffelen
1384*5c591343SA. Cody Schuffelen // Set the prime size for instrumentation purposes
1385*5c591343SA. Cody Schuffelen INSTRUMENT_SET(PrimeIndex, PRIME_INDEX(keySizeInBits / 2));
1386*5c591343SA. Cody Schuffelen
1387*5c591343SA. Cody Schuffelen #if SIMULATION && USE_RSA_KEY_CACHE
1388*5c591343SA. Cody Schuffelen if(GET_CACHED_KEY(publicArea, sensitive, rand))
1389*5c591343SA. Cody Schuffelen return TPM_RC_SUCCESS;
1390*5c591343SA. Cody Schuffelen #endif
1391*5c591343SA. Cody Schuffelen
1392*5c591343SA. Cody Schuffelen // Make sure that key generation has been tested
1393*5c591343SA. Cody Schuffelen TEST(TPM_ALG_NULL);
1394*5c591343SA. Cody Schuffelen
1395*5c591343SA. Cody Schuffelen
1396*5c591343SA. Cody Schuffelen // The prime is computed in P. When a new prime is found, Q is checked to
1397*5c591343SA. Cody Schuffelen // see if it is zero. If so, P is copied to Q and a new P is found.
1398*5c591343SA. Cody Schuffelen // When both P and Q are non-zero, the modulus and
1399*5c591343SA. Cody Schuffelen // private exponent are computed and a trial encryption/decryption is
1400*5c591343SA. Cody Schuffelen // performed. If the encrypt/decrypt fails, assume that at least one of the
1401*5c591343SA. Cody Schuffelen // primes is composite. Since we don't know which one, set Q to zero and start
1402*5c591343SA. Cody Schuffelen // over and find a new pair of primes.
1403*5c591343SA. Cody Schuffelen
1404*5c591343SA. Cody Schuffelen for(i = 1; (retVal == TPM_RC_NO_RESULT) && (i != 100); i++)
1405*5c591343SA. Cody Schuffelen {
1406*5c591343SA. Cody Schuffelen if(_plat__IsCanceled())
1407*5c591343SA. Cody Schuffelen ERROR_RETURN(TPM_RC_CANCELED);
1408*5c591343SA. Cody Schuffelen
1409*5c591343SA. Cody Schuffelen if(BnGeneratePrimeForRSA(Z->P, keySizeInBits / 2, e, rand) == TPM_RC_FAILURE)
1410*5c591343SA. Cody Schuffelen {
1411*5c591343SA. Cody Schuffelen retVal = TPM_RC_FAILURE;
1412*5c591343SA. Cody Schuffelen goto Exit;
1413*5c591343SA. Cody Schuffelen }
1414*5c591343SA. Cody Schuffelen
1415*5c591343SA. Cody Schuffelen INSTRUMENT_INC(PrimeCounts[PrimeIndex]);
1416*5c591343SA. Cody Schuffelen
1417*5c591343SA. Cody Schuffelen // If this is the second prime, make sure that it differs from the
1418*5c591343SA. Cody Schuffelen // first prime by at least 2^100
1419*5c591343SA. Cody Schuffelen if(BnEqualZero(Z->Q))
1420*5c591343SA. Cody Schuffelen {
1421*5c591343SA. Cody Schuffelen // copy p to q and compute another prime in p
1422*5c591343SA. Cody Schuffelen BnCopy(Z->Q, Z->P);
1423*5c591343SA. Cody Schuffelen continue;
1424*5c591343SA. Cody Schuffelen }
1425*5c591343SA. Cody Schuffelen // Make sure that the difference is at least 100 bits. Need to do it this
1426*5c591343SA. Cody Schuffelen // way because the big numbers are only positive values
1427*5c591343SA. Cody Schuffelen if(BnUnsignedCmp(Z->P, Z->Q) < 0)
1428*5c591343SA. Cody Schuffelen BnSub(bnD, Z->Q, Z->P);
1429*5c591343SA. Cody Schuffelen else
1430*5c591343SA. Cody Schuffelen BnSub(bnD, Z->P, Z->Q);
1431*5c591343SA. Cody Schuffelen if(BnMsb(bnD) < 100)
1432*5c591343SA. Cody Schuffelen continue;
1433*5c591343SA. Cody Schuffelen
1434*5c591343SA. Cody Schuffelen //Form the public modulus and set the unique value
1435*5c591343SA. Cody Schuffelen BnMult(bnN, Z->P, Z->Q);
1436*5c591343SA. Cody Schuffelen BnTo2B(bnN, &publicArea->unique.rsa.b,
1437*5c591343SA. Cody Schuffelen (NUMBYTES)BITS_TO_BYTES(keySizeInBits));
1438*5c591343SA. Cody Schuffelen // Make sure everything came out right. The MSb of the values must be one
1439*5c591343SA. Cody Schuffelen if(((publicArea->unique.rsa.t.buffer[0] & 0x80) == 0)
1440*5c591343SA. Cody Schuffelen || (publicArea->unique.rsa.t.size
1441*5c591343SA. Cody Schuffelen != (NUMBYTES)BITS_TO_BYTES(keySizeInBits)))
1442*5c591343SA. Cody Schuffelen FAIL(FATAL_ERROR_INTERNAL);
1443*5c591343SA. Cody Schuffelen
1444*5c591343SA. Cody Schuffelen
1445*5c591343SA. Cody Schuffelen // Make sure that we can form the private exponent values
1446*5c591343SA. Cody Schuffelen if(ComputePrivateExponent(bnPubExp, Z) != TRUE)
1447*5c591343SA. Cody Schuffelen {
1448*5c591343SA. Cody Schuffelen // If ComputePrivateExponent could not find an inverse for
1449*5c591343SA. Cody Schuffelen // Q, then copy P and recompute P. This might
1450*5c591343SA. Cody Schuffelen // cause both to be recomputed if P is also zero
1451*5c591343SA. Cody Schuffelen if(BnEqualZero(Z->Q))
1452*5c591343SA. Cody Schuffelen BnCopy(Z->Q, Z->P);
1453*5c591343SA. Cody Schuffelen continue;
1454*5c591343SA. Cody Schuffelen }
1455*5c591343SA. Cody Schuffelen
1456*5c591343SA. Cody Schuffelen // Pack the private exponent into the sensitive area
1457*5c591343SA. Cody Schuffelen PackExponent(&sensitive->sensitive.rsa, Z);
1458*5c591343SA. Cody Schuffelen // Make sure everything came out right. The MSb of the values must be one
1459*5c591343SA. Cody Schuffelen if(((publicArea->unique.rsa.t.buffer[0] & 0x80) == 0)
1460*5c591343SA. Cody Schuffelen || ((sensitive->sensitive.rsa.t.buffer[0] & 0x80) == 0))
1461*5c591343SA. Cody Schuffelen FAIL(FATAL_ERROR_INTERNAL);
1462*5c591343SA. Cody Schuffelen
1463*5c591343SA. Cody Schuffelen retVal = TPM_RC_SUCCESS;
1464*5c591343SA. Cody Schuffelen // Do a trial encryption decryption if this is a signing key
1465*5c591343SA. Cody Schuffelen if(IS_ATTRIBUTE(publicArea->objectAttributes, TPMA_OBJECT, sign))
1466*5c591343SA. Cody Schuffelen {
1467*5c591343SA. Cody Schuffelen BN_RSA(temp1);
1468*5c591343SA. Cody Schuffelen BN_RSA(temp2);
1469*5c591343SA. Cody Schuffelen BnGenerateRandomInRange(temp1, bnN, rand);
1470*5c591343SA. Cody Schuffelen
1471*5c591343SA. Cody Schuffelen // Encrypt with public exponent...
1472*5c591343SA. Cody Schuffelen BnModExp(temp2, temp1, bnPubExp, bnN);
1473*5c591343SA. Cody Schuffelen // ... then decrypt with private exponent
1474*5c591343SA. Cody Schuffelen RsaPrivateKeyOp(temp2, Z);
1475*5c591343SA. Cody Schuffelen
1476*5c591343SA. Cody Schuffelen // If the starting and ending values are not the same,
1477*5c591343SA. Cody Schuffelen // start over )-;
1478*5c591343SA. Cody Schuffelen if(BnUnsignedCmp(temp2, temp1) != 0)
1479*5c591343SA. Cody Schuffelen {
1480*5c591343SA. Cody Schuffelen BnSetWord(Z->Q, 0);
1481*5c591343SA. Cody Schuffelen retVal = TPM_RC_NO_RESULT;
1482*5c591343SA. Cody Schuffelen }
1483*5c591343SA. Cody Schuffelen }
1484*5c591343SA. Cody Schuffelen }
1485*5c591343SA. Cody Schuffelen Exit:
1486*5c591343SA. Cody Schuffelen return retVal;
1487*5c591343SA. Cody Schuffelen }
1488*5c591343SA. Cody Schuffelen
1489*5c591343SA. Cody Schuffelen #endif // ALG_RSA