#endif
#if OPENSSL_VERSION_NUMBER >= 0x10100000L
# define EXIM_HAVE_OCSP_RESP_COUNT
+# define EXIM_HAVE_OPENSSL_DH_BITS
#else
# define EXIM_HAVE_EPHEM_RSA_KEX
# define EXIM_HAVE_RAND_PSEUDO
static int
setup_certs(SSL_CTX *sctx, uschar *certs, uschar *crl, host_item *host, BOOL optional,
- int (*cert_vfy_cb)(int, X509_STORE_CTX *) );
+ int (*cert_vfy_cb)(int, X509_STORE_CTX *), uschar ** errstr );
/* Callbacks */
#ifdef EXIM_HAVE_OPENSSL_TLSEXT
host NULL if setting up a server;
the connected host if setting up a client
msg error message or NULL if we should ask OpenSSL
+ errstr pointer to output error message
Returns: OK/DEFER/FAIL
*/
static int
-tls_error(uschar * prefix, const host_item * host, uschar * msg)
+tls_error(uschar * prefix, const host_item * host, uschar * msg, uschar ** errstr)
{
if (!msg)
{
ERR_error_string(ERR_get_error(), ssl_errstring);
- msg = (uschar *)ssl_errstring;
+ msg = US ssl_errstring;
}
-if (host)
- {
- log_write(0, LOG_MAIN, "H=%s [%s] TLS error on connection (%s): %s",
- host->name, host->address, prefix, msg);
- return FAIL;
- }
-else
- {
- uschar *conn_info = smtp_get_connection_info();
- if (Ustrncmp(conn_info, US"SMTP ", 5) == 0)
- conn_info += 5;
- /* I'd like to get separated H= here, but too hard for now */
- log_write(0, LOG_MAIN, "TLS error on %s (%s): %s",
- conn_info, prefix, msg);
- return DEFER;
- }
+if (errstr) *errstr = string_sprintf("(%s): %s", prefix, msg);
+return host ? FAIL : DEFER;
}
if (preverify_ok == 0)
{
- log_write(0, LOG_MAIN, "[%s] SSL verify error: depth=%d error=%s cert=%s",
- tlsp == &tls_out ? deliver_host_address : sender_host_address,
- depth,
- X509_verify_cert_error_string(X509_STORE_CTX_get_error(x509ctx)),
- dn);
+ uschar * extra = verify_mode ? string_sprintf(" (during %c-verify for [%s])",
+ *verify_mode, sender_host_address)
+ : US"";
+ log_write(0, LOG_MAIN, "[%s] SSL verify error%s: depth=%d error=%s cert=%s",
+ tlsp == &tls_out ? deliver_host_address : sender_host_address,
+ extra, depth,
+ X509_verify_cert_error_string(X509_STORE_CTX_get_error(x509ctx)), dn);
*calledp = TRUE;
if (!*optionalp)
{
if (rc < 0)
{
log_write(0, LOG_MAIN, "[%s] SSL verify error: internal error",
- deliver_host_address);
+ tlsp == &tls_out ? deliver_host_address : sender_host_address);
name = NULL;
}
break;
if (!tls_is_name_for_cert(verify_cert_hostnames, cert))
#endif
{
+ uschar * extra = verify_mode
+ ? string_sprintf(" (during %c-verify for [%s])",
+ *verify_mode, sender_host_address)
+ : US"";
log_write(0, LOG_MAIN,
- "[%s] SSL verify error: certificate name mismatch: "
- "DN=\"%s\" H=\"%s\"",
- deliver_host_address, dn, verify_cert_hostnames);
+ "[%s] SSL verify error%s: certificate name mismatch: DN=\"%s\" H=\"%s\"",
+ tlsp == &tls_out ? deliver_host_address : sender_host_address,
+ extra, dn, verify_cert_hostnames);
*calledp = TRUE;
if (!*optionalp)
{
sctx The current SSL CTX (inbound or outbound)
dhparam DH parameter file or fixed parameter identity string
host connected host, if client; NULL if server
+ errstr error string pointer
Returns: TRUE if OK (nothing to set up, or setup worked)
*/
static BOOL
-init_dh(SSL_CTX *sctx, uschar *dhparam, const host_item *host)
+init_dh(SSL_CTX *sctx, uschar *dhparam, const host_item *host, uschar ** errstr)
{
BIO *bio;
DH *dh;
uschar *dhexpanded;
const char *pem;
+int dh_bitsize;
-if (!expand_check(dhparam, US"tls_dhparam", &dhexpanded))
+if (!expand_check(dhparam, US"tls_dhparam", &dhexpanded, errstr))
return FALSE;
if (!dhexpanded || !*dhexpanded)
if (!(bio = BIO_new_file(CS dhexpanded, "r")))
{
tls_error(string_sprintf("could not read dhparams file %s", dhexpanded),
- host, US strerror(errno));
+ host, US strerror(errno), errstr);
return FALSE;
}
}
if (!(pem = std_dh_prime_named(dhexpanded)))
{
tls_error(string_sprintf("Unknown standard DH prime \"%s\"", dhexpanded),
- host, US strerror(errno));
+ host, US strerror(errno), errstr);
return FALSE;
}
bio = BIO_new_mem_buf(CS pem, -1);
{
BIO_free(bio);
tls_error(string_sprintf("Could not read tls_dhparams \"%s\"", dhexpanded),
- host, NULL);
+ host, NULL, errstr);
return FALSE;
}
+/* note: our default limit of 2236 is not a multiple of 8; the limit comes from
+ * an NSS limit, and the GnuTLS APIs handle bit-sizes fine, so we went with
+ * 2236. But older OpenSSL can only report in bytes (octets), not bits.
+ * If someone wants to dance at the edge, then they can raise the limit or use
+ * current libraries. */
+#ifdef EXIM_HAVE_OPENSSL_DH_BITS
+/* Added in commit 26c79d5641d; `git describe --contains` says OpenSSL_1_1_0-pre1~1022
+ * This predates OpenSSL_1_1_0 (before a, b, ...) so is in all 1.1.0 */
+dh_bitsize = DH_bits(dh);
+#else
+dh_bitsize = 8 * DH_size(dh);
+#endif
+
/* Even if it is larger, we silently return success rather than cause things
* to fail out, so that a too-large DH will not knock out all TLS; it's a
* debatable choice. */
-if ((8*DH_size(dh)) > tls_dh_max_bits)
+if (dh_bitsize > tls_dh_max_bits)
{
DEBUG(D_tls)
- debug_printf("dhparams file %d bits, is > tls_dh_max_bits limit of %d",
- 8*DH_size(dh), tls_dh_max_bits);
+ debug_printf("dhparams file %d bits, is > tls_dh_max_bits limit of %d\n",
+ dh_bitsize, tls_dh_max_bits);
}
else
{
SSL_CTX_set_tmp_dh(sctx, dh);
DEBUG(D_tls)
debug_printf("Diffie-Hellman initialized from %s with %d-bit prime\n",
- dhexpanded ? dhexpanded : US"default", 8*DH_size(dh));
+ dhexpanded ? dhexpanded : US"default", dh_bitsize);
}
DH_free(dh);
Arguments:
sctx The current SSL CTX (inbound or outbound)
host connected host, if client; NULL if server
+ errstr error string pointer
Returns: TRUE if OK (nothing to set up, or setup worked)
*/
static BOOL
-init_ecdh(SSL_CTX * sctx, host_item * host)
+init_ecdh(SSL_CTX * sctx, host_item * host, uschar ** errstr)
{
#ifdef OPENSSL_NO_ECDH
return TRUE;
return TRUE;
# else
-if (!expand_check(tls_eccurve, US"tls_eccurve", &exp_curve))
+if (!expand_check(tls_eccurve, US"tls_eccurve", &exp_curve, errstr))
return FALSE;
if (!exp_curve || !*exp_curve)
return TRUE;
#if OPENSSL_VERSION_NUMBER < 0x10002000L
DEBUG(D_tls) debug_printf(
"ECDH OpenSSL < 1.0.2: temp key parameter settings: overriding \"auto\" with \"prime256v1\"\n");
- exp_curve = "prime256v1";
+ exp_curve = US"prime256v1";
#else
# if defined SSL_CTRL_SET_ECDH_AUTO
DEBUG(D_tls) debug_printf(
# endif
)
{
- tls_error(string_sprintf("Unknown curve name tls_eccurve '%s'",
- exp_curve),
- host, NULL);
+ tls_error(string_sprintf("Unknown curve name tls_eccurve '%s'", exp_curve),
+ host, NULL, errstr);
return FALSE;
}
if (!(ecdh = EC_KEY_new_by_curve_name(nid)))
{
- tls_error(US"Unable to create ec curve", host, NULL);
+ tls_error(US"Unable to create ec curve", host, NULL, errstr);
return FALSE;
}
not to the stability of the interface. */
if ((rv = SSL_CTX_set_tmp_ecdh(sctx, ecdh) == 0))
- tls_error(string_sprintf("Error enabling '%s' curve", exp_curve), host, NULL);
+ tls_error(string_sprintf("Error enabling '%s' curve", exp_curve), host, NULL, errstr);
else
DEBUG(D_tls) debug_printf("ECDH: enabled '%s' curve\n", exp_curve);
/* Create and install a selfsigned certificate, for use in server mode */
static int
-tls_install_selfsign(SSL_CTX * sctx)
+tls_install_selfsign(SSL_CTX * sctx, uschar ** errstr)
{
X509 * x509 = NULL;
EVP_PKEY * pkey;
return OK;
err:
- (void) tls_error(where, NULL, NULL);
+ (void) tls_error(where, NULL, NULL, errstr);
if (x509) X509_free(x509);
if (pkey) EVP_PKEY_free(pkey);
return DEFER;
Arguments:
sctx the SSL_CTX* to update
cbinfo various parts of session state
+ errstr error string pointer
Returns: OK/DEFER/FAIL
*/
static int
-tls_expand_session_files(SSL_CTX *sctx, tls_ext_ctx_cb *cbinfo)
+tls_expand_session_files(SSL_CTX *sctx, tls_ext_ctx_cb *cbinfo,
+ uschar ** errstr)
{
uschar *expanded;
if (cbinfo->host) /* client */
return OK;
/* server */
- if (tls_install_selfsign(sctx) != OK)
+ if (tls_install_selfsign(sctx, errstr) != OK)
return DEFER;
}
else
)
reexpand_tls_files_for_sni = TRUE;
- if (!expand_check(cbinfo->certificate, US"tls_certificate", &expanded))
+ if (!expand_check(cbinfo->certificate, US"tls_certificate", &expanded, errstr))
return DEFER;
if (expanded != NULL)
if (!SSL_CTX_use_certificate_chain_file(sctx, CS expanded))
return tls_error(string_sprintf(
"SSL_CTX_use_certificate_chain_file file=%s", expanded),
- cbinfo->host, NULL);
+ cbinfo->host, NULL, errstr);
}
if (cbinfo->privatekey != NULL &&
- !expand_check(cbinfo->privatekey, US"tls_privatekey", &expanded))
+ !expand_check(cbinfo->privatekey, US"tls_privatekey", &expanded, errstr))
return DEFER;
/* If expansion was forced to fail, key_expanded will be NULL. If the result
DEBUG(D_tls) debug_printf("tls_privatekey file %s\n", expanded);
if (!SSL_CTX_use_PrivateKey_file(sctx, CS expanded, SSL_FILETYPE_PEM))
return tls_error(string_sprintf(
- "SSL_CTX_use_PrivateKey_file file=%s", expanded), cbinfo->host, NULL);
+ "SSL_CTX_use_PrivateKey_file file=%s", expanded), cbinfo->host, NULL, errstr);
}
}
#ifndef DISABLE_OCSP
if (cbinfo->is_server && cbinfo->u_ocsp.server.file)
{
- if (!expand_check(cbinfo->u_ocsp.server.file, US"tls_ocsp_file", &expanded))
+ if (!expand_check(cbinfo->u_ocsp.server.file, US"tls_ocsp_file", &expanded, errstr))
return DEFER;
if (expanded && *expanded)
tls_ext_ctx_cb *cbinfo = (tls_ext_ctx_cb *) arg;
int rc;
int old_pool = store_pool;
+uschar * dummy_errstr;
if (!servername)
return SSL_TLSEXT_ERR_OK;
SSL_CTX_set_tlsext_servername_callback(server_sni, tls_servername_cb);
SSL_CTX_set_tlsext_servername_arg(server_sni, cbinfo);
-if ( !init_dh(server_sni, cbinfo->dhparam, NULL)
- || !init_ecdh(server_sni, NULL)
+if ( !init_dh(server_sni, cbinfo->dhparam, NULL, &dummy_errstr)
+ || !init_ecdh(server_sni, NULL, &dummy_errstr)
)
return SSL_TLSEXT_ERR_NOACK;
#endif
if ((rc = setup_certs(server_sni, tls_verify_certificates, tls_crl, NULL, FALSE,
- verify_callback_server)) != OK)
+ verify_callback_server, &dummy_errstr)) != OK)
return SSL_TLSEXT_ERR_NOACK;
/* do this after setup_certs, because this can require the certs for verifying
OCSP information. */
-if ((rc = tls_expand_session_files(server_sni, cbinfo)) != OK)
+if ((rc = tls_expand_session_files(server_sni, cbinfo, &dummy_errstr)) != OK)
return SSL_TLSEXT_ERR_NOACK;
DEBUG(D_tls) debug_printf("Switching SSL context.\n");
ocsp_file file of stapling info (server); flag for require ocsp (client)
addr address if client; NULL if server (for some randomness)
cbp place to put allocated callback context
+ errstr error string pointer
Returns: OK/DEFER/FAIL
*/
#ifndef DISABLE_OCSP
uschar *ocsp_file,
#endif
- address_item *addr, tls_ext_ctx_cb ** cbp)
+ address_item *addr, tls_ext_ctx_cb ** cbp, uschar ** errstr)
{
+SSL_CTX * ctx;
long init_options;
int rc;
-BOOL okay;
tls_ext_ctx_cb * cbinfo;
cbinfo = store_malloc(sizeof(tls_ext_ctx_cb));
By disabling with openssl_options, we can let admins re-enable with the
existing knob. */
-*ctxp = SSL_CTX_new(host ? SSLv23_client_method() : SSLv23_server_method());
-
-if (!*ctxp) return tls_error(US"SSL_CTX_new", host, NULL);
+if (!(ctx = SSL_CTX_new(host ? SSLv23_client_method() : SSLv23_server_method())))
+ return tls_error(US"SSL_CTX_new", host, NULL, errstr);
/* It turns out that we need to seed the random number generator this early in
order to get the full complement of ciphers to work. It took me roughly a day
if (!RAND_status())
return tls_error(US"RAND_status", host,
- US"unable to seed random number generator");
+ US"unable to seed random number generator", errstr);
}
/* Set up the information callback, which outputs if debugging is at a suitable
level. */
-DEBUG(D_tls) SSL_CTX_set_info_callback(*ctxp, (void (*)())info_callback);
+DEBUG(D_tls) SSL_CTX_set_info_callback(ctx, (void (*)())info_callback);
/* Automatically re-try reads/writes after renegotiation. */
-(void) SSL_CTX_set_mode(*ctxp, SSL_MODE_AUTO_RETRY);
+(void) SSL_CTX_set_mode(ctx, SSL_MODE_AUTO_RETRY);
/* Apply administrator-supplied work-arounds.
Historically we applied just one requested option,
No OpenSSL version number checks: the options we accept depend upon the
availability of the option value macros from OpenSSL. */
-okay = tls_openssl_options_parse(openssl_options, &init_options);
-if (!okay)
- return tls_error(US"openssl_options parsing failed", host, NULL);
+if (!tls_openssl_options_parse(openssl_options, &init_options))
+ return tls_error(US"openssl_options parsing failed", host, NULL, errstr);
if (init_options)
{
DEBUG(D_tls) debug_printf("setting SSL CTX options: %#lx\n", init_options);
- if (!(SSL_CTX_set_options(*ctxp, init_options)))
+ if (!(SSL_CTX_set_options(ctx, init_options)))
return tls_error(string_sprintf(
- "SSL_CTX_set_option(%#lx)", init_options), host, NULL);
+ "SSL_CTX_set_option(%#lx)", init_options), host, NULL, errstr);
}
else
DEBUG(D_tls) debug_printf("no SSL CTX options to set\n");
+/* Disable session cache unconditionally */
+
+(void) SSL_CTX_set_session_cache_mode(ctx, SSL_SESS_CACHE_OFF);
+
/* Initialize with DH parameters if supplied */
/* Initialize ECDH temp key parameter selection */
-if ( !init_dh(*ctxp, dhparam, host)
- || !init_ecdh(*ctxp, host)
+if ( !init_dh(ctx, dhparam, host, errstr)
+ || !init_ecdh(ctx, host, errstr)
)
return DEFER;
/* Set up certificate and key (and perhaps OCSP info) */
-if ((rc = tls_expand_session_files(*ctxp, cbinfo)) != OK)
+if ((rc = tls_expand_session_files(ctx, cbinfo, errstr)) != OK)
return rc;
/* If we need to handle SNI or OCSP, do so */
callback is invoked. */
if (cbinfo->u_ocsp.server.file)
{
- SSL_CTX_set_tlsext_status_cb(server_ctx, tls_server_stapling_cb);
- SSL_CTX_set_tlsext_status_arg(server_ctx, cbinfo);
+ SSL_CTX_set_tlsext_status_cb(ctx, tls_server_stapling_cb);
+ SSL_CTX_set_tlsext_status_arg(ctx, cbinfo);
}
# endif
/* We always do this, so that $tls_sni is available even if not used in
tls_certificate */
- SSL_CTX_set_tlsext_servername_callback(*ctxp, tls_servername_cb);
- SSL_CTX_set_tlsext_servername_arg(*ctxp, cbinfo);
+ SSL_CTX_set_tlsext_servername_callback(ctx, tls_servername_cb);
+ SSL_CTX_set_tlsext_servername_arg(ctx, cbinfo);
}
# ifndef DISABLE_OCSP
else /* client */
DEBUG(D_tls) debug_printf("failed to create store for stapling verify\n");
return FAIL;
}
- SSL_CTX_set_tlsext_status_cb(*ctxp, tls_client_stapling_cb);
- SSL_CTX_set_tlsext_status_arg(*ctxp, cbinfo);
+ SSL_CTX_set_tlsext_status_cb(ctx, tls_client_stapling_cb);
+ SSL_CTX_set_tlsext_status_arg(ctx, cbinfo);
}
# endif
#endif
#ifdef EXIM_HAVE_EPHEM_RSA_KEX
/* Set up the RSA callback */
-SSL_CTX_set_tmp_rsa_callback(*ctxp, rsa_callback);
+SSL_CTX_set_tmp_rsa_callback(ctx, rsa_callback);
#endif
/* Finally, set the timeout, and we are done */
-SSL_CTX_set_timeout(*ctxp, ssl_session_timeout);
+SSL_CTX_set_timeout(ctx, ssl_session_timeout);
DEBUG(D_tls) debug_printf("Initialized TLS\n");
*cbp = cbinfo;
+*ctxp = ctx;
return OK;
}
optional TRUE if called from a server for a host in tls_try_verify_hosts;
otherwise passed as FALSE
cert_vfy_cb Callback function for certificate verification
+ errstr error string pointer
Returns: OK/DEFER/FAIL
*/
static int
setup_certs(SSL_CTX *sctx, uschar *certs, uschar *crl, host_item *host, BOOL optional,
- int (*cert_vfy_cb)(int, X509_STORE_CTX *) )
+ int (*cert_vfy_cb)(int, X509_STORE_CTX *), uschar ** errstr)
{
uschar *expcerts, *expcrl;
-if (!expand_check(certs, US"tls_verify_certificates", &expcerts))
+if (!expand_check(certs, US"tls_verify_certificates", &expcerts, errstr))
return DEFER;
+DEBUG(D_tls) debug_printf("tls_verify_certificates: %s\n", expcerts);
if (expcerts && *expcerts)
{
CA bundle. Then add the ones specified in the config, if any. */
if (!SSL_CTX_set_default_verify_paths(sctx))
- return tls_error(US"SSL_CTX_set_default_verify_paths", host, NULL);
+ return tls_error(US"SSL_CTX_set_default_verify_paths", host, NULL, errstr);
if (Ustrcmp(expcerts, "system") != 0)
{
if ( (!file || statbuf.st_size > 0)
&& !SSL_CTX_load_verify_locations(sctx, CS file, CS dir))
- return tls_error(US"SSL_CTX_load_verify_locations", host, NULL);
+ return tls_error(US"SSL_CTX_load_verify_locations", host, NULL, errstr);
/* Load the list of CAs for which we will accept certs, for sending
to the client. This is only for the one-file tls_verify_certificates
OpenSSL will then handle the verify against CA certs and CRLs by
itself in the verify callback." */
- if (!expand_check(crl, US"tls_crl", &expcrl)) return DEFER;
+ if (!expand_check(crl, US"tls_crl", &expcrl, errstr)) return DEFER;
if (expcrl && *expcrl)
{
struct stat statbufcrl;
DEBUG(D_tls) debug_printf("SSL CRL value is a file %s\n", file);
}
if (X509_STORE_load_locations(cvstore, CS file, CS dir) == 0)
- return tls_error(US"X509_STORE_load_locations", host, NULL);
+ return tls_error(US"X509_STORE_load_locations", host, NULL, errstr);
/* setting the flags to check against the complete crl chain */
Arguments:
require_ciphers allowed ciphers
+ errstr pointer to error message
Returns: OK on success
DEFER for errors before the start of the negotiation
*/
int
-tls_server_start(const uschar *require_ciphers)
+tls_server_start(const uschar * require_ciphers, uschar ** errstr)
{
int rc;
-uschar *expciphers;
-tls_ext_ctx_cb *cbinfo;
+uschar * expciphers;
+tls_ext_ctx_cb * cbinfo;
static uschar peerdn[256];
static uschar cipherbuf[256];
if (tls_in.active >= 0)
{
- tls_error(US"STARTTLS received after TLS started", NULL, US"");
- smtp_printf("554 Already in TLS\r\n");
+ tls_error(US"STARTTLS received after TLS started", NULL, US"", errstr);
+ smtp_printf("554 Already in TLS\r\n", FALSE);
return FAIL;
}
#ifndef DISABLE_OCSP
tls_ocsp_file,
#endif
- NULL, &server_static_cbinfo);
+ NULL, &server_static_cbinfo, errstr);
if (rc != OK) return rc;
cbinfo = server_static_cbinfo;
-if (!expand_check(require_ciphers, US"tls_require_ciphers", &expciphers))
+if (!expand_check(require_ciphers, US"tls_require_ciphers", &expciphers, errstr))
return FAIL;
/* In OpenSSL, cipher components are separated by hyphens. In GnuTLS, they
while (*s != 0) { if (*s == '_') *s = '-'; s++; }
DEBUG(D_tls) debug_printf("required ciphers: %s\n", expciphers);
if (!SSL_CTX_set_cipher_list(server_ctx, CS expciphers))
- return tls_error(US"SSL_CTX_set_cipher_list", NULL, NULL);
+ return tls_error(US"SSL_CTX_set_cipher_list", NULL, NULL, errstr);
cbinfo->server_cipher_list = expciphers;
}
if (verify_check_host(&tls_verify_hosts) == OK)
{
rc = setup_certs(server_ctx, tls_verify_certificates, tls_crl, NULL,
- FALSE, verify_callback_server);
+ FALSE, verify_callback_server, errstr);
if (rc != OK) return rc;
server_verify_optional = FALSE;
}
else if (verify_check_host(&tls_try_verify_hosts) == OK)
{
rc = setup_certs(server_ctx, tls_verify_certificates, tls_crl, NULL,
- TRUE, verify_callback_server);
+ TRUE, verify_callback_server, errstr);
if (rc != OK) return rc;
server_verify_optional = TRUE;
}
/* Prepare for new connection */
-if (!(server_ssl = SSL_new(server_ctx))) return tls_error(US"SSL_new", NULL, NULL);
+if (!(server_ssl = SSL_new(server_ctx)))
+ return tls_error(US"SSL_new", NULL, NULL, errstr);
/* Warning: we used to SSL_clear(ssl) here, it was removed.
*
SSL_set_session_id_context(server_ssl, sid_ctx, Ustrlen(sid_ctx));
if (!tls_in.on_connect)
{
- smtp_printf("220 TLS go ahead\r\n");
+ smtp_printf("220 TLS go ahead\r\n", FALSE);
fflush(smtp_out);
}
if (rc <= 0)
{
- tls_error(US"SSL_accept", NULL, sigalrm_seen ? US"timed out" : NULL);
- if (ERR_get_error() == 0)
- log_write(0, LOG_MAIN,
- "TLS client disconnected cleanly (rejected our certificate?)");
+ (void) tls_error(US"SSL_accept", NULL, sigalrm_seen ? US"timed out" : NULL, errstr);
return FAIL;
}
ssl_xfer_eof = ssl_xfer_error = 0;
receive_getc = tls_getc;
+receive_getbuf = tls_getbuf;
receive_get_cache = tls_get_cache;
receive_ungetc = tls_ungetc;
receive_feof = tls_feof;
static int
tls_client_basic_ctx_init(SSL_CTX * ctx,
- host_item * host, smtp_transport_options_block * ob, tls_ext_ctx_cb * cbinfo
- )
+ host_item * host, smtp_transport_options_block * ob, tls_ext_ctx_cb * cbinfo,
+ uschar ** errstr)
{
int rc;
/* stick to the old behaviour for compatibility if tls_verify_certificates is
return OK;
if ((rc = setup_certs(ctx, ob->tls_verify_certificates,
- ob->tls_crl, host, client_verify_optional, verify_callback_client)) != OK)
+ ob->tls_crl, host, client_verify_optional, verify_callback_client,
+ errstr)) != OK)
return rc;
if (verify_check_given_host(&ob->tls_verify_cert_hostnames, host) == OK)
#ifdef EXPERIMENTAL_DANE
static int
-dane_tlsa_load(SSL * ssl, host_item * host, dns_answer * dnsa)
+dane_tlsa_load(SSL * ssl, host_item * host, dns_answer * dnsa, uschar ** errstr)
{
dns_record * rr;
dns_scan dnss;
int found = 0;
if (DANESSL_init(ssl, NULL, hostnames) != 1)
- return tls_error(US"hostnames load", host, NULL);
+ return tls_error(US"hostnames load", host, NULL, errstr);
for (rr = dns_next_rr(dnsa, &dnss, RESET_ANSWERS);
rr;
switch (DANESSL_add_tlsa(ssl, usage, selector, mdname, p, rr->size - 3))
{
default:
- return tls_error(US"tlsa load", host, NULL);
+ return tls_error(US"tlsa load", host, NULL, errstr);
case 0: /* action not taken */
case 1: break;
}
addr the first address
tb transport (always smtp)
tlsa_dnsa tlsa lookup, if DANE, else null
+ errstr error string pointer
Returns: OK on success
FAIL otherwise - note that tls_error() will not give DEFER
int
tls_client_start(int fd, host_item *host, address_item *addr,
- transport_instance *tb
+ transport_instance * tb,
#ifdef EXPERIMENTAL_DANE
- , dns_answer * tlsa_dnsa
+ dns_answer * tlsa_dnsa,
#endif
- )
+ uschar ** errstr)
{
smtp_transport_options_block * ob =
(smtp_transport_options_block *)tb->options_block;
#ifndef DISABLE_OCSP
(void *)(long)request_ocsp,
#endif
- addr, &client_static_cbinfo);
+ addr, &client_static_cbinfo, errstr);
if (rc != OK) return rc;
tls_out.certificate_verified = FALSE;
client_verify_callback_called = FALSE;
if (!expand_check(ob->tls_require_ciphers, US"tls_require_ciphers",
- &expciphers))
+ &expciphers, errstr))
return FAIL;
/* In OpenSSL, cipher components are separated by hyphens. In GnuTLS, they
are separated by underscores. So that I can use either form in my tests, and
also for general convenience, we turn underscores into hyphens here. */
-if (expciphers != NULL)
+if (expciphers)
{
uschar *s = expciphers;
- while (*s != 0) { if (*s == '_') *s = '-'; s++; }
+ while (*s) { if (*s == '_') *s = '-'; s++; }
DEBUG(D_tls) debug_printf("required ciphers: %s\n", expciphers);
if (!SSL_CTX_set_cipher_list(client_ctx, CS expciphers))
- return tls_error(US"SSL_CTX_set_cipher_list", host, NULL);
+ return tls_error(US"SSL_CTX_set_cipher_list", host, NULL, errstr);
}
#ifdef EXPERIMENTAL_DANE
verify_callback_client_dane);
if (!DANESSL_library_init())
- return tls_error(US"library init", host, NULL);
+ return tls_error(US"library init", host, NULL, errstr);
if (DANESSL_CTX_init(client_ctx) <= 0)
- return tls_error(US"context init", host, NULL);
+ return tls_error(US"context init", host, NULL, errstr);
}
else
#endif
- if ((rc = tls_client_basic_ctx_init(client_ctx, host, ob, client_static_cbinfo))
- != OK)
+ if ((rc = tls_client_basic_ctx_init(client_ctx, host, ob,
+ client_static_cbinfo, errstr)) != OK)
return rc;
if ((client_ssl = SSL_new(client_ctx)) == NULL)
- return tls_error(US"SSL_new", host, NULL);
+ return tls_error(US"SSL_new", host, NULL, errstr);
SSL_set_session_id_context(client_ssl, sid_ctx, Ustrlen(sid_ctx));
SSL_set_fd(client_ssl, fd);
SSL_set_connect_state(client_ssl);
if (ob->tls_sni)
{
- if (!expand_check(ob->tls_sni, US"tls_sni", &tls_out.sni))
+ if (!expand_check(ob->tls_sni, US"tls_sni", &tls_out.sni, errstr))
return FAIL;
- if (tls_out.sni == NULL)
+ if (!tls_out.sni)
{
DEBUG(D_tls) debug_printf("Setting TLS SNI forced to fail, not sending\n");
}
#ifdef EXPERIMENTAL_DANE
if (tlsa_dnsa)
- if ((rc = dane_tlsa_load(client_ssl, host, tlsa_dnsa)) != OK)
+ if ((rc = dane_tlsa_load(client_ssl, host, tlsa_dnsa, errstr)) != OK)
return rc;
#endif
#endif
if (rc <= 0)
- return tls_error(US"SSL_connect", host, sigalrm_seen ? US"timed out" : NULL);
+ return tls_error(US"SSL_connect", host, sigalrm_seen ? US"timed out" : NULL,
+ errstr);
DEBUG(D_tls) debug_printf("SSL_connect succeeded\n");
+static BOOL
+tls_refill(unsigned lim)
+{
+int error;
+int inbytes;
+
+DEBUG(D_tls) debug_printf("Calling SSL_read(%p, %p, %u)\n", server_ssl,
+ ssl_xfer_buffer, ssl_xfer_buffer_size);
+
+if (smtp_receive_timeout > 0) alarm(smtp_receive_timeout);
+inbytes = SSL_read(server_ssl, CS ssl_xfer_buffer,
+ MIN(ssl_xfer_buffer_size, lim));
+error = SSL_get_error(server_ssl, inbytes);
+alarm(0);
+
+/* SSL_ERROR_ZERO_RETURN appears to mean that the SSL session has been
+closed down, not that the socket itself has been closed down. Revert to
+non-SSL handling. */
+
+if (error == SSL_ERROR_ZERO_RETURN)
+ {
+ DEBUG(D_tls) debug_printf("Got SSL_ERROR_ZERO_RETURN\n");
+
+ receive_getc = smtp_getc;
+ receive_getbuf = smtp_getbuf;
+ receive_get_cache = smtp_get_cache;
+ receive_ungetc = smtp_ungetc;
+ receive_feof = smtp_feof;
+ receive_ferror = smtp_ferror;
+ receive_smtp_buffered = smtp_buffered;
+
+ SSL_free(server_ssl);
+ server_ssl = NULL;
+ tls_in.active = -1;
+ tls_in.bits = 0;
+ tls_in.cipher = NULL;
+ tls_in.peerdn = NULL;
+ tls_in.sni = NULL;
+
+ return FALSE;
+ }
+
+/* Handle genuine errors */
+
+else if (error == SSL_ERROR_SSL)
+ {
+ ERR_error_string(ERR_get_error(), ssl_errstring);
+ log_write(0, LOG_MAIN, "TLS error (SSL_read): %s", ssl_errstring);
+ ssl_xfer_error = 1;
+ return FALSE;
+ }
+
+else if (error != SSL_ERROR_NONE)
+ {
+ DEBUG(D_tls) debug_printf("Got SSL error %d\n", error);
+ ssl_xfer_error = 1;
+ return FALSE;
+ }
+
+#ifndef DISABLE_DKIM
+dkim_exim_verify_feed(ssl_xfer_buffer, inbytes);
+#endif
+ssl_xfer_buffer_hwm = inbytes;
+ssl_xfer_buffer_lwm = 0;
+return TRUE;
+}
+
+
/*************************************************
* TLS version of getc *
*************************************************/
tls_getc(unsigned lim)
{
if (ssl_xfer_buffer_lwm >= ssl_xfer_buffer_hwm)
- {
- int error;
- int inbytes;
-
- DEBUG(D_tls) debug_printf("Calling SSL_read(%p, %p, %u)\n", server_ssl,
- ssl_xfer_buffer, ssl_xfer_buffer_size);
+ if (!tls_refill(lim))
+ return ssl_xfer_error ? EOF : smtp_getc(lim);
- if (smtp_receive_timeout > 0) alarm(smtp_receive_timeout);
- inbytes = SSL_read(server_ssl, CS ssl_xfer_buffer,
- MIN(ssl_xfer_buffer_size, lim));
- error = SSL_get_error(server_ssl, inbytes);
- alarm(0);
-
- /* SSL_ERROR_ZERO_RETURN appears to mean that the SSL session has been
- closed down, not that the socket itself has been closed down. Revert to
- non-SSL handling. */
-
- if (error == SSL_ERROR_ZERO_RETURN)
- {
- DEBUG(D_tls) debug_printf("Got SSL_ERROR_ZERO_RETURN\n");
-
- receive_getc = smtp_getc;
- receive_get_cache = smtp_get_cache;
- receive_ungetc = smtp_ungetc;
- receive_feof = smtp_feof;
- receive_ferror = smtp_ferror;
- receive_smtp_buffered = smtp_buffered;
-
- SSL_free(server_ssl);
- server_ssl = NULL;
- tls_in.active = -1;
- tls_in.bits = 0;
- tls_in.cipher = NULL;
- tls_in.peerdn = NULL;
- tls_in.sni = NULL;
-
- return smtp_getc(lim);
- }
+/* Something in the buffer; return next uschar */
- /* Handle genuine errors */
+return ssl_xfer_buffer[ssl_xfer_buffer_lwm++];
+}
- else if (error == SSL_ERROR_SSL)
- {
- ERR_error_string(ERR_get_error(), ssl_errstring);
- log_write(0, LOG_MAIN, "TLS error (SSL_read): %s", ssl_errstring);
- ssl_xfer_error = 1;
- return EOF;
- }
+uschar *
+tls_getbuf(unsigned * len)
+{
+unsigned size;
+uschar * buf;
- else if (error != SSL_ERROR_NONE)
+if (ssl_xfer_buffer_lwm >= ssl_xfer_buffer_hwm)
+ if (!tls_refill(*len))
{
- DEBUG(D_tls) debug_printf("Got SSL error %d\n", error);
- ssl_xfer_error = 1;
- return EOF;
+ if (!ssl_xfer_error) return smtp_getbuf(len);
+ *len = 0;
+ return NULL;
}
-#ifndef DISABLE_DKIM
- dkim_exim_verify_feed(ssl_xfer_buffer, inbytes);
-#endif
- ssl_xfer_buffer_hwm = inbytes;
- ssl_xfer_buffer_lwm = 0;
- }
-
-/* Something in the buffer; return next uschar */
-
-return ssl_xfer_buffer[ssl_xfer_buffer_lwm++];
+if ((size = ssl_xfer_buffer_hwm - ssl_xfer_buffer_lwm) > *len)
+ size = *len;
+buf = &ssl_xfer_buffer[ssl_xfer_buffer_lwm];
+ssl_xfer_buffer_lwm += size;
+*len = size;
+return buf;
}
+
void
tls_get_cache()
{
}
+BOOL
+tls_could_read(void)
+{
+return ssl_xfer_buffer_lwm < ssl_xfer_buffer_hwm || SSL_pending(server_ssl) > 0;
+}
+
/*************************************************
* Read bytes from TLS channel *
return -1;
}
else if (error != SSL_ERROR_NONE)
- {
return -1;
- }
return inbytes;
}
is_server channel specifier
buff buffer of data
len number of bytes
+ more further data expected soon
Returns: the number of bytes after a successful write,
-1 after a failed write
*/
int
-tls_write(BOOL is_server, const uschar *buff, size_t len)
+tls_write(BOOL is_server, const uschar *buff, size_t len, BOOL more)
{
-int outbytes;
-int error;
-int left = len;
+int outbytes, error, left;
SSL *ssl = is_server ? server_ssl : client_ssl;
+static uschar * corked = NULL;
+static int c_size = 0, c_len = 0;
+
+DEBUG(D_tls) debug_printf("%s(%p, %d%s)\n", __FUNCTION__,
+ buff, left, more ? ", more" : "");
+
+/* Lacking a CORK or MSG_MORE facility (such as GnuTLS has) we copy data when
+"more" is notified. This hack is only ok if small amounts are involved AND only
+one stream does it, in one context (i.e. no store reset). Currently it is used
+for the responses to the received SMTP MAIL , RCPT, DATA sequence, only. */
+
+if (is_server && (more || corked))
+ {
+ corked = string_catn(corked, &c_size, &c_len, buff, len);
+ if (more)
+ return len;
+ buff = CUS corked;
+ len = c_len;
+ corked = NULL; c_size = c_len = 0;
+ }
-DEBUG(D_tls) debug_printf("tls_do_write(%p, %d)\n", buff, left);
-while (left > 0)
+for (left = len; left > 0;)
{
DEBUG(D_tls) debug_printf("SSL_write(SSL, %p, %d)\n", buff, left);
outbytes = SSL_write(ssl, CS buff, left);
if (!(tls_require_ciphers && *tls_require_ciphers))
return NULL;
-if (!expand_check(tls_require_ciphers, US"tls_require_ciphers", &expciphers))
+if (!expand_check(tls_require_ciphers, US"tls_require_ciphers", &expciphers,
+ &err))
return US"failed to expand tls_require_ciphers";
if (!(expciphers && *expciphers))
if (!SSL_CTX_set_cipher_list(ctx, CS expciphers))
{
ERR_error_string(ERR_get_error(), ssl_errstring);
- err = string_sprintf("SSL_CTX_set_cipher_list(%s) failed", expciphers);
+ err = string_sprintf("SSL_CTX_set_cipher_list(%s) failed: %s",
+ expciphers, ssl_errstring);
}
SSL_CTX_free(ctx);
uschar keep_c;
BOOL adding, item_parsed;
-result = 0L;
+result = SSL_OP_NO_TICKET;
/* Prior to 4.80 we or'd in SSL_OP_DONT_INSERT_EMPTY_FRAGMENTS; removed
* from default because it increases BEAST susceptibility. */
#ifdef SSL_OP_NO_SSLv2
result |= SSL_OP_SINGLE_DH_USE;
#endif
-if (option_spec == NULL)
+if (!option_spec)
{
*results = result;
return TRUE;