peyotls: Pretty Easy YOshikuni-made TLS library

[ bsd3, library, network ] [ Propose Tags ]

Currently implement the TLS1.2 protocol only, and support the following cipher suites.

  • TLS_RSA_WITH_AES_128_CBC_SHA

  • TLS_RSA_WITH_AES_128_CBC_SHA256

  • TLS_DHE_RSA_WITH_AES_128_CBC_SHA

  • TLS_DHE_RSA_WITH_AES_128_CBC_SHA256

  • TLS_ECDHE_RSA_WITH_AES_128_CBC_SHA

  • TLS_ECDHE_RSA_WITH_AES_128_CBC_SHA256

  • TLS_ECDHE_ECDSA_WITH_AES_128_CBC_SHA

  • TLS_ECDHE_ECDSA_WITH_AES_128_CBC_SHA256

And support client certificate with the following algorithms.

  • RSA (SHA1 or SHA256 depending on the agreed cipher suite)

  • ECDSA (SHA1 or SHA256 depending on the agreed cipher suite)

Currently not implement the following features.

  • session resumption (RFC 5077)

  • renegotiation (RFC 5746)

Server sample

  • file: examples/simpleServer.hs

localhost.key: key file

-----BEGIN RSA PRIVATE KEY-----
...
-----END RSA PRIVATE KEY-----

localhost.crt: certificate file

-----BEGIN CERTIFICATE-----
...
-----END CERTIFICATE-----

examples/simpleServer.hs

extensions

  • OverloadedStrings

  • PackageImports

 import Control.Applicative
 import Control.Monad
 import "monads-tf" Control.Monad.State
 import Control.Concurrent
 import Data.HandleLike
 import Network
 import Network.PeyoTLS.Server
 import Network.PeyoTLS.ReadFile
 import "crypto-random" Crypto.Random

 import qualified Data.ByteString as BS
 import qualified Data.ByteString.Char8 as BSC

 main :: IO ()
 main = do
	k <- readKey "localhost.key"
	c <- readCertificateChain "localhost.crt"
	g0 <- cprgCreate <$> createEntropyPool :: IO SystemRNG
	soc <- listenOn $ PortNumber 443
	void . (`runStateT` g0) . forever $ do
		(h, _, _) <- liftIO $ accept soc
		g <- StateT $ return . cprgFork
		liftIO . forkIO . (`run` g) $ do
			p <- open h ["TLS_RSA_WITH_AES_128_CBC_SHA"] [(k, c)]
				Nothing
			doUntil BS.null (hlGetLine p) >>= liftIO . mapM_ BSC.putStrLn
			hlPut p $ BS.concat [
				"HTTP/1.1 200 OK\r\n",
				"Transfer-Encoding: chunked\r\n",
				"Content-Type: text/plain\r\n\r\n",
				"5\r\nHello0\r\n\r\n" ]
			hlClose p

 doUntil :: Monad m => (a -> Bool) -> m a -> m [a]
 doUntil p rd = rd >>= \x ->
	(if p x then return . (: []) else (`liftM` doUntil p rd) . (:)) x

Client sample (only show HTTP header)

  • file: examples/simpleClient.hs

cacert.pem: self-signed root certificate to validate server

-----BEGIN CERTIFICATE-----
...
-----END CERTIFICATE-----

examples/simpleClient.hs

extensions

  • OverloadedStrings

  • PackageImports

import Control.Applicative
import Control.Monad
import "monads-tf" Control.Monad.Trans
import Data.HandleLike
import Network
import Network.PeyoTLS.ReadFile
import Network.PeyoTLS.Client
import "crypto-random" Crypto.Random

import qualified Data.ByteString.Char8 as BSC

main :: IO ()
main = do
	ca <- readCertificateStore ["cacert.pem"]
	h <- connectTo "localhost" $ PortNumber 443
	g <- cprgCreate <$> createEntropyPool :: IO SystemRNG
	(`run` g) $ do
		p <- open h ["TLS_RSA_WITH_AES_128_CBC_SHA"] [] ca
		unless ("localhost" `elem` names p) $
			error "certificate name mismatch"
		hlPut p "GET / HTTP/1.1 \r\n"
		hlPut p "Host: localhost\r\n\r\n"
		doUntil BSC.null (hlGetLine p) >>= liftIO . mapM_ BSC.putStrLn
		hlClose p

doUntil :: Monad m => (a -> Bool) -> m a -> m [a]
doUntil p rd = rd >>= \x ->
	(if p x then return . (: []) else (`liftM` doUntil p rd) . (:)) x

Client certificate server

  • file: examples/clcertServer.hs

% diff examples/simpleServer.hs examples/clcertServer.hs
19a20
>	ca <- readCertificateStore ["cacert.pem"]
27c28
<				Nothing
---
>				$ Just ca

Client certificate client (RSA certificate)

  • file: examples/clcertClient.hs

% diff examples/simpleClient.hs examples/clcertClient.hs
15a16,17
>	rk <- readKey "client_rsa.key"
>	rc <- readCertificateChain "client_rsa.crt"
20c22
<		p <- open h ["TLS_RSA_WITH_AES_128_CBC_SHA"] [] ca
---
>		p <- open h ["TLS_RSA_WITH_AES_128_CBC_SHA"] [(rk, rc)] ca

Client certificate client (ECDSA or RSA certificate)

  • file: examples/clcertEcdsaClient.hs

