CVS difference for ai05s/ai05-0144-2.txt

Differences between 1.8 and version 1.9
Log of other versions for file ai05s/ai05-0144-2.txt

--- ai05s/ai05-0144-2.txt	2010/05/04 03:44:13	1.8
+++ ai05s/ai05-0144-2.txt	2010/05/20 05:09:01	1.9
@@ -49,11 +49,11 @@
 
   * both names are dereferences (implicit or explicit), the
     dereferenced names are known to denote the same object,
-    and both names have the same immediately enclosing statement or
-    declaration; or
+    and both names have the same immediately enclosing complete context (see
+    8.6); or
 
-AARM Reason: We need the requirement to have the same enclosing statement in order
-to avoid problems with renames. Consider:
+AARM Reason: We need the requirement to have the same enclosing complete context
+in order to avoid problems with renames. Consider:
 
       type Ref is access Some_Type;
       Ptr : Ref := new Some_Type'(...);
@@ -68,36 +68,37 @@
 
   * both names are indexed_components, their prefixes are known
     to denote the same object, and each of the pairs of corresponding
-    index values are either static expressions with the same value
-    or names that are known to denote the same object; or
+    index values are known to have the same value; or
 
+AARM Discussion: "Statically known to have the same value" is defined below.
+The term is necessary to avoid problems with renames similar to the dereference
+example above.
+
   * both names are slices, their prefixes are known to denote the
     same object, and the two slices have statically matching
     index constraints; or
 
   * one of the two names statically denotes a renaming declaration
     whose renamed object_name is known to denote the same object
-    as the other name; or
+    as the other name.
 
 AARM Reason: This exposes known renamings of slices, indexing, and so on
 to this definition. In particular, if we have
    C : Character renames S(1);
 then C and S(1) are known to denote the same object.
 End AARM Reason.
-
-    * both names are known to denote the same object as a third name.
 
-AARM Reason: "Known to denote the same object" is intended to be an equivalence
-relationship, that is, it is reflexive, symmetric, and transitive. This last bullet
-is needed to make the relationship transitive. For instance, given the following
-declarations:
+AARM Ramification: "Known to denote the same object" is intended to be an equivalence
+relationship, that is, it is reflexive, symmetric, and transitive. We believe this
+follows for the rules. For instance, given the following declarations:
      S   : String(1..10);
      ONE : constant Natural := 1;
      R   : Character renames S(1);
 the names R and S(1) are known to denote the same object by the sixth bullet, and
-S(1) and S(ONE) are known to denote the same object by the fourth bullet, but we need
-the last bullet for R and S(ONE) to be known to denote the same object.
-END AARM Reason. 
+S(1) and S(ONE) are known to denote the same object by the fourth bullet, so using
+the sixth bullet on R and S(ONE), we simply have to test S(1) vs. S(ONE), which
+we already know denote the same object.
+END AARM Ramification.
 
 
     AARM Discussion: Whether or not names or prefixes are known to denote the
@@ -107,14 +108,71 @@
 
     These rules make no attempt to handle slices of objects that are known to be
     the same when the slices have dynamic bounds (other than the trivial case of
-    bounds being defined by the same subtype), even when the bounds could be proven to be the
-    same, as it is just too complex to get right and these rules are intended to be
-    conservative.
+    bounds being defined by the same subtype), even when the bounds could be
+    proven to be the same, as it is just too complex to get right and these
+    rules are intended to be conservative.
     End AARM Discussion.
 
