aboutsummaryrefslogtreecommitdiff
path: root/jessl.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeffrey.armstrong@approximatrix.com>2020-05-19 08:36:22 -0400
committerJeffrey Armstrong <jeffrey.armstrong@approximatrix.com>2020-05-19 08:36:22 -0400
commit2492cdf6ce85963f2fe269b4d41fd09d92ccf277 (patch)
treec1025eecf8da7263923392ff1c657db75b0ef76e /jessl.f90
parent273cccb1a687dfe7d74486def016514a7887c1f5 (diff)
downloadLR-87-2492cdf6ce85963f2fe269b4d41fd09d92ccf277.tar.gz
LR-87-2492cdf6ce85963f2fe269b4d41fd09d92ccf277.zip
Requests should now include SNI over TLS
Diffstat (limited to 'jessl.f90')
-rw-r--r--jessl.f9043
1 files changed, 43 insertions, 0 deletions
diff --git a/jessl.f90 b/jessl.f90
index bd9d1fe..0df3180 100644
--- a/jessl.f90
+++ b/jessl.f90
@@ -23,8 +23,14 @@
! Just Enough SSL...
module jessl
+use iso_c_binding
implicit none
+ ! Constants needed for SNI
+ integer(kind=c_long), parameter::TLSEXT_NAMETYPE_host_name = 0
+
+ integer(kind=c_int), parameter::SSL_CTRL_SET_TLSEXT_HOSTNAME = 55
+
interface
subroutine library_init() bind(c, name="OPENSSL_init_ssl")
@@ -90,6 +96,15 @@ implicit none
type(c_ptr), value::ctx
end function ctx_free
+ function ssl_ctrl_c(ctx, cmd, arg, vp) bind(c, name="SSL_ctrl")
+ use iso_c_binding
+ type(c_ptr), value::ctx
+ integer(kind=c_int), value::cmd
+ integer(kind=c_long), value::arg
+ type(c_ptr), value::vp
+ integer(kind=c_long)::ssl_ctrl_c
+ end function ssl_ctrl_c
+
! Actually a macro...
!function get_cipher_c(ssl) bind(c, name="SSL_get_cipher_name")
!use iso_c_binding
@@ -207,5 +222,33 @@ contains
end if
end subroutine get_cipher
+
+ function set_tlsext_host_name(ctx, hostname)
+ use iso_c_binding
+ implicit none
+
+ type(c_ptr)::ctx
+ character(*), intent(in)::hostname
+ integer::set_tlsext_host_name
+
+ character(kind=c_char), dimension(:), allocatable, target::chostname
+
+ integer::i
+
+ allocate(chostname(len_trim(hostname)+1))
+
+ do i = 1, len_trim(hostname)
+ chostname(i) = hostname(i:i)
+ end do
+ chostname(len_trim(hostname)+1) = c_null_char
+
+ set_tlsext_host_name = ssl_ctrl_c(ctx, &
+ SSL_CTRL_SET_TLSEXT_HOSTNAME, &
+ TLSEXT_NAMETYPE_host_name, &
+ c_loc(chostname))
+
+ deallocate(chostname)
+
+ end function set_tlsext_host_name
end module jessl