Version 1.3 of ais/ai-00324.txt

Unformatted version of ais/ai-00324.txt version 1.3
Other versions for file ais/ai-00324.txt

!standard A.16 (01)          03-02-01 AI95-00324/01
!class amendment 03-02-01
!status No Action (10-0-0) 04-03-05
!status work item 03-02-01
!status received 03-02-01
!priority Medium
!difficulty Medium
!subject Physical Units Checking
!summary
A new set of packages and generic packages is proposed that provide compile-time checking for calculations involving physical units.
!problem
Ada is one of the very few languages that provides strong type checking for numeric types. Unfortunately, the checking Ada provides for multiplicative operators is often not correct when performing calculations involving physical quantities. Such quantities are generally measured using units such as centimeters, grams, seconds, miles-per-hour, etc. Multplication and division are only meaningful when the units "work out" properly. Exponentiation is of course only meaningful when the corresponding multiplication would have been meaningful.
!proposal
A new set of packages and generic packages is proposed, all in a new hierarchy "Ada.Units.*", which together provide support for compile-time checking of calculations involving physical quantities.
Note: This is a joint proposal from Tucker Taft and Thom Brooke.
-----
The package Ada.Units forms the root of the hierarchy devoted to physical units checking.
package Ada.Units is subtype Exponent_Type is Integer; type Scale_Type is digits 11; -- Implementation defined end Ada.Units;
Exponent_Type is used to define the exponent for a physical unit along each dimension (length, mass, time, charge, etc.).
-----
The generic package Ada.Units.Dimension_Exponents defines the Exponent_Array type, which is used throughout to describe the dimensions associated with a physical unit.
generic type Names_Of_Dimensions is (<>); package Ada.Units.Dimension_Exponents is -- Names_Of_Dimensions should be an enumeration type; -- Each enumeration literal corresponds to one dimension -- in the system of units.
-- NOTE: It is recommended that each enumeration literal -- be a generic dimension name like "length" or "time" so it -- won't collide with the name of a specific unit such as "cm" -- which would be the typical name for an instance of the -- "Unit" generic.
type Exponent_Array is array(Names_Of_Dimensions) of Exponent_Type;
Number_Of_Dimensions : constant Integer := Exponent_Array'Length;
function "+"(Left, Right : Exponent_Array) return Exponent_Array; function "-"(Left, Right : Exponent_Array) return Exponent_Array; function "-"(Right : Exponent_Array) return Exponent_Array; -- Component-wise "+" and "-" end Ada.Units.Dimension_Exponents;
The enumeration type Names_Of_Dimensions provides names for the various dimensions in the system of units being defined. Typically, this type might be defined with the enumeration literals such as "Length", "Mass", "Time", etc.
The operators on the exponent array type are used within Assert pragmas to verify that the units passed into a generic are related appropriately.
-----
The package Ada.Units.Name_Support provides a set of default name construction utilities which are used in the absence of an explicit specification of a name for a "scaled" unit, a "product" unit, or a "quotient" unit. See System_Of_Units below for what it means to be a scaled, product, or quotient unit.
package Ada.Units.Name_Support is -- Package of string utilities useful for generating -- names automatically
function Scale_Prefix(Scale_Factor : Scale_Type) return String; -- Return appropriate prefix given scale factor. -- (e.g. "kilo" for 1000.0) -- If scale factor is not something common, then return -- Scale_Type'Image(Scale_Factor) & '*'
function Short_Scale_Prefix(Scale_Factor : Scale_Type) return String; -- Return appropriate short prefix given scale factor. -- (e.g. "K" for 1000.0) -- If scale factor is not something common, then return "?"
function Prefixed_Name(Unit_Name : String; Relative_Scale : Scale_Type) return String; -- Add a prefix to name to account for scale factor -- E.g., if Relative_Scale = 1000.0, return "kilo" -- or "K" depending on length of Unit_Name ("K" if -- Unit_Name <= 3 chars in length, "kilo" otherwise)
function Pluralize(Singular_Name : String) return String; -- Return plural form given singular form. -- In general returns Singular_Name unchanged -- if it is <= 2 characters, and adds an 's' otherwise. -- TBD: Internationalization
function Product_Name(Unit_A, Unit_B : String) return String; -- Return default name for Product_Unit, given name -- of two units forming the product. -- Currently just returns Unit_A & '-' & Unit_B
function Quotient_Name(Numerator, Denominator : String) return String; -- Return default name for Quotient_Unit, given name -- of numerator and denominator -- Currently just returns Numerator & '/' & Denominator
function Is_Quotient_Name(Name : String) return Boolean; -- Return true if name consists of numerator and denominator -- with separating '/'
function Numerator_Part(Quotient : String) return String; -- Return numerator part of name constructed via -- Quotient_Name
function Denominator_Part(Quotient : String) return String; -- Return denominator part of name constructed via -- Quotient_Name
end Ada.Units.Name_Support;
-----
The generic package Ada.Units.System_Of_Units provides the primary support for physical units checking. It provides nested generics for creating particular units that together form a single "system" of units, such as "CGS" (cm, g, sec) or "MKS" (meter, kg, sec). A typical use would first instantiate System_Of_Units, and then instantiate the nested generic Unit, once for each unit of interest, such as "cm" or "g" or "kph". See the examples for further understanding.
with Ada.Text_IO; -- for text_output with Ada.Units.Name_Support; with Ada.Units.Dimension_Exponents; generic type Names_Of_Dimensions is (<>); type Value_Type is digits <>; package Ada.Units.System_Of_Units is -- Instantiate this package for each system of units
-- Names_Of_Dimensions should be an enumeration type; -- Each enumeration literal corresponds to one dimension -- in the system of units. -- Value_Type is floating-point type that will be parent type -- for all types declared in this package.
package Dimensions is new Ada.Units.Dimension_Exponents(Names_Of_Dimensions);
use Dimensions;
generic Name : in String; Exponents : in Exponent_Array; Scale_Factor : in Scale_Type := 1.0; type Value is digits <>; package Unit_Signature is end Unit_Signature; -- This is a generic "signature" package used -- to allow uniform use of the various types -- declared below. -- Scale_Factor is scaling factor. It is expressed -- in the base units (e.g. grams, meters, whatever). -- Every value is implicitly multiplied by this scale -- to give its value in the base unit. -- So for milliseconds the scale would be 0.001 presuming -- the base unit is seconds.
package Unitless is -- These types are unitless (aka dimensionless) type Value is new Value_Type'Base; -- Multiplicative operators are OK on Unitless types
-- Define other parameters used in signature package Name : constant String := "(unitless)"; Exponents : constant Exponent_Array := (others => 0); Scale_Factor : constant Scale_Type := 1.0;
package Signature is new Unit_Signature( Name, Exponents, Scale_Factor, Value);
package Sig renames Signature; -- for convenience
end Unitless;
-- Define a type to be used as a base for further derivations -- and provide the operators that combine with the unitless type type Base_For_Derivation is new Value_Type'Base; function "*"(Left : Base_For_Derivation; Right : Unitless.Value) return Base_For_Derivation; function "*"(Left : Unitless.Value; Right : Base_For_Derivation) return Base_For_Derivation; function "/"(Left : Base_For_Derivation; Right : Unitless.Value) return Base_For_Derivation; function "/"(Left : Base_For_Derivation; Right : Base_For_Derivation) return Unitless.Value;
-- And make the predefined multiplicative operators abstract function "*"(Left, Right : Base_For_Derivation) return Base_For_Derivation is abstract; function "/"(Left, Right : Base_For_Derivation) return Base_For_Derivation is abstract; function "**"(Left : Base_For_Derivation; Right : Integer) return Base_For_Derivation is abstract;
pragma Inline("*", "/");
generic Name : in String; Exponents : in Exponent_Array; package Unit is -- Instantiate this generic once for each distinct base unit -- Name is default name to use for unit on output (singular) -- Exponents is array of powers of each dimension
-- This package is for units that have some non-zero dimension -- See Dimensionless_Unit below for case -- where exponents are all zero pragma Assert(Exponents /= Unitless.Exponents);
type Value is new Base_For_Derivation; -- Inherit ops with unitless type
-- Scale_Factor of base unit is always 1.0 Scale_Factor : constant Scale_Type := 1.0;
package Signature is new Unit_Signature( Name, Exponents, Scale_Factor, Value); -- Provide signature package for use with other generics
package Sig renames Signature; -- for convenience
end Unit;
generic with package Unit_A is new Unit_Signature(<>); with package Unit_B is new Unit_Signature(<>); package Scaling is -- Instantiate this to get scaling functions -- between units representing same physical dimensions -- but with different scale factors
-- Note that this is instantiated as part of -- defining a scaled unit below, providing -- scaling functions between the base unit -- and the scaled unit. Instantiate this directly -- to get additional scaling functions between two scaled units -- (with the same base unit).
pragma Assert(Unit_A.Exponents = Unit_B.Exponents); function Scale(From : Unit_A.Value) return Unit_B.Value; function Scale(From : Unit_B.Value) return Unit_A.Value;
pragma Inline(Scale); end Scaling;
generic with package Base_Unit is new Unit_Signature(<>); Relative_Scale : in Scale_Type; Name : in String := Name_Support.Prefixed_Name(Base_Unit.Name, Relative_Scale); package Scaled_Unit is -- Instantiate this package to create a unit -- with the same dimensions as the base unit, -- but a different scale factor -- Relative_Scale is scale factor relative to base unit -- "Absolute" scale factor is -- Relative_Scale * Base_Unit.Scale_Factor
type Value is new Base_For_Derivation; -- Inherit ops with Unitless type -- (no need to override ops because no scaling required -- when combining with unitless type)
-- Define other parameters to signature Scale_Factor : constant Scale_Type := Relative_Scale * Base_Unit.Scale_Factor;
Exponents : Exponent_Array renames Base_Unit.Exponents;
package Signature is new Unit_Signature( Name, Exponents, Scale_Factor, Value); -- Provide signature for use with other generics
package Sig renames Signature; -- for convenience
package Scaling is new Ada.Units.System_Of_Units.Scaling( Base_Unit, Scaled_Unit.Signature); -- Get scaling functions between base unit and scaled unit
-- And rename them for direct visibility function Scale(From : Base_Unit.Value) return Scaled_Unit.Value renames Scaling.Scale; function Scale(From : Scaled_Unit.Value) return Base_Unit.Value renames Scaling.Scale; -- also note that unary "+" can be used for this scaling -- (see below)
-- Define the appropriate additive operators -- NOTE: Except for unary "+", these all return Base_Unit.Value to -- avoid ambiguity in complicated expressions. function "+"(Left : Base_Unit.Value; Right : Scaled_Unit.Value) return Base_Unit.Value; function "+"(Left : Scaled_Unit.Value; Right : Base_Unit.Value) return Base_Unit.Value; function "+"(Right : Scaled_Unit.Value) return Base_Unit.Value renames Scaling.Scale; -- Unary "+" can be used for scaling.
function "+"(Right : Base_Unit.Value) return Scaled_Unit.Value renames Scaling.Scale; -- Unary "+" can be used for scaling.
function "-"(Left : Base_Unit.Value; Right : Scaled_Unit.Value) return Base_Unit.Value; function "-"(Left : Scaled_Unit.Value; Right : Base_Unit.Value) return Base_Unit.Value; function "-"(Right : Scaled_Unit.Value) return Base_Unit.Value;
pragma Inline("+", "-");
end Scaled_Unit;
generic with package Unit_A is new Unit_Signature(<>); with package Unit_B is new Unit_Signature(<>); with package Unit_C is new Unit_Signature(<>); package Multiplicative_Operators is -- Instantiate this package with three units -- where A * B = C is well defined to get -- the appropriate multiplicative operators. -- Scaling is performed automatically. -- NOTE: This is instantiated below in Product_Unit -- and Quotient_Unit. Those are the preferred way -- for getting these cross-unit operators.
pragma Assert( Unit_A.Exponents + Unit_B.Exponents = Unit_C.Exponents);
function "*"(Left : Unit_A.Value; Right : Unit_B.Value) return Unit_C.Value; function "*"(Left : Unit_B.Value; Right : Unit_A.Value) return Unit_C.Value; function "/"(Left : Unit_C.Value; Right : Unit_A.Value) return Unit_B.Value; function "/"(Left : Unit_C.Value; Right : Unit_B.Value) return Unit_A.Value;
pragma Inline("*", "/"); end Multiplicative_Operators;
generic with package Unit_A is new Unit_Signature(<>); with package Unit_B is new Unit_Signature(<>); Name : in String := Name_Support.Product_Name(Unit_A.Name, Unit_B.Name); package Product_Unit is -- Instantiate this package for a unit that is -- the product of two other units. -- The Exponents of the new type is the sum of those for -- Unit_A and Unit_B. -- The Scale_Factor for the new type is the product of the scales -- of Unit_A and Unit_B. -- Use Scaled_Unit to get other scalings. -- The default Name is <unit_a>-<unit_b> (e.g. "foot-lb")
type Value is new Base_For_Derivation; -- Get ops with unitless type, etc.
-- provide other parameters of signature Scale_Factor : constant Scale_Type := Unit_A.Scale_Factor * Unit_B.Scale_Factor;
Exponents : constant Exponent_Array := Unit_A.Exponents + Unit_B.Exponents;
package Signature is new Unit_Signature( Name, Exponents, Scale_Factor, Value);
package Sig renames Signature; -- for convenience
-- Get appropriate multiplicative operators package Ops is new Multiplicative_Operators( Unit_A, Unit_B, Product_Unit.Signature);
-- Rename operators for direct visibility function "*"(Left : Unit_A.Value; Right : Unit_B.Value) return Product_Unit.Value renames Ops."*"; function "*"(Left : Unit_B.Value; Right : Unit_A.Value) return Product_Unit.Value renames Ops."*"; function "/"(Left : Product_Unit.Value; Right : Unit_A.Value) return Unit_B.Value renames Ops."/"; function "/"(Left : Product_Unit.Value; Right : Unit_B.Value) return Unit_A.Value renames Ops."/";
end Product_Unit;
generic with package Unit_A is new Unit_Signature(<>); with package Unit_B is new Unit_Signature(<>); Name : in String := Name_Support.Quotient_Name(Unit_A.Name, Unit_B.Name); package Quotient_Unit is -- Instantiate this package for a unit that is -- the quotient of two other units. -- The Exponents of the new type is the difference of those for -- Unit_A and Unit_B. -- The Scale_Factor for the new type is the ratio of the scales -- of Unit_A and Unit_B. -- Use Scaled_Unit to get other scalings. -- The default Name is <unit_a>/<unit_b> (e.g. "cm/sec")
type Value is new Base_For_Derivation; -- Get ops with unitless type, etc.
-- provide other parameters of signature Scale_Factor : constant Scale_Type := Unit_A.Scale_Factor / Unit_B.Scale_Factor;
Exponents : constant Exponent_Array := Unit_A.Exponents - Unit_B.Exponents;
package Signature is new Unit_Signature( Name, Exponents, Scale_Factor, Value);
package Sig renames Signature; -- for convenience
-- Get appropriate multiplicative operators package Ops is new Multiplicative_Operators( Quotient_Unit.Signature, Unit_B, Unit_A);
-- Rename operators for direct visibility function "*"(Left : Quotient_Unit.Value; Right : Unit_B.Value) return Unit_A.Value renames Ops."*"; function "*"(Left : Unit_B.Value; Right : Quotient_Unit.Value) return Unit_A.Value renames Ops."*"; function "/"(Left : Unit_A.Value; Right : Quotient_Unit.Value) return Unit_B.Value renames Ops."/"; function "/"(Left : Unit_A.Value; Right : Unit_B.Value) return Quotient_Unit.Value renames Ops."/";
end Quotient_Unit;
generic Name : in String; package Dimensionless_Unit is -- Instantiate this generic once for each -- distinct dimensionless base unit (e.g. radians), -- where multiplication and division of the unit -- with itself are well defined (and hence exponentiation makes -- sense). -- Name is default name to use for unit on output (singular).
type Value is new Value_Type'Base; -- All operators inherited, including multiply, divide, and -- exponentiation.
-- Exponents all zero Exponents : Exponent_Array renames Unitless.Exponents;
-- Scale_Factor of base unit is always 1.0 Scale_Factor : constant Scale_Type := 1.0;
package Signature is new Unit_Signature( Name, Exponents, Scale_Factor, Value); -- Provide signature package for use with other generics
package Sig renames Signature; -- for convenience
-- NOTE: We do not provide the operators that combine -- with the unitless type as they create too much ambiguity
end Dimensionless_Unit;
-- Ideally this would be a generic child to avoid -- the main generic from having a dependence on Text_IO. -- Unfortunately, GNAT 3.14p can't deal with this as a child unit -- so at least until that problem is remedied, Text_Output -- is included as a nested generic rather than as a child.
-- with Ada.Units.Name_Support; -- with Ada.Text_IO; generic with package Unit_For_Output is new Unit_Signature(<>); Singular : in String := Unit_For_Output.Name; Plural : in String := Name_Support.Pluralize(Singular); -- Name for unit, plural form Fore : Ada.Text_IO.Field := 2; Aft : Ada.Text_IO.Field := 3; -- 3 digits after decimal pt Exp : Ada.Text_IO.Field := 0; -- No exponent by default package Text_Output is -- Ada.Units.System_Of_Units.Text_Output is -- Instantiate this for text output (and Image) with units included -- Singular is label when Val = 1.0 -- Plural is label in other cases -- Fore is minimum digits before decimal point -- Aft is digits after decimal point -- Exp is number of digits allowed for exponent -- (as used in Float_IO.Put)
use Unit_For_Output;
procedure Put(Val : in Value); procedure Put(File : in Ada.Text_IO.File_Type; Val : in Value); function Image(Val : in Value) return String;
end Text_Output; -- end Ada.Units.System_Of_Units.Text_Output;
end Ada.Units.System_Of_Units;
This generic package is instantiated with a "base" floating point type to be used for all unit calculations, and the names for the various dimensions of interest to the system of units.
Throughout System_Of_Units, a unit is represented using an instantiation of the generic "signature" package Unit_Signature. A generic signature package is one that is instantiated simply so it can be used as an actual parameter for a formal package parameter.
Particular units within the system of units are defined using the nested generic packages Unit, Scaled_Unit, Product_Unit, Quotient_Unit, and Dimensionless_Unit. These generic packages automatically provide appropriate multiplicative and additive operators between the units, which do scaling as necessary, and ensure that only meaningfuul combinations of units are performed. They also provide an instantiation of the Unit_Signature generic signature package so that the newly defined unit may be used with other generics within System_Of_Units. This signature is available with the name "Signature," and with the abbreviation "Sig."
Additional operations may be created by instantiating the nested generic packages Scaling and Multiplicative_Operators, though this will generally not be necessary for most uses, as the automatically provided operators will usually be sufficient.
Finally, there is a nested generic package Text_Output which provides an Image function and text output that includes the name of the unit as part of the output. Note that this package might better be a generic child unit, but not all compilers seem to be able to handle that yet, when combined with the use of generic signatures.
!wording
(See proposal.)
!example
Here is a simple example of use of the System_Of_Units generic, and its nested generics.
with Ada.Text_IO; with Ada.Units.system_of_units; -- with Ada.Units.System_Of_Units.Text_Output; use Ada.Units; procedure test_units is type dim_names is (length, mass, time);
package cgs is new system_of_units(dim_names, Standard.Float); use type cgs.unitless.value;
package cm is new cgs.unit("cm", (length => 1, others => 0)); package cm_output is new cgs.text_output(cm.signature);
package g is new cgs.unit("g", (mass => 1, others => 0)); package g_output is new cgs.text_output(g.sig);
package sec is new cgs.unit("sec", (time => 1, others => 0)); package sec_output is new cgs.text_output(sec.signature);
package cps is new cgs.quotient_unit(cm.sig, sec.sig); package cps_output is new cgs.text_output(cps.signature);
package meter is new cgs.scaled_unit( cm.sig, relative_scale => 100.0, name => "meter"); package meter_output is new cgs.text_output(meter.sig);
package kg is new cgs.scaled_unit( base_unit => g.sig, relative_scale => 1000.0); package kg_output is new cgs.text_output(kg.sig);
package usec is new cgs.scaled_unit( base_unit => sec.sig, relative_scale => 1.0E-6); package usec_output is new cgs.text_output(usec.sig);
package msec is new cgs.scaled_unit(base_unit => sec.sig, relative_scale => 1.0E-3);
X : meter.value := 27.0;
Y : cm.value := 540.0;
Speed : cps.value; -- cm/sec Interval : sec.value := 33.0; -- seconds
use type cm.value, meter.value; use type cps.value; begin meter_output.put(X); ada.text_io.put(" + "); cm_output.put(Y); ada.text_io.put(" = "); cm_output.put(X + Y); ada.text_io.new_line; speed := (X + Y)/Interval; ada.text_io.put_line("If traveled in " & sec_output.image(Interval) & " then speed = " & cps_output.image(speed));
ada.text_io.put_line("Three kilograms = " & kg_output.image(3.0)); ada.text_io.put_line("Two and a half microsecs = " & usec_output.image(2.5)); end test_units;
Here is the output produced by compiling and running this test:
27.000 meters + 540.000 cm = 3240.000 cm If traveled in 33.000 secs then speed = 98.182 cm/sec Three kilograms = 3.000 Kg Two and a half microsecs = 2.500 usecs
Points to note about the output: - Text_Output by default has 3 digits after decimal point and no
exponent. This can be overridden when instantiating it.
- Text_Output by default uses the name of the unit provided
when the unit was first created.
- For scaled, product, and quotient units, the name of the unit is by
default constructed from the name(s) of the base unit(s), using the Name_Support routines. Examples of these automatically constructed names are "Kg", "usec" and "cm/sec".
!discussion
As mentioned in the "problem" statement, Ada's strong numeric type checking does not work very well for multiplicative operators in some cases, as it always allows unit-A * unit-A => unit-A, while disallowing unit-A * unit-B => unit-C even when meaningful. However, the ability to make certain operators "abstract," combined with the ability to define new numeric types and new cross-type definitions for the multiplicative operators can provide a solution.
Unfortunately, manually building up a set of types with appropriate cross-type multiplicative operators is error prone and tedious. Various approaches have been tried in the past, but using generic "signature" packages and appropriate pragma Assert's has not been tried in combination before, as far as we know.
In any case, whether this approach is novel or not, it becomes significantly more valuable if there is one, standard way of doing it, with one standard generic signature package, etc. This will allow more functionality (such as periodicity, more sophisticated input and output routines, etc.) to be layered on top in the future, and built into other shared abstractions.
Other approaches that were considered involved special pragmas combined with using Ada subtypes rather than derived types, special attributes, zero-space-overhead discriminants, etc. Essentially all of these approaches involved significant compiler development work, and it is unclear whether the added capability could justify the inevitably high cost of this development.
By contrast, this approach uses features already supported by Ada 95 compilers (albeit perhaps in ways that may stretch the capability of some compilers ;-), and seems to provide almost all the capability that additional language features, pragmas, or attributes could provide.
There are a few limitations of the current proposal that we know how to fix, but are not sure whether that is wise at this point. First of all, numeric literals and explicit type conversion are available for the types associated with units. This to some degree reduces the safety guarantees provided. If the types were made into private types, we could make stronger guarantees. However, you would then not be able to use the types in existing generics that require floating point types. That also might be considered a good thing or a bad thing. For instance it is not clear it makes sense to instantiate Generic_Elementary_Functions with a type representing centimeters.
It would be possible to use private types. There are some technical difficulties when combining private types and generic signature instantiations (which might become the subject of another AI), but it is possible to work around these problems. [Basically, you need to define the private type completely in a subpackage, and then derive from it in the package where the instantiation of the signature takes place.]
Another limitation is that the units are only for floating point types. This could also be solved, by having a more elaborate set of formal parameters to System_Of_Units, perhaps a private type and a bunch of operators, or an instanace of a signature for a numeric-ish type. Probably the most interesting non-floating-point type would be type Complex, though conceivably users of fixed-point types or even integer types might find this to be a useful approach to units checking. Of course, since it is just a "normal" generic package with no magic, it can be used a model for complex, integer, or fixed-point versions.
Another important issue is whether "pre-instantiations" should be supplied for common systems of units (e.g. "CGS"). This might lower the entry barrier to use, and would provide "standard" examples as models as well.
Here is an example of such a pre-instantiation, and it should probably be considered as an explicit option in this proposal:
with Ada.Units.System_Of_Units; pragma Elaborate_All(Ada.Units.System_Of_Units); package Ada.Units.CGS_Units is
type Dimensions is (Length, Mass, Time);
package CGS is new System_Of_Units( Names_Of_Dimensions => Dimensions, Value_Type => Standard.Float);
package cm is new CGS.Unit( Name => "cm", Exponents => (Length => 1, others => 0));
package g is new CGS.Unit( Name => "g", Exponents => (Mass => 1, others => 0));
package sec is new CGS.Unit( Name => "sec", Exponents => (Time => 1, others => 0));
end Ada.Units.CGS_Units;
!appendix