-Two names are *known to refer to the same object* if the names
-are known to denote the same object, or if one of the two names is known to
-denote a subcomponent or slice of the object denoted by the others.
+Given two names or expressions of the same discrete type, one is
+*known to have the same value* as the other if
+
+  * both are static expressions and their values are the same; or
+
+  * both are names and the two names are known to denote the same object and
+    that object is a constant object; or
+
+AARM discussion: A dereference of an access-to-constant value denotes a constant
+view of a potentially variable object, not a constant object.
+
+  * both are names and the two names are known to denote the same object and
+    both names have the same immediately enclosing complete context (see 8.6);
+    or
+
+  * one of the two is a name which statically denotes a renaming declaration
+    whose renamed object_name is known to have the same value as the other
+    name or expression; or
+
+  * one of the two is a name which statically denotes a non-deferred constant
+    object whose initialization expression is known to have the same
+    value as the other name or expression; or
+
+  * one of the two is a parenthesized expression or qualified_expression
+    whose operand is known to have the same value as the other name
+    or expression.
+
+AARM Discussion: This is a slippery slope in that we could continue to add
+rules here until the cows come home [thanks to the Beatles for that phrase].
+For instance, we could imagine having "Both expressions are calls to the same
+predefined operator, and the corresponding operands of the expressions are
+statically known to have the same value." But the above captures all of the
+most likely cases.
+
+AARM To Be Honest: "Known to have the same value" doesn't guarantee
+that the value is the same in some obscure cases:
+* An intervening function call changes the value of an object included in one
+of the expressions;
+* One of the expressions includes a Volatile variable modified outside of the
+program;
+* One of the expressions includes a variable defined with an address clause
+(or similar features) and an intervening subprogram call modifies its location.
+These aren't a problem for this use; the first case is exactly what we are
+trying to detect (code that is not portable because it depends on the order
+of evaluation), and the others are unspeakably tricky if they are actually
+intended behavior. However, future authors of the standard should take care
+if they use this term in some other context.
+End AARM To Be Honest.
+
+Two names are *known to refer to the same object* if
+
+     The two names are known to denote the same object; or
+
+     One of the names is a selected_component, indexed_component,
+     or slice and its prefix is known to refer to the same object
+     as the other name; or
+
+     One of the two names statically denotes a renaming declaration
+     whose renamed object_name is known to refer to the same object
+     as the other name.
 
     AARM Reason: This ensures that names Prefix.Comp and Prefix are
     known to refer to the same object for the purposes of the
@@ -1311,5 +1369,584 @@
 preserve the overall safety level of Ada, as we add [IN] OUT parameters to
 functions.  In my view, there is nothing more important than preserving the
 overall safety level of Ada going forward.
