Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
18 changes: 18 additions & 0 deletions unix.c
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@
#include <stdlib.h>
#include <unistd.h>
#include <sys/types.h>
#include <sys/stat.h>
#include <sys/wait.h>
#include <fcntl.h>
#include <assert.h>
Expand Down Expand Up @@ -310,6 +311,22 @@ pl_environ(term_t l)
return PL_unify_nil(t);
}

static foreign_t
pl_mkfifo(term_t Path, term_t Mode)
{ char *pathname;
mode_t mode;

if ( !PL_get_file_name(Path, &pathname, CVT_ALL|BUF_MALLOC|REP_MB) )
return FALSE;
if ( !PL_get_integer(Mode, (int *)&mode) )
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I guess we can share with chmod/2 to support symbolic modes?

Copy link
Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

It looks like sharing mode_bits/2 and file_mode/2 suffices. How would you like to do that? Arguably, since mode handling will now span multiple libraries, it makes sense to expose. If that's the right move, I'd wager they belong in library(unix).

return pl_error("mkfifo", 2, NULL, ERR_ARGTYPE, 1, Mode, "mode");
if ( !mkfifo(pathname, mode) < 0 )
return pl_error("mkfifo", 2, NULL, ERR_ERRNO, errno, "create", "fifo", Path);

PL_free(pathname);
return TRUE;
}


/*******************************
* DEAMON IO *
Expand Down Expand Up @@ -527,6 +544,7 @@ install_unix()
PL_register_foreign("dup", 2, pl_dup, 0);
PL_register_foreign("detach_IO", 1, pl_detach_IO, 0);
PL_register_foreign("environ", 1, pl_environ, 0);
PL_register_foreign("mkfifo", 2, pl_mkfifo, 0);
#ifdef HAVE_PRCTL
PL_register_foreign("prctl", 1, pl_prctl, 0);
#endif
Expand Down
23 changes: 22 additions & 1 deletion unix.pl
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,8 @@
dup/2, % +From, +To
detach_IO/0,
detach_IO/1, % +Stream
environ/1 % -[Name=Value]
environ/1, % -[Name=Value]
mkfifo/2 % +Path, +Mode
]).

/** <module> Unix specific operations
Expand Down Expand Up @@ -306,6 +307,26 @@

:- endif.

%! mkfifo(+Path, +Mode) is det.
%
% Interface to Unix mkfifo(), which makes a FIFO special file with
% name Path and file permissions specified by Mode.
%
% Once created, the FIFO can be used with open/3 and close/2 just
% like any normal file; however, writes will block unless the file
% is also open for reads, and vice versa.
%
% Path is a file name and Mode mirrors the same used by chmod/2,
% e.g. the following creates a FIFO readable and writable by the
% user.
%
% ```
% ?- mkfifo(myfifo, +urw)
% ```
%
% Note that, in addition to Mode, actual the actual permissions
% granted to Path are determined by the running process' umask.

/*******************************
* MESSAGES *
*******************************/
Expand Down