1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT RUN-TIME COMPONENTS                         --
4--                                                                          --
5--                      A D A . D I R E C T O R I E S                       --
6--                                                                          --
7--                                 B o d y                                  --
8--                                                                          --
9--          Copyright (C) 2004-2012, Free Software Foundation, Inc.         --
10--                                                                          --
11-- GNAT is free software;  you can  redistribute it  and/or modify it under --
12-- terms of the  GNU General Public License as published  by the Free Soft- --
13-- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14-- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15-- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16-- or FITNESS FOR A PARTICULAR PURPOSE.                                     --
17--                                                                          --
18-- As a special exception under Section 7 of GPL version 3, you are granted --
19-- additional permissions described in the GCC Runtime Library Exception,   --
20-- version 3.1, as published by the Free Software Foundation.               --
21--                                                                          --
22-- You should have received a copy of the GNU General Public License and    --
23-- a copy of the GCC Runtime Library Exception along with this program;     --
24-- see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see    --
25-- <http://www.gnu.org/licenses/>.                                          --
26--                                                                          --
27-- GNAT was originally developed  by the GNAT team at  New York University. --
28-- Extensive contributions were provided by Ada Core Technologies Inc.      --
29--                                                                          --
30------------------------------------------------------------------------------
31
32with Ada.Calendar;               use Ada.Calendar;
33with Ada.Calendar.Formatting;    use Ada.Calendar.Formatting;
34with Ada.Characters.Handling;    use Ada.Characters.Handling;
35with Ada.Directories.Validity;   use Ada.Directories.Validity;
36with Ada.Strings.Fixed;
37with Ada.Strings.Maps;           use Ada.Strings.Maps;
38with Ada.Strings.Unbounded;      use Ada.Strings.Unbounded;
39with Ada.Unchecked_Conversion;
40with Ada.Unchecked_Deallocation;
41
42with System;              use System;
43with System.CRTL;         use System.CRTL;
44with System.File_IO;      use System.File_IO;
45with System.OS_Constants; use System.OS_Constants;
46with System.OS_Lib;       use System.OS_Lib;
47with System.Regexp;       use System.Regexp;
48
49package body Ada.Directories is
50
51   Filename_Max : constant Integer := 1024;
52   --  1024 is the value of FILENAME_MAX in stdio.h
53
54   type Dir_Type_Value is new Address;
55   --  This is the low-level address directory structure as returned by the C
56   --  opendir routine.
57
58   No_Dir : constant Dir_Type_Value := Dir_Type_Value (Null_Address);
59   --  Null directory value
60
61   Dir_Separator : constant Character;
62   pragma Import (C, Dir_Separator, "__gnat_dir_separator");
63   --  Running system default directory separator
64
65   Dir_Seps : constant Character_Set := Strings.Maps.To_Set ("/\");
66   --  UNIX and DOS style directory separators
67
68   Max_Path : Integer;
69   pragma Import (C, Max_Path, "__gnat_max_path_len");
70   --  The maximum length of a path
71
72   type Search_Data is record
73      Is_Valid      : Boolean := False;
74      Name          : Unbounded_String;
75      Pattern       : Regexp;
76      Filter        : Filter_Type;
77      Dir           : Dir_Type_Value := No_Dir;
78      Entry_Fetched : Boolean := False;
79      Dir_Entry     : Directory_Entry_Type;
80   end record;
81   --  The current state of a search
82
83   Empty_String : constant String := (1 .. 0 => ASCII.NUL);
84   --  Empty string, returned by function Extension when there is no extension
85
86   procedure Free is new Ada.Unchecked_Deallocation (Search_Data, Search_Ptr);
87
88   procedure Close (Dir : Dir_Type_Value);
89
90   function File_Exists (Name : String) return Boolean;
91   --  Returns True if the named file exists
92
93   procedure Fetch_Next_Entry (Search : Search_Type);
94   --  Get the next entry in a directory, setting Entry_Fetched if successful
95   --  or resetting Is_Valid if not.
96
97   ---------------
98   -- Base_Name --
99   ---------------
100
101   function Base_Name (Name : String) return String is
102      Simple : constant String := Simple_Name (Name);
103      --  Simple'First is guaranteed to be 1
104
105   begin
106      --  Look for the last dot in the file name and return the part of the
107      --  file name preceding this last dot. If the first dot is the first
108      --  character of the file name, the base name is the empty string.
109
110      for Pos in reverse Simple'Range loop
111         if Simple (Pos) = '.' then
112            return Simple (1 .. Pos - 1);
113         end if;
114      end loop;
115
116      --  If there is no dot, return the complete file name
117
118      return Simple;
119   end Base_Name;
120
121   -----------
122   -- Close --
123   -----------
124
125   procedure Close (Dir : Dir_Type_Value) is
126      Discard : Integer;
127      pragma Warnings (Off, Discard);
128
129      function closedir (directory : DIRs) return Integer;
130      pragma Import (C, closedir, "__gnat_closedir");
131
132   begin
133      Discard := closedir (DIRs (Dir));
134   end Close;
135
136   -------------
137   -- Compose --
138   -------------
139
140   function Compose
141     (Containing_Directory : String := "";
142      Name                 : String;
143      Extension            : String := "") return String
144   is
145      Result : String (1 .. Containing_Directory'Length +
146                              Name'Length + Extension'Length + 2);
147      Last   : Natural;
148
149   begin
150      --  First, deal with the invalid cases
151
152      if Containing_Directory /= ""
153        and then not Is_Valid_Path_Name (Containing_Directory)
154      then
155         raise Name_Error with
156           "invalid directory path name """ & Containing_Directory & '"';
157
158      elsif
159        Extension'Length = 0 and then (not Is_Valid_Simple_Name (Name))
160      then
161         raise Name_Error with
162           "invalid simple name """ & Name & '"';
163
164      elsif Extension'Length /= 0
165        and then not Is_Valid_Simple_Name (Name & '.' & Extension)
166      then
167         raise Name_Error with
168           "invalid file name """ & Name & '.' & Extension & '"';
169
170      --  This is not an invalid case so build the path name
171
172      else
173         Last := Containing_Directory'Length;
174         Result (1 .. Last) := Containing_Directory;
175
176         --  Add a directory separator if needed
177
178         if Last /= 0 and then not Is_In (Result (Last), Dir_Seps) then
179            Last := Last + 1;
180            Result (Last) := Dir_Separator;
181         end if;
182
183         --  Add the file name
184
185         Result (Last + 1 .. Last + Name'Length) := Name;
186         Last := Last + Name'Length;
187
188         --  If extension was specified, add dot followed by this extension
189
190         if Extension'Length /= 0 then
191            Last := Last + 1;
192            Result (Last) := '.';
193            Result (Last + 1 .. Last + Extension'Length) := Extension;
194            Last := Last + Extension'Length;
195         end if;
196
197         return Result (1 .. Last);
198      end if;
199   end Compose;
200
201   --------------------------
202   -- Containing_Directory --
203   --------------------------
204
205   function Containing_Directory (Name : String) return String is
206   begin
207      --  First, the invalid case
208
209      if not Is_Valid_Path_Name (Name) then
210         raise Name_Error with "invalid path name """ & Name & '"';
211
212      else
213         declare
214            --  We need to resolve links because of A.16(47), since we must not
215            --  return alternative names for files.
216
217            Norm    : constant String := Normalize_Pathname (Name);
218            Last_DS : constant Natural :=
219              Strings.Fixed.Index (Name, Dir_Seps, Going => Strings.Backward);
220
221         begin
222            if Last_DS = 0 then
223
224               --  There is no directory separator, returns current working
225               --  directory.
226
227               return Current_Directory;
228
229            --  If Name indicates a root directory, raise Use_Error, because
230            --  it has no containing directory.
231
232            elsif Norm = "/"
233              or else
234                (Windows
235                  and then
236                    (Norm = "\"
237                      or else
238                        (Norm'Length = 3
239                          and then Norm (Norm'Last - 1 .. Norm'Last) = ":\"
240                          and then (Norm (Norm'First) in 'a' .. 'z'
241                                     or else
242                                       Norm (Norm'First) in 'A' .. 'Z'))))
243            then
244               raise Use_Error with
245                 "directory """ & Name & """ has no containing directory";
246
247            else
248               declare
249                  Last   : Positive := Last_DS - Name'First + 1;
250                  Result : String (1 .. Last);
251
252               begin
253                  Result := Name (Name'First .. Last_DS);
254
255                  --  Remove any trailing directory separator, except as the
256                  --  first character or the first character following a drive
257                  --  number on Windows.
258
259                  while Last > 1 loop
260                     exit when
261                       Result (Last) /= '/'
262                         and then
263                       Result (Last) /= Directory_Separator;
264
265                     exit when Windows
266                       and then Last = 3
267                       and then Result (2) = ':'
268                       and then
269                         (Result (1) in 'A' .. 'Z'
270                           or else
271                          Result (1) in 'a' .. 'z');
272
273                     Last := Last - 1;
274                  end loop;
275
276                  --  Special case of current directory, identified by "."
277
278                  if Last = 1 and then Result (1) = '.' then
279                     return Current_Directory;
280
281                  --  Special case of "..": the current directory may be a root
282                  --  directory.
283
284                  elsif Last = 2 and then Result (1 .. 2) = ".." then
285                     return Containing_Directory (Current_Directory);
286
287                  else
288                     return Result (1 .. Last);
289                  end if;
290               end;
291            end if;
292         end;
293      end if;
294   end Containing_Directory;
295
296   ---------------
297   -- Copy_File --
298   ---------------
299
300   procedure Copy_File
301     (Source_Name : String;
302      Target_Name : String;
303      Form        : String := "")
304   is
305      Success  : Boolean;
306      Mode     : Copy_Mode := Overwrite;
307      Preserve : Attribute := None;
308
309   begin
310      --  First, the invalid cases
311
312      if not Is_Valid_Path_Name (Source_Name) then
313         raise Name_Error with
314           "invalid source path name """ & Source_Name & '"';
315
316      elsif not Is_Valid_Path_Name (Target_Name) then
317         raise Name_Error with
318           "invalid target path name """ & Target_Name & '"';
319
320      elsif not Is_Regular_File (Source_Name) then
321         raise Name_Error with '"' & Source_Name & """ is not a file";
322
323      elsif Is_Directory (Target_Name) then
324         raise Use_Error with "target """ & Target_Name & """ is a directory";
325
326      else
327         if Form'Length > 0 then
328            declare
329               Formstr : String (1 .. Form'Length + 1);
330               V1, V2  : Natural;
331
332            begin
333               --  Acquire form string, setting required NUL terminator
334
335               Formstr (1 .. Form'Length) := Form;
336               Formstr (Formstr'Last) := ASCII.NUL;
337
338               --  Convert form string to lower case
339
340               for J in Formstr'Range loop
341                  if Formstr (J) in 'A' .. 'Z' then
342                     Formstr (J) :=
343                       Character'Val (Character'Pos (Formstr (J)) + 32);
344                  end if;
345               end loop;
346
347               --  Check Form
348
349               Form_Parameter (Formstr, "mode", V1, V2);
350
351               if V1 = 0 then
352                  Mode := Overwrite;
353               elsif Formstr (V1 .. V2) = "copy" then
354                  Mode := Copy;
355               elsif Formstr (V1 .. V2) = "overwrite" then
356                  Mode := Overwrite;
357               elsif Formstr (V1 .. V2) = "append" then
358                  Mode := Append;
359               else
360                  raise Use_Error with "invalid Form";
361               end if;
362
363               Form_Parameter (Formstr, "preserve", V1, V2);
364
365               if V1 = 0 then
366                  Preserve := None;
367               elsif Formstr (V1 .. V2) = "timestamps" then
368                  Preserve := Time_Stamps;
369               elsif Formstr (V1 .. V2) = "all_attributes" then
370                  Preserve := Full;
371               elsif Formstr (V1 .. V2) = "no_attributes" then
372                  Preserve := None;
373               else
374                  raise Use_Error with "invalid Form";
375               end if;
376            end;
377         end if;
378
379         --  Do actual copy using System.OS_Lib.Copy_File
380
381         Copy_File (Source_Name, Target_Name, Success, Mode, Preserve);
382
383         if not Success then
384            raise Use_Error with "copy of """ & Source_Name & """ failed";
385         end if;
386      end if;
387   end Copy_File;
388
389   ----------------------
390   -- Create_Directory --
391   ----------------------
392
393   procedure Create_Directory
394     (New_Directory : String;
395      Form          : String := "")
396   is
397      C_Dir_Name : constant String := New_Directory & ASCII.NUL;
398
399   begin
400      --  First, the invalid case
401
402      if not Is_Valid_Path_Name (New_Directory) then
403         raise Name_Error with
404           "invalid new directory path name """ & New_Directory & '"';
405
406      else
407         --  Acquire setting of encoding parameter
408
409         declare
410            Formstr : constant String := To_Lower (Form);
411
412            Encoding : CRTL.Filename_Encoding;
413            --  Filename encoding specified into the form parameter
414
415            V1, V2 : Natural;
416
417         begin
418            Form_Parameter (Formstr, "encoding", V1, V2);
419
420            if V1 = 0 then
421               Encoding := CRTL.Unspecified;
422            elsif Formstr (V1 .. V2) = "utf8" then
423               Encoding := CRTL.UTF8;
424            elsif Formstr (V1 .. V2) = "8bits" then
425               Encoding := CRTL.ASCII_8bits;
426            else
427               raise Use_Error with "invalid Form";
428            end if;
429
430            if CRTL.mkdir (C_Dir_Name, Encoding) /= 0 then
431               raise Use_Error with
432                 "creation of new directory """ & New_Directory & """ failed";
433            end if;
434         end;
435      end if;
436   end Create_Directory;
437
438   -----------------
439   -- Create_Path --
440   -----------------
441
442   procedure Create_Path
443     (New_Directory : String;
444      Form          : String := "")
445   is
446      New_Dir : String (1 .. New_Directory'Length + 1);
447      Last    : Positive := 1;
448      Start   : Positive := 1;
449
450   begin
451      --  First, the invalid case
452
453      if not Is_Valid_Path_Name (New_Directory) then
454         raise Name_Error with
455           "invalid new directory path name """ & New_Directory & '"';
456
457      else
458         --  Build New_Dir with a directory separator at the end, so that the
459         --  complete path will be found in the loop below.
460
461         New_Dir (1 .. New_Directory'Length) := New_Directory;
462         New_Dir (New_Dir'Last) := Directory_Separator;
463
464         --  If host is windows, and the first two characters are directory
465         --  separators, we have an UNC path. Skip it.
466
467         if Directory_Separator = '\'
468           and then New_Dir'Length > 2
469           and then Is_In (New_Dir (1), Dir_Seps)
470           and then Is_In (New_Dir (2), Dir_Seps)
471         then
472            Start := 2;
473            loop
474               Start := Start + 1;
475               exit when Start = New_Dir'Last
476                 or else Is_In (New_Dir (Start), Dir_Seps);
477            end loop;
478         end if;
479
480         --  Create, if necessary, each directory in the path
481
482         for J in Start + 1 .. New_Dir'Last loop
483
484            --  Look for the end of an intermediate directory
485
486            if not Is_In (New_Dir (J), Dir_Seps) then
487               Last := J;
488
489            --  We have found a new intermediate directory each time we find
490            --  a first directory separator.
491
492            elsif not Is_In (New_Dir (J - 1), Dir_Seps) then
493
494               --  No need to create the directory if it already exists
495
496               if Is_Directory (New_Dir (1 .. Last)) then
497                  null;
498
499               --  It is an error if a file with such a name already exists
500
501               elsif Is_Regular_File (New_Dir (1 .. Last)) then
502                  raise Use_Error with
503                    "file """ & New_Dir (1 .. Last) & """ already exists";
504
505               else
506                  Create_Directory
507                    (New_Directory => New_Dir (1 .. Last), Form => Form);
508               end if;
509            end if;
510         end loop;
511      end if;
512   end Create_Path;
513
514   -----------------------
515   -- Current_Directory --
516   -----------------------
517
518   function Current_Directory return String is
519      Path_Len : Natural := Max_Path;
520      Buffer   : String (1 .. 1 + Max_Path + 1);
521
522      procedure Local_Get_Current_Dir (Dir : Address; Length : Address);
523      pragma Import (C, Local_Get_Current_Dir, "__gnat_get_current_dir");
524
525   begin
526      Local_Get_Current_Dir (Buffer'Address, Path_Len'Address);
527
528      --  We need to resolve links because of RM A.16(47), which requires
529      --  that we not return alternative names for files.
530
531      return Normalize_Pathname (Buffer (1 .. Path_Len));
532   end Current_Directory;
533
534   ----------------------
535   -- Delete_Directory --
536   ----------------------
537
538   procedure Delete_Directory (Directory : String) is
539   begin
540      --  First, the invalid cases
541
542      if not Is_Valid_Path_Name (Directory) then
543         raise Name_Error with
544           "invalid directory path name """ & Directory & '"';
545
546      elsif not Is_Directory (Directory) then
547         raise Name_Error with '"' & Directory & """ not a directory";
548
549      --  Do the deletion, checking for error
550
551      else
552         declare
553            C_Dir_Name : constant String := Directory & ASCII.NUL;
554         begin
555            if rmdir (C_Dir_Name) /= 0 then
556               raise Use_Error with
557                 "deletion of directory """ & Directory & """ failed";
558            end if;
559         end;
560      end if;
561   end Delete_Directory;
562
563   -----------------
564   -- Delete_File --
565   -----------------
566
567   procedure Delete_File (Name : String) is
568      Success : Boolean;
569
570   begin
571      --  First, the invalid cases
572
573      if not Is_Valid_Path_Name (Name) then
574         raise Name_Error with "invalid path name """ & Name & '"';
575
576      elsif not Is_Regular_File (Name)
577        and then not Is_Symbolic_Link (Name)
578      then
579         raise Name_Error with "file """ & Name & """ does not exist";
580
581      else
582         --  Do actual deletion using System.OS_Lib.Delete_File
583
584         Delete_File (Name, Success);
585
586         if not Success then
587            raise Use_Error with "file """ & Name & """ could not be deleted";
588         end if;
589      end if;
590   end Delete_File;
591
592   -----------------
593   -- Delete_Tree --
594   -----------------
595
596   procedure Delete_Tree (Directory : String) is
597      Current_Dir : constant String := Current_Directory;
598      Search      : Search_Type;
599      Dir_Ent     : Directory_Entry_Type;
600   begin
601      --  First, the invalid cases
602
603      if not Is_Valid_Path_Name (Directory) then
604         raise Name_Error with
605           "invalid directory path name """ & Directory & '"';
606
607      elsif not Is_Directory (Directory) then
608         raise Name_Error with '"' & Directory & """ not a directory";
609
610      else
611         Set_Directory (Directory);
612
613         Start_Search (Search, Directory => ".", Pattern => "");
614         while More_Entries (Search) loop
615            Get_Next_Entry (Search, Dir_Ent);
616
617            declare
618               File_Name : constant String := Simple_Name (Dir_Ent);
619
620            begin
621               if OS_Lib.Is_Directory (File_Name) then
622                  if File_Name /= "." and then File_Name /= ".." then
623                     Delete_Tree (File_Name);
624                  end if;
625
626               else
627                  Delete_File (File_Name);
628               end if;
629            end;
630         end loop;
631
632         Set_Directory (Current_Dir);
633         End_Search (Search);
634
635         declare
636            C_Dir_Name : constant String := Directory & ASCII.NUL;
637
638         begin
639            if rmdir (C_Dir_Name) /= 0 then
640               raise Use_Error with
641                 "directory tree rooted at """ &
642                   Directory & """ could not be deleted";
643            end if;
644         end;
645      end if;
646   end Delete_Tree;
647
648   ------------
649   -- Exists --
650   ------------
651
652   function Exists (Name : String) return Boolean is
653   begin
654      --  First, the invalid case
655
656      if not Is_Valid_Path_Name (Name) then
657         raise Name_Error with "invalid path name """ & Name & '"';
658
659      else
660         --  The implementation is in File_Exists
661
662         return File_Exists (Name);
663      end if;
664   end Exists;
665
666   ---------------
667   -- Extension --
668   ---------------
669
670   function Extension (Name : String) return String is
671   begin
672      --  First, the invalid case
673
674      if not Is_Valid_Path_Name (Name) then
675         raise Name_Error with "invalid path name """ & Name & '"';
676
677      else
678         --  Look for first dot that is not followed by a directory separator
679
680         for Pos in reverse Name'Range loop
681
682            --  If a directory separator is found before a dot, there is no
683            --  extension.
684
685            if Is_In (Name (Pos), Dir_Seps) then
686               return Empty_String;
687
688            elsif Name (Pos) = '.' then
689
690               --  We found a dot, build the return value with lower bound 1
691
692               declare
693                  subtype Result_Type is String (1 .. Name'Last - Pos);
694               begin
695                  return Result_Type (Name (Pos + 1 .. Name'Last));
696               end;
697            end if;
698         end loop;
699
700         --  No dot were found, there is no extension
701
702         return Empty_String;
703      end if;
704   end Extension;
705
706   ----------------------
707   -- Fetch_Next_Entry --
708   ----------------------
709
710   procedure Fetch_Next_Entry (Search : Search_Type) is
711      Name : String (1 .. 255);
712      Last : Natural;
713
714      Kind : File_Kind := Ordinary_File;
715      --  Initialized to avoid a compilation warning
716
717      Filename_Addr : Address;
718      Filename_Len  : aliased Integer;
719
720      Buffer : array (0 .. Filename_Max + 12) of Character;
721      --  12 is the size of the dirent structure (see dirent.h), without the
722      --  field for the filename.
723
724      function readdir_gnat
725        (Directory : Address;
726         Buffer    : Address;
727         Last      : not null access Integer) return Address;
728      pragma Import (C, readdir_gnat, "__gnat_readdir");
729
730   begin
731      --  Search.Value.Is_Valid is always True when Fetch_Next_Entry is called
732
733      loop
734         Filename_Addr :=
735           readdir_gnat
736             (Address (Search.Value.Dir),
737              Buffer'Address,
738              Filename_Len'Access);
739
740         --  If no matching entry is found, set Is_Valid to False
741
742         if Filename_Addr = Null_Address then
743            Search.Value.Is_Valid := False;
744            exit;
745         end if;
746
747         declare
748            subtype Path_String is String (1 .. Filename_Len);
749            type    Path_String_Access is access Path_String;
750
751            function Address_To_Access is new
752              Ada.Unchecked_Conversion
753                (Source => Address,
754                 Target => Path_String_Access);
755
756            Path_Access : constant Path_String_Access :=
757              Address_To_Access (Filename_Addr);
758
759         begin
760            Last := Filename_Len;
761            Name (1 .. Last) := Path_Access.all;
762         end;
763
764         --  Check if the entry matches the pattern
765
766         if Match (Name (1 .. Last), Search.Value.Pattern) then
767            declare
768               Full_Name : constant String :=
769                 Compose (To_String (Search.Value.Name), Name (1 .. Last));
770               Found     : Boolean := False;
771
772            begin
773               if File_Exists (Full_Name) then
774
775                  --  Now check if the file kind matches the filter
776
777                  if Is_Regular_File (Full_Name) then
778                     if Search.Value.Filter (Ordinary_File) then
779                        Kind := Ordinary_File;
780                        Found := True;
781                     end if;
782
783                  elsif Is_Directory (Full_Name) then
784                     if Search.Value.Filter (Directory) then
785                        Kind := Directory;
786                        Found := True;
787                     end if;
788
789                  elsif Search.Value.Filter (Special_File) then
790                     Kind := Special_File;
791                     Found := True;
792                  end if;
793
794                  --  If it does, update Search and return
795
796                  if Found then
797                     Search.Value.Entry_Fetched := True;
798                     Search.Value.Dir_Entry :=
799                       (Is_Valid => True,
800                        Simple   => To_Unbounded_String (Name (1 .. Last)),
801                        Full     => To_Unbounded_String (Full_Name),
802                        Kind     => Kind);
803                     exit;
804                  end if;
805               end if;
806            end;
807         end if;
808      end loop;
809   end Fetch_Next_Entry;
810
811   -----------------
812   -- File_Exists --
813   -----------------
814
815   function File_Exists (Name : String) return Boolean is
816      function C_File_Exists (A : Address) return Integer;
817      pragma Import (C, C_File_Exists, "__gnat_file_exists");
818
819      C_Name : String (1 .. Name'Length + 1);
820
821   begin
822      C_Name (1 .. Name'Length) := Name;
823      C_Name (C_Name'Last) := ASCII.NUL;
824      return C_File_Exists (C_Name (1)'Address) = 1;
825   end File_Exists;
826
827   --------------
828   -- Finalize --
829   --------------
830
831   procedure Finalize (Search : in out Search_Type) is
832   begin
833      if Search.Value /= null then
834
835         --  Close the directory, if one is open
836
837         if Search.Value.Dir /= No_Dir then
838            Close (Search.Value.Dir);
839         end if;
840
841         Free (Search.Value);
842      end if;
843   end Finalize;
844
845   ---------------
846   -- Full_Name --
847   ---------------
848
849   function Full_Name (Name : String) return String is
850   begin
851      --  First, the invalid case
852
853      if not Is_Valid_Path_Name (Name) then
854         raise Name_Error with "invalid path name """ & Name & '"';
855
856      else
857         --  Build the return value with lower bound 1
858
859         --  Use System.OS_Lib.Normalize_Pathname
860
861         declare
862            --  We need to resolve links because of (RM A.16(47)), which says
863            --  we must not return alternative names for files.
864
865            Value : constant String := Normalize_Pathname (Name);
866            subtype Result is String (1 .. Value'Length);
867
868         begin
869            return Result (Value);
870         end;
871      end if;
872   end Full_Name;
873
874   function Full_Name (Directory_Entry : Directory_Entry_Type) return String is
875   begin
876      --  First, the invalid case
877
878      if not Directory_Entry.Is_Valid then
879         raise Status_Error with "invalid directory entry";
880
881      else
882         --  The value to return has already been computed
883
884         return To_String (Directory_Entry.Full);
885      end if;
886   end Full_Name;
887
888   --------------------
889   -- Get_Next_Entry --
890   --------------------
891
892   procedure Get_Next_Entry
893     (Search          : in out Search_Type;
894      Directory_Entry : out Directory_Entry_Type)
895   is
896   begin
897      --  First, the invalid case
898
899      if Search.Value = null or else not Search.Value.Is_Valid then
900         raise Status_Error with "invalid search";
901      end if;
902
903      --  Fetch the next entry, if needed
904
905      if not Search.Value.Entry_Fetched then
906         Fetch_Next_Entry (Search);
907      end if;
908
909      --  It is an error if no valid entry is found
910
911      if not Search.Value.Is_Valid then
912         raise Status_Error with "no next entry";
913
914      else
915         --  Reset Entry_Fetched and return the entry
916
917         Search.Value.Entry_Fetched := False;
918         Directory_Entry := Search.Value.Dir_Entry;
919      end if;
920   end Get_Next_Entry;
921
922   ----------
923   -- Kind --
924   ----------
925
926   function Kind (Name : String) return File_Kind is
927   begin
928      --  First, the invalid case
929
930      if not File_Exists (Name) then
931         raise Name_Error with "file """ & Name & """ does not exist";
932
933      --  If OK, return appropriate kind
934
935      elsif Is_Regular_File (Name) then
936         return Ordinary_File;
937
938      elsif Is_Directory (Name) then
939         return Directory;
940
941      else
942         return Special_File;
943      end if;
944   end Kind;
945
946   function Kind (Directory_Entry : Directory_Entry_Type) return File_Kind is
947   begin
948      --  First, the invalid case
949
950      if not Directory_Entry.Is_Valid then
951         raise Status_Error with "invalid directory entry";
952
953      else
954         --  The value to return has already be computed
955
956         return Directory_Entry.Kind;
957      end if;
958   end Kind;
959
960   -----------------------
961   -- Modification_Time --
962   -----------------------
963
964   function Modification_Time (Name : String) return Time is
965      Date   : OS_Time;
966      Year   : Year_Type;
967      Month  : Month_Type;
968      Day    : Day_Type;
969      Hour   : Hour_Type;
970      Minute : Minute_Type;
971      Second : Second_Type;
972      Result : Time;
973
974   begin
975      --  First, the invalid cases
976
977      if not (Is_Regular_File (Name) or else Is_Directory (Name)) then
978         raise Name_Error with '"' & Name & """ not a file or directory";
979
980      else
981         Date := File_Time_Stamp (Name);
982
983         --  Break down the time stamp into its constituents relative to GMT.
984         --  This version of Split does not recognize leap seconds or buffer
985         --  space for time zone processing.
986
987         GM_Split (Date, Year, Month, Day, Hour, Minute, Second);
988
989         --  On OpenVMS, the resulting time value must be in the local time
990         --  zone. Ada.Calendar.Time_Of is exactly what we need. Note that
991         --  in both cases, the sub seconds are set to zero (0.0) because the
992         --  time stamp does not store them in its value.
993
994         if OpenVMS then
995            Result :=
996              Ada.Calendar.Time_Of
997                (Year, Month, Day, Seconds_Of (Hour, Minute, Second, 0.0));
998
999         --  On Unix and Windows, the result must be in GMT. Ada.Calendar.
1000         --  Formatting.Time_Of with default time zone of zero (0) is the
1001         --  routine of choice.
1002
1003         else
1004            Result := Time_Of (Year, Month, Day, Hour, Minute, Second, 0.0);
1005         end if;
1006
1007         return Result;
1008      end if;
1009   end Modification_Time;
1010
1011   function Modification_Time
1012     (Directory_Entry : Directory_Entry_Type) return Ada.Calendar.Time
1013   is
1014   begin
1015      --  First, the invalid case
1016
1017      if not Directory_Entry.Is_Valid then
1018         raise Status_Error with "invalid directory entry";
1019
1020      else
1021         --  The value to return has already be computed
1022
1023         return Modification_Time (To_String (Directory_Entry.Full));
1024      end if;
1025   end Modification_Time;
1026
1027   ------------------
1028   -- More_Entries --
1029   ------------------
1030
1031   function More_Entries (Search : Search_Type) return Boolean is
1032   begin
1033      if Search.Value = null then
1034         return False;
1035
1036      elsif Search.Value.Is_Valid then
1037
1038         --  Fetch the next entry, if needed
1039
1040         if not Search.Value.Entry_Fetched then
1041            Fetch_Next_Entry (Search);
1042         end if;
1043      end if;
1044
1045      return Search.Value.Is_Valid;
1046   end More_Entries;
1047
1048   ------------
1049   -- Rename --
1050   ------------
1051
1052   procedure Rename (Old_Name, New_Name : String) is
1053      Success : Boolean;
1054
1055   begin
1056      --  First, the invalid cases
1057
1058      if not Is_Valid_Path_Name (Old_Name) then
1059         raise Name_Error with "invalid old path name """ & Old_Name & '"';
1060
1061      elsif not Is_Valid_Path_Name (New_Name) then
1062         raise Name_Error with "invalid new path name """ & New_Name & '"';
1063
1064      elsif not Is_Regular_File (Old_Name)
1065            and then not Is_Directory (Old_Name)
1066      then
1067         raise Name_Error with "old file """ & Old_Name & """ does not exist";
1068
1069      elsif Is_Regular_File (New_Name) or else Is_Directory (New_Name) then
1070         raise Use_Error with
1071           "new name """ & New_Name
1072           & """ designates a file that already exists";
1073
1074      --  Do actual rename using System.OS_Lib.Rename_File
1075
1076      else
1077         Rename_File (Old_Name, New_Name, Success);
1078
1079         if not Success then
1080
1081            --  AI05-0231-1: Name_Error should be raised in case a directory
1082            --  component of New_Name does not exist (as in New_Name =>
1083            --  "/no-such-dir/new-filename"). ENOENT indicates that. ENOENT
1084            --  also indicate that the Old_Name does not exist, but we already
1085            --  checked for that above. All other errors are Use_Error.
1086
1087            if Errno = ENOENT then
1088               raise Name_Error with
1089                 "file """ & Containing_Directory (New_Name) & """ not found";
1090
1091            else
1092               raise Use_Error with
1093                 "file """ & Old_Name & """ could not be renamed";
1094            end if;
1095         end if;
1096      end if;
1097   end Rename;
1098
1099   ------------
1100   -- Search --
1101   ------------
1102
1103   procedure Search
1104     (Directory : String;
1105      Pattern   : String;
1106      Filter    : Filter_Type := (others => True);
1107      Process   : not null access procedure
1108                                    (Directory_Entry : Directory_Entry_Type))
1109   is
1110      Srch            : Search_Type;
1111      Directory_Entry : Directory_Entry_Type;
1112
1113   begin
1114      Start_Search (Srch, Directory, Pattern, Filter);
1115      while More_Entries (Srch) loop
1116         Get_Next_Entry (Srch, Directory_Entry);
1117         Process (Directory_Entry);
1118      end loop;
1119
1120      End_Search (Srch);
1121   end Search;
1122
1123   -------------------
1124   -- Set_Directory --
1125   -------------------
1126
1127   procedure Set_Directory (Directory : String) is
1128      C_Dir_Name : constant String := Directory & ASCII.NUL;
1129   begin
1130      if not Is_Valid_Path_Name (Directory) then
1131         raise Name_Error with
1132           "invalid directory path name & """ & Directory & '"';
1133
1134      elsif not Is_Directory (Directory) then
1135         raise Name_Error with
1136           "directory """ & Directory & """ does not exist";
1137
1138      elsif chdir (C_Dir_Name) /= 0 then
1139         raise Name_Error with
1140           "could not set to designated directory """ & Directory & '"';
1141      end if;
1142   end Set_Directory;
1143
1144   -----------------
1145   -- Simple_Name --
1146   -----------------
1147
1148   function Simple_Name (Name : String) return String is
1149
1150      function Simple_Name_Internal (Path : String) return String;
1151      --  This function does the job
1152
1153      --------------------------
1154      -- Simple_Name_Internal --
1155      --------------------------
1156
1157      function Simple_Name_Internal (Path : String) return String is
1158         Cut_Start : Natural :=
1159           Strings.Fixed.Index (Path, Dir_Seps, Going => Strings.Backward);
1160         Cut_End   : Natural;
1161
1162      begin
1163         --  Cut_Start pointS to the first simple name character
1164
1165         Cut_Start := (if Cut_Start = 0 then Path'First else Cut_Start + 1);
1166
1167         --  Cut_End point to the last simple name character
1168
1169         Cut_End := Path'Last;
1170
1171         Check_For_Standard_Dirs : declare
1172            BN : constant String := Path (Cut_Start .. Cut_End);
1173
1174            Has_Drive_Letter : constant Boolean :=
1175              OS_Lib.Path_Separator /= ':';
1176            --  If Path separator is not ':' then we are on a DOS based OS
1177            --  where this character is used as a drive letter separator.
1178
1179         begin
1180            if BN = "." or else BN = ".." then
1181               return "";
1182
1183            elsif Has_Drive_Letter
1184              and then BN'Length > 2
1185              and then Characters.Handling.Is_Letter (BN (BN'First))
1186              and then BN (BN'First + 1) = ':'
1187            then
1188               --  We have a DOS drive letter prefix, remove it
1189
1190               return BN (BN'First + 2 .. BN'Last);
1191
1192            else
1193               return BN;
1194            end if;
1195         end Check_For_Standard_Dirs;
1196      end Simple_Name_Internal;
1197
1198   --  Start of processing for Simple_Name
1199
1200   begin
1201      --  First, the invalid case
1202
1203      if not Is_Valid_Path_Name (Name) then
1204         raise Name_Error with "invalid path name """ & Name & '"';
1205
1206      else
1207         --  Build the value to return with lower bound 1
1208
1209         declare
1210            Value : constant String := Simple_Name_Internal (Name);
1211            subtype Result is String (1 .. Value'Length);
1212         begin
1213            return Result (Value);
1214         end;
1215      end if;
1216   end Simple_Name;
1217
1218   function Simple_Name
1219     (Directory_Entry : Directory_Entry_Type) return String is
1220   begin
1221      --  First, the invalid case
1222
1223      if not Directory_Entry.Is_Valid then
1224         raise Status_Error with "invalid directory entry";
1225
1226      else
1227         --  The value to return has already be computed
1228
1229         return To_String (Directory_Entry.Simple);
1230      end if;
1231   end Simple_Name;
1232
1233   ----------
1234   -- Size --
1235   ----------
1236
1237   function Size (Name : String) return File_Size is
1238      C_Name : String (1 .. Name'Length + 1);
1239
1240      function C_Size (Name : Address) return Long_Integer;
1241      pragma Import (C, C_Size, "__gnat_named_file_length");
1242
1243   begin
1244      --  First, the invalid case
1245
1246      if not Is_Regular_File (Name) then
1247         raise Name_Error with "file """ & Name & """ does not exist";
1248
1249      else
1250         C_Name (1 .. Name'Length) := Name;
1251         C_Name (C_Name'Last) := ASCII.NUL;
1252         return File_Size (C_Size (C_Name'Address));
1253      end if;
1254   end Size;
1255
1256   function Size (Directory_Entry : Directory_Entry_Type) return File_Size is
1257   begin
1258      --  First, the invalid case
1259
1260      if not Directory_Entry.Is_Valid then
1261         raise Status_Error with "invalid directory entry";
1262
1263      else
1264         --  The value to return has already be computed
1265
1266         return Size (To_String (Directory_Entry.Full));
1267      end if;
1268   end Size;
1269
1270   ------------------
1271   -- Start_Search --
1272   ------------------
1273
1274   procedure Start_Search
1275     (Search    : in out Search_Type;
1276      Directory : String;
1277      Pattern   : String;
1278      Filter    : Filter_Type := (others => True))
1279   is
1280      function opendir (file_name : String) return DIRs;
1281      pragma Import (C, opendir, "__gnat_opendir");
1282
1283      C_File_Name : constant String := Directory & ASCII.NUL;
1284      Pat         : Regexp;
1285      Dir         : Dir_Type_Value;
1286
1287   begin
1288      --  First, the invalid case Name_Error
1289
1290      if not Is_Directory (Directory) then
1291         raise Name_Error with
1292           "unknown directory """ & Simple_Name (Directory) & '"';
1293      end if;
1294
1295      --  Check the pattern
1296
1297      begin
1298         Pat := Compile
1299           (Pattern,
1300            Glob           => True,
1301            Case_Sensitive => Is_Path_Name_Case_Sensitive);
1302      exception
1303         when Error_In_Regexp =>
1304            Free (Search.Value);
1305            raise Name_Error with "invalid pattern """ & Pattern & '"';
1306      end;
1307
1308      Dir := Dir_Type_Value (opendir (C_File_Name));
1309
1310      if Dir = No_Dir then
1311         raise Use_Error with
1312           "unreadable directory """ & Simple_Name (Directory) & '"';
1313      end if;
1314
1315      --  If needed, finalize Search
1316
1317      Finalize (Search);
1318
1319      --  Allocate the default data
1320
1321      Search.Value := new Search_Data;
1322
1323      --  Initialize some Search components
1324
1325      Search.Value.Filter   := Filter;
1326      Search.Value.Name     := To_Unbounded_String (Full_Name (Directory));
1327      Search.Value.Pattern  := Pat;
1328      Search.Value.Dir      := Dir;
1329      Search.Value.Is_Valid := True;
1330   end Start_Search;
1331
1332end Ada.Directories;
1333