Commit 30681738 by Robert Dewar Committed by Arnaud Charlet

g-string.adb, [...]: Replace GNAT.xxx by System.xxx when appropriate.

2007-04-20  Robert Dewar  <dewar@adacore.com>

	* g-string.adb, s-proinf-irix-athread.adb, s-gloloc-mingw.adb,
	s-tfsetr-default.adb, gnatfind.adb, gnatxref.adb, gprep.adb,
	g-regexp.adb, g-regexp.ads, g-regpat.ads, g-tasloc.adb, g-tasloc.ads,
	output.adb, switch-m.ads, tree_in.ads, tree_io.ads, indepsw.ads,
	g-utf_32.adb, g-utf_32.ads, a-wichun.adb, a-wichun.ads, a-zchuni.adb,
	a-zchuni.ads: Replace GNAT.xxx by System.xxx when appropriate.

	* s-utf_32.adb, s-utf_32.ads, s-os_lib.adb, s-os_lib.ads, s-regexp.adb,
	s-regexp.ads, s-regpat.adb, s-regpat.ads, s-string.adb, s-string.ads,
	s-tasloc.adb, s-tasloc.ads: New files.

From-SVN: r125360
parent cecaf88a
......@@ -6,7 +6,7 @@
-- --
-- B o d y --
-- --
-- Copyright (C) 2005, Free Software Foundation, Inc. --
-- Copyright (C) 2005-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -33,7 +33,7 @@
package body Ada.Wide_Characters.Unicode is
package G renames GNAT.UTF_32;
package G renames System.UTF_32;
------------------
-- Get_Category --
......
......@@ -6,7 +6,7 @@
-- --
-- S p e c --
-- --
-- Copyright (C) 2005, Free Software Foundation, Inc. --
-- Copyright (C) 2005-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -36,7 +36,7 @@
-- Ada 2005 unit), but we make it available in Ada 95 mode, since it
-- only deals with wide characters.
with GNAT.UTF_32;
with System.UTF_32;
package Ada.Wide_Characters.Unicode is
......@@ -44,7 +44,7 @@ package Ada.Wide_Characters.Unicode is
-- The one addition we make is Fe, which represents the characters FFFE
-- and FFFF in any of the planes.
type Category is new GNAT.UTF_32.Category;
type Category is new System.UTF_32.Category;
-- Cc Other, Control
-- Cf Other, Format
-- Cn Other, Not Assigned
......
......@@ -6,7 +6,7 @@
-- --
-- B o d y --
-- --
-- Copyright (C) 2005, Free Software Foundation, Inc. --
-- Copyright (C) 2005-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -33,7 +33,7 @@
package body Ada.Wide_Wide_Characters.Unicode is
package G renames GNAT.UTF_32;
package G renames System.UTF_32;
------------------
-- Get_Category --
......
......@@ -6,7 +6,7 @@
-- --
-- S p e c --
-- --
-- Copyright (C) 2005, Free Software Foundation, Inc. --
-- Copyright (C) 2005-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -33,7 +33,7 @@
-- Unicode categorization routines for Wide_Wide_Character
with GNAT.UTF_32;
with System.UTF_32;
package Ada.Wide_Wide_Characters.Unicode is
......@@ -41,7 +41,7 @@ package Ada.Wide_Wide_Characters.Unicode is
-- The one addition we make is Fe, which represents the characters FFFE
-- and FFFF in any of the planes.
type Category is new GNAT.UTF_32.Category;
type Category is new System.UTF_32.Category;
-- Cc Other, Control
-- Cf Other, Format
-- Cn Other, Not Assigned
......
......@@ -6,7 +6,7 @@
-- --
-- S p e c --
-- --
-- Copyright (C) 1998-2005, AdaCore --
-- Copyright (C) 1998-2007, AdaCore --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -37,6 +37,8 @@
-- pattern matching algorithm, using a subset of the syntax of regular
-- expressions copied from familiar Unix style utilities.
-- See file s-regexp.ads for full documentation of the interface
------------------------------------------------------------
-- Summary of Pattern Matching Packages in GNAT Hierarchy --
------------------------------------------------------------
......@@ -45,14 +47,14 @@
-- the following is an outline of these packages, to help you determine
-- which is best for your needs.
-- GNAT.Regexp (files g-regexp.ads/g-regexp.adb)
-- GNAT.Regexp (files g-regexp.ads/s-regexp.ads/s-regexp.adb)
-- This is a simple package providing Unix-style regular expression
-- matching with the restriction that it matches entire strings. It
-- is particularly useful for file name matching, and in particular
-- it provides "globbing patterns" that are useful in implementing
-- unix or DOS style wild card matching for file names.
-- GNAT.Regpat (files g-regpat.ads/g-regpat.adb)
-- GNAT.Regpat (files g-regpat.ads/s-regpat.ads/g-regpat.adb)
-- This is a more complete implementation of Unix-style regular
-- expressions, copied from the original V7 style regular expression
-- library written in C by Henry Spencer. It is functionally the
......@@ -65,99 +67,6 @@
-- language is modeled on context free grammars, with context sensitive
-- extensions that provide full (type 0) computational capabilities.
with Ada.Finalization;
package GNAT.Regexp is
-- The regular expression must first be compiled, using the Compile
-- function, which creates a finite state matching table, allowing
-- very fast matching once the expression has been compiled.
-- The following is the form of a regular expression, expressed in Ada
-- reference manual style BNF is as follows
-- regexp ::= term
-- regexp ::= term | term -- alternation (term or term ...)
-- term ::= item
-- term ::= item item ... -- concatenation (item then item)
-- item ::= elmt -- match elmt
-- item ::= elmt * -- zero or more elmt's
-- item ::= elmt + -- one or more elmt's
-- item ::= elmt ? -- matches elmt or nothing
-- elmt ::= nchr -- matches given character
-- elmt ::= [nchr nchr ...] -- matches any character listed
-- elmt ::= [^ nchr nchr ...] -- matches any character not listed
-- elmt ::= [char - char] -- matches chars in given range
-- elmt ::= . -- matches any single character
-- elmt ::= ( regexp ) -- parens used for grouping
-- char ::= any character, including special characters
-- nchr ::= any character except \()[].*+?^ or \char to match char
-- ... is used to indication repetition (one or more terms)
-- See also regexp(1) man page on Unix systems for further details
-- A second kind of regular expressions is provided. This one is more
-- like the wild card patterns used in file names by the Unix shell (or
-- DOS prompt) command lines. The grammar is the following:
-- regexp ::= term
-- term ::= elmt
-- term ::= elmt elmt ... -- concatenation (elmt then elmt)
-- term ::= * -- any string of 0 or more characters
-- term ::= ? -- matches any character
-- term ::= [char char ...] -- matches any character listed
-- term ::= [char - char] -- matches any character in given range
-- term ::= {elmt, elmt, ...} -- alternation (matches any of elmt)
-- Important note : This package was mainly intended to match regular
-- expressions against file names. The whole string has to match the
-- regular expression. If only a substring matches, then the function
-- Match will return False.
type Regexp is private;
-- Private type used to represent a regular expression
Error_In_Regexp : exception;
-- Exception raised when an error is found in the regular expression
function Compile
(Pattern : String;
Glob : Boolean := False;
Case_Sensitive : Boolean := True) return Regexp;
-- Compiles a regular expression S. If the syntax of the given
-- expression is invalid (does not match above grammar, Error_In_Regexp
-- is raised. If Glob is True, the pattern is considered as a 'globbing
-- pattern', that is a pattern as given by the second grammar above.
-- As a special case, if Pattern is the empty string it will always
-- match.
function Match (S : String; R : Regexp) return Boolean;
-- True if S matches R, otherwise False. Raises Constraint_Error if
-- R is an uninitialized regular expression value.
private
type Regexp_Value;
type Regexp_Access is access Regexp_Value;
type Regexp is new Ada.Finalization.Controlled with record
R : Regexp_Access := null;
end record;
pragma Finalize_Storage_Only (Regexp);
procedure Finalize (R : in out Regexp);
-- Free the memory occupied by R
procedure Adjust (R : in out Regexp);
-- Called after an assignment (do a copy of the Regexp_Access.all)
with System.Regexp;
end GNAT.Regexp;
package GNAT.Regexp renames System.Regexp;
......@@ -7,7 +7,7 @@
-- S p e c --
-- --
-- Copyright (C) 1986 by University of Toronto. --
-- Copyright (C) 1996-2006, AdaCore --
-- Copyright (C) 1996-2007, AdaCore --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -40,6 +40,8 @@
-- interface has been considerably changed to use the Ada String type
-- instead of C-style nul-terminated strings.
-- See file s-regpat.ads for full documentation of the interface
------------------------------------------------------------
-- Summary of Pattern Matching Packages in GNAT Hierarchy --
------------------------------------------------------------
......@@ -48,14 +50,14 @@
-- the following is an outline of these packages, to help you determine
-- which is best for your needs.
-- GNAT.Regexp (files g-regexp.ads/g-regexp.adb)
-- GNAT.Regexp (files g-regexp.ads/s-regexp.ads/s-regexp.adb)
-- This is a simple package providing Unix-style regular expression
-- matching with the restriction that it matches entire strings. It
-- is particularly useful for file name matching, and in particular
-- it provides "globbing patterns" that are useful in implementing
-- unix or DOS style wild card matching for file names.
-- GNAT.Regpat (files g-regpat.ads/g-regpat.adb)
-- GNAT.Regpat (files g-regpat.ads/s-regpat.ads/s-regpat.adb)
-- This is a more complete implementation of Unix-style regular
-- expressions, copied from the Perl regular expression engine,
-- written originally in C by Henry Spencer. It is functionally the
......@@ -67,591 +69,6 @@
-- language is modeled on context free grammars, with context sensitive
-- extensions that provide full (type 0) computational capabilities.
package GNAT.Regpat is
pragma Preelaborate;
-- The grammar is the following:
-- regexp ::= expr
-- ::= ^ expr -- anchor at the beginning of string
-- ::= expr $ -- anchor at the end of string
-- expr ::= term
-- ::= term | term -- alternation (term or term ...)
-- term ::= item
-- ::= item item ... -- concatenation (item then item)
-- item ::= elmt -- match elmt
-- ::= elmt * -- zero or more elmt's
-- ::= elmt + -- one or more elmt's
-- ::= elmt ? -- matches elmt or nothing
-- ::= elmt *? -- zero or more times, minimum number
-- ::= elmt +? -- one or more times, minimum number
-- ::= elmt ?? -- zero or one time, minimum number
-- ::= elmt { num } -- matches elmt exactly num times
-- ::= elmt { num , } -- matches elmt at least num times
-- ::= elmt { num , num2 } -- matches between num and num2 times
-- ::= elmt { num }? -- matches elmt exactly num times
-- ::= elmt { num , }? -- matches elmt at least num times
-- non-greedy version
-- ::= elmt { num , num2 }? -- matches between num and num2 times
-- non-greedy version
-- elmt ::= nchr -- matches given character
-- ::= [range range ...] -- matches any character listed
-- ::= [^ range range ...] -- matches any character not listed
-- ::= . -- matches any single character
-- -- except newlines
-- ::= ( expr ) -- parens used for grouping
-- ::= \ num -- reference to num-th parenthesis
-- range ::= char - char -- matches chars in given range
-- ::= nchr
-- ::= [: posix :] -- any character in the POSIX range
-- ::= [:^ posix :] -- not in the POSIX range
-- posix ::= alnum -- alphanumeric characters
-- ::= alpha -- alphabetic characters
-- ::= ascii -- ascii characters (0 .. 127)
-- ::= cntrl -- control chars (0..31, 127..159)
-- ::= digit -- digits ('0' .. '9')
-- ::= graph -- graphic chars (32..126, 160..255)
-- ::= lower -- lower case characters
-- ::= print -- printable characters (32..127)
-- ::= punct -- printable, except alphanumeric
-- ::= space -- space characters
-- ::= upper -- upper case characters
-- ::= word -- alphanumeric characters
-- ::= xdigit -- hexadecimal chars (0..9, a..f)
-- char ::= any character, including special characters
-- ASCII.NUL is not supported.
-- nchr ::= any character except \()[].*+?^ or \char to match char
-- \n means a newline (ASCII.LF)
-- \t means a tab (ASCII.HT)
-- \r means a return (ASCII.CR)
-- \b matches the empty string at the beginning or end of a
-- word. A word is defined as a set of alphanumerical
-- characters (see \w below).
-- \B matches the empty string only when *not* at the
-- beginning or end of a word.
-- \d matches any digit character ([0-9])
-- \D matches any non digit character ([^0-9])
-- \s matches any white space character. This is equivalent
-- to [ \t\n\r\f\v] (tab, form-feed, vertical-tab,...
-- \S matches any non-white space character.
-- \w matches any alphanumeric character or underscore.
-- This include accented letters, as defined in the
-- package Ada.Characters.Handling.
-- \W matches any non-alphanumeric character.
-- \A match the empty string only at the beginning of the
-- string, whatever flags are used for Compile (the
-- behavior of ^ can change, see Regexp_Flags below).
-- \G match the empty string only at the end of the
-- string, whatever flags are used for Compile (the
-- behavior of $ can change, see Regexp_Flags below).
-- ... ::= is used to indication repetition (one or more terms)
-- Embedded newlines are not matched by the ^ operator.
-- It is possible to retrieve the substring matched a parenthesis
-- expression. Although the depth of parenthesis is not limited in the
-- regexp, only the first 9 substrings can be retrieved.
-- The highest value possible for the arguments to the curly operator ({})
-- are given by the constant Max_Curly_Repeat below.
-- The operators '*', '+', '?' and '{}' always match the longest possible
-- substring. They all have a non-greedy version (with an extra ? after the
-- operator), which matches the shortest possible substring.
-- For instance:
-- regexp="<.*>" string="<h1>title</h1>" matches="<h1>title</h1>"
-- regexp="<.*?>" string="<h1>title</h1>" matches="<h1>"
--
-- '{' and '}' are only considered as special characters if they appear
-- in a substring that looks exactly like '{n}', '{n,m}' or '{n,}', where
-- n and m are digits. No space is allowed. In other contexts, the curly
-- braces will simply be treated as normal characters.
-- Compiling Regular Expressions
-- =============================
-- To use this package, you first need to compile the regular expression
-- (a string) into a byte-code program, in a Pattern_Matcher structure.
-- This first step checks that the regexp is valid, and optimizes the
-- matching algorithms of the second step.
-- Two versions of the Compile subprogram are given: one in which this
-- package will compute itself the best possible size to allocate for the
-- byte code; the other where you must allocate enough memory yourself. An
-- exception is raised if there is not enough memory.
-- declare
-- Regexp : String := "a|b";
-- Matcher : Pattern_Matcher := Compile (Regexp);
-- -- The size for matcher is automatically allocated
-- Matcher2 : Pattern_Matcher (1000);
-- -- Some space is allocated directly.
-- begin
-- Compile (Matcher2, Regexp);
-- ...
-- end;
-- Note that the second version is significantly faster, since with the
-- first version the regular expression has in fact to be compiled twice
-- (first to compute the size, then to generate the byte code).
-- Note also that you cannot use the function version of Compile if you
-- specify the size of the Pattern_Matcher, since the discriminants will
-- most probably be different and you will get a Constraint_Error
-- Matching Strings
-- ================
-- Once the regular expression has been compiled, you can use it as often
-- as needed to match strings.
-- Several versions of the Match subprogram are provided, with different
-- parameters and return results.
-- See the description under each of these subprograms
-- Here is a short example showing how to get the substring matched by
-- the first parenthesis pair.
-- declare
-- Matches : Match_Array (0 .. 1);
-- Regexp : String := "a(b|c)d";
-- Str : String := "gacdg";
-- begin
-- Match (Compile (Regexp), Str, Matches);
-- return Str (Matches (1).First .. Matches (1).Last);
-- -- returns 'c'
-- end;
-- Finding all occurrences
-- =======================
-- Finding all the occurrences of a regular expression in a string cannot
-- be done by simply passing a slice of the string. This wouldn't work for
-- anchored regular expressions (the ones starting with "^" or ending with
-- "$").
-- Instead, you need to use the last parameter to Match (Data_First), as in
-- the following loop:
-- declare
-- Str : String :=
-- "-- first line" & ASCII.LF & "-- second line";
-- Matches : Match_array (0 .. 0);
-- Regexp : Pattern_Matcher := Compile ("^--", Multiple_Lines);
-- Current : Natural := Str'First;
-- begin
-- loop
-- Match (Regexp, Str, Matches, Current);
-- exit when Matches (0) = No_Match;
--
-- -- Process the match at position Matches (0).First
--
-- Current := Matches (0).Last + 1;
-- end loop;
-- end;
-- String Substitution
-- ===================
-- No subprogram is currently provided for string substitution.
-- However, this is easy to simulate with the parenthesis groups, as
-- shown below.
-- This example swaps the first two words of the string:
-- declare
-- Regexp : String := "([a-z]+) +([a-z]+)";
-- Str : String := " first second third ";
-- Matches : Match_Array (0 .. 2);
-- begin
-- Match (Compile (Regexp), Str, Matches);
-- return Str (Str'First .. Matches (1).First - 1)
-- & Str (Matches (2).First .. Matches (2).Last)
-- & " "
-- & Str (Matches (1).First .. Matches (1).Last)
-- & Str (Matches (2).Last + 1 .. Str'Last);
-- -- returns " second first third "
-- end;
---------------
-- Constants --
---------------
Expression_Error : exception;
-- This exception is raised when trying to compile an invalid regular
-- expression. All subprograms taking an expression as parameter may raise
-- Expression_Error.
Max_Paren_Count : constant := 255;
-- Maximum number of parenthesis in a regular expression. This is limited
-- by the size of a Character, as found in the byte-compiled version of
-- regular expressions.
Max_Curly_Repeat : constant := 32767;
-- Maximum number of repetition for the curly operator. The digits in the
-- {n}, {n,} and {n,m } operators cannot be higher than this constant,
-- since they have to fit on two characters in the byte-compiled version of
-- regular expressions.
Max_Program_Size : constant := 2**15 - 1;
-- Maximum size that can be allocated for a program
type Program_Size is range 0 .. Max_Program_Size;
for Program_Size'Size use 16;
-- Number of bytes allocated for the byte-compiled version of a regular
-- expression. The size required depends on the complexity of the regular
-- expression in a complex manner that is undocumented (other than in the
-- body of the Compile procedure). Normally the size is automatically set
-- and the programmer need not be concerned about it. There are two
-- exceptions to this. First in the calls to Match, it is possible to
-- specify a non-zero size that is known to be large enough. This can
-- slightly increase the efficiency by avoiding a copy. Second, in the case
-- of calling compile, it is possible using the procedural form of Compile
-- to use a single Pattern_Matcher variable for several different
-- expressions by setting its size sufficiently large.
Auto_Size : constant := 0;
-- Used in calls to Match to indicate that the Size should be set to
-- a value appropriate to the expression being used automatically.
type Regexp_Flags is mod 256;
for Regexp_Flags'Size use 8;
-- Flags that can be given at compile time to specify default
-- properties for the regular expression.
No_Flags : constant Regexp_Flags;
Case_Insensitive : constant Regexp_Flags;
-- The automaton is optimized so that the matching is done in a case
-- insensitive manner (upper case characters and lower case characters
-- are all treated the same way).
Single_Line : constant Regexp_Flags;
-- Treat the Data we are matching as a single line. This means that
-- ^ and $ will ignore \n (unless Multiple_Lines is also specified),
-- and that '.' will match \n.
Multiple_Lines : constant Regexp_Flags;
-- Treat the Data as multiple lines. This means that ^ and $ will also
-- match on internal newlines (ASCII.LF), in addition to the beginning
-- and end of the string.
--
-- This can be combined with Single_Line.
-----------------
-- Match_Array --
-----------------
subtype Match_Count is Natural range 0 .. Max_Paren_Count;
type Match_Location is record
First : Natural := 0;
Last : Natural := 0;
end record;
type Match_Array is array (Match_Count range <>) of Match_Location;
-- The substring matching a given pair of parenthesis. Index 0 is the whole
-- substring that matched the full regular expression.
--
-- For instance, if your regular expression is something like: "a(b*)(c+)",
-- then Match_Array(1) will be the indexes of the substring that matched
-- "b*" and Match_Array(2) will be the substring that matched "c+".
--
-- The number of parenthesis groups that can be retrieved is unlimited, and
-- all the Match subprograms below can use a Match_Array of any size.
-- Indexes that do not have any matching parenthesis are set to No_Match.
No_Match : constant Match_Location := (First => 0, Last => 0);
-- The No_Match constant is (0, 0) to differentiate between matching a null
-- string at position 1, which uses (1, 0) and no match at all.
---------------------------------
-- Pattern_Matcher Compilation --
---------------------------------
-- The subprograms here are used to precompile regular expressions for use
-- in subsequent Match calls. Precompilation improves efficiency if the
-- same regular expression is to be used in more than one Match call.
type Pattern_Matcher (Size : Program_Size) is private;
-- Type used to represent a regular expression compiled into byte code
Never_Match : constant Pattern_Matcher;
-- A regular expression that never matches anything
function Compile
(Expression : String;
Flags : Regexp_Flags := No_Flags) return Pattern_Matcher;
-- Compile a regular expression into internal code
--
-- Raises Expression_Error if Expression is not a legal regular expression
--
-- The appropriate size is calculated automatically to correspond to the
-- provided expression. This is the normal default method of compilation.
-- Note that it is generally not possible to assign the result of two
-- different calls to this Compile function to the same Pattern_Matcher
-- variable, since the sizes will differ.
--
-- Flags is the default value to use to set properties for Expression
-- (e.g. case sensitivity,...).
procedure Compile
(Matcher : out Pattern_Matcher;
Expression : String;
Final_Code_Size : out Program_Size;
Flags : Regexp_Flags := No_Flags);
-- Compile a regular expression into into internal code
-- This procedure is significantly faster than the Compile function since
-- it avoids the extra step of precomputing the required size.
--
-- However, it requires the user to provide a Pattern_Matcher variable
-- whose size is preset to a large enough value. One advantage of this
-- approach, in addition to the improved efficiency, is that the same
-- Pattern_Matcher variable can be used to hold the compiled code for
-- several different regular expressions by setting a size that is large
-- enough to accomodate all possibilities.
--
-- In this version of the procedure call, the actual required code size is
-- returned. Also if Matcher.Size is zero on entry, then the resulting code
-- is not stored. A call with Matcher.Size set to Auto_Size can thus be
-- used to determine the space required for compiling the given regular
-- expression.
--
-- This function raises Storage_Error if Matcher is too small to hold
-- the resulting code (i.e. Matcher.Size has too small a value).
--
-- Expression_Error is raised if the string Expression does not contain
-- a valid regular expression.
--
-- Flags is the default value to use to set properties for Expression (case
-- sensitivity,...).
procedure Compile
(Matcher : out Pattern_Matcher;
Expression : String;
Flags : Regexp_Flags := No_Flags);
-- -- Same procedure as above, expect it does not return the final
-- -- program size, and Matcher.Size cannot be Auto_Size.
function Paren_Count (Regexp : Pattern_Matcher) return Match_Count;
pragma Inline (Paren_Count);
-- Return the number of parenthesis pairs in Regexp.
--
-- This is the maximum index that will be filled if a Match_Array is
-- used as an argument to Match.
--
-- Thus, if you want to be sure to get all the parenthesis, you should
-- do something like:
--
-- declare
-- Regexp : Pattern_Matcher := Compile ("a(b*)(c+)");
-- Matched : Match_Array (0 .. Paren_Count (Regexp));
-- begin
-- Match (Regexp, "a string", Matched);
-- end;
-------------
-- Quoting --
-------------
function Quote (Str : String) return String;
-- Return a version of Str so that every special character is quoted.
-- The resulting string can be used in a regular expression to match
-- exactly Str, whatever character was present in Str.
--------------
-- Matching --
--------------
-- The Match subprograms are given a regular expression in string
-- form, and perform the corresponding match. The following parameters
-- are present in all forms of the Match call.
-- Expression contains the regular expression to be matched as a string
-- Data contains the string to be matched
-- Data_First is the lower bound for the match, i.e. Data (Data_First)
-- will be the first character to be examined. If Data_First is set to
-- the special value of -1 (the default), then the first character to
-- be examined is Data (Data_First). However, the regular expression
-- character ^ (start of string) still refers to the first character
-- of the full string (Data (Data'First)), which is why there is a
-- separate mechanism for specifying Data_First.
-- Data_Last is the upper bound for the match, i.e. Data (Data_Last)
-- will be the last character to be examined. If Data_Last is set to
-- the special value of Positive'Last (the default), then the last
-- character to be examined is Data (Data_Last). However, the regular
-- expression character $ (end of string) still refers to the last
-- character of the full string (Data (Data'Last)), which is why there
-- is a separate mechanism for specifying Data_Last.
-- Note: the use of Data_First and Data_Last is not equivalent to
-- simply passing a slice as Expression because of the handling of
-- regular expression characters ^ and $.
-- Size is the size allocated for the compiled byte code. Normally
-- this is defaulted to Auto_Size which means that the appropriate
-- size is allocated automatically. It is possible to specify an
-- explicit size, which must be sufficiently large. This slightly
-- increases the efficiency by avoiding the extra step of computing
-- the appropriate size.
-- The following exceptions can be raised in calls to Match
--
-- Storage_Error is raised if a non-zero value is given for Size
-- and it is too small to hold the compiled byte code.
--
-- Expression_Error is raised if the given expression is not a legal
-- regular expression.
procedure Match
(Expression : String;
Data : String;
Matches : out Match_Array;
Size : Program_Size := Auto_Size;
Data_First : Integer := -1;
Data_Last : Positive := Positive'Last);
-- This version returns the result of the match stored in Match_Array.
-- At most Matches'Length parenthesis are returned.
function Match
(Expression : String;
Data : String;
Size : Program_Size := Auto_Size;
Data_First : Integer := -1;
Data_Last : Positive := Positive'Last) return Natural;
-- This version returns the position where Data matches, or if there is
-- no match, then the value Data'First - 1.
function Match
(Expression : String;
Data : String;
Size : Program_Size := Auto_Size;
Data_First : Integer := -1;
Data_Last : Positive := Positive'Last) return Boolean;
-- This version returns True if the match succeeds, False otherwise
------------------------------------------------
-- Matching a Pre-Compiled Regular Expression --
------------------------------------------------
-- The following functions are significantly faster if you need to reuse
-- the same regular expression multiple times, since you only have to
-- compile it once. For these functions you must first compile the
-- expression with a call to Compile as previously described.
-- The parameters Data, Data_First and Data_Last are as described
-- in the previous section.
function Match
(Self : Pattern_Matcher;
Data : String;
Data_First : Integer := -1;
Data_Last : Positive := Positive'Last) return Natural;
-- Match Data using the given pattern matcher. Returns the position
-- where Data matches, or (Data'First - 1) if there is no match.
function Match
(Self : Pattern_Matcher;
Data : String;
Data_First : Integer := -1;
Data_Last : Positive := Positive'Last) return Boolean;
-- Return True if Data matches using the given pattern matcher
pragma Inline (Match);
-- All except the last one below
procedure Match
(Self : Pattern_Matcher;
Data : String;
Matches : out Match_Array;
Data_First : Integer := -1;
Data_Last : Positive := Positive'Last);
-- Match Data using the given pattern matcher and store result in Matches.
-- The expression matches if Matches (0) /= No_Match. The lower bound of
-- Matches is required to be zero.
--
-- At most Matches'Length parenthesis are returned
-----------
-- Debug --
-----------
procedure Dump (Self : Pattern_Matcher);
-- Dump the compiled version of the regular expression matched by Self
--------------------------
-- Private Declarations --
--------------------------
private
subtype Pointer is Program_Size;
-- The Pointer type is used to point into Program_Data
-- Note that the pointer type is not necessarily 2 bytes
-- although it is stored in the program using 2 bytes
type Program_Data is array (Pointer range <>) of Character;
Program_First : constant := 1;
-- The "internal use only" fields in regexp are present to pass info from
-- compile to execute that permits the execute phase to run lots faster on
-- simple cases. They are:
-- First character that must begin a match or ASCII.Nul
-- Anchored true iff match must start at beginning of line
-- Must_Have pointer to string that match must include or null
-- Must_Have_Length length of Must_Have string
-- First and Anchored permit very fast decisions on suitable starting
-- points for a match, cutting down the work a lot. Must_Have permits fast
-- rejection of lines that cannot possibly match.
-- The Must_Have tests are costly enough that Optimize supplies a Must_Have
-- only if the r.e. contains something potentially expensive (at present,
-- the only such thing detected is * or at the start of the r.e., which can
-- involve a lot of backup). The length is supplied because the test in
-- Execute needs it and Optimize is computing it anyway.
-- The initialization is meant to fail-safe in case the user of this
-- package tries to use an uninitialized matcher. This takes advantage
-- of the knowledge that ASCII.Nul translates to the end-of-program (EOP)
-- instruction code of the state machine.
No_Flags : constant Regexp_Flags := 0;
Case_Insensitive : constant Regexp_Flags := 1;
Single_Line : constant Regexp_Flags := 2;
Multiple_Lines : constant Regexp_Flags := 4;
type Pattern_Matcher (Size : Pointer) is record
First : Character := ASCII.NUL; -- internal use only
Anchored : Boolean := False; -- internal use only
Must_Have : Pointer := 0; -- internal use only
Must_Have_Length : Natural := 0; -- internal use only
Paren_Count : Natural := 0; -- # paren groups
Flags : Regexp_Flags := No_Flags;
Program : Program_Data (Program_First .. Size) :=
(others => ASCII.NUL);
end record;
Never_Match : constant Pattern_Matcher :=
(0, ASCII.NUL, False, 0, 0, 0, No_Flags, (others => ASCII.NUL));
with System.Regpat;
end GNAT.Regpat;
package GNAT.Regpat renames System.Regpat;
......@@ -6,7 +6,7 @@
-- --
-- B o d y --
-- --
-- Copyright (C) 1997-2005, AdaCore --
-- Copyright (C) 1997-2007, AdaCore --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -31,27 +31,8 @@
-- --
------------------------------------------------------------------------------
with System.Soft_Links;
-- used for Lock_Task, Unlock_Task
-- This package does not require a body, since it is a package renaming. We
-- provide a dummy file containing a No_Body pragma so that previous versions
-- of the body (which did exist) will not intefere.
package body GNAT.Task_Lock is
----------
-- Lock --
----------
procedure Lock is
begin
System.Soft_Links.Lock_Task.all;
end Lock;
------------
-- Unlock --
------------
procedure Unlock is
begin
System.Soft_Links.Unlock_Task.all;
end Unlock;
end GNAT.Task_Lock;
pragma No_Body;
......@@ -6,7 +6,7 @@
-- --
-- S p e c --
-- --
-- Copyright (C) 1998-2005, AdaCore --
-- Copyright (C) 1998-2007, AdaCore --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -41,56 +41,8 @@
-- These routines may be used in a non-tasking program, and in that case
-- they have no effect (they do NOT cause the tasking runtime to be loaded).
package GNAT.Task_Lock is
pragma Elaborate_Body;
-- See file s-tasloc.ads for full documentation of the interface
procedure Lock;
pragma Inline (Lock);
-- Acquires the global lock, starts the execution of a critical region
-- which no other task can enter until the locking task calls Unlock
with System.Task_Lock;
procedure Unlock;
pragma Inline (Unlock);
-- Releases the global lock, allowing another task to successfully
-- complete a Lock operation. Terminates the critical region.
--
-- The recommended protocol for using these two procedures is as
-- follows:
--
-- Locked_Processing : begin
-- Lock;
-- ...
-- TSL.Unlock;
--
-- exception
-- when others =>
-- Unlock;
-- raise;
-- end Locked_Processing;
--
-- This ensures that the lock is not left set if an exception is raised
-- explicitly or implicitly during the critical locked region.
--
-- Note on multiple calls to Lock: It is permissible to call Lock
-- more than once with no intervening Unlock from a single task,
-- and the lock will not be released until the corresponding number
-- of Unlock operations has been performed. For example:
--
-- GNAT.Task_Lock.Lock; -- acquires lock
-- GNAT.Task_Lock.Lock; -- no effect
-- GNAT.Task_Lock.Lock; -- no effect
-- GNAT.Task_Lock.Unlock; -- no effect
-- GNAT.Task_Lock.Unlock; -- no effect
-- GNAT.Task_Lock.Unlock; -- releases lock
--
-- However, as previously noted, the Task_Lock facility should only
-- be used for very local locks where the probability of conflict is
-- low, so usually this kind of nesting is not a good idea in any case.
-- In more complex locking situations, it is more appropriate to define
-- an appropriate protected type to provide the required locking.
--
-- It is an error to call Unlock when there has been no prior call to
-- Lock. The effect of such an erroneous call is undefined, and may
-- result in deadlock, or other malfunction of the run-time system.
end GNAT.Task_Lock;
package GNAT.Task_Lock renames System.Task_Lock;
This source diff could not be displayed because it is too large. You can view the blob instead.
......@@ -6,7 +6,7 @@
-- --
-- S p e c --
-- --
-- Copyright (C) 2005 Free Software Foundation, Inc. --
-- Copyright (C) 2005-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -42,155 +42,8 @@
-- and also serves as the basis for Ada.Wide_Wide_Characters.Unicode and
-- Ada.Wide_Characters.Unicode, which can also be used directly.
package GNAT.UTF_32 is
-- See file s-utf_32.ads for full documentation of the interface
type UTF_32 is range 0 .. 16#7FFF_FFFF#;
-- So far, the only defined character codes are in 0 .. 16#01_FFFF#
with System.UTF_32;
-- The following type defines the categories from the unicode definitions.
-- The one addition we make is Fe, which represents the characters FFFE
-- and FFFF in any of the planes.
type Category is (
Cc, -- Other, Control
Cf, -- Other, Format
Cn, -- Other, Not Assigned
Co, -- Other, Private Use
Cs, -- Other, Surrogate
Ll, -- Letter, Lowercase
Lm, -- Letter, Modifier
Lo, -- Letter, Other
Lt, -- Letter, Titlecase
Lu, -- Letter, Uppercase
Mc, -- Mark, Spacing Combining
Me, -- Mark, Enclosing
Mn, -- Mark, Nonspacing
Nd, -- Number, Decimal Digit
Nl, -- Number, Letter
No, -- Number, Other
Pc, -- Punctuation, Connector
Pd, -- Punctuation, Dash
Pe, -- Punctuation, Close
Pf, -- Punctuation, Final quote
Pi, -- Punctuation, Initial quote
Po, -- Punctuation, Other
Ps, -- Punctuation, Open
Sc, -- Symbol, Currency
Sk, -- Symbol, Modifier
Sm, -- Symbol, Math
So, -- Symbol, Other
Zl, -- Separator, Line
Zp, -- Separator, Paragraph
Zs, -- Separator, Space
Fe); -- relative position FFFE/FFFF in any plane
function Get_Category (U : UTF_32) return Category;
-- Given a UTF32 code, returns corresponding Category, or Cn if
-- the code does not have an assigned unicode category.
-- The following functions perform category tests corresponding to lexical
-- classes defined in the Ada standard. There are two interfaces for each
-- function. The second takes a Category (e.g. returned by Get_Category).
-- The first takes a UTF_32 code. The form taking the UTF_32 code is
-- typically more efficient than calling Get_Category, but if several
-- different tests are to be performed on the same code, it is more
-- efficient to use Get_Category to get the category, then test the
-- resulting category.
function Is_UTF_32_Letter (U : UTF_32) return Boolean;
function Is_UTF_32_Letter (C : Category) return Boolean;
pragma Inline (Is_UTF_32_Letter);
-- Returns true iff U is a letter that can be used to start an identifier,
-- or if C is one of the corresponding categories, which are the following:
-- Letter, Uppercase (Lu)
-- Letter, Lowercase (Ll)
-- Letter, Titlecase (Lt)
-- Letter, Modifier (Lm)
-- Letter, Other (Lo)
-- Number, Letter (Nl)
function Is_UTF_32_Digit (U : UTF_32) return Boolean;
function Is_UTF_32_Digit (C : Category) return Boolean;
pragma Inline (Is_UTF_32_Digit);
-- Returns true iff U is a digit that can be used to extend an identifer,
-- or if C is one of the corresponding categories, which are the following:
-- Number, Decimal_Digit (Nd)
function Is_UTF_32_Line_Terminator (U : UTF_32) return Boolean;
pragma Inline (Is_UTF_32_Line_Terminator);
-- Returns true iff U is an allowed line terminator for source programs,
-- if U is in the category Zp (Separator, Paragaph), or Zs (Separator,
-- Line), or if U is a conventional line terminator (CR, LF, VT, FF).
-- There is no category version for this function, since the set of
-- characters does not correspond to a set of Unicode categories.
function Is_UTF_32_Mark (U : UTF_32) return Boolean;
function Is_UTF_32_Mark (C : Category) return Boolean;
pragma Inline (Is_UTF_32_Mark);
-- Returns true iff U is a mark character which can be used to extend an
-- identifier, or if C is one of the corresponding categories, which are
-- the following:
-- Mark, Non-Spacing (Mn)
-- Mark, Spacing Combining (Mc)
function Is_UTF_32_Other (U : UTF_32) return Boolean;
function Is_UTF_32_Other (C : Category) return Boolean;
pragma Inline (Is_UTF_32_Other);
-- Returns true iff U is an other format character, which means that it
-- can be used to extend an identifier, but is ignored for the purposes of
-- matching of identiers, or if C is one of the corresponding categories,
-- which are the following:
-- Other, Format (Cf)
function Is_UTF_32_Punctuation (U : UTF_32) return Boolean;
function Is_UTF_32_Punctuation (C : Category) return Boolean;
pragma Inline (Is_UTF_32_Punctuation);
-- Returns true iff U is a punctuation character that can be used to
-- separate pices of an identifier, or if C is one of the corresponding
-- categories, which are the following:
-- Punctuation, Connector (Pc)
function Is_UTF_32_Space (U : UTF_32) return Boolean;
function Is_UTF_32_Space (C : Category) return Boolean;
pragma Inline (Is_UTF_32_Space);
-- Returns true iff U is considered a space to be ignored, or if C is one
-- of the corresponding categories, which are the following:
-- Separator, Space (Zs)
function Is_UTF_32_Non_Graphic (U : UTF_32) return Boolean;
function Is_UTF_32_Non_Graphic (C : Category) return Boolean;
pragma Inline (Is_UTF_32_Non_Graphic);
-- Returns true iff U is considered to be a non-graphic character, or if C
-- is one of the corresponding categories, which are the following:
-- Other, Control (Cc)
-- Other, Private Use (Co)
-- Other, Surrogate (Cs)
-- Separator, Line (Zl)
-- Separator, Paragraph (Zp)
-- FFFE or FFFF positions in any plane (Fe)
--
-- Note that the Ada category format effector is subsumed by the above
-- list of Unicode categories.
--
-- Note that Other, Unassiged (Cn) is quite deliberately not included
-- in the list of categories above. This means that should any of these
-- code positions be defined in future with graphic characters they will
-- be allowed without a need to change implementations or the standard.
--
-- Note that Other, Format (Cf) is also quite deliberately not included
-- in the list of categories above. This means that these characters can
-- be included in character and string literals.
-- The following function is used to fold to upper case, as required by
-- the Ada 2005 standard rules for identifier case folding. Two
-- identifiers are equivalent if they are identical after folding all
-- letters to upper case using this routine.
function UTF_32_To_Upper_Case (U : UTF_32) return UTF_32;
pragma Inline (UTF_32_To_Upper_Case);
-- If U represents a lower case letter, returns the corresponding upper
-- case letter, otherwise U is returned unchanged. The folding is locale
-- independent as defined by documents referenced in the note in section
-- 1 of ISO/IEC 10646:2003
end GNAT.UTF_32;
package GNAT.UTF_32 renames System.UTF_32;
......@@ -6,7 +6,7 @@
-- --
-- B o d y --
-- --
-- Copyright (C) 1998-2005 Free Software Foundation, Inc. --
-- Copyright (C) 1998-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -34,8 +34,10 @@ with Opt;
with Ada.Strings.Fixed; use Ada.Strings.Fixed;
with Ada.Text_IO; use Ada.Text_IO;
with GNAT.Command_Line; use GNAT.Command_Line;
with GNAT.Strings; use GNAT.Strings;
with System.Strings; use System.Strings;
--------------
-- Gnatfind --
......
......@@ -6,7 +6,7 @@
-- --
-- B o d y --
-- --
-- Copyright (C) 1998-2005, Free Software Foundation, Inc. --
-- Copyright (C) 1998-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -34,8 +34,10 @@ with Opt;
with Ada.Strings.Fixed; use Ada.Strings.Fixed;
with Ada.Text_IO; use Ada.Text_IO;
with GNAT.Command_Line; use GNAT.Command_Line;
with GNAT.Strings; use GNAT.Strings;
with System.Strings; use System.Strings;
procedure Gnatxref is
Search_Unused : Boolean := False;
......
......@@ -6,7 +6,7 @@
-- --
-- B o d y --
-- --
-- Copyright (C) 2002-2006, Free Software Foundation, Inc. --
-- Copyright (C) 2002-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -40,10 +40,12 @@ with Stringt; use Stringt;
with Types; use Types;
with Ada.Text_IO; use Ada.Text_IO;
with GNAT.Case_Util; use GNAT.Case_Util;
with GNAT.Command_Line;
with GNAT.Directory_Operations; use GNAT.Directory_Operations;
with GNAT.OS_Lib; use GNAT.OS_Lib;
with System.OS_Lib; use System.OS_Lib;
package body GPrep is
......
......@@ -6,7 +6,7 @@
-- --
-- S p e c --
-- --
-- Copyright (C) 2004-2005, Free Software Foundation, Inc. --
-- Copyright (C) 2004-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -36,7 +36,7 @@
-- Used to convert GNAT switches to their platform-dependent switch
-- equivalent for the underlying linker.
with GNAT.OS_Lib; use GNAT.OS_Lib;
with System.OS_Lib; use System.OS_Lib;
package Indepsw is
......
......@@ -6,7 +6,7 @@
-- --
-- B o d y --
-- --
-- Copyright (C) 1992-2006, Free Software Foundation, Inc. --
-- Copyright (C) 1992-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -31,7 +31,7 @@
-- --
------------------------------------------------------------------------------
with GNAT.OS_Lib; use GNAT.OS_Lib;
with System.OS_Lib; use System.OS_Lib;
package body Output is
......
......@@ -6,7 +6,7 @@
-- --
-- B o d y --
-- --
-- Copyright (C) 1999-2006, AdaCore --
-- Copyright (C) 1999-2007, AdaCore --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -33,14 +33,14 @@
-- This implementation is specific to NT
with GNAT.Task_Lock;
with System.Task_Lock;
with Interfaces.C.Strings;
with System.OS_Interface;
package body System.Global_Locks is
package TSL renames GNAT.Task_Lock;
package TSL renames System.Task_Lock;
package OSI renames System.OS_Interface;
package ICS renames Interfaces.C.Strings;
......
------------------------------------------------------------------------------
-- --
-- GNAT COMPILER COMPONENTS --
-- --
-- S Y S T E M . O S _ L I B --
-- --
-- B o d y --
-- --
-- Copyright (C) 1995-2007, AdaCore --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- ware Foundation; either version 2, or (at your option) any later ver- --
-- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
-- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
-- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
-- for more details. You should have received a copy of the GNU General --
-- Public License distributed with GNAT; see file COPYING. If not, write --
-- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
-- Boston, MA 02110-1301, USA. --
-- --
-- As a special exception, if other files instantiate generics from this --
-- unit, or you link this unit with other files to produce an executable, --
-- this unit does not by itself cause the resulting executable to be --
-- covered by the GNU General Public License. This exception does not --
-- however invalidate any other reasons why the executable file might be --
-- covered by the GNU Public License. --
-- --
-- GNAT was originally developed by the GNAT team at New York University. --
-- Extensive contributions were provided by Ada Core Technologies Inc. --
-- --
------------------------------------------------------------------------------
with System.Case_Util;
with System.CRTL;
with System.Soft_Links;
with Ada.Unchecked_Conversion;
with Ada.Unchecked_Deallocation;
with System; use System;
package body System.OS_Lib is
-- Imported procedures Dup and Dup2 are used in procedures Spawn and
-- Non_Blocking_Spawn.
function Dup (Fd : File_Descriptor) return File_Descriptor;
pragma Import (C, Dup, "__gnat_dup");
procedure Dup2 (Old_Fd, New_Fd : File_Descriptor);
pragma Import (C, Dup2, "__gnat_dup2");
On_Windows : constant Boolean := Directory_Separator = '\';
-- An indication that we are on Windows. Used in Normalize_Pathname, to
-- deal with drive letters in the beginning of absolute paths.
package SSL renames System.Soft_Links;
-- The following are used by Create_Temp_File
First_Temp_File_Name : constant String := "GNAT-TEMP-000000.TMP";
-- Used to initialize Current_Temp_File_Name and Temp_File_Name_Last_Digit
Current_Temp_File_Name : String := First_Temp_File_Name;
-- Name of the temp file last created
Temp_File_Name_Last_Digit : constant Positive :=
First_Temp_File_Name'Last - 4;
-- Position of the last digit in Current_Temp_File_Name
Max_Attempts : constant := 100;
-- The maximum number of attempts to create a new temp file
-----------------------
-- Local Subprograms --
-----------------------
function Args_Length (Args : Argument_List) return Natural;
-- Returns total number of characters needed to create a string
-- of all Args terminated by ASCII.NUL characters
function C_String_Length (S : Address) return Integer;
-- Returns the length of a C string. Does check for null address
-- (returns 0).
procedure Spawn_Internal
(Program_Name : String;
Args : Argument_List;
Result : out Integer;
Pid : out Process_Id;
Blocking : Boolean);
-- Internal routine to implement the two Spawn (blocking/non blocking)
-- routines. If Blocking is set to True then the spawn is blocking
-- otherwise it is non blocking. In this latter case the Pid contains the
-- process id number. The first three parameters are as in Spawn. Note that
-- Spawn_Internal normalizes the argument list before calling the low level
-- system spawn routines (see Normalize_Arguments).
--
-- Note: Normalize_Arguments is designed to do nothing if it is called more
-- than once, so calling Normalize_Arguments before calling one of the
-- spawn routines is fine.
function To_Path_String_Access
(Path_Addr : Address;
Path_Len : Integer) return String_Access;
-- Converts a C String to an Ada String. We could do this making use of
-- Interfaces.C.Strings but we prefer not to import that entire package
---------
-- "<" --
---------
function "<" (X, Y : OS_Time) return Boolean is
begin
return Long_Integer (X) < Long_Integer (Y);
end "<";
----------
-- "<=" --
----------
function "<=" (X, Y : OS_Time) return Boolean is
begin
return Long_Integer (X) <= Long_Integer (Y);
end "<=";
---------
-- ">" --
---------
function ">" (X, Y : OS_Time) return Boolean is
begin
return Long_Integer (X) > Long_Integer (Y);
end ">";
----------
-- ">=" --
----------
function ">=" (X, Y : OS_Time) return Boolean is
begin
return Long_Integer (X) >= Long_Integer (Y);
end ">=";
-----------------
-- Args_Length --
-----------------
function Args_Length (Args : Argument_List) return Natural is
Len : Natural := 0;
begin
for J in Args'Range loop
Len := Len + Args (J)'Length + 1; -- One extra for ASCII.NUL
end loop;
return Len;
end Args_Length;
-----------------------------
-- Argument_String_To_List --
-----------------------------
function Argument_String_To_List
(Arg_String : String) return Argument_List_Access
is
Max_Args : constant Integer := Arg_String'Length;
New_Argv : Argument_List (1 .. Max_Args);
New_Argc : Natural := 0;
Idx : Integer;
begin
Idx := Arg_String'First;
loop
exit when Idx > Arg_String'Last;
declare
Quoted : Boolean := False;
Backqd : Boolean := False;
Old_Idx : Integer;
begin
Old_Idx := Idx;
loop
-- An unquoted space is the end of an argument
if not (Backqd or Quoted)
and then Arg_String (Idx) = ' '
then
exit;
-- Start of a quoted string
elsif not (Backqd or Quoted)
and then Arg_String (Idx) = '"'
then
Quoted := True;
-- End of a quoted string and end of an argument
elsif (Quoted and not Backqd)
and then Arg_String (Idx) = '"'
then
Idx := Idx + 1;
exit;
-- Following character is backquoted
elsif Arg_String (Idx) = '\' then
Backqd := True;
-- Turn off backquoting after advancing one character
elsif Backqd then
Backqd := False;
end if;
Idx := Idx + 1;
exit when Idx > Arg_String'Last;
end loop;
-- Found an argument
New_Argc := New_Argc + 1;
New_Argv (New_Argc) :=
new String'(Arg_String (Old_Idx .. Idx - 1));
-- Skip extraneous spaces
while Idx <= Arg_String'Last and then Arg_String (Idx) = ' ' loop
Idx := Idx + 1;
end loop;
end;
end loop;
return new Argument_List'(New_Argv (1 .. New_Argc));
end Argument_String_To_List;
---------------------
-- C_String_Length --
---------------------
function C_String_Length (S : Address) return Integer is
function Strlen (S : Address) return Integer;
pragma Import (C, Strlen, "strlen");
begin
if S = Null_Address then
return 0;
else
return Strlen (S);
end if;
end C_String_Length;
-----------
-- Close --
-----------
procedure Close (FD : File_Descriptor) is
procedure C_Close (FD : File_Descriptor);
pragma Import (C, C_Close, "close");
begin
C_Close (FD);
end Close;
procedure Close (FD : File_Descriptor; Status : out Boolean) is
function C_Close (FD : File_Descriptor) return Integer;
pragma Import (C, C_Close, "close");
begin
Status := (C_Close (FD) = 0);
end Close;
---------------
-- Copy_File --
---------------
procedure Copy_File
(Name : String;
Pathname : String;
Success : out Boolean;
Mode : Copy_Mode := Copy;
Preserve : Attribute := Time_Stamps)
is
From : File_Descriptor;
To : File_Descriptor;
Copy_Error : exception;
-- Internal exception raised to signal error in copy
function Build_Path (Dir : String; File : String) return String;
-- Returns pathname Dir catenated with File adding the directory
-- separator only if needed.
procedure Copy (From, To : File_Descriptor);
-- Read data from From and place them into To. In both cases the
-- operations uses the current file position. Raises Constraint_Error
-- if a problem occurs during the copy.
procedure Copy_To (To_Name : String);
-- Does a straight copy from source to designated destination file
----------------
-- Build_Path --
----------------
function Build_Path (Dir : String; File : String) return String is
Res : String (1 .. Dir'Length + File'Length + 1);
Base_File_Ptr : Integer;
-- The base file name is File (Base_File_Ptr + 1 .. File'Last)
function Is_Dirsep (C : Character) return Boolean;
pragma Inline (Is_Dirsep);
-- Returns True if C is a directory separator. On Windows we
-- handle both styles of directory separator.
---------------
-- Is_Dirsep --
---------------
function Is_Dirsep (C : Character) return Boolean is
begin
return C = Directory_Separator or else C = '/';
end Is_Dirsep;
-- Start of processing for Build_Path
begin
-- Find base file name
Base_File_Ptr := File'Last;
while Base_File_Ptr >= File'First loop
exit when Is_Dirsep (File (Base_File_Ptr));
Base_File_Ptr := Base_File_Ptr - 1;
end loop;
declare
Base_File : String renames
File (Base_File_Ptr + 1 .. File'Last);
begin
Res (1 .. Dir'Length) := Dir;
if Is_Dirsep (Dir (Dir'Last)) then
Res (Dir'Length + 1 .. Dir'Length + Base_File'Length) :=
Base_File;
return Res (1 .. Dir'Length + Base_File'Length);
else
Res (Dir'Length + 1) := Directory_Separator;
Res (Dir'Length + 2 .. Dir'Length + 1 + Base_File'Length) :=
Base_File;
return Res (1 .. Dir'Length + 1 + Base_File'Length);
end if;
end;
end Build_Path;
----------
-- Copy --
----------
procedure Copy (From, To : File_Descriptor) is
Buf_Size : constant := 200_000;
type Buf is array (1 .. Buf_Size) of Character;
type Buf_Ptr is access Buf;
Buffer : Buf_Ptr;
R : Integer;
W : Integer;
Status_From : Boolean;
Status_To : Boolean;
-- Statuses for the calls to Close
procedure Free is new Ada.Unchecked_Deallocation (Buf, Buf_Ptr);
begin
-- Check for invalid descriptors, making sure that we do not
-- accidentally leave an open file descriptor around.
if From = Invalid_FD then
if To /= Invalid_FD then
Close (To, Status_To);
end if;
raise Copy_Error;
elsif To = Invalid_FD then
Close (From, Status_From);
raise Copy_Error;
end if;
-- Allocate the buffer on the heap
Buffer := new Buf;
loop
R := Read (From, Buffer (1)'Address, Buf_Size);
-- For VMS, the buffer may not be full. So, we need to try again
-- until there is nothing to read.
exit when R = 0;
W := Write (To, Buffer (1)'Address, R);
if W < R then
-- Problem writing data, could be a disk full. Close files
-- without worrying about status, since we are raising a
-- Copy_Error exception in any case.
Close (From, Status_From);
Close (To, Status_To);
Free (Buffer);
raise Copy_Error;
end if;
end loop;
Close (From, Status_From);
Close (To, Status_To);
Free (Buffer);
if not (Status_From and Status_To) then
raise Copy_Error;
end if;
end Copy;
-------------
-- Copy_To --
-------------
procedure Copy_To (To_Name : String) is
function Copy_Attributes
(From, To : System.Address;
Mode : Integer) return Integer;
pragma Import (C, Copy_Attributes, "__gnat_copy_attribs");
-- Mode = 0 - copy only time stamps.
-- Mode = 1 - copy time stamps and read/write/execute attributes
C_From : String (1 .. Name'Length + 1);
C_To : String (1 .. To_Name'Length + 1);
begin
From := Open_Read (Name, Binary);
To := Create_File (To_Name, Binary);
Copy (From, To);
-- Copy attributes
C_From (1 .. Name'Length) := Name;
C_From (C_From'Last) := ASCII.Nul;
C_To (1 .. To_Name'Length) := To_Name;
C_To (C_To'Last) := ASCII.Nul;
case Preserve is
when Time_Stamps =>
if Copy_Attributes (C_From'Address, C_To'Address, 0) = -1 then
raise Copy_Error;
end if;
when Full =>
if Copy_Attributes (C_From'Address, C_To'Address, 1) = -1 then
raise Copy_Error;
end if;
when None =>
null;
end case;
end Copy_To;
-- Start of processing for Copy_File
begin
Success := True;
-- The source file must exist
if not Is_Regular_File (Name) then
raise Copy_Error;
end if;
-- The source file exists
case Mode is
-- Copy case, target file must not exist
when Copy =>
-- If the target file exists, we have an error
if Is_Regular_File (Pathname) then
raise Copy_Error;
-- Case of target is a directory
elsif Is_Directory (Pathname) then
declare
Dest : constant String := Build_Path (Pathname, Name);
begin
-- If target file exists, we have an error, else do copy
if Is_Regular_File (Dest) then
raise Copy_Error;
else
Copy_To (Dest);
end if;
end;
-- Case of normal copy to file (destination does not exist)
else
Copy_To (Pathname);
end if;
-- Overwrite case (destination file may or may not exist)
when Overwrite =>
if Is_Directory (Pathname) then
Copy_To (Build_Path (Pathname, Name));
else
Copy_To (Pathname);
end if;
-- Append case (destination file may or may not exist)
when Append =>
-- Appending to existing file
if Is_Regular_File (Pathname) then
-- Append mode and destination file exists, append data at the
-- end of Pathname.
From := Open_Read (Name, Binary);
To := Open_Read_Write (Pathname, Binary);
Lseek (To, 0, Seek_End);
Copy (From, To);
-- Appending to directory, not allowed
elsif Is_Directory (Pathname) then
raise Copy_Error;
-- Appending when target file does not exist
else
Copy_To (Pathname);
end if;
end case;
-- All error cases are caught here
exception
when Copy_Error =>
Success := False;
end Copy_File;
procedure Copy_File
(Name : C_File_Name;
Pathname : C_File_Name;
Success : out Boolean;
Mode : Copy_Mode := Copy;
Preserve : Attribute := Time_Stamps)
is
Ada_Name : String_Access :=
To_Path_String_Access
(Name, C_String_Length (Name));
Ada_Pathname : String_Access :=
To_Path_String_Access
(Pathname, C_String_Length (Pathname));
begin
Copy_File (Ada_Name.all, Ada_Pathname.all, Success, Mode, Preserve);
Free (Ada_Name);
Free (Ada_Pathname);
end Copy_File;
----------------------
-- Copy_Time_Stamps --
----------------------
procedure Copy_Time_Stamps (Source, Dest : String; Success : out Boolean) is
function Copy_Attributes
(From, To : System.Address;
Mode : Integer) return Integer;
pragma Import (C, Copy_Attributes, "__gnat_copy_attribs");
-- Mode = 0 - copy only time stamps.
-- Mode = 1 - copy time stamps and read/write/execute attributes
begin
if Is_Regular_File (Source) and then Is_Writable_File (Dest) then
declare
C_Source : String (1 .. Source'Length + 1);
C_Dest : String (1 .. Dest'Length + 1);
begin
C_Source (1 .. Source'Length) := Source;
C_Source (C_Source'Last) := ASCII.NUL;
C_Dest (1 .. Dest'Length) := Dest;
C_Dest (C_Dest'Last) := ASCII.NUL;
if Copy_Attributes (C_Source'Address, C_Dest'Address, 0) = -1 then
Success := False;
else
Success := True;
end if;
end;
else
Success := False;
end if;
end Copy_Time_Stamps;
procedure Copy_Time_Stamps
(Source, Dest : C_File_Name;
Success : out Boolean)
is
Ada_Source : String_Access :=
To_Path_String_Access
(Source, C_String_Length (Source));
Ada_Dest : String_Access :=
To_Path_String_Access
(Dest, C_String_Length (Dest));
begin
Copy_Time_Stamps (Ada_Source.all, Ada_Dest.all, Success);
Free (Ada_Source);
Free (Ada_Dest);
end Copy_Time_Stamps;
-----------------
-- Create_File --
-----------------
function Create_File
(Name : C_File_Name;
Fmode : Mode) return File_Descriptor
is
function C_Create_File
(Name : C_File_Name;
Fmode : Mode) return File_Descriptor;
pragma Import (C, C_Create_File, "__gnat_open_create");
begin
return C_Create_File (Name, Fmode);
end Create_File;
function Create_File
(Name : String;
Fmode : Mode) return File_Descriptor
is
C_Name : String (1 .. Name'Length + 1);
begin
C_Name (1 .. Name'Length) := Name;
C_Name (C_Name'Last) := ASCII.NUL;
return Create_File (C_Name (C_Name'First)'Address, Fmode);
end Create_File;
---------------------
-- Create_New_File --
---------------------
function Create_New_File
(Name : C_File_Name;
Fmode : Mode) return File_Descriptor
is
function C_Create_New_File
(Name : C_File_Name;
Fmode : Mode) return File_Descriptor;
pragma Import (C, C_Create_New_File, "__gnat_open_new");
begin
return C_Create_New_File (Name, Fmode);
end Create_New_File;
function Create_New_File
(Name : String;
Fmode : Mode) return File_Descriptor
is
C_Name : String (1 .. Name'Length + 1);
begin
C_Name (1 .. Name'Length) := Name;
C_Name (C_Name'Last) := ASCII.NUL;
return Create_New_File (C_Name (C_Name'First)'Address, Fmode);
end Create_New_File;
-----------------------------
-- Create_Output_Text_File --
-----------------------------
function Create_Output_Text_File (Name : String) return File_Descriptor is
function C_Create_File
(Name : C_File_Name) return File_Descriptor;
pragma Import (C, C_Create_File, "__gnat_create_output_file");
C_Name : String (1 .. Name'Length + 1);
begin
C_Name (1 .. Name'Length) := Name;
C_Name (C_Name'Last) := ASCII.NUL;
return C_Create_File (C_Name (C_Name'First)'Address);
end Create_Output_Text_File;
----------------------
-- Create_Temp_File --
----------------------
procedure Create_Temp_File
(FD : out File_Descriptor;
Name : out Temp_File_Name)
is
function Open_New_Temp
(Name : System.Address;
Fmode : Mode) return File_Descriptor;
pragma Import (C, Open_New_Temp, "__gnat_open_new_temp");
begin
FD := Open_New_Temp (Name'Address, Binary);
end Create_Temp_File;
procedure Create_Temp_File
(FD : out File_Descriptor;
Name : out String_Access)
is
Pos : Positive;
Attempts : Natural := 0;
Current : String (Current_Temp_File_Name'Range);
begin
-- Loop until a new temp file can be created
File_Loop : loop
Locked : begin
-- We need to protect global variable Current_Temp_File_Name
-- against concurrent access by different tasks.
SSL.Lock_Task.all;
-- Start at the last digit
Pos := Temp_File_Name_Last_Digit;
Digit_Loop :
loop
-- Increment the digit by one
case Current_Temp_File_Name (Pos) is
when '0' .. '8' =>
Current_Temp_File_Name (Pos) :=
Character'Succ (Current_Temp_File_Name (Pos));
exit Digit_Loop;
when '9' =>
-- For 9, set the digit to 0 and go to the previous digit
Current_Temp_File_Name (Pos) := '0';
Pos := Pos - 1;
when others =>
-- If it is not a digit, then there are no available
-- temp file names. Return Invalid_FD. There is almost
-- no that this code will be ever be executed, since
-- it would mean that there are one million temp files
-- in the same directory!
SSL.Unlock_Task.all;
FD := Invalid_FD;
Name := null;
exit File_Loop;
end case;
end loop Digit_Loop;
Current := Current_Temp_File_Name;
-- We can now release the lock, because we are no longer
-- accessing Current_Temp_File_Name.
SSL.Unlock_Task.all;
exception
when others =>
SSL.Unlock_Task.all;
raise;
end Locked;
-- Attempt to create the file
FD := Create_New_File (Current, Binary);
if FD /= Invalid_FD then
Name := new String'(Current);
exit File_Loop;
end if;
if not Is_Regular_File (Current) then
-- If the file does not already exist and we are unable to create
-- it, we give up after Max_Attempts. Otherwise, we try again with
-- the next available file name.
Attempts := Attempts + 1;
if Attempts >= Max_Attempts then
FD := Invalid_FD;
Name := null;
exit File_Loop;
end if;
end if;
end loop File_Loop;
end Create_Temp_File;
-----------------
-- Delete_File --
-----------------
procedure Delete_File (Name : Address; Success : out Boolean) is
R : Integer;
function unlink (A : Address) return Integer;
pragma Import (C, unlink, "unlink");
begin
R := unlink (Name);
Success := (R = 0);
end Delete_File;
procedure Delete_File (Name : String; Success : out Boolean) is
C_Name : String (1 .. Name'Length + 1);
begin
C_Name (1 .. Name'Length) := Name;
C_Name (C_Name'Last) := ASCII.NUL;
Delete_File (C_Name'Address, Success);
end Delete_File;
---------------------
-- File_Time_Stamp --
---------------------
function File_Time_Stamp (FD : File_Descriptor) return OS_Time is
function File_Time (FD : File_Descriptor) return OS_Time;
pragma Import (C, File_Time, "__gnat_file_time_fd");
begin
return File_Time (FD);
end File_Time_Stamp;
function File_Time_Stamp (Name : C_File_Name) return OS_Time is
function File_Time (Name : Address) return OS_Time;
pragma Import (C, File_Time, "__gnat_file_time_name");
begin
return File_Time (Name);
end File_Time_Stamp;
function File_Time_Stamp (Name : String) return OS_Time is
F_Name : String (1 .. Name'Length + 1);
begin
F_Name (1 .. Name'Length) := Name;
F_Name (F_Name'Last) := ASCII.NUL;
return File_Time_Stamp (F_Name'Address);
end File_Time_Stamp;
---------------------------
-- Get_Debuggable_Suffix --
---------------------------
function Get_Debuggable_Suffix return String_Access is
procedure Get_Suffix_Ptr (Length, Ptr : Address);
pragma Import (C, Get_Suffix_Ptr, "__gnat_get_debuggable_suffix_ptr");
procedure Strncpy (Astring_Addr, Cstring : Address; N : Integer);
pragma Import (C, Strncpy, "strncpy");
Suffix_Ptr : Address;
Suffix_Length : Integer;
Result : String_Access;
begin
Get_Suffix_Ptr (Suffix_Length'Address, Suffix_Ptr'Address);
Result := new String (1 .. Suffix_Length);
if Suffix_Length > 0 then
Strncpy (Result.all'Address, Suffix_Ptr, Suffix_Length);
end if;
return Result;
end Get_Debuggable_Suffix;
---------------------------
-- Get_Executable_Suffix --
---------------------------
function Get_Executable_Suffix return String_Access is
procedure Get_Suffix_Ptr (Length, Ptr : Address);
pragma Import (C, Get_Suffix_Ptr, "__gnat_get_executable_suffix_ptr");
procedure Strncpy (Astring_Addr, Cstring : Address; N : Integer);
pragma Import (C, Strncpy, "strncpy");
Suffix_Ptr : Address;
Suffix_Length : Integer;
Result : String_Access;
begin
Get_Suffix_Ptr (Suffix_Length'Address, Suffix_Ptr'Address);
Result := new String (1 .. Suffix_Length);
if Suffix_Length > 0 then
Strncpy (Result.all'Address, Suffix_Ptr, Suffix_Length);
end if;
return Result;
end Get_Executable_Suffix;
-----------------------
-- Get_Object_Suffix --
-----------------------
function Get_Object_Suffix return String_Access is
procedure Get_Suffix_Ptr (Length, Ptr : Address);
pragma Import (C, Get_Suffix_Ptr, "__gnat_get_object_suffix_ptr");
procedure Strncpy (Astring_Addr, Cstring : Address; N : Integer);
pragma Import (C, Strncpy, "strncpy");
Suffix_Ptr : Address;
Suffix_Length : Integer;
Result : String_Access;
begin
Get_Suffix_Ptr (Suffix_Length'Address, Suffix_Ptr'Address);
Result := new String (1 .. Suffix_Length);
if Suffix_Length > 0 then
Strncpy (Result.all'Address, Suffix_Ptr, Suffix_Length);
end if;
return Result;
end Get_Object_Suffix;
----------------------------------
-- Get_Target_Debuggable_Suffix --
----------------------------------
function Get_Target_Debuggable_Suffix return String_Access is
Target_Exec_Ext_Ptr : Address;
pragma Import
(C, Target_Exec_Ext_Ptr, "__gnat_target_debuggable_extension");
procedure Strncpy (Astring_Addr, Cstring : Address; N : Integer);
pragma Import (C, Strncpy, "strncpy");
function Strlen (Cstring : Address) return Integer;
pragma Import (C, Strlen, "strlen");
Suffix_Length : Integer;
Result : String_Access;
begin
Suffix_Length := Strlen (Target_Exec_Ext_Ptr);
Result := new String (1 .. Suffix_Length);
if Suffix_Length > 0 then
Strncpy (Result.all'Address, Target_Exec_Ext_Ptr, Suffix_Length);
end if;
return Result;
end Get_Target_Debuggable_Suffix;
----------------------------------
-- Get_Target_Executable_Suffix --
----------------------------------
function Get_Target_Executable_Suffix return String_Access is
Target_Exec_Ext_Ptr : Address;
pragma Import
(C, Target_Exec_Ext_Ptr, "__gnat_target_executable_extension");
procedure Strncpy (Astring_Addr, Cstring : Address; N : Integer);
pragma Import (C, Strncpy, "strncpy");
function Strlen (Cstring : Address) return Integer;
pragma Import (C, Strlen, "strlen");
Suffix_Length : Integer;
Result : String_Access;
begin
Suffix_Length := Strlen (Target_Exec_Ext_Ptr);
Result := new String (1 .. Suffix_Length);
if Suffix_Length > 0 then
Strncpy (Result.all'Address, Target_Exec_Ext_Ptr, Suffix_Length);
end if;
return Result;
end Get_Target_Executable_Suffix;
------------------------------
-- Get_Target_Object_Suffix --
------------------------------
function Get_Target_Object_Suffix return String_Access is
Target_Object_Ext_Ptr : Address;
pragma Import
(C, Target_Object_Ext_Ptr, "__gnat_target_object_extension");
procedure Strncpy (Astring_Addr, Cstring : Address; N : Integer);
pragma Import (C, Strncpy, "strncpy");
function Strlen (Cstring : Address) return Integer;
pragma Import (C, Strlen, "strlen");
Suffix_Length : Integer;
Result : String_Access;
begin
Suffix_Length := Strlen (Target_Object_Ext_Ptr);
Result := new String (1 .. Suffix_Length);
if Suffix_Length > 0 then
Strncpy (Result.all'Address, Target_Object_Ext_Ptr, Suffix_Length);
end if;
return Result;
end Get_Target_Object_Suffix;
------------
-- Getenv --
------------
function Getenv (Name : String) return String_Access is
procedure Get_Env_Value_Ptr (Name, Length, Ptr : Address);
pragma Import (C, Get_Env_Value_Ptr, "__gnat_getenv");
procedure Strncpy (Astring_Addr, Cstring : Address; N : Integer);
pragma Import (C, Strncpy, "strncpy");
Env_Value_Ptr : aliased Address;
Env_Value_Length : aliased Integer;
F_Name : aliased String (1 .. Name'Length + 1);
Result : String_Access;
begin
F_Name (1 .. Name'Length) := Name;
F_Name (F_Name'Last) := ASCII.NUL;
Get_Env_Value_Ptr
(F_Name'Address, Env_Value_Length'Address, Env_Value_Ptr'Address);
Result := new String (1 .. Env_Value_Length);
if Env_Value_Length > 0 then
Strncpy (Result.all'Address, Env_Value_Ptr, Env_Value_Length);
end if;
return Result;
end Getenv;
------------
-- GM_Day --
------------
function GM_Day (Date : OS_Time) return Day_Type is
Y : Year_Type;
Mo : Month_Type;
D : Day_Type;
H : Hour_Type;
Mn : Minute_Type;
S : Second_Type;
begin
GM_Split (Date, Y, Mo, D, H, Mn, S);
return D;
end GM_Day;
-------------
-- GM_Hour --
-------------
function GM_Hour (Date : OS_Time) return Hour_Type is
Y : Year_Type;
Mo : Month_Type;
D : Day_Type;
H : Hour_Type;
Mn : Minute_Type;
S : Second_Type;
begin
GM_Split (Date, Y, Mo, D, H, Mn, S);
return H;
end GM_Hour;
---------------
-- GM_Minute --
---------------
function GM_Minute (Date : OS_Time) return Minute_Type is
Y : Year_Type;
Mo : Month_Type;
D : Day_Type;
H : Hour_Type;
Mn : Minute_Type;
S : Second_Type;
begin
GM_Split (Date, Y, Mo, D, H, Mn, S);
return Mn;
end GM_Minute;
--------------
-- GM_Month --
--------------
function GM_Month (Date : OS_Time) return Month_Type is
Y : Year_Type;
Mo : Month_Type;
D : Day_Type;
H : Hour_Type;
Mn : Minute_Type;
S : Second_Type;
begin
GM_Split (Date, Y, Mo, D, H, Mn, S);
return Mo;
end GM_Month;
---------------
-- GM_Second --
---------------
function GM_Second (Date : OS_Time) return Second_Type is
Y : Year_Type;
Mo : Month_Type;
D : Day_Type;
H : Hour_Type;
Mn : Minute_Type;
S : Second_Type;
begin
GM_Split (Date, Y, Mo, D, H, Mn, S);
return S;
end GM_Second;
--------------
-- GM_Split --
--------------
procedure GM_Split
(Date : OS_Time;
Year : out Year_Type;
Month : out Month_Type;
Day : out Day_Type;
Hour : out Hour_Type;
Minute : out Minute_Type;
Second : out Second_Type)
is
procedure To_GM_Time
(P_Time_T, P_Year, P_Month, P_Day, P_Hours, P_Mins, P_Secs : Address);
pragma Import (C, To_GM_Time, "__gnat_to_gm_time");
T : OS_Time := Date;
Y : Integer;
Mo : Integer;
D : Integer;
H : Integer;
Mn : Integer;
S : Integer;
begin
-- Use the global lock because To_GM_Time is not thread safe
Locked_Processing : begin
SSL.Lock_Task.all;
To_GM_Time
(T'Address, Y'Address, Mo'Address, D'Address,
H'Address, Mn'Address, S'Address);
SSL.Unlock_Task.all;
exception
when others =>
SSL.Unlock_Task.all;
raise;
end Locked_Processing;
Year := Y + 1900;
Month := Mo + 1;
Day := D;
Hour := H;
Minute := Mn;
Second := S;
end GM_Split;
-------------
-- GM_Year --
-------------
function GM_Year (Date : OS_Time) return Year_Type is
Y : Year_Type;
Mo : Month_Type;
D : Day_Type;
H : Hour_Type;
Mn : Minute_Type;
S : Second_Type;
begin
GM_Split (Date, Y, Mo, D, H, Mn, S);
return Y;
end GM_Year;
----------------------
-- Is_Absolute_Path --
----------------------
function Is_Absolute_Path (Name : String) return Boolean is
function Is_Absolute_Path
(Name : Address;
Length : Integer) return Integer;
pragma Import (C, Is_Absolute_Path, "__gnat_is_absolute_path");
begin
return Is_Absolute_Path (Name'Address, Name'Length) /= 0;
end Is_Absolute_Path;
------------------
-- Is_Directory --
------------------
function Is_Directory (Name : C_File_Name) return Boolean is
function Is_Directory (Name : Address) return Integer;
pragma Import (C, Is_Directory, "__gnat_is_directory");
begin
return Is_Directory (Name) /= 0;
end Is_Directory;
function Is_Directory (Name : String) return Boolean is
F_Name : String (1 .. Name'Length + 1);
begin
F_Name (1 .. Name'Length) := Name;
F_Name (F_Name'Last) := ASCII.NUL;
return Is_Directory (F_Name'Address);
end Is_Directory;
----------------------
-- Is_Readable_File --
----------------------
function Is_Readable_File (Name : C_File_Name) return Boolean is
function Is_Readable_File (Name : Address) return Integer;
pragma Import (C, Is_Readable_File, "__gnat_is_readable_file");
begin
return Is_Readable_File (Name) /= 0;
end Is_Readable_File;
function Is_Readable_File (Name : String) return Boolean is
F_Name : String (1 .. Name'Length + 1);
begin
F_Name (1 .. Name'Length) := Name;
F_Name (F_Name'Last) := ASCII.NUL;
return Is_Readable_File (F_Name'Address);
end Is_Readable_File;
---------------------
-- Is_Regular_File --
---------------------
function Is_Regular_File (Name : C_File_Name) return Boolean is
function Is_Regular_File (Name : Address) return Integer;
pragma Import (C, Is_Regular_File, "__gnat_is_regular_file");
begin
return Is_Regular_File (Name) /= 0;
end Is_Regular_File;
function Is_Regular_File (Name : String) return Boolean is
F_Name : String (1 .. Name'Length + 1);
begin
F_Name (1 .. Name'Length) := Name;
F_Name (F_Name'Last) := ASCII.NUL;
return Is_Regular_File (F_Name'Address);
end Is_Regular_File;
----------------------
-- Is_Symbolic_Link --
----------------------
function Is_Symbolic_Link (Name : C_File_Name) return Boolean is
function Is_Symbolic_Link (Name : Address) return Integer;
pragma Import (C, Is_Symbolic_Link, "__gnat_is_symbolic_link");
begin
return Is_Symbolic_Link (Name) /= 0;
end Is_Symbolic_Link;
function Is_Symbolic_Link (Name : String) return Boolean is
F_Name : String (1 .. Name'Length + 1);
begin
F_Name (1 .. Name'Length) := Name;
F_Name (F_Name'Last) := ASCII.NUL;
return Is_Symbolic_Link (F_Name'Address);
end Is_Symbolic_Link;
----------------------
-- Is_Writable_File --
----------------------
function Is_Writable_File (Name : C_File_Name) return Boolean is
function Is_Writable_File (Name : Address) return Integer;
pragma Import (C, Is_Writable_File, "__gnat_is_writable_file");
begin
return Is_Writable_File (Name) /= 0;
end Is_Writable_File;
function Is_Writable_File (Name : String) return Boolean is
F_Name : String (1 .. Name'Length + 1);
begin
F_Name (1 .. Name'Length) := Name;
F_Name (F_Name'Last) := ASCII.NUL;
return Is_Writable_File (F_Name'Address);
end Is_Writable_File;
-------------------------
-- Locate_Exec_On_Path --
-------------------------
function Locate_Exec_On_Path
(Exec_Name : String) return String_Access
is
function Locate_Exec_On_Path (C_Exec_Name : Address) return Address;
pragma Import (C, Locate_Exec_On_Path, "__gnat_locate_exec_on_path");
procedure Free (Ptr : System.Address);
pragma Import (C, Free, "free");
C_Exec_Name : String (1 .. Exec_Name'Length + 1);
Path_Addr : Address;
Path_Len : Integer;
Result : String_Access;
begin
C_Exec_Name (1 .. Exec_Name'Length) := Exec_Name;
C_Exec_Name (C_Exec_Name'Last) := ASCII.NUL;
Path_Addr := Locate_Exec_On_Path (C_Exec_Name'Address);
Path_Len := C_String_Length (Path_Addr);
if Path_Len = 0 then
return null;
else
Result := To_Path_String_Access (Path_Addr, Path_Len);
Free (Path_Addr);
-- Always return an absolute path name
if not Is_Absolute_Path (Result.all) then
declare
Absolute_Path : constant String :=
Normalize_Pathname (Result.all);
begin
Free (Result);
Result := new String'(Absolute_Path);
end;
end if;
return Result;
end if;
end Locate_Exec_On_Path;
-------------------------
-- Locate_Regular_File --
-------------------------
function Locate_Regular_File
(File_Name : C_File_Name;
Path : C_File_Name) return String_Access
is
function Locate_Regular_File
(C_File_Name, Path_Val : Address) return Address;
pragma Import (C, Locate_Regular_File, "__gnat_locate_regular_file");
procedure Free (Ptr : System.Address);
pragma Import (C, Free, "free");
Path_Addr : Address;
Path_Len : Integer;
Result : String_Access;
begin
Path_Addr := Locate_Regular_File (File_Name, Path);
Path_Len := C_String_Length (Path_Addr);
if Path_Len = 0 then
return null;
else
Result := To_Path_String_Access (Path_Addr, Path_Len);
Free (Path_Addr);
return Result;
end if;
end Locate_Regular_File;
function Locate_Regular_File
(File_Name : String;
Path : String) return String_Access
is
C_File_Name : String (1 .. File_Name'Length + 1);
C_Path : String (1 .. Path'Length + 1);
Result : String_Access;
begin
C_File_Name (1 .. File_Name'Length) := File_Name;
C_File_Name (C_File_Name'Last) := ASCII.NUL;
C_Path (1 .. Path'Length) := Path;
C_Path (C_Path'Last) := ASCII.NUL;
Result := Locate_Regular_File (C_File_Name'Address, C_Path'Address);
-- Always return an absolute path name
if Result /= null and then not Is_Absolute_Path (Result.all) then
declare
Absolute_Path : constant String := Normalize_Pathname (Result.all);
begin
Free (Result);
Result := new String'(Absolute_Path);
end;
end if;
return Result;
end Locate_Regular_File;
------------------------
-- Non_Blocking_Spawn --
------------------------
function Non_Blocking_Spawn
(Program_Name : String;
Args : Argument_List) return Process_Id
is
Junk : Integer;
Pid : Process_Id;
begin
Spawn_Internal (Program_Name, Args, Junk, Pid, Blocking => False);
return Pid;
end Non_Blocking_Spawn;
function Non_Blocking_Spawn
(Program_Name : String;
Args : Argument_List;
Output_File_Descriptor : File_Descriptor;
Err_To_Out : Boolean := True) return Process_Id
is
Saved_Output : File_Descriptor;
Saved_Error : File_Descriptor := Invalid_FD; -- prevent warning
Pid : Process_Id;
begin
if Output_File_Descriptor = Invalid_FD then
return Invalid_Pid;
end if;
-- Set standard output and, if specified, error to the temporary file
Saved_Output := Dup (Standout);
Dup2 (Output_File_Descriptor, Standout);
if Err_To_Out then
Saved_Error := Dup (Standerr);
Dup2 (Output_File_Descriptor, Standerr);
end if;
-- Spawn the program
Pid := Non_Blocking_Spawn (Program_Name, Args);
-- Restore the standard output and error
Dup2 (Saved_Output, Standout);
if Err_To_Out then
Dup2 (Saved_Error, Standerr);
end if;
-- And close the saved standard output and error file descriptors
Close (Saved_Output);
if Err_To_Out then
Close (Saved_Error);
end if;
return Pid;
end Non_Blocking_Spawn;
function Non_Blocking_Spawn
(Program_Name : String;
Args : Argument_List;
Output_File : String;
Err_To_Out : Boolean := True) return Process_Id
is
Output_File_Descriptor : constant File_Descriptor :=
Create_Output_Text_File (Output_File);
Result : Process_Id;
begin
-- Do not attempt to spawn if the output file could not be created
if Output_File_Descriptor = Invalid_FD then
return Invalid_Pid;
else
Result := Non_Blocking_Spawn
(Program_Name, Args, Output_File_Descriptor, Err_To_Out);
-- Close the file just created for the output, as the file descriptor
-- cannot be used anywhere, being a local value. It is safe to do
-- that, as the file descriptor has been duplicated to form
-- standard output and error of the spawned process.
Close (Output_File_Descriptor);
return Result;
end if;
end Non_Blocking_Spawn;
-------------------------
-- Normalize_Arguments --
-------------------------
procedure Normalize_Arguments (Args : in out Argument_List) is
procedure Quote_Argument (Arg : in out String_Access);
-- Add quote around argument if it contains spaces
C_Argument_Needs_Quote : Integer;
pragma Import (C, C_Argument_Needs_Quote, "__gnat_argument_needs_quote");
Argument_Needs_Quote : constant Boolean := C_Argument_Needs_Quote /= 0;
--------------------
-- Quote_Argument --
--------------------
procedure Quote_Argument (Arg : in out String_Access) is
Res : String (1 .. Arg'Length * 2);
J : Positive := 1;
Quote_Needed : Boolean := False;
begin
if Arg (Arg'First) /= '"' or else Arg (Arg'Last) /= '"' then
-- Starting quote
Res (J) := '"';
for K in Arg'Range loop
J := J + 1;
if Arg (K) = '"' then
Res (J) := '\';
J := J + 1;
Res (J) := '"';
Quote_Needed := True;
elsif Arg (K) = ' ' then
Res (J) := Arg (K);
Quote_Needed := True;
else
Res (J) := Arg (K);
end if;
end loop;
if Quote_Needed then
-- If null terminated string, put the quote before
if Res (J) = ASCII.Nul then
Res (J) := '"';
J := J + 1;
Res (J) := ASCII.Nul;
-- If argument is terminated by '\', then double it. Otherwise
-- the ending quote will be taken as-is. This is quite strange
-- spawn behavior from Windows, but this is what we see!
else
if Res (J) = '\' then
J := J + 1;
Res (J) := '\';
end if;
-- Ending quote
J := J + 1;
Res (J) := '"';
end if;
declare
Old : String_Access := Arg;
begin
Arg := new String'(Res (1 .. J));
Free (Old);
end;
end if;
end if;
end Quote_Argument;
-- Start of processing for Normalize_Arguments
begin
if Argument_Needs_Quote then
for K in Args'Range loop
if Args (K) /= null and then Args (K)'Length /= 0 then
Quote_Argument (Args (K));
end if;
end loop;
end if;
end Normalize_Arguments;
------------------------
-- Normalize_Pathname --
------------------------
function Normalize_Pathname
(Name : String;
Directory : String := "";
Resolve_Links : Boolean := True;
Case_Sensitive : Boolean := True) return String
is
Max_Path : Integer;
pragma Import (C, Max_Path, "__gnat_max_path_len");
-- Maximum length of a path name
procedure Get_Current_Dir
(Dir : System.Address;
Length : System.Address);
pragma Import (C, Get_Current_Dir, "__gnat_get_current_dir");
Path_Buffer : String (1 .. Max_Path + Max_Path + 2);
End_Path : Natural := 0;
Link_Buffer : String (1 .. Max_Path + 2);
Status : Integer;
Last : Positive;
Start : Natural;
Finish : Positive;
Max_Iterations : constant := 500;
function Get_File_Names_Case_Sensitive return Integer;
pragma Import
(C, Get_File_Names_Case_Sensitive,
"__gnat_get_file_names_case_sensitive");
Fold_To_Lower_Case : constant Boolean :=
not Case_Sensitive
and then Get_File_Names_Case_Sensitive = 0;
function Readlink
(Path : System.Address;
Buf : System.Address;
Bufsiz : Integer) return Integer;
pragma Import (C, Readlink, "__gnat_readlink");
function To_Canonical_File_Spec
(Host_File : System.Address) return System.Address;
pragma Import
(C, To_Canonical_File_Spec, "__gnat_to_canonical_file_spec");
The_Name : String (1 .. Name'Length + 1);
Canonical_File_Addr : System.Address;
Canonical_File_Len : Integer;
Need_To_Check_Drive_Letter : Boolean := False;
-- Set to true if Name is an absolute path that starts with "//"
function Strlen (S : System.Address) return Integer;
pragma Import (C, Strlen, "strlen");
function Final_Value (S : String) return String;
-- Make final adjustment to the returned string.
-- To compensate for non standard path name in Interix,
-- if S is "/x" or starts with "/x", where x is a capital
-- letter 'A' to 'Z', add an additional '/' at the beginning
-- so that the returned value starts with "//x".
function Get_Directory (Dir : String) return String;
-- If Dir is not empty, return it, adding a directory separator
-- if not already present, otherwise return current working directory
-- with terminating directory separator.
-----------------
-- Final_Value --
-----------------
function Final_Value (S : String) return String is
S1 : String := S;
-- We may need to fold S to lower case, so we need a variable
Last : Natural;
begin
-- Interix has the non standard notion of disk drive
-- indicated by two '/' followed by a capital letter
-- 'A' .. 'Z'. One of the two '/' may have been removed
-- by Normalize_Pathname. It has to be added again.
-- For other OSes, this should not make no difference.
if Need_To_Check_Drive_Letter
and then S'Length >= 2
and then S (S'First) = '/'
and then S (S'First + 1) in 'A' .. 'Z'
and then (S'Length = 2 or else S (S'First + 2) = '/')
then
declare
Result : String (1 .. S'Length + 1);
begin
Result (1) := '/';
Result (2 .. Result'Last) := S;
Last := Result'Last;
if Fold_To_Lower_Case then
System.Case_Util.To_Lower (Result);
end if;
-- Remove trailing directory separator, if any
if Last > 1 and then
(Result (Last) = '/' or else
Result (Last) = Directory_Separator)
then
Last := Last - 1;
end if;
return Result (1 .. Last);
end;
else
if Fold_To_Lower_Case then
System.Case_Util.To_Lower (S1);
end if;
-- Remove trailing directory separator, if any
Last := S1'Last;
if Last > 1
and then (S1 (Last) = '/'
or else
S1 (Last) = Directory_Separator)
then
-- Special case for Windows: C:\
if Last = 3
and then S1 (1) /= Directory_Separator
and then S1 (2) = ':'
then
null;
else
Last := Last - 1;
end if;
end if;
return S1 (1 .. Last);
end if;
end Final_Value;
-------------------
-- Get_Directory --
-------------------
function Get_Directory (Dir : String) return String is
begin
-- Directory given, add directory separator if needed
if Dir'Length > 0 then
if Dir (Dir'Last) = Directory_Separator then
return Dir;
else
declare
Result : String (1 .. Dir'Length + 1);
begin
Result (1 .. Dir'Length) := Dir;
Result (Result'Length) := Directory_Separator;
return Result;
end;
end if;
-- Directory name not given, get current directory
else
declare
Buffer : String (1 .. Max_Path + 2);
Path_Len : Natural := Max_Path;
begin
Get_Current_Dir (Buffer'Address, Path_Len'Address);
if Buffer (Path_Len) /= Directory_Separator then
Path_Len := Path_Len + 1;
Buffer (Path_Len) := Directory_Separator;
end if;
-- By default, the drive letter on Windows is in upper case
if On_Windows and then Path_Len >= 2 and then
Buffer (2) = ':'
then
System.Case_Util.To_Upper (Buffer (1 .. 1));
end if;
return Buffer (1 .. Path_Len);
end;
end if;
end Get_Directory;
Reference_Dir : constant String := Get_Directory (Directory);
-- Current directory name specified
-- Start of processing for Normalize_Pathname
begin
-- Special case, if name is null, then return null
if Name'Length = 0 then
return "";
end if;
-- First, convert VMS file spec to Unix file spec.
-- If Name is not in VMS syntax, then this is equivalent
-- to put Name at the begining of Path_Buffer.
VMS_Conversion : begin
The_Name (1 .. Name'Length) := Name;
The_Name (The_Name'Last) := ASCII.NUL;
Canonical_File_Addr := To_Canonical_File_Spec (The_Name'Address);
Canonical_File_Len := Strlen (Canonical_File_Addr);
-- If VMS syntax conversion has failed, return an empty string
-- to indicate the failure.
if Canonical_File_Len = 0 then
return "";
end if;
declare
subtype Path_String is String (1 .. Canonical_File_Len);
type Path_String_Access is access Path_String;
function Address_To_Access is new
Ada.Unchecked_Conversion (Source => Address,
Target => Path_String_Access);
Path_Access : constant Path_String_Access :=
Address_To_Access (Canonical_File_Addr);
begin
Path_Buffer (1 .. Canonical_File_Len) := Path_Access.all;
End_Path := Canonical_File_Len;
Last := 1;
end;
end VMS_Conversion;
-- Replace all '/' by Directory Separators (this is for Windows)
if Directory_Separator /= '/' then
for Index in 1 .. End_Path loop
if Path_Buffer (Index) = '/' then
Path_Buffer (Index) := Directory_Separator;
end if;
end loop;
end if;
-- Resolve directory names for Windows (formerly also VMS)
-- On VMS, if we have a Unix path such as /temp/..., and TEMP is a
-- logical name, we must not try to resolve this logical name, because
-- it may have multiple equivalences and if resolved we will only
-- get the first one.
-- On Windows, if we have an absolute path starting with a directory
-- separator, we need to have the drive letter appended in front.
-- On Windows, Get_Current_Dir will return a suitable directory
-- name (path starting with a drive letter on Windows). So we take this
-- drive letter and prepend it to the current path.
if On_Windows
and then Path_Buffer (1) = Directory_Separator
and then Path_Buffer (2) /= Directory_Separator
then
declare
Cur_Dir : String := Get_Directory ("");
-- Get the current directory to get the drive letter
begin
if Cur_Dir'Length > 2
and then Cur_Dir (Cur_Dir'First + 1) = ':'
then
Path_Buffer (3 .. End_Path + 2) := Path_Buffer (1 .. End_Path);
Path_Buffer (1 .. 2) :=
Cur_Dir (Cur_Dir'First .. Cur_Dir'First + 1);
End_Path := End_Path + 2;
end if;
end;
end if;
-- Start the conversions
-- If this is not finished after Max_Iterations, give up and return an
-- empty string.
for J in 1 .. Max_Iterations loop
-- If we don't have an absolute pathname, prepend the directory
-- Reference_Dir.
if Last = 1
and then not Is_Absolute_Path (Path_Buffer (1 .. End_Path))
then
Path_Buffer
(Reference_Dir'Length + 1 .. Reference_Dir'Length + End_Path) :=
Path_Buffer (1 .. End_Path);
End_Path := Reference_Dir'Length + End_Path;
Path_Buffer (1 .. Reference_Dir'Length) := Reference_Dir;
Last := Reference_Dir'Length;
end if;
-- If name starts with "//", we may have a drive letter on Interix
if Last = 1 and then End_Path >= 3 then
Need_To_Check_Drive_Letter := (Path_Buffer (1 .. 2)) = "//";
end if;
Start := Last + 1;
Finish := Last;
-- Ensure that Windows network drives are kept, e.g: \\server\drive-c
if Start = 2
and then Directory_Separator = '\'
and then Path_Buffer (1 .. 2) = "\\"
then
Start := 3;
end if;
-- If we have traversed the full pathname, return it
if Start > End_Path then
return Final_Value (Path_Buffer (1 .. End_Path));
end if;
-- Remove duplicate directory separators
while Path_Buffer (Start) = Directory_Separator loop
if Start = End_Path then
return Final_Value (Path_Buffer (1 .. End_Path - 1));
else
Path_Buffer (Start .. End_Path - 1) :=
Path_Buffer (Start + 1 .. End_Path);
End_Path := End_Path - 1;
end if;
end loop;
-- Find the end of the current field: last character or the one
-- preceding the next directory separator.
while Finish < End_Path
and then Path_Buffer (Finish + 1) /= Directory_Separator
loop
Finish := Finish + 1;
end loop;
-- Remove "." field
if Start = Finish and then Path_Buffer (Start) = '.' then
if Start = End_Path then
if Last = 1 then
return (1 => Directory_Separator);
else
if Fold_To_Lower_Case then
System.Case_Util.To_Lower (Path_Buffer (1 .. Last - 1));
end if;
return Path_Buffer (1 .. Last - 1);
end if;
else
Path_Buffer (Last + 1 .. End_Path - 2) :=
Path_Buffer (Last + 3 .. End_Path);
End_Path := End_Path - 2;
end if;
-- Remove ".." fields
elsif Finish = Start + 1
and then Path_Buffer (Start .. Finish) = ".."
then
Start := Last;
loop
Start := Start - 1;
exit when Start < 1 or else
Path_Buffer (Start) = Directory_Separator;
end loop;
if Start <= 1 then
if Finish = End_Path then
return (1 => Directory_Separator);
else
Path_Buffer (1 .. End_Path - Finish) :=
Path_Buffer (Finish + 1 .. End_Path);
End_Path := End_Path - Finish;
Last := 1;
end if;
else
if Finish = End_Path then
return Final_Value (Path_Buffer (1 .. Start - 1));
else
Path_Buffer (Start + 1 .. Start + End_Path - Finish - 1) :=
Path_Buffer (Finish + 2 .. End_Path);
End_Path := Start + End_Path - Finish - 1;
Last := Start;
end if;
end if;
-- Check if current field is a symbolic link
elsif Resolve_Links then
declare
Saved : constant Character := Path_Buffer (Finish + 1);
begin
Path_Buffer (Finish + 1) := ASCII.NUL;
Status := Readlink (Path_Buffer'Address,
Link_Buffer'Address,
Link_Buffer'Length);
Path_Buffer (Finish + 1) := Saved;
end;
-- Not a symbolic link, move to the next field, if any
if Status <= 0 then
Last := Finish + 1;
-- Replace symbolic link with its value
else
if Is_Absolute_Path (Link_Buffer (1 .. Status)) then
Path_Buffer (Status + 1 .. End_Path - (Finish - Status)) :=
Path_Buffer (Finish + 1 .. End_Path);
End_Path := End_Path - (Finish - Status);
Path_Buffer (1 .. Status) := Link_Buffer (1 .. Status);
Last := 1;
else
Path_Buffer
(Last + Status + 1 .. End_Path - Finish + Last + Status) :=
Path_Buffer (Finish + 1 .. End_Path);
End_Path := End_Path - Finish + Last + Status;
Path_Buffer (Last + 1 .. Last + Status) :=
Link_Buffer (1 .. Status);
end if;
end if;
else
Last := Finish + 1;
end if;
end loop;
-- Too many iterations: give up
-- This can happen when there is a circularity in the symbolic links: A
-- is a symbolic link for B, which itself is a symbolic link, and the
-- target of B or of another symbolic link target of B is A. In this
-- case, we return an empty string to indicate failure to resolve.
return "";
end Normalize_Pathname;
---------------
-- Open_Read --
---------------
function Open_Read
(Name : C_File_Name;
Fmode : Mode) return File_Descriptor
is
function C_Open_Read
(Name : C_File_Name;
Fmode : Mode) return File_Descriptor;
pragma Import (C, C_Open_Read, "__gnat_open_read");
begin
return C_Open_Read (Name, Fmode);
end Open_Read;
function Open_Read
(Name : String;
Fmode : Mode) return File_Descriptor
is
C_Name : String (1 .. Name'Length + 1);
begin
C_Name (1 .. Name'Length) := Name;
C_Name (C_Name'Last) := ASCII.NUL;
return Open_Read (C_Name (C_Name'First)'Address, Fmode);
end Open_Read;
---------------------
-- Open_Read_Write --
---------------------
function Open_Read_Write
(Name : C_File_Name;
Fmode : Mode) return File_Descriptor
is
function C_Open_Read_Write
(Name : C_File_Name;
Fmode : Mode) return File_Descriptor;
pragma Import (C, C_Open_Read_Write, "__gnat_open_rw");
begin
return C_Open_Read_Write (Name, Fmode);
end Open_Read_Write;
function Open_Read_Write
(Name : String;
Fmode : Mode) return File_Descriptor
is
C_Name : String (1 .. Name'Length + 1);
begin
C_Name (1 .. Name'Length) := Name;
C_Name (C_Name'Last) := ASCII.NUL;
return Open_Read_Write (C_Name (C_Name'First)'Address, Fmode);
end Open_Read_Write;
--------------------
-- Pid_To_Integer --
--------------------
function Pid_To_Integer (Pid : Process_Id) return Integer is
begin
return Integer (Pid);
end Pid_To_Integer;
----------
-- Read --
----------
function Read
(FD : File_Descriptor;
A : System.Address;
N : Integer) return Integer
is
begin
return Integer (System.CRTL.read
(System.CRTL.int (FD), System.CRTL.chars (A), System.CRTL.int (N)));
end Read;
-----------------
-- Rename_File --
-----------------
procedure Rename_File
(Old_Name : C_File_Name;
New_Name : C_File_Name;
Success : out Boolean)
is
function rename (From, To : Address) return Integer;
pragma Import (C, rename, "rename");
R : Integer;
begin
R := rename (Old_Name, New_Name);
Success := (R = 0);
end Rename_File;
procedure Rename_File
(Old_Name : String;
New_Name : String;
Success : out Boolean)
is
C_Old_Name : String (1 .. Old_Name'Length + 1);
C_New_Name : String (1 .. New_Name'Length + 1);
begin
C_Old_Name (1 .. Old_Name'Length) := Old_Name;
C_Old_Name (C_Old_Name'Last) := ASCII.NUL;
C_New_Name (1 .. New_Name'Length) := New_Name;
C_New_Name (C_New_Name'Last) := ASCII.NUL;
Rename_File (C_Old_Name'Address, C_New_Name'Address, Success);
end Rename_File;
-----------------------
-- Set_Close_On_Exec --
-----------------------
procedure Set_Close_On_Exec
(FD : File_Descriptor;
Close_On_Exec : Boolean;
Status : out Boolean)
is
function C_Set_Close_On_Exec
(FD : File_Descriptor; Close_On_Exec : System.CRTL.int)
return System.CRTL.int;
pragma Import (C, C_Set_Close_On_Exec, "__gnat_set_close_on_exec");
begin
Status := C_Set_Close_On_Exec (FD, Boolean'Pos (Close_On_Exec)) = 0;
end Set_Close_On_Exec;
--------------------
-- Set_Executable --
--------------------
procedure Set_Executable (Name : String) is
procedure C_Set_Executable (Name : C_File_Name);
pragma Import (C, C_Set_Executable, "__gnat_set_executable");
C_Name : aliased String (Name'First .. Name'Last + 1);
begin
C_Name (Name'Range) := Name;
C_Name (C_Name'Last) := ASCII.NUL;
C_Set_Executable (C_Name (C_Name'First)'Address);
end Set_Executable;
--------------------
-- Set_Read_Only --
--------------------
procedure Set_Read_Only (Name : String) is
procedure C_Set_Read_Only (Name : C_File_Name);
pragma Import (C, C_Set_Read_Only, "__gnat_set_readonly");
C_Name : aliased String (Name'First .. Name'Last + 1);
begin
C_Name (Name'Range) := Name;
C_Name (C_Name'Last) := ASCII.NUL;
C_Set_Read_Only (C_Name (C_Name'First)'Address);
end Set_Read_Only;
--------------------
-- Set_Writable --
--------------------
procedure Set_Writable (Name : String) is
procedure C_Set_Writable (Name : C_File_Name);
pragma Import (C, C_Set_Writable, "__gnat_set_writable");
C_Name : aliased String (Name'First .. Name'Last + 1);
begin
C_Name (Name'Range) := Name;
C_Name (C_Name'Last) := ASCII.NUL;
C_Set_Writable (C_Name (C_Name'First)'Address);
end Set_Writable;
------------
-- Setenv --
------------
procedure Setenv (Name : String; Value : String) is
F_Name : String (1 .. Name'Length + 1);
F_Value : String (1 .. Value'Length + 1);
procedure Set_Env_Value (Name, Value : System.Address);
pragma Import (C, Set_Env_Value, "__gnat_setenv");
begin
F_Name (1 .. Name'Length) := Name;
F_Name (F_Name'Last) := ASCII.NUL;
F_Value (1 .. Value'Length) := Value;
F_Value (F_Value'Last) := ASCII.NUL;
Set_Env_Value (F_Name'Address, F_Value'Address);
end Setenv;
-----------
-- Spawn --
-----------
function Spawn
(Program_Name : String;
Args : Argument_List) return Integer
is
Junk : Process_Id;
Result : Integer;
begin
Spawn_Internal (Program_Name, Args, Result, Junk, Blocking => True);
return Result;
end Spawn;
procedure Spawn
(Program_Name : String;
Args : Argument_List;
Success : out Boolean)
is
begin
Success := (Spawn (Program_Name, Args) = 0);
end Spawn;
procedure Spawn
(Program_Name : String;
Args : Argument_List;
Output_File_Descriptor : File_Descriptor;
Return_Code : out Integer;
Err_To_Out : Boolean := True)
is
Saved_Output : File_Descriptor;
Saved_Error : File_Descriptor := Invalid_FD; -- prevent compiler warning
begin
-- Set standard output and error to the temporary file
Saved_Output := Dup (Standout);
Dup2 (Output_File_Descriptor, Standout);
if Err_To_Out then
Saved_Error := Dup (Standerr);
Dup2 (Output_File_Descriptor, Standerr);
end if;
-- Spawn the program
Return_Code := Spawn (Program_Name, Args);
-- Restore the standard output and error
Dup2 (Saved_Output, Standout);
if Err_To_Out then
Dup2 (Saved_Error, Standerr);
end if;
-- And close the saved standard output and error file descriptors
Close (Saved_Output);
if Err_To_Out then
Close (Saved_Error);
end if;
end Spawn;
procedure Spawn
(Program_Name : String;
Args : Argument_List;
Output_File : String;
Success : out Boolean;
Return_Code : out Integer;
Err_To_Out : Boolean := True)
is
FD : File_Descriptor;
begin
Success := True;
Return_Code := 0;
FD := Create_Output_Text_File (Output_File);
if FD = Invalid_FD then
Success := False;
return;
end if;
Spawn (Program_Name, Args, FD, Return_Code, Err_To_Out);
Close (FD, Success);
end Spawn;
--------------------
-- Spawn_Internal --
--------------------
procedure Spawn_Internal
(Program_Name : String;
Args : Argument_List;
Result : out Integer;
Pid : out Process_Id;
Blocking : Boolean)
is
procedure Spawn (Args : Argument_List);
-- Call Spawn with given argument list
N_Args : Argument_List (Args'Range);
-- Normalized arguments
-----------
-- Spawn --
-----------
procedure Spawn (Args : Argument_List) is
type Chars is array (Positive range <>) of aliased Character;
type Char_Ptr is access constant Character;
Command_Len : constant Positive := Program_Name'Length + 1
+ Args_Length (Args);
Command_Last : Natural := 0;
Command : aliased Chars (1 .. Command_Len);
-- Command contains all characters of the Program_Name and Args, all
-- terminated by ASCII.NUL characters
Arg_List_Len : constant Positive := Args'Length + 2;
Arg_List_Last : Natural := 0;
Arg_List : aliased array (1 .. Arg_List_Len) of Char_Ptr;
-- List with pointers to NUL-terminated strings of the Program_Name
-- and the Args and terminated with a null pointer. We rely on the
-- default initialization for the last null pointer.
procedure Add_To_Command (S : String);
-- Add S and a NUL character to Command, updating Last
function Portable_Spawn (Args : Address) return Integer;
pragma Import (C, Portable_Spawn, "__gnat_portable_spawn");
function Portable_No_Block_Spawn (Args : Address) return Process_Id;
pragma Import
(C, Portable_No_Block_Spawn, "__gnat_portable_no_block_spawn");
--------------------
-- Add_To_Command --
--------------------
procedure Add_To_Command (S : String) is
First : constant Natural := Command_Last + 1;
begin
Command_Last := Command_Last + S'Length;
-- Move characters one at a time, because Command has aliased
-- components.
-- But not volatile, so why is this necessary ???
for J in S'Range loop
Command (First + J - S'First) := S (J);
end loop;
Command_Last := Command_Last + 1;
Command (Command_Last) := ASCII.NUL;
Arg_List_Last := Arg_List_Last + 1;
Arg_List (Arg_List_Last) := Command (First)'Access;
end Add_To_Command;
-- Start of processing for Spawn
begin
Add_To_Command (Program_Name);
for J in Args'Range loop
Add_To_Command (Args (J).all);
end loop;
if Blocking then
Pid := Invalid_Pid;
Result := Portable_Spawn (Arg_List'Address);
else
Pid := Portable_No_Block_Spawn (Arg_List'Address);
Result := Boolean'Pos (Pid /= Invalid_Pid);
end if;
end Spawn;
-- Start of processing for Spawn_Internal
begin
-- Copy arguments into a local structure
for K in N_Args'Range loop
N_Args (K) := new String'(Args (K).all);
end loop;
-- Normalize those arguments
Normalize_Arguments (N_Args);
-- Call spawn using the normalized arguments
Spawn (N_Args);
-- Free arguments list
for K in N_Args'Range loop
Free (N_Args (K));
end loop;
end Spawn_Internal;
---------------------------
-- To_Path_String_Access --
---------------------------
function To_Path_String_Access
(Path_Addr : Address;
Path_Len : Integer) return String_Access
is
subtype Path_String is String (1 .. Path_Len);
type Path_String_Access is access Path_String;
function Address_To_Access is new
Ada.Unchecked_Conversion (Source => Address,
Target => Path_String_Access);
Path_Access : constant Path_String_Access :=
Address_To_Access (Path_Addr);
Return_Val : String_Access;
begin
Return_Val := new String (1 .. Path_Len);
for J in 1 .. Path_Len loop
Return_Val (J) := Path_Access (J);
end loop;
return Return_Val;
end To_Path_String_Access;
------------------
-- Wait_Process --
------------------
procedure Wait_Process (Pid : out Process_Id; Success : out Boolean) is
Status : Integer;
function Portable_Wait (S : Address) return Process_Id;
pragma Import (C, Portable_Wait, "__gnat_portable_wait");
begin
Pid := Portable_Wait (Status'Address);
Success := (Status = 0);
end Wait_Process;
-----------
-- Write --
-----------
function Write
(FD : File_Descriptor;
A : System.Address;
N : Integer) return Integer
is
begin
return Integer (System.CRTL.write
(System.CRTL.int (FD), System.CRTL.chars (A), System.CRTL.int (N)));
end Write;
end System.OS_Lib;
------------------------------------------------------------------------------
-- --
-- GNAT COMPILER COMPONENTS --
-- --
-- S Y S T E M . O S _ L I B --
-- --
-- S p e c --
-- --
-- Copyright (C) 1995-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- ware Foundation; either version 2, or (at your option) any later ver- --
-- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
-- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
-- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
-- for more details. You should have received a copy of the GNU General --
-- Public License distributed with GNAT; see file COPYING. If not, write --
-- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
-- Boston, MA 02110-1301, USA. --
-- --
-- As a special exception, if other files instantiate generics from this --
-- unit, or you link this unit with other files to produce an executable, --
-- this unit does not by itself cause the resulting executable to be --
-- covered by the GNU General Public License. This exception does not --
-- however invalidate any other reasons why the executable file might be --
-- covered by the GNU Public License. --
-- --
-- GNAT was originally developed by the GNAT team at New York University. --
-- Extensive contributions were provided by Ada Core Technologies Inc. --
-- --
------------------------------------------------------------------------------
-- Operating system interface facilities
-- This package contains types and procedures for interfacing to the
-- underlying OS. It is used by the GNAT compiler and by tools associated
-- with the GNAT compiler, and therefore works for the various operating
-- systems to which GNAT has been ported. This package will undoubtedly grow
-- as new services are needed by various tools.
-- This package tends to use fairly low-level Ada in order to not bring in
-- large portions of the RTL. For example, functions return access to string
-- as part of avoiding functions returning unconstrained types.
-- Except where specifically noted, these routines are portable across all
-- GNAT implementations on all supported operating systems.
-- Note: this package is in the System hierarchy so that it can be directly
-- be used by other predefined packages. User access to this package is via
-- a renaming of this package in GNAT.OS_Lib (file g-os_lib.ads).
with System;
with System.Strings;
package System.OS_Lib is
pragma Elaborate_Body (OS_Lib);
-----------------------
-- String Operations --
-----------------------
-- These are reexported from package Strings (which was introduced to
-- avoid different packages declarting different types unnecessarily).
-- See package System.Strings for details.
subtype String_Access is Strings.String_Access;
function "=" (Left, Right : String_Access) return Boolean
renames Strings."=";
procedure Free (X : in out String_Access) renames Strings.Free;
subtype String_List is Strings.String_List;
function "=" (Left, Right : String_List) return Boolean
renames Strings."=";
function "&" (Left : String_Access; Right : String_Access)
return String_List renames Strings."&";
function "&" (Left : String_Access; Right : String_List)
return String_List renames Strings."&";
function "&" (Left : String_List; Right : String_Access)
return String_List renames Strings."&";
function "&" (Left : String_List; Right : String_List)
return String_List renames Strings."&";
subtype String_List_Access is Strings.String_List_Access;
function "=" (Left, Right : String_List_Access) return Boolean
renames Strings."=";
procedure Free (Arg : in out String_List_Access)
renames Strings.Free;
---------------------
-- Time/Date Stuff --
---------------------
type OS_Time is private;
-- The OS's notion of time is represented by the private type OS_Time.
-- This is the type returned by the File_Time_Stamp functions to obtain
-- the time stamp of a specified file. Functions and a procedure (modeled
-- after the similar subprograms in package Calendar) are provided for
-- extracting information from a value of this type. Although these are
-- called GM, the intention is not that they provide GMT times in all
-- cases but rather the actual (time-zone independent) time stamp of the
-- file (of course in Unix systems, this *is* in GMT form).
Invalid_Time : constant OS_Time;
-- A special unique value used to flag an invalid time stamp value
subtype Year_Type is Integer range 1900 .. 2099;
subtype Month_Type is Integer range 1 .. 12;
subtype Day_Type is Integer range 1 .. 31;
subtype Hour_Type is Integer range 0 .. 23;
subtype Minute_Type is Integer range 0 .. 59;
subtype Second_Type is Integer range 0 .. 59;
-- Declarations similar to those in Calendar, breaking down the time
function Current_Time return OS_Time;
-- Return the system clock value as OS_Time
function GM_Year (Date : OS_Time) return Year_Type;
function GM_Month (Date : OS_Time) return Month_Type;
function GM_Day (Date : OS_Time) return Day_Type;
function GM_Hour (Date : OS_Time) return Hour_Type;
function GM_Minute (Date : OS_Time) return Minute_Type;
function GM_Second (Date : OS_Time) return Second_Type;
-- Functions to extract information from OS_Time value
function "<" (X, Y : OS_Time) return Boolean;
function ">" (X, Y : OS_Time) return Boolean;
function ">=" (X, Y : OS_Time) return Boolean;
function "<=" (X, Y : OS_Time) return Boolean;
-- Basic comparison operators on OS_Time with obvious meanings. Note that
-- these have Intrinsic convention, so for example it is not permissible
-- to create accesses to any of these functions.
procedure GM_Split
(Date : OS_Time;
Year : out Year_Type;
Month : out Month_Type;
Day : out Day_Type;
Hour : out Hour_Type;
Minute : out Minute_Type;
Second : out Second_Type);
-- Analogous to the Split routine in Ada.Calendar, takes an OS_Time
-- and provides a representation of it as a set of component parts,
-- to be interpreted as a date point in UTC.
----------------
-- File Stuff --
----------------
-- These routines give access to the open/creat/close/read/write level of
-- I/O routines in the typical C library (these functions are not part of
-- the ANSI C standard, but are typically available in all systems). See
-- also package Interfaces.C_Streams for access to the stream level
-- routines.
-- Note on file names. If a file name is passed as type String in any of
-- the following specifications, then the name is a normal Ada string and
-- need not be NUL-terminated. However, a trailing NUL character is
-- permitted, and will be ignored (more accurately, the NUL and any
-- characters that follow it will be ignored).
type File_Descriptor is new Integer;
-- Corresponds to the int file handle values used in the C routines
Standin : constant File_Descriptor := 0;
Standout : constant File_Descriptor := 1;
Standerr : constant File_Descriptor := 2;
-- File descriptors for standard input output files
Invalid_FD : constant File_Descriptor := -1;
-- File descriptor returned when error in opening/creating file;
type Mode is (Binary, Text);
for Mode'Size use Integer'Size;
for Mode use (Binary => 0, Text => 1);
-- Used in all the Open and Create calls to specify if the file is to be
-- opened in binary mode or text mode. In systems like Unix, this has no
-- effect, but in systems capable of text mode translation, the use of
-- Text as the mode parameter causes the system to do CR/LF translation
-- and also to recognize the DOS end of file character on input. The use
-- of Text where appropriate allows programs to take a portable Unix view
-- of DOS-format files and process them appropriately.
function Open_Read
(Name : String;
Fmode : Mode) return File_Descriptor;
-- Open file Name for reading, returning file descriptor File descriptor
-- returned is Invalid_FD if file cannot be opened.
function Open_Read_Write
(Name : String;
Fmode : Mode) return File_Descriptor;
-- Open file Name for both reading and writing, returning file descriptor.
-- File descriptor returned is Invalid_FD if file cannot be opened.
function Create_File
(Name : String;
Fmode : Mode) return File_Descriptor;
-- Creates new file with given name for writing, returning file descriptor
-- for subsequent use in Write calls. File descriptor returned is
-- Invalid_FD if file cannot be successfully created.
function Create_Output_Text_File (Name : String) return File_Descriptor;
-- Creates new text file with given name suitable to redirect standard
-- output, returning file descriptor. File descriptor returned is
-- Invalid_FD if file cannot be successfully created.
function Create_New_File
(Name : String;
Fmode : Mode) return File_Descriptor;
-- Create new file with given name for writing, returning file descriptor
-- for subsequent use in Write calls. This differs from Create_File in
-- that it fails if the file already exists. File descriptor returned is
-- Invalid_FD if the file exists or cannot be created.
Temp_File_Len : constant Integer := 12;
-- Length of name returned by Create_Temp_File call (GNAT-XXXXXX & NUL)
subtype Temp_File_Name is String (1 .. Temp_File_Len);
-- String subtype set by Create_Temp_File
procedure Create_Temp_File
(FD : out File_Descriptor;
Name : out Temp_File_Name);
-- Create and open for writing a temporary file in the current working
-- directory. The name of the file and the File Descriptor are returned.
-- The File Descriptor returned is Invalid_FD in the case of failure. No
-- mode parameter is provided. Since this is a temporary file, there is no
-- point in doing text translation on it.
--
-- On some OSes, the maximum number of temp files that can be created with
-- this procedure may be limited. When the maximum is reached, this
-- procedure returns Invalid_FD. On some OSes, there may be a race
-- condition between processes trying to create temp files at the same
-- time in the same directory using this procedure.
procedure Create_Temp_File
(FD : out File_Descriptor;
Name : out String_Access);
-- Create and open for writing a temporary file in the current working
-- directory. The name of the file and the File Descriptor are returned.
-- No mode parameter is provided. Since this is a temporary file, there is
-- no point in doing text translation on it. It is the responsibility of
-- the caller to deallocate the access value returned in Name.
--
-- This procedure will always succeed if the current working directory is
-- writable. If the current working directory is not writable, then
-- Invalid_FD is returned for the file descriptor and null for the Name.
-- There is no race condition problem between processes trying to create
-- temp files at the same time in the same directory.
procedure Close (FD : File_Descriptor; Status : out Boolean);
-- Close file referenced by FD. Status is False if the underlying service
-- failed. Reasons for failure include: disk full, disk quotas exceeded
-- and invalid file descriptor (the file may have been closed twice).
procedure Close (FD : File_Descriptor);
-- Close file referenced by FD. This form is used when the caller wants to
-- ignore any possible error (see above for error cases).
procedure Set_Close_On_Exec
(FD : File_Descriptor;
Close_On_Exec : Boolean;
Status : out Boolean);
-- When Close_On_Exec is True, mark FD to be closed automatically when new
-- program is executed by the calling process (i.e. prevent FD from being
-- inherited by child processes). When Close_On_Exec is False, mark FD to
-- not be closed on exec (i.e. allow it to be inherited). Status is False
-- if the operation could not be performed.
procedure Delete_File (Name : String; Success : out Boolean);
-- Deletes file. Success is set True or False indicating if the delete is
-- successful.
procedure Rename_File
(Old_Name : String;
New_Name : String;
Success : out Boolean);
-- Rename a file. Success is set True or False indicating if the rename is
-- successful or not.
-- The following defines the mode for the Copy_File procedure below. Note
-- that "time stamps and other file attributes" in the descriptions below
-- refers to the creation and last modification times, and also the file
-- access (read/write/execute) status flags.
type Copy_Mode is
(Copy,
-- Copy the file. It is an error if the target file already exists. The
-- time stamps and other file attributes are preserved in the copy.
Overwrite,
-- If the target file exists, the file is replaced otherwise the file
-- is just copied. The time stamps and other file attributes are
-- preserved in the copy.
Append);
-- If the target file exists, the contents of the source file is
-- appended at the end. Otherwise the source file is just copied. The
-- time stamps and other file attributes are are preserved if the
-- destination file does not exist.
type Attribute is
(Time_Stamps,
-- Copy time stamps from source file to target file. All other
-- attributes are set to normal default values for file creation.
Full,
-- All attributes are copied from the source file to the target file.
-- This includes the timestamps, and for example also includes
-- read/write/execute attributes in Unix systems.
None);
-- No attributes are copied. All attributes including the time stamp
-- values are set to normal default values for file creation.
-- Note: The default is Time_Stamps, which corresponds to the normal
-- default on Windows style systems. Full corresponds to the typical
-- effect of "cp -p" on Unix systems, and None corresponds to the typical
-- effect of "cp" on Unix systems.
-- Note: Time_Stamps and Full are not supported on VMS and VxWorks
procedure Copy_File
(Name : String;
Pathname : String;
Success : out Boolean;
Mode : Copy_Mode := Copy;
Preserve : Attribute := Time_Stamps);
-- Copy a file. Name must designate a single file (no wild cards allowed).
-- Pathname can be a filename or directory name. In the latter case Name
-- is copied into the directory preserving the same file name. Mode
-- defines the kind of copy, see above with the default being a normal
-- copy in which the target file must not already exist. Success is set to
-- True or False indicating if the copy is successful (depending on the
-- specified Mode).
--
-- Note: this procedure is only supported to a very limited extent on VMS.
-- The only supported mode is Overwrite, and the only supported value for
-- Preserve is None, resulting in the default action which for Overwrite
-- is to leave attributes unchanged. Furthermore, the copy only works for
-- simple text files.
procedure Copy_Time_Stamps (Source, Dest : String; Success : out Boolean);
-- Copy Source file time stamps (last modification and last access time
-- stamps) to Dest file. Source and Dest must be valid filenames,
-- furthermore Dest must be writable. Success will be set to True if the
-- operation was successful and False otherwise.
--
-- Note: this procedure is not supported on VMS and VxWorks. On these
-- platforms, Success is always set to False.
function Read
(FD : File_Descriptor;
A : System.Address;
N : Integer) return Integer;
-- Read N bytes to address A from file referenced by FD. Returned value is
-- count of bytes actually read, which can be less than N at EOF.
function Write
(FD : File_Descriptor;
A : System.Address;
N : Integer) return Integer;
-- Write N bytes from address A to file referenced by FD. The returned
-- value is the number of bytes written, which can be less than N if a
-- disk full condition was detected.
Seek_Cur : constant := 1;
Seek_End : constant := 2;
Seek_Set : constant := 0;
-- Used to indicate origin for Lseek call
procedure Lseek
(FD : File_Descriptor;
offset : Long_Integer;
origin : Integer);
pragma Import (C, Lseek, "__gnat_lseek");
-- Sets the current file pointer to the indicated offset value, relative
-- to the current position (origin = SEEK_CUR), end of file (origin =
-- SEEK_END), or start of file (origin = SEEK_SET).
function File_Length (FD : File_Descriptor) return Long_Integer;
pragma Import (C, File_Length, "__gnat_file_length");
-- Get length of file from file descriptor FD
function File_Time_Stamp (Name : String) return OS_Time;
-- Given the name of a file or directory, Name, obtains and returns the
-- time stamp. This function can be used for an unopened file. Returns
-- Invalid_Time is Name doesn't correspond to an existing file.
function File_Time_Stamp (FD : File_Descriptor) return OS_Time;
-- Get time stamp of file from file descriptor FD Returns Invalid_Time is
-- FD doesn't correspond to an existing file.
function Normalize_Pathname
(Name : String;
Directory : String := "";
Resolve_Links : Boolean := True;
Case_Sensitive : Boolean := True) return String;
-- Returns a file name as an absolute path name, resolving all relative
-- directories, and symbolic links. The parameter Directory is a fully
-- resolved path name for a directory, or the empty string (the default).
-- Name is the name of a file, which is either relative to the given
-- directory name, if Directory is non-null, or to the current working
-- directory if Directory is null. The result returned is the normalized
-- name of the file. For most cases, if two file names designate the same
-- file through different paths, Normalize_Pathname will return the same
-- canonical name in both cases. However, there are cases when this is not
-- true; for example, this is not true in Unix for two hard links
-- designating the same file.
--
-- On Windows, the returned path will start with a drive letter except
-- when Directory is not empty and does not include a drive letter. If
-- Directory is empty (the default) and Name is a relative path or an
-- absolute path without drive letter, the letter of the current drive
-- will start the returned path. If Case_Sensitive is True (the default),
-- then this drive letter will be forced to upper case ("C:\...").
--
-- If Resolve_Links is set to True, then the symbolic links, on systems
-- that support them, will be fully converted to the name of the file or
-- directory pointed to. This is slightly less efficient, since it
-- requires system calls.
--
-- If Name cannot be resolved or is null on entry (for example if there is
-- symbolic link circularity, e.g. A is a symbolic link for B, and B is a
-- symbolic link for A), then Normalize_Pathname returns an empty string.
--
-- In VMS, if Name follows the VMS syntax file specification, it is first
-- converted into Unix syntax. If the conversion fails, Normalize_Pathname
-- returns an empty string.
--
-- For case-sensitive file systems, the value of Case_Sensitive parameter
-- is ignored. For file systems that are not case-sensitive, such as
-- Windows and OpenVMS, if this parameter is set to False, then the file
-- and directory names are folded to lower case. This allows checking
-- whether two files are the same by applying this function to their names
-- and comparing the results. If Case_Sensitive is set to True, this
-- function does not change the casing of file and directory names.
function Is_Absolute_Path (Name : String) return Boolean;
-- Returns True if Name is an absolute path name, i.e. it designates a
-- file or directory absolutely rather than relative to another directory.
function Is_Regular_File (Name : String) return Boolean;
-- Determines if the given string, Name, is the name of an existing
-- regular file. Returns True if so, False otherwise. Name may be an
-- absolute path name or a relative path name, including a simple file
-- name. If it is a relative path name, it is relative to the current
-- working directory.
function Is_Directory (Name : String) return Boolean;
-- Determines if the given string, Name, is the name of a directory.
-- Returns True if so, False otherwise. Name may be an absolute path
-- name or a relative path name, including a simple file name. If it is
-- a relative path name, it is relative to the current working directory.
function Is_Readable_File (Name : String) return Boolean;
-- Determines if the given string, Name, is the name of an existing file
-- that is readable. Returns True if so, False otherwise. Note that this
-- function simply interrogates the file attributes (e.g. using the C
-- function stat), so it does not indicate a situation in which a file may
-- not actually be readable due to some other process having exclusive
-- access.
function Is_Writable_File (Name : String) return Boolean;
-- Determines if the given string, Name, is the name of an existing file
-- that is writable. Returns True if so, False otherwise. Note that this
-- function simply interrogates the file attributes (e.g. using the C
-- function stat), so it does not indicate a situation in which a file may
-- not actually be writeable due to some other process having exclusive
-- access.
function Is_Symbolic_Link (Name : String) return Boolean;
-- Determines if the given string, Name, is the path of a symbolic link on
-- systems that support it. Returns True if so, False if the path is not a
-- symbolic link or if the system does not support symbolic links.
--
-- A symbolic link is an indirect pointer to a file; its directory entry
-- contains the name of the file to which it is linked. Symbolic links may
-- span file systems and may refer to directories.
procedure Set_Writable (Name : String);
-- Change the permissions on the named file to make it writable
-- for its owner.
procedure Set_Read_Only (Name : String);
-- Change the permissions on the named file to make it non-writable
-- for its owner.
procedure Set_Executable (Name : String);
-- Change the permissions on the named file to make it executable
-- for its owner.
function Locate_Exec_On_Path
(Exec_Name : String) return String_Access;
-- Try to locate an executable whose name is given by Exec_Name in the
-- directories listed in the environment Path. If the Exec_Name doesn't
-- have the executable suffix, it will be appended before the search.
-- Otherwise works like Locate_Regular_File below.
--
-- Note that this function allocates some memory for the returned value.
-- This memory needs to be deallocated after use.
function Locate_Regular_File
(File_Name : String;
Path : String) return String_Access;
-- Try to locate a regular file whose name is given by File_Name in the
-- directories listed in Path. If a file is found, its full pathname is
-- returned; otherwise, a null pointer is returned. If the File_Name given
-- is an absolute pathname, then Locate_Regular_File just checks that the
-- file exists and is a regular file. Otherwise, if the File_Name given
-- includes directory information, Locate_Regular_File first checks if the
-- file exists relative to the current directory. If it does not, or if
-- the File_Name given is a simple file name, the Path argument is parsed
-- according to OS conventions, and for each directory in the Path a check
-- is made if File_Name is a relative pathname of a regular file from that
-- directory.
--
-- Note that this function allocates some memory for the returned value.
-- This memory needs to be deallocated after use.
function Get_Debuggable_Suffix return String_Access;
-- Return the debuggable suffix convention. Usually this is the same as
-- the convention for Get_Executable_Suffix. The result is allocated on
-- the heap and should be freed after use to avoid storage leaks.
function Get_Target_Debuggable_Suffix return String_Access;
-- Return the target debuggable suffix convention. Usually this is the
-- same as the convention for Get_Executable_Suffix. The result is
-- allocated on the heap and should be freed after use to avoid storage
-- leaks.
function Get_Executable_Suffix return String_Access;
-- Return the executable suffix convention. The result is allocated on the
-- heap and should be freed after use to avoid storage leaks.
function Get_Object_Suffix return String_Access;
-- Return the object suffix convention. The result is allocated on the heap
-- and should be freed after use to avoid storage leaks.
function Get_Target_Executable_Suffix return String_Access;
-- Return the target executable suffix convention. The result is allocated
-- on the heap and should be freed after use to avoid storage leaks.
function Get_Target_Object_Suffix return String_Access;
-- Return the target object suffix convention. The result is allocated on
-- the heap and should be freed after use to avoid storage leaks.
-- The following section contains low-level routines using addresses to
-- pass file name and executable name. In each routine the name must be
-- Nul-Terminated. For complete documentation refer to the equivalent
-- routine (using String in place of C_File_Name) defined above.
subtype C_File_Name is System.Address;
-- This subtype is used to document that a parameter is the address of a
-- null-terminated string containing the name of a file.
-- All the following functions need comments ???
function Open_Read
(Name : C_File_Name;
Fmode : Mode) return File_Descriptor;
function Open_Read_Write
(Name : C_File_Name;
Fmode : Mode) return File_Descriptor;
function Create_File
(Name : C_File_Name;
Fmode : Mode) return File_Descriptor;
function Create_New_File
(Name : C_File_Name;
Fmode : Mode) return File_Descriptor;
procedure Delete_File (Name : C_File_Name; Success : out Boolean);
procedure Rename_File
(Old_Name : C_File_Name;
New_Name : C_File_Name;
Success : out Boolean);
procedure Copy_File
(Name : C_File_Name;
Pathname : C_File_Name;
Success : out Boolean;
Mode : Copy_Mode := Copy;
Preserve : Attribute := Time_Stamps);
procedure Copy_Time_Stamps
(Source, Dest : C_File_Name;
Success : out Boolean);
function File_Time_Stamp (Name : C_File_Name) return OS_Time;
-- Returns Invalid_Time is Name doesn't correspond to an existing file
function Is_Regular_File (Name : C_File_Name) return Boolean;
function Is_Directory (Name : C_File_Name) return Boolean;
function Is_Readable_File (Name : C_File_Name) return Boolean;
function Is_Writable_File (Name : C_File_Name) return Boolean;
function Is_Symbolic_Link (Name : C_File_Name) return Boolean;
function Locate_Regular_File
(File_Name : C_File_Name;
Path : C_File_Name) return String_Access;
------------------
-- Subprocesses --
------------------
subtype Argument_List is String_List;
-- Type used for argument list in call to Spawn. The lower bound of the
-- array should be 1, and the length of the array indicates the number of
-- arguments.
subtype Argument_List_Access is String_List_Access;
-- Type used to return Argument_List without dragging in secondary stack.
-- Note that there is a Free procedure declared for this subtype which
-- frees the array and all referenced strings.
procedure Normalize_Arguments (Args : in out Argument_List);
-- Normalize all arguments in the list. This ensure that the argument list
-- is compatible with the running OS and will works fine with Spawn and
-- Non_Blocking_Spawn for example. If Normalize_Arguments is called twice
-- on the same list it will do nothing the second time. Note that Spawn
-- and Non_Blocking_Spawn call Normalize_Arguments automatically, but
-- since there is a guarantee that a second call does nothing, this
-- internal call will have no effect if Normalize_Arguments is called
-- before calling Spawn. The call to Normalize_Arguments assumes that the
-- individual referenced arguments in Argument_List are on the heap, and
-- may free them and reallocate if they are modified.
procedure Spawn
(Program_Name : String;
Args : Argument_List;
Success : out Boolean);
-- This procedure spawns a program with a given list of arguments. The
-- first parameter of is the name of the executable. The second parameter
-- contains the arguments to be passed to this program. Success is False
-- if the named program could not be spawned or its execution completed
-- unsuccessfully. Note that the caller will be blocked until the
-- execution of the spawned program is complete. For maximum portability,
-- use a full path name for the Program_Name argument. On some systems
-- (notably Unix systems) a simple file name may also work (if the
-- executable can be located in the path).
--
-- "Spawn" should not be used in tasking applications. Why not??? More
-- documentation would be helpful here ??? Is it really tasking programs,
-- or tasking activity that cause trouble ???
--
-- Note: Arguments in Args that contain spaces and/or quotes such as
-- "--GCC=gcc -v" or "--GCC=""gcc -v""" are not portable across all
-- operating systems, and would not have the desired effect if they were
-- passed directly to the operating system. To avoid this problem, Spawn
-- makes an internal call to Normalize_Arguments, which ensures that such
-- arguments are modified in a manner that ensures that the desired effect
-- is obtained on all operating systems. The caller may call
-- Normalize_Arguments explicitly before the call (e.g. to print out the
-- exact form of arguments passed to the operating system). In this case
-- the guarantee a second call to Normalize_Arguments has no effect
-- ensures that the internal call will not affect the result. Note that
-- the implicit call to Normalize_Arguments may free and reallocate some
-- of the individual arguments.
--
-- This function will always set Success to False under VxWorks and other
-- similar operating systems which have no notion of the concept of
-- dynamically executable file.
function Spawn
(Program_Name : String;
Args : Argument_List) return Integer;
-- Similar to the above procedure, but returns the actual status returned
-- by the operating system, or -1 under VxWorks and any other similar
-- operating systems which have no notion of separately spawnable programs.
--
-- "Spawn" should not be used in tasking applications.
procedure Spawn
(Program_Name : String;
Args : Argument_List;
Output_File_Descriptor : File_Descriptor;
Return_Code : out Integer;
Err_To_Out : Boolean := True);
-- Similar to the procedure above, but redirects the output to the file
-- designated by Output_File_Descriptor. If Err_To_Out is True, then the
-- Standard Error output is also redirected.
-- Return_Code is set to the status code returned by the operating system
--
-- "Spawn" should not be used in tasking applications.
procedure Spawn
(Program_Name : String;
Args : Argument_List;
Output_File : String;
Success : out Boolean;
Return_Code : out Integer;
Err_To_Out : Boolean := True);
-- Similar to the procedure above, but saves the output of the command to
-- a file with the name Output_File.
--
-- Success is set to True if the command is executed and its output
-- successfully written to the file. If Success is True, then Return_Code
-- will be set to the status code returned by the operating system.
-- Otherwise, Return_Code is undefined.
--
-- "Spawn" should not be used in tasking applications.
type Process_Id is private;
-- A private type used to identify a process activated by the following
-- non-blocking calls. The only meaningful operation on this type is a
-- comparison for equality.
Invalid_Pid : constant Process_Id;
-- A special value used to indicate errors, as described below
function Pid_To_Integer (Pid : Process_Id) return Integer;
-- Convert a process id to an Integer. Useful for writing hash functions
-- for type Process_Id or to compare two Process_Id (e.g. for sorting).
function Non_Blocking_Spawn
(Program_Name : String;
Args : Argument_List) return Process_Id;
-- This is a non blocking call. The Process_Id of the spawned process is
-- returned. Parameters are to be used as in Spawn. If Invalid_Pid is
-- returned the program could not be spawned.
--
-- "Non_Blocking_Spawn" should not be used in tasking applications.
--
-- This function will always return Invalid_Pid under VxWorks, since there
-- is no notion of executables under this OS.
function Non_Blocking_Spawn
(Program_Name : String;
Args : Argument_List;
Output_File_Descriptor : File_Descriptor;
Err_To_Out : Boolean := True) return Process_Id;
-- Similar to the procedure above, but redirects the output to the file
-- designated by Output_File_Descriptor. If Err_To_Out is True, then the
-- Standard Error output is also redirected. Invalid_Pid is returned
-- if the program could not be spawned successfully.
--
-- "Non_Blocking_Spawn" should not be used in tasking applications.
--
-- This function will always return Invalid_Pid under VxWorks, since there
-- is no notion of executables under this OS.
function Non_Blocking_Spawn
(Program_Name : String;
Args : Argument_List;
Output_File : String;
Err_To_Out : Boolean := True) return Process_Id;
-- Similar to the procedure above, but saves the output of the command to
-- a file with the name Output_File.
--
-- Success is set to True if the command is executed and its output
-- successfully written to the file. Invalid_Pid is returned if the output
-- file could not be created or if the program could not be spawned
-- successfully.
--
-- "Non_Blocking_Spawn" should not be used in tasking applications.
--
-- This function will always return Invalid_Pid under VxWorks, since there
-- is no notion of executables under this OS.
procedure Wait_Process (Pid : out Process_Id; Success : out Boolean);
-- Wait for the completion of any of the processes created by previous
-- calls to Non_Blocking_Spawn. The caller will be suspended until one of
-- these processes terminates (normally or abnormally). If any of these
-- subprocesses terminates prior to the call to Wait_Process (and has not
-- been returned by a previous call to Wait_Process), then the call to
-- Wait_Process is immediate. Pid identifies the process that has
-- terminated (matching the value returned from Non_Blocking_Spawn).
-- Success is set to True if this sub-process terminated successfully. If
-- Pid = Invalid_Pid, there were no subprocesses left to wait on.
--
-- This function will always set success to False under VxWorks, since
-- there is no notion of executables under this OS.
function Argument_String_To_List
(Arg_String : String) return Argument_List_Access;
-- Take a string that is a program and its arguments and parse it into an
-- Argument_List. Note that the result is allocated on the heap, and must
-- be freed by the programmer (when it is no longer needed) to avoid
-- memory leaks.
-------------------
-- Miscellaneous --
-------------------
function Getenv (Name : String) return String_Access;
-- Get the value of the environment variable. Returns an access to the
-- empty string if the environment variable does not exist or has an
-- explicit null value (in some operating systems these are distinct
-- cases, in others they are not; this interface abstracts away that
-- difference. The argument is allocated on the heap (even in the null
-- case), and needs to be freed explicitly when no longer needed to avoid
-- memory leaks.
procedure Setenv (Name : String; Value : String);
-- Set the value of the environment variable Name to Value. This call
-- modifies the current environment, but does not modify the parent
-- process environment. After a call to Setenv, Getenv (Name) will always
-- return a String_Access referencing the same String as Value. This is
-- true also for the null string case (the actual effect may be to either
-- set an explicit null as the value, or to remove the entry, this is
-- operating system dependent). Note that any following calls to Spawn
-- will pass an environment to the spawned process that includes the
-- changes made by Setenv calls. This procedure is not available on VMS.
procedure OS_Exit (Status : Integer);
pragma Import (C, OS_Exit, "__gnat_os_exit");
pragma No_Return (OS_Exit);
-- Exit to OS with given status code (program is terminated). Note that
-- this is abrupt termination. All tasks are immediately terminated. There
-- are no finalization or other Ada-specific cleanup actions performed. On
-- systems with atexit handlers (such as Unix and Windows) are performed.
procedure OS_Abort;
pragma Import (C, OS_Abort, "abort");
pragma No_Return (OS_Abort);
-- Exit to OS signalling an abort (traceback or other appropriate
-- diagnostic information should be given if possible, or entry made to
-- the debugger if that is possible).
function Errno return Integer;
pragma Import (C, Errno, "__get_errno");
-- Return the task-safe last error number
procedure Set_Errno (Errno : Integer);
pragma Import (C, Set_Errno, "__set_errno");
-- Set the task-safe error number
Directory_Separator : constant Character;
-- The character that is used to separate parts of a pathname
Path_Separator : constant Character;
-- The character to separate paths in an environment variable value
private
pragma Import (C, Path_Separator, "__gnat_path_separator");
pragma Import (C, Directory_Separator, "__gnat_dir_separator");
pragma Import (C, Current_Time, "__gnat_current_time");
type OS_Time is new Long_Integer;
-- Type used for timestamps in the compiler. This type is used to hold
-- time stamps, but may have a different representation than C's time_t.
-- This type needs to match the declaration of OS_Time in adaint.h.
-- Add pragma Inline statements for comparison operations on OS_Time. It
-- would actually be nice to use pragma Import (Intrinsic) here, but this
-- was not properly supported till GNAT 3.15a, so that would cause
-- bootstrap path problems. To be changed later ???
Invalid_Time : constant OS_Time := -1;
-- This value should match the return valud by __gnat_file_time_*
pragma Inline ("<");
pragma Inline (">");
pragma Inline ("<=");
pragma Inline (">=");
type Process_Id is new Integer;
Invalid_Pid : constant Process_Id := -1;
end System.OS_Lib;
......@@ -6,7 +6,7 @@
-- --
-- B o d y --
-- --
-- Copyright (C) 1997-2005 Free Software Foundation, Inc. --
-- Copyright (C) 1997-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -31,10 +31,10 @@
-- --
------------------------------------------------------------------------------
-- This is an Irix (old pthread library) version of this package.
-- This is an Irix (old pthread library) version of this package
-- This package contains the parameters used by the run-time system at
-- program startup. These parameters are isolated in this package body to
-- This package contains the parameters used by the run-time system at
-- program startup. These parameters are isolated in this package body to
-- facilitate replacement by the end user.
--
-- To replace the default values, copy this source file into your build
......@@ -44,10 +44,9 @@
-- % gcc -c -O2 -gnatpg s-proinf.adb
--
-- then relink your application as usual.
--
pragma Warnings (Off);
with GNAT.OS_Lib;
pragma Warnings (Off); -- why???
with System.OS_Lib;
pragma Warnings (On);
package body System.Program_Info is
......@@ -75,8 +74,8 @@ package body System.Program_Info is
MP_NPROCS : constant := 1; -- # processor in complex
Pthread_Sproc_Count : constant GNAT.OS_Lib.String_Access :=
GNAT.OS_Lib.Getenv ("PTHREAD_SPROC_COUNT");
Pthread_Sproc_Count : constant System.OS_Lib.String_Access :=
System.OS_Lib.Getenv ("PTHREAD_SPROC_COUNT");
begin
if Pthread_Sproc_Count.all'Length = 0 then
......@@ -88,6 +87,7 @@ package body System.Program_Info is
else
return Integer'Value (Pthread_Sproc_Count.all);
end if;
exception
when others =>
return Default_Initial_Sproc_Count;
......@@ -98,8 +98,8 @@ package body System.Program_Info is
---------------------
function Max_Sproc_Count return Integer is
Pthread_Max_Sproc_Count : constant GNAT.OS_Lib.String_Access :=
GNAT.OS_Lib.Getenv ("PTHREAD_MAX_SPROC_COUNT");
Pthread_Max_Sproc_Count : constant System.OS_Lib.String_Access :=
System.OS_Lib.Getenv ("PTHREAD_MAX_SPROC_COUNT");
begin
if Pthread_Max_Sproc_Count.all'Length = 0 then
......@@ -126,10 +126,12 @@ package body System.Program_Info is
------------------------
function Default_Time_Slice return Duration is
Pthread_Time_Slice_Sec : constant GNAT.OS_Lib.String_Access :=
GNAT.OS_Lib.Getenv ("PTHREAD_TIME_SLICE_SEC");
Pthread_Time_Slice_Usec : constant GNAT.OS_Lib.String_Access :=
GNAT.OS_Lib.Getenv ("PTHREAD_TIME_SLICE_USEC");
Pthread_Time_Slice_Sec : constant System.OS_Lib.String_Access :=
System.OS_Lib.Getenv
("PTHREAD_TIME_SLICE_SEC");
Pthread_Time_Slice_Usec : constant System.OS_Lib.String_Access :=
System.OS_Lib.Getenv
("PTHREAD_TIME_SLICE_USEC");
Val_Sec, Val_Usec : Integer := 0;
......@@ -169,9 +171,9 @@ package body System.Program_Info is
-----------------------
function Stack_Guard_Pages return Integer is
Pthread_Stack_Guard_Pages : constant GNAT.OS_Lib.String_Access :=
GNAT.OS_Lib.Getenv ("PTHREAD_STACK_GUARD_PAGES");
Pthread_Stack_Guard_Pages : constant System.OS_Lib.String_Access :=
System.OS_Lib.Getenv
("PTHREAD_STACK_GUARD_PAGES");
begin
if Pthread_Stack_Guard_Pages.all'Length /= 0 then
return Integer'Value (Pthread_Stack_Guard_Pages.all);
......@@ -197,8 +199,9 @@ package body System.Program_Info is
------------------------
function Pthread_Arena_Size return Integer is
Pthread_Arena_Size : constant GNAT.OS_Lib.String_Access :=
GNAT.OS_Lib.Getenv ("PTHREAD_ARENA_SIZE");
Pthread_Arena_Size : constant System.OS_Lib.String_Access :=
System.OS_Lib.Getenv
("PTHREAD_ARENA_SIZE");
begin
if Pthread_Arena_Size.all'Length = 0 then
......@@ -206,6 +209,7 @@ package body System.Program_Info is
else
return Integer'Value (Pthread_Arena_Size.all);
end if;
exception
when others =>
return Default_Pthread_Arena_Size;
......
------------------------------------------------------------------------------
-- --
-- GNAT COMPILER COMPONENTS --
-- --
-- G N A T . R E G E X P --
-- --
-- B o d y --
-- --
-- Copyright (C) 1999-2007, AdaCore --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- ware Foundation; either version 2, or (at your option) any later ver- --
-- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
-- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
-- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
-- for more details. You should have received a copy of the GNU General --
-- Public License distributed with GNAT; see file COPYING. If not, write --
-- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
-- Boston, MA 02110-1301, USA. --
-- --
-- As a special exception, if other files instantiate generics from this --
-- unit, or you link this unit with other files to produce an executable, --
-- this unit does not by itself cause the resulting executable to be --
-- covered by the GNU General Public License. This exception does not --
-- however invalidate any other reasons why the executable file might be --
-- covered by the GNU Public License. --
-- --
-- GNAT was originally developed by the GNAT team at New York University. --
-- Extensive contributions were provided by Ada Core Technologies Inc. --
-- --
------------------------------------------------------------------------------
with Ada.Unchecked_Deallocation;
with Ada.Exceptions;
with System.Case_Util;
package body System.Regexp is
Open_Paren : constant Character := '(';
Close_Paren : constant Character := ')';
Open_Bracket : constant Character := '[';
Close_Bracket : constant Character := ']';
type State_Index is new Natural;
type Column_Index is new Natural;
type Regexp_Array is array
(State_Index range <>, Column_Index range <>) of State_Index;
-- First index is for the state number
-- Second index is for the character type
-- Contents is the new State
type Regexp_Array_Access is access Regexp_Array;
-- Use this type through the functions Set below, so that it
-- can grow dynamically depending on the needs.
type Mapping is array (Character'Range) of Column_Index;
-- Mapping between characters and column in the Regexp_Array
type Boolean_Array is array (State_Index range <>) of Boolean;
type Regexp_Value
(Alphabet_Size : Column_Index;
Num_States : State_Index) is
record
Map : Mapping;
States : Regexp_Array (1 .. Num_States, 0 .. Alphabet_Size);
Is_Final : Boolean_Array (1 .. Num_States);
Case_Sensitive : Boolean;
end record;
-- Deterministic finite-state machine
-----------------------
-- Local Subprograms --
-----------------------
procedure Set
(Table : in out Regexp_Array_Access;
State : State_Index;
Column : Column_Index;
Value : State_Index);
-- Sets a value in the table. If the table is too small, reallocate it
-- dynamically so that (State, Column) is a valid index in it.
function Get
(Table : Regexp_Array_Access;
State : State_Index;
Column : Column_Index)
return State_Index;
-- Returns the value in the table at (State, Column).
-- If this index does not exist in the table, returns 0
procedure Free is new Ada.Unchecked_Deallocation
(Regexp_Array, Regexp_Array_Access);
------------
-- Adjust --
------------
procedure Adjust (R : in out Regexp) is
Tmp : Regexp_Access;
begin
Tmp := new Regexp_Value (Alphabet_Size => R.R.Alphabet_Size,
Num_States => R.R.Num_States);
Tmp.all := R.R.all;
R.R := Tmp;
end Adjust;
-------------
-- Compile --
-------------
function Compile
(Pattern : String;
Glob : Boolean := False;
Case_Sensitive : Boolean := True)
return Regexp
is
S : String := Pattern;
-- The pattern which is really compiled (when the pattern is case
-- insensitive, we convert this string to lower-cases
Map : Mapping := (others => 0);
-- Mapping between characters and columns in the tables
Alphabet_Size : Column_Index := 0;
-- Number of significant characters in the regular expression.
-- This total does not include special operators, such as *, (, ...
procedure Create_Mapping;
-- Creates a mapping between characters in the regexp and columns
-- in the tables representing the regexp. Test that the regexp is
-- well-formed Modifies Alphabet_Size and Map
procedure Create_Primary_Table
(Table : out Regexp_Array_Access;
Num_States : out State_Index;
Start_State : out State_Index;
End_State : out State_Index);
-- Creates the first version of the regexp (this is a non determinist
-- finite state machine, which is unadapted for a fast pattern
-- matching algorithm). We use a recursive algorithm to process the
-- parenthesis sub-expressions.
--
-- Table : at the end of the procedure : Column 0 is for any character
-- ('.') and the last columns are for no character (closure)
-- Num_States is set to the number of states in the table
-- Start_State is the number of the starting state in the regexp
-- End_State is the number of the final state when the regexp matches
procedure Create_Primary_Table_Glob
(Table : out Regexp_Array_Access;
Num_States : out State_Index;
Start_State : out State_Index;
End_State : out State_Index);
-- Same function as above, but it deals with the second possible
-- grammar for 'globbing pattern', which is a kind of subset of the
-- whole regular expression grammar.
function Create_Secondary_Table
(First_Table : Regexp_Array_Access;
Num_States : State_Index;
Start_State : State_Index;
End_State : State_Index)
return Regexp;
-- Creates the definitive table representing the regular expression
-- This is actually a transformation of the primary table First_Table,
-- where every state is grouped with the states in its 'no-character'
-- columns. The transitions between the new states are then recalculated
-- and if necessary some new states are created.
--
-- Note that the resulting finite-state machine is not optimized in
-- terms of the number of states : it would be more time-consuming to
-- add a third pass to reduce the number of states in the machine, with
-- no speed improvement...
procedure Raise_Exception
(M : String;
Index : Integer);
pragma No_Return (Raise_Exception);
-- Raise an exception, indicating an error at character Index in S
--------------------
-- Create_Mapping --
--------------------
procedure Create_Mapping is
procedure Add_In_Map (C : Character);
-- Add a character in the mapping, if it is not already defined
----------------
-- Add_In_Map --
----------------
procedure Add_In_Map (C : Character) is
begin
if Map (C) = 0 then
Alphabet_Size := Alphabet_Size + 1;
Map (C) := Alphabet_Size;
end if;
end Add_In_Map;
J : Integer := S'First;
Parenthesis_Level : Integer := 0;
Curly_Level : Integer := 0;
-- Start of processing for Create_Mapping
begin
while J <= S'Last loop
case S (J) is
when Open_Bracket =>
J := J + 1;
if S (J) = '^' then
J := J + 1;
end if;
if S (J) = ']' or S (J) = '-' then
J := J + 1;
end if;
-- The first character never has a special meaning
loop
if J > S'Last then
Raise_Exception
("Ran out of characters while parsing ", J);
end if;
exit when S (J) = Close_Bracket;
if S (J) = '-'
and then S (J + 1) /= Close_Bracket
then
declare
Start : constant Integer := J - 1;
begin
J := J + 1;
if S (J) = '\' then
J := J + 1;
end if;
for Char in S (Start) .. S (J) loop
Add_In_Map (Char);
end loop;
end;
else
if S (J) = '\' then
J := J + 1;
end if;
Add_In_Map (S (J));
end if;
J := J + 1;
end loop;
-- A close bracket must follow a open_bracket,
-- and cannot be found alone on the line
when Close_Bracket =>
Raise_Exception
("Incorrect character ']' in regular expression", J);
when '\' =>
if J < S'Last then
J := J + 1;
Add_In_Map (S (J));
else
-- \ not allowed at the end of the regexp
Raise_Exception
("Incorrect character '\' in regular expression", J);
end if;
when Open_Paren =>
if not Glob then
Parenthesis_Level := Parenthesis_Level + 1;
else
Add_In_Map (Open_Paren);
end if;
when Close_Paren =>
if not Glob then
Parenthesis_Level := Parenthesis_Level - 1;
if Parenthesis_Level < 0 then
Raise_Exception
("')' is not associated with '(' in regular "
& "expression", J);
end if;
if S (J - 1) = Open_Paren then
Raise_Exception
("Empty parenthesis not allowed in regular "
& "expression", J);
end if;
else
Add_In_Map (Close_Paren);
end if;
when '.' =>
if Glob then
Add_In_Map ('.');
end if;
when '{' =>
if not Glob then
Add_In_Map (S (J));
else
Curly_Level := Curly_Level + 1;
end if;
when '}' =>
if not Glob then
Add_In_Map (S (J));
else
Curly_Level := Curly_Level - 1;
end if;
when '*' | '?' =>
if not Glob then
if J = S'First then
Raise_Exception
("'*', '+', '?' and '|' operators cannot be in "
& "first position in regular expression", J);
end if;
end if;
when '|' | '+' =>
if not Glob then
if J = S'First then
-- These operators must apply to a sub-expression,
-- and cannot be found at the beginning of the line
Raise_Exception
("'*', '+', '?' and '|' operators cannot be in "
& "first position in regular expression", J);
end if;
else
Add_In_Map (S (J));
end if;
when others =>
Add_In_Map (S (J));
end case;
J := J + 1;
end loop;
-- A closing parenthesis must follow an open parenthesis
if Parenthesis_Level /= 0 then
Raise_Exception
("'(' must always be associated with a ')'", J);
end if;
if Curly_Level /= 0 then
Raise_Exception
("'{' must always be associated with a '}'", J);
end if;
end Create_Mapping;
--------------------------
-- Create_Primary_Table --
--------------------------
procedure Create_Primary_Table
(Table : out Regexp_Array_Access;
Num_States : out State_Index;
Start_State : out State_Index;
End_State : out State_Index)
is
Empty_Char : constant Column_Index := Alphabet_Size + 1;
Current_State : State_Index := 0;
-- Index of the last created state
procedure Add_Empty_Char
(State : State_Index;
To_State : State_Index);
-- Add a empty-character transition from State to To_State
procedure Create_Repetition
(Repetition : Character;
Start_Prev : State_Index;
End_Prev : State_Index;
New_Start : out State_Index;
New_End : in out State_Index);
-- Create the table in case we have a '*', '+' or '?'.
-- Start_Prev .. End_Prev should indicate respectively the start and
-- end index of the previous expression, to which '*', '+' or '?' is
-- applied.
procedure Create_Simple
(Start_Index : Integer;
End_Index : Integer;
Start_State : out State_Index;
End_State : out State_Index);
-- Fill the table for the regexp Simple.
-- This is the recursive procedure called to handle () expressions
-- If End_State = 0, then the call to Create_Simple creates an
-- independent regexp, not a concatenation
-- Start_Index .. End_Index is the starting index in the string S.
--
-- Warning: it may look like we are creating too many empty-string
-- transitions, but they are needed to get the correct regexp.
-- The table is filled as follow ( s means start-state, e means
-- end-state) :
--
-- regexp state_num | a b * empty_string
-- ------- ------------------------------
-- a 1 (s) | 2 - - -
-- 2 (e) | - - - -
--
-- ab 1 (s) | 2 - - -
-- 2 | - - - 3
-- 3 | - 4 - -
-- 4 (e) | - - - -
--
-- a|b 1 | 2 - - -
-- 2 | - - - 6
-- 3 | - 4 - -
-- 4 | - - - 6
-- 5 (s) | - - - 1,3
-- 6 (e) | - - - -
--
-- a* 1 | 2 - - -
-- 2 | - - - 4
-- 3 (s) | - - - 1,4
-- 4 (e) | - - - 3
--
-- (a) 1 (s) | 2 - - -
-- 2 (e) | - - - -
--
-- a+ 1 | 2 - - -
-- 2 | - - - 4
-- 3 (s) | - - - 1
-- 4 (e) | - - - 3
--
-- a? 1 | 2 - - -
-- 2 | - - - 4
-- 3 (s) | - - - 1,4
-- 4 (e) | - - - -
--
-- . 1 (s) | 2 2 2 -
-- 2 (e) | - - - -
function Next_Sub_Expression
(Start_Index : Integer;
End_Index : Integer)
return Integer;
-- Returns the index of the last character of the next sub-expression
-- in Simple. Index cannot be greater than End_Index.
--------------------
-- Add_Empty_Char --
--------------------
procedure Add_Empty_Char
(State : State_Index;
To_State : State_Index)
is
J : Column_Index := Empty_Char;
begin
while Get (Table, State, J) /= 0 loop
J := J + 1;
end loop;
Set (Table, State, J, To_State);
end Add_Empty_Char;
-----------------------
-- Create_Repetition --
-----------------------
procedure Create_Repetition
(Repetition : Character;
Start_Prev : State_Index;
End_Prev : State_Index;
New_Start : out State_Index;
New_End : in out State_Index)
is
begin
New_Start := Current_State + 1;
if New_End /= 0 then
Add_Empty_Char (New_End, New_Start);
end if;
Current_State := Current_State + 2;
New_End := Current_State;
Add_Empty_Char (End_Prev, New_End);
Add_Empty_Char (New_Start, Start_Prev);
if Repetition /= '+' then
Add_Empty_Char (New_Start, New_End);
end if;
if Repetition /= '?' then
Add_Empty_Char (New_End, New_Start);
end if;
end Create_Repetition;
-------------------
-- Create_Simple --
-------------------
procedure Create_Simple
(Start_Index : Integer;
End_Index : Integer;
Start_State : out State_Index;
End_State : out State_Index)
is
J : Integer := Start_Index;
Last_Start : State_Index := 0;
begin
Start_State := 0;
End_State := 0;
while J <= End_Index loop
case S (J) is
when Open_Paren =>
declare
J_Start : constant Integer := J + 1;
Next_Start : State_Index;
Next_End : State_Index;
begin
J := Next_Sub_Expression (J, End_Index);
Create_Simple (J_Start, J - 1, Next_Start, Next_End);
if J < End_Index
and then (S (J + 1) = '*' or else
S (J + 1) = '+' or else
S (J + 1) = '?')
then
J := J + 1;
Create_Repetition
(S (J),
Next_Start,
Next_End,
Last_Start,
End_State);
else
Last_Start := Next_Start;
if End_State /= 0 then
Add_Empty_Char (End_State, Last_Start);
end if;
End_State := Next_End;
end if;
end;
when '|' =>
declare
Start_Prev : constant State_Index := Start_State;
End_Prev : constant State_Index := End_State;
Start_J : constant Integer := J + 1;
Start_Next : State_Index := 0;
End_Next : State_Index := 0;
begin
J := Next_Sub_Expression (J, End_Index);
-- Create a new state for the start of the alternative
Current_State := Current_State + 1;
Last_Start := Current_State;
Start_State := Last_Start;
-- Create the tree for the second part of alternative
Create_Simple (Start_J, J, Start_Next, End_Next);
-- Create the end state
Add_Empty_Char (Last_Start, Start_Next);
Add_Empty_Char (Last_Start, Start_Prev);
Current_State := Current_State + 1;
End_State := Current_State;
Add_Empty_Char (End_Prev, End_State);
Add_Empty_Char (End_Next, End_State);
end;
when Open_Bracket =>
Current_State := Current_State + 1;
declare
Next_State : State_Index := Current_State + 1;
begin
J := J + 1;
if S (J) = '^' then
J := J + 1;
Next_State := 0;
for Column in 0 .. Alphabet_Size loop
Set (Table, Current_State, Column,
Value => Current_State + 1);
end loop;
end if;
-- Automatically add the first character
if S (J) = '-' or S (J) = ']' then
Set (Table, Current_State, Map (S (J)),
Value => Next_State);
J := J + 1;
end if;
-- Loop till closing bracket found
loop
exit when S (J) = Close_Bracket;
if S (J) = '-'
and then S (J + 1) /= ']'
then
declare
Start : constant Integer := J - 1;
begin
J := J + 1;
if S (J) = '\' then
J := J + 1;
end if;
for Char in S (Start) .. S (J) loop
Set (Table, Current_State, Map (Char),
Value => Next_State);
end loop;
end;
else
if S (J) = '\' then
J := J + 1;
end if;
Set (Table, Current_State, Map (S (J)),
Value => Next_State);
end if;
J := J + 1;
end loop;
end;
Current_State := Current_State + 1;
-- If the next symbol is a special symbol
if J < End_Index
and then (S (J + 1) = '*' or else
S (J + 1) = '+' or else
S (J + 1) = '?')
then
J := J + 1;
Create_Repetition
(S (J),
Current_State - 1,
Current_State,
Last_Start,
End_State);
else
Last_Start := Current_State - 1;
if End_State /= 0 then
Add_Empty_Char (End_State, Last_Start);
end if;
End_State := Current_State;
end if;
when '*' | '+' | '?' | Close_Paren | Close_Bracket =>
Raise_Exception
("Incorrect character in regular expression :", J);
when others =>
Current_State := Current_State + 1;
-- Create the state for the symbol S (J)
if S (J) = '.' then
for K in 0 .. Alphabet_Size loop
Set (Table, Current_State, K,
Value => Current_State + 1);
end loop;
else
if S (J) = '\' then
J := J + 1;
end if;
Set (Table, Current_State, Map (S (J)),
Value => Current_State + 1);
end if;
Current_State := Current_State + 1;
-- If the next symbol is a special symbol
if J < End_Index
and then (S (J + 1) = '*' or else
S (J + 1) = '+' or else
S (J + 1) = '?')
then
J := J + 1;
Create_Repetition
(S (J),
Current_State - 1,
Current_State,
Last_Start,
End_State);
else
Last_Start := Current_State - 1;
if End_State /= 0 then
Add_Empty_Char (End_State, Last_Start);
end if;
End_State := Current_State;
end if;
end case;
if Start_State = 0 then
Start_State := Last_Start;
end if;
J := J + 1;
end loop;
end Create_Simple;
-------------------------
-- Next_Sub_Expression --
-------------------------
function Next_Sub_Expression
(Start_Index : Integer;
End_Index : Integer)
return Integer
is
J : Integer := Start_Index;
Start_On_Alter : Boolean := False;
begin
if S (J) = '|' then
Start_On_Alter := True;
end if;
loop
exit when J = End_Index;
J := J + 1;
case S (J) is
when '\' =>
J := J + 1;
when Open_Bracket =>
loop
J := J + 1;
exit when S (J) = Close_Bracket;
if S (J) = '\' then
J := J + 1;
end if;
end loop;
when Open_Paren =>
J := Next_Sub_Expression (J, End_Index);
when Close_Paren =>
return J;
when '|' =>
if Start_On_Alter then
return J - 1;
end if;
when others =>
null;
end case;
end loop;
return J;
end Next_Sub_Expression;
-- Start of Create_Primary_Table
begin
Table.all := (others => (others => 0));
Create_Simple (S'First, S'Last, Start_State, End_State);
Num_States := Current_State;
end Create_Primary_Table;
-------------------------------
-- Create_Primary_Table_Glob --
-------------------------------
procedure Create_Primary_Table_Glob
(Table : out Regexp_Array_Access;
Num_States : out State_Index;
Start_State : out State_Index;
End_State : out State_Index)
is
Empty_Char : constant Column_Index := Alphabet_Size + 1;
Current_State : State_Index := 0;
-- Index of the last created state
procedure Add_Empty_Char
(State : State_Index;
To_State : State_Index);
-- Add a empty-character transition from State to To_State
procedure Create_Simple
(Start_Index : Integer;
End_Index : Integer;
Start_State : out State_Index;
End_State : out State_Index);
-- Fill the table for the S (Start_Index .. End_Index).
-- This is the recursive procedure called to handle () expressions
--------------------
-- Add_Empty_Char --
--------------------
procedure Add_Empty_Char
(State : State_Index;
To_State : State_Index)
is
J : Column_Index := Empty_Char;
begin
while Get (Table, State, J) /= 0 loop
J := J + 1;
end loop;
Set (Table, State, J,
Value => To_State);
end Add_Empty_Char;
-------------------
-- Create_Simple --
-------------------
procedure Create_Simple
(Start_Index : Integer;
End_Index : Integer;
Start_State : out State_Index;
End_State : out State_Index)
is
J : Integer := Start_Index;
Last_Start : State_Index := 0;
begin
Start_State := 0;
End_State := 0;
while J <= End_Index loop
case S (J) is
when Open_Bracket =>
Current_State := Current_State + 1;
declare
Next_State : State_Index := Current_State + 1;
begin
J := J + 1;
if S (J) = '^' then
J := J + 1;
Next_State := 0;
for Column in 0 .. Alphabet_Size loop
Set (Table, Current_State, Column,
Value => Current_State + 1);
end loop;
end if;
-- Automatically add the first character
if S (J) = '-' or S (J) = ']' then
Set (Table, Current_State, Map (S (J)),
Value => Current_State);
J := J + 1;
end if;
-- Loop till closing bracket found
loop
exit when S (J) = Close_Bracket;
if S (J) = '-'
and then S (J + 1) /= ']'
then
declare
Start : constant Integer := J - 1;
begin
J := J + 1;
if S (J) = '\' then
J := J + 1;
end if;
for Char in S (Start) .. S (J) loop
Set (Table, Current_State, Map (Char),
Value => Next_State);
end loop;
end;
else
if S (J) = '\' then
J := J + 1;
end if;
Set (Table, Current_State, Map (S (J)),
Value => Next_State);
end if;
J := J + 1;
end loop;
end;
Last_Start := Current_State;
Current_State := Current_State + 1;
if End_State /= 0 then
Add_Empty_Char (End_State, Last_Start);
end if;
End_State := Current_State;
when '{' =>
declare
End_Sub : Integer;
Start_Regexp_Sub : State_Index;
End_Regexp_Sub : State_Index;
Create_Start : State_Index := 0;
Create_End : State_Index := 0;
-- Initialized to avoid junk warning
begin
while S (J) /= '}' loop
-- First step : find sub pattern
End_Sub := J + 1;
while S (End_Sub) /= ','
and then S (End_Sub) /= '}'
loop
End_Sub := End_Sub + 1;
end loop;
-- Second step : create a sub pattern
Create_Simple
(J + 1,
End_Sub - 1,
Start_Regexp_Sub,
End_Regexp_Sub);
J := End_Sub;
-- Third step : create an alternative
if Create_Start = 0 then
Current_State := Current_State + 1;
Create_Start := Current_State;
Add_Empty_Char (Create_Start, Start_Regexp_Sub);
Current_State := Current_State + 1;
Create_End := Current_State;
Add_Empty_Char (End_Regexp_Sub, Create_End);
else
Current_State := Current_State + 1;
Add_Empty_Char (Current_State, Create_Start);
Create_Start := Current_State;
Add_Empty_Char (Create_Start, Start_Regexp_Sub);
Add_Empty_Char (End_Regexp_Sub, Create_End);
end if;
end loop;
if End_State /= 0 then
Add_Empty_Char (End_State, Create_Start);
end if;
End_State := Create_End;
Last_Start := Create_Start;
end;
when '*' =>
Current_State := Current_State + 1;
if End_State /= 0 then
Add_Empty_Char (End_State, Current_State);
end if;
Add_Empty_Char (Current_State, Current_State + 1);
Add_Empty_Char (Current_State, Current_State + 3);
Last_Start := Current_State;
Current_State := Current_State + 1;
for K in 0 .. Alphabet_Size loop
Set (Table, Current_State, K,
Value => Current_State + 1);
end loop;
Current_State := Current_State + 1;
Add_Empty_Char (Current_State, Current_State + 1);
Current_State := Current_State + 1;
Add_Empty_Char (Current_State, Last_Start);
End_State := Current_State;
when others =>
Current_State := Current_State + 1;
if S (J) = '?' then
for K in 0 .. Alphabet_Size loop
Set (Table, Current_State, K,
Value => Current_State + 1);
end loop;
else
if S (J) = '\' then
J := J + 1;
end if;
-- Create the state for the symbol S (J)
Set (Table, Current_State, Map (S (J)),
Value => Current_State + 1);
end if;
Last_Start := Current_State;
Current_State := Current_State + 1;
if End_State /= 0 then
Add_Empty_Char (End_State, Last_Start);
end if;
End_State := Current_State;
end case;
if Start_State = 0 then
Start_State := Last_Start;
end if;
J := J + 1;
end loop;
end Create_Simple;
-- Start of processing for Create_Primary_Table_Glob
begin
Table.all := (others => (others => 0));
Create_Simple (S'First, S'Last, Start_State, End_State);
Num_States := Current_State;
end Create_Primary_Table_Glob;
----------------------------
-- Create_Secondary_Table --
----------------------------
function Create_Secondary_Table
(First_Table : Regexp_Array_Access;
Num_States : State_Index;
Start_State : State_Index;
End_State : State_Index) return Regexp
is
pragma Warnings (Off, Num_States);
Last_Index : constant State_Index := First_Table'Last (1);
type Meta_State is array (1 .. Last_Index) of Boolean;
Table : Regexp_Array (1 .. Last_Index, 0 .. Alphabet_Size) :=
(others => (others => 0));
Meta_States : array (1 .. Last_Index + 1) of Meta_State :=
(others => (others => False));
Temp_State_Not_Null : Boolean;
Is_Final : Boolean_Array (1 .. Last_Index) := (others => False);
Current_State : State_Index := 1;
Nb_State : State_Index := 1;
procedure Closure
(State : in out Meta_State;
Item : State_Index);
-- Compute the closure of the state (that is every other state which
-- has a empty-character transition) and add it to the state
-------------
-- Closure --
-------------
procedure Closure
(State : in out Meta_State;
Item : State_Index)
is
begin
if State (Item) then
return;
end if;
State (Item) := True;
for Column in Alphabet_Size + 1 .. First_Table'Last (2) loop
if First_Table (Item, Column) = 0 then
return;
end if;
Closure (State, First_Table (Item, Column));
end loop;
end Closure;
-- Start of procesing for Create_Secondary_Table
begin
-- Create a new state
Closure (Meta_States (Current_State), Start_State);
while Current_State <= Nb_State loop
-- If this new meta-state includes the primary table end state,
-- then this meta-state will be a final state in the regexp
if Meta_States (Current_State)(End_State) then
Is_Final (Current_State) := True;
end if;
-- For every character in the regexp, calculate the possible
-- transitions from Current_State
for Column in 0 .. Alphabet_Size loop
Meta_States (Nb_State + 1) := (others => False);
Temp_State_Not_Null := False;
for K in Meta_States (Current_State)'Range loop
if Meta_States (Current_State)(K)
and then First_Table (K, Column) /= 0
then
Closure
(Meta_States (Nb_State + 1), First_Table (K, Column));
Temp_State_Not_Null := True;
end if;
end loop;
-- If at least one transition existed
if Temp_State_Not_Null then
-- Check if this new state corresponds to an old one
for K in 1 .. Nb_State loop
if Meta_States (K) = Meta_States (Nb_State + 1) then
Table (Current_State, Column) := K;
exit;
end if;
end loop;
-- If not, create a new state
if Table (Current_State, Column) = 0 then
Nb_State := Nb_State + 1;
Table (Current_State, Column) := Nb_State;
end if;
end if;
end loop;
Current_State := Current_State + 1;
end loop;
-- Returns the regexp
declare
R : Regexp_Access;
begin
R := new Regexp_Value (Alphabet_Size => Alphabet_Size,
Num_States => Nb_State);
R.Map := Map;
R.Is_Final := Is_Final (1 .. Nb_State);
R.Case_Sensitive := Case_Sensitive;
for State in 1 .. Nb_State loop
for K in 0 .. Alphabet_Size loop
R.States (State, K) := Table (State, K);
end loop;
end loop;
return (Ada.Finalization.Controlled with R => R);
end;
end Create_Secondary_Table;
---------------------
-- Raise_Exception --
---------------------
procedure Raise_Exception
(M : String;
Index : Integer)
is
begin
Ada.Exceptions.Raise_Exception
(Error_In_Regexp'Identity, M & " at offset " & Index'Img);
end Raise_Exception;
-- Start of processing for Compile
begin
-- Special case for the empty string: it always matches, and the
-- following processing would fail on it.
if S = "" then
return (Ada.Finalization.Controlled with
R => new Regexp_Value'
(Alphabet_Size => 0,
Num_States => 1,
Map => (others => 0),
States => (others => (others => 1)),
Is_Final => (others => True),
Case_Sensitive => True));
end if;
if not Case_Sensitive then
System.Case_Util.To_Lower (S);
end if;
Create_Mapping;
-- Creates the primary table
declare
Table : Regexp_Array_Access;
Num_States : State_Index;
Start_State : State_Index;
End_State : State_Index;
R : Regexp;
begin
Table := new Regexp_Array (1 .. 100,
0 .. Alphabet_Size + 10);
if not Glob then
Create_Primary_Table (Table, Num_States, Start_State, End_State);
else
Create_Primary_Table_Glob
(Table, Num_States, Start_State, End_State);
end if;
-- Creates the secondary table
R := Create_Secondary_Table
(Table, Num_States, Start_State, End_State);
Free (Table);
return R;
end;
end Compile;
--------------
-- Finalize --
--------------
procedure Finalize (R : in out Regexp) is
procedure Free is new
Ada.Unchecked_Deallocation (Regexp_Value, Regexp_Access);
begin
Free (R.R);
end Finalize;
---------
-- Get --
---------
function Get
(Table : Regexp_Array_Access;
State : State_Index;
Column : Column_Index) return State_Index
is
begin
if State <= Table'Last (1)
and then Column <= Table'Last (2)
then
return Table (State, Column);
else
return 0;
end if;
end Get;
-----------
-- Match --
-----------
function Match (S : String; R : Regexp) return Boolean is
Current_State : State_Index := 1;
begin
if R.R = null then
raise Constraint_Error;
end if;
for Char in S'Range loop
if R.R.Case_Sensitive then
Current_State := R.R.States (Current_State, R.R.Map (S (Char)));
else
Current_State :=
R.R.States (Current_State,
R.R.Map (System.Case_Util.To_Lower (S (Char))));
end if;
if Current_State = 0 then
return False;
end if;
end loop;
return R.R.Is_Final (Current_State);
end Match;
---------
-- Set --
---------
procedure Set
(Table : in out Regexp_Array_Access;
State : State_Index;
Column : Column_Index;
Value : State_Index)
is
New_Lines : State_Index;
New_Columns : Column_Index;
New_Table : Regexp_Array_Access;
begin
if State <= Table'Last (1)
and then Column <= Table'Last (2)
then
Table (State, Column) := Value;
else
-- Doubles the size of the table until it is big enough that
-- (State, Column) is a valid index
New_Lines := Table'Last (1) * (State / Table'Last (1) + 1);
New_Columns := Table'Last (2) * (Column / Table'Last (2) + 1);
New_Table := new Regexp_Array (Table'First (1) .. New_Lines,
Table'First (2) .. New_Columns);
New_Table.all := (others => (others => 0));
for J in Table'Range (1) loop
for K in Table'Range (2) loop
New_Table (J, K) := Table (J, K);
end loop;
end loop;
Free (Table);
Table := New_Table;
Table (State, Column) := Value;
end if;
end Set;
end System.Regexp;
------------------------------------------------------------------------------
-- --
-- GNAT COMPILER COMPONENTS --
-- --
-- S Y S T E M . R E G E X P --
-- --
-- S p e c --
-- --
-- Copyright (C) 1998-2007, AdaCore --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- ware Foundation; either version 2, or (at your option) any later ver- --
-- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
-- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
-- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
-- for more details. You should have received a copy of the GNU General --
-- Public License distributed with GNAT; see file COPYING. If not, write --
-- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
-- Boston, MA 02110-1301, USA. --
-- --
-- As a special exception, if other files instantiate generics from this --
-- unit, or you link this unit with other files to produce an executable, --
-- this unit does not by itself cause the resulting executable to be --
-- covered by the GNU General Public License. This exception does not --
-- however invalidate any other reasons why the executable file might be --
-- covered by the GNU Public License. --
-- --
-- GNAT was originally developed by the GNAT team at New York University. --
-- Extensive contributions were provided by Ada Core Technologies Inc. --
-- --
------------------------------------------------------------------------------
-- Simple Regular expression matching
-- This package provides a simple implementation of a regular expression
-- pattern matching algorithm, using a subset of the syntax of regular
-- expressions copied from familiar Unix style utilities.
-- Note: this package is in the System hierarchy so that it can be directly
-- be used by other predefined packages. User access to this package is via
-- a renaming of this package in GNAT.Regexp (file g-regexp.ads).
with Ada.Finalization;
package System.Regexp is
-- The regular expression must first be compiled, using the Compile
-- function, which creates a finite state matching table, allowing
-- very fast matching once the expression has been compiled.
-- The following is the form of a regular expression, expressed in Ada
-- reference manual style BNF is as follows
-- regexp ::= term
-- regexp ::= term | term -- alternation (term or term ...)
-- term ::= item
-- term ::= item item ... -- concatenation (item then item)
-- item ::= elmt -- match elmt
-- item ::= elmt * -- zero or more elmt's
-- item ::= elmt + -- one or more elmt's
-- item ::= elmt ? -- matches elmt or nothing
-- elmt ::= nchr -- matches given character
-- elmt ::= [nchr nchr ...] -- matches any character listed
-- elmt ::= [^ nchr nchr ...] -- matches any character not listed
-- elmt ::= [char - char] -- matches chars in given range
-- elmt ::= . -- matches any single character
-- elmt ::= ( regexp ) -- parens used for grouping
-- char ::= any character, including special characters
-- nchr ::= any character except \()[].*+?^ or \char to match char
-- ... is used to indication repetition (one or more terms)
-- See also regexp(1) man page on Unix systems for further details
-- A second kind of regular expressions is provided. This one is more
-- like the wild card patterns used in file names by the Unix shell (or
-- DOS prompt) command lines. The grammar is the following:
-- regexp ::= term
-- term ::= elmt
-- term ::= elmt elmt ... -- concatenation (elmt then elmt)
-- term ::= * -- any string of 0 or more characters
-- term ::= ? -- matches any character
-- term ::= [char char ...] -- matches any character listed
-- term ::= [char - char] -- matches any character in given range
-- term ::= {elmt, elmt, ...} -- alternation (matches any of elmt)
-- Important note : This package was mainly intended to match regular
-- expressions against file names. The whole string has to match the
-- regular expression. If only a substring matches, then the function
-- Match will return False.
type Regexp is private;
-- Private type used to represent a regular expression
Error_In_Regexp : exception;
-- Exception raised when an error is found in the regular expression
function Compile
(Pattern : String;
Glob : Boolean := False;
Case_Sensitive : Boolean := True) return Regexp;
-- Compiles a regular expression S. If the syntax of the given
-- expression is invalid (does not match above grammar, Error_In_Regexp
-- is raised. If Glob is True, the pattern is considered as a 'globbing
-- pattern', that is a pattern as given by the second grammar above.
-- As a special case, if Pattern is the empty string it will always
-- match.
function Match (S : String; R : Regexp) return Boolean;
-- True if S matches R, otherwise False. Raises Constraint_Error if
-- R is an uninitialized regular expression value.
private
type Regexp_Value;
type Regexp_Access is access Regexp_Value;
type Regexp is new Ada.Finalization.Controlled with record
R : Regexp_Access := null;
end record;
pragma Finalize_Storage_Only (Regexp);
procedure Finalize (R : in out Regexp);
-- Free the memory occupied by R
procedure Adjust (R : in out Regexp);
-- Called after an assignment (do a copy of the Regexp_Access.all)
end System.Regexp;
This source diff could not be displayed because it is too large. You can view the blob instead.
------------------------------------------------------------------------------
-- --
-- GNAT LIBRARY COMPONENTS --
-- --
-- S Y S T E M . R E G P A T --
-- --
-- S p e c --
-- --
-- Copyright (C) 1986 by University of Toronto. --
-- Copyright (C) 1996-2007, AdaCore --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- ware Foundation; either version 2, or (at your option) any later ver- --
-- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
-- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
-- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
-- for more details. You should have received a copy of the GNU General --
-- Public License distributed with GNAT; see file COPYING. If not, write --
-- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
-- Boston, MA 02110-1301, USA. --
-- --
-- As a special exception, if other files instantiate generics from this --
-- unit, or you link this unit with other files to produce an executable, --
-- this unit does not by itself cause the resulting executable to be --
-- covered by the GNU General Public License. This exception does not --
-- however invalidate any other reasons why the executable file might be --
-- covered by the GNU Public License. --
-- --
-- GNAT was originally developed by the GNAT team at New York University. --
-- Extensive contributions were provided by Ada Core Technologies Inc. --
-- --
------------------------------------------------------------------------------
-- This package implements roughly the same set of regular expressions as
-- are available in the Perl or Python programming languages.
-- This is an extension of the original V7 style regular expression library
-- written in C by Henry Spencer. Apart from the translation to Ada, the
-- interface has been considerably changed to use the Ada String type
-- instead of C-style nul-terminated strings.
-- Note: this package is in the System hierarchy so that it can be directly
-- be used by other predefined packages. User access to this package is via
-- a renaming of this package in GNAT.Regpat (file g-regpat.ads).
package System.Regpat is
pragma Preelaborate;
-- The grammar is the following:
-- regexp ::= expr
-- ::= ^ expr -- anchor at the beginning of string
-- ::= expr $ -- anchor at the end of string
-- expr ::= term
-- ::= term | term -- alternation (term or term ...)
-- term ::= item
-- ::= item item ... -- concatenation (item then item)
-- item ::= elmt -- match elmt
-- ::= elmt * -- zero or more elmt's
-- ::= elmt + -- one or more elmt's
-- ::= elmt ? -- matches elmt or nothing
-- ::= elmt *? -- zero or more times, minimum number
-- ::= elmt +? -- one or more times, minimum number
-- ::= elmt ?? -- zero or one time, minimum number
-- ::= elmt { num } -- matches elmt exactly num times
-- ::= elmt { num , } -- matches elmt at least num times
-- ::= elmt { num , num2 } -- matches between num and num2 times
-- ::= elmt { num }? -- matches elmt exactly num times
-- ::= elmt { num , }? -- matches elmt at least num times
-- non-greedy version
-- ::= elmt { num , num2 }? -- matches between num and num2 times
-- non-greedy version
-- elmt ::= nchr -- matches given character
-- ::= [range range ...] -- matches any character listed
-- ::= [^ range range ...] -- matches any character not listed
-- ::= . -- matches any single character
-- -- except newlines
-- ::= ( expr ) -- parens used for grouping
-- ::= \ num -- reference to num-th parenthesis
-- range ::= char - char -- matches chars in given range
-- ::= nchr
-- ::= [: posix :] -- any character in the POSIX range
-- ::= [:^ posix :] -- not in the POSIX range
-- posix ::= alnum -- alphanumeric characters
-- ::= alpha -- alphabetic characters
-- ::= ascii -- ascii characters (0 .. 127)
-- ::= cntrl -- control chars (0..31, 127..159)
-- ::= digit -- digits ('0' .. '9')
-- ::= graph -- graphic chars (32..126, 160..255)
-- ::= lower -- lower case characters
-- ::= print -- printable characters (32..127)
-- -- and whitespaces (9 .. 13)
-- ::= punct -- printable, except alphanumeric
-- ::= space -- space characters
-- ::= upper -- upper case characters
-- ::= word -- alphanumeric characters
-- ::= xdigit -- hexadecimal chars (0..9, a..f)
-- char ::= any character, including special characters
-- ASCII.NUL is not supported.
-- nchr ::= any character except \()[].*+?^ or \char to match char
-- \n means a newline (ASCII.LF)
-- \t means a tab (ASCII.HT)
-- \r means a return (ASCII.CR)
-- \b matches the empty string at the beginning or end of a
-- word. A word is defined as a set of alphanumerical
-- characters (see \w below).
-- \B matches the empty string only when *not* at the
-- beginning or end of a word.
-- \d matches any digit character ([0-9])
-- \D matches any non digit character ([^0-9])
-- \s matches any white space character. This is equivalent
-- to [ \t\n\r\f\v] (tab, form-feed, vertical-tab,...
-- \S matches any non-white space character.
-- \w matches any alphanumeric character or underscore.
-- This include accented letters, as defined in the
-- package Ada.Characters.Handling.
-- \W matches any non-alphanumeric character.
-- \A match the empty string only at the beginning of the
-- string, whatever flags are used for Compile (the
-- behavior of ^ can change, see Regexp_Flags below).
-- \G match the empty string only at the end of the
-- string, whatever flags are used for Compile (the
-- behavior of $ can change, see Regexp_Flags below).
-- ... ::= is used to indication repetition (one or more terms)
-- Embedded newlines are not matched by the ^ operator.
-- It is possible to retrieve the substring matched a parenthesis
-- expression. Although the depth of parenthesis is not limited in the
-- regexp, only the first 9 substrings can be retrieved.
-- The highest value possible for the arguments to the curly operator ({})
-- are given by the constant Max_Curly_Repeat below.
-- The operators '*', '+', '?' and '{}' always match the longest possible
-- substring. They all have a non-greedy version (with an extra ? after the
-- operator), which matches the shortest possible substring.
-- For instance:
-- regexp="<.*>" string="<h1>title</h1>" matches="<h1>title</h1>"
-- regexp="<.*?>" string="<h1>title</h1>" matches="<h1>"
--
-- '{' and '}' are only considered as special characters if they appear
-- in a substring that looks exactly like '{n}', '{n,m}' or '{n,}', where
-- n and m are digits. No space is allowed. In other contexts, the curly
-- braces will simply be treated as normal characters.
-- Compiling Regular Expressions
-- =============================
-- To use this package, you first need to compile the regular expression
-- (a string) into a byte-code program, in a Pattern_Matcher structure.
-- This first step checks that the regexp is valid, and optimizes the
-- matching algorithms of the second step.
-- Two versions of the Compile subprogram are given: one in which this
-- package will compute itself the best possible size to allocate for the
-- byte code; the other where you must allocate enough memory yourself. An
-- exception is raised if there is not enough memory.
-- declare
-- Regexp : String := "a|b";
-- Matcher : Pattern_Matcher := Compile (Regexp);
-- -- The size for matcher is automatically allocated
-- Matcher2 : Pattern_Matcher (1000);
-- -- Some space is allocated directly.
-- begin
-- Compile (Matcher2, Regexp);
-- ...
-- end;
-- Note that the second version is significantly faster, since with the
-- first version the regular expression has in fact to be compiled twice
-- (first to compute the size, then to generate the byte code).
-- Note also that you cannot use the function version of Compile if you
-- specify the size of the Pattern_Matcher, since the discriminants will
-- most probably be different and you will get a Constraint_Error
-- Matching Strings
-- ================
-- Once the regular expression has been compiled, you can use it as often
-- as needed to match strings.
-- Several versions of the Match subprogram are provided, with different
-- parameters and return results.
-- See the description under each of these subprograms
-- Here is a short example showing how to get the substring matched by
-- the first parenthesis pair.
-- declare
-- Matches : Match_Array (0 .. 1);
-- Regexp : String := "a(b|c)d";
-- Str : String := "gacdg";
-- begin
-- Match (Compile (Regexp), Str, Matches);
-- return Str (Matches (1).First .. Matches (1).Last);
-- -- returns 'c'
-- end;
-- Finding all occurrences
-- =======================
-- Finding all the occurrences of a regular expression in a string cannot
-- be done by simply passing a slice of the string. This wouldn't work for
-- anchored regular expressions (the ones starting with "^" or ending with
-- "$").
-- Instead, you need to use the last parameter to Match (Data_First), as in
-- the following loop:
-- declare
-- Str : String :=
-- "-- first line" & ASCII.LF & "-- second line";
-- Matches : Match_Array (0 .. 0);
-- Regexp : Pattern_Matcher := Compile ("^--", Multiple_Lines);
-- Current : Natural := Str'First;
-- begin
-- loop
-- Match (Regexp, Str, Matches, Current);
-- exit when Matches (0) = No_Match;
--
-- -- Process the match at position Matches (0).First
--
-- Current := Matches (0).Last + 1;
-- end loop;
-- end;
-- String Substitution
-- ===================
-- No subprogram is currently provided for string substitution.
-- However, this is easy to simulate with the parenthesis groups, as
-- shown below.
-- This example swaps the first two words of the string:
-- declare
-- Regexp : String := "([a-z]+) +([a-z]+)";
-- Str : String := " first second third ";
-- Matches : Match_Array (0 .. 2);
-- begin
-- Match (Compile (Regexp), Str, Matches);
-- return Str (Str'First .. Matches (1).First - 1)
-- & Str (Matches (2).First .. Matches (2).Last)
-- & " "
-- & Str (Matches (1).First .. Matches (1).Last)
-- & Str (Matches (2).Last + 1 .. Str'Last);
-- -- returns " second first third "
-- end;
---------------
-- Constants --
---------------
Expression_Error : exception;
-- This exception is raised when trying to compile an invalid regular
-- expression. All subprograms taking an expression as parameter may raise
-- Expression_Error.
Max_Paren_Count : constant := 255;
-- Maximum number of parenthesis in a regular expression. This is limited
-- by the size of a Character, as found in the byte-compiled version of
-- regular expressions.
Max_Curly_Repeat : constant := 32767;
-- Maximum number of repetition for the curly operator. The digits in the
-- {n}, {n,} and {n,m } operators cannot be higher than this constant,
-- since they have to fit on two characters in the byte-compiled version of
-- regular expressions.
Max_Program_Size : constant := 2**15 - 1;
-- Maximum size that can be allocated for a program
type Program_Size is range 0 .. Max_Program_Size;
for Program_Size'Size use 16;
-- Number of bytes allocated for the byte-compiled version of a regular
-- expression. The size required depends on the complexity of the regular
-- expression in a complex manner that is undocumented (other than in the
-- body of the Compile procedure). Normally the size is automatically set
-- and the programmer need not be concerned about it. There are two
-- exceptions to this. First in the calls to Match, it is possible to
-- specify a non-zero size that is known to be large enough. This can
-- slightly increase the efficiency by avoiding a copy. Second, in the case
-- of calling compile, it is possible using the procedural form of Compile
-- to use a single Pattern_Matcher variable for several different
-- expressions by setting its size sufficiently large.
Auto_Size : constant := 0;
-- Used in calls to Match to indicate that the Size should be set to
-- a value appropriate to the expression being used automatically.
type Regexp_Flags is mod 256;
for Regexp_Flags'Size use 8;
-- Flags that can be given at compile time to specify default
-- properties for the regular expression.
No_Flags : constant Regexp_Flags;
Case_Insensitive : constant Regexp_Flags;
-- The automaton is optimized so that the matching is done in a case
-- insensitive manner (upper case characters and lower case characters
-- are all treated the same way).
Single_Line : constant Regexp_Flags;
-- Treat the Data we are matching as a single line. This means that
-- ^ and $ will ignore \n (unless Multiple_Lines is also specified),
-- and that '.' will match \n.
Multiple_Lines : constant Regexp_Flags;
-- Treat the Data as multiple lines. This means that ^ and $ will also
-- match on internal newlines (ASCII.LF), in addition to the beginning
-- and end of the string.
--
-- This can be combined with Single_Line.
-----------------
-- Match_Array --
-----------------
subtype Match_Count is Natural range 0 .. Max_Paren_Count;
type Match_Location is record
First : Natural := 0;
Last : Natural := 0;
end record;
type Match_Array is array (Match_Count range <>) of Match_Location;
-- Used for regular expressions that can contain parenthesized
-- subexpressions. Certain Match subprograms below produce Matches of type
-- Match_Array. Each component of Matches is set to the subrange of the
-- matches substring, or to No_Match if no match. Matches (N) is for the
-- N'th parenthesized subexpressions; Matches (0) is for the whole
-- expression.
--
-- For instance, if your regular expression is: "a((b*)c+)(d+)", then
-- 12 3
-- Matches (0) is for "a((b*)c+)(d+)" (the entire expression)
-- Matches (1) is for "(b*)c+"
-- Matches (2) is for "c+"
-- Matches (3) is for "d+"
--
-- The number of parenthesis groups that can be retrieved is limited only
-- by Max_Paren_Count.
--
-- Normally, the bounds of the Matches actual parameter will be
-- 0 .. Paren_Count (Regexp), to get all the matches. However, it is fine
-- if Matches is shorter than that on either end; missing components will
-- be ignored. Thus, in the above example, you could use 2 .. 2 if all you
-- care about it the second parenthesis pair "b*". Likewise, if
-- Matches'Last > Paren_Count (Regexp), the extra components will be set to
-- No_Match.
No_Match : constant Match_Location := (First => 0, Last => 0);
-- The No_Match constant is (0, 0) to differentiate between matching a null
-- string at position 1, which uses (1, 0) and no match at all.
---------------------------------
-- Pattern_Matcher Compilation --
---------------------------------
-- The subprograms here are used to precompile regular expressions for use
-- in subsequent Match calls. Precompilation improves efficiency if the
-- same regular expression is to be used in more than one Match call.
type Pattern_Matcher (Size : Program_Size) is private;
-- Type used to represent a regular expression compiled into byte code
Never_Match : constant Pattern_Matcher;
-- A regular expression that never matches anything
function Compile
(Expression : String;
Flags : Regexp_Flags := No_Flags) return Pattern_Matcher;
-- Compile a regular expression into internal code
--
-- Raises Expression_Error if Expression is not a legal regular expression
--
-- The appropriate size is calculated automatically to correspond to the
-- provided expression. This is the normal default method of compilation.
-- Note that it is generally not possible to assign the result of two
-- different calls to this Compile function to the same Pattern_Matcher
-- variable, since the sizes will differ.
--
-- Flags is the default value to use to set properties for Expression
-- (e.g. case sensitivity,...).
procedure Compile
(Matcher : out Pattern_Matcher;
Expression : String;
Final_Code_Size : out Program_Size;
Flags : Regexp_Flags := No_Flags);
-- Compile a regular expression into into internal code
-- This procedure is significantly faster than the Compile function since
-- it avoids the extra step of precomputing the required size.
--
-- However, it requires the user to provide a Pattern_Matcher variable
-- whose size is preset to a large enough value. One advantage of this
-- approach, in addition to the improved efficiency, is that the same
-- Pattern_Matcher variable can be used to hold the compiled code for
-- several different regular expressions by setting a size that is large
-- enough to accomodate all possibilities.
--
-- In this version of the procedure call, the actual required code size is
-- returned. Also if Matcher.Size is zero on entry, then the resulting code
-- is not stored. A call with Matcher.Size set to Auto_Size can thus be
-- used to determine the space required for compiling the given regular
-- expression.
--
-- This function raises Storage_Error if Matcher is too small to hold
-- the resulting code (i.e. Matcher.Size has too small a value).
--
-- Expression_Error is raised if the string Expression does not contain
-- a valid regular expression.
--
-- Flags is the default value to use to set properties for Expression (case
-- sensitivity,...).
procedure Compile
(Matcher : out Pattern_Matcher;
Expression : String;
Flags : Regexp_Flags := No_Flags);
-- Same procedure as above, expect it does not return the final
-- program size, and Matcher.Size cannot be Auto_Size.
function Paren_Count (Regexp : Pattern_Matcher) return Match_Count;
pragma Inline (Paren_Count);
-- Return the number of parenthesis pairs in Regexp.
--
-- This is the maximum index that will be filled if a Match_Array is
-- used as an argument to Match.
--
-- Thus, if you want to be sure to get all the parenthesis, you should
-- do something like:
--
-- declare
-- Regexp : Pattern_Matcher := Compile ("a(b*)(c+)");
-- Matched : Match_Array (0 .. Paren_Count (Regexp));
-- begin
-- Match (Regexp, "a string", Matched);
-- end;
-------------
-- Quoting --
-------------
function Quote (Str : String) return String;
-- Return a version of Str so that every special character is quoted.
-- The resulting string can be used in a regular expression to match
-- exactly Str, whatever character was present in Str.
--------------
-- Matching --
--------------
-- The Match subprograms are given a regular expression in string
-- form, and perform the corresponding match. The following parameters
-- are present in all forms of the Match call.
-- Expression contains the regular expression to be matched as a string
-- Data contains the string to be matched
-- Data_First is the lower bound for the match, i.e. Data (Data_First)
-- will be the first character to be examined. If Data_First is set to
-- the special value of -1 (the default), then the first character to
-- be examined is Data (Data_First). However, the regular expression
-- character ^ (start of string) still refers to the first character
-- of the full string (Data (Data'First)), which is why there is a
-- separate mechanism for specifying Data_First.
-- Data_Last is the upper bound for the match, i.e. Data (Data_Last)
-- will be the last character to be examined. If Data_Last is set to
-- the special value of Positive'Last (the default), then the last
-- character to be examined is Data (Data_Last). However, the regular
-- expression character $ (end of string) still refers to the last
-- character of the full string (Data (Data'Last)), which is why there
-- is a separate mechanism for specifying Data_Last.
-- Note: the use of Data_First and Data_Last is not equivalent to
-- simply passing a slice as Expression because of the handling of
-- regular expression characters ^ and $.
-- Size is the size allocated for the compiled byte code. Normally
-- this is defaulted to Auto_Size which means that the appropriate
-- size is allocated automatically. It is possible to specify an
-- explicit size, which must be sufficiently large. This slightly
-- increases the efficiency by avoiding the extra step of computing
-- the appropriate size.
-- The following exceptions can be raised in calls to Match
--
-- Storage_Error is raised if a non-zero value is given for Size
-- and it is too small to hold the compiled byte code.
--
-- Expression_Error is raised if the given expression is not a legal
-- regular expression.
procedure Match
(Expression : String;
Data : String;
Matches : out Match_Array;
Size : Program_Size := Auto_Size;
Data_First : Integer := -1;
Data_Last : Positive := Positive'Last);
-- This version returns the result of the match stored in Match_Array;
-- see comments under Match_Array above for details.
function Match
(Expression : String;
Data : String;
Size : Program_Size := Auto_Size;
Data_First : Integer := -1;
Data_Last : Positive := Positive'Last) return Natural;
-- This version returns the position where Data matches, or if there is
-- no match, then the value Data'First - 1.
function Match
(Expression : String;
Data : String;
Size : Program_Size := Auto_Size;
Data_First : Integer := -1;
Data_Last : Positive := Positive'Last) return Boolean;
-- This version returns True if the match succeeds, False otherwise
------------------------------------------------
-- Matching a Pre-Compiled Regular Expression --
------------------------------------------------
-- The following functions are significantly faster if you need to reuse
-- the same regular expression multiple times, since you only have to
-- compile it once. For these functions you must first compile the
-- expression with a call to Compile as previously described.
-- The parameters Data, Data_First and Data_Last are as described
-- in the previous section.
function Match
(Self : Pattern_Matcher;
Data : String;
Data_First : Integer := -1;
Data_Last : Positive := Positive'Last) return Natural;
-- Match Data using the given pattern matcher. Returns the position
-- where Data matches, or (Data'First - 1) if there is no match.
function Match
(Self : Pattern_Matcher;
Data : String;
Data_First : Integer := -1;
Data_Last : Positive := Positive'Last) return Boolean;
-- Return True if Data matches using the given pattern matcher
pragma Inline (Match);
-- All except the last one below
procedure Match
(Self : Pattern_Matcher;
Data : String;
Matches : out Match_Array;
Data_First : Integer := -1;
Data_Last : Positive := Positive'Last);
-- Match Data using the given pattern matcher and store result in Matches;
-- see comments under Match_Array above for details.
-----------
-- Debug --
-----------
procedure Dump (Self : Pattern_Matcher);
-- Dump the compiled version of the regular expression matched by Self
--------------------------
-- Private Declarations --
--------------------------
private
subtype Pointer is Program_Size;
-- The Pointer type is used to point into Program_Data
-- Note that the pointer type is not necessarily 2 bytes
-- although it is stored in the program using 2 bytes
type Program_Data is array (Pointer range <>) of Character;
Program_First : constant := 1;
-- The "internal use only" fields in regexp are present to pass info from
-- compile to execute that permits the execute phase to run lots faster on
-- simple cases. They are:
-- First character that must begin a match or ASCII.Nul
-- Anchored true iff match must start at beginning of line
-- Must_Have pointer to string that match must include or null
-- Must_Have_Length length of Must_Have string
-- First and Anchored permit very fast decisions on suitable starting
-- points for a match, cutting down the work a lot. Must_Have permits fast
-- rejection of lines that cannot possibly match.
-- The Must_Have tests are costly enough that Optimize supplies a Must_Have
-- only if the r.e. contains something potentially expensive (at present,
-- the only such thing detected is * or at the start of the r.e., which can
-- involve a lot of backup). The length is supplied because the test in
-- Execute needs it and Optimize is computing it anyway.
-- The initialization is meant to fail-safe in case the user of this
-- package tries to use an uninitialized matcher. This takes advantage
-- of the knowledge that ASCII.Nul translates to the end-of-program (EOP)
-- instruction code of the state machine.
No_Flags : constant Regexp_Flags := 0;
Case_Insensitive : constant Regexp_Flags := 1;
Single_Line : constant Regexp_Flags := 2;
Multiple_Lines : constant Regexp_Flags := 4;
type Pattern_Matcher (Size : Pointer) is record
First : Character := ASCII.NUL; -- internal use only
Anchored : Boolean := False; -- internal use only
Must_Have : Pointer := 0; -- internal use only
Must_Have_Length : Natural := 0; -- internal use only
Paren_Count : Natural := 0; -- # paren groups
Flags : Regexp_Flags := No_Flags;
Program : Program_Data (Program_First .. Size) :=
(others => ASCII.NUL);
end record;
Never_Match : constant Pattern_Matcher :=
(0, ASCII.NUL, False, 0, 0, 0, No_Flags, (others => ASCII.NUL));
end System.Regpat;
------------------------------------------------------------------------------
-- --
-- GNAT COMPILER COMPONENTS --
-- --
-- S Y S T E M . S T R I N G S --
-- --
-- B o d y --
-- --
-- Copyright (C) 1995-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- ware Foundation; either version 2, or (at your option) any later ver- --
-- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
-- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
-- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
-- for more details. You should have received a copy of the GNU General --
-- Public License distributed with GNAT; see file COPYING. If not, write --
-- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
-- Boston, MA 02110-1301, USA. --
-- --
-- As a special exception, if other files instantiate generics from this --
-- unit, or you link this unit with other files to produce an executable, --
-- this unit does not by itself cause the resulting executable to be --
-- covered by the GNU General Public License. This exception does not --
-- however invalidate any other reasons why the executable file might be --
-- covered by the GNU Public License. --
-- --
-- GNAT was originally developed by the GNAT team at New York University. --
-- Extensive contributions were provided by Ada Core Technologies Inc. --
-- --
------------------------------------------------------------------------------
package body System.Strings is
----------
-- Free --
----------
procedure Free (Arg : in out String_List_Access) is
X : String_Access;
procedure Free_Array is new Ada.Unchecked_Deallocation
(Object => String_List, Name => String_List_Access);
begin
-- First free all the String_Access components if any
if Arg /= null then
for J in Arg'Range loop
X := Arg (J);
Free (X);
end loop;
end if;
-- Now free the allocated array
Free_Array (Arg);
end Free;
end System.Strings;
------------------------------------------------------------------------------
-- --
-- GNAT COMPILER COMPONENTS --
-- --
-- S Y S T E M . S T R I N G S --
-- --
-- S p e c --
-- --
-- Copyright (C) 1995-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- ware Foundation; either version 2, or (at your option) any later ver- --
-- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
-- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
-- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
-- for more details. You should have received a copy of the GNU General --
-- Public License distributed with GNAT; see file COPYING. If not, write --
-- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
-- Boston, MA 02110-1301, USA. --
-- --
-- As a special exception, if other files instantiate generics from this --
-- unit, or you link this unit with other files to produce an executable, --
-- this unit does not by itself cause the resulting executable to be --
-- covered by the GNU General Public License. This exception does not --
-- however invalidate any other reasons why the executable file might be --
-- covered by the GNU Public License. --
-- --
-- GNAT was originally developed by the GNAT team at New York University. --
-- Extensive contributions were provided by Ada Core Technologies Inc. --
-- --
------------------------------------------------------------------------------
-- Common String access types and related subprograms
-- Note: this package is in the System hierarchy so that it can be directly
-- be used by other predefined packages. User access to this package is via
-- a renaming of this package in GNAT.String (file g-string.ads).
with Ada.Unchecked_Deallocation;
package System.Strings is
pragma Preelaborate;
type String_Access is access all String;
-- General purpose string access type. Note that the caller is
-- responsible for freeing allocated strings to avoid memory leaks.
procedure Free is new Ada.Unchecked_Deallocation
(Object => String, Name => String_Access);
-- This procedure is provided for freeing allocated values of type
-- String_Access.
type String_List is array (Positive range <>) of String_Access;
type String_List_Access is access all String_List;
-- General purpose array and pointer for list of string accesses
procedure Free (Arg : in out String_List_Access);
-- Frees the given array and all strings that its elements reference,
-- and then sets the argument to null. Provided for freeing allocated
-- values of this type.
end System.Strings;
------------------------------------------------------------------------------
-- --
-- GNAT RUN-TIME COMPONENTS --
-- --
-- S Y S T E M . T A S K _ L O C K --
-- --
-- B o d y --
-- --
-- Copyright (C) 1997-2007, AdaCore --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- ware Foundation; either version 2, or (at your option) any later ver- --
-- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
-- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
-- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
-- for more details. You should have received a copy of the GNU General --
-- Public License distributed with GNAT; see file COPYING. If not, write --
-- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
-- Boston, MA 02110-1301, USA. --
-- --
-- As a special exception, if other files instantiate generics from this --
-- unit, or you link this unit with other files to produce an executable, --
-- this unit does not by itself cause the resulting executable to be --
-- covered by the GNU General Public License. This exception does not --
-- however invalidate any other reasons why the executable file might be --
-- covered by the GNU Public License. --
-- --
-- GNAT was originally developed by the GNAT team at New York University. --
-- Extensive contributions were provided by Ada Core Technologies Inc. --
-- --
------------------------------------------------------------------------------
with System.Soft_Links;
-- used for Lock_Task, Unlock_Task
package body System.Task_Lock is
----------
-- Lock --
----------
procedure Lock is
begin
System.Soft_Links.Lock_Task.all;
end Lock;
------------
-- Unlock --
------------
procedure Unlock is
begin
System.Soft_Links.Unlock_Task.all;
end Unlock;
end System.Task_Lock;
------------------------------------------------------------------------------
-- --
-- GNAT RUN-TIME COMPONENTS --
-- --
-- S Y S T E M . T A S K _ L O C K --
-- --
-- S p e c --
-- --
-- Copyright (C) 1998-2007, AdaCore --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- ware Foundation; either version 2, or (at your option) any later ver- --
-- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
-- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
-- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
-- for more details. You should have received a copy of the GNU General --
-- Public License distributed with GNAT; see file COPYING. If not, write --
-- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
-- Boston, MA 02110-1301, USA. --
-- --
-- As a special exception, if other files instantiate generics from this --
-- unit, or you link this unit with other files to produce an executable, --
-- this unit does not by itself cause the resulting executable to be --
-- covered by the GNU General Public License. This exception does not --
-- however invalidate any other reasons why the executable file might be --
-- covered by the GNU Public License. --
-- --
-- GNAT was originally developed by the GNAT team at New York University. --
-- Extensive contributions were provided by Ada Core Technologies Inc. --
-- --
------------------------------------------------------------------------------
-- Simple task lock and unlock routines
-- A small package containing a task lock and unlock routines for creating
-- a critical region. The lock involved is a global lock, shared by all
-- tasks, and by all calls to these routines, so these routines should be
-- used with care to avoid unnecessary reduction of concurrency.
-- These routines may be used in a non-tasking program, and in that case
-- they have no effect (they do NOT cause the tasking runtime to be loaded).
-- Note: this package is in the System hierarchy so that it can be directly
-- be used by other predefined packages. User access to this package is via
-- a renaming of this package in GNAT.Task_Lock (file g-tasloc.ads).
package System.Task_Lock is
pragma Elaborate_Body;
procedure Lock;
pragma Inline (Lock);
-- Acquires the global lock, starts the execution of a critical region
-- which no other task can enter until the locking task calls Unlock
procedure Unlock;
pragma Inline (Unlock);
-- Releases the global lock, allowing another task to successfully
-- complete a Lock operation. Terminates the critical region.
--
-- The recommended protocol for using these two procedures is as
-- follows:
--
-- Locked_Processing : begin
-- Lock;
-- ...
-- TSL.Unlock;
--
-- exception
-- when others =>
-- Unlock;
-- raise;
-- end Locked_Processing;
--
-- This ensures that the lock is not left set if an exception is raised
-- explicitly or implicitly during the critical locked region.
--
-- Note on multiple calls to Lock: It is permissible to call Lock
-- more than once with no intervening Unlock from a single task,
-- and the lock will not be released until the corresponding number
-- of Unlock operations has been performed. For example:
--
-- System.Task_Lock.Lock; -- acquires lock
-- System.Task_Lock.Lock; -- no effect
-- System.Task_Lock.Lock; -- no effect
-- System.Task_Lock.Unlock; -- no effect
-- System.Task_Lock.Unlock; -- no effect
-- System.Task_Lock.Unlock; -- releases lock
--
-- However, as previously noted, the Task_Lock facility should only
-- be used for very local locks where the probability of conflict is
-- low, so usually this kind of nesting is not a good idea in any case.
-- In more complex locking situations, it is more appropriate to define
-- an appropriate protected type to provide the required locking.
--
-- It is an error to call Unlock when there has been no prior call to
-- Lock. The effect of such an erroneous call is undefined, and may
-- result in deadlock, or other malfunction of the run-time system.
end System.Task_Lock;
......@@ -6,7 +6,7 @@
-- --
-- B o d y --
-- --
-- Copyright (C) 2001-2005 Free Software Foundation, Inc. --
-- Copyright (C) 2001-2007, Free Software Foundation, Inc. --
-- --
-- GNARL is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -34,8 +34,8 @@
-- This version is for all targets, provided that System.IO.Put_Line is
-- functional. It prints debug information to Standard Output
with System.IO; use System.IO;
with GNAT.Regpat; use GNAT.Regpat;
with System.IO; use System.IO;
with System.Regpat; use System.Regpat;
----------------
-- Send_Trace --
......
This source diff could not be displayed because it is too large. You can view the blob instead.
------------------------------------------------------------------------------
-- --
-- GNAT RUN-TIME COMPONENTS --
-- --
-- S Y S T E M . U T F _ 3 2 --
-- --
-- S p e c --
-- --
-- Copyright (C) 2005-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- ware Foundation; either version 2, or (at your option) any later ver- --
-- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
-- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
-- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
-- for more details. You should have received a copy of the GNU General --
-- Public License distributed with GNAT; see file COPYING. If not, write --
-- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
-- Boston, MA 02110-1301, USA. --
-- --
-- As a special exception, if other files instantiate generics from this --
-- unit, or you link this unit with other files to produce an executable, --
-- this unit does not by itself cause the resulting executable to be --
-- covered by the GNU General Public License. This exception does not --
-- however invalidate any other reasons why the executable file might be --
-- covered by the GNU Public License. --
-- --
-- GNAT was originally developed by the GNAT team at New York University. --
-- Extensive contributions were provided by Ada Core Technologies Inc. --
-- --
------------------------------------------------------------------------------
-- This package is an internal package that provides basic character
-- classification capabilities needed by the compiler for handling full
-- 32-bit wide wide characters. We avoid the use of the actual type
-- Wide_Wide_Character, since we want to use these routines in the compiler
-- itself, and we want to be able to compile the compiler with old versions
-- of GNAT that did not implement Wide_Wide_Character.
-- System.UTF_32 should not be directly used from an application program, but
-- an equivalent package GNAT.UTF_32 can be used directly and provides exactly
-- the same services. The reason this package is in System is so that it can
-- with'ed by other packages in the Ada and System hierarchies.
package System.UTF_32 is
type UTF_32 is range 0 .. 16#7FFF_FFFF#;
-- So far, the only defined character codes are in 0 .. 16#01_FFFF#
-- The following type defines the categories from the unicode definitions.
-- The one addition we make is Fe, which represents the characters FFFE
-- and FFFF in any of the planes.
type Category is (
Cc, -- Other, Control
Cf, -- Other, Format
Cn, -- Other, Not Assigned
Co, -- Other, Private Use
Cs, -- Other, Surrogate
Ll, -- Letter, Lowercase
Lm, -- Letter, Modifier
Lo, -- Letter, Other
Lt, -- Letter, Titlecase
Lu, -- Letter, Uppercase
Mc, -- Mark, Spacing Combining
Me, -- Mark, Enclosing
Mn, -- Mark, Nonspacing
Nd, -- Number, Decimal Digit
Nl, -- Number, Letter
No, -- Number, Other
Pc, -- Punctuation, Connector
Pd, -- Punctuation, Dash
Pe, -- Punctuation, Close
Pf, -- Punctuation, Final quote
Pi, -- Punctuation, Initial quote
Po, -- Punctuation, Other
Ps, -- Punctuation, Open
Sc, -- Symbol, Currency
Sk, -- Symbol, Modifier
Sm, -- Symbol, Math
So, -- Symbol, Other
Zl, -- Separator, Line
Zp, -- Separator, Paragraph
Zs, -- Separator, Space
Fe); -- relative position FFFE/FFFF in any plane
function Get_Category (U : UTF_32) return Category;
-- Given a UTF32 code, returns corresponding Category, or Cn if
-- the code does not have an assigned unicode category.
-- The following functions perform category tests corresponding to lexical
-- classes defined in the Ada standard. There are two interfaces for each
-- function. The second takes a Category (e.g. returned by Get_Category).
-- The first takes a UTF_32 code. The form taking the UTF_32 code is
-- typically more efficient than calling Get_Category, but if several
-- different tests are to be performed on the same code, it is more
-- efficient to use Get_Category to get the category, then test the
-- resulting category.
function Is_UTF_32_Letter (U : UTF_32) return Boolean;
function Is_UTF_32_Letter (C : Category) return Boolean;
pragma Inline (Is_UTF_32_Letter);
-- Returns true iff U is a letter that can be used to start an identifier,
-- or if C is one of the corresponding categories, which are the following:
-- Letter, Uppercase (Lu)
-- Letter, Lowercase (Ll)
-- Letter, Titlecase (Lt)
-- Letter, Modifier (Lm)
-- Letter, Other (Lo)
-- Number, Letter (Nl)
function Is_UTF_32_Digit (U : UTF_32) return Boolean;
function Is_UTF_32_Digit (C : Category) return Boolean;
pragma Inline (Is_UTF_32_Digit);
-- Returns true iff U is a digit that can be used to extend an identifer,
-- or if C is one of the corresponding categories, which are the following:
-- Number, Decimal_Digit (Nd)
function Is_UTF_32_Line_Terminator (U : UTF_32) return Boolean;
pragma Inline (Is_UTF_32_Line_Terminator);
-- Returns true iff U is an allowed line terminator for source programs,
-- if U is in the category Zp (Separator, Paragaph), or Zs (Separator,
-- Line), or if U is a conventional line terminator (CR, LF, VT, FF).
-- There is no category version for this function, since the set of
-- characters does not correspond to a set of Unicode categories.
function Is_UTF_32_Mark (U : UTF_32) return Boolean;
function Is_UTF_32_Mark (C : Category) return Boolean;
pragma Inline (Is_UTF_32_Mark);
-- Returns true iff U is a mark character which can be used to extend an
-- identifier, or if C is one of the corresponding categories, which are
-- the following:
-- Mark, Non-Spacing (Mn)
-- Mark, Spacing Combining (Mc)
function Is_UTF_32_Other (U : UTF_32) return Boolean;
function Is_UTF_32_Other (C : Category) return Boolean;
pragma Inline (Is_UTF_32_Other);
-- Returns true iff U is an other format character, which means that it
-- can be used to extend an identifier, but is ignored for the purposes of
-- matching of identiers, or if C is one of the corresponding categories,
-- which are the following:
-- Other, Format (Cf)
function Is_UTF_32_Punctuation (U : UTF_32) return Boolean;
function Is_UTF_32_Punctuation (C : Category) return Boolean;
pragma Inline (Is_UTF_32_Punctuation);
-- Returns true iff U is a punctuation character that can be used to
-- separate pices of an identifier, or if C is one of the corresponding
-- categories, which are the following:
-- Punctuation, Connector (Pc)
function Is_UTF_32_Space (U : UTF_32) return Boolean;
function Is_UTF_32_Space (C : Category) return Boolean;
pragma Inline (Is_UTF_32_Space);
-- Returns true iff U is considered a space to be ignored, or if C is one
-- of the corresponding categories, which are the following:
-- Separator, Space (Zs)
function Is_UTF_32_Non_Graphic (U : UTF_32) return Boolean;
function Is_UTF_32_Non_Graphic (C : Category) return Boolean;
pragma Inline (Is_UTF_32_Non_Graphic);
-- Returns true iff U is considered to be a non-graphic character, or if C
-- is one of the corresponding categories, which are the following:
-- Other, Control (Cc)
-- Other, Private Use (Co)
-- Other, Surrogate (Cs)
-- Separator, Line (Zl)
-- Separator, Paragraph (Zp)
-- FFFE or FFFF positions in any plane (Fe)
--
-- Note that the Ada category format effector is subsumed by the above
-- list of Unicode categories.
--
-- Note that Other, Unassiged (Cn) is quite deliberately not included
-- in the list of categories above. This means that should any of these
-- code positions be defined in future with graphic characters they will
-- be allowed without a need to change implementations or the standard.
--
-- Note that Other, Format (Cf) is also quite deliberately not included
-- in the list of categories above. This means that these characters can
-- be included in character and string literals.
-- The following function is used to fold to upper case, as required by
-- the Ada 2005 standard rules for identifier case folding. Two
-- identifiers are equivalent if they are identical after folding all
-- letters to upper case using this routine.
function UTF_32_To_Upper_Case (U : UTF_32) return UTF_32;
pragma Inline (UTF_32_To_Upper_Case);
-- If U represents a lower case letter, returns the corresponding upper
-- case letter, otherwise U is returned unchanged. The folding is locale
-- independent as defined by documents referenced in the note in section
-- 1 of ISO/IEC 10646:2003
end System.UTF_32;
......@@ -6,7 +6,7 @@
-- --
-- S p e c --
-- --
-- Copyright (C) 2001-2006, Free Software Foundation, Inc. --
-- Copyright (C) 2001-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -30,7 +30,7 @@
-- switches that are recognized. In addition, package Debug documents
-- the otherwise undocumented debug switches that are also recognized.
with GNAT.OS_Lib; use GNAT.OS_Lib;
with System.OS_Lib; use System.OS_Lib;
package Switch.M is
......
......@@ -6,7 +6,7 @@
-- --
-- S p e c --
-- --
-- Copyright (C) 1992,1993,1994,1995 Free Software Foundation, Inc. --
-- Copyright (C) 1992-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -36,7 +36,7 @@
-- tools that need to read the tree to the tree reading routines, and is
-- thus bound as part of such tools.
with GNAT.OS_Lib; use GNAT.OS_Lib;
with System.OS_Lib; use System.OS_Lib;
procedure Tree_In (Desc : File_Descriptor);
-- Desc is the file descriptor for the file containing the tree, as written
......
......@@ -6,7 +6,7 @@
-- --
-- S p e c --
-- --
-- Copyright (C) 1992-2005, Free Software Foundation, Inc. --
-- Copyright (C) 1992-2007, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
......@@ -36,9 +36,10 @@
-- create and close routines are elsewhere (in Osint in the compiler, and in
-- the tree read driver for the tree read interface).
with GNAT.OS_Lib; use GNAT.OS_Lib;
with System; use System;
with Types; use Types;
with Types; use Types;
with System; use System;
with System.OS_Lib; use System.OS_Lib;
package Tree_IO is
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment