Skip to content

Commit

Permalink
Add Unix.realpath.
Browse files Browse the repository at this point in the history
Binds to realpath(3) on POSIX and GetFinalPathNameByHandle on
Windows.
  • Loading branch information
dbuenzli committed Nov 26, 2020
1 parent 10c91b3 commit ad888cf
Show file tree
Hide file tree
Showing 12 changed files with 145 additions and 58 deletions.
3 changes: 3 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,9 @@ Working version

### Other libraries:

- #XXXX Add `Unix.realpath`
(Daniel Bünzli, review by XXX)

### Tools:

### Manual and documentation:
Expand Down
63 changes: 7 additions & 56 deletions configure

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 2 additions & 0 deletions configure.ac
Original file line number Diff line number Diff line change
Expand Up @@ -1343,6 +1343,8 @@ AC_CHECK_FUNC([symlink],
[AC_CHECK_FUNC([readlink],
[AC_CHECK_FUNC([lstat], [AC_DEFINE([HAS_SYMLINK])])])])

AC_CHECK_FUNC([realpath], [AC_DEFINE([HAS_REALPATH])])

# wait
AC_CHECK_FUNC(
[waitpid],
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/unix/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ COBJS=accept.o access.o addrofstr.o alarm.o bind.o channels.o chdir.o \
gettimeofday.o getserv.o getsockname.o getuid.o gmtime.o \
initgroups.o isatty.o itimer.o kill.o link.o listen.o lockf.o lseek.o \
mkdir.o mkfifo.o mmap.o mmap_ba.o \
nice.o open.o opendir.o pipe.o putenv.o read.o \
nice.o open.o opendir.o pipe.o putenv.o read.o realpath.o \
readdir.o readlink.o rename.o rewinddir.o rmdir.o select.o sendrecv.o \
setgid.o setgroups.o setsid.o setuid.o shutdown.o signals.o \
sleep.o socket.o socketaddr.o \
Expand Down
43 changes: 43 additions & 0 deletions otherlibs/unix/realpath.c
Original file line number Diff line number Diff line change
@@ -0,0 +1,43 @@
/**************************************************************************/
/* */
/* OCaml */
/* */
/* The OCaml programmers */
/* */
/* Copyright 2020 Institut National de Recherche en Informatique et */
/* en Automatique. */
/* */
/* All rights reserved. This file is distributed under the terms of */
/* the GNU Lesser General Public License version 2.1, with the */
/* special exception on linking described in the file LICENSE. */
/* */
/**************************************************************************/

#include <caml/mlvalues.h>
#include <caml/memory.h>
#include <caml/alloc.h>
#include <caml/fail.h>
#include "unixsupport.h"

#ifdef HAS_REALPATH

CAMLprim value unix_realpath (value p)
{
CAMLparam1 (p);
char *r;
value rp;

caml_unix_check_path (p, "realpath");
r = realpath (String_val (p), NULL);
if (r == NULL) { uerror ("realpath", p); }
rp = caml_copy_string (r);
free (r);
CAMLreturn (rp);
}

#else

CAMLprim value unix_realpath (value p)
{ caml_invalid_argument ("realpath not implemented"); }

#endif
1 change: 1 addition & 0 deletions otherlibs/unix/unix.ml
Original file line number Diff line number Diff line change
Expand Up @@ -322,6 +322,7 @@ external isatty : file_descr -> bool = "unix_isatty"
external unlink : string -> unit = "unix_unlink"
external rename : string -> string -> unit = "unix_rename"
external link : ?follow:bool -> string -> string -> unit = "unix_link"
external realpath : string -> string = "unix_realpath"

module LargeFile =
struct
Expand Down
5 changes: 5 additions & 0 deletions otherlibs/unix/unix.mli
Original file line number Diff line number Diff line change
Expand Up @@ -622,6 +622,11 @@ val link : ?follow (* thwart tools/sync_stdlib_docs *) :bool ->
unavailable.
@raise ENOSYS On {e Windows} if [~follow:false] is requested. *)

val realpath : string -> string
(** [realpath p] is the absolute pathname for [p] obtained by resolving
all extra [/] characters, relative path segments and symbolic links.
@since 4.13.0 *)

(** {1 File permissions and ownership} *)

