OSDN Git Service

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