Hi Haskellers,

I am trying to connect a Java client to a Haskell server using the
Haskell tls package, and things are not working out for me. There is a
lot of steps involved and I do not know what I am doing wrong, so this
is a long message. But first I create a private/public key-pair:

> openssl genrsa -out privkey.pem 2048

then I make a self-signed certificate:

> openssl req -new -x509 -key privkey.pem -out cacert.pem -days 1095

> Country Name (2 letter code) [AU]:
> State or Province Name (full name) [Some-State]:
> Locality Name (eg, city) []:
> Organization Name (eg, company) [Internet Widgits Pty Ltd]:
> Organizational Unit Name (eg, section) []:
> Common Name (eg, YOUR name) []:192.168.1.6
> Email Address []:

then I convert the certificate to DER format and stuff it into a Java
keystore:

> openssl x509 -in cacert.pem -out cert.der -outform DER
> keytool -keystore myKeystore.store -importcert -storepass foobar -keypass 
> foobar -file cert.der

now I start the Haskell server:

> ghc -hide-package monads-tf Server.hs -e main

and then the Java client:

> javac Client.java
> java  -Djavax.net.debug=all -Djavax.net.ssl.trustStore=myKeystore.store 
> -Djavax.net.ssl.trustStorePassword=foobar Client >JavaClientOutput.txt 2>&1

The server output is:

> <interactive>: user error (unexpected type received. expecting handshake ++ 
> Left (Error_Packet "invalid type"))

and not "Hello world" as expected.

The client output is very long, but the most interesting part is
properly:

> main, received EOFException: error
> main, handling exception: javax.net.ssl.SSLHandshakeException: Remote host 
> closed connection during handshake
> main, SEND TLSv1 ALERT:  fatal, description = handshake_failure

I have attached the Haskell server, the Java client and the full java
output. Hope somebody can help figure out what I do wrong.

I am using the Haskell tsl package version 0.3.1. And I run Debian
Linux.


I also tried connecting a Java client to a Java server. First create
server keystore:

> openssl pkcs8 -topk8 -nocrypt -in privkey.pem -inform PEM -out privkey.der 
> -outform DER
> java -Dkeystore=myServerKeystore.store ImportKey privkey.der cert.der

ImportKey.java can be found here
http://www.agentbob.info/agentbob/79-AB.html .

then start Java server:

> javac JavaServer.java
> java -Djavax.net.ssl.keyStore=myServerKeystore.store 
> -Djavax.net.ssl.keyStorePassword=importkey JavaServer

and run the client again:

> java  -Djavax.net.debug=all -Djavax.net.ssl.trustStore=myKeystore.store 
> -Djavax.net.ssl.trustStorePassword=foobar Client

and the server outputs:

> Hello world

as expected. Thus I think the certificates are fine, and the Java client
is fine. But what am I doing wrong in the Haskell server?

I have attached JavaServer.java.


Regards,

Mads Lindstrøm

import javax.net.*;
import java.net.*;
import javax.net.ssl.*;
import java.io.*;

class Client {
    public static void main(String[] args) {
	try {
	    int port = 8000;
	    String hostname = "192.168.1.6";  // Insert your localhost ip
	    SocketFactory socketFactory = SSLSocketFactory.getDefault();
	    Socket socket = socketFactory.createSocket(hostname, port);
	    // Create streams to securely send and receive data to the server
	    InputStream in = socket.getInputStream();
	    OutputStream out = socket.getOutputStream();
	    
	    PrintWriter writer = new PrintWriter(out);
	    writer.println("Hello world");
	    
	    // Read from in and write to out...
	    // Close the socket 
	    writer.close();
	    in.close(); 
	    out.close();
	} catch(IOException e) {
	    e.printStackTrace();
	    System.out.println(e.getMessage());
	}
    }
} 
import javax.net.*;
import java.net.*;
import javax.net.ssl.*;
import java.io.*;

class JavaServer {
    public static void main(String[] args) {
	try {
	    int port = 8000;
	    String hostname = "192.168.1.6";  // Insert your localhost ip
	    
	    ServerSocketFactory ssocketFactory = SSLServerSocketFactory.getDefault();
	    ServerSocket ssocket = ssocketFactory.createServerSocket(port); 
	    
	    // Listen for connections
	    Socket socket = ssocket.accept();

	    // Create streams to securely send and receive data to the client
	    InputStream in = socket.getInputStream();
	    OutputStream out = socket.getOutputStream(); 

	    BufferedReader reader = new BufferedReader(new InputStreamReader(in));
	    System.out.println(reader.readLine());
	    
	    // Read from in and write to out...
	    // Close the socket 
	    reader.close();
	    in.close(); 
	    out.close();
	} catch(IOException e) {
	    e.printStackTrace();
	    System.out.println(e.getMessage());
	}
    }
} 
-- ghci -hide-package monads-tf Server.hs