+
+*****************************************************************
+
+A private back and forth between Steve Baird and Randy Brukardt
+regarding the wording for this AI: Apr 30-May 7, 2010:
+
+Steve:
+Oh dear, heat vision seems to have ignited something.
+
+Consider
+
+     type Ref is access Some_Type;
+     Ptr : Ref := new Some_Type'(...);
+     X : Some_Type renames Ptr.all;
+   begin
+     Ptr := new Some_Type'(...);
+     P (Func_With_Out_Params (Ptr.all, X));
+
+The addition of renames into the mix has introduced the possibility that two
+different evaluations of "P.all" may yield references to different objects.
+
+We could address this by adding something to the
+   "both names are dereferences"
+bullet along the lines of
+    "both have the same immediately enclosing statement or
+     declaration"
+.
+
+Even this isn't quite right because of short circuit evaluation of functions
+with side effects.
+
+I don't know; what do you think?
+
+Thinking about this some more, I'm not sure that there is an issue here. I think
+the "same enclosing blah-blah" rule might actually be good enough.
+
+Randy:
+OK, I'll add that (and your example in an AARM note to show what is meant).
+[Editor's Note: This was the state at the point of version /06. But then...]
+
+Steve:
+>      * both names are known to denote the same object as a third name.
+>
+> AARM Reason: "Known to denote the same object" is intended to be an
+> equivalence relationship, that is, it is symmetric, reflexive, and
+> transitive. This last bullet is needed to make the relationship transitive.
+
+I don't believe this new bullet is needed. I think it is redundant (and a note
+about transitivity might be appropriate).
+
+> For instance, given the following declarations:
+>
+>      S : String(1..10);
+>      ONE : constant Natural := 1;
+>      R : Character renames S(1);
+>
+> the names R and S(1) are known to denote the same object by the sixth
+> bullet, and S(1) and S(ONE) are known to denote the same object by the
+> fourth bullet, but we need the last bullet for R and
+> S(ONE) to be known to denote the same object.
+> END AARM Reason.
+
+As you pointed out, the names R and S(1) are known to denote the same object, as
+are S(1) and S(ONE),
+
+So reapplying the rename rule to the names R and S(ONE), we get the desired
+conclusion about those two names without any new bullet. Right?
+
+Randy:
+You might be right that recursive application will do the trick. It's hard to
+wrap ones mind around, that's for sure.
+
+In any case, we need to talk about this once we have rules that actually no
+longer have holes. The fix(es) could destroy this property.
+
+Steve:
+> Two names are *known to refer to the same object* if the names are
+> known to denote the same object, or if one of the two names is known
+> to denote a subcomponent or slice of the object denoted by the others.
+>
+> This is actually shorter.
+>
+Typo: "others" => "other".
+
+The "Known to denote the same object" relationship is a relation on names. When
+you talk about "known to denote a subcomponent of", I think you are implicitly
+conjuring up nonexistent names, as in
+
+     two names "are known to refer to the same object" if I could
+     conjure up zero or more additional selectors and tack them on
+     the end of one of the names in order to produce a name which
+     is known to denote the same object as the other name.
+
+I think I'd prefer something like
+
+   ... or if a prefix of one of the two names is known to denote
+   the same object as the other name.
+
+but then we need to worry about renames. Given
+
+     R : T renames X.Field;
+
+we'd like to say that the names R and X are known to refer to the same object,
+so we need something to get the effect of
+    "or if one of the names denotes a rename whose renamed
+     object_name is known to refer to the same object as the
+     other name"
+(this is not intended to be precise wording).
+
+Randy:
+
+> The "Known to denote the same object" relationship is a relation on
+> names. When you talk about "known to denote a subcomponent of", I
+> think you are implicitly conjuring up nonexistent names, as in
+>
+>      two names "are known to refer to the same object" if I could
+>      conjure up zero or more additional selectors and tack them on
+>      the end of one of the names in order to produce a name which
+>      is known to denote the same object as the other name.
+
+I suppose you can think of it that way. It doesn't sound good...
+
+> I think I'd prefer something like
+>
+>    ... or if a prefix of one of the two names is known to denote
+>    the same object as the other name.
+
+That's too broad. Prefixes are used in cases other than subcomponents and
+slices, such as attribute references and subprogram calls. If F is a function,
+we surely don't want
+    X and X.F
+to be known to refer to the same object. (Not to mention dereferences).
+
+It seems to me that handling this properly will get *really* messy.
+
+> but then we need to worry about renames. Given
+>
+>      R : T renames X.Field;
+>
+> we'd like to say that the names R and X are known to refer to the same
+> object, so we need something to get the effect of
+>     "or if one of the names denotes a rename whose renamed
+>      object_name is known to refer to the same object as the
+>      other name"
+> (this is not intended to be precise wording).
+
+Here being another reason this idea is nasty.
+
+Want to try again closer to the original wording?? The idea of "conjuring"
+selectors, indexes, or slices is a lot simpler, and it is obvious to the
+compiler what is needed (if anything).
+
+Steve:
+> Want to try again closer to the original wording?? The idea of "conjuring"
+> selectors, indexes, or slices is a lot simpler, and it is obvious to
+> the compiler what is needed (if anything).
+
+You are right that Prefix is too general an idea to use here.
+How about a more constrained, specific but still prefix-based approach?
+
+====
+
+Two names are known to refer to the same object if
+
+     The two names are known to denote the same object; or
+
+     One of the names is a selected_component, index_component,
+     or slice and its prefix is known to refer to the same object
+     as the other name; or
+
+     One of the two names statically denotes a renaming declaration
+     whose renamed object_name is known to refer to the same object
+     as the other name.
+
+====
+
+Randy:
+I said yesterday:
+
+> I was worried that indexed_components also would have a similar
+> problem to dereferences, but I think we're OK because renames is
+> essentially by-reference, and indexes have to be discrete. A constant
+> would be a problem, but since it is technically a different object, it
+> wouldn't hit under these rules.
+>
+>     S : String(1..10);
+>     I : Natural := 5;
+>     R : Natural renames I;
+>   begin
+>     I := 3;
+>     P (S(I), S(R)); -- OK, both I and R are 3 here.
+
+I wasn't clever enough yesterday. Try:
+
+    S : String(1..10);
+    I : Natural := 5;
+    R : Character renames S(I);
+  begin
+    I := 3;
+    P (S(I), R); -- !!!
+
+Here, the bullets we currently have make S(I) and R "known to denote the same
+object": but S(I) = S(3) and R = S(5)! Those can't possible denote the same
+object because they're different objects!
+
+Fixing this seems difficult; we could just drop the part about the indexes being
+known to denote the same object, but that is nasty because it means that S(I) is
+not known to denote the same object as S(I). (Which is going to allow a lot of
+errors through.)
+
+Else we have to add the same scope rule that you have for dereferences. That's
+also ugly.
+
+A final idea is to apply that scope rule more generally. That is, make the
+statically denotes bullet require the same scope of the reference. Then I think
+we wouldn't need that rule for dereferences or for indexed components.
+
+Note that some of these fixes endanger the sense of equivalence here.
+
+Steve:
+Good point. I tried making use of the "same evaluation" wording that is used in
+4.9.1 (the phrase is also used in 4.5.2, but that doesn't help because it is
+dynamic semantics).
+
+Let's try replacing
+
+   * both names are indexed_components, their prefixes are known
+     to denote the same object, and each of the pairs of corresponding
+     index values are either static expressions with the same value
+     or names that are known to denote the same object; or
+
+with
+
+   * both names are indexed_components, their prefixes are known
+     to denote the same object, and each of the pairs of corresponding
+     index values are statically known to have the same value.
+
+But of course, now we need something like
+
+    Two discrete expressions are statically known to have the same
+    value if
+       * they are static expressions with the same value; or
+       * both expressions are names and the two names are known
+         to denote the same constant object; or
+       * <both names denote constants and one of them provides the
+         initial value for the other, perhaps via other intervening
+         constants>
+
+Constructs to watch out for here include factored lists
+
+     X, Y : constant Integer := Function_Call;
+       -- X and Y should not be statically known to have the same value
+
+and constant views of non-constants
+
+      X : aliased Integer;
+
+      Y : constant access constant Integer := X'Access;
+
+      Z1 : constant Integer := Y.all;
+
+      X := X+1; -- somehow get this stmt into the decl list
+
+      Z2 : constant Integer := Y.all;
+      -- Z1 and Z2 should not be statically known to have the same value
+
+, but I think these cases fall out (I mention them because this is still up in
+the air, so we just want to remember to check that they are handled right).
+
+Does this seem like a reasonable approach (i.e., worth fleshing out the
+details)?
+
+Randy:
+Yes, but it doesn't handle the case that was the original motivation for
+including the same objects in the first place:
+
+     Swap (S(I), S(I));
+
+It wouldn't be very helpful if this case wasn't detected, especially as it
+represents a bug (either nothing is needed or S(J) was meant for the second
+parameter).
+
+I was wondering if there was a problem with the above having to do with
+functions with "in out" parameters, but I think those would be illegal by other
+checks. That is, if we have
+
+    function Bump (I : in out Natural) return Natural is
+    begin
+        I := I + 1;
+        return I - 1;
+    end Bump;
+
+In:
+
+    P (S(I), Bump(I), S(I));
+
+We don't know if the two S(I)'s are the same object or not. But this is already
+illegal (I hope! It's the classic problem) so it is irrelevant.
+
+You could do something similar with side-effects, but since the results would
+not be portable, it's OK to reject the call (this is the same reason that we use
+to justify rejecting the explicit problem).
+
+So I think we would need a bullet similar to the one for dereferences.
+
+   * The expressions are both object_names, the names are known to denote the
+     same object, and both names have the same immediately enclosing statement
+     or declaration;
+
+Thoughts?
+
+Steve:
+> Yes, but it doesn't handle the case that was the original motivation
+> for including the same objects in the first place:
+>
+>      Swap (S(I), S(I));
+>
+
+Good point.
+
+>
+> So I think we would need a bullet similar to the one for dereferences.
+>
+>    * The expressions are both object_names, the names are known to
+> denote the same object, and both names have the same immediately
+> enclosing statement or declaration;
+>
+> Thoughts?
+
+Looks good.
+
+Would you want to relax the "same immediately enclosing" rule in the the case of
+a constant?
+
+The idea that you are trying to capture here is that the two evaluations of this
+name will yield the same value and that ought to be true for a constant
+regardless of where the two names occur (although it might not be true for a
+constant view of a variable; but down this road lies madness, or at least
+complexity. Do we really want to worry about the fact that a "constant"'s
+finalization can modify it?).
+
+Randy:
+Maybe, but I think it would have to be a real discrete constant (a stand-alone
+constant), rather than a constant component of a composite type (or a constant
+view of a variable), as those can change via other channels. Not sure it is
+worth the effort because of that limitation (and because if the constant is
+considered static, it is already covered anyway).
+
+You could conceive of handling expressions of predefined operators as well:
+   C : constant := 1;
+
+   Swap (S(I+1),S(I+C));
+
+* Both expressions are calls to the same predefined operator, and the
+  corresponding operands of the expressions are statically known to have the
+  same value.
+
+This of course can quickly become a slippery slope. (How about selected
+attributes? And on and on and on...)
+
+Steve:
+I think I like your approach of limiting this to top-level discrete constants,
+avoiding anything to do with composite or access types. Your exploration of the
+slippery slope associated with more general approaches has convinced me that we
+don't want to go there.
+
+Randy:
+OK. Please propose some wording (to be part of your editorial review, of course,
+and to be reviewed during our phone call on May 20).
+
+Steve:
+Do we now only need wording for this new "statically known to have the same
+value" (today, I think I prefer "statically known to be equal") relationship
+between two discrete expressions ?
+
+Randy:
+I think that is it. You had:
+
+   * both names are indexed_components, their prefixes are known
+     to denote the same object, and each of the pairs of corresponding
+     index values are statically known to have the same value.
+
+And that looks OK (modulo whatever term you choose). You also were trying to
+convince me that we don't need a transitivity rule. I'm still a bit dubious, but
+you might be right (I haven't been able to figure out a problem case yet,
+although it seems that finding the right intermediate name might be difficult in
+some cases).
+
+And then I believe you wanted to change the "refer to" definition:
+
+  Two names are known to refer to the same object if
+
+     The two names are known to denote the same object; or
+
+     One of the names is a selected_component, indexed_component,
+     or slice and its prefix is known to refer to the same object
+     as the other name; or
+
+     One of the two names statically denotes a renaming declaration
+     whose renamed object_name is known to refer to the same object
+     as the other name.
+
+I think this is OK as well.
+
+Steve:
+I don't remember if we talked about "enclosing statement or declaration" anywhere else, but it should probably be replaced with "immediately enclosing complete context" if we did (consider a pragma). I've made that replacement below.
+
+We need to be consistent with regard to "known" vs. "statically known"
+in defining these various new terms.
+I'm happy with whatever is consistent with existing wording.
+
+In the case of this new predicate (below), I realize that it is so far from being bulletproof that I don't like using the word "known"
+at all. Hence "very likely".
+
+I changed from "statically known" to "very likely" when I starting thinking about
+
+      if Function_With_In_Out_Params
+          (X(I), Function_Call_That_Modifies_I, X(I)) then
+
+or the various cases involving modification of constants (finalization routines, Current_Instance_Of_A_Limited_Type'Access, pragma Import).
+If we are really only talking about a 90% heuristic, then let's not pretend otherwise.
+
+What do you think?
+
+====
+
+    Given two names or expressions of the same discrete type, one is
+    *very likely to have the same value* as the other if
+
+      * both are static expressions and their values are the same; or
+
+      * both are names and the two names are statically
+        known to denote the same object and that object is
+        a constant object; or
+
+AARM note: A dereference of an access-to-constant value denotes a constant view
+of a potentially variable object, not a constant object.
+
+      * both are names and the two names are statically
+        known to denote the same object and both names have the same
+        immediately enclosing complete context (see 8.6); or
+
+     * one of the two is a name which statically denotes
+       a renaming declaration whose renamed object_name
+       is very likely to have the same value as the
+       other name name or expression; or
+
+     * one of the two is a name which statically denotes
+       a non-deferred constant object whose initialization expression
+       is very likely to have the same value as the other name
+       or expression.
+
+Randy:
+
+> We need to be consistent with regard to "known" vs. "statically known"
+> in defining these various new terms.
+> I'm happy with whatever is consistent with existing wording.
+
+I think we used "statically known" to make it clear that we are talking about
+compile time, not whether A(I) and A(J) are the same at runtime. I can't think
+of any existing wording off-hand other than that in this clause.
+
+> In the case of this new predicate (below), I realize that it is so far
+> from being bulletproof that I don't like using the word "known"
+> at all. Hence "very likely".
+>
+> I changed from "statically known" to "very likely" when I starting
+> thinking about
+>
+>       if Function_With_In_Out_Params
+>           (X(I), Function_Call_That_Modifies_I, X(I)) then
+>
+> or the various cases involving modification of constants (finalization
+> routines, Current_Instance_Of_A_Limited_Type'Access, pragma Import).
+> If we are really only talking about a 90% heuristic, then let's not
+> pretend otherwise.
+
+I think "very likely" is going to turn people *way* off. Moreover, it isn't that
+hard to close the vast majority of these loopholes: restrict the constant object
+case to elementary objects. That's what we did in 3.3(13/3), after all, for
+these very same reasons. Moreover, for the intended use, we really only care
+about elementary constants anyway. And I know I suggested that a few days ago.
+
+And I rationalized ignoring the "Function_Call_That_Modifies_I case" in a
+previous message. The use of these rules is to find cases where the undefined
+order-of-evaluation could cause differing/non-portable results. The above
+*surely* is such a case. Similarly, if some uses an address clause or something
+like that to modify values under the covers, they've got problems anyway: the
+code is insanely tricky. It's OK to blow them away. :-)
+
+So I think it is OK to call it "known", although we might want a AARM To Be
+Honest note that suggests care if someone ever tries to use this definition
+elsewhere, because it is not bulletproof (although it is in any reasonable
+program).
+
+...
+>      * one of the two is a name which statically denotes
+>        a non-deferred constant object whose initialization expression
+>        is very likely to have the same value as the other name
+>        or expression.
+
+I'd stick with "known", and add the requirement to be elementary in the two
+constant object rules. Otherwise, looks fine to me.
+
+Steve:
+
+> I think "very likely" is going to turn people *way* off.
+
+I agree, but only because it is an accurate description.
+If we called it "known", then people won't be turned off until they figure out
+that this is a case of false advertising. Still, I agree with you - when we
+start defining technical terms with names like "as near as I can tell", it does
+seem that we've taken a wrong turn somewhere.
+
+> Moreover, it isn't
+> that hard to close the vast majority of these loopholes: restrict the
+> constant object case to elementary objects.
+
+I think the wording I sent does that. In which case I shouldn't have mentioned
+finalization as one of the FUD-sources regarding the value of a constant; ditto
+for Rosen-tricks and the like. So you are right.
+
+> That's what we did in 3.3(13/3),
+> after all, for these very same reasons. Moreover, for the intended
+> use, we really only care about elementary constants anyway. And I know
+> I suggested that a few days ago.
+
+Repeating myself, I think I got the wording right with respect to this issue -
+it was just my color commentary that needed to be toned down.
+
+> And I rationalized ignoring the "Function_Call_That_Modifies_I case"
+> in a previous message. The use of these rules is to find cases where
+> the undefined order-of-evaluation could cause differing/non-portable results.
+> The above *surely* is such a case.
+
+> Similarly, if some uses an address clause or something like that to
+> modify values under the covers, they've got problems anyway: the code
+> is insanely tricky. It's OK to blow them away. :-)
+
+You're not too concerned about an imported constant, even if it is subject to a
+Volatile pragma? I guess I can live with that. Especially when a user can work
+around any problems in this area by adding a set of parens. If we reject
+
+     F (A(I), A(I));
+, I think we'll still accept
+     F (A ((I)), A(I));
+
+Ada is generally a very readable language, but when you wander off into the
+corner cases, it can get weird.
+
+> So I think it is OK to call it "known", although we might want a AARM
+> To Be Honest note that suggests care if someone ever tries to use this
+> definition elsewhere, because it is not bulletproof (although it is in
+> any reasonable program).
+
+Agreed.
+
+Randy:
+> You're not too concerned about an imported constant, even if it is
+> subject to a Volatile pragma? I guess I can live with that.
+
+Hadn't thought of that one. But of course B.1(38.1) sort of saves us: Ada semantics is that the value doesn't change. If it *does* change, the program is erroneous. And of course, the result is an error message that isn't accurate -- but the code is very 
tricky if they meant to depend on that, and if they didn't, well then they have a bug.
+
+> Especially when a user can work around any problems in this area by
+> adding a set of parens. If we reject
+>
+>      F (A(I), A(I));
+> , I think we'll still accept
+>      F (A ((I)), A(I));
+>
+> Ada is generally a very readable language, but when you wander off
+> into the corner cases, it can get weird.
+
+That seems like a bug, but it isn't worth trying to fix it. After all, the
+purpose of these rules was to make Tucker happy. He seems happy now, let's not
+disturb his slumber. ;-)
+
+[Editor's note: If you are still reading this at this point, you are at
+least as crazy as Steve and I. You deserve a libation of your choice. :-)]
 
 *****************************************************************

Questions? Ask the ACAA Technical Agent