Here is a prototypical implementation of the proposed packages:

--------------------

package body Ada.Units.Dimension_Exponents is
     function "+"(Left, Right : Exponent_Array) return Exponent_Array is
         -- Component-wise "+"
         Result : Exponent_Array;
     begin
         for I in Result'Range loop
             Result(I) := Left(I) + Right(I);
         end loop;
         return Result;
     end "+";

     function "-"(Left, Right : Exponent_Array) return Exponent_Array is
         -- Component-wise "-"
         Result : Exponent_Array;
     begin
         for I in Result'Range loop
             Result(I) := Left(I) - Right(I);
         end loop;
         return Result;
     end "-";

     function "-"(Right : Exponent_Array) return Exponent_Array is
         -- Component-wise unary "-"
         Result : Exponent_Array;
     begin
         for I in Result'Range loop
             Result(I) := - Right(I);
         end loop;
         return Result;
     end "-";
end Ada.Units.Dimension_Exponents;

package body Ada.Units.Name_Support is
     -- Package of string utilities useful for generating
     -- names automatically

     function Scale_Prefix(Scale_Factor : Scale_Type) return String is
       -- Return appropriate prefix given scale factor.
       -- (e.g. "kilo" for 1000.0)
       -- If scale factor is not something common, then return
       -- Scale_Type'Image(Scale_Factor) & '*'
     begin
         if Scale_Factor = 1.0 then
             return "";
         elsif Scale_Factor = 10.0 then
             return "deca";
         elsif Scale_Factor = 100.0 then
             return "heca";
         elsif Scale_Factor = 1000.0 then
             return "kilo";
         elsif Scale_Factor = 1.0E6 then
             return "mega";
         elsif Scale_Factor = 1.0E9 then
             return "giga";
         elsif Scale_Factor = 1.0E12 then
             return "tera";
         elsif Scale_Factor = 1.0E15 then
             return "peta";
         elsif Scale_Factor = 0.1 then
             return "deci";
         elsif Scale_Factor = 0.01 then
             return "centi";
         elsif Scale_Factor = 0.001 then
             return "milli";
         elsif Scale_Factor = 1.0E-6 then
             return "micro";
         elsif Scale_Factor = 1.0E-9 then
             return "nano";
         elsif Scale_Factor = 1.0E-12 then
             return "pico";
         else
             return Scale_Type'Image(Scale_Factor) & '*';
         end if;
     end Scale_Prefix;

     function Short_Scale_Prefix(Scale_Factor : Scale_Type) return String is
       -- Return appropriate short prefix given scale factor.
       -- (e.g. "K" for 1000.0)
       -- If scale factor is not something common, then return
       -- Scale_Type'Image(Scale_Factor) & '*'
     begin
         if Scale_Factor = 1.0 then
             return "";
         elsif Scale_Factor = 10.0 then
             return "D";
         elsif Scale_Factor = 100.0 then
             return "H";
         elsif Scale_Factor = 1000.0 then
             return "K";
         elsif Scale_Factor = 1.0E6 then
             return "M";
         elsif Scale_Factor = 1.0E9 then
             return "G";
         elsif Scale_Factor = 1.0E12 then
             return "T";
         elsif Scale_Factor = 1.0E15 then
             return "P";
         elsif Scale_Factor = 0.1 then
             return "d";
         elsif Scale_Factor = 0.01 then
             return "c";
         elsif Scale_Factor = 0.001 then
             return "m";
         elsif Scale_Factor = 1.0E-6 then
             return "u";
         elsif Scale_Factor = 1.0E-9 then
             return "n";
         elsif Scale_Factor = 1.0E-12 then
             return "p";
         else
             return "?";
         end if;
     end Short_Scale_Prefix;

     function Prefixed_Name(Unit_Name : String; Relative_Scale : Scale_Type)
       return String is
       -- Add a prefix to name to account for scale factor
       -- E.g., if Relative_Scale = 1000.0, return "kilo"
       -- or "K" depending on length of Unit_Name ("K" if
       -- Unit_Name <= 3 chars in length, "kilo" otherwise)
     begin
         if Unit_Name'Length <= 3 then
             return Short_Scale_Prefix(Relative_Scale) & Unit_Name;
         else
             return Scale_Prefix(Relative_Scale) & Unit_Name;
         end if;
     end Prefixed_Name;


     function Product_Name(Unit_A, Unit_B : String)
       return String is
         -- Return default name for Product_Unit, given name
         -- of two units forming the product.
         -- Currently just returns Unit_A & '-' & Unit_B
     begin
         return Unit_A & '-' & Unit_B;
     end Product_Name;

     function Quotient_Name(Numerator, Denominator : String)
       return String is
         -- Return default name for Quotient_Unit, given name
         -- of numerator and denominator
         -- Currently just returns Numerator & '/' & Denominator
     begin
         return Numerator & '/' & Denominator;
     end Quotient_Name;

     function Is_Quotient_Name(Name : String) return Boolean is
       -- Return true if name consists of numerator and denominator
       -- with separating '/'
     begin
         for I in Name'Range loop
             if Name(I) = '/' then
                 return True;
             end if;
         end loop;
         return False;
     end Is_Quotient_Name;

     function Numerator_Part(Quotient : String) return String is
       -- Return numerator part of name constructed via
       -- Quotient_Name
     begin
         for I in Quotient'Range loop
             if Quotient(I) = '/' then
                 return Quotient(Quotient'First .. I-1);
             end if;
         end loop;
         return Quotient;  -- Should never happen
     end Numerator_Part;

     function Denominator_Part(Quotient : String) return String is
       -- Return denominator part of name constructed via
       -- Quotient_Name
     begin
         for I in Quotient'Range loop
             if Quotient(I) = '/' then
                 return Quotient(I+1 .. Quotient'Last);
             end if;
         end loop;
         return "??";  -- Should never happen
     end Denominator_Part;

     function Pluralize(Singular_Name : String) return String is
       -- Return plural form given singular form.
       -- In general returns Singular_Name unchanged
       -- if it is <= 2 characters, and adds an 's' otherwise.
       -- TBD: Internationalization
     begin
         if Singular_Name'Length <= 2 or else
           Singular_Name(Singular_Name'Last) = 's' then
             -- Short names generally don't add an 's'
             -- (e.g. "g").
             return Singular_Name;
         elsif Is_Quotient_Name(Singular_Name) then
             -- If is a quotient name, then pluralize the numerator
             -- part only
             return Quotient_Name(
               Pluralize(Numerator_Part(Singular_Name)),
               Denominator_Part(Singular_Name));
         else
             -- TBD: Internationalization
             return Singular_Name & 's';
         end if;
     end Pluralize;

end Ada.Units.Name_Support;

with Ada.Long_Float_Text_IO; -- implementation-dependent choice
with Ada.Text_IO;
package body Ada.Units.System_Of_Units is

     use type Unitless.Value;

       -- Provide the operators that combine with the unitless type
       -- Be careful not to recurse infinitely
       -- No scaling is necessary
     function "*"(Left : Base_For_Derivation; Right : Unitless.Value)
       return Base_For_Derivation is
     begin
         return Base_For_Derivation(Unitless.Value(Left) * Right);
     end "*";

     function "*"(Left : Unitless.Value; Right : Base_For_Derivation)
       return Base_For_Derivation is
     begin
         return Base_For_Derivation(Left * Unitless.Value(Right));
     end "*";

     function "/"(Left : Base_For_Derivation; Right : Unitless.Value)
       return Base_For_Derivation is
     begin
         return Base_For_Derivation(Unitless.Value(Left) / Right);
     end "/";

     function "/"(Left : Base_For_Derivation; Right : Base_For_Derivation)
       return Unitless.Value is
     begin
         return Unitless.Value(Left) / Unitless.Value(Right);
     end "/";

     package body Scaling is
         -- Instantiate this to get scaling functions
         -- between units representing same physical dimensions
         -- but with different scale factors

         function Scale(From : Unit_A.Value) return Unit_B.Value is
         begin
             return Unit_B.Value(Unit_A.Scale_Factor / Unit_B.Scale_Factor *
               Scale_Type(From));
         end Scale;

         function Scale(From : Unit_B.Value) return Unit_A.Value is
         begin
             return Unit_A.Value(Unit_B.Scale_Factor / Unit_A.Scale_Factor *
               Scale_Type(From));
         end Scale;

     end Scaling;

     package body Scaled_Unit is
         -- Define the appropriate additive operators
         -- NOTE: These all return Base_Unit.Value to avoid
         -- ambiguity in complicated expressions.

         use type Base_Unit.Value;

         function "+"(Left : Base_Unit.Value; Right : Scaled_Unit.Value)
           return Base_Unit.Value is
         begin
             return Left + Scale(Right);
         end "+";

         function "+"(Left : Scaled_Unit.Value; Right : Base_Unit.Value)
           return Base_Unit.Value is
         begin
             return Scale(Left) + Right;
         end "+";

         function "-"(Left : Base_Unit.Value; Right : Scaled_Unit.Value)
           return Base_Unit.Value is
         begin
             return Left - Scale(Right);
         end "-";
         function "-"(Left : Scaled_Unit.Value; Right : Base_Unit.Value)
           return Base_Unit.Value is
         begin
             return Scale(Left) - Right;
         end "-";
         function "-"(Right : Scaled_Unit.Value)
           return Base_Unit.Value is
         begin
             return - Scale(Right);
         end "-";

     end Scaled_Unit;

     package body Multiplicative_Operators is
         -- Scaling is performed automatically.

         Combined_Scale_Factor : constant Scale_Type :=
           Unit_A.Scale_Factor * Unit_B.Scale_Factor / Unit_C.Scale_Factor;
         Inverse_Combined_Scale_Factor : constant Scale_Type :=
           Unit_C.Scale_Factor / (Unit_A.Scale_Factor * Unit_B.Scale_Factor);

         function "*"(Left : Unit_A.Value; Right : Unit_B.Value)
           return Unit_C.Value is
         begin
             return Unit_C.Value(Combined_Scale_Factor *
               Scale_Type(Left) * Scale_Type(Right));
         end "*";
         function "*"(Left : Unit_B.Value; Right : Unit_A.Value)
           return Unit_C.Value is
         begin
             return Unit_C.Value(Combined_Scale_Factor *
               Scale_Type(Left) * Scale_Type(Right));
         end "*";
         function "/"(Left : Unit_C.Value; Right : Unit_A.Value)
           return Unit_B.Value is
         begin
             return Unit_B.Value(Inverse_Combined_Scale_Factor *
               Scale_Type(Left) / Scale_Type(Right));
         end "/";
         function "/"(Left : Unit_C.Value; Right : Unit_B.Value)
           return Unit_A.Value is
         begin
             return Unit_A.Value(Inverse_Combined_Scale_Factor *
               Scale_Type(Left) / Scale_Type(Right));
         end "/";

     end Multiplicative_Operators;

     -- with Ada.Long_Float_Text_IO; -- implementation-dependent choice
     -- GNAT can't deal with this as a generic child
     package body Text_Output is

         subtype IO_Type is Long_Float;  -- implementation-dependent choice
         package Float_IO renames Ada.Long_Float_Text_IO;
                    -- implementation-dependent choice

         function Name(Is_One : Boolean) return String is
           -- Return Singular or Plural, depending on
           -- whether Val = 1.0 (i.e. Is_One true)
         begin
             if Is_One then
                 return Singular;
             else
                 return Plural;
             end if;
         end Name;

         procedure Put(Val : in Value) is
         begin
             Float_IO.Put(IO_Type(Val),
               Fore => Fore, Aft => Aft, Exp => Exp);
             Ada.Text_IO.Put(' ' & Name(Is_One => Val = 1.0));
         end Put;

         procedure Put(File : in Ada.Text_IO.File_Type;
           Val : in Value) is
         begin
             Float_IO.Put(File, IO_Type(Val),
               Fore => Fore, Aft => Aft, Exp => Exp);
             Ada.Text_IO.Put(File, ' ' & Name(Is_One => Val = 1.0));
         end Put;

         function Image(Val : in Value) return String is
             Extra_Digits_Before_Decimal : constant := 30;
               -- This is extra room allowed in the Result string
               -- declared below.
               -- TBD: The value "30" allows for the case when EXP
               -- is zero. The value 30 is pretty arbitrary but
               -- should be more than sufficient.

             Result : String(1 .. Fore + Aft + Exp + 2 +
               Extra_Digits_Before_Decimal);
         begin
             Float_IO.Put(Result, IO_Type(Val),
               Aft => Aft, Exp => Exp);
             for I in Result'Range loop
                 if Result(I) /= ' ' then
                     return Result(I..Result'Last) & ' ' &
                       Name(Is_One => Val = 1.0);
                 end if;
             end loop;
             return "??";  -- Should never happen
         end Image;

     end Text_Output;

end Ada.Units.System_Of_Units;

!ACATS test

ACATS tests are needed to test this package throughly.

!appendix

From: Pascal Leroy
Sent: Monday, February 3, 2003  9:14 AM

I like it.

Random comments:

I wonder why you pass Names_Of_Dimensions and not an instantiation of
Dimension_Exponents to System_Of_Units.  If you work with several system of
units, it would seem that factoring the exponents could be useful.  (I am told
that there are countries were SI is not the only system of units in practical
use.)

I think this should not be restricted to floating-point types.  Fixed-point
types and complex come to mind.

References to GNAT bugs have nothing to do in an AI, unless we want to enshrine
them in the RM ;-)

The style of Text_Output, where you pass Fore/Aft/Exp at instantiation time, is
different from that of, say, Complex_IO.  I don't think that's a good idea.

A preinstantiation should be provided for the SI system.  Btw, some of the
examples will need to be sanitized to be in line with the SI conventions (s
instead of sec, K is for Kelvin, k is for kilo, etc.).  Incidentally, there is
in Standard.Character a Greek mu (position 181) precisely to be able to write SI
prefixes.

Would there be a way to provide conversion of units?  For instance you would say
that an inch is 2.54 cm and it would know how to convert square inches to square
centimeters.  That would be cool, but I don't know if it's possible.

****************************************************************

From: Tucker Taft
Sent: Monday, February 3, 2003  1:26 PM

Pascal Leroy wrote:
>
> > !subject Physical Units Checking
>
> I like it.
>
> Random comments:
>
> I wonder why you pass Names_Of_Dimensions and not an instantiation of
> Dimension_Exponents to System_Of_Units.  If you work with several system of
> units, it would seem that factoring the exponents could be useful.  (I am told
> that there are countries were SI is not the only system of units in practical
> use.)

The Dimension_Exponents package was really just to simplify the
visible part of System_Of_Units, so it didn't include the
operators for Exponent_Arrays.  I played around with using
a formal package parameter instead of the enumeration type for
the names of dimensions, but it seemed to add complexity for the
user without any obvious additional functionality.  You can
still factor out the exponents by having multiple instantiations
of System_Of_Units all use the same Names_Of_Dimensions type.
If some other abstraction really wanted a formal package instead
of the formal type, the instantiator has an instance of Dimension_Exponents
called "Dimensions" available in any instantiation of System_Of_Units.

> I think this should not be restricted to floating-point types.  Fixed-point
> types and complex come to mind.

I discussed this in the AI.  I fear it may make the interface a bit
daunting.  Perhaps if we provide pre-instantiations, that becomes
less of an issue.

>
> References to GNAT bugs have nothing to do in an AI, unless we want to enshrine
> them in the RM ;-)

I agree with that, but we presumably don't want to propose something
that can't be compiled by popular compilers, so I wanted to explain why I made Text_Output
a nested package.  That could presumably be relegated to the discussion
section only, or the ACT folks could sign up to fix the problem
real-soon-now.

>
> The style of Text_Output, where you pass Fore/Aft/Exp at instantiation time, is
> different from that of, say, Complex_IO.  I don't think that's a good idea.

I suppose consistency make sense.  But having the Default_Fore, etc. as
global variables just seems gratuitously non thread-safe.  Perhaps the
generic parameters could be the Defaults, and then each Put function
(and Image) could take Fore/Aft/Exp as actual parameters.  Or perhaps
I could just accept the gnarly "standard" approach to Default_Fore/Aft/Exp
and get on with it... ;-).  I guess I still think the default ought
to be without an exponent.  The output is so much easier to read without
exponents flying around, and one of the points of units is so you don't
have to keep talking about 3.5E-9 meters, and instead can talk about 3.5 nm.

> A preinstantiation should be provided for the SI system.  Btw, some of the
> examples will need to be sanitized to be in line with the SI conventions (s
> instead of sec, K is for Kelvin, k is for kilo, etc.).  Incidentally, there is
> in Standard.Character a Greek mu (position 181) precisely to be able to write SI
> prefixes.

I will need some help with the SI preinstantiation.  Maybe Thom Brooke
can help do that.  I am definitely not an expert in SI.

> Would there be a way to provide conversion of units?  For instance you would say
> that an inch is 2.54 cm and it would know how to convert square inches to square
> centimeters.  That would be cool, but I don't know if it's possible.

That is already possible.  Any two units that have the same dimensions
can have a scaling function created for them by instantiating the Scaling
generic.  So if you build up square-cm and square-inch using Product_Unit
from cm and inch, and inch is defined in terms of cm using Scaled_Unit (or
vice-versa), then Scaling can be instantiated with square-cm and square-inch
and the Scale functions will do the right thing.   You don't
have to explicitly instantiate Scaling if the units are defined directly
in terms of each other using Scaled_Unit (since it pre-instantiates Scaling),
but if the units are only indirectly related, the Scaling generic may be used
to produce direct Scale converters.  See the attached "test_squares.ada" example.

Here is the output of running the attached example to get this kind of scaling:

  30.000 square-cms converts to 4.650 square-inches

----

with Ada.Text_IO;
with Ada.Units.system_of_units;
with Ada.Units.System_Of_Units.Text_Output;
use Ada.Units;
procedure test_squares is
    type dim_names is (length, mass, time);

    package cgs is new system_of_units(dim_names, Standard.Float);
    use type cgs.unitless.value;

    package cm is new cgs.unit("cm", (length => 1, others => 0));
    package cm_output is new cgs.text_output(cm.signature);

    package square_cm is new cgs.product_unit(cm.sig, cm.sig, name =>
      "square-cm");
    package sqcm_output is new cgs.text_output(square_cm.sig);

    package inch is new cgs.scaled_unit(cm.sig, relative_scale => 2.54,
      name => "inch");

    package square_inch is new cgs.product_unit(inch.sig, inch.sig, name =>
      "square-inch");
    package sqin_output is new cgs.text_output(square_inch.sig,
      plural => "square-inches");

    package square_scaling is new cgs.scaling(
      square_cm.sig, square_inch.sig);

    sqcm : square_cm.value := 30.0;

    sqi : square_inch.value := square_scaling.scale(sqcm);

begin

    Ada.Text_IO.Put_Line(sqcm_output.image(sqcm) & " converts to " &
      sqin_output.image(sqi));

end;

****************************************************************

From: Robert I. Eachus
Sent: Monday, February 3, 2003  1:47 PM

I need to do more reading of the proposal, but there is one comment I
would like to make up front.

There are some computations where you run into non-integer values for
units.  These have no meaning as such in the final results, but are
needed in intermediates.  I never tried to deal with exponentials and
logs, but half-integer powers show up all over the place.  The "trick" I
used to get around this was to use Paul Hilfinger's package with all the
units multiplied by two.  That way the 3/2 power of length had an
exponent of 3.  I recently commented to Ben Brogol on this that using a
multiplier of 6 might be worthwhile, or even 12.  Sixty, which allows
for square, cube, fourth and fifth roots looks very execessive.  But
doing it this way allowed for a meaningful square root function for
values with units.

Of course, it would be nicest if the exponent values could be hiden from
sight.  In other words:

type Meter is private;

but then you lose the visible numeric literals.  Of course that is not
necessarily a bad thing:

X: Centimeters := 1.0 * Cm;

****************************************************************

From: Tucker Taft
Sent: Monday, February 3, 2003  2:21 PM

My initial version of this used floats for the exponents, and that
worked fine (they aren't discriminants, so there is really no
problem supporting floats as exponents).  My co-sponsor didn't
think it was necessary to accommodate non-integral exponents,
so I switched to integers.  But it could easily be switched back.
Of course we would then probably want a version of Sqrt that would
do the "right thing" with respect to units, which is quite
possible.  Also, a Square_Root_Unit generic would be desirable.

Note that exponents are "fiddled with" only at generic instantiation
time, so overhead relating to using floating point exponents would
be irrelevant.

> Of course, it would be nicest if the exponent values could be hiden from
> sight.  In other words:
>
> type Meter is private;

The visibility of the exponents has *nothing* to do with the
privateness of the type in this proposal.  You probably need
to take another look at it...

> but then you lose the visible numeric literals.  Of course that is not
> necessarily a bad thing:
>
> X: Centimeters := 1.0 * Cm;

I discussed the issue of privateness in the AI.  More specific comments on
this topic are welcome.

****************************************************************

From: Robert A. Duff
Sent: Monday, February 3, 2003  2:42 PM

> My initial version of this used floats for the exponents, and that
> worked fine (they aren't discriminants, so there is really no
> problem supporting floats as exponents).

I would think the exponents should be fixed point.  If you want integer
exponents, you use 'Small=1.0.  If you want square roots, you use
'Small=0.5.  Or whatever else you want.

****************************************************************

From: Gary Dismukes
Sent: Monday, February 3, 2003  2:14 PM

As Pascal pointed out:
>
> References to GNAT bugs have nothing to do in an AI, unless we want to enshrine
> them in the RM ;-)

