Module Unix


module Unix = struct ... end 
Types
error Errors defined in the POSIX standard
= E2BIG Argument list too long
| EACCES Permission denied
| EAGAIN Resource temporarily unavailable; try again
| EBADF Bad file descriptor
| EBUSY Resource unavailable
| ECHILD No child process
| EDEADLK Resource deadlock would occur
| EDOM Domain error for math functions, etc.
| EEXIST File exists
| EFAULT Bad address
| EFBIG File too large
| EINTR Function interrupted by signal
| EINVAL Invalid argument
| EIO Hardware I/O error
| EISDIR Is a directory
| EMFILE Too many open files by the process
| EMLINK Too many links
| ENAMETOOLONG Filename too long
| ENFILE Too many open files in the system
| ENODEV No such device
| ENOENT No such file or directory
| ENOEXEC Not an executable file
| ENOLCK No locks available
| ENOMEM Not enough memory
| ENOSPC No space left on device
| ENOSYS Function not supported
| ENOTDIR Not a directory
| ENOTEMPTY Directory not empty
| ENOTTY Inappropriate I/O control operation
| ENXIO No such device or address
| EPERM Operation not permitted
| EPIPE Broken pipe
| ERANGE Result too large
| EROFS Read-only file system
| ESPIPE Invalid seek e.g. on a pipe
| ESRCH No such process
| EXDEV Invalid link
| EWOULDBLOCK Operation would block
| EINPROGRESS Operation now in progress
| EALREADY Operation already in progress
| ENOTSOCK Socket operation on non-socket
| EDESTADDRREQ Destination address required
| EMSGSIZE Message too long
| EPROTOTYPE Protocol wrong type for socket
| ENOPROTOOPT Protocol not available
| EPROTONOSUPPORT Protocol not supported
| ESOCKTNOSUPPORT Socket type not supported
| EOPNOTSUPP Operation not supported on socket
| EPFNOSUPPORT Protocol family not supported
| EAFNOSUPPORT Address family not supported by protocol family
| EADDRINUSE Address already in use
| EADDRNOTAVAIL Can't assign requested address
| ENETDOWN Network is down
| ENETUNREACH Network is unreachable
| ENETRESET Network dropped connection on reset
| ECONNABORTED Software caused connection abort
| ECONNRESET Connection reset by peer
| ENOBUFS No buffer space available
| EISCONN Socket is already connected
| ENOTCONN Socket is not connected
| ESHUTDOWN Can't send after socket shutdown
| ETOOMANYREFS Too many references: can't splice
| ETIMEDOUT Connection timed out
| ECONNREFUSED Connection refused
| EHOSTDOWN Host is down
| EHOSTUNREACH No route to host
| ELOOP Too many levels of symbolic links
| EUNKNOWNERR of  int
Unknown error
process_status
= WEXITED of  int
| WSIGNALED of  int
| WSTOPPED of  int
wait_flag
= WNOHANG
| WUNTRACED
file_descr The abstract type of file descriptors.
Abstract
open_flag
= O_RDONLY Open for reading
| O_WRONLY Open for writing
| O_RDWR Open for reading and writing
| O_NONBLOCK Open in non-blocking mode
| O_APPEND Open for append
| O_CREAT Create if nonexistent
| O_TRUNC Truncate to 0 length if existing
| O_EXCL Fail if existing
file_perm The type of file access rights.
= int
seek_command
= SEEK_SET
| SEEK_CUR
| SEEK_END
file_kind
= S_REG Regular file
| S_DIR Directory
| S_CHR Character device
| S_BLK Block device
| S_LNK Symbolic link
| S_FIFO Named pipe
| S_SOCK Socket
stats Last status change time
= {
st_dev :  int ;
Device number
st_ino :  int ;
Inode number
st_kind :  file_kind ;
Kind of the file
st_perm :  file_perm ;
Access rights
st_nlink :  int ;
Number of links
st_uid :  int ;
User id of the owner
st_gid :  int ;
Group ID of the file's group
st_rdev :  int ;
Device minor number
st_size :  int ;
Size in bytes
st_atime :  float ;
Last access time
st_mtime :  float ;
Last modification time
st_ctime :  float ;
}
access_permission
= R_OK Read permission
| W_OK Write permission
| X_OK Execution permission
| F_OK File exists
dir_handle Abstract
lock_command
= F_ULOCK Unlock a region
| F_LOCK Lock a region for writing, and block if already locked
| F_TLOCK Lock a region for writing, or fail if already locked
| F_TEST Test a region for other process locks
| F_RLOCK Lock a region for reading, and block if already locked
| F_TRLOCK Lock a region for reading, or fail if already locked
sigprocmask_command
= SIG_SETMASK
| SIG_BLOCK
| SIG_UNBLOCK
process_times System time for the children processes
= {
tms_utime :  float ;
User time for the process
tms_stime :  float ;
System time for the process
tms_cutime :  float ;
User time for the children processes
tms_cstime :  float ;
}
tm Daylight time savings in effect
= {
tm_sec :  int ;
Seconds 0..59
tm_min :  int ;
Minutes 0..59
tm_hour :  int ;
Hours 0..23
tm_mday :  int ;
Day of month 1..31
tm_mon :  int ;
Month of year 0..11
tm_year :  int ;
Year - 1900
tm_wday :  int ;
Day of week (Sunday is 0)
tm_yday :  int ;
Day of year 0..365
tm_isdst :  bool ;
}
interval_timer
= ITIMER_REAL
| ITIMER_VIRTUAL
| ITIMER_PROF The three kinds of interval timers. ITIMER_REAL decrements in real time, and sends the signal SIGALRM when expired. ITIMER_VIRTUAL decrements in process virtual time, and sends SIGVTALRM when expired. ITIMER_PROF (for profiling) decrements both when the process is running and when the system is running on behalf of the process; it sends SIGPROF when expired.
interval_timer_status Current value of the timer
= {
it_interval :  float ;
Period
it_value :  float ;
}
passwd_entry Structure of entries in the passwd database.
= {
pw_name :  string ;
pw_passwd :  string ;
pw_uid :  int ;
pw_gid :  int ;
pw_gecos :  string ;
pw_dir :  string ;
pw_shell :  string ;
}
group_entry Structure of entries in the groups database.
= {
gr_name :  string ;
gr_passwd :  string ;
gr_gid :  int ;
gr_mem :  string array ;
}
inet_addr The abstract type of Internet addresses.
Abstract
socket_domain
= PF_UNIX Unix domain
| PF_INET Internet domain
socket_type
= SOCK_STREAM Stream socket
| SOCK_DGRAM Datagram socket
| SOCK_RAW Raw socket
| SOCK_SEQPACKET Sequenced packets socket
sockaddr
= ADDR_UNIX of  string
| ADDR_INET of  inet_addr * int
shutdown_command
= SHUTDOWN_RECEIVE Close for receiving
| SHUTDOWN_SEND Close for sending
| SHUTDOWN_ALL Close both
msg_flag
= MSG_OOB
| MSG_DONTROUTE
| MSG_PEEK The flags for recv, recvfrom, send and sendto.
socket_bool_option
= SO_DEBUG Record debugging information
| SO_BROADCAST Permit sending of broadcast messages
| SO_REUSEADDR Allow reuse of local addresses for bind
| SO_KEEPALIVE Keep connection active
| SO_DONTROUTE Bypass the standard routing algorithms
| SO_OOBINLINE Leave out-of-band data in line
| SO_ACCEPTCONN Report whether socket listening is enabled
socket_int_option
= SO_SNDBUF Size of send buffer
| SO_RCVBUF Size of received buffer
| SO_ERROR Report the error status and clear it
| SO_TYPE Report the socket type
| SO_RCVLOWAT Minimum number of bytes to process for input operations
| SO_SNDLOWAT Minimum number of bytes to process for output operations
socket_optint_option
= SO_LINGER Whether to linger on closed connections that have data present, and for how long (in seconds)
socket_float_option
= SO_RCVTIMEO Timeout for input operations
| SO_SNDTIMEO Timeout for output operations
host_entry Structure of entries in the hosts database.
= {
h_name :  string ;
h_aliases :  string array ;
h_addrtype :  socket_domain ;
h_addr_list :  inet_addr array ;
}
protocol_entry Structure of entries in the protocols database.
= {
p_name :  string ;
p_aliases :  string array ;
p_proto :  int ;
}
service_entry Structure of entries in the services database.
= {
s_name :  string ;
s_aliases :  string array ;
s_port :  int ;
s_proto :  string ;
}
terminal_io = {
c_ignbrk
(mutable)
:  bool ;
Ignore the break condition.
c_brkint
(mutable)
:  bool ;
Signal interrupt on break condition.
c_ignpar
(mutable)
:  bool ;
Ignore characters with parity errors.
c_parmrk
(mutable)
:  bool ;
Mark parity errors.
c_inpck
(mutable)
:  bool ;
Enable parity check on input.
c_istrip
(mutable)
:  bool ;
Strip 8th bit on input characters.
c_inlcr
(mutable)
:  bool ;
Map NL to CR on input.
c_igncr
(mutable)
:  bool ;
Ignore CR on input.
c_icrnl
(mutable)
:  bool ;
Map CR to NL on input.
c_ixon
(mutable)
:  bool ;
Recognize XON/XOFF characters on input.
c_ixoff
(mutable)
:  bool ;
Emit XON/XOFF chars to control input flow.
c_opost
(mutable)
:  bool ;
Enable output processing.
c_obaud
(mutable)
:  int ;
Output baud rate (0 means close connection).
c_ibaud
(mutable)
:  int ;
Input baud rate.
c_csize
(mutable)
:  int ;
Number of bits per character (5-8).
c_cstopb
(mutable)
:  int ;
Number of stop bits (1-2).
c_cread
(mutable)
:  bool ;
Reception is enabled.
c_parenb
(mutable)
:  bool ;
Enable parity generation and detection.
c_parodd
(mutable)
:  bool ;
Specify odd parity instead of even.
c_hupcl
(mutable)
:  bool ;
Hang up on last close.
c_clocal
(mutable)
:  bool ;
Ignore modem status lines.
c_isig
(mutable)
:  bool ;
Generate signal on INTR, QUIT, SUSP.
c_icanon
(mutable)
:  bool ;
Enable canonical processing (line buffering and editing)
c_noflsh
(mutable)
:  bool ;
Disable flush after INTR, QUIT, SUSP.
c_echo
(mutable)
:  bool ;
Echo input characters.
c_echoe
(mutable)
:  bool ;
Echo ERASE (to erase previous character).
c_echok
(mutable)
:  bool ;
Echo KILL (to erase the current line).
c_echonl
(mutable)
:  bool ;
Echo NL even if c_echo is not set.
c_vintr
(mutable)
:  char ;
Interrupt character (usually ctrl-C).
c_vquit
(mutable)
:  char ;
Quit character (usually ctrl-\).
c_verase
(mutable)
:  char ;
Erase character (usually DEL or ctrl-H).
c_vkill
(mutable)
:  char ;
Kill line character (usually ctrl-U).
c_veof
(mutable)
:  char ;
End-of-file character (usually ctrl-D).
c_veol
(mutable)
:  char ;
Alternate end-of-line char. (usually none).
c_vmin
(mutable)
:  int ;
Minimum number of characters to read before the read request is satisfied.
c_vtime
(mutable)
:  int ;
Maximum read wait (in 0.1s units).
c_vstart
(mutable)
:  char ;
Start character (usually ctrl-Q).
c_vstop
(mutable)
:  char ;
Stop character (usually ctrl-S).
}
setattr_when
= TCSANOW
| TCSADRAIN
| TCSAFLUSH
flush_queue
= TCIFLUSH
| TCOFLUSH
| TCIOFLUSH
flow_action
= TCOOFF
| TCOON
| TCIOFF
| TCION

