chiark / gitweb /
algorithms.py: Support the IETF versions of ChaCha etc. with 96-bit nonce.
[catacomb-python] / pubkey.c
index 862fe515ee28ac125dc869591cc8138bbd029bec..311152ac4bf69fd9f0bf687a18731dab65de6773 100644 (file)
--- a/pubkey.c
+++ b/pubkey.c
@@ -1,13 +1,11 @@
 /* -*-c-*-
- *
- * $Id$
  *
  * Public-key cryptography
  *
  * (c) 2004 Straylight/Edgeware
  */
 
-/*----- Licensing notice --------------------------------------------------* 
+/*----- Licensing notice --------------------------------------------------*
  *
  * This file is part of the Python interface to Catacomb.
  *
  * it under the terms of the GNU General Public License as published by
  * the Free Software Foundation; either version 2 of the License, or
  * (at your option) any later version.
- * 
+ *
  * Catacomb/Python is distributed in the hope that it will be useful,
  * but WITHOUT ANY WARRANTY; without even the implied warranty of
  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
  * GNU General Public License for more details.
- * 
+ *
  * You should have received a copy of the GNU General Public License
  * along with Catacomb/Python; if not, write to the Free Software Foundation,
  * Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
@@ -73,7 +71,7 @@ static PyObject *dsa_setup(PyTypeObject *ty, PyObject *G, PyObject *u,
   g->d.r = GRAND_R(rng);
   g->d.h = GCHASH_CH(hash);
   g->G = G; Py_INCREF(G); g->u = u; Py_INCREF(u); g->p = p; Py_INCREF(p);
-  rng = g->rng; Py_INCREF(rng); g->hash = hash; Py_INCREF(hash);
+  g->rng = rng; Py_INCREF(rng); g->hash = hash; Py_INCREF(hash);
   return ((PyObject *)g);
 end:
   FREEOBJ(g);
@@ -87,7 +85,7 @@ static PyObject *dsapub_pynew(PyTypeObject *ty,
   PyObject *rc = 0;
   char *kwlist[] = { "G", "p", "u", "hash", "rng", 0 };
 
-  if (!PyArg_ParseTupleAndKeywords(arg, kw, "O!O!O!|OO!:new", kwlist,
+  if (!PyArg_ParseTupleAndKeywords(arg, kw, "O!O!|OO!O!:new", kwlist,
                                   group_pytype, &G,
                                   ge_pytype, &p,
                                   &u,
@@ -122,7 +120,7 @@ static PyObject *dsameth_sign(PyObject *me, PyObject *arg, PyObject *kw)
 {
   gdsa_sig s = GDSA_SIG_INIT;
   char *p;
-  int n;
+  Py_ssize_t n;
   mp *k = 0;
   PyObject *rc = 0;
   char *kwlist[] = { "msg", "k", 0 };
@@ -142,7 +140,7 @@ end:
 static PyObject *dsameth_verify(PyObject *me, PyObject *arg)
 {
   char *p;
-  int n;
+  Py_ssize_t n;
   gdsa_sig s = GDSA_SIG_INIT;
   PyObject *rc = 0;
 
@@ -151,7 +149,7 @@ static PyObject *dsameth_verify(PyObject *me, PyObject *arg)
     goto end;
   if (n != DSA_D(me)->h->hashsz)
     VALERR("bad message length (doesn't match hash size)");
-  rc = getbool(gdsa_verify(DSA_D(me), &s, p));
+  rc = getbool(!gdsa_verify(DSA_D(me), &s, p));
 end:
   mp_drop(s.r);
   mp_drop(s.s);
@@ -165,13 +163,13 @@ static PyObject *dsapriv_pynew(PyTypeObject *ty,
   PyObject *rc = 0;
   char *kwlist[] = { "G", "p", "u", "hash", "rng", 0 };
 
-  if (!PyArg_ParseTupleAndKeywords(arg, kw, "O!O!|O!OO!:new", kwlist,
+  if (!PyArg_ParseTupleAndKeywords(arg, kw, "O!O!O|O!O!:new", kwlist,
                                   group_pytype, &G,
                                   ge_pytype, &p,
                                   &u,
                                   gchash_pytype, &hash,
                                   grand_pytype, &rng) ||
-      (rc = dsa_setup(dsapriv_pytype, G, p, u, rng, hash)) == 0)
+      (rc = dsa_setup(dsapriv_pytype, G, u, p, rng, hash)) == 0)
     goto end;
 end:
   return (rc);
@@ -198,7 +196,7 @@ static PyMemberDef dsapub_pymembers[] = {
   MEMBER(G,    T_OBJECT, READONLY, "D.G -> group to work in")
   MEMBER(p,    T_OBJECT, READONLY, "D.p -> public key (group element")
   MEMBER(rng,  T_OBJECT, READONLY, "D.rng -> random number generator")
-  MEMBER(hash,         T_OBJECT, READONLY, "D.hash -> hash class")
+  MEMBER(hash, T_OBJECT, READONLY, "D.hash -> hash class")
 #undef MEMBERSTRUCT
   { 0 }
 };
@@ -212,7 +210,7 @@ static PyMemberDef dsapriv_pymembers[] = {
 
 static PyTypeObject dsapub_pytype_skel = {
   PyObject_HEAD_INIT(0) 0,             /* Header */
