summaryrefslogtreecommitdiff
path: root/gcc/ada/g-socket.ads
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/ada/g-socket.ads')
-rw-r--r--gcc/ada/g-socket.ads559
1 files changed, 383 insertions, 176 deletions
diff --git a/gcc/ada/g-socket.ads b/gcc/ada/g-socket.ads
index 213de119c02..57a83743f1e 100644
--- a/gcc/ada/g-socket.ads
+++ b/gcc/ada/g-socket.ads
@@ -6,7 +6,7 @@
-- --
-- S p e c --
-- --
--- Copyright (C) 2001-2002 Ada Core Technologies, Inc. --
+-- Copyright (C) 2001-2003 Ada Core Technologies, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
@@ -26,311 +26,343 @@
-- however invalidate any other reasons why the executable file might be --
-- covered by the GNU Public License. --
-- --
--- GNAT is maintained by Ada Core Technologies Inc (http://www.gnat.com). --
+-- GNAT was originally developed by the GNAT team at New York University. --
+-- Extensive contributions were provided by Ada Core Technologies Inc. --
-- --
------------------------------------------------------------------------------
--- This package provides an interface to the sockets communication facility
--- provided on many operating systems. Currently this is implemented on all
--- native GNAT ports except for VMS. It is not yet implemented on the Lynx
--- cross-ports.
+-- This package provides an interface to the sockets communication
+-- facility provided on many operating systems. This is implemented
+-- on the following platforms:
--- Another restriction is that there is no multicast support under Windows
--- or under any system on which the multicast support is not available or
--- installed.
+-- All native ports, except Interix, with restrictions as follows
+
+-- Multicast is available only on systems which provide support
+-- for this feature, so it is not available if Multicast is not
+-- supported, or not installed. In particular Multicast is not
+-- available with the Windows version.
+
+-- The VMS implementation has implemented using the DECC RTL Socket
+-- API, and is thus subject to limitations in the implementation of
+-- this API.
+
+-- This package is not supported on the Interix port of GNAT.
+
+-- VxWorks cross ports fully implement this package.
+
+-- This package is not yet implemented on LynxOS.
with Ada.Exceptions;
with Ada.Streams;
+with System;
+
package GNAT.Sockets is
-- Sockets are designed to provide a consistent communication facility
- -- between applications. This package provides an Ada-like intrerface
- -- similar to that proposed as part of the BSD socket layer. This is a
- -- system independent thick binding.
+ -- between applications. This package provides an Ada-like interface
+ -- similar to that proposed as part of the BSD socket layer.
+
+ -- GNAT.Sockets has been designed with several ideas in mind.
+
+ -- This is a system independent interface. Therefore, we try as
+ -- much as possible to mask system incompatibilities. Some
+ -- functionalities are not available because there are not fully
+ -- supported on some systems.
+
+ -- This is a thick binding. For instance, a major effort has been
+ -- done to avoid using memory addresses or untyped ints. We
+ -- preferred to define streams and enumeration types. Errors are
+ -- not returned as returned values but as exceptions.
+
+ -- This package provides a POSIX-compliant interface (between two
+ -- different implementations of the same routine, we adopt the one
+ -- closest to the POSIX specification). For instance, using
+ -- select(), the notification of an asynchronous connect failure
+ -- is delivered in the write socket set (POSIX) instead of the
+ -- exception socket set (NT).
-- Here is a typical example of what you can do:
-- with GNAT.Sockets; use GNAT.Sockets;
- --
+
-- with Ada.Text_IO;
-- with Ada.Exceptions; use Ada.Exceptions;
- --
+
-- procedure PingPong is
- --
+
-- Group : constant String := "239.255.128.128";
- -- -- Multicast groupe: administratively scoped IP address
- --
+ -- -- Multicast group: administratively scoped IP address
+
-- task Pong is
-- entry Start;
-- entry Stop;
-- end Pong;
- --
+
-- task body Pong is
-- Address : Sock_Addr_Type;
-- Server : Socket_Type;
-- Socket : Socket_Type;
-- Channel : Stream_Access;
- --
+
-- begin
-- accept Start;
--
-- -- Get an Internet address of a host (here the local host name).
-- -- Note that a host can have several addresses. Here we get
-- -- the first one which is supposed to be the official one.
- --
+
-- Address.Addr := Addresses (Get_Host_By_Name (Host_Name), 1);
- --
+
-- -- Get a socket address that is an Internet address and a port
- --
- -- Address.Port := 5432;
- --
+
+ -- Address.Port := 5876;
+
-- -- The first step is to create a socket. Once created, this
-- -- socket must be associated to with an address. Usually only
-- -- a server (Pong here) needs to bind an address explicitly.
-- -- Most of the time clients can skip this step because the
-- -- socket routines will bind an arbitrary address to an unbound
-- -- socket.
- --
+
-- Create_Socket (Server);
- --
- -- -- Allow reuse of local addresses.
- --
+
+ -- -- Allow reuse of local addresses
+
-- Set_Socket_Option
-- (Server,
-- Socket_Level,
-- (Reuse_Address, True));
- --
+
-- Bind_Socket (Server, Address);
- --
- -- -- A server marks a socket as willing to receive connect events.
- --
+
+ -- -- A server marks a socket as willing to receive connect events
+
-- Listen_Socket (Server);
- --
+
-- -- Once a server calls Listen_Socket, incoming connects events
-- -- can be accepted. The returned Socket is a new socket that
-- -- represents the server side of the connection. Server remains
-- -- available to receive further connections.
- --
+
-- Accept_Socket (Server, Socket, Address);
- --
- -- -- Return a stream associated to the connected socket.
- --
+
+ -- -- Return a stream associated to the connected socket
+
-- Channel := Stream (Socket);
- --
+
-- -- Force Pong to block
- --
+
-- delay 0.2;
- --
- -- -- Receive and print message from client Ping.
- --
+
+ -- -- Receive and print message from client Ping
+
-- declare
-- Message : String := String'Input (Channel);
- --
+
-- begin
-- Ada.Text_IO.Put_Line (Message);
- --
- -- -- Send same message to server Pong.
- --
+
+ -- -- Send same message back to client Ping
+
-- String'Output (Channel, Message);
-- end;
- --
+
-- Close_Socket (Server);
-- Close_Socket (Socket);
- --
+
-- -- Part of the multicast example
- --
+
-- -- Create a datagram socket to send connectionless, unreliable
-- -- messages of a fixed maximum length.
- --
+
-- Create_Socket (Socket, Family_Inet, Socket_Datagram);
- --
- -- -- Allow reuse of local addresses.
- --
+
+ -- -- Allow reuse of local addresses
+
-- Set_Socket_Option
-- (Socket,
-- Socket_Level,
-- (Reuse_Address, True));
- --
- -- -- Join a multicast group.
- --
+
+ -- -- Join a multicast group
+
-- Set_Socket_Option
-- (Socket,
-- IP_Protocol_For_IP_Level,
-- (Add_Membership, Inet_Addr (Group), Any_Inet_Addr));
- --
+
-- -- Controls the live time of the datagram to avoid it being
-- -- looped forever due to routing errors. Routers decrement
-- -- the TTL of every datagram as it traverses from one network
-- -- to another and when its value reaches 0 the packet is
-- -- dropped. Default is 1.
- --
+
-- Set_Socket_Option
-- (Socket,
-- IP_Protocol_For_IP_Level,
-- (Multicast_TTL, 1));
- --
- -- -- Want the data you send to be looped back to your host.
- --
+
+ -- -- Want the data you send to be looped back to your host
+
-- Set_Socket_Option
-- (Socket,
-- IP_Protocol_For_IP_Level,
-- (Multicast_Loop, True));
- --
- -- -- If this socket is intended to receive messages, bind it to a
- -- -- given socket address.
- --
+
+ -- -- If this socket is intended to receive messages, bind it
+ -- -- to a given socket address.
+
-- Address.Addr := Any_Inet_Addr;
-- Address.Port := 55505;
- --
+
-- Bind_Socket (Socket, Address);
- --
+
-- -- If this socket is intended to send messages, provide the
-- -- receiver socket address.
- --
+
-- Address.Addr := Inet_Addr (Group);
-- Address.Port := 55506;
- --
+
-- Channel := Stream (Socket, Address);
- --
- -- -- Receive and print message from client Ping.
- --
+
+ -- -- Receive and print message from client Ping
+
-- declare
-- Message : String := String'Input (Channel);
- --
+
-- begin
- --
- -- -- Get the address of the sender.
- --
+ -- -- Get the address of the sender
+
-- Address := Get_Address (Channel);
-- Ada.Text_IO.Put_Line (Message & " from " & Image (Address));
- --
- -- -- Send same message to server Pong.
- --
+
+ -- -- Send same message back to client Ping
+
-- String'Output (Channel, Message);
-- end;
- --
+
-- Close_Socket (Socket);
- --
+
-- accept Stop;
- --
+
-- exception when E : others =>
-- Ada.Text_IO.Put_Line
-- (Exception_Name (E) & ": " & Exception_Message (E));
-- end Pong;
- --
+
-- task Ping is
-- entry Start;
-- entry Stop;
-- end Ping;
- --
+
-- task body Ping is
-- Address : Sock_Addr_Type;
-- Socket : Socket_Type;
-- Channel : Stream_Access;
- --
+
-- begin
-- accept Start;
- --
- -- -- See comments in Ping section for the first steps.
- --
+
+ -- -- See comments in Ping section for the first steps
+
-- Address.Addr := Addresses (Get_Host_By_Name (Host_Name), 1);
- -- Address.Port := 5432;
+ -- Address.Port := 5876;
-- Create_Socket (Socket);
- --
+
-- Set_Socket_Option
-- (Socket,
-- Socket_Level,
-- (Reuse_Address, True));
- --
+
-- -- Force Pong to block
- --
+
-- delay 0.2;
- --
+
-- -- If the client's socket is not bound, Connect_Socket will
-- -- bind to an unused address. The client uses Connect_Socket to
-- -- create a logical connection between the client's socket and
-- -- a server's socket returned by Accept_Socket.
- --
+
-- Connect_Socket (Socket, Address);
- --
+
-- Channel := Stream (Socket);
- --
+
-- -- Send message to server Pong.
- --
+
-- String'Output (Channel, "Hello world");
- --
+
-- -- Force Ping to block
- --
+
-- delay 0.2;
- --
- -- -- Receive and print message from server Pong.
- --
+
+ -- -- Receive and print message from server Pong
+
-- Ada.Text_IO.Put_Line (String'Input (Channel));
-- Close_Socket (Socket);
- --
- -- -- Part of multicast example. Code similar to Pong's one.
- --
+
+ -- -- Part of multicast example. Code similar to Pong's one
+
-- Create_Socket (Socket, Family_Inet, Socket_Datagram);
- --
+
-- Set_Socket_Option
-- (Socket,
-- Socket_Level,
-- (Reuse_Address, True));
- --
+
-- Set_Socket_Option
-- (Socket,
-- IP_Protocol_For_IP_Level,
-- (Add_Membership, Inet_Addr (Group), Any_Inet_Addr));
- --
+
-- Set_Socket_Option
-- (Socket,
-- IP_Protocol_For_IP_Level,
-- (Multicast_TTL, 1));
- --
+
-- Set_Socket_Option
-- (Socket,
-- IP_Protocol_For_IP_Level,
-- (Multicast_Loop, True));
- --
+
-- Address.Addr := Any_Inet_Addr;
-- Address.Port := 55506;
- --
+
-- Bind_Socket (Socket, Address);
- --
+
-- Address.Addr := Inet_Addr (Group);
-- Address.Port := 55505;
- --
+
-- Channel := Stream (Socket, Address);
- --
- -- -- Send message to server Pong.
- --
+
+ -- -- Send message to server Pong
+
-- String'Output (Channel, "Hello world");
- --
- -- -- Receive and print message from server Pong.
- --
+
+ -- -- Receive and print message from server Pong
+
-- declare
-- Message : String := String'Input (Channel);
- --
+
-- begin
-- Address := Get_Address (Channel);
-- Ada.Text_IO.Put_Line (Message & " from " & Image (Address));
-- end;
- --
+
-- Close_Socket (Socket);
- --
+
-- accept Stop;
- --
+
-- exception when E : others =>
-- Ada.Text_IO.Put_Line
-- (Exception_Name (E) & ": " & Exception_Message (E));
-- end Ping;
- --
+
-- begin
-- -- Indicate whether the thread library provides process
-- -- blocking IO. Basically, if you are not using FSU threads
-- -- the default is ok.
- --
+
-- Initialize (Process_Blocking_IO => False);
-- Ping.Start;
-- Pong.Start;
@@ -340,11 +372,18 @@ package GNAT.Sockets is
-- end PingPong;
procedure Initialize (Process_Blocking_IO : Boolean := False);
- -- Initialize must be called before using any socket routines. If
- -- the thread library provides process blocking IO - basically
- -- with FSU threads - GNAT.Sockets should be initialized with a
- -- value of True to simulate thread blocking IO. Further calls to
- -- Initialize will be ignored.
+ -- Initialize must be called before using any other socket routines.
+ -- The Process_Blocking_IO parameter indicates whether the thread
+ -- library provides process-blocking or thread-blocking input/output
+ -- operations. In the former case (typically with FSU threads)
+ -- GNAT.Sockets should be initialized with a value of True to
+ -- provide task-blocking IO through an emulation mechanism.
+ -- Only the first call to Initialize is taken into account (further
+ -- calls will be ignored). Note that with the default value
+ -- of Process_Blocking_IO, this operation is a no-op on UNIX
+ -- platforms, but applications should make sure to call it
+ -- if portability is expected: some platforms (such as Windows)
+ -- require initialization before any other socket operations.
procedure Finalize;
-- After Finalize is called it is not possible to use any routines
@@ -431,7 +470,7 @@ package GNAT.Sockets is
-- Convert address image from numbers-and-dots notation into an
-- inet address.
- -- Host entries provide a complete information on a given host:
+ -- Host entries provide complete information on a given host:
-- the official name, an array of alternative names or aliases and
-- array of network addresses.
@@ -473,11 +512,50 @@ package GNAT.Sockets is
function Get_Host_By_Name
(Name : String)
return Host_Entry_Type;
- -- Return host entry structure for the given host name
+ -- Return host entry structure for the given host name. Here name
+ -- is either a host name, or an IP address.
function Host_Name return String;
-- Return the name of the current host
+ -- Service entries provide complete information on a given
+ -- service: the official name, an array of alternative names or
+ -- aliases and the port number.
+
+ type Service_Entry_Type (Aliases_Length : Natural) is private;
+
+ function Official_Name (S : Service_Entry_Type) return String;
+ -- Return official name in service entry
+
+ function Port_Number (S : Service_Entry_Type) return Port_Type;
+ -- Return port number in service entry
+
+ function Protocol_Name (S : Service_Entry_Type) return String;
+ -- Return Protocol in service entry (usually UDP or TCP)
+
+ function Aliases_Length (S : Service_Entry_Type) return Natural;
+ -- Return number of aliases in service entry
+
+ function Aliases
+ (S : Service_Entry_Type;
+ N : Positive := 1)
+ return String;
+ -- Return N'th aliases in service entry. The first index is 1.
+
+ function Get_Service_By_Name
+ (Name : String;
+ Protocol : String)
+ return Service_Entry_Type;
+ -- Return service entry structure for the given service name
+
+ function Get_Service_By_Port
+ (Port : Port_Type;
+ Protocol : String)
+ return Service_Entry_Type;
+ -- Return service entry structure for the given service port number
+
+ Service_Error : exception;
+
-- Errors are described by an enumeration type. There is only one
-- exception Socket_Error in this package to deal with an error
-- during a socket routine. Once raised, its message contains the
@@ -486,32 +564,48 @@ package GNAT.Sockets is
-- The name of the enumeration constant documents the error condition.
type Error_Type is
- (Permission_Denied,
+ (Success,
+ Permission_Denied,
Address_Already_In_Use,
Cannot_Assign_Requested_Address,
Address_Family_Not_Supported_By_Protocol,
Operation_Already_In_Progress,
Bad_File_Descriptor,
+ Software_Caused_Connection_Abort,
Connection_Refused,
+ Connection_Reset_By_Peer,
+ Destination_Address_Required,
Bad_Address,
+ Host_Is_Down,
+ No_Route_To_Host,
Operation_Now_In_Progress,
Interrupted_System_Call,
Invalid_Argument,
Input_Output_Error,
Transport_Endpoint_Already_Connected,
+ Too_Many_Symbolic_Links,
+ Too_Many_Open_Files,
Message_Too_Long,
+ File_Name_Too_Long,
+ Network_Is_Down,
+ Network_Dropped_Connection_Because_Of_Reset,
Network_Is_Unreachable,
No_Buffer_Space_Available,
Protocol_Not_Available,
Transport_Endpoint_Not_Connected,
+ Socket_Operation_On_Non_Socket,
Operation_Not_Supported,
+ Protocol_Family_Not_Supported,
Protocol_Not_Supported,
+ Protocol_Wrong_Type_For_Socket,
+ Cannot_Send_After_Transport_Endpoint_Shutdown,
Socket_Type_Not_Supported,
Connection_Timed_Out,
+ Too_Many_References,
Resource_Temporarily_Unavailable,
Unknown_Host,
Host_Name_Lookup_Failure,
- No_Address_Associated_With_Name,
+ Non_Recoverable_Error,
Unknown_Server_Error,
Cannot_Resolve_Error);
@@ -541,7 +635,7 @@ package GNAT.Sockets is
No_Delay, -- Do not delay send to coalesce packets (TCP_NODELAY)
Add_Membership, -- Join a multicast group
Drop_Membership, -- Leave a multicast group
- Multicast_TTL, -- Indicates the time-to-live of sent multicast packets
+ Multicast_TTL, -- Indicate the time-to-live of sent multicast packets
Multicast_Loop); -- Sent multicast packets are looped to the local socket
type Option_Type (Name : Option_Name := Keep_Alive) is record
@@ -599,11 +693,53 @@ package GNAT.Sockets is
end case;
end record;
+ -- A request flag allows to specify the type of message
+ -- transmissions or receptions. A request flag can be a
+ -- combination of zero or more predefined request flags.
+
+ type Request_Flag_Type is private;
+
+ No_Request_Flag : constant Request_Flag_Type;
+ -- This flag corresponds to the normal execution of an operation.
+
+ Process_Out_Of_Band_Data : constant Request_Flag_Type;
+ -- This flag requests that the receive or send function operates
+ -- on out-of-band data when the socket supports this notion (e.g.
+ -- Socket_Stream).
+
+ Peek_At_Incoming_Data : constant Request_Flag_Type;
+ -- This flag causes the receive operation to return data from the
+ -- beginning of the receive queue without removing that data from
+ -- the queue. A subsequent receive call will return the same data.
+
+ Wait_For_A_Full_Reception : constant Request_Flag_Type;
+ -- This flag requests that the operation block until the full
+ -- request is satisfied. However, the call may still return less
+ -- data than requested if a signal is caught, an error or
+ -- disconnect occurs, or the next data to be received is of a dif-
+ -- ferent type than that returned.
+
+ Send_End_Of_Record : constant Request_Flag_Type;
+ -- This flag indicates that the entire message has been sent and
+ -- so this terminates the record.
+
+ function "+" (L, R : Request_Flag_Type) return Request_Flag_Type;
+ -- Combine flag L with flag R
+
+ type Stream_Element_Reference is access all Ada.Streams.Stream_Element;
+
+ type Vector_Element is record
+ Base : Stream_Element_Reference;
+ Length : Ada.Streams.Stream_Element_Count;
+ end record;
+
+ type Vector_Type is array (Integer range <>) of Vector_Element;
+
procedure Create_Socket
(Socket : out Socket_Type;
Family : Family_Type := Family_Inet;
Mode : Mode_Type := Socket_Stream);
- -- Create an endpoint for communication. Raise Socket_Error on error.
+ -- Create an endpoint for communication. Raises Socket_Error on error.
procedure Accept_Socket
(Server : Socket_Type;
@@ -613,7 +749,7 @@ package GNAT.Sockets is
-- connections, creates a new connected socket with mostly the
-- same properties as Server, and allocates a new socket. The
-- returned Address is filled in with the address of the
- -- connection. Raise Socket_Error on error.
+ -- connection. Raises Socket_Error on error.
procedure Bind_Socket
(Socket : Socket_Type;
@@ -628,30 +764,31 @@ package GNAT.Sockets is
(Socket : Socket_Type;
Server : in out Sock_Addr_Type);
-- Make a connection to another socket which has the address of
- -- Server. Raise Socket_Error on error.
+ -- Server. Raises Socket_Error on error.
procedure Control_Socket
(Socket : Socket_Type;
Request : in out Request_Type);
-- Obtain or set parameter values that control the socket. This
-- control differs from the socket options in that they are not
- -- specific to sockets but are avaiable for any device.
+ -- specific to sockets but are available for any device.
function Get_Peer_Name (Socket : Socket_Type) return Sock_Addr_Type;
-- Return the peer or remote socket address of a socket. Raise
-- Socket_Error on error.
function Get_Socket_Name (Socket : Socket_Type) return Sock_Addr_Type;
- -- Return the local or current socket address of a socket. Raise
- -- Socket_Error on error.
+ -- Return the local or current socket address of a socket. Return
+ -- No_Sock_Addr on error (for instance, socket closed or not
+ -- locally bound).
function Get_Socket_Option
(Socket : Socket_Type;
Level : Level_Type := Socket_Level;
Name : Option_Name)
return Option_Type;
- -- Get the options associated with a socket. Raise Socket_Error on
- -- error.
+ -- Get the options associated with a socket. Raises Socket_Error
+ -- on error.
procedure Listen_Socket
(Socket : Socket_Type;
@@ -664,26 +801,36 @@ package GNAT.Sockets is
procedure Receive_Socket
(Socket : Socket_Type;
Item : out Ada.Streams.Stream_Element_Array;
- Last : out Ada.Streams.Stream_Element_Offset);
+ Last : out Ada.Streams.Stream_Element_Offset;
+ Flags : Request_Flag_Type := No_Request_Flag);
-- Receive message from Socket. Last is the index value such that
-- Item (Last) is the last character assigned. Note that Last is
-- set to Item'First - 1 when the socket has been closed by
- -- peer. This is not an error and no exception is raised. Raise
- -- Socket_Error on error.
+ -- peer. This is not an error and no exception is raised. Flags
+ -- allows to control the reception. Raise Socket_Error on error.
procedure Receive_Socket
(Socket : Socket_Type;
Item : out Ada.Streams.Stream_Element_Array;
Last : out Ada.Streams.Stream_Element_Offset;
- From : out Sock_Addr_Type);
+ From : out Sock_Addr_Type;
+ Flags : Request_Flag_Type := No_Request_Flag);
-- Receive message from Socket. If Socket is not
-- connection-oriented, the source address From of the message is
-- filled in. Last is the index value such that Item (Last) is the
- -- last character assigned. Raise Socket_Error on error.
+ -- last character assigned. Flags allows to control the
+ -- reception. Raises Socket_Error on error.
+
+ procedure Receive_Vector
+ (Socket : Socket_Type;
+ Vector : Vector_Type;
+ Count : out Ada.Streams.Stream_Element_Count);
+ -- Receive data from a socket and scatter it into the set of vector
+ -- elements Vector. Count is set to the count of received stream elements.
function Resolve_Exception
(Occurrence : Ada.Exceptions.Exception_Occurrence)
- return Error_Type;
+ return Error_Type;
-- When Socket_Error or Host_Error are raised, the exception
-- message contains the error code between brackets and a string
-- describing the error code. Resolve_Error extracts the error
@@ -693,24 +840,36 @@ package GNAT.Sockets is
procedure Send_Socket
(Socket : Socket_Type;
Item : Ada.Streams.Stream_Element_Array;
- Last : out Ada.Streams.Stream_Element_Offset);
+ Last : out Ada.Streams.Stream_Element_Offset;
+ Flags : Request_Flag_Type := No_Request_Flag);
-- Transmit a message to another socket. Note that Last is set to
- -- Item'First when socket has been closed by peer. This is not an
- -- error and no exception is raised. Raise Socket_Error on error;
+ -- Item'First-1 when socket has been closed by peer. This is not
+ -- considered an error and no exception is raised. Flags allows to
+ -- control the transmission. Raises Socket_Error on any other
+ -- error condition.
procedure Send_Socket
(Socket : Socket_Type;
Item : Ada.Streams.Stream_Element_Array;
Last : out Ada.Streams.Stream_Element_Offset;
- To : Sock_Addr_Type);
+ To : Sock_Addr_Type;
+ Flags : Request_Flag_Type := No_Request_Flag);
-- Transmit a message to another socket. The address is given by
- -- To. Raise Socket_Error on error;
+ -- To. Flags allows to control the transmission. Raises
+ -- Socket_Error on error.
+
+ procedure Send_Vector
+ (Socket : Socket_Type;
+ Vector : Vector_Type;
+ Count : out Ada.Streams.Stream_Element_Count);
+ -- Transmit data gathered from the set of vector elements Vector to a
+ -- socket. Count is set to the count of transmitted stream elements.
procedure Set_Socket_Option
(Socket : Socket_Type;
Level : Level_Type := Socket_Level;
Option : Option_Type);
- -- Manipulate socket options. Raise Socket_Error on error.
+ -- Manipulate socket options. Raises Socket_Error on error.
procedure Shutdown_Socket
(Socket : Socket_Type;
@@ -739,11 +898,11 @@ package GNAT.Sockets is
function Get_Address
(Stream : Stream_Access)
- return Sock_Addr_Type;
+ return Sock_Addr_Type;
-- Return the socket address from which the last message was
-- received.
- type Socket_Set_Type is private;
+ type Socket_Set_Type is limited private;
-- This type allows to manipulate sets of sockets. It allows to
-- wait for events on multiple endpoints at one time. This is an
-- access type on a system dependent structure. To avoid memory
@@ -753,14 +912,18 @@ package GNAT.Sockets is
procedure Clear (Item : in out Socket_Set_Type; Socket : Socket_Type);
-- Remove Socket from Item
- procedure Set (Item : in out Socket_Set_Type; Socket : Socket_Type);
- -- Insert Socket into Item
+ procedure Copy (Source : Socket_Set_Type; Target : in out Socket_Set_Type);
+ -- Copy Source into Target as Socket_Set_Type is limited private
procedure Empty (Item : in out Socket_Set_Type);
-- Remove all Sockets from Item and deallocate internal data
+ procedure Get (Item : in out Socket_Set_Type; Socket : out Socket_Type);
+ -- Extract a Socket from socket set Item. Socket is set to
+ -- No_Socket when the set is empty.
+
function Is_Empty
- (Item : Socket_Set_Type)
+ (Item : Socket_Set_Type)
return Boolean;
-- Return True if Item is empty
@@ -770,6 +933,9 @@ package GNAT.Sockets is
return Boolean;
-- Return True if Socket is present in Item
+ procedure Set (Item : in out Socket_Set_Type; Socket : Socket_Type);
+ -- Insert Socket into Item
+
-- C select() waits for a number of file descriptors to change
-- status. Usually, three independent sets of descriptors are
-- watched (read, write and exception). A timeout gives an upper
@@ -790,11 +956,19 @@ package GNAT.Sockets is
-- abort a select operation is typically to add a socket in one of
-- the socket sets when the timeout is set to forever.
- Forever : constant Duration;
-
type Selector_Type is limited private;
type Selector_Access is access all Selector_Type;
+ -- Selector_Duration is a subtype of Standard.Duration because the
+ -- full range of Standard.Duration cannot be represented in the
+ -- equivalent C structure. Moreover, negative values are not
+ -- allowed to avoid system incompatibilities.
+
+ Immediate : constant := 0.0;
+ Forever : constant := Duration (Integer'Last) * 1.0;
+
+ subtype Selector_Duration is Duration range Immediate .. Forever;
+
procedure Create_Selector (Selector : out Selector_Type);
-- Create a new selector
@@ -808,7 +982,7 @@ package GNAT.Sockets is
R_Socket_Set : in out Socket_Set_Type;
W_Socket_Set : in out Socket_Set_Type;
Status : out Selector_Status;
- Timeout : Duration := Forever);
+ Timeout : Selector_Duration := Forever);
-- Return when one Socket in R_Socket_Set has some data to be read
-- or if one Socket in W_Socket_Set is ready to receive some
-- data. In these cases Status is set to Completed and sockets
@@ -818,7 +992,21 @@ package GNAT.Sockets is
-- received while checking socket status. As this procedure
-- returns when Timeout occurs, it is a design choice to keep this
-- procedure process blocking. Note that a Timeout of 0.0 returns
- -- immediatly.
+ -- immediately. Also note that two different objects must be passed
+ -- as R_Socket_Set and W_Socket_Set (even if they contain the same
+ -- set of Sockets), or some event will be lost.
+
+ procedure Check_Selector
+ (Selector : in out Selector_Type;
+ R_Socket_Set : in out Socket_Set_Type;
+ W_Socket_Set : in out Socket_Set_Type;
+ E_Socket_Set : in out Socket_Set_Type;
+ Status : out Selector_Status;
+ Timeout : Selector_Duration := Forever);
+ -- This refined version of Check_Selector allows to watch for
+ -- exception events (that is notifications of out-of-band
+ -- transmission and reception). As above, all of R_Socket_Set,
+ -- W_Socket_Set and E_Socket_Set must be different objects.
procedure Abort_Selector (Selector : Selector_Type);
-- Send an abort signal to the selector.
@@ -828,18 +1016,23 @@ private
type Socket_Type is new Integer;
No_Socket : constant Socket_Type := -1;
- Forever : constant Duration := Duration'Last;
-
type Selector_Type is limited record
R_Sig_Socket : Socket_Type;
W_Sig_Socket : Socket_Type;
- In_Progress : Boolean := False;
end record;
+
+ pragma Volatile (Selector_Type);
+
-- The two signalling sockets are used to abort a select
-- operation.
- type Socket_Set_Record;
- type Socket_Set_Type is access all Socket_Set_Record;
+ subtype Socket_Set_Access is System.Address;
+ No_Socket_Set : constant Socket_Set_Access := System.Null_Address;
+
+ type Socket_Set_Type is record
+ Last : Socket_Type := No_Socket;
+ Set : Socket_Set_Access := No_Socket_Set;
+ end record;
subtype Inet_Addr_Comp_Type is Natural range 0 .. 255;
-- Octet for Internet address
@@ -867,25 +1060,39 @@ private
No_Sock_Addr : constant Sock_Addr_Type := (Family_Inet, No_Inet_Addr, 0);
- Max_Host_Name_Length : constant := 64;
+ Max_Name_Length : constant := 64;
-- The constant MAXHOSTNAMELEN is usually set to 64
- subtype Host_Name_Index is Natural range 1 .. Max_Host_Name_Length;
+ subtype Name_Index is Natural range 1 .. Max_Name_Length;
- type Host_Name_Type
- (Length : Host_Name_Index := Max_Host_Name_Length)
+ type Name_Type
+ (Length : Name_Index := Max_Name_Length)
is record
Name : String (1 .. Length);
end record;
-- We need fixed strings to avoid access types in host entry type
- type Host_Name_Array is array (Natural range <>) of Host_Name_Type;
+ type Name_Array is array (Natural range <>) of Name_Type;
type Inet_Addr_Array is array (Natural range <>) of Inet_Addr_Type;
type Host_Entry_Type (Aliases_Length, Addresses_Length : Natural) is record
- Official : Host_Name_Type;
- Aliases : Host_Name_Array (1 .. Aliases_Length);
+ Official : Name_Type;
+ Aliases : Name_Array (1 .. Aliases_Length);
Addresses : Inet_Addr_Array (1 .. Addresses_Length);
end record;
+ type Service_Entry_Type (Aliases_Length : Natural) is record
+ Official : Name_Type;
+ Aliases : Name_Array (1 .. Aliases_Length);
+ Port : Port_Type;
+ Protocol : Name_Type;
+ end record;
+
+ type Request_Flag_Type is mod 2 ** 8;
+ No_Request_Flag : constant Request_Flag_Type := 0;
+ Process_Out_Of_Band_Data : constant Request_Flag_Type := 1;
+ Peek_At_Incoming_Data : constant Request_Flag_Type := 2;
+ Wait_For_A_Full_Reception : constant Request_Flag_Type := 4;
+ Send_End_Of_Record : constant Request_Flag_Type := 8;
+
end GNAT.Sockets;