summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Connection/Tcp.hs (renamed from Presence/Server.hs)8
-rw-r--r--Presence/XMPPServer.hs2
-rw-r--r--dht-client.cabal2
-rw-r--r--examples/dhtd.hs6
-rw-r--r--simplechat.hs2
-rw-r--r--test-server.hs2
6 files changed, 11 insertions, 11 deletions
diff --git a/Presence/Server.hs b/Connection/Tcp.hs
index c38aec2a..73d01c40 100644
--- a/Presence/Server.hs
+++ b/Connection/Tcp.hs
@@ -9,7 +9,7 @@
9{-# LANGUAGE LambdaCase #-} 9{-# LANGUAGE LambdaCase #-}
10----------------------------------------------------------------------------- 10-----------------------------------------------------------------------------
11-- | 11-- |
12-- Module : Server 12-- Module : Connection.Tcp
13-- 13--
14-- Maintainer : joe@jerkface.net 14-- Maintainer : joe@jerkface.net
15-- Stability : experimental 15-- Stability : experimental
@@ -20,8 +20,8 @@
20-- 20--
21-- * interface tweaks 21-- * interface tweaks
22-- 22--
23module Server 23module Connection.Tcp
24 ( module Server 24 ( module Connection.Tcp
25 , module PingMachine ) where 25 , module PingMachine ) where
26 26
27import Data.ByteString (ByteString,hGetNonBlocking) 27import Data.ByteString (ByteString,hGetNonBlocking)
@@ -216,7 +216,7 @@ noCleanUp io _ = ( (,) () ) `liftM` liftIO io
216-- | Construct a 'Server' object. Use 'Control.Monad.Trans.Resource.ResourceT' 216-- | Construct a 'Server' object. Use 'Control.Monad.Trans.Resource.ResourceT'
217-- to ensure proper cleanup. For example, 217-- to ensure proper cleanup. For example,
218-- 218--
219-- > import Server 219-- > import Connection.Tcp
220-- > import Control.Monad.Trans.Resource (runResourceT) 220-- > import Control.Monad.Trans.Resource (runResourceT)
221-- > import Control.Monad.IO.Class (liftIO) 221-- > import Control.Monad.IO.Class (liftIO)
222-- > import Control.Monad.STM (atomically) 222-- > import Control.Monad.STM (atomically)
diff --git a/Presence/XMPPServer.hs b/Presence/XMPPServer.hs
index 6d6d3bd7..5a0ed20e 100644
--- a/Presence/XMPPServer.hs
+++ b/Presence/XMPPServer.hs
@@ -34,7 +34,7 @@ module XMPPServer
34import ConnectionKey 34import ConnectionKey
35import qualified Control.Concurrent.STM.UpdateStream as Slotted 35import qualified Control.Concurrent.STM.UpdateStream as Slotted
36import Nesting 36import Nesting
37import Server 37import Connection.Tcp
38import EventUtil 38import EventUtil
39import ControlMaybe 39import ControlMaybe
40import LockedChan 40import LockedChan
diff --git a/dht-client.cabal b/dht-client.cabal
index 81453e38..849ebf28 100644
--- a/dht-client.cabal
+++ b/dht-client.cabal
@@ -118,7 +118,7 @@ library
118 Nesting 118 Nesting
119 Paths 119 Paths
120 PeerResolve 120 PeerResolve
121 Server 121 Connection.Tcp
122 SockAddr 122 SockAddr
123 TraversableT 123 TraversableT
124 UTmp 124 UTmp
diff --git a/examples/dhtd.hs b/examples/dhtd.hs
index 527af7e7..4b38a7ea 100644
--- a/examples/dhtd.hs
+++ b/examples/dhtd.hs
@@ -99,7 +99,7 @@ import Presence
99import XMPPServer 99import XMPPServer
100import Connection 100import Connection
101import ToxToXMPP 101import ToxToXMPP
102import qualified Server (ConnectionEvent(..)) 102import qualified Connection.Tcp (ConnectionEvent(..))
103 103
104 104
105showReport :: [(String,String)] -> String 105showReport :: [(String,String)] -> String
@@ -987,7 +987,7 @@ noArgPing :: (x -> IO (Maybe r)) -> [String] -> x -> IO (Maybe r)
987noArgPing f [] x = f x 987noArgPing f [] x = f x
988noArgPing _ _ _ = return Nothing 988noArgPing _ _ _ = return Nothing
989 989
990announceToxConnection :: TChan ((ConnectionKey,SockAddr), Server.ConnectionEvent XML.Event) 990announceToxConnection :: TChan ((ConnectionKey,SockAddr), Connection.Tcp.ConnectionEvent XML.Event)
991 -> SockAddr 991 -> SockAddr
992 -> SockAddr 992 -> SockAddr
993 -> STM Bool 993 -> STM Bool
@@ -997,7 +997,7 @@ announceToxConnection :: TChan ((ConnectionKey,SockAddr), Server.ConnectionEvent
997announceToxConnection echan laddr saddr pingflag tsrc tsnk 997announceToxConnection echan laddr saddr pingflag tsrc tsnk
998 = atomically $ writeTChan echan 998 = atomically $ writeTChan echan
999 ( (PeerKey saddr, laddr ) 999 ( (PeerKey saddr, laddr )
1000 , Server.Connection pingflag xsrc xsnk ) 1000 , Connection.Tcp.Connection pingflag xsrc xsnk )
1001 where 1001 where
1002 xsrc = tsrc =$= toxToXmpp 1002 xsrc = tsrc =$= toxToXmpp
1003 xsnk = flushPassThrough xmppToTox =$= tsnk 1003 xsnk = flushPassThrough xmppToTox =$= tsnk
diff --git a/simplechat.hs b/simplechat.hs
index bf592db3..84b33e13 100644
--- a/simplechat.hs
+++ b/simplechat.hs
@@ -16,7 +16,7 @@ import Control.Concurrent (forkIO)
16import Control.Concurrent.Chan 16import Control.Concurrent.Chan
17import Data.HList 17import Data.HList
18 18
19import Server 19import Connection.Tcp
20 20
21 21
22startCon socket st = do 22startCon socket st = do
diff --git a/test-server.hs b/test-server.hs
index 795a8190..b47a4bcb 100644
--- a/test-server.hs
+++ b/test-server.hs
@@ -5,7 +5,7 @@ import Debug.Trace
5import Control.Exception (evaluate) -- ,handle,SomeException(..),bracketOnError) 5import Control.Exception (evaluate) -- ,handle,SomeException(..),bracketOnError)
6import Control.Exception ({-evaluate,-}handle,SomeException(..),bracketOnError,ErrorCall(..)) 6import Control.Exception ({-evaluate,-}handle,SomeException(..),bracketOnError,ErrorCall(..))
7import System.IO.Error (ioeGetErrorType) 7import System.IO.Error (ioeGetErrorType)
8import Server 8import Connection.Tcp
9import Control.Monad 9import Control.Monad
10import Control.Monad.Trans.Resource 10import Control.Monad.Trans.Resource
11import Control.Monad.IO.Class 11import Control.Monad.IO.Class