Exceptions
Unix_error of  error * string * string
Raised by the system calls below when an error is encountered. The first component is the error code; the second component is the function name; the third component is the string parameter to the function, if it has one, or the empty string otherwise.

Simple values
stdin file_descr
stdout file_descr
stderr file_descr
File descriptors for standard input, standard output and standard error.
inet_addr_any inet_addr
A special Internet address, for use only with bind, representing all the Internet addresses that the host machine possesses.

Functions

error_message : error -> string
Return a string describing the given error code.

handle_unix_error : ('a -> 'b) -> 'a -> 'b
handle_unix_error f x applies f to x and returns the result. If the exception Unix_error is raised, it prints a message describing the error and exits with code 2.

environment : unit -> string array
Return the process environment, as an array of strings with the format ``variable=value''.

getenv : string -> string
Return the value associated to a variable in the process environment. Raise Not_found if the variable is unbound. (This function is identical to Sys.getenv.)

putenv : string -> string -> unit
Unix.putenv name value sets the value associated to a variable in the process environment. name is the name of the environment variable, and value its new associated value.

execv : prog:string -> args:string array -> unit
execv prog args execute the program in file prog, with the arguments args, and the current process environment.

execve : prog:string -> args:string array -> env:string array -> unit
Same as execv, except that the third argument provides the environment to the program executed.