Expand Down
5 changes: 5 additions & 0 deletions otherlibs/unix/unixLabels.mli
Original file line number Diff line number Diff line change
Expand Up @@ -622,6 +622,11 @@ val link : ?follow (* thwart tools/sync_stdlib_docs *) :bool ->
unavailable.
@raise ENOSYS On {e Windows} if [~follow:false] is requested. *)

val realpath : string -> string
(** [realpath p] is the absolute pathname for [p] obtained by resolving
all extra [/] characters, relative path segments and symbolic links.
@since 4.13.0 *)

(** {1 File permissions and ownership} *)

Expand Down
2 changes: 1 addition & 1 deletion otherlibs/win32unix/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ WIN_FILES = accept.c bind.c channels.c close.c \
getpeername.c getpid.c getsockname.c gettimeofday.c isatty.c \
link.c listen.c lockf.c lseek.c nonblock.c \
mmap.c open.c pipe.c read.c readlink.c rename.c \
select.c sendrecv.c \
realpath.c select.c sendrecv.c \
shutdown.c sleep.c socket.c sockopt.c startup.c stat.c \
symlink.c system.c times.c truncate.c unixsupport.c windir.c winwait.c \
write.c winlist.c winworker.c windbug.c utimes.c
Expand Down
73 changes: 73 additions & 0 deletions otherlibs/win32unix/realpath.c
Original file line number Diff line number Diff line change
@@ -0,0 +1,73 @@
/**************************************************************************/
/* */
/* OCaml */
/* */
/* The OCaml programmers */
/* */
/* Copyright 2020 Institut National de Recherche en Informatique et */
/* en Automatique. */
/* */
/* All rights reserved. This file is distributed under the terms of */
/* the GNU Lesser General Public License version 2.1, with the */
/* special exception on linking described in the file LICENSE. */
/* */
/**************************************************************************/

#define CAML_INTERNALS

#include <caml/mlvalues.h>
#include <caml/memory.h>
#include <caml/alloc.h>
#include <caml/fail.h>
#include <caml/osdeps.h>
#include "unixsupport.h"

#include <windows.h>
#include <fileapi.h>
#include <stdio.h>

CAMLprim value unix_realpath (value p)
{
CAMLparam1 (p);
HANDLE h;
wchar_t *wp;
wchar_t *wr;
DWORD wr_len;
value rp;

caml_unix_check_path (p, "realpath");
wp = caml_stat_strdup_to_utf16 (String_val (p));
h = CreateFile (wp, GENERIC_READ, FILE_SHARE_READ, NULL, OPEN_EXISTING,
FILE_ATTRIBUTE_NORMAL, NULL);
caml_stat_free (wp);

if (h == INVALID_HANDLE_VALUE)
{
win32_maperr (GetLastError ());
uerror ("realpath", p);
}

wr_len = GetFinalPathNameByHandle (h, NULL, 0, VOLUME_NAME_DOS);
if (wr_len == 0)
{
win32_maperr (GetLastError ());
CloseHandle (h);
uerror ("realpath", p);
}

wr = caml_stat_alloc ((wr_len + 1) * sizeof (wchar_t));
wr_len = GetFinalPathNameByHandle (h, wr, wr_len, VOLUME_NAME_DOS);

if (wr_len == 0)
{
win32_maperr (GetLastError ());
CloseHandle (h);
caml_stat_free (wr);
uerror ("realpath", p);
}

rp = caml_copy_string_of_utf16 (wr);
CloseHandle (h);
caml_stat_free (wr);
CAMLreturn (rp);
}
1 change: 1 addition & 0 deletions otherlibs/win32unix/unix.ml
Original file line number Diff line number Diff line change
Expand Up @@ -364,6 +364,7 @@ external isatty : file_descr -> bool = "unix_isatty"
external unlink : string -> unit = "unix_unlink"
external rename : string -> string -> unit = "unix_rename"
external link : ?follow:bool -> string -> string -> unit = "unix_link"
external realpath : string -> string = "unix_realpath"

(* Operations on large files *)

Expand Down
3 changes: 3 additions & 0 deletions runtime/caml/s.h.in
Original file line number Diff line number Diff line change
Expand Up @@ -141,6 +141,9 @@

/* Define HAS_SYMLINK if you have symlink() and readlink() and lstat(). */

#undef HAS_REALPATH
/* Define HAS_REALPATH if you have realpath(). */

#undef HAS_WAIT4
#undef HAS_WAITPID

Expand Down

0 comments on commit ad888cf

Please sign in to comment.