~singpolyma/network-protocol-xmpp

ref: 1eb63b40e7a543279418b0053799157299879fa4 network-protocol-xmpp/Network/Protocol/XMPP/Handle.hs -rw-r--r-- 2.5 KiB
1eb63b40 — John Millikin Use strict text and bytestrings for everything. 12 years ago
                                                                                
6ac34f1c John Millikin
915f7dba John Millikin
57a89320 John Millikin
915f7dba John Millikin
6831ae34 John Millikin
915f7dba John Millikin
6ac34f1c John Millikin
d0f194da John Millikin
6ac34f1c John Millikin
1eb63b40 John Millikin
d0f194da John Millikin
31e363ef John Millikin
6ac34f1c John Millikin
915f7dba John Millikin
31e363ef John Millikin
1eb63b40 John Millikin
31e363ef John Millikin
1eb63b40 John Millikin
31e363ef John Millikin
1eb63b40 John Millikin
31e363ef John Millikin
915f7dba John Millikin
1eb63b40 John Millikin
d0f194da John Millikin
21fada26 John Millikin
31e363ef John Millikin
21fada26 John Millikin
31e363ef John Millikin
915f7dba John Millikin
1eb63b40 John Millikin
915f7dba John Millikin
1eb63b40 John Millikin
6831ae34 John Millikin
f94ad358 John Millikin
1eb63b40 John Millikin
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
{-# LANGUAGE OverloadedStrings #-}

-- Copyright (C) 2010-2011 John Millikin <jmillikin@gmail.com>
-- 
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- any later version.
-- 
-- This program 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 this program.  If not, see <http://www.gnu.org/licenses/>.

module Network.Protocol.XMPP.Handle
	( Handle (..)
	, startTLS
	, hPutBytes
	, hGetBytes
	) where

import           Control.Monad (when)
import qualified Control.Monad.Error as E
import           Control.Monad.Trans (liftIO)
import qualified Data.ByteString
import           Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy
import qualified Data.Text
import           Data.Text (Text)
import qualified System.IO as IO
import qualified Network.Protocol.TLS.GNU as TLS
import           Network.Protocol.XMPP.ErrorT

data Handle =
	  PlainHandle IO.Handle
	| SecureHandle IO.Handle TLS.Session

liftTLS :: TLS.Session -> TLS.TLS a -> ErrorT Text IO a
liftTLS s = liftTLS' . TLS.runTLS s

liftTLS' :: IO (Either TLS.Error a) -> ErrorT Text IO a
liftTLS' io = do
	eitherX <- liftIO io
	case eitherX of
		Left err -> E.throwError $ Data.Text.pack $ show err
		Right x -> return x

startTLS :: Handle -> ErrorT Text IO Handle
startTLS (SecureHandle _ _) = E.throwError "Can't start TLS on a secure handle"
startTLS (PlainHandle h) = liftTLS' $ TLS.runClient (TLS.handleTransport h) $ do
	TLS.setPriority [TLS.X509]
	TLS.setCredentials =<< TLS.certificateCredentials
	TLS.handshake
	SecureHandle h `fmap` TLS.getSession

hPutBytes :: Handle -> ByteString -> ErrorT Text IO ()
hPutBytes (PlainHandle h)  = liftIO . Data.ByteString.hPut h
hPutBytes (SecureHandle _ s) = liftTLS s . TLS.putBytes . toLazy where
	toLazy bytes = Data.ByteString.Lazy.fromChunks [bytes]

hGetBytes :: Handle -> Integer -> ErrorT Text IO ByteString
hGetBytes (PlainHandle h) n = liftIO $ Data.ByteString.hGet h $ fromInteger n
hGetBytes (SecureHandle h s) n = liftTLS s $ do
	pending <- TLS.checkPending
	let wait = IO.hWaitForInput h (- 1) >> return ()
	when (pending == 0) (liftIO wait)
	lazy <- TLS.getBytes n
	return (Data.ByteString.concat (Data.ByteString.Lazy.toChunks lazy))