execvp : prog:string -> args:string array -> unit

execvpe : prog:string -> args:string array -> env:string array -> unit
Same as execv and execvp respectively, except that the program is searched in the path.

fork : unit -> int
Fork a new process. The returned integer is 0 for the child process, the pid of the child process for the parent process.

wait : unit -> int * process_status
Wait until one of the children processes die, and return its pid and termination status.

waitpid : mode:wait_flag list -> int -> int * process_status
Same as wait, but waits for the process whose pid is given. A pid of -1 means wait for any child. A pid of 0 means wait for any child in the same process group as the current process. Negative pid arguments represent process groups. The list of options indicates whether waitpid should return immediately without waiting, or also report stopped children.

system : string -> process_status
Execute the given command, wait until it terminates, and return its termination status. The string is interpreted by the shell /bin/sh and therefore can contain redirections, quotes, variables, etc. The result WEXITED 127 indicates that the shell couldn't be executed.

getpid : unit -> int
Return the pid of the process.

getppid : unit -> int
Return the pid of the parent process.

nice : int -> int
Change the process priority. The integer argument is added to the ``nice'' value. (Higher values of the ``nice'' value mean lower priorities.) Return the new nice value.

openfile : string -> mode:open_flag list -> perm:file_perm -> file_descr
Open the named file with the given flags. Third argument is the permissions to give to the file if it is created. Return a file descriptor on the named file.