-  "catacomb.DSAPub",                   /* @tp_name@ */
+  "DSAPub",                            /* @tp_name@ */
   sizeof(dsa_pyobj),                   /* @tp_basicsize@ */
   0,                                   /* @tp_itemsize@ */
 
@@ -242,7 +240,7 @@ static PyTypeObject dsapub_pytype_skel = {
   0,                                   /* @tp_richcompare@ */
   0,                                   /* @tp_weaklistoffset@ */
   0,                                   /* @tp_iter@ */
-  0,                                   /* @tp_iternexr@ */
+  0,                                   /* @tp_iternext@ */
   dsapub_pymethods,                    /* @tp_methods@ */
   dsapub_pymembers,                    /* @tp_members@ */
   0,                                   /* @tp_getset@ */
@@ -260,7 +258,7 @@ static PyTypeObject dsapub_pytype_skel = {
 
 static PyTypeObject dsapriv_pytype_skel = {
   PyObject_HEAD_INIT(0) 0,             /* Header */
-  "catacomb.DSAPriv",                  /* @tp_name@ */
+  "DSAPriv",                           /* @tp_name@ */
   sizeof(dsa_pyobj),                   /* @tp_basicsize@ */
   0,                                   /* @tp_itemsize@ */
 
@@ -290,7 +288,7 @@ static PyTypeObject dsapriv_pytype_skel = {
   0,                                   /* @tp_richcompare@ */
   0,                                   /* @tp_weaklistoffset@ */
   0,                                   /* @tp_iter@ */
-  0,                                   /* @tp_iternexr@ */
+  0,                                   /* @tp_iternext@ */
   dsapriv_pymethods,                   /* @tp_methods@ */
   dsapriv_pymembers,                   /* @tp_members@ */
   0,                                   /* @tp_getset@ */
@@ -313,13 +311,13 @@ static PyObject *kcdsapub_pynew(PyTypeObject *ty,
   PyObject *rc = 0;
   char *kwlist[] = { "G", "p", "u", "hash", "rng", 0 };
 
-  if (!PyArg_ParseTupleAndKeywords(arg, kw, "O!O!O!|OO!:new", kwlist,
+  if (!PyArg_ParseTupleAndKeywords(arg, kw, "O!O!O|O!O!:new", kwlist,
                                   group_pytype, &G,
                                   ge_pytype, &p,
                                   &u,
                                   gchash_pytype, &hash,
                                   grand_pytype, &rng) ||
-      (rc = dsa_setup(kcdsapub_pytype, G, p, u, rng, hash)) == 0)
+      (rc = dsa_setup(kcdsapub_pytype, G, u, p, rng, hash)) == 0)
     goto end;
 end:
   return (rc);
@@ -332,13 +330,13 @@ static PyObject *kcdsapriv_pynew(PyTypeObject *ty,
   PyObject *rc = 0;
   char *kwlist[] = { "G", "p", "u", "hash", "rng", 0 };
 
-  if (!PyArg_ParseTupleAndKeywords(arg, kw, "O!O!|O!OO!:new", kwlist,
+  if (!PyArg_ParseTupleAndKeywords(arg, kw, "O!O!|OO!O!:new", kwlist,
                                   group_pytype, &G,
                                   ge_pytype, &p,
                                   &u,
                                   gchash_pytype, &hash,
                                   grand_pytype, &rng) ||
-      (rc = dsa_setup(kcdsapriv_pytype, G, p, u, rng, hash)) == 0)
+      (rc = dsa_setup(kcdsapriv_pytype, G, u, p, rng, hash)) == 0)
     goto end;
 end:
   return (rc);
@@ -367,7 +365,7 @@ static PyObject *kcdsameth_sign(PyObject *me, PyObject *arg, PyObject *kw)
 {
   gkcdsa_sig s = GKCDSA_SIG_INIT;
   char *p;
-  int n;
+  Py_ssize_t n;
   mp *k = 0;
   PyObject *r = 0, *rc = 0;
   char *kwlist[] = { "msg", "k", 0 };
@@ -378,9 +376,9 @@ static PyObject *kcdsameth_sign(PyObject *me, PyObject *arg, PyObject *kw)
   if (n != DSA_D(me)->h->hashsz)
     VALERR("bad message length (doesn't match hash size)");
   r = bytestring_pywrap(0, DSA_D(me)->h->hashsz);
-  s.r = PyString_AS_STRING(r);
+  s.r = (octet *)PyString_AS_STRING(r);
   gkcdsa_sign(DSA_D(me), &s, p, k);
-  rc = Py_BuildValue("(NN)", r, mp_pywrap(s.s));
+  rc = Py_BuildValue("(ON)", r, mp_pywrap(s.s));
 end:
   Py_XDECREF(r);
   mp_drop(k);
@@ -390,7 +388,7 @@ end:
 static PyObject *kcdsameth_verify(PyObject *me, PyObject *arg)
 {
   char *p;
-  int n, rn;
+  Py_ssize_t n, rn;
   gkcdsa_sig s = GKCDSA_SIG_INIT;
   PyObject *rc = 0;
 
@@ -401,7 +399,7 @@ static PyObject *kcdsameth_verify(PyObject *me, PyObject *arg)
     VALERR("bad message length (doesn't match hash size)");
   if (rn != DSA_D(me)->h->hashsz)
     VALERR("bad signature `r' length (doesn't match hash size)");
-  rc = getbool(gkcdsa_verify(DSA_D(me), &s, p));
+  rc = getbool(!gkcdsa_verify(DSA_D(me), &s, p));
 end:
   mp_drop(s.s);
   return (rc);
@@ -425,7 +423,7 @@ static PyMethodDef kcdsapriv_pymethods[] = {
 
 static PyTypeObject kcdsapub_pytype_skel = {
   PyObject_HEAD_INIT(0) 0,             /* Header */
-  "catacomb.KCDSAPub",                 /* @tp_name@ */
+  "KCDSAPub",                          /* @tp_name@ */
   sizeof(dsa_pyobj),                   /* @tp_basicsize@ */
   0,                                   /* @tp_itemsize@ */
 
@@ -455,7 +453,7 @@ static PyTypeObject kcdsapub_pytype_skel = {
   0,                                   /* @tp_richcompare@ */
   0,                                   /* @tp_weaklistoffset@ */
   0,                                   /* @tp_iter@ */
-  0,                                   /* @tp_iternexr@ */
+  0,                                   /* @tp_iternext@ */
   kcdsapub_pymethods,                  /* @tp_methods@ */
   dsapub_pymembers,                    /* @tp_members@ */
   0,                                   /* @tp_getset@ */
@@ -473,7 +471,7 @@ static PyTypeObject kcdsapub_pytype_skel = {
 
 static PyTypeObject kcdsapriv_pytype_skel = {
   PyObject_HEAD_INIT(0) 0,             /* Header */
-  "catacomb.KCDSAPriv",                        /* @tp_name@ */
+  "KCDSAPriv",                         /* @tp_name@ */
   sizeof(dsa_pyobj),                   /* @tp_basicsize@ */
   0,                                   /* @tp_itemsize@ */
 
@@ -503,7 +501,7 @@ static PyTypeObject kcdsapriv_pytype_skel = {
   0,                                   /* @tp_richcompare@ */
   0,                                   /* @tp_weaklistoffset@ */
   0,                                   /* @tp_iter@ */
-  0,                                   /* @tp_iternexr@ */
+  0,                                   /* @tp_iternext@ */
   kcdsapriv_pymethods,                 /* @tp_methods@ */
   dsapriv_pymembers,                   /* @tp_members@ */
   0,                                   /* @tp_getset@ */
@@ -555,6 +553,7 @@ static PyObject *rsapub_pynew(PyTypeObject *ty,
   if (!PyArg_ParseTupleAndKeywords(arg, kw, "O&O&:new", kwlist,
                                   convmp, &rp.n, convmp, &rp.e))
     goto end;
+  if (!MP_ODDP(rp.n)) VALERR("RSA modulus must be even");
   o = (rsapub_pyobj *)ty->tp_alloc(ty, 0);
   o->pub = rp;
   rsa_pubcreate(&o->pubctx, &o->pub);
@@ -627,6 +626,10 @@ static PyObject *rsapriv_pynew(PyTypeObject *ty,
                                   convmp, &rp.q_inv,
                                   &rng))
     goto end;
+  if ((rp.n && !MP_ODDP(rp.n)) ||
+      (rp.p && !MP_ODDP(rp.p)) ||
+      (rp.p && !MP_ODDP(rp.q)))
+    VALERR("RSA modulus and factors must be odd");
   if (rsa_recover(&rp)) VALERR("couldn't construct private key");
   if (rng != Py_None && !GRAND_PYCHECK(rng))
     TYERR("not a random number source");
@@ -670,7 +673,9 @@ static PyObject *rsaget_rng(PyObject *me, void *hunoz)
 static int rsaset_rng(PyObject *me, PyObject *val, void *hunoz)
 {
   int rc = -1;
-  if (val != Py_None && !GRAND_PYCHECK(val))
+  if (!val)
+    val = Py_None;
+  else if (val != Py_None && !GRAND_PYCHECK(val))
     TYERR("expected grand or None");
   Py_DECREF(RSA_RNG(me));
   RSA_RNG(me) = val;
@@ -759,7 +764,7 @@ static PyMethodDef rsapriv_pymethods[] = {
 
 static PyTypeObject rsapub_pytype_skel = {
   PyObject_HEAD_INIT(0) 0,             /* Header */
-  "catacomb.RSAPub",                   /* @tp_name@ */
+  "RSAPub",                            /* @tp_name@ */
   sizeof(rsapub_pyobj),                        /* @tp_basicsize@ */
   0,                                   /* @tp_itemsize@ */
 
@@ -789,7 +794,7 @@ static PyTypeObject rsapub_pytype_skel = {
   0,                                   /* @tp_richcompare@ */
   0,                                   /* @tp_weaklistoffset@ */
   0,                                   /* @tp_iter@ */
-  0,                                   /* @tp_iternexr@ */
+  0,                                   /* @tp_iternext@ */
   rsapub_pymethods,                    /* @tp_methods@ */
   0,                                   /* @tp_members@ */
   rsapub_pygetset,                     /* @tp_getset@ */
@@ -807,7 +812,7 @@ static PyTypeObject rsapub_pytype_skel = {
 
 static PyTypeObject rsapriv_pytype_skel = {
   PyObject_HEAD_INIT(0) 0,             /* Header */
-  "catacomb.RSAPriv",                  /* @tp_name@ */
+  "RSAPriv",                           /* @tp_name@ */
   sizeof(rsapriv_pyobj),               /* @tp_basicsize@ */
   0,                                   /* @tp_itemsize@ */
 
@@ -837,7 +842,7 @@ static PyTypeObject rsapriv_pytype_skel = {
   0,                                   /* @tp_richcompare@ */
   0,                                   /* @tp_weaklistoffset@ */
   0,                                   /* @tp_iter@ */
-  0,                                   /* @tp_iternexr@ */
+  0,                                   /* @tp_iternext@ */
   rsapriv_pymethods,                   /* @tp_methods@ */
   0,                                   /* @tp_members@ */
   rsapriv_pygetset,                    /* @tp_getset@ */
@@ -860,7 +865,7 @@ static PyObject *meth__p1crypt_encode(PyObject *me,
 {
   pkcs1 p1;
   char *m, *ep;
-  int msz, epsz;
+  Py_ssize_t msz, epsz;
   unsigned long nbits;
   PyObject *rc = 0;
   octet *b = 0;
@@ -889,7 +894,7 @@ static PyObject *meth__p1crypt_decode(PyObject *me,
 {
   pkcs1 p1;
   char *ep;
-  int epsz;
+  Py_ssize_t epsz;
   unsigned long nbits;
   int n;
   PyObject *rc = 0;
@@ -921,7 +926,7 @@ static PyObject *meth__p1sig_encode(PyObject *me,
 {
   pkcs1 p1;
   char *m, *ep;
-  int msz, epsz;
+  Py_ssize_t msz, epsz;
   unsigned long nbits;
   PyObject *rc = 0;
   octet *b = 0;
@@ -950,7 +955,7 @@ static PyObject *meth__p1sig_decode(PyObject *me,
 {
   pkcs1 p1;
   char *ep;
-  int epsz;
+  Py_ssize_t epsz;
   unsigned long nbits;
   int n;
   PyObject *hukairz;
@@ -983,7 +988,7 @@ static PyObject *meth__oaep_encode(PyObject *me,
 {
   oaep o;
   char *m, *ep;
-  int msz, epsz;
+  Py_ssize_t msz, epsz;
   unsigned long nbits;
   PyObject *rc = 0;
   octet *b = 0;
@@ -1015,7 +1020,7 @@ static PyObject *meth__oaep_decode(PyObject *me,
 {
   oaep o;
   char *ep;
-  int epsz;
+  Py_ssize_t epsz;
   unsigned long nbits;
   int n;
   PyObject *rc = 0;
@@ -1050,7 +1055,7 @@ static PyObject *meth__pss_encode(PyObject *me,
 {
   pss p;
   char *m;
-  int msz;
+  Py_ssize_t msz;
   unsigned long nbits;
   PyObject *rc = 0;
   octet *b = 0;
@@ -1082,7 +1087,7 @@ static PyObject *meth__pss_decode(PyObject *me,
 {
   pss p;
   char *m;
-  int msz;
+  Py_ssize_t msz;
   unsigned long nbits;
   PyObject *rc = 0;
   octet *b = 0;