module Main where

import qualified Control.Monad.Trans as Trans
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as L
import qualified Data.Certificate.PEM as PEM
import qualified Data.Certificate.Key as Key
import qualified Data.Certificate.X509 as X509

import qualified Network.TLS.Server as S
import qualified Network.TLS.Struct as Struct
import qualified Network.TLS.Cipher as Cipher
import qualified Network.TLS.SRandom as SRandom

import qualified Control.Exception as E
import qualified Network as Net
import qualified Network.Socket as Socket
import qualified IO as IO
import qualified Control.Concurrent as Concurrent

main :: IO ()
main = do
  pk <- readPrivateKey "privkey.pem"
  (certdata, cert) <- readCertificate "cacert.pem"
  listenForClients (certdata, cert, snd pk)
  return ()

type SpCert = (B.ByteString, X509.Certificate, Key.PrivateKey)

listenForClients :: SpCert -> IO ()
listenForClients spCert
    = Net.withSocketsDo $ E.bracket aquireSocket Net.sClose loop where
   aquireSocket =
       do socket <- Net.listenOn $ Net.PortNumber 8000
          Socket.setSocketOption socket Socket.ReuseAddr 1
          return socket
   loop socket =
       do (handle, _, _) <- Net.accept socket
          sslListen spCert handle
          loop socket

sslListen :: SpCert -> IO.Handle -> IO ()
sslListen spCert handle = do
  serverRNG <- getRandomGen
  let serverState = makeValidParams spCert
  let tlsServer = do
         S.listen handle
         d <- S.recvData handle
         Trans.lift $ print d
         return ()
  Concurrent.forkIO (S.runTLSServer tlsServer serverState serverRNG >> return ())
  return ()

getRandomGen :: IO SRandom.SRandomGen
getRandomGen = SRandom.makeSRandomGen >>= either (fail . show) (return . id)


makeValidParams :: SpCert -> S.TLSServerParams
makeValidParams spCert =
  S.TLSServerParams
         supportedVersions
         [] -- session
         supportedCiphers
         (Just spCert) -- server certificate
         False -- check for client certificate
         (S.TLSServerCallbacks { S.cbCertificates = Nothing })

supportedVersions :: [Struct.Version]
supportedVersions = [Struct.SSL3, Struct.TLS10, Struct.TLS11]

supportedCiphers :: [Cipher.Cipher]
supportedCiphers =
    [ Cipher.cipher_AES128_SHA1
    , Cipher.cipher_AES256_SHA1
    , Cipher.cipher_RC4_128_MD5
    , Cipher.cipher_RC4_128_SHA1
    ]

readCertificate :: FilePath -> IO (B.ByteString, X509.Certificate)
readCertificate filepath = do
  content <- B.readFile filepath
  let certdata = case PEM.parsePEMCert content of
                   Nothing -> error ("no valid certificate section")
                   Just x -> x
  let cert = case X509.decodeCertificate $ L.fromChunks [certdata] of
               Left err -> error ("cannot decode certificate: " ++ err)
               Right x -> x
  return (certdata, cert)

readPrivateKey :: FilePath -> IO (L.ByteString, Key.PrivateKey)
readPrivateKey filepath = do
  content <- B.readFile filepath
  let pkdata = case PEM.parsePEMKeyRSA content of
                 Nothing -> error ("no valid RSA key section")
                 Just x -> L.fromChunks [x]
  let pk = case Key.decodePrivateKey pkdata of
             Left err -> error ("cannot decode key: " ++ err)
             Right x -> x
  return (pkdata, pk)
keyStore is : 
keyStore type is : jks
keyStore provider is : 
init keystore
init keymanager of type SunX509
trustStore is: myKeystore.store
trustStore type is : jks
trustStore provider is : 
init truststore
adding as trusted cert:
  Subject: CN=192.168.1.6, O=Internet Widgits Pty Ltd, ST=Some-State, C=AU
  Issuer:  CN=192.168.1.6, O=Internet Widgits Pty Ltd, ST=Some-State, C=AU
  Algorithm: RSA; Serial number: 0xafd8b93f9f4ca3d7
  Valid from Sun Dec 12 19:50:14 CET 2010 until Wed Dec 11 19:50:14 CET 2013

