summaryrefslogtreecommitdiff
path: root/ghc/lib/misc/Socket.lhs
blob: b960b9059124acbcbd2ee6530e041d0991ae8f2d (plain)
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
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
%
% (c) The GRASP/AQUA Project, Glasgow University, 1995-98
%
% Last Modified: Fri Jul 21 15:53:32 1995
% Darren J Moffat <moffatd@dcs.gla.ac.uk>
%
% Further hacked on by Sigbjorn Finne <sof@dcs.gla.ac.uk>
%
\section[Socket]{Haskell 1.3 Socket bindings}


\begin{code}       
{-# OPTIONS -#include "cbits/ghcSockets.h" #-}

#include "config.h"

module Socket (
        PortID(..),
	Hostname,

	connectTo,	-- :: Hostname -> PortID -> IO Handle
	listenOn,	-- :: PortID -> IO Socket
	
	accept,		-- :: Socket -> IO (Handle, HostName)

	sendTo,		-- :: Hostname -> PortID -> String -> IO ()
	recvFrom,	-- :: Hostname -> PortID -> IO String

	socketPort,	-- :: Socket -> IO PortID
	
	withSocketsDo,  -- :: IO a   -> IO a
	
	PortNumber,
	mkPortNumber	-- :: Int    -> PortNumber

       ) where

import BSD
import SocketPrim hiding ( accept, socketPort, recvFrom, sendTo )
import qualified SocketPrim ( accept, socketPort )
import IO
\end{code} 

%***************************************************************************
%*                                                                         *
\subsection[Socket-Setup]{High Level ``Setup'' functions}
%*                                                                         *
%***************************************************************************

Calling @connectTo@ creates a client side socket which is
connected to the given host and port.  The Protocol and socket type is
derived from the given port identifier.  If a port number is given
then the result is always an internet family @Stream@ socket. 

If the @PortID@ specifies a unix family socket and the @Hostname@
differs from that returned by @getHostname@ then an error is
raised. Alternatively an empty string may be given to @connectTo@
signalling that the current hostname applies.

\begin{code}
data PortID = 
	  Service String		-- Service Name eg "ftp"
	| PortNumber PortNumber		-- User defined Port Number
#ifndef _WIN32
	| UnixSocket String		-- Unix family socket in file system
#endif

type Hostname = String
-- Maybe consider this alternative.
-- data Hostname = Name String | IP Int Int Int Int
\end{code}
   
If more control over the socket type is required then $socketPrim$
should be used instead.

\begin{code}
connectTo :: Hostname		-- Hostname
	  -> PortID 		-- Port Identifier
	  -> IO Handle		-- Connected Socket

connectTo hostname (Service serv) = do
    proto	<- getProtocolNumber "tcp"
    sock	<- socket AF_INET Stream proto
    port	<- getServicePortNumber serv
    he		<- getHostByName hostname
    connect sock (SockAddrInet port (hostAddress he))
    socketToHandle sock	ReadWriteMode

connectTo hostname (PortNumber port) = do
    proto	<- getProtocolNumber "tcp"
    sock        <- socket AF_INET Stream proto
    he		<- getHostByName hostname
    connect sock (SockAddrInet port (hostAddress he))
    socketToHandle sock ReadWriteMode

#ifndef _WIN32
connectTo _ (UnixSocket path) = do
    sock    <- socket AF_UNIX Datagram 0
    connect sock (SockAddrUnix path)
    socketToHandle sock ReadWriteMode
#endif

\end{code}

The dual to the @connectTo@ call. This creates the server side
socket which has been bound to the specified port.

\begin{code}
listenOn :: PortID 	-- Port Identifier
	 -> IO Socket	-- Connected Socket

listenOn (Service serv) = do
    proto   <- getProtocolNumber "tcp"
    sock    <- socket AF_INET Stream proto
    port    <- getServicePortNumber serv
    bindSocket sock (SockAddrInet port iNADDR_ANY)
    listen sock maxListenQueue
    return sock

listenOn (PortNumber port) = do
    proto <- getProtocolNumber "tcp"
    sock  <- socket AF_INET Stream proto
    bindSocket sock (SockAddrInet port iNADDR_ANY)
    listen sock maxListenQueue
    return sock

#ifndef _WIN32
listenOn (UnixSocket path) = do
    sock <- socket AF_UNIX Datagram 0
    bindSocket sock (SockAddrUnix path)
    return sock
#endif
\end{code}

\begin{code}
accept :: Socket 		-- Listening Socket
       -> IO (Handle, 		-- StdIO Handle for read/write
	      HostName)		-- HostName of Peer socket
accept sock = do
 ~(sock', (SockAddrInet _ haddr)) <- SocketPrim.accept sock
 (HostEntry peer _ _ _)           <- getHostByAddr AF_INET haddr
 handle				  <- socketToHandle sock' ReadWriteMode
 return (handle, peer)

\end{code}

Send and recived data from/to the given host and port number.  These
should normally only be used where the socket will not be required for
further calls.

Thse are wrappers around socket, bind, and listen.

\begin{code}
sendTo :: Hostname 	-- Hostname
       -> PortID	-- Port Number
       -> String	-- Message to send
       -> IO ()
sendTo h p msg = do
  s <- connectTo h p
  hPutStr s msg
  hClose s

recvFrom :: Hostname 	-- Hostname
	 -> PortID	-- Port Number
	 -> IO String	-- Received Data
recvFrom host port = do
 s <- listenOn port
 let 
  waiting = do
     ~(s', SockAddrInet _ haddr) <-  SocketPrim.accept s
     (HostEntry peer _ _ _)      <- getHostByAddr AF_INET haddr
     if peer /= host 
      then do
         sClose s'
         waiting
      else do
        msg <- readSocketAll s'
        sClose s'
        return msg

 message <- waiting
 sClose s
 return message

\end{code}

Access function returning the port type/id of socket.

\begin{code}
socketPort :: Socket -> IO PortID
socketPort s = do
    sockaddr <- getSocketName s
    return (portID sockaddr)
  where
   portID sa =
    case sa of
     SockAddrInet port _    -> PortNumber port
#ifndef _WIN32
     SockAddrUnix path	    -> UnixSocket path
#endif

\end{code}