close : file_descr -> unit
Close a file descriptor.

read : file_descr -> buf:string -> pos:int -> len:int -> int
read fd buff ofs len reads len characters from descriptor fd, storing them in string buff, starting at position ofs in string buff. Return the number of characters actually read.

write : file_descr -> buf:string -> pos:int -> len:int -> int
write fd buff ofs len writes len characters to descriptor fd, taking them from string buff, starting at position ofs in string buff. Return the number of characters actually written.

in_channel_of_descr : file_descr -> Pervasives.in_channel
Create an input channel reading from the given descriptor. The channel is initially in binary mode; use set_binary_mode_in ic false if text mode is desired.

out_channel_of_descr : file_descr -> Pervasives.out_channel
Create an output channel writing on the given descriptor. The channel is initially in binary mode; use set_binary_mode_out oc false if text mode is desired.

descr_of_in_channel : Pervasives.in_channel -> file_descr
Return the descriptor corresponding to an input channel.

descr_of_out_channel : Pervasives.out_channel -> file_descr
Return the descriptor corresponding to an output channel.

lseek : file_descr -> int -> mode:seek_command -> int
Set the current position for a file descriptor

truncate : string -> len:int -> unit
Truncates the named file to the given size.

ftruncate : file_descr -> len:int -> unit
Truncates the file corresponding to the given descriptor to the given size.

stat : string -> stats
Return the information for the named file.

lstat : string -> stats
Same as stat, but in case the file is a symbolic link, return the information for the link itself.

fstat : file_descr -> stats
Return the information for the file associated with the given descriptor.

unlink : string -> unit
Removes the named file

rename : src:string -> dst:string -> unit
rename old new changes the name of a file from old to new.

link : src:string -> dst:string -> unit
link source dest creates a hard link named dest to the file named new.

chmod : string -> perm:file_perm -> unit
Change the permissions of the named file.

fchmod : file_descr -> perm:file_perm -> unit
Change the permissions of an opened file.

chown : string -> uid:int -> gid:int -> unit
Change the owner uid and owner gid of the named file.

fchown : file_descr -> uid:int -> gid:int -> unit
Change the owner uid and owner gid of an opened file.

umask : int -> int
Set the process creation mask, and return the previous mask.

access : string -> perm:access_permission list -> unit
Check that the process has the given permissions over the named file. Raise Unix_error otherwise.

dup : file_descr -> file_descr
Return a new file descriptor referencing the same file as the given descriptor.

dup2 : src:file_descr -> dst:file_descr -> unit
dup2 fd1 fd2 duplicates fd1 to fd2, closing fd2 if already opened.

set_nonblock : file_descr -> unit

clear_nonblock : file_descr -> unit
Set or clear the ``non-blocking'' flag on the given descriptor. When the non-blocking flag is set, reading on a descriptor on which there is temporarily no data available raises the EAGAIN or EWOULDBLOCK error instead of blocking; writing on a descriptor on which there is temporarily no room for writing also raises EAGAIN or EWOULDBLOCK.