trigger seeding of SecureRandom
done seeding SecureRandom
Allow unsafe renegotiation: false
Allow legacy hello messages: true
Is initial handshake: true
Is secure renegotiation: false
%% No cached client session
*** ClientHello, TLSv1
RandomCookie:  GMT: 1292180106 bytes = { 40, 135, 73, 129, 198, 116, 247, 112, 
56, 12, 229, 94, 70, 112, 36, 197, 0, 80, 139, 101, 102, 152, 214, 85, 31, 198, 
224, 53 }
Session ID:  {}
Cipher Suites: [SSL_RSA_WITH_RC4_128_MD5, SSL_RSA_WITH_RC4_128_SHA, 
TLS_RSA_WITH_AES_128_CBC_SHA, TLS_DHE_RSA_WITH_AES_128_CBC_SHA, 
TLS_DHE_DSS_WITH_AES_128_CBC_SHA, SSL_RSA_WITH_3DES_EDE_CBC_SHA, 
SSL_DHE_RSA_WITH_3DES_EDE_CBC_SHA, SSL_DHE_DSS_WITH_3DES_EDE_CBC_SHA, 
SSL_RSA_WITH_DES_CBC_SHA, SSL_DHE_RSA_WITH_DES_CBC_SHA, 
SSL_DHE_DSS_WITH_DES_CBC_SHA, SSL_RSA_EXPORT_WITH_RC4_40_MD5, 
SSL_RSA_EXPORT_WITH_DES40_CBC_SHA, SSL_DHE_RSA_EXPORT_WITH_DES40_CBC_SHA, 
SSL_DHE_DSS_EXPORT_WITH_DES40_CBC_SHA, TLS_EMPTY_RENEGOTIATION_INFO_SCSV]
Compression Methods:  { 0 }
***
[write] MD5 and SHA1 hashes:  len = 75
0000: 01 00 00 47 03 01 4D 05   1B 8A 28 87 49 81 C6 74  ...G..M...(.I..t
0010: F7 70 38 0C E5 5E 46 70   24 C5 00 50 8B 65 66 98  .p8..^Fp$..P.ef.
0020: D6 55 1F C6 E0 35 00 00   20 00 04 00 05 00 2F 00  .U...5.. ...../.
0030: 33 00 32 00 0A 00 16 00   13 00 09 00 15 00 12 00  3.2.............
0040: 03 00 08 00 14 00 11 00   FF 01 00                 ...........
main, WRITE: TLSv1 Handshake, length = 75
[write] MD5 and SHA1 hashes:  len = 101
0000: 01 03 01 00 3C 00 00 00   20 00 00 04 01 00 80 00  ....<... .......
0010: 00 05 00 00 2F 00 00 33   00 00 32 00 00 0A 07 00  ..../..3..2.....
0020: C0 00 00 16 00 00 13 00   00 09 06 00 40 00 00 15  ............@...
0030: 00 00 12 00 00 03 02 00   80 00 00 08 00 00 14 00  ................
0040: 00 11 00 00 FF 4D 05 1B   8A 28 87 49 81 C6 74 F7  .....M...(.I..t.
0050: 70 38 0C E5 5E 46 70 24   C5 00 50 8B 65 66 98 D6  p8..^Fp$..P.ef..
0060: 55 1F C6 E0 35                                     U...5
main, WRITE: SSLv2 client hello message, length = 101
[Raw write]: length = 103
0000: 80 65 01 03 01 00 3C 00   00 00 20 00 00 04 01 00  .e....<... .....
0010: 80 00 00 05 00 00 2F 00   00 33 00 00 32 00 00 0A  ....../..3..2...
0020: 07 00 C0 00 00 16 00 00   13 00 00 09 06 00 40 00  ..............@.
0030: 00 15 00 00 12 00 00 03   02 00 80 00 00 08 00 00  ................
0040: 14 00 00 11 00 00 FF 4D   05 1B 8A 28 87 49 81 C6  .......M...(.I..
0050: 74 F7 70 38 0C E5 5E 46   70 24 C5 00 50 8B 65 66  t.p8..^Fp$..P.ef
0060: 98 D6 55 1F C6 E0 35                               ..U...5
main, received EOFException: error
main, handling exception: javax.net.ssl.SSLHandshakeException: Remote host 
closed connection during handshake
main, SEND TLSv1 ALERT:  fatal, description = handshake_failure
main, WRITE: TLSv1 Alert, length = 2
[Raw write]: length = 7
0000: 15 03 01 00 02 02 28                               ......(
main, called closeSocket()
main, called close()
main, called closeInternal(true)
main, called close()
main, called closeInternal(true)
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to