[m-rev.] for review: library changes for `mmc --make' on Windows

Simon Taylor stayl at cs.mu.OZ.AU
Sun Jul 20 01:25:16 AEST 2003


On 15-Jul-2003, Fergus Henderson <fjh at cs.mu.OZ.AU> wrote:
> On 15-Jul-2003, Simon Taylor <stayl at cs.mu.OZ.AU> wrote:
> > 	Don't add repated directory separators in '/'.
> 
> s/repated/repeated/

Done.
 
> > diff -u library/dir.m library/dir.m
> ...
> > +	% Note that the predicates and functions in this module may
> > +	% change directory separators in paths passed to them
> > +	% to the normal separator for the platform.
> 
> If that comment is supposed to apply to all predicates and functions in the
> module, then I think it should go at the top of the module.

Done.
 
> Also, I think any occurrences of implementation dependent behaviour
> should be explicitly flagged with the words "implementation dependent"
> or "system depend" or "unspecified" or something like that, rather than
> just using the word "may".

All specifiers are now converted.

> But in general, implementation dependent behaviour should be avoided
> whenever possible.  I think it would be better to explicitly specify
> either (a) that the original directory separators will be preserved
> (but that any *new* directory separators added will use the platform's
> default directory separator), or (b) that *all* directory separators
> in path names will be replaced with the platform's default directory
> separator.
> 
> How difficult would it be to preserve the original
> directory separator?

The .NET CLI doesn't, so it would be very difficult.
 
> >  	% Returns ".".
> >  :- func dir__this_directory = string.
> > @@ -39,25 +48,39 @@
> >  	% dir__split_name(PathName, DirName, BaseName).
> >  	% Split a filename into a directory part and a filename part.
> >  	% Fails for root directories or relative filenames not
> > -	% containing a directory separator.
> > +	% containing directory information.
> > +	% Trailing slashes are removed from PathName before splitting.
> > +	% DirName may have a trailing slash.
> >  :- pred dir__split_name(string::in, string::out, string::out) is semidet.
> 
> Here again I think that if the intent is that the behaviour be
> implementation-dependent, the documentation should call attention
> to that by using the words "implementation-dependent" or "unspecified",
> but that it would be better to explicitly specify it.
 
The behaviour is not well-defined.

> >  	% dir__basename(PathName) = BaseName.
> >  	% Returns the non-directory part of a filename.
> > -	% Fails when given a root directory.
> > +	% Fails when given a root directory, "." or "..".
> > +	% Trailing slashes in PathName are removed first.
> >  :- func dir__basename(string) = string is semidet.
> >  :- pred dir__basename(string::in, string::out) is semidet.
> 
> What does this do for path names such as "C:" or "C:\"?
> The documentation does not make that clear.

Fixed.

> > +	% dir__dirname(PathName) = DirName.
> >  	% Returns the directory part of a filename.
> > +	% Returns PathName if it specifies a root directory.
> > +	% Returns `dir__this_directory' when given a filename
> > +	% without any directory information (e.g. "foo").
> > +	% Returns PathName for Windows paths such as "X:"
> > +	% (the current directory on drive `X').
> > +	% Trailing slashes in PathName are removed first.
> > +	% DirName may have a trailing slash.
> > +:- func dir__dirname(string) = string.
> >  :- pred dir__dirname(string::in, string::out) is det.
> 
> This description seems to imply that dirname("C:\") = "C:",
> since trailing slashes are removed first, but that would be
> semantically wrong, since "C:" is not the directory part of "C:\".

Fixed.
 
> >  	% Is the path name syntactically an absolute path
> >  	% (doesn't check whether the path exists).
> > +	% On Unix systems, this means that the path starts with '/'.
> > +	% On Microsoft Windows systems a root directory starts
> > +	% with a drive root (e.g. 'C:\', '\') or a UNC share
> > +	% root (e.g. \\server\share\).
> >  :- pred dir__path_name_is_absolute(string::in) is semidet.
> 
> The predicate checks whether the path name is an absolute path,
> but the documentation here says "a _root_ directory starts with ..." --
> did you mean to say "an _absolute_ directory starts with ..."?
> 
> Also, since `\' is really relative to the current drive,
> I think the documentation should draw the programmers attention
> to the fact that the routine's behaviour may not completely match
> its name.  For example, perhaps add something like the following:
> 
> 	% Note that on Microsoft Windows systems, path names starting
> 	% with '\' (or '/') are technically relative to the current drive,
> 	% but this routine treats them as absolute.

Done.
 
> > +dir__is_directory_separator(Char) :-
> > +	( Char = dir__directory_separator
> > +	; Char = dir__alt_directory_separator, Char \= dir__directory_separator
> > +	).
> 
> In the case where dir__directory_separator = dir__alt_directory_separator,
> the `out' mode of this routine will leave an unnecessary choice point behind.
> 
> It would be better to write it with the "\=" in the first clause,
> 
> 	( Char = dir__directory_separator, Char \= dir__alt_directory_separator
> 	; Char = dir__alt_directory_separator
> 	).

Done.
 
> or using an if-then-else:
> 
> 	dir__is_directory_separator(Char) :-
> 		( dir__directory_separator = dir__alt_directory_separator ->
> 			Char = dir__directory_separator
> 		;
> 			( Char = dir__directory_separator
> 			; Char = dir__alt_directory_separator
> 			)
> 		).
> 
> > +canonicalize_path_chars_2([], RevFileName) = reverse(RevFileName).
> > +canonicalize_path_chars_2([C0 | FileName0], RevFileName0) =
> > +		canonicalize_path_chars_2(FileName0, RevFileName) :-
> > +	% Convert all directory separators to the standard
> > +	% separator for the platform.
> > +	C = ( is_directory_separator(C0) -> directory_separator ; C0 ),
> > +	(
> > +		C = directory_separator,
> > +		FileName0 = [C2 | _],
> > +		dir__is_directory_separator(C2)
> > +	->
> > +		RevFileName = RevFileName0
> >  	;
> > -		FileName = strip_repeated_dir_separators_2(FileName0,
> > -				[C | RevFileName])
> > +		RevFileName = [C | RevFileName0]
> >  	).
> 
> It would help to have a comment "strip repeated directory separators"
> before the if-then-else.

Done.
 
> > +dir__dotnet_path_name_is_absolute(FileName) :-
> > +	dir__dotnet_path_name_is_absolute_2(FileName),
> > +
> > +	% The .NET CLI function System.IO.Path.IsPathRooted succeeds for
> > +	% paths such as `C:', which specifies a directory relative to the
> > +	% current directory on drive C.
> > +	\+ (
> > +		use_windows_paths,
> > +		FileNameLen = length(FileName),
> > +		( FileNameLen >= 2 ->
> > +			char__is_alpha(string__unsafe_index(FileName, 0)),
> > +			string__unsafe_index(FileName, 1) = (':'),
> > +			( FileNameLen > 2 ->
> > +				string__unsafe_index(FileName, 2)
> > +					\= directory_separator `with_type` char
> 
> Why do you need the "`with_type` char" here?

There are both function and predicate versions of string.unsafe_index
and dir.directory_separator.
 
> Also, shouldn't this use `\+ is_directory_separator(...)'  rather than
> `... \= directory_separator'?  Windows (or at least the Microsoft.NET
> CLI implementation -- I didn't check direct use of the Win32 API) treats
> "//server/share" as a UNC path too, not just "\\server/share".

Done.

> > -dir__make_path_name(DirName, FileName) = PathName :-
> > +dir__make_path_name(DirName, FileName) = DirName/FileName.
> > +
> > +DirName/FileName =
> > +	( if
> > +	    (
> > +		% Check for construction of relative paths of the form "C:foo".
> > +		use_windows_paths,
> > +		length(DirName) = 2,
> > +		char__is_alpha(string__unsafe_index(DirName, 0)),
> > +		string__unsafe_index(DirName, 1) = (':')
> > +	    ;
> > +		% Don't introduce duplicate directory separators.
> > +		% On Windows \\foo (a UNC server specification) is
> > +		% not equivalent to \foo (the directory X:\foo, where
> > +		% X is the current drive).
> > +		string__unsafe_index(DirName,
> > +		    string__length(DirName) - 1) =
> > +			dir__directory_separator `with_type` char
> > +	    )
> 
> Likewise here.

Done.
 
> > +:- pragma promise_pure(dir__make_directory_2/4).
> > +dir__make_directory_2(_::in, _::out, _::di, _::uo) :-
> > +	private_builtin__sorry("dir__make_directory").
> 
> Why is that needed?
> Won't that be handled by the automatic stub generation?
 
Removed.
 
> > @@ -822,15 +1018,14 @@
> >  	ML_check_dir_readable(DirName, &is_readable, &Result);
> >  	if (is_readable) {
> >  		dir_pattern_len = strlen(DirName);
> > -		MR_allocate_aligned_string_msg(dir_pattern,
> > -			dir_pattern_len + 2, MR_PROC_LABEL);
> > +		dir_pattern = MR_malloc(dir_pattern_len + 2);
> >  		strcpy(dir_pattern, DirName);
> >  		dir_pattern[dir_pattern_len] = '\\\\';
> >  		dir_pattern[dir_pattern_len + 1] = '*';
> >  		dir_pattern[dir_pattern_len + 2] = '\\0';
> 
> Off-by-one error in the argument to MR_malloc.

I've changed it to use `dir./'.

Simon.


Estimated hours taken: 120
Branches: main

Library changes required to make the compiler work on Windows
without Cygwin.  (Compiler changes to come separately).

library/dir.m:
	Handle Windows-style paths.

	Change the determinism of dir.basename and dir.split_name.
	dir.basename now fails for root directories (a new function
	dir.basename_det calls error/1 rather than failing).
	dir.split_name fails for root directories or if the pathname
	passed doesn't contain a directory separator.

	Add predicates dir.make_directory, dir.path_name_is_absolute
	and dir.path_name_is_root_directory.

	Add a multi predicate dir.is_directory separator which
	returns all separators for the platform (including '/' on
	Windows), not just the standard one.
	
	Add a function dir.parent_directory (returns "..").
	
	Add dir.foldl2 and dir.recursive_foldl2, to iterate through
	the entries in a directory (and maybe its subdirectories).

	Change '/' to correctly handle Windows paths of the form
	"C:"/"foo" and "\"/"foo".

	Don't add repeated directory separators in '/'.
	
library/io.m:
	Add io.file_type and io.check_file_accessibility.

	Add predicates to deal with symlinks -- io.have_symlinks,
	io.make_symlink and io.follow_symlink.

	Add io.file_id for use by dir.foldl2 to detect
	symlink loops. This is a bit low level, so it's
	not included in the user documentation.

	Add io.(binary_)input_stream_foldl2_io_maybe_stop, which
	is like io.(binary_)input_stream_foldl2_io, but allows
	stopping part of the way through. This is useful for
	implementing `diff'-like functionality to replace
	mercury_update_interface.

	Use Windows-style paths when generating temporary file
	names on Windows.
	
	Add versions of the predicates to generate error messages
	to handle Win32 errors.

	Add versions of the predicates to generate error messages
	which take a system error code, rather than looking up
	errno. This simplifies things where the error we
	are interested in was not from the last system call.

library/exception.m:
	Add a predicate finally/6 which performs the same function
	as the `finally' clause in languages such as C# and Java.

	Add predicates try_det, try_io_det and try_store_det,
	which only have one mode so they are more convenient
	to pass to promise_only solution.

library/Mmakefile:
	Add dependencies on runtime/mercury_conf.h for files which
	use the MR_HAVE_* macros.

library/string.m:
	Add a function version of string__index.

NEWS:
	Document the new predicates and functions and the change
	of determinism of dir.split_name and dir.basename.

configure.in:
runtime/mercury_conf.h.in:
	Test for lstat, mkdir, symlink and readlink.

runtime/mercury_conf_param.h:
	Add a macro MR_BROKEN_ST_INO, which is true if the st_ino
	field of `struct stat' is garbage. Currently defined iff
	MR_WIN32 is defined.

compiler/compile_target_code.m:
compiler/modules.m:
compiler/options_file.m:
compiler/prog_io.m:
compiler/source_file_map.m:
	Changes required by the change of determinism of
	dir.split_name and dir.basename.

tests/hard_coded/Mmakefile:
tests/hard_coded/dir_test.{m,exp,exp2}:
	Test case.

diff -u NEWS NEWS
--- NEWS
+++ NEWS
@@ -37,6 +37,7 @@
 	foldl2/6,
 	parent_directory/0,
 	path_name_is_absolute/1,
+	path_name_is_root_directory/1,
 	recursive_foldl2/7.
 * We've added several new predicates to the io module:
 	have_symlinks/0,
@@ -122,6 +123,7 @@
 	foldl2/6,
 	parent_directory/0,
 	path_name_is_absolute/1,
+	path_name_is_root_directory/1,
 	recursive_foldl2/7.
 
 * We've added several new predicates to the io module:
diff -u library/dir.m library/dir.m
--- library/dir.m
+++ library/dir.m
@@ -9,7 +9,13 @@
 
 % Filename and directory handling.
 % Stability: high.
-
+%
+% Note that the predicates and functions in this module change
+% directory separators in paths passed to them to the normal
+% separator for the platform.  Duplicate directory separators
+% and trailing separators are also removed where that doesn't
+% change the meaning of the path name.
+% 
 %-----------------------------------------------------------------------------%
 
 :- module dir.
@@ -28,9 +34,6 @@
 	% Is the character a directory separator.
 	% On Microsoft Windows systems this will succeed for '/'
 	% as well as '\\'.
-	% Note that the predicates and functions in this module may
-	% change directory separators in paths passed to them
-	% to the normal separator for the platform.
 :- pred dir__is_directory_separator(character).
 :- mode dir__is_directory_separator(in) is semidet.
 :- mode dir__is_directory_separator(out) is multi.
@@ -46,17 +49,32 @@
 :- mode dir__parent_directory(out) is det.	
 
 	% dir__split_name(PathName, DirName, BaseName).
+	%
 	% Split a filename into a directory part and a filename part.
+	%
 	% Fails for root directories or relative filenames not
 	% containing directory information.
-	% Trailing slashes are removed from PathName before splitting.
-	% DirName may have a trailing slash.
+	%
+	% Trailing slashes are removed from PathName before splitting,
+	% if that doesn't change the meaning of PathName.
+	%
+	% Trailing slashes are removed from DirName after splitting,
+	% if that doesn't change the meaning of DirName.
+	%
+	% On Windows, drive current directories are handled correctly,
+	% for example `dir__split_name("C:foo", "C:", "foo")'.
+	% (`X:' is the current directory on drive `X').
 :- pred dir__split_name(string::in, string::out, string::out) is semidet.
 
 	% dir__basename(PathName) = BaseName.
+	%
 	% Returns the non-directory part of a filename.
-	% Fails when given a root directory, "." or "..".
-	% Trailing slashes in PathName are removed first.
+	%
+	% Fails when given a root directory, ".", ".." or a Windows
+	% path such as "X:".
+	%
+	% Trailing slashes are removed from PathName before splitting,
+	% if that doesn't change the meaning of PathName.
 :- func dir__basename(string) = string is semidet.
 :- pred dir__basename(string::in, string::out) is semidet.
 
@@ -64,29 +82,62 @@
 :- func dir__basename_det(string) = string.
 
 	% dir__dirname(PathName) = DirName.
+	%
 	% Returns the directory part of a filename.
+	%
 	% Returns PathName if it specifies a root directory.
+	%
+	% Returns PathName for Windows paths such as "X:".
+	%
 	% Returns `dir__this_directory' when given a filename
 	% without any directory information (e.g. "foo").
-	% Returns PathName for Windows paths such as "X:"
-	% (the current directory on drive `X').
-	% Trailing slashes in PathName are removed first.
-	% DirName may have a trailing slash.
+	%
+	% Trailing slashes in PathName are removed first, if that
+	% doesn't change the meaning of PathName.
+	%
+	% Trailing slashes are removed from DirName after splitting,
+	% if that doesn't change the meaning of DirName.
 :- func dir__dirname(string) = string.
 :- pred dir__dirname(string::in, string::out) is det.
 
+	% dir__path_name_is_absolute(PathName)
+	%
 	% Is the path name syntactically an absolute path
-	% (doesn't check whether the path exists).
-	% On Unix systems, this means that the path starts with '/'.
-	% On Microsoft Windows systems a root directory starts
-	% with a drive root (e.g. 'C:\', '\') or a UNC share
-	% root (e.g. \\server\share\).
+	% (this doesn't check whether the path exists).
+	%
+	% An path is absolute iff it begins with a root directory
+	% (see dir__path_name_is_root_directory).
 :- pred dir__path_name_is_absolute(string::in) is semidet.
 
+	% dir__path_name_is_root_directory(PathName)
+	%
+	% On Unix, '/' is the only root directory.
+	% On Windows, a root directory is one of the following:
+	%	'X:\', which specifies the root directory of drive X,
+	%		where X is any letter.
+	%	'\', which specifies the root directory of the current drive.
+	%	'\\server\share\', which specifies a UNC root directory for
+	%		a network drive.
+	%
+	% Note that 'X:' is not a Windows root directory -- it specifies the
+	% current directory on drive X, where X is any letter.
+:- pred dir__path_name_is_root_directory(string::in) is semidet.
+
+	% PathName = DirName / FileName
+	%
 	% Given a directory name and a filename, return the pathname of that
 	% file in that directory.
-:- func dir__make_path_name(string, string) = string.
+	%
+	% Duplicate directory separators will not be introduced if
+	% DirName ends with a directory separator.
+	%
+	% On Windows, a call such as `"C:"/"foo"' will return "C:foo".
+	%
+	% Throws an exception if FileName is an absolute path name.
+	% Throws an exception on Windows if FileName is a current
+	% drive relative path such as "C:".
 :- func string / string = string.
+:- func dir__make_path_name(string, string) = string.
 
 %-----------------------------------------------------------------------------%
 
@@ -96,6 +147,12 @@
 :- pred dir__make_directory(string, io__res, io__state, io__state).
 :- mode dir__make_directory(in, out, di, uo) is det.
 
+	% Make only the given directory.
+	% Fails if the directory already exists, or the parent
+	% directory doesn't.
+:- pred dir__make_single_directory(string, io__res, io__state, io__state).
+:- mode dir__make_single_directory(in, out, di, uo) is det.
+
 %-----------------------------------------------------------------------------%
 
 	% FoldlPred(DirName, BaseName, FileType, Continue, !Data, !IO).
@@ -113,7 +170,7 @@
 	% Directories are not processed recursively.
 	% Processing will stop if the boolean (Continue) output of P is bound
 	% to `no'.
-	% The order in which the entries are processed is system dependent.
+	% The order in which the entries are processed is unspecified.
 :- pred dir__foldl2(dir__foldl_pred(T), string,
 	T, io__maybe_partial_res(T), io__state, io__state).
 :- mode dir__foldl2(in(dir__foldl_pred), in, in, out, di, uo) is det.
@@ -176,11 +233,6 @@
 	Sep = System.IO.Path.DirectorySeparatorChar;
 ").		
 
-dir__is_directory_separator(Char) :-
-	( Char = dir__directory_separator
-	; Char = dir__alt_directory_separator, Char \= dir__directory_separator
-	).
-
 :- func dir__alt_directory_separator = char.
 
 dir__alt_directory_separator = ('/').
@@ -190,6 +242,18 @@
 	Sep = System.IO.Path.AltDirectorySeparatorChar;
 ").		
 
+dir__is_directory_separator(Char) :-
+	( Char = dir__directory_separator, Char \= dir__alt_directory_separator
+	; Char = dir__alt_directory_separator
+	).
+
+	% Single-moded version of is_directory_separator
+	% for passing as a closure.
+:- pred dir__is_directory_separator_semidet(char::in) is semidet.
+
+dir__is_directory_separator_semidet(Char) :-
+	dir__is_directory_separator(Char).
+
 use_windows_paths :- dir__directory_separator = ('\\').
 
 :- pragma export((dir__this_directory = out), "ML_dir_this_directory").
@@ -231,14 +295,14 @@
 	(
 		dir__is_root_directory(FileNameChars)
 	->
-		DirName = FileName
+		DirName = string__from_char_list(FileNameChars)
 	;
 		% Current directory on the given drive.
 		use_windows_paths,
 	  	FileNameChars = [Drive, (':')],
 		char__is_alpha(Drive)
 	->	
-	  	DirName = FileName
+		DirName = string__from_char_list(FileNameChars)
 	;
 		dir__split_name_2(FileNameChars, DirName0, _)
 	->
@@ -286,17 +350,42 @@
 dir__split_name_3(FileNameChars, DirName, BaseName) :-
 	% Remove any trailing separator.
 	RevFileNameChars0 = reverse(FileNameChars),
-	( RevFileNameChars0 = [dir__directory_separator | RevFileNameChars1] ->
+	(
+		RevFileNameChars0 = [LastChar | RevFileNameChars1],
+		dir__is_directory_separator(LastChar)
+	->
 		RevFileNameChars = RevFileNameChars1
 	;
 		RevFileNameChars = RevFileNameChars0
 	),
 	(
-		list__takewhile(isnt(unify(dir__directory_separator)),
-			RevFileNameChars, RevBaseName, RevDirName),
+		list__takewhile(isnt(dir__is_directory_separator_semidet),
+			RevFileNameChars, RevBaseName, RevDirName0),
 		RevBaseName \= [],
-		RevDirName \= []
+		RevDirName0 \= []
 	->
+		%
+		% Strip the trailing separator off the directory name
+		% if doing so doesn't change the meaning.
+		%
+		(
+			RevDirName0 = [Sep | RevDirName1],
+			\+ (
+				dir__is_directory_separator(Sep),
+				(
+					use_windows_paths,
+					RevDirName1 = [(':'), Drive],
+					char__is_alpha(Drive)
+				;
+					RevDirName1 = []
+				)
+			)
+		->	
+			RevDirName = RevDirName1
+		;
+			RevDirName = RevDirName0
+		),
+
 		BaseName = string__from_rev_char_list(RevBaseName),
 		DirName = string__from_rev_char_list(RevDirName)
 	;
@@ -305,7 +394,7 @@
 		FileNameChars = [Drive, (':') | BaseNameChars],
 		char__is_alpha(Drive),
 		BaseNameChars = [BaseNameFirst | _],
-		BaseNameFirst \= dir__directory_separator
+		\+ dir__is_directory_separator(BaseNameFirst)
 	->
 		BaseName = string__from_char_list(BaseNameChars),
 		DirName = string__from_char_list([Drive, (':')])
@@ -340,22 +429,27 @@
 	}
 ").
 
-	% Convert alternative path separators to the normal path
-	% separator for the platform, and remove repeated path
-	% separators.
+	% Remove repeated path separators.
 :- func canonicalize_path_chars(list(char)) = list(char).
 
-canonicalize_path_chars(FileName0) =
+canonicalize_path_chars(FileName0) = FileName :-
 	(
-		% Windows allows paths of the form "\\server\share".
+		% Windows allows path names of the form "\\server\share".
+		% These path names are referred to as UNC path names.
 		use_windows_paths,
 		FileName0 = [Char1 | FileName1],
 		is_directory_separator(Char1)
 	->
-		[dir__directory_separator |
-			canonicalize_path_chars_2(FileName1, [])]
+		FileName2 = canonicalize_path_chars_2(FileName1, []),
+
+		% "\\" isn't a UNC path name, so it is equivalent to "\".
+		( FileName2 = [Char2], is_directory_separator(Char2) ->
+			FileName = FileName2	
+		;
+			FileName = [directory_separator | FileName2]
+		)
 	;	
-		canonicalize_path_chars_2(FileName0, [])
+		FileName = canonicalize_path_chars_2(FileName0, [])
 	).
 
 :- func canonicalize_path_chars_2(list(char), list(char)) = list(char).
@@ -363,11 +457,13 @@
 canonicalize_path_chars_2([], RevFileName) = reverse(RevFileName).
 canonicalize_path_chars_2([C0 | FileName0], RevFileName0) =
 		canonicalize_path_chars_2(FileName0, RevFileName) :-
-	% Convert all directory separators to the standard
-	% separator for the platform.
+	% Convert all directory separators to the standard separator
+	% for the platform.
 	C = ( is_directory_separator(C0) -> directory_separator ; C0 ),
+
+	% Remove repeated directory separators.
 	(
-		C = directory_separator,
+		dir__is_directory_separator(C),
 		FileName0 = [C2 | _],
 		dir__is_directory_separator(C2)
 	->
@@ -388,6 +484,10 @@
 			Chars
 		).
 
+dir__path_name_is_root_directory(PathName) :-
+	is_root_directory(canonicalize_path_chars(
+		string__to_char_list(PathName))).
+
 	% Assumes repeated directory separators have been removed.
 :- pred is_root_directory(list(char)::in) is semidet.
 
@@ -397,7 +497,8 @@
 	; use_windows_paths ->
 		strip_leading_win32_root_directory(FileName, [])
 	;
-		FileName = [dir__directory_separator]
+		FileName = [Char],
+		dir__is_directory_separator(Char)
 	).
 
 	% strip_leading_win32_root_directory(FileName, FileNameMinusRoot)
@@ -420,18 +521,21 @@
 		list(char)::out) is semidet.
 
 strip_leading_win32_drive_root_directory(
-		[Letter, ':', dir__directory_separator| !.FileName],
+		[Letter, ':', Sep| !.FileName],
 		!:FileName) :-
-	char__is_alpha(Letter).
+	char__is_alpha(Letter),
+	dir__is_directory_separator(Sep).
 
 	% Check for `\foo...'.
 :- pred strip_leading_win32_current_drive_root_directory(list(char)::in,
 		list(char)::out) is semidet.
 
 strip_leading_win32_current_drive_root_directory(
-		[dir__directory_separator | !.FileName], !:FileName) :-
+		[Char1 | !.FileName], !:FileName) :-
+	dir__is_directory_separator(Char1),
 	( !.FileName = []
-	; !.FileName = [Char2 | !:FileName], Char2 \= dir__directory_separator
+	; !.FileName = [Char2 | !:FileName],
+		\+ dir__is_directory_separator(Char2)
 	).
 
 	% Check for `\\server\' or `\\server\share\'.
@@ -439,8 +543,8 @@
 		list(char)::out) is semidet.
 
 strip_leading_win32_unc_root_directory([Sep, Sep | !.FileName], !:FileName) :-
-	Sep = dir__directory_separator,
-	list__takewhile(isnt(unify(Sep)), !.FileName,
+	dir__is_directory_separator(Sep),
+	list__takewhile(isnt(dir__is_directory_separator_semidet), !.FileName,
 		Server, !:FileName),
 	Server \= [],
 	(
@@ -451,8 +555,9 @@
 			!.FileName = []
 		;
 			!.FileName = [_|_],
-			list__takewhile(isnt(unify(Sep)), !.FileName,
-				Share, !:FileName),
+			list__takewhile(
+				isnt(dir__is_directory_separator_semidet),
+				!.FileName, Share, !:FileName),
 			Share \= [],
 			( !.FileName = [Sep | !:FileName]
 			; !.FileName = []
@@ -470,12 +575,11 @@
 		% For reasons known only to Microsoft,
 		% trailing slashes are significant.
 		FileNameLen = length(FileName),
-		(
-			is_directory_separator(
-				string__unsafe_index(FileName, FileNameLen - 1))
-		->
-			is_dotnet_root_directory_2(
-				string__left(FileName, FileNameLen - 1))
+		( FileNameLen > 0 ->
+			is_directory_separator(string__unsafe_index(
+				FileName, FileNameLen - 1)),
+			is_dotnet_root_directory_2(string__left(
+				FileName, FileNameLen - 1))
 		;
 			fail
 		)
@@ -508,7 +612,8 @@
 				string__to_char_list(FileName)),
 			_)
 	;
-		string__index(FileName, 0, dir__directory_separator)
+		string__index(FileName, 0, FirstChar),
+		dir__is_directory_separator(FirstChar)
 	).
 
 :- pred dir__dotnet_path_name_is_absolute(string::in) is semidet.
@@ -526,8 +631,8 @@
 			char__is_alpha(string__unsafe_index(FileName, 0)),
 			string__unsafe_index(FileName, 1) = (':'),
 			( FileNameLen > 2 ->
-				string__unsafe_index(FileName, 2)
-					\= directory_separator `with_type` char
+				\+ dir__is_directory_separator(
+					string__unsafe_index(FileName, 2))
 			;
 				true
 			)
@@ -556,35 +661,60 @@
 
 dir__make_path_name(DirName, FileName) = DirName/FileName.
 
-DirName/FileName =
-	( if
-	    (
-		% Check for construction of relative paths of the form "C:foo".
-		use_windows_paths,
-		length(DirName) = 2,
-		char__is_alpha(string__unsafe_index(DirName, 0)),
-		string__unsafe_index(DirName, 1) = (':')
-	    ;
-		% Don't introduce duplicate directory separators.
-		% On Windows \\foo (a UNC server specification) is
-		% not equivalent to \foo (the directory X:\foo, where
-		% X is the current drive).
-		string__unsafe_index(DirName,
-		    string__length(DirName) - 1) =
-			dir__directory_separator `with_type` char
-	    )
-	  then
-		DirName ++ FileName
-	  else
-		% Using string__append_list has a fixed overhead of six
-		% words, whereas using two string__appends back to back
-		% would have a memory overhead proportional to the size
-		% of the string copied twice. We prefer the former because
-		% it is bounded.
-		string__append_list([DirName,
-			string__char_to_string(dir__directory_separator),
-			FileName])
-	).
+:- pragma export(dir__make_path_name(in, in) = out, "ML_make_path_name").
+DirName0/FileName0 = PathName :-
+    DirName = string__from_char_list(canonicalize_path_chars(
+    		string__to_char_list(DirName0))),
+    FileName = string__from_char_list(canonicalize_path_chars(
+    		string__to_char_list(FileName0))),
+    (
+        dir__path_name_is_absolute(FileName)
+    ->
+        error("dir./: second argument is absolute")
+    ;
+        % Check that FileName is not a relative path of the form "C:foo".
+        use_windows_paths,   
+        Length = length(FileName),
+        ( Length >= 2 ->
+            char__is_alpha(string__unsafe_index(FileName, 0)),
+            string__unsafe_index(FileName, 1) = (':'),
+            ( Length > 2 ->
+                \+ is_directory_separator(string__unsafe_index(FileName, 2))
+            ;
+                true
+            )
+        ;
+            fail
+        )
+    ->
+        error("dir./: second argument is a current drive relative path")
+    ;
+        (
+            % Check for construction of relative paths of the form "C:foo".
+            use_windows_paths,
+            length(DirName) = 2,
+            char__is_alpha(string__unsafe_index(DirName, 0)),
+            string__unsafe_index(DirName, 1) = (':')
+        ;
+            % Don't introduce duplicate directory separators.
+            % On Windows \\foo (a UNC server specification) is
+            % not equivalent to \foo (the directory X:\foo, where
+            % X is the current drive).
+            dir__is_directory_separator(
+                string__unsafe_index(DirName, string__length(DirName) - 1))
+        )
+    ->
+        PathName = DirName ++ FileName
+    ;
+        % Using string__append_list has a fixed overhead of six
+        % words, whereas using two string__appends back to back
+        % would have a memory overhead proportional to the size
+        % of the string copied twice. We prefer the former because
+        % it is bounded.
+        PathName = string__append_list([DirName,
+            string__char_to_string(dir__directory_separator),
+            FileName])
+    ).
 
 %-----------------------------------------------------------------------------%
 
@@ -594,28 +724,29 @@
 		( PathName = DirName ->
 			% We've been asked to make a root directory --
 			% the mkdir will fail.
-			dir__make_directory_2(PathName, Result, !IO)
+			dir__make_single_directory_2(0, PathName, Result, !IO)
 		;
 			( DirName = dir__this_directory ->
 				% Just go ahead and attempt to make the
 				% directory -- if the current directory
 				% is not accessible, the mkdir will fail.
-				dir__make_directory_2(PathName, Result, !IO)
+				dir__make_single_directory_2(0,
+					PathName, Result, !IO)
 			;
 				io__check_file_accessibility(DirName, [],
 					ParentAccessResult, !IO),
 				(
 					ParentAccessResult = ok,
-					dir__make_directory_2(PathName,
-						Result, !IO)
+					dir__make_single_directory_2(0,
+						PathName, Result, !IO)
 				;
 					ParentAccessResult = error(_),
 					dir__make_directory(DirName,
 						ParentResult, !IO),
 					(
 						ParentResult = ok,
-						dir__make_directory_2(PathName,
-							Result, !IO)	
+						dir__make_single_directory_2(0,
+							PathName, Result, !IO)
 					;
 						ParentResult = error(_),
 						Result = ParentResult
@@ -673,42 +804,89 @@
 	"SUCCESS_INDICATOR = true;"
 ).
 
-:- pred dir__make_directory_2(string::in, io__res::out,
-		io__state::di, io__state::uo) is det.
+dir__make_single_directory(DirName, Result, !IO) :-
+	dir__make_single_directory_2(1, DirName, Result, !IO).	
 
-:- pragma promise_pure(dir__make_directory_2/4).
-dir__make_directory_2(_::in, _::out, _::di, _::uo) :-
-	private_builtin__sorry("dir__make_directory").
+:- pred dir__make_single_directory_2(int::in, string::in, io__res::out,
+		io__state::di, io__state::uo) is det.
 
 :- pragma foreign_proc("C",
-	dir__make_directory_2(DirName::in, Result::out, IO0::di, IO::uo),
+	dir__make_single_directory_2(ErrorIfExists::in, DirName::in,
+		Result::out, IO0::di, IO::uo),
 	[will_not_call_mercury, promise_pure, tabled_for_io, thread_safe],
 "{
 #if defined(MR_WIN32)
-	int error;
-
 	if (CreateDirectory(DirName, NULL)) {
 		Result = ML_make_mkdir_res_ok();
-	} else if ((error = GetLastError()) == ERROR_ALREADY_EXISTS) {
-		ML_make_mkdir_res_exists(error, DirName, &Result);
 	} else {
-		ML_make_mkdir_res_error(error, &Result);
+		int error;
+
+		error = GetLastError();
+		if (!ErrorIfExists && error == ERROR_ALREADY_EXISTS) {
+			ML_make_mkdir_res_exists(error, DirName, &Result);
+		} else {
+			ML_make_mkdir_res_error(error, &Result);
+		}
 	}
 #elif defined(MR_HAVE_MKDIR)
 	if (mkdir(DirName, 0777) == 0) {
 		Result = ML_make_mkdir_res_ok();
   #ifdef EEXIST
-	} else if (errno == EEXIST) {
+	} else if (!ErrorIfExists && errno == EEXIST) {
 		ML_make_mkdir_res_exists(errno, DirName, &Result);
   #endif /* EEXIST */
 	} else {
 		ML_make_mkdir_res_error(errno, &Result);
 	}
 #else /* !MR_WIN32 && !MR_HAVE_MKDIR */
-	MR_fatal_error(""dir.make_directory_2 called but not supported"");
+	MR_fatal_error(
+		""dir.make_single_directory_2 called but not supported"");
 #endif
 	IO = IO0;
 }").
+:- pragma foreign_proc("C#",
+	dir__make_single_directory_2(ErrorIfExists::in, DirName::in,
+		Result::out, _IO0::di, _IO::uo),
+	[will_not_call_mercury, promise_pure, tabled_for_io, thread_safe],
+"{
+    try {
+	// CreateDirectory doesn't fail if a file with the same
+	// name as the directory being created already exists.
+	if (System.IO.File.Exists(DirName)) {
+		mercury.dir.mercury_code.ML_make_mkdir_res_error(
+			new System.Exception(
+				""a file with that name already exists""),
+				ref Result);
+	} else {
+		System.IO.DirectoryInfo info =
+			new System.IO.DirectoryInfo(DirName);
+		System.IO.DirectoryInfo parent_info = info.Parent;
+
+		if (parent_info == null) {
+			mercury.dir.mercury_code.ML_make_mkdir_res_error(
+				new System.Exception(
+					""can't create root directory""),
+				ref Result);
+		} else if (!info.Parent.Exists) {
+			mercury.dir.mercury_code.ML_make_mkdir_res_error(
+				new System.Exception(
+					""parent directory does not exist""),
+				ref Result);
+		} else if (ErrorIfExists == 1 && info.Exists) {
+			mercury.dir.mercury_code.ML_make_mkdir_res_error(
+				new System.Exception(
+					""directory already exists""),
+				ref Result);
+		} else {
+			info.Create();
+			Result =
+			    mercury.dir.mercury_code.ML_make_mkdir_res_ok();
+		}
+	}
+    } catch (System.Exception e) {
+	mercury.dir.mercury_code.ML_make_mkdir_res_error(e, ref Result);
+    }
+}").
 
 :- func dir__make_mkdir_res_ok = io__res.
 :- pragma export((dir__make_mkdir_res_ok = out), "ML_make_mkdir_res_ok"). 
@@ -1012,18 +1190,12 @@
 	ML_DIR_STREAM Dir;
 	LPTSTR FirstFileName;
 	char *dir_pattern;
-	int dir_pattern_len;
-	int is_readable;
+	MR_Integer is_readable;
 
 	ML_check_dir_readable(DirName, &is_readable, &Result);
 	if (is_readable) {
-		dir_pattern_len = strlen(DirName);
-		dir_pattern = MR_malloc(dir_pattern_len + 2);
-		strcpy(dir_pattern, DirName);
-		dir_pattern[dir_pattern_len] = '\\\\';
-		dir_pattern[dir_pattern_len + 1] = '*';
-		dir_pattern[dir_pattern_len + 2] = '\\0';
-
+		dir_pattern = ML_make_path_name(DirName,
+				MR_make_string_const(""*""));
 		Dir = FindFirstFile(dir_pattern, &file_data);
 		if (Dir == INVALID_HANDLE_VALUE) {
 			int error = GetLastError();
diff -u library/exception.m library/exception.m
--- library/exception.m
+++ library/exception.m
@@ -345,6 +345,7 @@
 		pred(out, di, uo) is det, out, di, uo) is cc_multi.
 :- mode finally_2(pred(out, di, uo) is cc_multi,
 		pred(out, di, uo) is cc_multi, out, di, uo) is cc_multi.
+:- pragma promise_pure(finally_2/5).
 
 finally_2(P, Cleanup, {PRes, CleanupRes}, !IO) :-
 	try_io(P, ExcpResult, !IO),
@@ -357,28 +358,31 @@
 		% The io__state resulting from Cleanup can't
 		% possibly be used, so we have to trick the
 		% compiler into not removing the call.
-		( use(!.IO) ->
+		(
+			semidet_succeed,
+			impure use(!.IO)
+		->
 			rethrow(ExcpResult)		
 		;
 			error("exception.finally_2")
 		)
 	).
 
-:- pred use(T).
-:- mode use(in) is semidet.
+:- impure pred use(T).
+:- mode use(in) is det.
 
 :- pragma foreign_proc("C",
 	use(_T::in),
-	[will_not_call_mercury, promise_pure, thread_safe],
-	"SUCCESS_INDICATOR = MR_TRUE;").
+	[will_not_call_mercury, thread_safe],
+	";").
 :- pragma foreign_proc("C#",
 	use(_T::in),
-	[will_not_call_mercury, promise_pure, thread_safe],
-	"SUCCESS_INDICATOR = true;").
+	[will_not_call_mercury, thread_safe],
+	";").
 :- pragma foreign_proc("Java",
 	use(_T::in),
-	[will_not_call_mercury, promise_pure, thread_safe],
-	"SUCCESS_INDICATOR = true;").
+	[will_not_call_mercury, thread_safe],
+	";").
 
 %-----------------------------------------------------------------------------%
 
diff -u tests/hard_coded/dir_test.m tests/hard_coded/dir_test.m
--- tests/hard_coded/dir_test.m
+++ tests/hard_coded/dir_test.m
@@ -8,7 +8,7 @@
 
 :- implementation.
 
-:- import_module bool, dir, list, require, string.
+:- import_module bool, dir, exception, list, require, std_util, string.
 
 main -->
 	io__write_string("Directory separator is '"),
@@ -33,8 +33,18 @@
 	run_test("//foo//bar/"),
 	run_test("//foo//"),
 	run_test("/"),
+	run_test("//"),
 	run_test("foo/bar"),
 
+	test_make_path_name("C:", "foo"),
+	test_make_path_name("C:\\", "foo"),
+	test_make_path_name("C:", "C:"),
+	test_make_path_name("C:", "C:\\foo"),
+	test_make_path_name(".", "/foo"),
+	test_make_path_name(".", "\\foo"),
+	test_make_path_name("foo", "bar/baz"),
+	test_make_path_name("foo/", "bar/baz"),
+
 	io__write_string("checking whether `unwritable' is readable..."),
 	io__check_file_accessibility("unwritable", [read], ReadResult),
 	io__write(ReadResult),
@@ -55,6 +65,23 @@
 	% Test making a directory that already exists.
 	test0("make_directory", dir__make_directory(Dir1)),
 
+	{ Dir2 = "test_dir"/"d2" },
+	dir__make_single_directory(Dir2/"d2", Dir2Res),
+	(
+		{ Dir2Res = ok },
+		io__write_string(
+"Error: dir.make_single_directory succeeded but parent doesn't exist.\n")
+	;
+		{ Dir2Res = error(_) },
+		io__write_string(
+"dir.make_single_directory with non-existent parent failed as expected.\n")
+	),
+
+	test0("make_single_directory", dir__make_single_directory(Dir2)),
+	test0("make_single_directory 2",
+		dir__make_single_directory(Dir2/"d2")),
+
+
 	test1("file_type", io__file_type(yes, Dir1), Type),
 	io__write_string("type of "),
 	io__write_string(Dir1),
@@ -89,7 +116,7 @@
 	( { io__have_symlinks } ->
 		test0("making symlink 1", io__make_symlink("baz", Dir1/"bar")),
 		test0("making symlink 2", io__make_symlink("d1",
-			"test_dir"/"d2")),
+			"test_dir"/"d3")),
 
 		% Make a loop.
 		test0("making symlink 3",
@@ -203,6 +230,7 @@
 	test_dirname(PathName),
 	test_basename(PathName),
 	test_path_name_is_absolute(PathName),
+	test_path_name_is_root_directory(PathName),
 	io__nl.
 
 :- pred test_split_name(string::in, io__state::di, io__state::uo) is det.
@@ -216,7 +244,8 @@
 		io__write_string(DirName),
 		io__write_string(""", """),
 		io__write_string(FileName),
-		io__write_string(""").\n")
+		io__write_string(""").\n"""),
+		test_make_path_name(DirName, FileName)
 	;
 		io__write_string("_, _) failed.\n")
 	).
@@ -257,6 +286,45 @@
 		io__write_string(" failed\n")
 	).
 
+:- pred test_path_name_is_root_directory(string::in,
+		io__state::di, io__state::uo) is det.
+
+test_path_name_is_root_directory(PathName) -->
+	io__write_string("dir__path_name_is_root_directory("""),
+	io__write_string(PathName),
+	io__write_string(""")"),
+	( { dir__path_name_is_root_directory(PathName) } ->
+		io__write_string(".\n")		
+	;
+		io__write_string(" failed\n")
+	).
+
+:- pred test_make_path_name(string::in, string::in,
+		io__state::di, io__state::uo) is det.
+
+test_make_path_name(DirName, FileName) -->
+	io__write_string(""""),
+	io__write_string(DirName),
+	io__write_string("""/"""),
+	io__write_string(FileName),
+	io__write_string(""" "),
+	{ Res = promise_only_solution(try_det(
+		(pred(R::out) is det :- R = DirName/FileName))) },
+	(
+		{ Res = succeeded(Path) },
+		io__write_string(" = """),
+		io__write_string(Path),
+		io__write_string(""".\n")
+	;
+		{ Res = failed },
+		{ error("dir./ failed") }
+	;
+		{ Res = exception(Excp) },
+		io__write_string("threw exception: "),
+		io__write(univ_value(Excp)),
+		io__nl
+	).
+
 :- pred touch_file(string::in, io__state::di, io__state::uo) is det.
 
 touch_file(FileName) -->

tests/hard_coded/dir_test.exp:
==============================
Directory separator is '\'.
dir__split_name("\\server\share\foo", "\\server\share", "foo").
""\\server\share"/"foo"  = "\\server\share\foo".
dir__dirname("\\server\share\foo") = "\\server\share".
dir__basename("\\server\share\foo") = "foo".
dir__path_name_is_absolute("\\server\share\foo").
dir__path_name_is_root_directory("\\server\share\foo") failed

dir__split_name("\\server\share", _, _) failed.
dir__dirname("\\server\share") = "\\server\share".
dir__basename("\\server\share") = _ failed.
dir__path_name_is_absolute("\\server\share").
dir__path_name_is_root_directory("\\server\share").

dir__split_name("\\server\share\\", _, _) failed.
dir__dirname("\\server\share\\") = "\\server\share\".
dir__basename("\\server\share\\") = _ failed.
dir__path_name_is_absolute("\\server\share\\").
dir__path_name_is_root_directory("\\server\share\\").

dir__split_name("C:\foo", "C:\", "foo").
""C:\"/"foo"  = "C:\foo".
dir__dirname("C:\foo") = "C:\".
dir__basename("C:\foo") = "foo".
dir__path_name_is_absolute("C:\foo").
dir__path_name_is_root_directory("C:\foo") failed

dir__split_name("C:\foo\", "C:\", "foo").
""C:\"/"foo"  = "C:\foo".
dir__dirname("C:\foo\") = "C:\".
dir__basename("C:\foo\") = "foo".
dir__path_name_is_absolute("C:\foo\").
dir__path_name_is_root_directory("C:\foo\") failed

dir__split_name("C:\", _, _) failed.
dir__dirname("C:\") = "C:\".
dir__basename("C:\") = _ failed.
dir__path_name_is_absolute("C:\").
dir__path_name_is_root_directory("C:\").

dir__split_name("C:", _, _) failed.
dir__dirname("C:") = "C:".
dir__basename("C:") = _ failed.
dir__path_name_is_absolute("C:") failed
dir__path_name_is_root_directory("C:") failed

dir__split_name("\", _, _) failed.
dir__dirname("\") = "\".
dir__basename("\") = _ failed.
dir__path_name_is_absolute("\").
dir__path_name_is_root_directory("\").

dir__split_name("", _, _) failed.
dir__dirname("") = ".".
dir__basename("") = "".
dir__path_name_is_absolute("") failed
dir__path_name_is_root_directory("") failed

dir__split_name("foo\\bar\", "foo", "bar").
""foo"/"bar"  = "foo\bar".
dir__dirname("foo\\bar\") = "foo".
dir__basename("foo\\bar\") = "bar".
dir__path_name_is_absolute("foo\\bar\") failed
dir__path_name_is_root_directory("foo\\bar\") failed

dir__split_name("foo\bar\", "foo", "bar").
""foo"/"bar"  = "foo\bar".
dir__dirname("foo\bar\") = "foo".
dir__basename("foo\bar\") = "bar".
dir__path_name_is_absolute("foo\bar\") failed
dir__path_name_is_root_directory("foo\bar\") failed

dir__split_name("foo", _, _) failed.
dir__dirname("foo") = ".".
dir__basename("foo") = "foo".
dir__path_name_is_absolute("foo") failed
dir__path_name_is_root_directory("foo") failed

dir__split_name("/foo", "\", "foo").
""\"/"foo"  = "\foo".
dir__dirname("/foo") = "\".
dir__basename("/foo") = "foo".
dir__path_name_is_absolute("/foo").
dir__path_name_is_root_directory("/foo") failed

dir__split_name("/foo//bar///", "\foo", "bar").
""\foo"/"bar"  = "\foo\bar".
dir__dirname("/foo//bar///") = "\foo".
dir__basename("/foo//bar///") = "bar".
dir__path_name_is_absolute("/foo//bar///").
dir__path_name_is_root_directory("/foo//bar///") failed

dir__split_name("//foo//bar/", _, _) failed.
dir__dirname("//foo//bar/") = "\\foo\bar\".
dir__basename("//foo//bar/") = _ failed.
dir__path_name_is_absolute("//foo//bar/").
dir__path_name_is_root_directory("//foo//bar/").

dir__split_name("//foo//", _, _) failed.
dir__dirname("//foo//") = "\\foo\".
dir__basename("//foo//") = _ failed.
dir__path_name_is_absolute("//foo//").
dir__path_name_is_root_directory("//foo//").

dir__split_name("/", _, _) failed.
dir__dirname("/") = "\".
dir__basename("/") = _ failed.
dir__path_name_is_absolute("/").
dir__path_name_is_root_directory("/").

dir__split_name("//", _, _) failed.
dir__dirname("//") = "\".
dir__basename("//") = _ failed.
dir__path_name_is_absolute("//").
dir__path_name_is_root_directory("//").

dir__split_name("foo/bar", "foo", "bar").
""foo"/"bar"  = "foo\bar".
dir__dirname("foo/bar") = "foo".
dir__basename("foo/bar") = "bar".
dir__path_name_is_absolute("foo/bar") failed
dir__path_name_is_root_directory("foo/bar") failed

"C:"/"foo"  = "C:foo".
"C:\"/"foo"  = "C:\foo".
"C:"/"C:" threw exception: software_error("dir./: second argument is a current drive relative path")
"C:"/"C:\foo" threw exception: software_error("dir./: second argument is absolute")
"."/"/foo" threw exception: software_error("dir./: second argument is absolute")
"."/"\foo" threw exception: software_error("dir./: second argument is absolute")
"foo"/"bar/baz"  = "foo\bar\baz".
"foo/"/"bar/baz"  = "foo\bar\baz".
checking whether `unwritable' is readable...ok
unwritable file found to be unwritable
make_directory succeeded
make_directory succeeded
dir.make_single_directory with non-existent parent failed as expected.
make_single_directory succeeded
make_single_directory 2 succeeded
file_type succeeded
type of test_dir\d1 is directory
file_type 2 succeeded
type of dir_test.m is regular_file
touching file succeeded
touching file succeeded
touching file succeeded
touching file succeeded
creating directory with same name as ordinary file failed (as expected).
symlinks not available on this platform
dir__foldl2 succeeded
Files in test_dir:
test_dir\d1, test_dir\d2, test_dir\quark, test_dir\queeg
dir__recursive_foldl2 (no symlinks) succeeded
Files in test_dir (recursive, not following symlinks):
test_dir\d1, test_dir\d1\foo, test_dir\d1\baz, test_dir\d2, test_dir\d2\d2, test_dir\quark, test_dir\queeg
dir__recursive_foldl2 (symlinks) succeeded
Files in test_dir (recursive, following symlinks:
test_dir\d1, test_dir\d1\foo, test_dir\d1\baz, test_dir\d2, test_dir\d2\d2, test_dir\quark, test_dir\queeg
dir.recursive_foldl2(list_files, "dir_test.m", ...) failed as expected.

tests/hard_coded/dir_test.exp2:
==============================
Directory separator is '/'.
dir__split_name("\\server\share\foo", _, _) failed.
dir__dirname("\\server\share\foo") = ".".
dir__basename("\\server\share\foo") = "\\server\share\foo".
dir__path_name_is_absolute("\\server\share\foo") failed
dir__path_name_is_root_directory("\\server\share\foo") failed

dir__split_name("\\server\share", _, _) failed.
dir__dirname("\\server\share") = ".".
dir__basename("\\server\share") = "\\server\share".
dir__path_name_is_absolute("\\server\share") failed
dir__path_name_is_root_directory("\\server\share") failed

dir__split_name("\\server\share\\", _, _) failed.
dir__dirname("\\server\share\\") = ".".
dir__basename("\\server\share\\") = "\\server\share\\".
dir__path_name_is_absolute("\\server\share\\") failed
dir__path_name_is_root_directory("\\server\share\\") failed

dir__split_name("C:\foo", _, _) failed.
dir__dirname("C:\foo") = ".".
dir__basename("C:\foo") = "C:\foo".
dir__path_name_is_absolute("C:\foo") failed
dir__path_name_is_root_directory("C:\foo") failed

dir__split_name("C:\foo\", _, _) failed.
dir__dirname("C:\foo\") = ".".
dir__basename("C:\foo\") = "C:\foo\".
dir__path_name_is_absolute("C:\foo\") failed
dir__path_name_is_root_directory("C:\foo\") failed

dir__split_name("C:\", _, _) failed.
dir__dirname("C:\") = ".".
dir__basename("C:\") = "C:\".
dir__path_name_is_absolute("C:\") failed
dir__path_name_is_root_directory("C:\") failed

dir__split_name("C:", _, _) failed.
dir__dirname("C:") = ".".
dir__basename("C:") = "C:".
dir__path_name_is_absolute("C:") failed
dir__path_name_is_root_directory("C:") failed

dir__split_name("\", _, _) failed.
dir__dirname("\") = ".".
dir__basename("\") = "\".
dir__path_name_is_absolute("\") failed
dir__path_name_is_root_directory("\") failed

dir__split_name("", _, _) failed.
dir__dirname("") = ".".
dir__basename("") = "".
dir__path_name_is_absolute("") failed
dir__path_name_is_root_directory("") failed

dir__split_name("foo\\bar\", _, _) failed.
dir__dirname("foo\\bar\") = ".".
dir__basename("foo\\bar\") = "foo\\bar\".
dir__path_name_is_absolute("foo\\bar\") failed
dir__path_name_is_root_directory("foo\\bar\") failed

dir__split_name("foo\bar\", _, _) failed.
dir__dirname("foo\bar\") = ".".
dir__basename("foo\bar\") = "foo\bar\".
dir__path_name_is_absolute("foo\bar\") failed
dir__path_name_is_root_directory("foo\bar\") failed

dir__split_name("foo", _, _) failed.
dir__dirname("foo") = ".".
dir__basename("foo") = "foo".
dir__path_name_is_absolute("foo") failed
dir__path_name_is_root_directory("foo") failed

dir__split_name("/foo", "/", "foo").
"/"/"foo"  = "/foo".
dir__dirname("/foo") = "/".
dir__basename("/foo") = "foo".
dir__path_name_is_absolute("/foo").
dir__path_name_is_root_directory("/foo") failed

dir__split_name("/foo//bar///", "/foo", "bar").
"/foo"/"bar"  = "/foo/bar".
dir__dirname("/foo//bar///") = "/foo".
dir__basename("/foo//bar///") = "bar".
dir__path_name_is_absolute("/foo//bar///").
dir__path_name_is_root_directory("/foo//bar///") failed

dir__split_name("//foo//bar/", "/foo", "bar").
"/foo"/"bar"  = "/foo/bar".
dir__dirname("//foo//bar/") = "/foo".
dir__basename("//foo//bar/") = "bar".
dir__path_name_is_absolute("//foo//bar/").
dir__path_name_is_root_directory("//foo//bar/") failed

dir__split_name("//foo//", "/", "foo").
"/"/"foo"  = "/foo".
dir__dirname("//foo//") = "/".
dir__basename("//foo//") = "foo".
dir__path_name_is_absolute("//foo//").
dir__path_name_is_root_directory("//foo//") failed

dir__split_name("/", _, _) failed.
dir__dirname("/") = "/".
dir__basename("/") = _ failed.
dir__path_name_is_absolute("/").
dir__path_name_is_root_directory("/").

dir__split_name("//", _, _) failed.
dir__dirname("//") = "/".
dir__basename("//") = _ failed.
dir__path_name_is_absolute("//").
dir__path_name_is_root_directory("//").

dir__split_name("foo/bar", "foo", "bar").
"foo"/"bar"  = "foo/bar".
dir__dirname("foo/bar") = "foo".
dir__basename("foo/bar") = "bar".
dir__path_name_is_absolute("foo/bar") failed
dir__path_name_is_root_directory("foo/bar") failed

C:"/"foo"  = "C:/foo".
C:\"/"foo"  = "C:\/foo".
C:"/"C:"  = "C:/C:".
C:"/"C:\foo"  = "C:/C:\foo".
."/"/foo" threw exception: software_error("dir./: second argument is absolute")
."/"\foo"  = "./\foo".
foo"/"bar/baz"  = "foo/bar/baz".
foo/"/"bar/baz"  = "foo/bar/baz".
checking whether `unwritable' is readable...ok
unwritable file found to be unwritable
make_directory succeeded
make_directory succeeded
dir.make_single_directory with non-existent parent failed as expected.
make_single_directory succeeded
make_single_directory 2 succeeded
file_type succeeded
type of test_dir/d1 is directory
file_type 2 succeeded
type of dir_test.m is regular_file
touching file succeeded
touching file succeeded
touching file succeeded
touching file succeeded
creating directory with same name as ordinary file failed (as expected).
making symlink 1 succeeded
making symlink 2 succeeded
making symlink 3 succeeded
following symlink succeeded
test_dir/d1/bar points to baz
file_type 3 succeeded
type of test_dir/d1/bar is symbolic_link
dir__foldl2 succeeded
Files in test_dir:
test_dir/d1, test_dir/d2, test_dir/d3, test_dir/quark, test_dir/queeg
dir__recursive_foldl2 (no symlinks) succeeded
Files in test_dir (recursive, not following symlinks):
test_dir/d1, test_dir/d1/bar, test_dir/d1/baz, test_dir/d1/foo, test_dir/d1/parent, test_dir/d2, test_dir/d2/d2, test_dir/d3, test_dir/quark, test_dir/queeg
dir__recursive_foldl2 (symlinks) succeeded
Files in test_dir (recursive, following symlinks:
test_dir/d1, test_dir/d1/bar, test_dir/d1/baz, test_dir/d1/foo, test_dir/d1/parent, test_dir/d2, test_dir/d2/d2, test_dir/d3, test_dir/d3/bar, test_dir/d3/baz, test_dir/d3/foo, test_dir/d3/parent, test_dir/quark, test_dir/queeg
dir.recursive_foldl2(list_files, "dir_test.m", ...) failed as expected.
--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list