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;
......@@ -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;
......
......@@ -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 --
-- --
-- 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 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.
......@@ -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