1 /**************************************************************************/
2 /*                                                                        */
3 /*                                 OCaml                                  */
4 /*                                                                        */
5 /*                David Allsopp, MetaStack Solutions Ltd.                 */
6 /*                                                                        */
7 /*   Copyright 2015 MetaStack Solutions Ltd.                              */
8 /*                                                                        */
9 /*   All rights reserved.  This file is distributed under the terms of    */
10 /*   the GNU Lesser General Public License version 2.1, with the          */
11 /*   special exception on linking described in the file LICENSE.          */
12 /*                                                                        */
13 /**************************************************************************/
14 
15 #include <caml/mlvalues.h>
16 #include <caml/memory.h>
17 #include <caml/alloc.h>
18 #include <caml/fail.h>
19 #include <caml/signals.h>
20 #include "unixsupport.h"
21 #include <errno.h>
22 #include <winioctl.h>
23 
unix_readlink(value opath)24 CAMLprim value unix_readlink(value opath)
25 {
26   CAMLparam1(opath);
27   CAMLlocal1(result);
28   HANDLE h;
29   char* path;
30   DWORD attributes;
31   caml_unix_check_path(opath, "readlink");
32   path = caml_strdup(String_val(opath));
33 
34   caml_enter_blocking_section();
35   attributes = GetFileAttributes(path);
36   caml_leave_blocking_section();
37 
38   if (attributes == INVALID_FILE_ATTRIBUTES) {
39     caml_stat_free(path);
40     win32_maperr(GetLastError());
41     uerror("readlink", opath);
42   }
43   else if (!(attributes & FILE_ATTRIBUTE_REPARSE_POINT)) {
44     caml_stat_free(path);
45     errno = EINVAL;
46     uerror("readlink", opath);
47   }
48   else {
49     caml_enter_blocking_section();
50     if ((h = CreateFile(path,
51                         FILE_READ_ATTRIBUTES,
52                         FILE_SHARE_DELETE | FILE_SHARE_READ | FILE_SHARE_WRITE,
53                         NULL,
54                         OPEN_EXISTING,
55                         FILE_FLAG_BACKUP_SEMANTICS | FILE_FLAG_OPEN_REPARSE_POINT,
56                         NULL)) == INVALID_HANDLE_VALUE) {
57       caml_leave_blocking_section();
58       caml_stat_free(path);
59       errno = ENOENT;
60       uerror("readlink", opath);
61     }
62     else {
63       char buffer[16384];
64       DWORD read;
65       REPARSE_DATA_BUFFER* point;
66 
67       caml_stat_free(path);
68 
69       if (DeviceIoControl(h, FSCTL_GET_REPARSE_POINT, NULL, 0, buffer, 16384, &read, NULL)) {
70         caml_leave_blocking_section();
71         point = (REPARSE_DATA_BUFFER*)buffer;
72         if (point->ReparseTag == IO_REPARSE_TAG_SYMLINK) {
73           int cbLen = point->SymbolicLinkReparseBuffer.SubstituteNameLength / sizeof(WCHAR);
74           int len;
75           len = WideCharToMultiByte(
76                   CP_THREAD_ACP,
77                   0,
78                   point->SymbolicLinkReparseBuffer.PathBuffer + point->SymbolicLinkReparseBuffer.SubstituteNameOffset / 2,
79                   cbLen,
80                   NULL,
81                   0,
82                   NULL,
83                   NULL);
84           result = caml_alloc_string(len);
85           WideCharToMultiByte(
86             CP_THREAD_ACP,
87             0,
88             point->SymbolicLinkReparseBuffer.PathBuffer + point->SymbolicLinkReparseBuffer.SubstituteNameOffset / 2,
89             cbLen,
90             String_val(result),
91             len,
92             NULL,
93             NULL);
94           CloseHandle(h);
95         }
96         else {
97           errno = EINVAL;
98           CloseHandle(h);
99           uerror("readline", opath);
100         }
101       }
102       else {
103         caml_leave_blocking_section();
104         win32_maperr(GetLastError());
105         CloseHandle(h);
106         uerror("readlink", opath);
107       }
108     }
109   }
110 
111   CAMLreturn(result);
112 }
113