1gen_tcp(3)                 Erlang Module Definition                 gen_tcp(3)
2
3
4

NAME

6       gen_tcp - Interface to TCP/IP sockets.
7

DESCRIPTION

9       This module provides functions for communicating with sockets using the
10       TCP/IP protocol.
11
12       The following code fragment is a simple example of a client  connecting
13       to  a  server at port 5678, transferring a binary, and closing the con‐
14       nection:
15
16       client() ->
17           SomeHostInNet = "localhost", % to make it runnable on one machine
18           {ok, Sock} = gen_tcp:connect(SomeHostInNet, 5678,
19                                        [binary, {packet, 0}]),
20           ok = gen_tcp:send(Sock, "Some Data"),
21           ok = gen_tcp:close(Sock).
22
23       At the other end, a server is listening on port 5678, accepts the  con‐
24       nection, and receives the binary:
25
26       server() ->
27           {ok, LSock} = gen_tcp:listen(5678, [binary, {packet, 0},
28                                               {active, false}]),
29           {ok, Sock} = gen_tcp:accept(LSock),
30           {ok, Bin} = do_recv(Sock, []),
31           ok = gen_tcp:close(Sock),
32           ok = gen_tcp:close(LSock),
33           Bin.
34
35       do_recv(Sock, Bs) ->
36           case gen_tcp:recv(Sock, 0) of
37               {ok, B} ->
38                   do_recv(Sock, [Bs, B]);
39               {error, closed} ->
40                   {ok, list_to_binary(Bs)}
41           end.
42
43       For more examples, see section Examples.
44
45   Note:
46       Functions  that create sockets can take an optional option; {inet_back‐
47       end, Backend} that, if specified, has to be the first option. This  se‐
48       lects the implementation backend towards the platform's socket API.
49
50       This is a temporary option that will be ignored in a future release.
51
52       The  default  is Backend = inet that selects the traditional inet_drv.c
53       driver. The other choice is Backend  =  socket  that  selects  the  new
54       socket module and its NIF implementation.
55
56       The system default can be changed when the node is started with the ap‐
57       plication kernel's configuration variable inet_backend.
58
59       For gen_tcp with inet_backend = socket we have tried to be as "compati‐
60       ble" as possible which has sometimes been impossible. Here is a list of
61       cases when the behaviour of inet-backend inet (default) and socket  are
62       different:
63
64         * Non-blocking send
65
66           If a user calling gen_tcp:send/2 with inet_backend = inet, tries to
67           send more data than there is room for in the OS buffers, the  "rest
68           data"  is  buffered by the inet driver (and later sent in the back‐
69           ground). The effect for the user is that the call is non-blocking.
70
71           This is not the effect when inet_backend = socket, since  there  is
72           no buffering. Instead the user hangs either until all data has been
73           sent or the send_timeout timeout has been reached.
74
75         * Remote close detected by background send.
76
77           An background send will detect  a  'remote  close'  and  (the  inet
78           driver will) mark the socket as 'closed'. No other action is taken.
79           If the socket has active set to false (passive) at this  point  and
80           no  one  is  reading,  this will not be noticed. But as soon as the
81           socket is "activated" (active set to not false, send/2 is called or
82           recv/2,3 is called), an error message will be sent to the caller or
83           (socket) owner: {tcp_error, Socket, econnreset}. Any data in the OS
84           receive buffers will be lost!
85
86           This  behaviour  is  not replicated by the socket implementation. A
87           send operation will detect a remote close  and  immediately  return
88           this  to the caller, but do nothing else. A reader will therefor be
89           able to extract any data from the OS buffers. If the socket is  set
90           to  active  to  not  false,  the  data will be received as expected
91           ({tcp, ...} and then a closed message ({tcp_closed,  ...}  will  be
92           received (not an error).
93
94         * The  option show_econnreset basically do not work as described when
95           used with inet_backend = socket. The "issue" is that a remote close
96           (as  described  above)  do allow a reader to extract what is in the
97           read buffers before a close is "delivered".
98
99         * The option nodelay is a TCP specific option that is not  compatible
100           with domain = local.
101
102           When  using  inet_backend  = socket, trying to create a socket (via
103           listen or connect) with domain = local  (for  example  with  option
104           {ifaddr, {local,"/tmp/test"}}) will fail with {error, enotsup}.
105
106           This  does not actually work for inet_backend = inet either, but in
107           that case the error is simply ignored, which is a bad idea. We have
108           choosen to not ignore this error for inet_backend = socket.
109
110         * Async shutdown write
111
112           Calling  gen_tcp:shutdown(Socket,  write  | read_write) on a socket
113           created with inet_backend = socket will take immediate effect,  un‐
114           like for a socket created with inet_backend = inet.
115
116           See async shutdown write for more info.
117

DATA TYPES

119       option() =
120           {active, true | false | once | -32768..32767} |
121           {buffer, integer() >= 0} |
122           {delay_send, boolean()} |
123           {deliver, port | term} |
124           {dontroute, boolean()} |
125           {exit_on_close, boolean()} |
126           {header, integer() >= 0} |
127           {high_msgq_watermark, integer() >= 1} |
128           {high_watermark, integer() >= 0} |
129           {keepalive, boolean()} |
130           {linger, {boolean(), integer() >= 0}} |
131           {low_msgq_watermark, integer() >= 1} |
132           {low_watermark, integer() >= 0} |
133           {mode, list | binary} |
134           list | binary |
135           {nodelay, boolean()} |
136           {packet,
137            0 | 1 | 2 | 4 | raw | sunrm | asn1 | cdr | fcgi | line |
138            tpkt | http | httph | http_bin | httph_bin} |
139           {packet_size, integer() >= 0} |
140           {priority, integer() >= 0} |
141           {raw,
142            Protocol :: integer() >= 0,
143            OptionNum :: integer() >= 0,
144            ValueBin :: binary()} |
145           {recbuf, integer() >= 0} |
146           {reuseaddr, boolean()} |
147           {send_timeout, integer() >= 0 | infinity} |
148           {send_timeout_close, boolean()} |
149           {show_econnreset, boolean()} |
150           {sndbuf, integer() >= 0} |
151           {tos, integer() >= 0} |
152           {tclass, integer() >= 0} |
153           {ttl, integer() >= 0} |
154           {recvtos, boolean()} |
155           {recvtclass, boolean()} |
156           {recvttl, boolean()} |
157           {ipv6_v6only, boolean()}
158
159       pktoptions_value() = {pktoptions, inet:ancillary_data()}
160
161              If the platform implements the IPv4 option IP_PKTOPTIONS, or the
162              IPv6  option  IPV6_PKTOPTIONS  or  IPV6_2292PKTOPTIONS  for  the
163              socket  this  value  is returned from inet:getopts/2 when called
164              with the option name pktoptions.
165
166          Note:
167              This option appears to be VERY Linux specific, and its existence
168              in  future  Linux kernel versions is also worrying since the op‐
169              tion is part of RFC 2292 which is since long (2003) obsoleted by
170              RFC  3542 that explicitly removes this possibility to get packet
171              information from a stream socket. For comparision:  it  has  ex‐
172              isted in FreeBSD but is now removed, at least since FreeBSD 10.
173
174
175       option_name() =
176           active | buffer | delay_send | deliver | dontroute |
177           exit_on_close | header | high_msgq_watermark |
178           high_watermark | keepalive | linger | low_msgq_watermark |
179           low_watermark | mode | nodelay | packet | packet_size |
180           priority |
181           {raw,
182            Protocol :: integer() >= 0,
183            OptionNum :: integer() >= 0,
184            ValueSpec ::
185                (ValueSize :: integer() >= 0) | (ValueBin :: binary())} |
186           recbuf | reuseaddr | send_timeout | send_timeout_close |
187           show_econnreset | sndbuf | tos | tclass | ttl | recvtos |
188           recvtclass | recvttl | pktoptions | ipv6_v6only
189
190       connect_option() =
191           {ip, inet:socket_address()} |
192           {fd, Fd :: integer() >= 0} |
193           {ifaddr, inet:socket_address()} |
194           inet:address_family() |
195           {port, inet:port_number()} |
196           {tcp_module, module()} |
197           {netns, file:filename_all()} |
198           {bind_to_device, binary()} |
199           option()
200
201       listen_option() =
202           {ip, inet:socket_address()} |
203           {fd, Fd :: integer() >= 0} |
204           {ifaddr, inet:socket_address()} |
205           inet:address_family() |
206           {port, inet:port_number()} |
207           {backlog, B :: integer() >= 0} |
208           {tcp_module, module()} |
209           {netns, file:filename_all()} |
210           {bind_to_device, binary()} |
211           option()
212
213       socket()
214
215              As returned by accept/1,2 and connect/3,4.
216

EXPORTS

218       accept(ListenSocket) -> {ok, Socket} | {error, Reason}
219
220       accept(ListenSocket, Timeout) -> {ok, Socket} | {error, Reason}
221
222              Types:
223
224                 ListenSocket = socket()
225                   Returned by listen/2.
226                 Timeout = timeout()
227                 Socket = socket()
228                 Reason = closed | timeout | system_limit | inet:posix()
229
230              Accepts  an  incoming  connection request on a listening socket.
231              Socket must be a socket returned from listen/2.  Timeout  speci‐
232              fies a time-out value in milliseconds. Defaults to infinity.
233
234              Returns:
235
236                * {ok, Socket} if a connection is established
237
238                * {error, closed} if ListenSocket is closed
239
240                * {error,  timeout} if no connection is established within the
241                  specified time
242
243                * {error, system_limit} if all available ports in  the  Erlang
244                  emulator are in use
245
246                * A  POSIX  error  value  if  something  else  goes wrong, see
247                  inet(3) for possible error values
248
249              Packets can be sent to the returned socket Socket using  send/2.
250              Packets  sent  from  the  peer are delivered as messages (unless
251              {active, false} is specified in the option list for the  listen‐
252              ing  socket,  in  which  case  packets  are retrieved by calling
253              recv/2):
254
255              {tcp, Socket, Data}
256
257          Note:
258              The accept call does not have to be issued from the socket owner
259              process.  Using version 5.5.3 and higher of the emulator, multi‐
260              ple simultaneous accept calls can be issued from different  pro‐
261              cesses,  which  allows for a pool of acceptor processes handling
262              incoming connections.
263
264
265       close(Socket) -> ok
266
267              Types:
268
269                 Socket = socket()
270
271              Closes a TCP socket.
272
273              Note that in most implementations of TCP, doing a close does not
274              guarantee  that  any data sent is delivered to the recipient be‐
275              fore the close is detected at the remote side. If  you  want  to
276              guarantee  delivery  of  the data to the recipient there are two
277              common ways to achieve this.
278
279                * Use gen_tcp:shutdown(Sock, write) to  signal  that  no  more
280                  data  is to be sent and wait for the read side of the socket
281                  to be closed.
282
283                * Use the socket option {packet, N} (or something similar)  to
284                  make  it  possible  for the receiver to close the connection
285                  when it knowns it has received all the data.
286
287       connect(Address, Port, Options) -> {ok, Socket} | {error, Reason}
288
289       connect(Address, Port, Options, Timeout) ->
290                  {ok, Socket} | {error, Reason}
291
292              Types:
293
294                 Address = inet:socket_address() | inet:hostname()
295                 Port = inet:port_number()
296                 Options = [inet:inet_backend() | connect_option()]
297                 Timeout = timeout()
298                 Socket = socket()
299                 Reason = timeout | inet:posix()
300
301              Connects to a server on TCP port Port on the host  with  IP  ad‐
302              dress  Address.  Argument Address can be a hostname or an IP ad‐
303              dress.
304
305              The following options are available:
306
307                {ip, Address}:
308                  If the host has many network interfaces, this option  speci‐
309                  fies which one to use.
310
311                {ifaddr, Address}:
312                  Same  as  {ip, Address}. If the host has many network inter‐
313                  faces, this option specifies which one to use.
314
315                {fd, integer() >= 0}:
316                  If  a  socket  has  somehow  been  connected  without  using
317                  gen_tcp, use this option to pass the file descriptor for it.
318                  If {ip, Address} and/or {port,  port_number()}  is  combined
319                  with this option, the fd is bound to the specified interface
320                  and port before connecting. If these options are not  speci‐
321                  fied,  it  is assumed that the fd is already bound appropri‐
322                  ately.
323
324                inet:
325                  Sets up the socket for IPv4.
326
327                inet6:
328                  Sets up the socket for IPv6.
329
330                local:
331                  Sets up a Unix Domain Socket. See inet:local_address()
332
333                {port, Port}:
334                  Specifies which local port number to use.
335
336                {tcp_module, module()}:
337                  Overrides  which  callback  module  is  used.  Defaults   to
338                  inet_tcp for IPv4 and inet6_tcp for IPv6.
339
340                Opt:
341                  See inet:setopts/2.
342
343              Packets  can be sent to the returned socket Socket using send/2.
344              Packets sent from the peer are delivered as messages:
345
346              {tcp, Socket, Data}
347
348              If the socket is in {active, N} mode (see inet:setopts/2 for de‐
349              tails) and its message counter drops to 0, the following message
350              is delivered to indicate that the  socket  has  transitioned  to
351              passive ({active, false}) mode:
352
353              {tcp_passive, Socket}
354
355              If the socket is closed, the following message is delivered:
356
357              {tcp_closed, Socket}
358
359              If  an  error occurs on the socket, the following message is de‐
360              livered (unless {active, false} is specified in the option  list
361              for  the  socket, in which case packets are retrieved by calling
362              recv/2):
363
364              {tcp_error, Socket, Reason}
365
366              The optional Timeout parameter specifies a time-out in millisec‐
367              onds. Defaults to infinity.
368
369          Note:
370              Keep  in mind that if the underlying OS connect() call returns a
371              timeout, gen_tcp:connect will also return a timeout  (i.e.  {er‐
372              ror, etimedout}), even if a larger Timeout was specified.
373
374
375          Note:
376              The  default  values for options specified to connect can be af‐
377              fected by the Kernel configuration  parameter  inet_default_con‐
378              nect_options. For details, see inet(3).
379
380
381       controlling_process(Socket, Pid) -> ok | {error, Reason}
382
383              Types:
384
385                 Socket = socket()
386                 Pid = pid()
387                 Reason = closed | not_owner | badarg | inet:posix()
388
389              Assigns a new controlling process Pid to Socket. The controlling
390              process is the process that receives messages from  the  socket.
391              If  called  by  any  other  process than the current controlling
392              process, {error, not_owner} is returned. If the process  identi‐
393              fied by Pid is not an existing local pid, {error, badarg} is re‐
394              turned. {error, badarg} may also be returned in some cases  when
395              Socket is closed during the execution of this function.
396
397              If the socket is set in active mode, this function will transfer
398              any messages in the mailbox of the caller to the new controlling
399              process.  If  any  other  process is interacting with the socket
400              while the transfer is happening, the transfer may not work  cor‐
401              rectly  and messages may remain in the caller's mailbox. For in‐
402              stance changing the sockets active mode before the  transfer  is
403              complete may cause this.
404
405       listen(Port, Options) -> {ok, ListenSocket} | {error, Reason}
406
407              Types:
408
409                 Port = inet:port_number()
410                 Options = [inet:inet_backend() | listen_option()]
411                 ListenSocket = socket()
412                 Reason = system_limit | inet:posix()
413
414              Sets up a socket to listen on port Port on the local host.
415
416              If  Port  == 0, the underlying OS assigns an available port num‐
417              ber, use inet:port/1 to retrieve it.
418
419              The following options are available:
420
421                list:
422                  Received Packet is delivered as a list.
423
424                binary:
425                  Received Packet is delivered as a binary.
426
427                {backlog, B}:
428                  B is an integer >= 0. The backlog value defines the  maximum
429                  length  that  the  queue of pending connections can grow to.
430                  Defaults to 5.
431
432                {ip, Address}:
433                  If the host has many network interfaces, this option  speci‐
434                  fies which one to listen on.
435
436                {port, Port}:
437                  Specifies which local port number to use.
438
439                {fd, Fd}:
440                  If  a  socket  has  somehow  been  connected  without  using
441                  gen_tcp, use this option to pass the file descriptor for it.
442
443                {ifaddr, Address}:
444                  Same as {ip, Address}. If the host has many  network  inter‐
445                  faces, this option specifies which one to use.
446
447                inet6:
448                  Sets up the socket for IPv6.
449
450                inet:
451                  Sets up the socket for IPv4.
452
453                {tcp_module, module()}:
454                  Overrides   which  callback  module  is  used.  Defaults  to
455                  inet_tcp for IPv4 and inet6_tcp for IPv6.
456
457                Opt:
458                  See inet:setopts/2.
459
460              The returned socket ListenSocket should be used in calls to  ac‐
461              cept/1,2 to accept incoming connection requests.
462
463          Note:
464              The  default  values  for options specified to listen can be af‐
465              fected by the Kernel configuration  parameter  inet_default_lis‐
466              ten_options. For details, see inet(3).
467
468
469       recv(Socket, Length) -> {ok, Packet} | {error, Reason}
470
471       recv(Socket, Length, Timeout) -> {ok, Packet} | {error, Reason}
472
473              Types:
474
475                 Socket = socket()
476                 Length = integer() >= 0
477                 Timeout = timeout()
478                 Packet = string() | binary() | HttpPacket
479                 Reason = closed | timeout | inet:posix()
480                 HttpPacket = term()
481                   See the description of HttpPacket in erlang:decode_packet/3
482                   in ERTS.
483
484              Receives a packet from a socket in passive mode. A closed socket
485              is indicated by return value {error, closed}.
486
487              Argument  Length  is  only  meaningful when the socket is in raw
488              mode and denotes the number of bytes to read. If  Length  is  0,
489              all  available bytes are returned. If Length > 0, exactly Length
490              bytes are returned, or an error; possibly discarding  less  than
491              Length  bytes  of  data when the socket is closed from the other
492              side.
493
494              The optional Timeout parameter specifies a time-out in millisec‐
495              onds. Defaults to infinity.
496
497       send(Socket, Packet) -> ok | {error, Reason}
498
499              Types:
500
501                 Socket = socket()
502                 Packet = iodata()
503                 Reason = closed | {timeout, RestData} | inet:posix()
504                 RestData = binary()
505
506              Sends a packet on a socket.
507
508              There  is no send call with a time-out option, use socket option
509              send_timeout if time-outs are desired. See section Examples.
510
511              The return value {error, {timeout, RestData}} can  only  be  re‐
512              turned when inet_backend = socket.
513
514          Note:
515              Non-blocking send.
516
517              If  the  user  tries to send more data than there is room for in
518              the OS send buffers, the 'rest data' is put into  (inet  driver)
519              internal  buffers and later sent in the background. The function
520              immediately returns ok (not informing the caller that not all of
521              the  data  was actually sent). Any issue while sending the 'rest
522              data' is maybe returned later.
523
524              When using inet_backend = socket, the  behaviour  is  different.
525              There  is no buffering done (like the inet-driver does), instead
526              the caller will "hang" until all of the data has  been  sent  or
527              send  timeout  (as specified by the send_timeout option) expires
528              (the function can hang even when using 'inet' backend if the in‐
529              ternal buffers are full).
530
531              If  this  happens  when  using packet =/= raw, we have a partial
532              package written. A new package therefor must not be  written  at
533              this  point, as there is no way for the peer to distinguish this
534              from the data portion of the current package. Instead, set pack‐
535              age  to raw, send the rest data (as raw data) and then set pack‐
536              age to the wanted package type again.
537
538
539       shutdown(Socket, How) -> ok | {error, Reason}
540
541              Types:
542
543                 Socket = socket()
544                 How = read | write | read_write
545                 Reason = inet:posix()
546
547              Closes a socket in one or two directions.
548
549              How == write means closing the socket for writing, reading  from
550              it is still possible.
551
552              If  How  ==  read  or  there is no outgoing data buffered in the
553              Socket port, the socket is shut down immediately and  any  error
554              encountered is returned in Reason.
555
556              If  there  is  data  buffered in the socket port, the attempt to
557              shutdown the socket is postponed until that data is  written  to
558              the  kernel  socket  send buffer. If any errors are encountered,
559              the socket is closed and {error, closed} is returned on the next
560              recv/2 or send/2.
561
562              Option  {exit_on_close,  false} is useful if the peer has done a
563              shutdown on the write side.
564
565          Note:
566              Async shutdown write (write or read_write).
567
568              If the shutdown attempt is made while the inet-driver is sending
569              buffered data in the background, the shutdown is postponed until
570              all buffered data has been sent. The  function  immediately  re‐
571              turns  ok  and the caller is not informed (that the shutdown has
572              not yet been performed).
573
574              When using inet_backend = socket, the behaviour is different.  A
575              shutdown with How == write | read_write, the operation will take
576              immediate effect (unlike the inet-driver, which basically  saves
577              the operation for later).
578
579

EXAMPLES

581       The  following example illustrates use of option {active,once} and mul‐
582       tiple accepts by implementing a server as a number of worker  processes
583       doing  accept  on a single listening socket. Function start/2 takes the
584       number of worker processes and the port number on which to  listen  for
585       incoming  connections.  If  LPort  is specified as 0, an ephemeral port
586       number is used, which is why the start function returns the actual port
587       number allocated:
588
589       start(Num,LPort) ->
590           case gen_tcp:listen(LPort,[{active, false},{packet,2}]) of
591               {ok, ListenSock} ->
592                   start_servers(Num,ListenSock),
593                   {ok, Port} = inet:port(ListenSock),
594                   Port;
595               {error,Reason} ->
596                   {error,Reason}
597           end.
598
599       start_servers(0,_) ->
600           ok;
601       start_servers(Num,LS) ->
602           spawn(?MODULE,server,[LS]),
603           start_servers(Num-1,LS).
604
605       server(LS) ->
606           case gen_tcp:accept(LS) of
607               {ok,S} ->
608                   loop(S),
609                   server(LS);
610               Other ->
611                   io:format("accept returned ~w - goodbye!~n",[Other]),
612                   ok
613           end.
614
615       loop(S) ->
616           inet:setopts(S,[{active,once}]),
617           receive
618               {tcp,S,Data} ->
619                   Answer = process(Data), % Not implemented in this example
620                   gen_tcp:send(S,Answer),
621                   loop(S);
622               {tcp_closed,S} ->
623                   io:format("Socket ~w closed [~w]~n",[S,self()]),
624                   ok
625           end.
626
627       Example of a simple client:
628
629       client(PortNo,Message) ->
630           {ok,Sock} = gen_tcp:connect("localhost",PortNo,[{active,false},
631                                                           {packet,2}]),
632           gen_tcp:send(Sock,Message),
633           A = gen_tcp:recv(Sock,0),
634           gen_tcp:close(Sock),
635           A.
636
637       The  send  call  does not accept a time-out option because time-outs on
638       send is handled through socket option send_timeout. The behavior  of  a
639       send operation with no receiver is mainly defined by the underlying TCP
640       stack and the network infrastructure. To  write  code  that  handles  a
641       hanging receiver that can eventually cause the sender to hang on a send
642       do like the following.
643
644       Consider a process that receives data from a client process to be  for‐
645       warded  to  a  server  on  the network. The process is connected to the
646       server through TCP/IP and does not get any acknowledge for each message
647       it  sends,  but  has to rely on the send time-out option to detect that
648       the other end is unresponsive. Option send_timeout  can  be  used  when
649       connecting:
650
651       {ok,Sock} = gen_tcp:connect(HostAddress, Port,
652                                   [{active,false},
653                                    {send_timeout, 5000},
654                                    {packet,2}]),
655                       loop(Sock), % See below
656
657       In  the  loop where requests are handled, send time-outs can now be de‐
658       tected:
659
660       loop(Sock) ->
661           receive
662               {Client, send_data, Binary} ->
663                   case gen_tcp:send(Sock,[Binary]) of
664                       {error, timeout} ->
665                           io:format("Send timeout, closing!~n",
666                                     []),
667                           handle_send_timeout(), % Not implemented here
668                           Client ! {self(),{error_sending, timeout}},
669                           %% Usually, it's a good idea to give up in case of a
670                           %% send timeout, as you never know how much actually
671                           %% reached the server, maybe only a packet header?!
672                           gen_tcp:close(Sock);
673                       {error, OtherSendError} ->
674                           io:format("Some other error on socket (~p), closing",
675                                     [OtherSendError]),
676                           Client ! {self(),{error_sending, OtherSendError}},
677                           gen_tcp:close(Sock);
678                       ok ->
679                           Client ! {self(), data_sent},
680                           loop(Sock)
681                   end
682           end.
683
684       Usually it suffices to detect time-outs on receive, as  most  protocols
685       include  some sort of acknowledgment from the server, but if the proto‐
686       col is strictly one way, option send_timeout comes in handy.
687
688
689
690Ericsson AB                      kernel 8.1.3                       gen_tcp(3)
Impressum