~singpolyma/network-protocol-xmpp

ref: d4a781fd2c1e389fc723657f068aa9e11edc3adf network-protocol-xmpp/Network/Protocol/XMPP/Handle.hs -rw-r--r-- 2.3 KiB
d4a781fd — John Millikin Use lazy instead of strict bytestrings. 13 years ago
                                                                                
915f7dba John Millikin
d0f194da John Millikin
57a89320 John Millikin
915f7dba John Millikin
8150ebe0 John Millikin
d0f194da John Millikin
d4a781fd John Millikin
d0f194da John Millikin
31e363ef John Millikin
d0f194da John Millikin
915f7dba John Millikin
31e363ef John Millikin
915f7dba John Millikin
d0f194da John Millikin
31e363ef John Millikin
915f7dba John Millikin
d0f194da John Millikin
31e363ef John Millikin
915f7dba John Millikin
d0f194da John Millikin
31e363ef John Millikin
8150ebe0 John Millikin
31e363ef John Millikin
8150ebe0 John Millikin
915f7dba John Millikin
31e363ef 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
-- Copyright (C) 2010 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/>.

{-# LANGUAGE OverloadedStrings #-}
module Network.Protocol.XMPP.Handle
	( Handle (..)
	, startTLS
	, hPutBytes
	, hGetChar
	) where

import Control.Monad (when)
import qualified Control.Monad.Error as E
import Control.Monad.Trans (liftIO)
import qualified Data.ByteString.Lazy.Char8 as B
import qualified Data.Text as T
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 T.Text IO a
liftTLS s = liftTLS' . TLS.runTLS s

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

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

hPutBytes :: Handle -> B.ByteString -> ErrorT T.Text IO ()
hPutBytes (PlainHandle h)  = liftIO . B.hPut h
hPutBytes (SecureHandle _ s) = liftTLS s . TLS.putBytes

hGetChar :: Handle -> ErrorT T.Text IO Char
hGetChar (PlainHandle h) = liftIO $ IO.hGetChar h
hGetChar (SecureHandle h s) = liftTLS s $ do
	pending <- TLS.checkPending
	when (pending == 0) $ do
		liftIO $ IO.hWaitForInput h (- 1)
		return ()
	
	bytes <- TLS.getBytes 1
	return . head . B.unpack $ bytes