Yes, please make sure that the two references to GNAT in the nested
generic package Text_Output (both in the spec and the later sample
body) are excised in the first version of this AI that's officially
posted to the web site.

-- Gary (on behalf of Ada Core Technologies:)

****************************************************************

From: Tucker Taft
Sent: Monday, February 3, 2003  3:29 PM

Well, at least I got your attention ;-).

****************************************************************

From: Gary Dismukes
Sent: Monday, February 3, 2003  4:10 PM

Probably the best thing to do in a case like this is to send
a problem report to report@gnat.com with a complete test case.
It seems reasonable to assume that in a case of legal Ada like
this that compilers will (and should) get fixed to allow it.

Anyway, at least now we know about it. ;-)

****************************************************************

From: Pascal Leroy
Sent: Tuesday, February 4, 2003  3:08 AM

> > The style of Text_Output, where you pass Fore/Aft/Exp at instantiation
> > time, is different from that of, say, Complex_IO.  I don't think that's
> > a good idea.
>
> I suppose consistency make sense.  But having the Default_Fore, etc. as
> global variables just seems gratuitously non thread-safe.  Perhaps the
> generic parameters could be the Defaults, and then each Put function
> (and Image) could take Fore/Aft/Exp as actual parameters.  Or perhaps
> I could just accept the gnarly "standard" approach to Default_Fore/Aft/Exp
> and get on with it... ;-).  I guess I still think the default ought
> to be without an exponent.  The output is so much easier to read without
> exponents flying around, and one of the points of units is so you don't
> have to keep talking about 3.5E-9 meters, and instead can talk about 3.5 nm.

Fine.  What I am suggesting is to use the style of Text_IO, but use 0 for the
default exponent.  That's exactly what Text_IO.Decimal_IO does, actually (I
suppose that accountants are not too happy with numbers like 1.35E5 USD).

> I will need some help with the SI preinstantiation.  Maybe Thom Brooke
> can help do that.  I am definitely not an expert in SI.

I am not an expert either, but having had some scientific education in a country
where SI is a religious dogma I know the basics.  I think I can help with the
preinstantiation.

> Here is the output of running the attached example to get this kind of
scaling:
>
>   30.000 square-cms converts to 4.650 square-inches

Great.

****************************************************************

From: Christoph Grein
Sent: Tuesday, February 4, 2003  4:00 AM

!subject Physical Units Checking

Jean-Pierre Rosen sent me this new AI to comment because I've prepared a paper
for Ada-Europe 2003 giving a survey of physical units handling techniques in
Ada.

While the proposal includes a lot of clever ideas about using generics with
(generic) signature packages, I must say that on first sight, I'm not very
impressed by the outcome. The proposed method is aimed at compile-time
checking of dimensions, but it suffers like all the members of this family
from the combinatorial explosion of instantiations and overloaded operators.
And despite all these overloadings, it remains silent how equations like

   d = (1/2) g t^2

should be handled when solved for t, because powers and roots are not
included.

This may sound like a very harsh wording, and I will put some flesh around
the bones of my critique presently.

Please do not misunderstand me. I do not want to say that there are no merits
in this proposal. I only think it is not a good idea to standardise it and
say: "Look, this is the way you have to deal in Ada with dimensions."

Let me rephrase Robert Dewar, who, referring to proposals for standard
container libraries, said:

   Put the proposal on the net, make it public, and wait for the
   reaction. If the proposal finds support, you can later think
   about standardisation.

Let me start with nit-picking and then go on to the more severe
deficiencies as I see them.

1. Names

Names of units (especially SI) are case sensitive.
The currently defined prefixes are the following:

  yocto: constant := 1.0E-24;  -- y
  zepto: constant := 1.0E-21;  -- z
  atto : constant := 1.0E-18;  -- a
  femto: constant := 1.0E-15;  -- f
  pico : constant := 1.0E-12;  -- p
  nano : constant := 1.0E-09;  -- n
  micro: constant := 1.0E-06;  -- æ (u)
  milli: constant := 1.0E-03;  -- m
  centi: constant := 1.0E-02;  -- c
  deci : constant := 1.0E-01;  -- d
  deka : constant := 1.0E+01;  -- da
  hecto: constant := 1.0E+02;  -- h
  kilo : constant := 1.0E+03;  -- k
  mega : constant := 1.0E+06;  -- M
  giga : constant := 1.0E+09;  -- G
  tera : constant := 1.0E+12;  -- T
  peta : constant := 1.0E+15;  -- P
  exa  : constant := 1.0E+18;  -- E
  zetta: constant := 1.0E+21;  -- Z
  yotta: constant := 1.0E+24;  -- Y

It further uses the fancy name "heca" for "hecto" and gets some prefix
symbols wrong:

"deca"  is 'da' not 'D'
"hecto" is 'h'  not 'H'
"kilo"  is 'k'  not 'K'

Also the symbol for Second is 's', not "sec". Speed is measured in
"m/s" not "m/sec".

See the National Institute of Standards and Technology
http://physics.nist.gov/cuu/Units/

This of course is nit-picking and can easily be cured.

2. Product Unit Name

Why is the default name of a product unit Unit_a & '-' & Unit_B?
Is this a misprint? Unit_a & '*' & Unit_B seems more appropriate and
is in line with the quotient name Unit_a & '/' & Unit_B.

   J = N-m  vs.  J = N*m

3. Mathematical Functions

These are not included. There is a statement:

   "For instance it is not clear it makes sense to instantiate
   Generic_Elementary_Functions with a type representing
   centimeters."

It is absolutely clear that it does not at all make sense.

exp (5 cm), ln (5 cm), sin (5 cm) all are nonesense.

However sqrt (5 cm) makes perfectly sense as does sin (5 cm, cycle => 10 cm)
and tan (y => 10 cm, x => 5 cm).

So mathematics has to be included up front, not added later.

4. Exponentiation and Roots

This is the most prominent shortcoming. How do you want to deal with the
most simple mechanical equation cited above

   d = (1/2) g t^2

let along with the Stefan Boltzmann equation

   S = Sigma * T^4

[S] = W/m^2, or the Schottky-Langmuir equation

   j = (4/9) eps0 Sqrt (2 e0 / m0) U^(3/2) / d^2

[j] = A/m^2? When you solve these equations for t, T, U, you need roots.
And Schottky-Langmuir shows that you even need fractional powers.

While in SI, final results never have fractional powers, intermediate
results do, and you want to be able to rearrange items in equations as is
most appropriate to the problem at hand and do not want to be forced to
write just the way the method supports.

   U^(3/2) => Sqrt (U * U * U)  -- what a mess

   j^(2/3) => ???

5. Combinatorial Explosion

As the examples above show, this method suffers severly from the
combinatorial explosion of operations needed.

Up to which power do you want to go? At least the fourth power seems
reasonable and for the inverse you then need square roots, cubic roots,
fourth roots.

If you do 3D vector dynamics, calculation of the absolute value of an
acceleration vector needs time in the (negative) fourth power.

Physics with all its powers and roots evades these (I'm apt to say:
naive) attempts.

The example code uses just three dimensions, Length, Time, Mass. In such
a restricted world, the proposal might work (but see below), but I doubt
that you can make it work for all seven SI base units.

6. Unit Systems

As an example, the CGS system is used, however only in a very restricted
form based on just cm, g, s. If you want to include electricity, you
immediately run into severe problems with this proposal.

The most appropriate CSG system is the Gaussian one (outdated as any other
CSG from practical use): It is symmetric in electric and magnetic effects,
i.e. Maxwell's equations are symmetric in vacuum and corresponding electric
and magnetic items have the same dimensions (albeit carrying different
names); there is just one fundamental constant, the speed of light.

The problem is that the basic unit for electric charge has fractional
powers:

   1 esu = 1 cm^(3/2) g^(1/2) s^(-1)

How are you going to handle this?

7. Clumsiness

Basing everything on a set of generics is appealing from a theoretic point
of view, but if I, as a developer, am given this set, it seems very awkward
for me to set up the system with the dimensions I need.

What developers want, is a simple set of ready-to-use packages. Until I see
an example with more than just three dimensions (best would be the full
SI system) where I can write

   U := cuberoot (Whatever);  -- [U] = V

as for Schottky-Langmuir above, without being artificially forced to arrange
items in Whatever in a form the current instance can handle, I'm not
convinced that this proposal is ripe for standardisation.

8. Abstract Operators

An annoying feature is that illegal operators like time * time -> time are
present and made abstract, rather than being absent.

Abstractness does not prevent operators to be taken into account upon
overload resolution. So they may raise their ugly heads every now and then
to the dismay of the poor user of the proposal (see below).

9. Over-Ambitiousness

While being severely flawed in some aspects, the proposal is over-ambitious
in wanting to provide natural language names for the units.

   27.000 meters + 540.000 cm = 3240.000 cm

Expecting such an output is silly. What one _can_ expect is

   27.000 m + 540.000 cm = 3240.000 cm

Natural language output like the following is out of the due purpose of a
package for unit handling:

   If traveled in 33.000 secs then speed = 98.182 cm/sec

In Italian, kilogram is chilogramm, you buy "un etto" or "due etti" of
something, i.e. 1 or 2 hg (hectogram, not Hg, "Hecagramm" - Hg is
quicksilver).

Do you really want to go into this business of internationalising plurals?

10. Example

I have added an equation that is quite common:

   M = m0 * (T/Tau)^2

and written it in several forms. The result is below. Many of the failing
statements can be cured be adding yet more instantiations. This is what I
mean with combinatorial explosion. Even for only three dimensions, this is
becoming awkward.

And if you write it in the most natural way, abstract operations get into
your way.

  use type kg.value, sec.value;

  T, Tau: sec.value := 1.0;
  M, m0 : kg .value := 1.0;

begin

  M := m0 * (T*T/(Tau*Tau));
  --          1      2
  -- >>> cannot call abstract subprogram ""*""
  -- >>> cannot call abstract subprogram ""*""

  M := m0 * (T*T)/(Tau*Tau);
  --      1           4
  -- >>> invalid operand types for operator "*"
  -- >>> left operand has type "Ada.Units.System_Of_Units.Value" from instance at line 28
  -- >>> right operand has type "Ada.Units.System_Of_Units.Value" from instance at line 19
  -- >>> expected type "Ada.Units.System_Of_Units.Value" from instance at line 28
  -- >>> found type "Ada.Units.System_Of_Units.Value" from instance at line 19

  M := m0 * T*T/(Tau*Tau);
  --      1   4     6
  -- >>> invalid operand types for operator "*"
  -- >>> left operand has type "Ada.Units.System_Of_Units.Value" from instance at line 28
  -- >>> right operand has type "Ada.Units.System_Of_Units.Value" from instance at line 19
  -- >>> expected type "Ada.Units.System_Of_Units.Value" from instance at line 28
  -- >>> found type "Ada.Units.System_Of_Units.Value" from instance at line 19
  -- >>> expected type "Ada.Units.System_Of_Units.Value" from instance at line 28
  -- >>> found type "Ada.Units.System_Of_Units.Value" from instance at line 19

  M := m0 * (T/Tau)*(T/Tau);

  M := m0 * (T/Tau*T/Tau);
  --              |
  -- >>> ambiguous expression (cannot resolve ""*"")
  -- >>> possible interpretation at a-usofun.ads:94, instance at line 19

  M := m0 * T/Tau*T/Tau;
  --      1   4   6 8
  -- >>> invalid operand types for operator "*"
  -- >>> left operand has type "Ada.Units.System_Of_Units.Value" from instance at line 28
  -- >>> right operand has type "Ada.Units.System_Of_Units.Value" from instance at line 19
  -- >>> expected type "Ada.Units.System_Of_Units.Value" from instance at line 28
  -- >>> found type "Ada.Units.System_Of_Units.Value" from instance at line 19
  -- >>> expected type "Ada.Units.System_Of_Units.Value" from instance at line 28
  -- >>> found type "Ada.Units.System_Of_Units.Value" from instance at line 19
  -- >>> expected type "Ada.Units.System_Of_Units.Value" from instance at line 28
  -- >>> found type "Ada.Units.System_Of_Units.Value" from instance at line 19

  M := m0 * T**2/Tau**2;
  --      1         4
  -- >>> invalid operand types for operator "*"
  -- >>> left operand has type "Ada.Units.System_Of_Units.Value" from instance at line 28
  -- >>> right operand has type "Ada.Units.System_Of_Units.Value" from instance at line 19
  -- >>> expected type "Ada.Units.System_Of_Units.Value" from instance at line 28
  -- >>> found type "Ada.Units.System_Of_Units.Value" from instance at line 19

  M := m0 * (T/Tau)**2;

end test_units;
--------------------------------------------------------------------------
Please let me summarize.

I do _not_ say that the method does not have its merits. I only want to point
out that it is, in its present form, not fit to handle physics in its whole
generality - which would be implied if it were standardised.

And, by the way, it wasn't the wrong equations that made Mars Lander fail,
it was improper mixing of imperial and metric units in communicating CSCIs,
and this method, as any other method, would not have prevented this failure,
since units are not transferred via data buses nor global memory.

Until shown a convincing example of a compile-time solution, I do believe
that full dimension handling can only be done during run-time (in Ada as it
is now).

C++ with its implicit instantiation of templates can do during compile-time
what Ada can do only during run-time. And indeed, there was a proposal of
such a feature for Ada9X:

   J. Shen, G. V. Cormack, Automatic Instantiation in Ada,
   ACM 0-89791-445-7/91/1000-0338 $1.50

(I do not say that I think inclusion of implicit instantiation into Ada is a
sensible thing. I let decide upon this by more competent persons.)

****************************************************************

From: Pascal Leroy
Sent: Tuesday, February 4, 2003  6:39 AM

> 8. Abstract Operators
>
> An annoying feature is that illegal operators like time * time -> time are
> present and made abstract, rather than being absent.
>
> Abstractness does not prevent operators to be taken into account upon
> overload resolution. So they may raise their ugly heads every now and then
> to the dismay of the poor user of the proposal (see below).

Note that AI 310 proposes a mechanism to ignore abstract operations during
overload resolutions in some cases.  This would help a lot in the context of
this AI.  In fact, I don't believe that an appropriate static solution to the
issue of physical unit checking can be found without AI 310 (or something
similar).

****************************************************************

From: David C. Hoos, Sr.
Sent: Tuesday, February 4, 2003  7:10 AM

> However sqrt (5 cm) makes perfectly sense as does sin (5 cm, cycle => 10 cm)
> and tan (y => 10 cm, x => 5 cm).

Did you mean arctan (y => 10 cm, x => 5 cm)?

****************************************************************

From: Christoph Grein
Sent: Tuesday, February 4, 2003  7:22 AM

Yes, of course. Thanx for reading so well.

****************************************************************

From: Pascal Leroy
Sent: Tuesday, February 4, 2003  7:11 AM

> 2. Product Unit Name
>
> Why is the default name of a product unit Unit_a & '-' & Unit_B?
> Is this a misprint? Unit_a & '*' & Unit_B seems more appropriate and
> is in line with the quotient name Unit_a & '/' & Unit_B.
>
>    J = N-m  vs.  J = N*m