set_close_on_exec : file_descr -> unit

clear_close_on_exec : file_descr -> unit
Set or clear the ``close-on-exec'' flag on the given descriptor. A descriptor with the close-on-exec flag is automatically closed when the current process starts another program with one of the exec functions.

mkdir : string -> perm:file_perm -> unit
Create a directory with the given permissions.

rmdir : string -> unit
Remove an empty directory.

chdir : string -> unit
Change the process working directory.

getcwd : unit -> string
Return the name of the current working directory.

chroot : string -> unit
Change the process root directory.

opendir : string -> dir_handle
Open a descriptor on a directory

readdir : dir_handle -> string
Return the next entry in a directory. Raise End_of_file when the end of the directory has been reached.

rewinddir : dir_handle -> unit
Reposition the descriptor to the beginning of the directory

closedir : dir_handle -> unit
Close a directory descriptor.

pipe : unit -> file_descr * file_descr
Create a pipe. The first component of the result is opened for reading, that's the exit to the pipe. The second component is opened for writing, that's the entrance to the pipe.

mkfifo : string -> perm:file_perm -> unit
Create a named pipe with the given permissions.

create_process : prog:string ->
args:string array ->
stdin:file_descr ->
stdout:file_descr -> stderr:file_descr -> int

create_process prog args new_stdin new_stdout new_stderr forks a new process that executes the program in file prog, with arguments args. The pid of the new process is returned immediately; the new process executes concurrently with the current process. The standard input and outputs of the new process are connected to the descriptors new_stdin, new_stdout and new_stderr. Passing e.g. stdout for new_stdout prevents the redirection and causes the new process to have the same standard output as the current process. The executable file prog is searched in the path. The new process has the same environment as the current process. All file descriptors of the current process are closed in the new process, except those redirected to standard input and outputs.

create_process_env : prog:string ->
args:string array ->
env:string array ->
stdin:file_descr ->
stdout:file_descr -> stderr:file_descr -> int

create_process_env prog args env new_stdin new_stdout new_stderr works as create_process, except that the extra argument env specifies the environment passed to the program.

open_process_in : string -> Pervasives.in_channel

open_process_out : string -> Pervasives.out_channel

open_process : string -> Pervasives.in_channel * Pervasives.out_channel
High-level pipe and process management. These functions run the given command in parallel with the program, and return channels connected to the standard input and/or the standard output of the command. The command is interpreted by the shell /bin/sh (cf. system). Warning: writes on channels are buffered, hence be careful to call flush at the right times to ensure correct synchronization.

open_process_full : string ->
env:string array ->
Pervasives.in_channel * Pervasives.out_channel * Pervasives.in_channel

Similar to open_process, but the second argument specifies the environment passed to the command. The result is a triple of channels connected to the standard output, standard input, and standard error of the command.

close_process_in : Pervasives.in_channel -> process_status

close_process_out : Pervasives.out_channel -> process_status

close_process : Pervasives.in_channel * Pervasives.out_channel -> process_status

close_process_full : Pervasives.in_channel * Pervasives.out_channel * Pervasives.in_channel ->
process_status

Close channels opened by open_process_in, open_process_out, open_process and open_process_full, respectively, wait for the associated command to terminate, and return its termination status.

symlink : src:string -> dst:string -> unit
symlink source dest creates the file dest as a symbolic link to the file source.

readlink : string -> string
Read the contents of a link.

select : read:file_descr list ->
write:file_descr list ->
except:file_descr list ->
timeout:float ->
file_descr list * file_descr list * file_descr list

Wait until some input/output operations become possible on some channels. The three list arguments are, respectively, a set of descriptors to check for reading (first argument), for writing (second argument), or for exceptional conditions (third argument). The fourth argument is the maximal timeout, in seconds; a negative fourth argument means no timeout (unbounded wait). The result is composed of three sets of descriptors: those ready for reading (first component), ready for writing (second component), and over which an exceptional condition is pending (third component).

lockf : file_descr -> mode:lock_command -> len:int -> unit

kill : pid:int -> signal:int -> unit
kill pid sig sends signal number sig to the process with id pid.