% diff examples/clcertClient.hs examples/clcertEcdsaClient.hs
17a18,19
>	ek <- readKey "client_ecdsa.key"
>	ec <- readCertificateChain "client_ecdsa.crt"
22c24
<		p <- open h ["TLS_RSA_WITH_AES_128_CBC_SHA"] [(rk, rc)] ca
---
>		p <- open h ["TLS_RSA_WITH_AES_128_CBC_SHA"] [(ek, ec), (rk, rc)] ca

ECC server (use ECC or RSA depending on client)

  • file: examples/eccServer.hs

% diff examples/simpleServer.hs examples/eccServer.hs
15a16,26
> cipherSuites :: [CipherSuite]
> cipherSuites = [
>       "TLS_ECDHE_ECDSA_WITH_AES_128_CBC_SHA256",
>       "TLS_ECDHE_ECDSA_WITH_AES_128_CBC_SHA",
>       "TLS_ECDHE_RSA_WITH_AES_128_CBC_SHA256",
>       "TLS_ECDHE_RSA_WITH_AES_128_CBC_SHA",
>       "TLS_DHE_RSA_WITH_AES_128_CBC_SHA256",
>       "TLS_DHE_RSA_WITH_AES_128_CBC_SHA",
>       "TLS_RSA_WITH_AES_128_CBC_SHA256",
>       "TLS_RSA_WITH_AES_128_CBC_SHA" ]
>
18,19c29,32
<       k <- readKey "localhost.key"
<       c <- readCertificateChain "localhost.crt"
---
>       rk <- readKey "localhost.key"
>       rc <- readCertificateChain "localhost.crt"
>       ek <- readKey "localhost_ecdsa.key"
>       ec <- readCertificateChain "localhost_ecdsa.crt"
26c39
<                       p <- open h ["TLS_RSA_WITH_AES_128_CBC_SHA"] [(k, c)]
---
>                       p <- open h cipherSuites [(rk, rc), (ek, ec)]

ECC client (use ECC or RSA depending on server)

  • file: examples/eccClient.hs

% diff examples/simpleClient.hs examples/eccClient.hs
13a14,24
> cipherSuites :: [CipherSuite]
> cipherSuites = [
>       "TLS_ECDHE_ECDSA_WITH_AES_128_CBC_SHA256",
>       "TLS_ECDHE_ECDSA_WITH_AES_128_CBC_SHA",
>       "TLS_ECDHE_RSA_WITH_AES_128_CBC_SHA256",
>       "TLS_ECDHE_RSA_WITH_AES_128_CBC_SHA",
>       "TLS_DHE_RSA_WITH_AES_128_CBC_SHA256",
>       "TLS_DHE_RSA_WITH_AES_128_CBC_SHA",
>       "TLS_RSA_WITH_AES_128_CBC_SHA256",
>       "TLS_RSA_WITH_AES_128_CBC_SHA" ]
>
20c31
<               p <- open h ["TLS_RSA_WITH_AES_128_CBC_SHA"] [] ca
---
>               p <- open h cipherSuites [] ca

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.0.0.0, 0.0.0.1, 0.0.0.2, 0.0.0.3, 0.0.0.4, 0.0.0.5, 0.0.0.6, 0.0.0.7, 0.0.0.8, 0.0.0.9, 0.0.0.10, 0.0.0.11, 0.0.0.12, 0.0.0.13, 0.0.0.14, 0.0.0.15, 0.0.0.16, 0.0.0.17, 0.0.0.18, 0.0.0.19, 0.0.0.20, 0.0.0.21, 0.0.0.22, 0.0.0.23, 0.0.0.24, 0.1.0.0, 0.1.1.0, 0.1.2.0, 0.1.3.0, 0.1.4.0, 0.1.4.1, 0.1.4.2, 0.1.4.3, 0.1.4.4, 0.1.4.5, 0.1.5.5, 0.1.6.0, 0.1.6.1, 0.1.6.2, 0.1.6.3, 0.1.6.4, 0.1.6.5, 0.1.6.6, 0.1.6.7, 0.1.6.8, 0.1.6.9, 0.1.6.10
Dependencies asn1-encoding (>=0.8 && <0.9), asn1-types (>=0.2 && <0.3), base (>=4 && <5), bytable (>=0.0.0 && <0.0.1), bytestring (>=0.10 && <0.11), cipher-aes (>=0.2 && <0.3), crypto-numbers (>=0.2 && <0.3), crypto-pubkey (>=0.2 && <0.3), crypto-pubkey-types (>=0.4 && <0.5), crypto-random (>=0.0 && <0.1), cryptohash (>=0.11 && <0.12), handle-like (>=0.0.0 && <0.0.1), monads-tf (>=0.1 && <0.2), pem (>=0.2 && <0.3), word24 (>=1.0 && <1.1), x509 (>=1.4 && <1.5), x509-store (>=1.4 && <1.5), x509-validation (>=1.5 && <1.6) [details]
License BSD-3-Clause
Author Yoshikuni Jujo <PAF01143@nifty.ne.jp>
Maintainer Yoshikuni Jujo <PAF01143@nifty.ne.jp>
Revised Revision 1 made by YoshikuniJujo at 2014-07-01T08:07:20Z
Category Network
Home page https://github.com/YoshikuniJujo/peyotls/wiki
Source repo head: git clone git://github.com/YoshikuniJujo/peyotls.git
this: git clone git://github.com/YoshikuniJujo/peyotls.git(tag peyotls-0.0.0.0)
Uploaded by YoshikuniJujo at 2014-07-01T08:03:05Z
Distributions
Reverse Dependencies 2 direct, 0 indirect [details]
Downloads 29682 total (98 in the last 30 days)
Rating 2.0 (votes: 1) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Successful builds reported [all 1 reports]