Actually, the character at position 183 is a middle dot which appears to be the
recommended way to express products of units (see
http://www.bipm.fr/pdf/si-brochure.pdf, paragraph 5.3).

****************************************************************

From: Tucker Taft
Sent: Tuesday, February 4, 2003  3:57 PM

Pascal Leroy wrote:
>
> > 8. Abstract Operators
> >
> > An annoying feature is that illegal operators like time * time -> time are
> > present and made abstract, rather than being absent.
> >
> > Abstractness does not prevent operators to be taken into account upon
> > overload resolution. So they may raise their ugly heads every now and then
> > to the dismay of the poor user of the proposal (see below).
>
> Note that AI 310 proposes a mechanism to ignore abstract operations during
> overload resolutions in some cases.  This would help a lot in the context of
> this AI.  In fact, I don't believe that an appropriate static solution to the
> issue of physical unit checking can be found without AI 310 (or something
> similar).

Actually, I think my attempt to use visible floating point types
is doomed, so I am in the process of changing to using private types
except for unitless/dimensionless types.
This will eliminate the need for making any predefined operators abstract.

The reason why using visible floating point types is doomed is that
numeric literals and named numbers will be usable anywhere and everywhere,
either creating lots of ambiguity, or "nicely" allowing the user to
violate the units checking model they so carefully constructed.

So my plan is to add "Val" and "Mag" (for "Magnitude") functions as follows:

   function Val(Mag : Unitless.Value) return My_Unit.Value;
   function Mag(Val : My_Unit.Value) return Unitless.Value;

These are analogous to the 'Val and 'Pos attributes of enumeration types.
To create a literal of a given unit, you can write "My_Unit.Val(3.325)".
If for some reason you want the underlying magnitude of a "My_Unit" value,
you can do something like use "My_Unit.Mag(X)".  Of course, the operators
defined by the various _Unit packages will use the "Mag()" and
"Val()" functions extensively to convert to/from a "real" floating
point type.

So, stay tuned for the next version...

****************************************************************

From: Christoph Grein
Sent: Wednesday, February 5, 2003 12:01 AM

> So my plan is to add "Val" and "Mag" (for "Magnitude") functions as follows:
>
>    function Val(Mag : Unitless.Value) return My_Unit.Value;
>    function Mag(Val : My_Unit.Value) return Unitless.Value;
>
> These are analogous to the 'Val and 'Pos attributes of enumeration types.

So why don't you use

     function Pos(Val : My_Unit.Value) return Unitless.Value;

> To create a literal of a given unit, you can write "My_Unit.Val(3.325)".

People are sometimes peculiar. I used the unary plus to construct private type
values from literals. Many collegues could never get used to this and kept
complaining. So in a follow-on project (where I'm not part) they changed my
private types to open numeric types just to have literals and with this opened
the door to many other unwanted features (like wrong type conversions).

So how much would they object to My_Unit.Val(3.325)?

Notwithstanding my above comments, I would propose to use

   function "+"(Mag : Unitless.Value) return My_Unit .Value;
   function Mag(Val : My_Unit .Value) return Unitless.Value;

> If for some reason you want the underlying magnitude of a "My_Unit" value,
> you can do something like use "My_Unit.Mag(X)".  Of course, the operators
> defined by the various _Unit packages will use the "Mag()" and
> "Val()" functions extensively to convert to/from a "real" floating
> point type.
>
> So, stay tuned for the next version...

Will this also take care of some of my other comments?

****************************************************************

From: Tucker Taft
Sent: Wednesday, February 5, 2003  3:49 AM

> So why don't you use
>
>      function Pos(Val : My_Unit.Value) return Unitless.Value;

Well "Pos" stands for position number, and it seemed
like that really only made sense for discrete types.


...
> Notwithstanding my above comments, I would propose to use
>
>    function "+"(Mag : Unitless.Value) return My_Unit .Value;
>    function Mag(Val : My_Unit .Value) return Unitless.Value;

I think using an opeator for "Val" will get back to the
same old problem.  If you write "Y := (+ 33.3) * X" then
you have said nothing about the units of "33.3" and the
compiler will automatically pick something that works.
That seems to pretty much defeat any units checking,
since you can assign anything to anything if you just
multiply it by "(+1.0)".

We could define a parameterless version of "Val" which
was equivalent to Val(1.0), so you could write:

    "Len := 3.0 * cm.Val;" rather than "Len := cm.Val(3.0);"

I don't see that as being any better, but maybe it
looks nicer with the literal outside of parens.
Or we could call this parameterless function "Unit" giving

    "Len := 3.0 * cm.Unit;"

Of course now the term "Unit" is getting pretty heavily overloaded,
but maybe that is OK.

...
> Will this also take care of some of my other comments?

Yes, I hope it will address a number of them.
Thanks a lot for your careful review.

****************************************************************

From: Christoph Grein
Sent: Wednesday, February 5, 2003  4:26 AM

>     "Len := 3.0 * cm.Val;" rather than "Len := cm.Val(3.0);"
>
> Or we could call this parameterless function "Unit" giving
>
>     "Len := 3.0 * cm.Unit;"

I like this much more since it looks natural:  D = 5 cm.

This is what I did in my package - I have constants for each every SI unit:

  Watt: constant Item := Joule / Second;

  Power: Item := 10.0 * Mega * Watt;

****************************************************************

From: Tucker Taft
Sent: Wednesday, February 5, 2003  5:39 AM

Ok, I have added a function called Unit, which
is just a renaming of "Val" but with the parameter defaulted to
1.0.  I.e.:

     function Unit(Mag : Scale_Type := 1.0) return Value renames Val;

I have included an example using some of the
SI preinstantiations below, along with this new
"Unit" function.

----------- example of output -----------

   27.000 m + 540.000 cm = 3240.000 cm
   If traveled in 33.000 s then speed = 98.182 cm/s
   Three kilograms = 3.000 kg
   Two and a half microsecs = 2.500 us

----------- source code for example using SI_Units ----------

with Ada.Text_IO;
with Ada.Units.system_of_units;
with Ada.Units.SI_Units.Derived_Units;

use Ada.Units;
use Ada.Units.SI_Units;
use Ada.Units.SI_Units.Derived_Units;
procedure test_si_units is

     package cm is new SI.scaled_unit(Meter.Sig, Relative_Scale => 0.01);
     package cm_output is new SI.text_output(cm.signature);

     package g_output is new SI.text_output(Gram.sig);

     package sec renames SI_Units.Second;
     package sec_output is new SI.text_output(sec.signature);

     package cps is new SI.quotient_unit(cm.sig, sec.sig);
     package cps_output is new SI.text_output(cps.signature);

     package meter_output is new SI.text_output(meter.sig);

     package kg renames SI_Units.Kilogram;
     package kg_output is new SI.text_output(kg.sig);

     package usec is new SI.scaled_unit(
       base_unit => sec.sig, relative_scale => 1.0E-6);
     package usec_output is new SI.text_output(usec.sig);

     package msec is new SI.scaled_unit(base_unit => sec.sig,
       relative_scale => 1.0E-3);

     use type cm.value, meter.value;
     X : meter.value := 27.0 * meter.unit;

     Y : cm.value := cm.val(540.0);


     use type sec.value;

     Speed : cps.value;         -- cm/sec
     Interval : sec.value := 33.0 * sec.unit;  -- seconds

     use type cps.value;
     use type usec.value;
begin
     meter_output.put(X); ada.text_io.put(" + ");
     cm_output.put(Y); ada.text_io.put(" = ");
     cm_output.put(+ X + Y);
     ada.text_io.new_line;
     speed := (+ X + Y)/Interval;
     ada.text_io.put_line("If traveled in " & sec_output.image(Interval) &
     " then speed = " & cps_output.image(speed));

     ada.text_io.put_line("Three kilograms = " & kg_output.image(kg.val(3.0)));

     ada.text_io.put_line("Two and a half microsecs = " &
         usec_output.image(2.5 * usec.unit));
end;

****************************************************************

From: Tucker Taft
Sent: Wednesday, February 5, 2003  5:19 AM

Here are updated specs and bodies for the Ada.Units.*
packages and generics.  I haven't updated
the AI as a whole yet.

The major changes are:

- the units are all now based on private types
   except for dimensionless, scale=1.0 units.
   This prevents the direct use of literals
   except as unitless multipliers.  A "Val"
   function, analogous the the 'Val attribute
   of enumeration types, is available for constructing
   values with particular units.  E.g. "cm.Val(3.5)"
   constructs a value of type "cm.Value" with magnitude
   3.5.  You can get back the magnitude with the
   inverse function, called "Mag" (analogous to the
   'Pos attribute of enumeration types).

- there is now support for units that are integral
   or fractional powers of one another.  There is
   special support for squared, cubed, and square
   root units, and then basic support for arbitrary
   powers.  This required returning to floating-point
   exponents in the exponent-array.  Since exponent-array
   fiddling all happens at elaboration time, the additional
   overhead seems pretty minor.  Note that we are relying
   on well-behaved floating point (e.g. IEEE) so equality
   works reliably with fractional exponents.  If this
   proves to be a problem, we may have to change the assertions
   to allow for a small mismatch in the exponents (based on
   Model_Epsilon, presumably).

- The scaling prefixes used now conform to
   the SI standard, except for places where they require
   characters outside of the ISO 646 7-bit set (e.g. "u"
   rather than "<greek mu>").  The prefixes can be
   overridden via the Localization mechanism (see below).

- The automatic unit name construction support package now
   allows for localization (aka Internationalization), in
   simple ways by simply changing certain fields of
   the Localization record, and in more sophisticated ways
   by extending the Localization type and overriding one or
   more of the name construction operations.

- There are now SI_Units and SI_Units.Derived_Units
   packages that include the standard 7 SI units, and 21
   of the 22 standard "derived" SI units.  These use
   the standard 1-3 character names for the units,
   except in cases where characters outside of the
   7-bit ISO 646 set were needed (e.g. "ohm" is used
   instead of "<omega char>").  The names can be
   overridden when instantiating Text_Output.

- The Text_Output generic now more closely conforms
   to the existing IO packages, such as Float_IO,
   Decimal_IO, and Complex_IO, in its handling of Fore/Aft/Exp.



-------------- specs -------------

pragma Ada_Child;
package Ada.Units is
     type Exponent_Type is digits 5; -- implementation defined
     type Scale_Type is digits 11; -- Implementation defined
end Ada.Units;

generic
     type Names_Of_Dimensions is (<>);
package Ada.Units.Dimension_Exponents is
     -- Names_Of_Dimensions should be an enumeration type;
     -- Each enumeration literal corresponds to one dimension
     -- in the system of units.

     -- NOTE: It is recommended that each enumeration literal
     -- be a generic dimension name like "length" or "time" so it
     -- won't collide with the name of a specific unit such as "cm"
     -- which would be the typical name for an instance of the
     -- "Unit" generic.

     type Exponent_Array is array(Names_Of_Dimensions) of Exponent_Type;

     Number_Of_Dimensions : constant Integer := Exponent_Array'Length;

     function "+"(Left, Right : Exponent_Array) return Exponent_Array;
     function "-"(Left, Right : Exponent_Array) return Exponent_Array;
     function "-"(Right : Exponent_Array) return Exponent_Array;
         -- Component-wise "+" and "-"

     function "*"(Left : Exponent_Type; Right : Exponent_Array)
       return Exponent_Array;
     function "*"(Left : Exponent_Array; Right : Exponent_Type)
       return Exponent_Array;
         -- Vector multiply
end Ada.Units.Dimension_Exponents;

package Ada.Units.Name_Support is
     -- Package of string utilities useful for generating
     -- names automatically

     type Localization is tagged record
       -- This type provides information that
       -- controls the effect of the Name Support operations.
       -- It may be extended, and the operations may be overridden
       -- to provide more extensive localization.
         Product_Name_Separator : Character;
           -- Separator character to use to form a "product" unit
         Quotient_Name_Separator : Character;
           -- Separator character to use to form a "quotient" unit
         Power_Name_Separator : Character;
         Micro_Abbreviation : Character;
           -- Character to use to represent "micro"
         Max_Length_With_Short_Prefix : Natural;
           -- Maximum length of unit name that should use
           -- the "short" SI prefix; Set to Natural'Last
           -- to use short prefix with all unit names.
         Max_Length_With_No_Pluralization : Natural;
           -- Maximum length of unit name that should
           -- undergo no pluralization;  Set to Natural'Last
           -- to suppress all pluralization.
         Pluralization_Character : Character;
           -- Pluralization character to be used for names
           -- longer than Max_Length_With_No_Pluralization.
     end record;

     function Scale_Prefix(Locale : Localization;
       Scale_Factor : Scale_Type) return String;
       -- Return appropriate prefix given scale factor.
       -- (e.g. "kilo" for 1000.0)
       -- If scale factor is not something common, then return
       -- Scale_Type'Image(Scale_Factor) & Locale.Product_Name_Separator

     function Short_Scale_Prefix(Locale : Localization;
       Scale_Factor : Scale_Type) return String;
       -- Return appropriate short prefix given scale factor.
       -- (e.g. "k" for 1000.0)
       -- If scale factor is not something common, then return
       -- Scale_Type'Image(Scale_Factor) & Locale.Product_Name_Separator

     function Prefixed_Name(Locale : Localization;
       Unit_Name : String; Relative_Scale : Scale_Type) return String;
       -- Add a prefix to name to account for scale factor
       -- E.g., if Relative_Scale = 1000.0, return "kilo"
       -- or "k" depending on length of Unit_Name ("k" if
       -- Unit_Name <= Locale.Max_Length_With_Short_Prefix chars in length,
       -- "kilo" otherwise)

     function Pluralize(Locale : Localization;
       Singular_Name : String) return String;
       -- Return plural form given singular form.
       -- In general returns Singular_Name unchanged
       -- if it is <= Locale.Max_Length_With_No_Pluralization characters,
       -- and adds a Locale.Pluralization_Character otherwise

     function Product_Name(Locale : Localization;
       Unit_A, Unit_B : String) return String;
         -- Return default name for Product_Unit, given name
         -- of two units forming the product.
         -- By default returns Unit_A & Locale.Product_Name_Separator & Unit_B

     function Quotient_Name(Locale : Localization;
       Numerator, Denominator : String) return String;
         -- Return default name for Quotient_Unit, given name
         -- of numerator and denominator
         -- By default returns Numerator & Locale.Quotient_Name_Separator &
         -- Denominator

     function Is_Quotient_Name(Locale : Localization;
       Name : String) return Boolean;
       -- Return true if name consists of numerator and denominator
       -- with separating Locale.Quotient_Name_Separator

     function Numerator_Part(Locale : Localization;
       Quotient : String) return String;
       -- Return numerator part of name constructed via
       -- Quotient_Name

     function Denominator_Part(Locale : Localization;
       Quotient : String) return String;
       -- Return denominator part of name constructed via
       -- Quotient_Name

     function Power_Name(Locale : Localization;
       Base_Unit : String; Power : Exponent_Type) return String;
         -- Return default name for Base_Unit raised to a power.
         -- By default returns Base_Unit & Locale.Power_Name_Separator &
         -- decimal textual image for Power, parenthesized if negative, with no
         -- leading space if positive, and no decimal point if integral

     -- Now that all dispatching operations have been declared,
     -- we can declare a default locale to use for System_Of_Units
     Default_Locale : constant Localization :=
       -- Defaults for localization, appropriate to
       -- ISO 646, English-speaking usages.
       (Product_Name_Separator => '.',
        Quotient_Name_Separator => '/',
        Power_Name_Separator => '^',
        Micro_Abbreviation => 'u',
        Max_Length_With_Short_Prefix => 3,
        Max_Length_With_No_Pluralization => 3,
        Pluralization_Character => 's');

end Ada.Units.Name_Support;

package Ada.Units.Powers is
     -- Functions used to support powers and fractional units
     function Sqrt(Val : Scale_Type) return Scale_Type;
     function Cube_Root(Val : Scale_Type) return Scale_Type;
     function "**"(Left : Scale_Type; Right : Exponent_Type) return Scale_Type;
end Ada.Units.Powers;

with Ada.Text_IO;  -- for text_output
with Ada.Units.Name_Support;
with Ada.Units.Dimension_Exponents;
with Ada.Units.Powers;
generic
     type Names_Of_Dimensions is (<>);
     type Value_Type is digits <>;
     Locale : Name_Support.Localization'Class := Name_Support.Default_Locale;
package Ada.Units.System_Of_Units is
     -- Instantiate this package for each system of units

     -- Names_Of_Dimensions should be an enumeration type;
     -- Each enumeration literal corresponds to one dimension
     -- in the system of units.
     -- Value_Type is floating-point type that will be parent type
     -- for all types declared in this package.
     -- Locale allows for more control over automatically
     -- constructed unit names (see Ada.Units.Name_Support).

     package Dimensions is
       new Ada.Units.Dimension_Exponents(Names_Of_Dimensions);

     use Dimensions;

     generic
         Name : in String;
         Exponents : in Exponent_Array;
         Scale_Factor : in Scale_Type := 1.0;
         type Value is private;
         with function Val(Mag : Scale_Type) return Value is <>;
         with function Mag(Val : Value) return Scale_Type is <>;
     package Unit_Signature is end Unit_Signature;
         -- This is a generic "signature" package used
         -- to allow uniform use of the various types
         -- declared below.
         -- Scale_Factor is scaling factor.  It is expressed
         -- in the base units (e.g. grams, meters, whatever).
         -- Every value is implicitly multiplied by this scale
         -- to give its value in the base unit.
         -- So for milliseconds the scale would be 0.001 presuming
         -- the base unit is seconds.
         -- Val and Mag (short for "Magnitude") are functions for
         -- converting the private Value type to/from the Scale_Type.


     package Unitless is
         -- These types are unitless (aka dimensionless)
         type Value is new Value_Type'Base;
         -- Multiplicative operators are OK on Unitless types

         -- Define other parameters used in signature package
         Name : constant String := "(unitless)";
         Exponents : constant Exponent_Array := (others => 0.0);
         Scale_Factor : constant Scale_Type := 1.0;

         function Val(Mag : Scale_Type) return Value;
         function Mag(Val : Value) return Scale_Type;

         package Signature is new Unit_Signature(
           Name, Exponents, Scale_Factor, Value);

         package Sig renames Signature; -- for convenience

         pragma Inline(Val, Mag);
     end Unitless;

     package Private_Numeric is
       -- Define a private type to be used as a base for further derivations;
       -- provide additive operators that operate on the type;
       -- provide multiplicative operators that combine with the unitless type.

         type Value is private;

         function "+"(Right : Value) return Value;
         function "+"(Left, Right : Value) return Value;

         function "-"(Right : Value) return Value;
         function "-"(Left, Right : Value) return Value;

         function "*"(Left : Value; Right : Unitless.Value) return Value;
         function "*"(Left : Unitless.Value; Right : Value) return Value;

         function "/"(Left : Value; Right : Unitless.Value) return Value;
         function "/"(Left : Value; Right : Value) return Unitless.Value;

         -- Provide operations for converting between private
         -- type and visible floating point type
         function Val(Mag : Scale_Type) return Value;
         function Mag(Val : Value) return Scale_Type;

     private
         pragma Inline("*", "/", Val, Mag);

         -- Use double rename "trick" to define "+"/"-" via renaming-as-body
         type Base_Value is new Value_Type'Base;
         function Plus(Right : Base_Value) return Base_Value renames "+";
         function Plus(Left, Right : Base_Value) return Base_Value renames "+";
         function Minus(Right : Base_Value) return Base_Value renames "-";
         function Minus(Left, Right : Base_Value) return Base_Value renames "-";

         type Value is new Base_Value;
         function "+"(Right : Value) return Value renames Plus;
         function "+"(Left, Right : Value) return Value renames Plus;
         function "-"(Right : Value) return Value renames Minus;
         function "-"(Left, Right : Value) return Value renames Minus;

     end Private_Numeric;


     generic
         Name : in String;
         Exponents : in Exponent_Array;
     package Unit is
         -- Instantiate this generic once for each distinct base unit
         -- Name is default name to use for unit on output (singular)
         -- Exponents is array of powers of each dimension

         -- This package is for units that have some non-zero dimension
         -- See Dimensionless_Unit below for case where exponents are all zero
         pragma Assert(Exponents /= Unitless.Exponents);

         type Value is new Private_Numeric.Value;
           -- Inherit ops with unitless type

         -- Scale_Factor of base unit is always 1.0
         Scale_Factor : constant Scale_Type := 1.0;

         package Signature is new Unit_Signature(
           Name, Exponents, Scale_Factor, Value);
           -- Provide signature package for use with other generics

         package Sig renames Signature; -- for convenience

     end Unit;

     generic
         with package Unit_A is new Unit_Signature(<>);
         with package Unit_B is new Unit_Signature(<>);
     package Scaling is
         -- Instantiate this to get scaling functions
         -- between units representing same physical dimensions
         -- but with different scale factors

         -- Note that this is instantiated as part of
         -- defining a scaled unit below, providing
         -- scaling functions between the base unit
         -- and the scaled unit.  Instantiate this directly
         -- to get additional scaling functions between two scaled units
         -- (with the same base unit).

         pragma Assert(Unit_A.Exponents = Unit_B.Exponents);
         function Scale(From : Unit_A.Value) return Unit_B.Value;
         function Scale(From : Unit_B.Value) return Unit_A.Value;

         pragma Inline(Scale);
     end Scaling;

     generic
         with package Base_Unit is new Unit_Signature(<>);
         Relative_Scale : in Scale_Type;
         Name : in String :=
           Name_Support.Prefixed_Name(Locale, Base_Unit.Name, Relative_Scale);
     package Scaled_Unit is
         -- Instantiate this package to create a unit
         -- with the same dimensions as the base unit,
         -- but a different scale factor
         -- Relative_Scale is scale factor relative to base unit
         -- "Absolute" scale factor is Relative_Scale * Base_Unit.Scale_Factor

         type Value is new Private_Numeric.Value;
             -- Inherit ops with Unitless type
             -- (no need to override ops because no scaling required
             --  when combining with unitless type)

           -- Define other parameters to signature
         Scale_Factor : constant Scale_Type :=
           Relative_Scale * Base_Unit.Scale_Factor;

         Exponents : Exponent_Array renames Base_Unit.Exponents;

         package Signature is new Unit_Signature(
           Name, Exponents, Scale_Factor, Value);
             -- Provide signature for use with other generics

         package Sig renames Signature; -- for convenience

         package Scaling is new Ada.Units.System_Of_Units.Scaling(
           Base_Unit, Scaled_Unit.Signature);
             -- Get scaling functions between base unit and scaled unit

         -- And rename them for direct visibility
         function Scale(From : Base_Unit.Value) return Scaled_Unit.Value
           renames Scaling.Scale;
         function Scale(From : Scaled_Unit.Value) return Base_Unit.Value
           renames Scaling.Scale;
             -- also note that unary "+" can be used for this scaling
             -- (see below)

         -- Define the appropriate additive operators
         -- NOTE: Except for unary "+", these all return Base_Unit.Value to
         -- avoid ambiguity in complicated expressions.
         function "+"(Left : Base_Unit.Value; Right : Scaled_Unit.Value)
           return Base_Unit.Value;
         function "+"(Left : Scaled_Unit.Value; Right : Base_Unit.Value)
           return Base_Unit.Value;
         function "+"(Right : Scaled_Unit.Value)
           return Base_Unit.Value renames Scaling.Scale;
             -- Unary "+" can be used for scaling.

         function "+"(Right : Base_Unit.Value)
           return Scaled_Unit.Value renames Scaling.Scale;
             -- Unary "+" can be used for scaling.

         function "-"(Left : Base_Unit.Value; Right : Scaled_Unit.Value)
           return Base_Unit.Value;
         function "-"(Left : Scaled_Unit.Value; Right : Base_Unit.Value)
           return Base_Unit.Value;
         function "-"(Right : Scaled_Unit.Value)
           return Base_Unit.Value;

         pragma Inline("+", "-");

     end Scaled_Unit;

     generic
         with package Unit_A is new Unit_Signature(<>);
         with package Unit_B is new Unit_Signature(<>);
         with package Unit_C is new Unit_Signature(<>);
     package Multiplicative_Operators is
         -- Instantiate this package with three units
         -- where A * B = C is well defined to get
         -- the appropriate multiplicative operators.
         -- Scaling is performed automatically.
         -- NOTE: This is instantiated below in Product_Unit
         -- and Quotient_Unit.  Those are the preferred way
         -- for getting these cross-unit operators.

         pragma Assert(Unit_A.Exponents + Unit_B.Exponents = Unit_C.Exponents);

         function "*"(Left : Unit_A.Value; Right : Unit_B.Value)
           return Unit_C.Value;
         function "*"(Left : Unit_B.Value; Right : Unit_A.Value)
           return Unit_C.Value;
         function "/"(Left : Unit_C.Value; Right : Unit_A.Value)
           return Unit_B.Value;
         function "/"(Left : Unit_C.Value; Right : Unit_B.Value)
           return Unit_A.Value;

         pragma Inline("*", "/");
     end Multiplicative_Operators;

     generic
         with package Unit_A is new Unit_Signature(<>);
         with package Unit_B is new Unit_Signature(<>);
         Name : in String :=
           Name_Support.Product_Name(Locale, Unit_A.Name, Unit_B.Name);
     package Product_Unit is
         -- Instantiate this package for a unit that is
         -- the product of two other units.
         -- The Exponents of the new type is the sum of those for
         -- Unit_A and Unit_B.
         -- The Scale_Factor for the new type is the product of the scales
         -- of Unit_A and Unit_B.
         -- Use Scaled_Unit to get other scalings.
         -- The default Name is <unit_a>.<unit_b> (e.g. "gm.sec")

         type Value is new Private_Numeric.Value;
           -- Get ops with unitless type, etc.


         -- provide other parameters of signature
         Scale_Factor : constant Scale_Type :=
           Unit_A.Scale_Factor * Unit_B.Scale_Factor;

         Exponents : constant Exponent_Array :=
           Unit_A.Exponents + Unit_B.Exponents;

         package Signature is new Unit_Signature(
           Name, Exponents, Scale_Factor, Value);

         package Sig renames Signature; -- for convenience

         -- Get appropriate multiplicative operators
         package Ops is new Multiplicative_Operators(
           Unit_A, Unit_B, Product_Unit.Signature);

         -- Rename operators for direct visibility
         function "*"(Left : Unit_A.Value; Right : Unit_B.Value)
           return Product_Unit.Value renames Ops."*";
         function "*"(Left : Unit_B.Value; Right : Unit_A.Value)
           return Product_Unit.Value renames Ops."*";
         function "/"(Left : Product_Unit.Value; Right : Unit_A.Value)
           return Unit_B.Value renames Ops."/";
         function "/"(Left : Product_Unit.Value; Right : Unit_B.Value)
           return Unit_A.Value renames Ops."/";

     end Product_Unit;

     generic
         with package Unit_A is new Unit_Signature(<>);
         with package Unit_B is new Unit_Signature(<>);
         Name : in String :=
           Name_Support.Quotient_Name(Locale, Unit_A.Name, Unit_B.Name);
     package Quotient_Unit is
         -- Instantiate this package for a unit that is
         -- the quotient of two other units.
         -- The Exponents of the new type is the difference of those for
         -- Unit_A and Unit_B.
         -- The Scale_Factor for the new type is the ratio of the scales
         -- of Unit_A and Unit_B.
         -- Use Scaled_Unit to get other scalings.
         -- The default Name is <unit_a>/<unit_b> (e.g. "cm/sec")

         type Value is new Private_Numeric.Value;
           -- Get ops with unitless type, etc.


         -- provide other parameters of signature
         Scale_Factor : constant Scale_Type :=
           Unit_A.Scale_Factor / Unit_B.Scale_Factor;

         Exponents : constant Exponent_Array :=
           Unit_A.Exponents - Unit_B.Exponents;

         package Signature is new Unit_Signature(
           Name, Exponents, Scale_Factor, Value);

         package Sig renames Signature; -- for convenience

         -- Get appropriate multiplicative operators
         package Ops is new Multiplicative_Operators(
           Quotient_Unit.Signature, Unit_B, Unit_A);

         -- Rename operators for direct visibility
         function "*"(Left : Quotient_Unit.Value; Right : Unit_B.Value)
           return Unit_A.Value renames Ops."*";
         function "*"(Left : Unit_B.Value; Right : Quotient_Unit.Value)
           return Unit_A.Value renames Ops."*";
         function "/"(Left : Unit_A.Value; Right : Quotient_Unit.Value)
           return Unit_B.Value renames Ops."/";
         function "/"(Left : Unit_A.Value; Right : Unit_B.Value)
           return Quotient_Unit.Value renames Ops."/";

     end Quotient_Unit;

     generic
         Name : in String;
     package Dimensionless_Unit is
         -- Instantiate this generic once for each
         -- distinct dimensionless base unit (e.g. radians),
         -- where multiplication and division of the unit
         -- with itself are well defined (and hence exponentiation makes
         -- sense).
         -- Name is default name to use for unit on output (singular).

         type Value is new Unitless.Value;
           -- All operators inherited, including multiply, divide, and
           -- exponentiation.

         -- Exponents all zero
         Exponents : Exponent_Array renames Unitless.Exponents;

         -- Scale_Factor of base unit is always 1.0
         Scale_Factor : constant Scale_Type := 1.0;


         package Signature is new Unit_Signature(
           Name, Exponents, Scale_Factor, Value);
           -- Provide signature package for use with other generics

         package Sig renames Signature; -- for convenience

           -- NOTE: We do not provide the operators that combine
           -- with the unitless type as they create too much ambiguity

     end Dimensionless_Unit;

     generic
         with package Base_Unit is new Unit_Signature(<>);
         Name : in String :=
           Name_Support.Power_Name(Locale, Base_Unit.Name, Power => 2.0);
     package Squared_Unit is
         -- Instantiate this package for a unit that is
         -- the square of some other unit.
         -- The Exponents of the new type are twice those of Base_Unit.
         -- The Scale_Factor for the new type is the square of
         -- the scale of Base_Unit.
         -- Use Scaled_Unit to get other scalings.
         -- The default Name is <base_unit>^2 (e.g. "cm^2")

         type Value is new Private_Numeric.Value;
           -- Get ops with unitless type, etc.

         -- provide other parameters of signature
         Scale_Factor : constant Scale_Type := Base_Unit.Scale_Factor ** 2;

         Exponents : constant Exponent_Array := 2.0 * Base_Unit.Exponents;

         package Signature is new Unit_Signature(
           Name, Exponents, Scale_Factor, Value);

         package Sig renames Signature; -- for convenience

         -- Declare multiplicative operators
         function "*"(Left : Base_Unit.Value; Right : Base_Unit.Value)
           return Squared_Unit.Value;
         function "/"(Left : Squared_Unit.Value; Right : Base_Unit.Value)
           return Base_Unit.Value;

         -- Declare squaring and square root operations
         function Square(Val : Base_Unit.Value) return Squared_Unit.Value;

         function Sqrt(Val : Squared_Unit.Value) return Base_Unit.Value;

         pragma Inline("*", "/", Square);
     end Squared_Unit;

     generic
         with package Base_Unit is new Unit_Signature(<>);
         with package Squared_Base_Unit is new Unit_Signature(<>);
         Name : in String :=
           Name_Support.Power_Name(Locale, Base_Unit.Name, Power => 3.0);
     package Cubed_Unit is
         -- Instantiate this package for a unit that is
         -- the cube of some other unit.
         -- Must provide unit created using Squared_Unit as additional
         -- parameter, so proper multiplicative operators can be declared.

         -- The Exponents of the new type are three times those of Base_Unit.
         -- The Scale_Factor for the new type is the cube of
         -- the scale of Base_Unit.
         -- Use Scaled_Unit to get other scalings.
         -- The default Name is <base_unit>^3 (e.g. "cm^3")

         -- Make sure Base_Unit and Squared_Base_Unit are related
         -- properly
         pragma Assert(2.0 * Base_Unit.Exponents = Squared_Base_Unit.Exponents);
         pragma Assert(
           Base_Unit.Scale_Factor**2 = Squared_Base_Unit.Scale_Factor);

         type Value is new Private_Numeric.Value;
           -- Get ops with unitless type, etc.

         -- provide other parameters of signature
         Scale_Factor : constant Scale_Type := Base_Unit.Scale_Factor ** 3;

         Exponents : constant Exponent_Array := 3.0 * Base_Unit.Exponents;

         package Signature is new Unit_Signature(
           Name, Exponents, Scale_Factor, Value);

         package Sig renames Signature; -- for convenience

         -- Get appropriate multiplicative operators
         package Ops is new Multiplicative_Operators(
           Base_Unit, Squared_Base_Unit, Cubed_Unit.Signature);

         -- Rename operators for direct visibility
         function "*"(Left : Base_Unit.Value; Right : Squared_Base_Unit.Value)
           return Cubed_Unit.Value renames Ops."*";
         function "*"(Left : Squared_Base_Unit.Value; Right : Base_Unit.Value)
           return Cubed_Unit.Value renames Ops."*";
         function "/"(Left : Cubed_Unit.Value; Right : Base_Unit.Value)
           return Squared_Base_Unit.Value renames Ops."/";
         function "/"(Left : Cubed_Unit.Value; Right : Squared_Base_Unit.Value)
           return Base_Unit.Value renames Ops."/";

         -- Declare cubing and cube root operations
         function Cube(Val : Base_Unit.Value) return Cubed_Unit.Value;

         function Cube_Root(Val : Cubed_Unit.Value) return Base_Unit.Value;

         pragma Inline(Cube);
     end Cubed_Unit;

     generic
         with package Base_Unit is new Unit_Signature(<>);
         Name : in String :=
           Name_Support.Power_Name(Locale, Base_Unit.Name, Power => 0.5);
     package Square_Root_Unit is
         -- Instantiate this package for a unit that is
         -- the square root of some other unit.
         -- The Exponents of the new type are half those of Base_Unit.
         -- The Scale_Factor for the new type is the square root of
         -- the scale of Base_Unit.
         -- Use Scaled_Unit to get other scalings.
         -- The default Name is <base_unit>^(1/2) (e.g. "cm^(1/2)")

         type Value is new Private_Numeric.Value;
           -- Get ops with unitless type, etc.

         -- provide other parameters of signature
         Scale_Factor : constant Scale_Type :=
           Powers.Sqrt(Base_Unit.Scale_Factor);

         Exponents : constant Exponent_Array := 2.0 * Base_Unit.Exponents;

         package Signature is new Unit_Signature(
           Name, Exponents, Scale_Factor, Value);

         package Sig renames Signature; -- for convenience

         -- Declare multiplicative operators
         function "*"(Left : Square_Root_Unit.Value;
           Right : Square_Root_Unit.Value) return Base_Unit.Value;
         function "/"(Left : Base_Unit.Value; Right : Square_Root_Unit.Value)
           return Square_Root_Unit.Value;

         -- Declare squaring and square root operations
         function Square(Val : Square_Root_Unit.Value) return Base_Unit.Value;

         function Sqrt(Val : Base_Unit.Value) return Square_Root_Unit.Value;

         pragma Inline("*", "/", Square);
     end Square_Root_Unit;

     generic
         with package Base_Unit is new Unit_Signature(<>);
         Power : in Exponent_Type;
         Name : in String :=
           Name_Support.Power_Name(Locale, Base_Unit.Name, Power => Power);
     package Arbitrary_Power_Unit is
         -- Instantiate this package for a unit that is
         -- some power of some other unit (integral or fractional)
         -- The Exponents of the new type are "Power" times those of Base_Unit
         -- The Scale_Factor for the new type is the given power of
         -- the scale of Base_Unit.
         -- Use Scaled_Unit to get other scalings.
         -- The default Name is <base_unit>^(<power>>) (e.g. "cm^(1/4)")
         -- In name, "power" is expressed as ratio of small integers
         -- if is multiple of 1/2, 1/3, or 1/4.

         type Value is new Private_Numeric.Value;
           -- Get ops with unitless type, etc.

         use Ada.Units.Powers;  -- for "**" operator on Scale_Type

         -- provide other parameters of signature
         Scale_Factor : constant Scale_Type :=
           Base_Unit.Scale_Factor ** Power;

         Exponents : constant Exponent_Array := Power * Base_Unit.Exponents;

         package Signature is new Unit_Signature(
           Name, Exponents, Scale_Factor, Value);

         package Sig renames Signature; -- for convenience

         -- Declare appropriate exponentiation operations
         function Exponentiate_By_Power(Val : Base_Unit.Value)
           return Arbitrary_Power_Unit.Value;

         function Exponentiate_By_Inverse_Power(
           Val : Arbitrary_Power_Unit.Value) return Base_Unit.Value;

         -- Instantiate Multiplicative_Operators to
         -- get any appropriate "*" and "/" operators

     end Arbitrary_Power_Unit;



     -- NOTE: Text_Output would preferably be a generic child unit,
     -- but some compilers can't deal with a generic child
     -- that takes a signature declared in the generic parent.
     generic
         with package Unit_For_Output is new Unit_Signature(<>);
         Singular : in String := Unit_For_Output.Name;
         Plural : in String := Name_Support.Pluralize(Locale, Singular);
                                         -- Name for unit, plural form
     package Text_Output is
         -- Instantiate this for text output (and Image) with units included
         -- Singular is label when Val = 1.0
         -- Plural is label in other cases

         Default_Fore : Ada.Text_IO.Field := 2;
         Default_Aft : Ada.Text_IO.Field := 3;      -- 3 digits after decimal pt
         Default_Exp : Ada.Text_IO.Field := 0;          -- No exponent by default

         -- Default_Fore is minimum digits before decimal point
         -- Default_Aft is digits after decimal point
         -- Default_Exp is number of digits allowed for exponent
         -- (as used in Float_IO.Put)


         procedure Put(Val : in Unit_For_Output.Value;
           Fore : Ada.Text_IO.Field := Default_Fore;
           Aft : Ada.Text_IO.Field := Default_Aft;
           Exp : Ada.Text_IO.Field := Default_Exp);

         procedure Put(File : in Ada.Text_IO.File_Type;
           Val : in Unit_For_Output.Value;
           Fore : Ada.Text_IO.Field := Default_Fore;
           Aft : Ada.Text_IO.Field := Default_Aft;
           Exp : Ada.Text_IO.Field := Default_Exp);

         function Image(Val : in Unit_For_Output.Value;
           Fore : Ada.Text_IO.Field := Default_Fore;
           Aft : Ada.Text_IO.Field := Default_Aft;
           Exp : Ada.Text_IO.Field := Default_Exp) return String;

     end Text_Output;

end Ada.Units.System_Of_Units;

with Ada.Units.System_Of_Units;
   pragma Elaborate_All(Ada.Units.System_Of_Units);
package Ada.Units.SI_Units is
     -- This package provides a preinstantiation of System_Of_Units
     -- for the International System of Units (SI), and
     -- preinstantiations of the seven base units, plus
     -- grams, which is used in defining kilograms.

     type SI_Dimensions is
       (Length, Mass, Time, Electric_Current,
        Temperature, Amount_Of_Substance, Luminous_Intensity);
     package SI is new System_Of_Units(SI_Dimensions, Standard.Float);

     package Gram is new SI.Unit(
       Exponents => (Mass => 1.0, others => 0.0),
       Name => "g");

     package Meter is new SI.Unit(
       Exponents => (Length => 1.0, others => 0.0),
       Name => "m");
     package Kilogram is new SI.Scaled_Unit(
       Base_Unit => Gram.Sig, Relative_Scale => 1000.0);
     package Second is new SI.Unit(
       Exponents => (Time => 1.0, others => 0.0),
       Name => "s");
     package Ampere is new SI.Unit(
       Exponents => (Electric_Current => 1.0, others => 0.0),
       Name => "A");
     package Kelvin is new SI.Unit(
       Exponents => (Temperature => 1.0, others => 0.0),
       Name => "K");
     package Mole is new SI.Unit(
       Exponents => (Amount_Of_Substance => 1.0, others => 0.0),
       Name => "mol");
     package Candela is new SI.Unit(
       Exponents => (Luminous_Intensity => 1.0, others => 0.0),
       Name => "cd");

end Ada.Units.SI_Units;

package Ada.Units.SI_Units.Derived_Units is
     -- This package provides preinstantiations for 21 of the
     -- 22 standard named "derived units" of the SI system.
     -- Centrigrade is omitted because it represents an
     -- offset relative to Kelvin, which is not currently supported.
     -- It also provides 6 other preinstantiations which
     -- are either used in defining the standard derived units,
     -- or expected to be of wide use.

     -- Various useful derived units
     package Square_Meter is new SI.Squared_Unit(Meter.Sig);

     package Cubic_Meter is new SI.Cubed_Unit(Meter.Sig, Square_Meter.Sig);

     package Meter_Per_Second is new SI.Quotient_Unit(Meter.Sig, Second.Sig);

     package Second_Squared is new SI.Squared_Unit(Second.Sig);

     package Meter_Per_Second_Squared is new SI.Quotient_Unit(
       Meter.Sig, Second_Squared.Sig);


     -- 21 of 22 standard derived units
     package Radian is new SI.Dimensionless_Unit(Name => "rad");

     package Steradian is new SI.Dimensionless_Unit(Name => "sr");

     package Hertz is new SI.Quotient_Unit(
       SI.Unitless.Sig, Second.Sig, Name => "Hz");

     package Newton is new SI.Product_Unit(
       Kilogram.Sig, Meter_Per_Second_Squared.Sig, Name => "N");

     package Pascal is new SI.Quotient_Unit(
       Newton.Sig, Square_Meter.Sig, Name => "P");

     package Joule is new SI.Product_Unit(
       Newton.Sig, Meter.Sig, Name => "J");

     package Watt is new SI.Quotient_Unit(
       Joule.Sig, Second.Sig, Name => "W");

     package Coulomb is new SI.Product_Unit(
       Second.Sig, Ampere.Sig, Name => "C");

     package Volt is new SI.Quotient_Unit(
       Watt.Sig, Ampere.Sig, Name => "V");

     package Farad is new SI.Quotient_Unit(
       Coulomb.Sig, Volt.Sig, Name => "F");

     package Ohm is new SI.Quotient_Unit(
       Volt.Sig, Ampere.Sig, Name => "ohm");
         -- SI actually uses greek Omega, we are
         -- sticking with ISO 646 (7-bit) characters here.

     package Siemens is new SI.Quotient_Unit(
       Ampere.Sig, Volt.Sig, Name => "S");

     package Weber is new SI.Product_Unit(
       Volt.Sig, Second.Sig, Name => "Wb");

     package Tesla is new SI.Quotient_Unit(
       Weber.Sig, Square_Meter.Sig, Name => "T");

     package Henry is new SI.Quotient_Unit(
       Weber.Sig, Ampere.Sig, Name => "H");

     package Lumen is new SI.Product_Unit(
       Candela.Sig, Steradian.Sig, Name => "lm");

     package Lux is new SI.Quotient_Unit(
       Lumen.Sig, Square_Meter.Sig, Name => "lx");

     package Becquerel is new SI.Quotient_Unit(
       SI.Unitless.Sig, Second.Sig, Name => "Bq");

     package Gray is new SI.Quotient_Unit(
       Joule.Sig, Kilogram.Sig, Name => "Gy");

     package Sievert is new SI.Quotient_Unit(
       Joule.Sig, Kilogram.Sig, Name => "Sv");

     package Katal is new SI.Quotient_Unit(
       Mole.Sig, Second.Sig, Name => "kat");

end Ada.Units.SI_Units.Derived_Units;

----------- bodies --------------

package body Ada.Units.Dimension_Exponents is
     function "+"(Left, Right : Exponent_Array) return Exponent_Array is
         -- Component-wise "+"
         Result : Exponent_Array;
     begin
         for I in Result'Range loop
             Result(I) := Left(I) + Right(I);
         end loop;
         return Result;
     end "+";

     function "-"(Left, Right : Exponent_Array) return Exponent_Array is
         -- Component-wise "-"
         Result : Exponent_Array;
     begin
         for I in Result'Range loop
             Result(I) := Left(I) - Right(I);
         end loop;
         return Result;
     end "-";

     function "-"(Right : Exponent_Array) return Exponent_Array is
         -- Component-wise unary "-"
         Result : Exponent_Array;
     begin
         for I in Result'Range loop
             Result(I) := - Right(I);
         end loop;
         return Result;
     end "-";

     function "*"(Left : Exponent_Type; Right : Exponent_Array)
       return Exponent_Array is
         -- Vector multiply
         Result : Exponent_Array;
     begin
         for I in Result'Range loop
             Result(I) := Left * Right(I);
         end loop;
         return Result;
     end "*";

     function "*"(Left : Exponent_Array; Right : Exponent_Type)
       return Exponent_Array is
         -- Vector multiply
     begin
         -- Just reverse parameters and hand off to other multiply op
         return Right * Left;
     end "*";
end Ada.Units.Dimension_Exponents;

package body Ada.Units.Name_Support is
     -- Package of string utilities useful for generating
     -- names automatically

     function Scale_Prefix(Locale : Localization;
       Scale_Factor : Scale_Type) return String is
       -- Return appropriate prefix given scale factor.
       -- (e.g. "kilo" for 1000.0)
       -- If scale factor is not something common, then return
       -- Scale_Type'Image(Scale_Factor) & Locale.Product_Name_Separator
       -- Note: these come from http://physics.nist.gov/cuu/Units/prefixes.html
     begin
         if Scale_Factor = 1.0 then
             return "";
         elsif Scale_Factor = 10.0 then
             return "deka";
         elsif Scale_Factor = 100.0 then
             return "hecto";
         elsif Scale_Factor = 1000.0 then
             return "kilo";
         elsif Scale_Factor = 1.0E6 then
             return "mega";
         elsif Scale_Factor = 1.0E9 then
             return "giga";
         elsif Scale_Factor = 1.0E12 then
             return "tera";
         elsif Scale_Factor = 1.0E15 then
             return "peta";
         elsif Scale_Factor = 1.0E18 then
             return "exa";
         elsif Scale_Factor = 1.0E21 then
             return "zetta";
         elsif Scale_Factor = 1.0E24 then
             return "yotta";
         elsif Scale_Factor = 0.1 then
             return "deci";
         elsif Scale_Factor = 0.01 then
             return "centi";
         elsif Scale_Factor = 0.001 then
             return "milli";
         elsif Scale_Factor = 1.0E-6 then
             return "micro";
         elsif Scale_Factor = 1.0E-9 then
             return "nano";
         elsif Scale_Factor = 1.0E-12 then
             return "pico";
         elsif Scale_Factor = 1.0E-15 then
             return "femto";
         elsif Scale_Factor = 1.0E-18 then
             return "atto";
         elsif Scale_Factor = 1.0E-21 then
             return "zepto";
         elsif Scale_Factor = 1.0E-24 then
             return "yocto";
         else
             return Scale_Type'Image(Scale_Factor) &
               Locale.Product_Name_Separator;
         end if;
     end Scale_Prefix;

     function Short_Scale_Prefix(Locale : Localization;
       Scale_Factor : Scale_Type) return String is
       -- Return appropriate short prefix given scale factor.
       -- (e.g. "k" for 1000.0)
       -- If scale factor is not something common, then return
       -- Scale_Type'Image(Scale_Factor) & Locale.Product_Name_Separator
       -- Note: these come from http://physics.nist.gov/cuu/Units/prefixes.html
     begin
         if Scale_Factor = 1.0 then
             return "";
         elsif Scale_Factor = 10.0 then
             return "da";
         elsif Scale_Factor = 100.0 then
             return "h";
         elsif Scale_Factor = 1000.0 then
             return "k";
         elsif Scale_Factor = 1.0E6 then
             return "M";
         elsif Scale_Factor = 1.0E9 then
             return "G";
         elsif Scale_Factor = 1.0E12 then
             return "T";
         elsif Scale_Factor = 1.0E15 then
             return "P";
         elsif Scale_Factor = 1.0E18 then
             return "E";
         elsif Scale_Factor = 1.0E21 then
             return "Z";
         elsif Scale_Factor = 1.0E24 then
             return "Y";
         elsif Scale_Factor = 0.1 then
             return "d";
         elsif Scale_Factor = 0.01 then
             return "c";
         elsif Scale_Factor = 0.001 then
             return "m";
         elsif Scale_Factor = 1.0E-6 then
             return "u";
         elsif Scale_Factor = 1.0E-9 then
             return "n";
         elsif Scale_Factor = 1.0E-12 then
             return "p";
         elsif Scale_Factor = 1.0E-15 then
             return "f";
         elsif Scale_Factor = 1.0E-18 then
             return "a";
         elsif Scale_Factor = 1.0E-21 then
             return "z";
         elsif Scale_Factor = 1.0E-24 then
             return "y";
         else
             return Scale_Type'Image(Scale_Factor) &
               Locale.Product_Name_Separator;
         end if;
     end Short_Scale_Prefix;

     function Prefixed_Name(Locale : Localization;
       Unit_Name : String; Relative_Scale : Scale_Type) return String is
       -- Add a prefix to name to account for scale factor
       -- E.g., if Relative_Scale = 1000.0, return "kilo"
       -- or "k" depending on length of Unit_Name ("k" if
       -- Unit_Name <= Locale.Max_Length_With_Short_Prefix chars in length,
       -- "kilo" otherwise)
     begin
         if Unit_Name'Length <= Locale.Max_Length_With_Short_Prefix then
             return Short_Scale_Prefix(Locale, Relative_Scale) & Unit_Name;
         else
             return Scale_Prefix(Locale, Relative_Scale) & Unit_Name;
         end if;
     end Prefixed_Name;

     function Product_Name(Locale : Localization;
       Unit_A, Unit_B : String) return String is
         -- Return default name for Product_Unit, given name
         -- of two units forming the product.
         -- By default returns Unit_A & Locale.Product_Name_Separator & Unit_B
     begin
         return Unit_A & Locale.Product_Name_Separator & Unit_B;
     end Product_Name;

     function Quotient_Name(Locale : Localization;
       Numerator, Denominator : String) return String is
         -- Return default name for Quotient_Unit, given name
         -- of numerator and denominator
         -- By default returns Numerator & Locale.Quotient_Name_Separator &
         -- Denominator
     begin
         return Numerator & Locale.Quotient_Name_Separator & Denominator;
     end Quotient_Name;

     function Is_Quotient_Name(Locale : Localization;
       Name : String) return Boolean is
       -- Return true if name consists of numerator and denominator
       -- with separating Locale.Quotient_Name_Separator
     begin
         for I in Name'Range loop
             if Name(I) = Locale.Quotient_Name_Separator then
                 return True;
             end if;
         end loop;
         return False;
     end Is_Quotient_Name;

     function Numerator_Part(Locale : Localization;
       Quotient : String) return String is
       -- Return numerator part of name constructed via
       -- Quotient_Name
     begin
         for I in Quotient'Range loop
             if Quotient(I) = Locale.Quotient_Name_Separator then
                 return Quotient(Quotient'First .. I-1);
             end if;
         end loop;
         return Quotient;  -- Should never happen
     end Numerator_Part;

     function Denominator_Part(Locale : Localization;
       Quotient : String) return String is
       -- Return denominator part of name constructed via
       -- Quotient_Name
     begin
         for I in Quotient'Range loop
             if Quotient(I) = Locale.Quotient_Name_Separator then
                 return Quotient(I+1 .. Quotient'Last);
             end if;
         end loop;
         return "??";  -- Should never happen
     end Denominator_Part;

     function Pluralize(Locale : Localization;
       Singular_Name : String) return String is
       -- Return plural form given singular form.
       -- In general returns Singular_Name unchanged
       -- if it is <= Locale.Max_Length_With_No_Pluralization characters,
       -- and adds a Locale.Pluralization_Character otherwise
     begin
         if Singular_Name'Length <= Locale.Max_Length_With_No_Pluralization then
             -- Short unit names generally don't get pluralized
             -- (e.g. "g").
             return Singular_Name;
         elsif Is_Quotient_Name(Locale, Singular_Name) then
             -- If is a quotient name, then pluralize the numerator
             -- part only
             return Quotient_Name(Locale,
               Pluralize(Locale, Numerator_Part(Locale, Singular_Name)),
               Denominator_Part(Locale, Singular_Name));
         elsif Locale.Pluralization_Character = 's' then
             -- Special case the English rules
             -- TBD: This is pretty naive at this point
             case Singular_Name(Singular_Name'Last) is
                 when 'x' | 's' =>
                     return Singular_Name & "es";
                 when others =>
                     return Singular_Name & 's';
             end case;
         else
             -- This presumes the language has a single character
             -- universally used for plurals.
             -- NOTE: We're not sure such a language exists.
             -- Almost certainly, anyone serious about
             -- making this work appropriately for another language
             -- will want to extend Localization and override Pluralize

             return Singular_Name & Locale.Pluralization_Character;
         end if;
     end Pluralize;

     function Trimmed(Img : String) return String is
       -- Local function to return image with leading space if any trimmed off
     begin
         if Img(Img'First) = ' ' then
             return Img(Img'First+1..Img'Last);
         else
             return Img;
         end if;
     end Trimmed;

     function Power_Name(Locale : Localization;
       Base_Unit : String; Power : Exponent_Type) return String is
         -- Return default name for Base_Unit raised to a power.
         -- By default returns Base_Unit & Locale.Power_Name_Separator &
         -- rational image for Power, parenthesized if negative or
         -- non integral, with no leading space if positive
         Numerator : Exponent_Type := 0.0;
         Int_Num : Integer;
     begin
         for Denominator in 1..4 loop
             -- See whether is multiple of 1/1, 1/2, 1/3, or 1/4
             Numerator := Numerator + Power;  -- Numerator = Den * Power
             Int_Num := Integer(Numerator);

             if Exponent_Type(Int_Num) = Numerator then
                 -- Power is Integral multiple of 1/Denominator
               declare
                 Num_Image : constant String := Trimmed(Integer'Image(Int_Num));
               begin
                 if Denominator /= 1 then
                     -- Parenthesize fractional power
                     return Base_Unit & Locale.Power_Name_Separator &
                       '(' & Num_Image & Locale.Quotient_Name_Separator &
                         Trimmed(Integer'Image(Denominator)) & ')';
                 elsif Int_Num < 0 then
                     -- Parenthesize negative integral power
                     return Base_Unit & Locale.Power_Name_Separator &
                       '(' & Num_Image & ')';
                 else
                     -- No paretheses necessary
                     -- since is a simple non-negative integral power
                     return Base_Unit & Locale.Power_Name_Separator &
                       Num_Image;
                 end if;
               end;
             end if;
         end loop;

         -- Not an integral multiple of 1/1, 1/2, 1/3, or 1/4
         -- Just parenthesize image of power
         return Base_Unit & Locale.Power_Name_Separator &
           '(' & Trimmed(Exponent_Type'Image(Power)) & ')';
     end Power_Name;

end Ada.Units.Name_Support;

with Ada.Numerics.Long_Elementary_Functions; -- implementation-dependent choice
package body Ada.Units.Powers is
     -- Functions used to support powers and fractional units

     subtype Elem_Func_Type is Standard.Long_Float'Base;
       -- implementation-dependent choice
     package Elementary_Functions
       renames Ada.Numerics.Long_Elementary_Functions;
         -- implementation-dependent choice

     function Sqrt(Val : Scale_Type) return Scale_Type is
     begin
         return Scale_Type(Elementary_Functions.Sqrt(
           Elem_Func_Type(Val)));
     end Sqrt;

     function "**"(Left : Scale_Type; Right : Exponent_Type)
       return Scale_Type is
     begin
         return Scale_Type(Elementary_Functions."**"(
           Elem_Func_Type(Left), Elem_Func_Type(Right)));
     end "**";

     function Cube_Root(Val : Scale_Type) return Scale_Type is
     begin
         return Val ** (1.0/3.0);
     end Cube_Root;
end Ada.Units.Powers;

with Ada.Long_Float_Text_IO; -- implementation-dependent choice
with Ada.Text_IO;
package body Ada.Units.System_Of_Units is

     package body Unitless is
         function Val(Mag : Scale_Type) return Value is
         begin
             return Value(Mag);
         end Val;

         function Mag(Val : Value) return Scale_Type is
         begin
             return Scale_Type(Val);
         end Mag;
     end Unitless;

     package body Private_Numeric is
         -- Define multiplicative operators that combine with the unitless type.
         -- Be careful not to recurse infinitely
         -- No scaling is necessary

         use type Unitless.Value;

         function "*"(Left : Value; Right : Unitless.Value)
           return Value is
         begin
             return Value(Unitless.Value(Left) * Right);
         end "*";

         function "*"(Left : Unitless.Value; Right : Value)
           return Value is
         begin
             return Value(Left * Unitless.Value(Right));
         end "*";

         function "/"(Left : Value; Right : Unitless.Value)
           return Value is
         begin
             return Value(Unitless.Value(Left) / Right);
         end "/";

         function "/"(Left : Value; Right : Value)
           return Unitless.Value is
         begin
             return Unitless.Value(Left) / Unitless.Value(Right);
         end "/";

         function Val(Mag : Scale_Type) return Value is
         begin
             return Value(Mag);
         end Val;

         function Mag(Val : Value) return Scale_Type is
         begin
             return Scale_Type(Val);
         end Mag;
     end Private_Numeric;

     package body Scaling is
         -- Instantiate this to get scaling functions
         -- between units representing same physical dimensions
         -- but with different scale factors

         function Scale(From : Unit_A.Value) return Unit_B.Value is
         begin
             return Unit_B.Val(Unit_A.Scale_Factor / Unit_B.Scale_Factor *
               Unit_A.Mag(From));
         end Scale;

         function Scale(From : Unit_B.Value) return Unit_A.Value is
         begin
             return Unit_A.Val(Unit_B.Scale_Factor / Unit_A.Scale_Factor *
               Unit_B.Mag(From));
         end Scale;

     end Scaling;

     package body Scaled_Unit is
         -- Define the appropriate additive operators
         -- NOTE: These all return Base_Unit.Value to avoid
         -- ambiguity in complicated expressions.

         use type Base_Unit.Value;

         function "+"(Left : Base_Unit.Value; Right : Scaled_Unit.Value)
           return Base_Unit.Value is
         begin
             return Base_Unit.Val(Base_Unit.Mag(Left) +
               Base_Unit.Mag(Scale(Right)));
         end "+";

         function "+"(Left : Scaled_Unit.Value; Right : Base_Unit.Value)
           return Base_Unit.Value is
         begin
             return Right + Left;
         end "+";

         function "-"(Left : Base_Unit.Value; Right : Scaled_Unit.Value)
           return Base_Unit.Value is
         begin
             return Base_Unit.Val(
               Base_Unit.Mag(Left) - Base_Unit.Mag(Scale(Right)));
         end "-";
         function "-"(Left : Scaled_Unit.Value; Right : Base_Unit.Value)
           return Base_Unit.Value is
         begin
             return Base_Unit.Val(
               Base_Unit.Mag(Scale(Left)) - Base_Unit.Mag(Right));
         end "-";
         function "-"(Right : Scaled_Unit.Value)
           return Base_Unit.Value is
         begin
             return Base_Unit.Val(- Base_Unit.Mag(Scale(Right)));
         end "-";

     end Scaled_Unit;

     package body Multiplicative_Operators is
         -- Scaling is performed automatically.

         Combined_Scale_Factor : constant Scale_Type :=
           Unit_A.Scale_Factor * Unit_B.Scale_Factor / Unit_C.Scale_Factor;
         Inverse_Combined_Scale_Factor : constant Scale_Type :=
           Unit_C.Scale_Factor / (Unit_A.Scale_Factor * Unit_B.Scale_Factor);

         function "*"(Left : Unit_A.Value; Right : Unit_B.Value)
           return Unit_C.Value is
         begin
             return Unit_C.Val(Combined_Scale_Factor *
               Unit_A.Mag(Left) * Unit_B.Mag(Right));
         end "*";
         function "*"(Left : Unit_B.Value; Right : Unit_A.Value)
           return Unit_C.Value is
         begin
             return Unit_C.Val(Combined_Scale_Factor *
               Unit_B.Mag(Left) * Unit_A.Mag(Right));
         end "*";
         function "/"(Left : Unit_C.Value; Right : Unit_A.Value)
           return Unit_B.Value is
         begin
             return Unit_B.Val(Inverse_Combined_Scale_Factor *
               Unit_C.Mag(Left) / Unit_A.Mag(Right));
         end "/";
         function "/"(Left : Unit_C.Value; Right : Unit_B.Value)
           return Unit_A.Value is
         begin
             return Unit_A.Val(Inverse_Combined_Scale_Factor *
               Unit_C.Mag(Left) / Unit_B.Mag(Right));
         end "/";

     end Multiplicative_Operators;

     package body Squared_Unit is

         function "*"(Left : Base_Unit.Value; Right : Base_Unit.Value)
           return Squared_Unit.Value is
         begin
             return Squared_Unit.Val(
               Base_Unit.Mag(Left) * Base_Unit.Mag(Right));
         end "*";

         function "/"(Left : Squared_Unit.Value; Right : Base_Unit.Value)
           return Base_Unit.Value is
         begin
             return Base_Unit.Val(
               Squared_Unit.Mag(Left) / Base_Unit.Mag(Right));
         end "/";

         -- Declare squaring and square root operations
         function Square(Val : Base_Unit.Value) return Squared_Unit.Value is
         begin
             return Val * Val;
         end Square;

         function Sqrt(Val : Squared_Unit.Value) return Base_Unit.Value is
         begin
             return Base_Unit.Val(Powers.Sqrt(Squared_Unit.Mag(Val)));
         end Sqrt;

     end Squared_Unit;

     package body Cubed_Unit is
         -- Declare cubing and cube root operations
         function Cube(Val : Base_Unit.Value) return Cubed_Unit.Value is
         begin
             return Cubed_Unit.Val(Base_Unit.Mag(Val) ** 3);
         end Cube;

         function Cube_Root(Val : Cubed_Unit.Value) return Base_Unit.Value is
             use Powers; -- for "**" on Scale_Type
         begin
             -- Raise to 1/3 power.
             return Base_Unit.Val(Cubed_Unit.Mag(Val) ** (1.0/3.0));
         end Cube_Root;

     end Cubed_Unit;

     package body Square_Root_Unit is
         -- Declare multiplicative operators
         function "*"(Left : Square_Root_Unit.Value;
           Right : Square_Root_Unit.Value) return Base_Unit.Value is
         begin
             return Base_Unit.Val(
               Square_Root_Unit.Mag(Left) * Square_Root_Unit.Mag(Right));
         end "*";

         function "/"(Left : Base_Unit.Value; Right : Square_Root_Unit.Value)
           return Square_Root_Unit.Value is
         begin
             return Square_Root_Unit.Val(
               Base_Unit.Mag(Left) / Square_Root_Unit.Mag(Right));
         end "/";

         -- Declare squaring and square root operations
         function Square(Val : Square_Root_Unit.Value) return Base_Unit.Value is
         begin
             return Val * Val;
         end Square;

         function Sqrt(Val : Base_Unit.Value) return Square_Root_Unit.Value is
         begin
             return Square_Root_Unit.Val(Powers.Sqrt(Base_Unit.Mag(Val)));
         end Sqrt;
     end Square_Root_Unit;

     package body Arbitrary_Power_Unit is
         -- Declare appropriate exponentiation operations
         function Exponentiate_By_Power(Val : Base_Unit.Value)
           return Arbitrary_Power_Unit.Value is
         begin
             return Arbitrary_Power_Unit.Val(
               Base_Unit.Mag(Val) ** Power);
         end Exponentiate_By_Power;

         function Exponentiate_By_Inverse_Power(
           Val : Arbitrary_Power_Unit.Value) return Base_Unit.Value is
         begin
             return Base_Unit.Val(
               Arbitrary_Power_Unit.Mag(Val) ** (1.0/Power));
         end Exponentiate_By_Inverse_Power;

     end Arbitrary_Power_Unit;

     -- Some compilers can't deal with this as a generic child
     package body Text_Output is

         subtype IO_Type is Long_Float;  -- implementation-dependent choice
         package Float_IO renames Ada.Long_Float_Text_IO;
                    -- implementation-dependent choice

         function Name(Is_One : Boolean) return String is
           -- Return Singular or Plural, depending on
           -- whether Val = 1.0 (i.e. Is_One true)
         begin
             if Is_One then
                 return Singular;
             else
                 return Plural;
             end if;
         end Name;

         procedure Put(Val : in Unit_For_Output.Value;
           Fore : in Ada.Text_IO.Field := Default_Fore;
           Aft : in Ada.Text_IO.Field := Default_Aft;
           Exp : in Ada.Text_IO.Field := Default_Exp) is
             IO_Val : constant IO_Type := IO_Type(Unit_For_Output.Mag(Val));
         begin
             Float_IO.Put(IO_Val,
               Fore => Fore, Aft => Aft, Exp => Exp);
             Ada.Text_IO.Put(' ' & Name(Is_One => IO_Val = 1.0));
         end Put;

         procedure Put(File : in Ada.Text_IO.File_Type;
           Val : in Unit_For_Output.Value;
           Fore : in Ada.Text_IO.Field := Default_Fore;
           Aft : in Ada.Text_IO.Field := Default_Aft;
           Exp : in Ada.Text_IO.Field := Default_Exp) is
             IO_Val : constant IO_Type := IO_Type(Unit_For_Output.Mag(Val));
         begin
             Float_IO.Put(File, IO_Val,
               Fore => Fore, Aft => Aft, Exp => Exp);
             Ada.Text_IO.Put(File, ' ' & Name(Is_One => IO_Val = 1.0));
         end Put;

         function Image(Val : Unit_For_Output.Value;
           Fore : Ada.Text_IO.Field := Default_Fore;
           Aft : Ada.Text_IO.Field := Default_Aft;
           Exp : Ada.Text_IO.Field := Default_Exp) return String is

             IO_Val : constant IO_Type := IO_Type(Unit_For_Output.Mag(Val));
             Extra_Digits_Before_Decimal : constant := 30;
               -- This is extra room allowed in the Result string
               -- declared below.
               -- TBD: The value "30" allows for the case when EXP
               -- is zero.  The value 30 is pretty arbitrary but
               -- should be more than sufficient.

             Result : String(1 .. Fore + Aft + Exp + 2 +
               Extra_Digits_Before_Decimal);
         begin
             Float_IO.Put(Result, IO_Val,
               Aft => Aft, Exp => Exp);
             for I in Result'Range loop
                 if Result(I) /= ' ' then
                     return Result(I..Result'Last) & ' ' &
                       Name(Is_One => IO_Val = 1.0);
                 end if;
             end loop;
             return "??";  -- Should never happen
         end Image;

     end Text_Output;

end Ada.Units.System_Of_Units;

****************************************************************

From: Pascal Leroy
Sent: Wednesday, February 5, 2003  7:44 AM

> - The scaling prefixes used now conform to
>    the SI standard, except for places where they require
>    characters outside of the ISO 646 7-bit set (e.g. "u"
>    rather than "<greek mu>").  The prefixes can be
>    overridden via the Localization mechanism (see below).

I know it's nitpicking, but I am going to object to any AI referencing ISO 646,
an obsolete, English-centric character set.  ISO 8859-1 is a perfectly good
character set, which is supported by all computer systems that I know of, and
it has all the characters you need to properly deal with the SI system of units.

Is there a smiley for French bad temper?

****************************************************************

From: Tucker Taft
Sent: Wednesday, February 5, 2003 11:06 AM

That's fine with me.  I don't really know whether
all my local editing tools and such will deal reliably
with the full ISO 8859-1 set.  I am still using "vi"
remember... ;-)  But I presume someone on the ARG
can make sure mu and omega end up looking correct,
if we go with them.

****************************************************************

From: Christoph Grein
Sent: Wednesday, February 5, 2003 11:12 PM

Chill out, Pascal.

> I know it's nitpicking, but I am going to object to any AI referencing ISO 646,
> an obsolete, English-centric character set.  ISO 8859-1 is a perfectly good
> character set, which is supported by all computer systems that I know of, and it
> has all the characters you need to properly deal with the SI system of units.

Latin_1.Micro_Sign = 'æ' (Character'Val (181), but there is no capital Greek
Omega needed for Ohm.

****************************************************************

From: Pascal Leroy
Sent: Thursday, February 6, 2003  2:31 AM

That's a good point, so you'd have to stick to "ohm" when using type String.

But then this leads me to suggest that it would be good to have a
Wide_String variant (or, probably more appropriately, to pass the string
type as a generic parameter in various places).

****************************************************************

From: Christoph Grein
Sent: Thursday, February 6, 2003  2:36 AM

> That's a good point, so you'd have to stick to "ohm" when using type String.
>
> But then this leads me to suggest that it would be good to have a
> Wide_String variant (or, probably more appropriately, to pass the string

perhaps

> type as a generic parameter in various places).

No, I think it's already complicated enough. Having 'æ' and 'u' for micro and
"Ohm" or "ohm" (I'd prefer the capitalised form "Ohm") instead of capital Omega
is OK for me.

So leave it as simple as possible (but not simpler).

****************************************************************

From: Jeffery Carter
Sent: Wednesday, February 5, 2003 12:01 PM

I never saw the message that started this thread. Is this a problem on
my end, or have others had similar results, indicating something with
the list server?

I haven't seen any responses to my recent post with revised data
structure packages. This may be because (in increasing order of
probability):

* No one received the message
* I didn't receive the responses
* No one felt it worth commenting on
Tucker has clearly done a lot of work on this. I would like to thank him
for this, but can't resist mentioning a couple of nits.

Tucker Taft wrote:
>     generic
>         Name : in String;
>         Exponents : in Exponent_Array;
>         Scale_Factor : in Scale_Type := 1.0;
>         type Value is private;

Put Scale_Factor here so positional notation can be used and still
accept all the defaulted parameters with their defaults.

>         with function Val(Mag : Scale_Type) return Value is <>;
>         with function Mag(Val : Value) return Scale_Type is <>;
>     package Unit_Signature is end Unit_Signature;

This looks odd to me. I suppose I'll get used to it if it's used in the
standard. I'd prefer

package Unit_Signature is
    -- null;
end Unit_Signature;

This clearly shows me that the package spec is deliberately empty.

Off_Topic : begin

As a general comment about language design (which I am very well
unqualified to make) I would have preferred it if the concept applied to
sequences of statements, that if they are empty they must contain a null
statement to show that they are deliberately empty, were extended to
other parts of the language that can contain statements but may be
empty. A declarative region, for example, would have to contain a null
statement if it contains no declarations:

generic -- Sig package
    -- Whatever
package Sig is
    null;
end Sig;

Obviously this has no chance of being incorporated in Ada.

Thank you for putting up with my digression.

end Off_Topic;

****************************************************************

From: Christoph Grein
Sent: Friday, February 7, 2003  4:52 AM

Just a little missprint:

Symbol for pressure unit Pascal is Pa, see Ada.Units.SI_Units.Derived_Units.

****************************************************************

From: Christoph Grein
Sent: Monday, February 10, 2003  5:22 AM

I'm still not convinced but I like this more than the previous proposal.

1. Wrong dimension

The proposal leads to incorrect names for units is some cases.

     generic
         Name : in String;
     package Dimensionless_Unit is
         -- Instantiate this generic once for each
         -- distinct dimensionless base unit (e.g. radians),
         -- where multiplication and division of the unit
         -- with itself are well defined (and hence exponentiation makes
         -- sense).

That's plain wrong. Of course radian = m/m = 1, so it has no dimension.
But this unit is used to say that the value is an angle, and an angle
squared does not make sense nor an angle divided by another angle.

If you have sin (x^2), then x^2 is of dimension radian, not x.

Show me an equation where you find an angle squared. You won't find one.

This is the same mistake as denoting a frequency with Becquerel.
Hz and Bq are both 1/s, but they may not be used arbitrarily.

A unit multiplied by a number may require a different unit, although the
dimension remains the same: Angular frequencies are not measured in Hz.

   f = 50 Hz, then omega = 2 pi f = 314/s  -- Hz is wrong for omega

Torque is measured in Newton*Meter, not Joule. Rotational work equation
is similar to W = F * d => W = T * phi

   [W] = J, [F] = N, [d] = m, [T] = N * m, [phi] = rad

The proposal forces one to use Joule instead of Newtonmeter. If you define
Newtonmeter as a separate unit, you'll get unresolvable ambiguities.

2. The definition of power units is really clever. My only point is that
Exponentiate_By_Power does not tell you anything:

   S = sigma * Exponentiate_By_Power (T) ??

You need an extra renaming after instantiation to make this make sense, e.g.:

   S = sigma * Power_4 (T)

3. This leads me to a very important point. I am persistent with disliking
the combinatorial explosion.

You have just defined the SI units. But that's not all you have to do - the
work proper has only just begun.

Who is going to define the operators for mixing all these units. You'll need
hundreds of instantiations of Multiplicative_Operators. Who is going to do
this? Will the poor user of this proposal have to do them? And will he or she
then have in every package using SI to add a context clause with hundreds of
packages?

Or do you intend to include them all in e.g. Ada.Units.Full_SI_Operators so
that there will be just one unit in a with and a use clause?

4. Polynomials cannot be defined.

  type Table is array (Natural range <>) of Item;

  function Polynomial (Coefficients: Table; X: Item) return Item is
    -- Use Horner's scheme.
    F: Item := (Value => 0.0,
                Unit  => Coefficients (Coefficients'Last).Unit / X.Unit);
  begin
    for I in reverse Coefficients'Range loop
      F := F * X + Coefficients (I);
    end loop;
    return F * X ** Coefficients'First;
  end Polynomial;

5. As much as I like the Name_Support for Product_Name, Quotient_Name,
Power_Name, I dislike the Localization with plurals. Units in SI do not
have plurals, show me the place at NIST where there are plurals.

Plurals are for natural language, and natural language support should be
off limits for Ada standard.

You may pronounce 5 Kilometers, but you write 5 km.

6. There is no Text Input. This would also be very difficult with this
proposal since there is no character in between the value and the unit
on output: 5 km.

How can you read this in? How do you discriminate between reading a
dimensionless value or a value with a unit? You need a character (other
than blank) in between.

I do think, proper Text_IO is far more important than Localization.

7. There is still no maths.

   Sin (5 dm, cycle => 1 m)

This is also more important than Localization.
--------------------------------------------------------------------------
I repeat my statement:

   Put the proposal on the net, make it public, and wait for the
   reaction. If the proposal finds support, you can later think
   about standardisation.

Just make an experiment and you'll experience combinatorial explosion:

Set up all operators you need to handle such simple equations as the
following (of course solved for any item involved and complete freedom
of the sequence of factors):

Pressure  p = rho g h

Buoyancy  F = rho g V = p A

Kepler    T^2 / a^3 = const

Newton    F = G m1 m2 / r^2

Centrif.  F = v^2 / r = r omega^2

There is no package for Kilogramm per Cubicmeter (Density rho)...

I'm sure you will need a lot more operators than you would think (only three
dimensions involved). Let me make a guess: You'll need about thirty
instantiations.

If you're going to define all combinations that might be needed for all
7 units, fine. I'm waiting. You can't let this do the user of Ada.Units.
I wouldn't do this, rather not use it.

Perhaps this proposal could be combined with Macks, a code generator
by Fraser Wilson for physical units I'm going to present in Toulouse.

****************************************************************

From: Tucker Taft
Sent: Monday, February 10, 2003  3:21 PM

Thank you again for your comments.  I am not a practicing
physicist or chemist, so I have only distant memories
of using these units from my college days.  Please have
patience with my mistakes ;-).

I have some further responses below...

>...
> If you have sin (x^2), then x^2 is of dimension radian, not x.
>
> Show me an equation where you find an angle squared. You won't find one.

I guess I considered the Taylor expansion of Sin and Cos
examples of equations that have various powers of angles, and
proceed to add them together.

But I can also see that in most other contexts, allowing
radians * radians => radians doesn't make sense.  I will
pass these comments on to Thom Brooke, as he was the one
who suggested the idea of Dimensionless units.  Perhaps
he had something else in mind.

...
> The proposal forces one to use Joule instead of Newtonmeter. If you define
> Newtonmeter as a separate unit, you'll get unresolvable ambiguities.

I think you will get the ambiguities only if you have
simultaneous "use" clauses in effect for Joules and Newton_Meters.


> 2. The definition of power units is really clever. My only point is that
> Exponentiate_By_Power does not tell you anything:
>
>    S = sigma * Exponentiate_By_Power (T) ??
>
> You need an extra renaming after instantiation to make this make sense, e.g.:
>
>    S = sigma * Power_4 (T)

The intent was that you would not "use" these packages,
only do a "use type" on the pkg.Value type.
The operations like Exponentiate_By_Power would always
be prefixed by the name of the unit, so hopefully
that would give a hint as to the power.  For example,
it isn't quite so mysterious if you see

     Meters_To_The_Fourth.Exponentiation_By_Power(metr)

But you are right, it is a bit mysterious, and the documentation
should suggest using a rename rather than a "use" clause.

> 3. This leads me to a very important point. I am persistent with disliking
> the combinatorial explosion.
>
> You have just defined the SI units. But that's not all you have to do - the
> work proper has only just begun.
>
> Who is going to define the operators for mixing all these units. You'll need
> hundreds of instantiations of Multiplicative_Operators. Who is going to do
> this? Will the poor user of this proposal have to do them? And will he or she
> then have in every package using SI to add a context clause with hundreds of
> packages?

My recommendation is that users would instantiate the
Multiplicative_Operators package themselves, and only as
necessary for their particular usage pattern. Lettings users
do their "own" instantiations is safe, because the units are checked
on each instantiation using the "Assert."

I agree that it is impractical to provide all the operations
that anyone could ever need.  But my expectation is that
in any given project, or certainly in any given package body,
a relatively small number of instantiations would be
necessary.

> Or do you intend to include them all in e.g. Ada.Units.Full_SI_Operators so
> that there will be just one unit in a with and a use clause?

No, I don't think that is practical.

...
> 5. As much as I like the Name_Support for Product_Name, Quotient_Name,
> Power_Name, I dislike the Localization with plurals. Units in SI do not
> have plurals, show me the place at NIST where there are plurals.

An important feature of the System_Of_Units generics is that
it can be used for "unit-like" purposes that have nothing
to do with chemistry or physics or SI.  I agree that the
preinstantiation for SI should avoid plurals, as they aren't
used there, and I believe because all are <= 3 in length,
no plurals will be generated.  However, I can also imagine
using System_Of_Units for other sorts of compile-time
checking, such as the distinction between bit counts,
byte counts, and word counts versus "pure" numbers.
In situations like these, plurals might be of more use.

> Plurals are for natural language, and natural language support should be
> off limits for Ada standard.
>
> You may pronounce 5 Kilometers, but you write 5 km.

I agree that for SI purposes, plurals are inappropriate.
But plenty of Ada output is intended to be more
"conversational" than that appropriate for scientific
calculations, and for these purposes, having control
over pluralization might be of some use.  It is also
easy to turn it off completely by setting the maximum-no-plurals
at Integer'Last.

> 6. There is no Text Input. This would also be very difficult with this
> proposal since there is no character in between the value and the unit
> on output: 5 km.
>
> How can you read this in? How do you discriminate between reading a
> dimensionless value or a value with a unit? You need a character (other
> than blank) in between.

I wasn't sure what were the requirements for text input.
If you can specify them, I am happy to turn the requirements into code.

> I do think, proper Text_IO is far more important than Localization.
>
> 7. There is still no maths.
>
>    Sin (5 dm, cycle => 1 m)
>
> This is also more important than Localization.

Again, having requirements for what would be useful
in this area would help.  My expertise is mostly
in using the features of the language to get more
compile-time, or instantiation-time, checking.

...
> If you're going to define all combinations that might be needed for all
> 7 units, fine. I'm waiting. You can't let this do the user of Ada.Units.
> I wouldn't do this, rather not use it.

I'm not sure I understand this comment, but I was
expecting users to do some number of instantiations
themselves.  The System_Of_Units generic and its
nested generics were designed to allow the user to
do safe instantiations relatively easily to match
the needs of a particular project or a particular
piece of code.  Since the instantiations themselves generate
little or no code, having several of them spread around
should not incur measurable overhead.  The SI_Units
preinstantiations would hopefully either be directly
useful, or useful as a model.

> Perhaps this proposal could be combined with Macks, a code generator
> by Fraser Wilson for physical units I'm going to present in Toulouse.

That would be interesting to investigate.

****************************************************************

From: Christoph Grein
Sent: Tuesday, February 11, 2003  12:32 AM

> Thank you again for your comments.  I am not a practicing
> physicist or chemist, so I have only distant memories
> of using these units from my college days.  Please have
> patience with my mistakes ;-).

No problem - it's just that what I'm after, try to practice physics with this
proposal and see how it works out. I'm full of doubt. Ask physicists in the Ada
community to use it on their problems at hand.

> I guess I considered the Taylor expansion of Sin and Cos
> examples of equations that have various powers of angles, and
> proceed to add them together.

For small x, sin x = x. But as an argument of sin, x may have the unit rad,
whereas the result is a pure number, no unit rad!

You see, dimensionless numbers have their quirks if you put a pseudo-dimension
on them.

Units in SI carry a connotation of what they measure, not only a dimension.

> > Torque is measured in Newton*Meter, not Joule. Rotational work equation
> > is similar to W = F * d => W = T * phi
> >
> >    [W] = J, [F] = N, [d] = m, [T] = N * m, [phi] = rad
> >
> > The proposal forces one to use Joule instead of Newtonmeter. If you define
> > Newtonmeter as a separate unit, you'll get unresolvable ambiguities.
>
> I think you will get the ambiguities only if you have
> simultaneous "use" clauses in effect for Joules and Newton_Meters.

But I would need them exactly then when I have such equations with torque and
work.

And do you really think it is practicable to select among the dozens or more use
clauses depending on the kind of equations you are going to handle?

> > 2. The definition of power units is really clever. My only point is that
> > Exponentiate_By_Power does not tell you anything:
> >
> >    S = sigma * Exponentiate_By_Power (T) ??
> >
> > You need an extra renaming after instantiation to make this make sense,
e.g.:
> >
> >    S = sigma * Power_4 (T)
>
> The intent was that you would not "use" these packages,
> only do a "use type" on the pkg.Value type.
> The operations like Exponentiate_By_Power would always
> be prefixed by the name of the unit, so hopefully
> that would give a hint as to the power.  For example,
> it isn't quite so mysterious if you see
>
>      Meters_To_The_Fourth.Exponentiation_By_Power(metr)

Oh no, please, that's a joke ? :-( That's just too much noise.

> But you are right, it is a bit mysterious, and the documentation
> should suggest using a rename rather than a "use" clause.
> >
> > 3. This leads me to a very important point. I am persistent with disliking
> > the combinatorial explosion.
> >
> > You have just defined the SI units. But that's not all you have to do - the
> > work proper has only just begun.
> >
> > Who is going to define the operators for mixing all these units. You'll need
> > hundreds of instantiations of Multiplicative_Operators. Who is going to do
> > this? Will the poor user of this proposal have to do them? And will he or
she
> > then have in every package using SI to add a context clause with hundreds of
> > packages?
>
> My recommendation is that users would instantiate the
> Multiplicative_Operators package themselves, and only as
> necessary for their particular usage pattern.  Lettings users
> do their "own" instantiations is safe, because the units are checked
> on each instantiation using the "Assert."

The last sentence may be true, but it is still impractical. This is my strongest
objection against this method.

You want to do physics and not fiddling with use clauses every now and then.

Oh, @!?, this does not compile - ah, I'm missing a use clause, but which one?
... Hm, better I rearrange the factors - @!?@!? now it again does not compile,
missing another use clause - oh no, @!?@!?!?@!, now it's ambiguous and I need to
qualify, or can I remove one of my dozen or so use clauses now?

Until there is a consolidated set of use clauses for a given problem domain,
this method will more impede than help you.

> I agree that it is impractical to provide all the operations
> that anyone could ever need.  But my expectation is that
> in any given project, or certainly in any given package body,
> a relatively small number of instantiations would be
> necessary.

What is small? Is 50 small? See the simple mechanical equations below.

> > 6. There is no Text Input. This would also be very difficult with this
> > proposal since there is no character in between the value and the unit
> > on output: 5 km.
> >
> > How can you read this in? How do you discriminate between reading a
> > dimensionless value or a value with a unit? You need a character (other
> > than blank) in between.
>
> I wasn't sure what were the requirements for text input.
> If you can specify them, I am happy to turn the
> requirements into code.

The requirements are simple, I think. What you print out, you should be able to
read in again, with full unit checking.

So reading a line like

   5.0 20.4 km/s 1.0e+6 ms 100.0 50.0 N

should be possible. But this is quite impossible. The following is better:

   5.0 20.4*km/s 1.0e+6*ms 100.0 50.0*N

You read a number, a speed, a time, a number, a force.

> > I do think, proper Text_IO is far more important than Localization.
> >
> > 7. There is still no maths.
> >
> >    Sin (5 dm, cycle => 1 m)
> >
> > This is also more important than Localization.
>
> Again, having requirements for what would be useful
> in this area would help.  My expertise is mostly
> in using the features of the language to get more
> compile-time, or instantiation-time, checking.

All math functions with dimensioned arguments (dim /= 1) are nonsense with the
exception of rational powers and trigonometric functions and their inverses with
a cycle parameter.

...
> > If you're going to define all combinations that might be needed for all
> > 7 units, fine. I'm waiting. You can't let this do the user of Ada.Units.
> > I wouldn't do this, rather not use it.
>
> I'm not sure I understand this comment, but I was
> expecting users to do some number of instantiations
> themselves.

See above. A method should not introduce noise into the equations, or they will
induce errors without affecting the dimensions. If you have to write something
like

   4.5 * Meters_To_The_Fourth.Exponentiation_By_Power(metr) *
         Another_long.expanded_name (PI * X)

you very easily overlook a dimensionless factor in all that noise. This is then
worse than calculating with no dimension checking at all:

   4.5 * Metr**4 * f (Pi * X)function Trig (x, cycle: Item) return
Dimensionless;

x and cycle must have the same dimension.

****************************************************************

From: Christoph Grein
Sent: Tuesday, February 11, 2003  4:10 AM

BTW: These SI prefixes (Kilo, Mega...) are, AFAIK, only allowed on SI units
(don't know whether they are allowed on øC) and some others for historical
reasons (e.g. eV, l, pc), but e.g. not on h, min.

What is their use with miles, yards etc? Have there ever been kiloyards or
milliinches?

****************************************************************

From: John Barnes
Sent: Tuesday, February 11, 2003 10:16 AM

Certainly not so far as I know. Nor with typesetting units
such as picas and points which are duodecimal.

****************************************************************

From: Tucker Taft
Sent: Tuesday, February 11, 2003  1:04 PM

According to the NIST website (http://physics.nist.gov/cuu/Units/)
prefixes are generally permitted on other units outside the "core"
set, and on degrees Centigrade.  However, prefixes are explicitly
discouraged on a few of the units, in particular h, min, ', '',
and degrees latitude/longitude.

> > What is their use with miles, yards etc? Have there ever been kiloyards or
> > milliinches?
>
> Certainly not so far as I know. Nor with typesetting units
> such as picas and points which are duodecimal.

They are used on other kinds of things, though.  I mentioned
bits and bytes.  Dollars and cents are another example, where
kilo, mega, and giga are sometimes used (e.g. kbits, M$, Gbytes).

Bits and bytes bring up a separate discussion, where the IEC has
standardized prefixes which represent 2**10, 2**20, etc. as opposed to
the approximately equal decimal values 1000, 10**6, etc.  I have
never seen them in use ("ki" for 1024, "Gi" for 2**30, etc.).
In any case, the SI prefixes seem to be spreading into other
areas of use, probably as their use with personal computer
performance characteristics has spread.

****************************************************************

From: Christoph Grein
Sent: Wednesday, February 12, 2003  5:04 AM

Nor have I, but I'm beginning to use them, and we all should do, because it
does make a difference:

    Does the milbus transfer 1Mbit/s or 1 Mibit/sec?

Pronunciation: Megabit vs. Mebibit, Kilobit vs. Kibibit ... the bi stands for
binary.

****************************************************************

From: Adam Beneschan
Sent: Tuesday, February 11, 2003  10:25 AM

> > I guess I considered the Taylor expansion of Sin and Cos
> > examples of equations that have various powers of angles, and
> > proceed to add them together.
>
> For small x, sin x = x.  But as an argument of sin, x may have the
> unit rad, whereas the result is a pure number, no unit rad!
>
> You see, dimensionless numbers have their quirks if you put a
> pseudo-dimension on them.

Radians are just special.  All the other units I can think of are
arbitrary; someone had to decide how big a meter or a gram or a second
would be, and there is no particular reason why choosing those
particular sizes for those units would be any better or worse than
choosing some other arbitrary size.  The size of a radian, however, is
not arbitrary---it's the angle such that the length of the arc of a
circle subtended by the angle is equal to the radius of the circle.
This makes it special mathematically; it's the reason why a value
measured in radians can be used in a Taylor expansion, while I don't
believe it would make any sense to use a value measured in meters or
joules or troy ounces or anything else in this manner.

****************************************************************

From: Christoph Grein
Sent: Wednesday, February 12, 2003  4:44 AM

Hi, I did not want to look too pessimistic, so I played a bit with

  p = rho g h .

So even with this litte example, I needed 10 further instantiations and already
lost a bit the orientation as to which units I can combine and which not because
of missing instantiations. Names became long and longer.

It was a tedious job, and on the way I was a bit confused because I had all
instantiations, yet it wouldn't compile, until I realised I missed a use clause.

So I'm still pessimistic. Do you really think you can leave all this to the poor
programmer?

Code below.

As to the problem with Joule and Newtonmeter. Perhaps a renming of package
Joule to Newton_Meter rather than a separate package would avoid the problems.
There is then the Name parameter problem.

Units do not only denote a dimension, they also show what is measured, so there
are different names for the same dimension. And rad has been introduced to solve
the problem that e.g. 5 might be misleading, but 5 rad tells you that this
denotes an angle, whereas alpha = 1/137 really is just a number.

So 5/s does not tell you whether it's a frequency or a circular frequency or a
decay rate, but 5 Hz definitely denotes a frequency, 5 rad/s denotes a circular
frequency, 5 Bq denotes a decay rate.

So perhaps it would be best to have only one package One_per_Second and handle
the different aspects by renamings. The Name parameter problem remains to be
solved - we need to be able to give alternative names.
--------------------------------------------------------------------
with Ada.Units.SI_Units.Derived_Units;
use  Ada.Units.SI_Units.Derived_Units, Ada.Units.SI_Units;

package Mechanics is

  package Meter_Squared_per_Second_Squared is
    new SI.Squared_Unit (Meter_Per_Second.Sig);

  package Kilogramm_per_Square_Meter is
    new SI.Quotient_Unit (Kilogram.Sig, Square_Meter.Sig);
  package Kilogramm_per_Cubic_Meter is
    new SI.Quotient_Unit (Kilogram.Sig, Cubic_Meter.Sig);

  package Pascal_per_Meter is
    new SI.Quotient_Unit (Pascal.Sig, Meter.Sig);

  package Kilogramm_per_Square_Meter_times_Meter_Per_Second_Squared is
    new SI.Multiplicative_Operators (Kilogramm_per_Square_Meter.Sig,
                                     Meter_Per_Second_Squared.Sig,
                                     Pascal.Sig);
  package Kilogramm_per_Cubic_Meter_times_Meter is
    new SI.Multiplicative_Operators (Kilogramm_per_Cubic_Meter.Sig,
                                     Meter.Sig,
                                     Kilogramm_per_Square_Meter.Sig);
  package Kilogramm_per_Cubic_Meter_times_Meter_Per_Second_Squared is
    new SI.Multiplicative_Operators (Kilogramm_per_Cubic_Meter.Sig,
                                     Meter_Per_Second_Squared.Sig,
                                     Pascal_per_Meter.Sig);
  package Pascal_per_Meter_times_Meter is
    new SI.Multiplicative_Operators (Pascal_per_Meter.Sig,
                                     Meter.Sig,
                                     Pascal.Sig);
  package Meter_per_Second_Squared_times_Meter is
    new SI.Multiplicative_Operators (Meter_per_Second_Squared.Sig,
                                     Meter.Sig,
                                     Meter_Squared_per_Second_Squared.Sig);
  package Meter_Squared_per_Second_Squared_times_Kilogramm_per_Cubic_Meter is
    new SI.Multiplicative_Operators (Meter_Squared_per_Second_Squared.Sig,
                                     Kilogramm_per_Cubic_Meter.Sig,
                                     Pascal.Sig);

end Mechanics;
with Ada.Units.SI_Units.Derived_Units;
use  Ada.Units.SI_Units.Derived_Units, Ada.Units.SI_Units;
with Mechanics;
use  Mechanics;

procedure Do_Mechanics is

  use Kilogramm_per_Cubic_Meter_times_Meter,
      Kilogramm_per_Cubic_Meter_times_Meter_Per_Second_Squared,
      Kilogramm_per_Square_Meter_times_Meter_Per_Second_Squared,
      Pascal_per_Meter_times_Meter,
      Meter_per_Second_Squared_times_Meter,
      Meter_Squared_per_Second_Squared_times_Kilogramm_per_Cubic_Meter;

  Gravity: constant Meter_Per_Second_Squared.Value
             := Meter_Per_Second_Squared.Val (8.81);

  Rho   : Kilogramm_per_Cubic_Meter.Value :=
             Kilogramm_per_Cubic_Meter.Val (1000.0);
  Height: Meter.Value := Meter.Val (10.0);

  Pressure: Pascal.Value;

begin

  Pressure := Rho * Gravity * Height;
  Pressure := Gravity * Rho * Height;
  Pressure := Height * Rho * Gravity;
  Pressure := Rho * Height * Gravity;
  Pressure := Gravity * Height * Rho;
  Pressure := Height * Gravity * Rho;

end Do_Mechanics;

****************************************************************

From: Tucker Taft
Sent: Wednesday, February 12, 2003  2:03 PM

...
> So I'm still pessimistic. Do you really think you can leave all this to the
> poor programmer?

Well, I guess I wouldn't expect any "real" program to use all of these
combinations, at least not all in such close proximity.

But I may be wrong.  Do you have some examples of "real" code where
one might test this hypothesis?

I might also suggest a paradigm where the instantiations of the
SI.Multiplicative_Operators generic are done local to the point of use,
followed immediately by the "use" clause.  E.g.:

    package Pascal_Ops1 is new SI.Multiplicative_Operators(
      Kilogramm_Per_Square_Meter.Sig, Meter_Per_Second_Squared.Sig, Pascal.Sig);
    use Pascal_Ops1;

This means that the name of the instantiation is less important,
and what you are effectively doing is a parameterized "use" clause,
in effect "use SI.Multiplicative_Operators(Unit1.sig, Unit2.sig, Unit3.sig);".

> Code below.
>
> As to the problem with Joule and Newtonmeter. Perhaps a renming of package
> Joule to Newton_Meter rather than a separate package would avoid the problems.
> There is then the Name parameter problem.

The "Name" can be supplied on instantiation of the Text_Output package
as well (actually "Singular" and "Plural" are separate parameters),
so even if you had only one instantiation of the Unit package
for the two distinct units, you could have more than one instantiation of
the Text_Output package, each with an appropriate Singular/Plural specified.

By the way, you have convinced me about dropping all the pluralization stuff.
The next version won't have anything remaining of that, so the Text_Output
generic will take just a "Name" parameter, defaulted to the name of the unit
passed in.

> Units do not only denote a dimension, they also show what is measured, so there
> are different names for the same dimension. And rad has been introduced to solve
> the problem that e.g. 5 might be misleading, but 5 rad tells you that this
> denotes an angle, whereas alpha = 1/137 really is just a number.
>
> So 5/s does not tell you whether it's a frequency or a circular frequency or a
> decay rate, but 5 Hz definitely denotes a frequency, 5 rad/s denotes a circular
> frequency, 5 Bq denotes a decay rate.
>
> So perhaps it would be best to have only one package One_per_Second and handle
> the different aspects by renamings. The Name parameter problem remains to be
> solved - we need to be able to give alternative names.

As mentioned above, the "name" is mostly relevant on input/output.
So long as you can specify a name string at each instantiation of the Text_Output
package, I would think that would be adequate.

****************************************************************

From: Christoph Grein
Sent: Thursday, February 13, 2003 12:26 AM

> Well, I guess I wouldn't expect any "real" program to use all of these
> combinations, at least not all in such close proximity.

But that is exactly my point: It is a nuisance in every instance to check which
operators are needed and to write exactly the required with and use clauses.
What we need is a simple to use package, not one that urges us to fiddle with
context clauses.

This is doing the work twice (or even thrice): The SRS writer has probably
checked the equation. Now I'm evaluating the operators to see which context
clauses I need, i.e. I'm checking the dimensions again - and then the compiler
checks them a third time.

> But I may be wrong.  Do you have some examples of "real" code where
> one might test this hypothesis?

This is exactly my other point. Feed this to the lions around doing physics and
see how they digest it. After this experience, go to standardise it (this will
then be Ada1Z :-)

I personally do not have such code to try out. Our project is avionics, and
there the physics is so simple that it isn't worth the effort (the complicated
parts are provided by other companies - equipment software). We have a
different method to handle units (this is the only method of the four I'm going
to present in Toulouse that has seen industrial use in several projects - at
least four I know of).

> I might also suggest a paradigm where the instantiations of the
> SI.Multiplicative_Operators generic are done local to the point of use,
> followed immediately by the "use" clause.  E.g.:
>
>     package Pascal_Ops1 is new SI.Multiplicative_Operators(
>       Kilogramm_Per_Square_Meter.Sig, Meter_Per_Second_Squared.Sig, Pascal.Sig);
>     use Pascal_Ops1;

This is even more annoying :-( When do I get to the real code? More and more am
I forced to lose my time with local instantiations.

> > As to the problem with Joule and Newtonmeter. Perhaps a renming of package
> > Joule to Newton_Meter rather than a separate package would avoid the
> > problems. There is then the Name parameter problem.
>
> The "Name" can be supplied on instantiation of the Text_Output package
> as well (actually "Singular" and "Plural" are separate parameters),
> so even if you had only one instantiation of the Unit package
> for the two distinct units, you could have more than one instantiation of
> the Text_Output package, each with an appropriate Singular/Plural specified.

Yes, I've noticed that, but I thought there could perhaps be a better solution.

I think we are (slowly) approximating a useful set of packages :-)

****************************************************************

From: Christoph Grein
Sent: Thursday, February 13, 2003  1:00 AM

> As mentioned above, the "name" is mostly relevant on input/output.
> So long as you can specify a name string at each instantiation of the
> Text_Output package, I would think that would be adequate.

I also think that's the way to go. Then we should define the "standard name" as
as generally as possible, i.e. not "Hz", but "1/s", and use the specific names
on the IO (note the "I") instantiations.

****************************************************************

From: Tucker Taft
Sent: Thursday, February 13, 2003  9:36 AM

Back to the subject of unit-ized Input.

Is the desired approach that Get checks to see if the unit name
is there, and if so, that it matches what is expected?
Or should Get allow the use of an arbitrary
SI prefix, like "k" or "c" so long as the base unit name matched,
and Get would automatically scale the value as necessary?

Also, should the unit name be optional or mandatory,
whether or not automatic scaling is provided?

I suppose the question comes up on output as well.
Should automatic scaling be provided by Put to keep the value
within some desired range (e.g. 0.5 .. 1000.0), or
should Put always use the unit specified in the instantiation,
with no scaling?

****************************************************************

From: Christoph Grein
Sent: Friday, February 14, 2003  1:19 AM

  generic
    with package Unit_For_Output is new Unit_Signature (<>);
    Name: in String := Unit_For_Output.Name;  -- called Singular in current spec
  package Text_IO is

    procedure Put (File: in Ada.Text_IO.File_Type;
                   Val : in Unit_For_Output.Value;
                   Fore: in Ada.Text_IO.Field := Default_Fore;
                   Aft : in Ada.Text_IO.Field := Default_Aft;
                   Exp : in Ada.Text_IO.Field := Default_Exp);
    -- Ouputs Val like Float_IO (with given Fore, Aft, Exp format), then
    -- adds the Name.
    -- Examples
    --    300.50*kg   50.0/ms   1.0*rad   5.0  (dimensionless)

There is a problem with this package: There is no check that Name is appropriate
for Unit_For_Output. If e.g. Unit_For_Output => Kilogramm and Name => "J", an
exception should be raised.

For Unit_For_Output => Kilogramm and Name => "g", an automatic scaling should be
applied.

As it stands, Name is just a string, and it's easy to fall into this trap. Ada
is generally free of such (albeit simple to detect) traps.

    procedure Get (File: in  Ada.Text_IO.File_Type;
                   Val : out Unit_For_Output.Value);
    -- Inputs Value like Float_IO, then, if a unit follows (next character
    -- one of *, or /), reads it (syntax to be defined, a missing unit is
    -- interpreted as 1), then checks whether it is commensurable with the
    -- given unit's signature. If it is, automatic scaling is done,
    -- else Data_Error is raised.
    -- Examples
    --   1.0       a unitless number
    --   1.0*rad   another unitless number
    --   1.0*g     if read for kg, 1.0E-3 will be result

A possible syntax for reading units could be:

    The dimension is read as a product of units. Reading stops if
    a unit is not followed by a '*' or '/', in any case at the end of
    the line.
    Each unit factor is read as follows:
    Characters are input only so long as the sequence input is an
    initial sequence of a literal having the syntax of a unit factor
    (in particular, input ceases when a line terminator is encounter-
    ed). The character or line terminator that causes input to cease
    remains available for subsequent input. [These two sentences mimic
    the behaviour for enumeration literals in RM A.10.6(5).]
    The exception Data_Error is propagated if the sequence input does
    not have the required syntax, or if the characters input for the
    unit symbol do not form an existing symbol.

It would be nice if there were a way to read any dimensioned value (without
previous knowledge of the dimension that will be read) and return the proper
type. I do not see how this could be done with this proposal.

****************************************************************

From: Christoph Grein
Sent: Friday, February 14, 2003  6:16 AM

>     Characters are input only so long as the sequence input is an
>     initial sequence of a literal having the syntax of a unit factor

To define the syntax for a unit factor name, we could perhaps add to
Name_Support.Localization a component holding the set of legal characters in a
name. For SI this would be like an Ada identifier except '_': 'a'..'z',
'A'..'Z'.

For cosmology or astronomy, one could also allow the underline, so that a unit
name could e.g. be "Sun_Mass" and an output would look like 4.0E+6*Sun_Mass or
4.0*MSun_Mass, i.e. 4 Million Sun Masses for the mass of a big black hole.

Each (simple) name would then have to consist of letters in this set or else an
exception Name_Support.Name_Error would be raised.

****************************************************************

From: Tucker Taft
Sent: Friday, February 14, 2003  9:45 AM

...
>     procedure Put (File: in Ada.Text_IO.File_Type;
>                    Val : in Unit_For_Output.Value;
>                    Fore: in Ada.Text_IO.Field := Default_Fore;
>                    Aft : in Ada.Text_IO.Field := Default_Aft;
>                    Exp : in Ada.Text_IO.Field := Default_Exp);
>     -- Ouputs Val like Float_IO (with given Fore, Aft, Exp format), then
>     -- adds the Name.
>     -- Examples
>     --    300.50*kg   50.0/ms   1.0*rad   5.0  (dimensionless)

I am now using the "Middle_Dot" character by default, rather than "*",
for product units, so we might want to use that here as well.  Alternatively,
why not just use one space?  That seems to be what the SI style
guide recommends.  It is no particular problem to look ahead
across a space to see if there is a unit name following.

>
> There is a problem with this package: There is no check that Name is appropriate
> for Unit_For_Output. If e.g. Unit_For_Output => Kilogramm and Name => "J", an
> exception should be raised.
>
> For Unit_For_Output => Kilogramm and Name => "g", an automatic scaling should be
> applied.
>
> As it stands, Name is just a string, and it's easy to fall into this trap. Ada
> is generally free of such (albeit simple to detect) traps.

I can't imagine quite how this check would work, presuming that there
might be non-SI uses for the package.  I suppose we could build up a
table of all instantiations of _Unit generics for a given instantiation of System_Of_Units,
and make sure that if the Name string passed in corresponds to some instantiation of
a _Unit package, then that instantiation's exponent array matches that of the
instantiation passed as the formal package parameter.  It's not clear
this sort of check is worth it.  Probably simpler would be to take
a second instantiation rather than a Name string, and the Name associated with
that instantiation would be used for output, even though the type would be from
the first instantiation.

Alternatively, we keep it simple, encourage people to allow the Name string
to default, and then call Scale (or unary "+") if you want to pass a value
of a different unit but with the same dimension exponents.

>     procedure Get (File: in  Ada.Text_IO.File_Type;
>                    Val : out Unit_For_Output.Value);
>     -- Inputs Value like Float_IO, then, if a unit follows (next character
>     -- one of *, or /), reads it (syntax to be defined, a missing unit is
>     -- interpreted as 1), then checks whether it is commensurable with the
>     -- given unit's signature. If it is, automatic scaling is done,
>     -- else Data_Error is raised.
>     -- Examples
>     --   1.0       a unitless number
>     --   1.0*rad   another unitless number
>     --   1.0*g     if read for kg, 1.0E-3 will be result

Again, I would think we just allow/require a trailing unit name with one
space separating it from the number, rather than using "*" or middle dot.

> A possible syntax for reading units could be:
>
>     The dimension is read as a product of units. Reading stops if
>     a unit is not followed by a '*' or '/', in any case at the end of
>     the line.
>     Each unit factor is read as follows:
>     Characters are input only so long as the sequence input is an
>     initial sequence of a literal having the syntax of a unit factor
>     (in particular, input ceases when a line terminator is encounter-
>     ed). The character or line terminator that causes input to cease
>     remains available for subsequent input. [These two sentences mimic
>     the behaviour for enumeration literals in RM A.10.6(5).]
>     The exception Data_Error is propagated if the sequence input does
>     not have the required syntax, or if the characters input for the
>     unit symbol do not form an existing symbol.
>
> It would be nice if there were a way to read any dimensioned value (without
> previous knowledge of the dimension that will be read) and return the proper
> type. I do not see how this could be done with this proposal.

I can't imagine that you would be in a position where you would want
a number of unknown dimension.  I could see not caring whether you
get kg or g, but that seems to be a scaling thing.

Perhaps we should record with all instantiations of _Unit packages what
is the "base" unit name separately from the scaling prefix, and allow
any unit name that has the same base unit name, but potentially a different
scaling prefix, and scaling would be performed automatically.

In any case, as far as my original question, are you saying that the
unit name should be required, and automatic scaling should be performed?
The only possible exception might be for dimensionless values.

****************************************************************

From: Christoph Grein
Sent: Tuesday, February 18, 2003  3:43 AM

> >     procedure Put (File: in Ada.Text_IO.File_Type;
> >                    Val : in Unit_For_Output.Value;
> >                    Fore: in Ada.Text_IO.Field := Default_Fore;
> >                    Aft : in Ada.Text_IO.Field := Default_Aft;
> >                    Exp : in Ada.Text_IO.Field := Default_Exp);
> >     -- Ouputs Val like Float_IO (with given Fore, Aft, Exp format), then
> >     -- adds the Name.
> >     -- Examples
> >     --    300.50*kg   50.0/ms   1.0*rad   5.0  (dimensionless)
>
> I am now using the "Middle_Dot" character by default, rather than "*",
> for product units, so we might want to use that here as well.  Alternatively,
> why not just use one space?  That seems to be what the SI style
> guide recommends.  It is no particular problem to look ahead
> across a space to see if there is a unit name following.

But I believe it could pose a considerable problem to decide whether what is
following the space is indeed a unit or something else and accordingly has to
be consumed or not.

Assume you are expecting a mass in;ut and have read "5 ". Next you expect
unit "g" possibly prefixed by 'k' or some such.

Next character is indeed a 'g', but what you are actually reading is a string
like "5 goats". Where do you stop reading and what do you return? Do you
return "5 g" and "oats" left in the input stream or do you raise an exception?

It's much easier if you insist in a character being present. Then "5 goats"
is easy to distinguish from "5*g" or even the nonsense "5*goats".

If you don't like the '*' or middle-dot here, I'd vote for no character in
between like "5g".

****************************************************************

From: Stephen Leake
Sent: Tuesday, February 11, 2003 11:21 AM

> > Thank you again for your comments.  I am not a practicing
> > physicist or chemist, so I have only distant memories
> > of using these units from my college days.  Please have
> > patience with my mistakes ;-).
>
> No problem - it's just that what I'm after, try to practice physics
> with this proposal and see how it works out. I'm full of doubt. Ask
> physicists in the Ada community to use it on their problems at hand.

Ok, I'll bite. I do satellite simulations for NASA Goddard.

I've played with putting units into Ada in the past.

My main applications use Cartesian vectors, in meters, meters/sec,
etc. All normal vector operations must be supported; multiply by
scalar, dot and cross product, multiply by matrix, etc. No
compile-time units package comes close to doing that; it's
combinatoric in both the units themselves and the dimension of the
vector or matrix!

In my experience, a good test finds units problems very easily, so
it's a waste of time trying to get the compiler to do it.

> > My recommendation is that users would instantiate the
> > Multiplicative_Operators package themselves, and only as
> > necessary for their particular usage pattern.  Lettings users
> > do their "own" instantiations is safe, because the units are checked
> > on each instantiation using the "Assert."
>
> The last sentence may be true, but it is still impractical. This is
> my strongest objection against this method.

I agree with this; requiring users to figure out which generics to
instantiate and with is too high a cost for the gain of checked units.

In addition, if you are relying on a run-time Assert to enforce
safety, you might as well go whole-hog and use the attributes
approach. I have not closely examined Christoph's latest effort in
this area, but it sounds promising; use the run-time attributes
approach for full checking, but then make a small code change to do no
checking in a release version.

However, I currently think a better place to do units is in SPARK, or
some similar semantics checker, not at compile time or run time. It
should be simple to build an ASIS tool that uses structured comments
on variables and parameters to check units.

****************************************************************

From: Christoph Grein
Sent: Wednesday, February 19, 2003  3:11 AM

OK, this is just one other opinion, so it does not make a good statistic ...
but it exactly reflects mine.

> ...
> In my experience, a good test finds units problems very easily, so
> it's a waste of time trying to get the compiler to do it.

Exactly, and also code walk-thru's.

> > > My recommendation is that users would instantiate the
> > > Multiplicative_Operators package themselves, and only as
> > > necessary for their particular usage pattern.  Lettings users
> > > do their "own" instantiations is safe, because the units are checked
> > > on each instantiation using the "Assert."
> >
> > The last sentence may be true, but it is still impractical. This is
> > my strongest objection against this method.
>
> I agree with this; requiring users to figure out which generics to
> instantiate and with is too high a cost for the gain of checked units.

I also believe that the presence of any such method must be (nearly)
completely unperceptible as long as there are no dimension errors.

As I said in my first very message, the problmes in big software projects
are buried at other places, e.g. missing analysis before reuse (see Ariane 5),
incomplete interface documents that do not specify the units (see Mars Lander).
This method would not have prevented Mars Lander's failure.

****************************************************************


Questions? Ask the ACAA Technical Agent