sigprocmask : mode:sigprocmask_command -> int list -> int list
sigprocmask cmd sigs changes the set of blocked signals. If cmd is SIG_SETMASK, blocked signals are set to those in the list sigs. If cmd is SIG_BLOCK, the signals in sigs are added to the set of blocked signals. If cmd is SIG_UNBLOCK, the signals in sigs are removed from the set of blocked signals. sigprocmask returns the set of previously blocked signals.

sigpending : unit -> int list
Return the set of blocked signals that are currently pending.

sigsuspend : int list -> unit
sigsuspend sigs atomically sets the blocked signals to sig and waits for a non-ignored, non-blocked signal to be delivered. On return, the blocked signals are reset to their initial value.

pause : unit -> unit
Wait until a non-ignored, non-blocked signal is delivered.

time : unit -> float
Return the current time since 00:00:00 GMT, Jan. 1, 1970, in seconds.

gettimeofday : unit -> float
Same as time, but with resolution better than 1 second.

gmtime : float -> tm
Convert a time in seconds, as returned by time, into a date and a time. Assumes Greenwich meridian time zone, also known as UTC.

localtime : float -> tm
Convert a time in seconds, as returned by time, into a date and a time. Assumes the local time zone.

mktime : tm -> float * tm
Convert a date and time, specified by the tm argument, into a time in seconds, as returned by time. Also return a normalized copy of the given tm record, with the tm_wday, tm_yday, and tm_isdst fields recomputed from the other fields. The tm argument is interpreted in the local time zone.

alarm : int -> int
Schedule a SIGALRM signals after the given number of seconds.

sleep : int -> unit
Stop execution for the given number of seconds.

times : unit -> process_times
Return the execution times of the process.

utimes : string -> access:float -> modif:float -> unit
Set the last access time (second arg) and last modification time (third arg) for a file. Times are expressed in seconds from 00:00:00 GMT, Jan. 1, 1970.

getitimer : interval_timer -> interval_timer_status
Return the current status of the given interval timer.

setitimer : interval_timer ->
interval_timer_status -> interval_timer_status

setitimer t s sets the interval timer t and returns its previous status. The s argument is interpreted as follows: s.it_value, if nonzero, is the time to the next timer expiration; s.it_interval, if nonzero, specifies a value to be used in reloading it_value when the timer expires. Setting s.it_value to zero disable the timer. Setting s.it_interval to zero causes the timer to be disabled after its next expiration.

getuid : unit -> int
Return the user id of the user executing the process.

geteuid : unit -> int
Return the effective user id under which the process runs.

setuid : int -> unit
Set the real user id and effective user id for the process.

getgid : unit -> int
Return the group id of the user executing the process.

getegid : unit -> int
Return the effective group id under which the process runs.

setgid : int -> unit
Set the real group id and effective group id for the process.

getgroups : unit -> int array
Return the list of groups to which the user executing the process belongs.

getlogin : unit -> string
Return the login name of the user executing the process.

getpwnam : string -> passwd_entry
Find an entry in passwd with the given name, or raise Not_found.

getgrnam : string -> group_entry
Find an entry in group with the given name, or raise Not_found.

getpwuid : int -> passwd_entry
Find an entry in passwd with the given user id, or raise Not_found.

getgrgid : int -> group_entry
Find an entry in group with the given group id, or raise Not_found.

inet_addr_of_string : string -> inet_addr

string_of_inet_addr : inet_addr -> string
Conversions between string with the format XXX.YYY.ZZZ.TTT and Internet addresses. inet_addr_of_string raises Failure when given a string that does not match this format.

socket : domain:socket_domain ->
kind:socket_type -> protocol:int -> file_descr

Create a new socket in the given domain, and with the given kind. The third argument is the protocol type; 0 selects the default protocol for that kind of sockets.

socketpair : domain:socket_domain ->
kind:socket_type -> protocol:int -> file_descr * file_descr

Create a pair of unnamed sockets, connected together.

accept : file_descr -> file_descr * sockaddr
Accept connections on the given socket. The returned descriptor is a socket connected to the client; the returned address is the address of the connecting client.

bind : file_descr -> addr:sockaddr -> unit
Bind a socket to an address.

connect : file_descr -> addr:sockaddr -> unit
Connect a socket to an address.

listen : file_descr -> max:int -> unit
Set up a socket for receiving connection requests. The integer argument is the maximal number of pending requests.

shutdown : file_descr -> mode:shutdown_command -> unit
Shutdown a socket connection. SHUTDOWN_SEND as second argument causes reads on the other end of the connection to return an end-of-file condition. SHUTDOWN_RECEIVE causes writes on the other end of the connection to return a closed pipe condition (SIGPIPE signal).

getsockname : file_descr -> sockaddr
Return the address of the given socket.

getpeername : file_descr -> sockaddr
Return the address of the host connected to the given socket.

recv : file_descr ->
buf:string -> pos:int -> len:int -> mode:msg_flag list -> int


recvfrom : file_descr ->
buf:string ->
pos:int -> len:int -> mode:msg_flag list -> int * sockaddr

Receive data from an unconnected socket.

send : file_descr ->
buf:string -> pos:int -> len:int -> mode:msg_flag list -> int


sendto : file_descr ->
buf:string ->
pos:int -> len:int -> mode:msg_flag list -> addr:sockaddr -> int

Send data over an unconnected socket.

getsockopt : file_descr -> socket_bool_option -> bool
Return the current status of a boolean-valued option in the given socket.

setsockopt : file_descr -> socket_bool_option -> bool -> unit
Set or clear a boolean-valued option in the given socket.

getsockopt_int : file_descr -> socket_int_option -> int

setsockopt_int : file_descr -> socket_int_option -> int -> unit
Same, for an integer-valued socket option.

getsockopt_optint : file_descr -> socket_optint_option -> int option

setsockopt_optint : file_descr -> socket_optint_option -> int option -> unit

getsockopt_float : file_descr -> socket_float_option -> float

setsockopt_float : file_descr -> socket_float_option -> float -> unit
Same, for a socket option whose value is a floating-point number.

open_connection : sockaddr -> Pervasives.in_channel * Pervasives.out_channel
Connect to a server at the given address. Return a pair of buffered channels connected to the server. Remember to call flush on the output channel at the right times to ensure correct synchronization.

shutdown_connection : Pervasives.in_channel -> unit
``Shut down'' a connection established with open_connection; that is, transmit an end-of-file condition to the server reading on the other side of the connection.

establish_server : (Pervasives.in_channel -> Pervasives.out_channel -> unit) ->
addr:sockaddr -> unit

Establish a server on the given address. The function given as first argument is called for each connection with two buffered channels connected to the client. A new process is created for each connection. The function establish_server never returns normally.

gethostname : unit -> string
Return the name of the local host.

gethostbyname : string -> host_entry
Find an entry in hosts with the given name, or raise Not_found.

gethostbyaddr : inet_addr -> host_entry
Find an entry in hosts with the given address, or raise Not_found.

getprotobyname : string -> protocol_entry
Find an entry in protocols with the given name, or raise Not_found.

getprotobynumber : int -> protocol_entry
Find an entry in protocols with the given protocol number, or raise Not_found.

getservbyname : string -> protocol:string -> service_entry
Find an entry in services with the given name, or raise Not_found.

getservbyport : int -> protocol:string -> service_entry
Find an entry in services with the given service number, or raise Not_found.

tcgetattr : file_descr -> terminal_io
Return the status of the terminal referred to by the given file descriptor.

tcsetattr : file_descr -> mode:setattr_when -> terminal_io -> unit
Set the status of the terminal referred to by the given file descriptor. The second argument indicates when the status change takes place: immediately (TCSANOW), when all pending output has been transmitted (TCSADRAIN), or after flushing all input that has been received but not read (TCSAFLUSH). TCSADRAIN is recommended when changing the output parameters; TCSAFLUSH, when changing the input parameters.

tcsendbreak : file_descr -> duration:int -> unit
Send a break condition on the given file descriptor. The second argument is the duration of the break, in 0.1s units; 0 means standard duration (0.25s).

tcdrain : file_descr -> unit
Waits until all output written on the given file descriptor has been transmitted.

tcflush : file_descr -> mode:flush_queue -> unit
Discard data written on the given file descriptor but not yet transmitted, or data received but not yet read, depending on the second argument: TCIFLUSH flushes data received but not read, TCOFLUSH flushes data written but not transmitted, and TCIOFLUSH flushes both.

tcflow : file_descr -> mode:flow_action -> unit
Suspend or restart reception or transmission of data on the given file descriptor, depending on the second argument: TCOOFF suspends output, TCOON restarts output, TCIOFF transmits a STOP character to suspend input, and TCION transmits a START character to restart input.

setsid : unit -> int
Put the calling process in a new session and detach it from its controlling terminal.