[ HPF Home | Versions | Compilers | Projects | Publications | Applications | Benchmarks | Events | Contact ] |
Next: Data Parallel Statements
Up: Data Alignment and
Previous: INHERIT Directive
Mapping directives may be applied to dummy arguments in the same manner as for other variables; such directives may also appear in interface blocks. However, there are additional options that may be used only with dummy arguments: asterisks, indicating that a specification is descriptive rather than prescriptive, and the INHERIT attribute.
First, consider the rules for the caller. If there is an explicit interface for the called subprogram and that interface contains mapping directives (whether prescriptive or descriptive) for the dummy argument in question, the actual argument will be remapped if necessary to conform to the directives in the explicit interface. The template of the dummy will then be as declared in the interface. If there is no explicit interface, then actual arguments that are whole arrays or regular array sections may be remapped at the discretion of the language processor; the values of other expressions may be mapped in any manner at the discretion of the language processor.
In order to describe explicitly the distribution of a dummy argument, the template that is subject to distribution must be determined. A dummy argument always has a fresh template to which it is ultimately aligned; this template is constructed in one of three ways:
In all of these cases, we say that the dummy has an inherited template rather than a natural template.
Consider the following example:
LOGICAL FRUG(128),TWIST(128)
!HPF DISTRIBUTE (BLOCK) ONTO DANCE_FLOOR::FRUG,TWIST
CALL TERPSICHORE(FRUG(1:40:3),TWIST(1:40:3))
The two array sections FRUG(1:40:3) and TWIST(1:40:3)
are mapped onto abstract processors in the same manner:
However, the
subroutine TERPSICHORE will view them in different ways
because it inherits the template for the second dummy but not the first:
SUBROUTINE TERPSICHORE(FOXTROT,TANGO)
LOGICAL FOXTROT(:),TANGO(:)
!HPF DISTRIBUTE TANGO *(BLOCK)
but it would not be correct to declare
!HPF
PROCESSORS DANCE_FLOOR(16)
!HPF
ALIGN FOXTROT(J) WITH *GURF(3*J-2)
could be correctly included in TERPSICHORE to describe the
layout of FOXTROT on entry to the subroutine without using
an inherited template.
The simplest case is the use of the INHERIT attribute alone.
If a dummy argument has the INHERIT attribute and no explicit
ALIGN or DISTRIBUTE attribute, the net effect is
to tell the compiler to leave the data exactly where it is-and not
attempt to remap the actual argument. The dummy argument will
be mapped in exactly the same manner as the actual argument;
the subprogram must be compiled in such a way as to work correctly
no matter how the actual argument may be mapped onto abstract processors.
(It has this effect because an INHERIT attribute on a dummy D
implicitly specifies the default distribution
!HPF DISTRIBUTE URANIA (CYCLIC) ONTO GALILEO
The language processor should do whatever it takes to cause URANIA to
have a CYCLIC distribution on the processor arrangement GALILEO.
!HPF
DISTRIBUTE THALIA *(CYCLIC) ONTO FLIP
The language processor should do whatever it takes to cause THALIA to
have a CYCLIC distribution on the processor arrangement FLIP;
THALIA already has
a cyclic distribution, though it might be on some other processor arrangement.
!HPF
DISTRIBUTE MELPOMENE * ONTO *EURIPIDES
MELPOMENE is asserted to already be distributed
onto EURIPIDES; use whatever distribution format the actual argument had
so, if possible, no data movement should occur.
(You can't say this in Subset HPF.)
!HPF
DISTRIBUTE EUTERPE (CYCLIC) ONTO *
The language processor should do whatever it takes to cause EUTERPE to
have a CYCLIC distribution onto whatever processor arrangement
the actual was distributed onto. (You can't say this in Subset HPF.)
!HPF
DISTRIBUTE ARTHUR_MURRAY *(CYCLIC) ONTO *
ARTHUR_MURRAY is asserted to already be distributed CYCLIC
onto whatever processor arrangement the actual argument was distributed
onto, and no data movement should occur.
(You can't say this in Subset HPF.)
Please note that DISTRIBUTE ERATO * ONTO * does not mean
the same thing as
!HPF DISTRIBUTE WHEEL_OF_FORTUNE *(CYCLIC)
WHEEL_OF_FORTUNE is asserted to already be CYCLIC.
As long as it is kept CYCLIC, it may be remapped it onto some
other processor arrangement, but there is no reason to.
!HPF
DISTRIBUTE DAVID_LETTERMAN ONTO *TV !Nonconforming
does not conform to the syntax for a DISTRIBUTE directive.)
The asterisk convention allows the programmer to make claims about the pre-existing distribution of a dummy based on knowledge of the mapping of the actual argument. But what claims may the programmer correctly make?
If the dummy argument has an inherited template, then the subprogram may contain directives corresponding to the directives describing the actual argument. Sometimes it is necessary, as an alternative, to introduce an explicit named template (using a TEMPLATE directive) rather than inheriting a template; an example of this (GURF) appears above, near the beginning of this section.
If the dummy argument has a natural template (no INHERIT attribute) then things are more complicated. In certain situations the programmer is justified in inferring a pre-existing distribution for the natural template from the distribution of the actual's template, that is, the template that would have been inherited if the INHERIT attribute had been specified. In all these situations, the actual argument must be a whole array or array section, and the template of the actual must be coextensive with the array along any axes having a distribution format other than ``*.''
If the actual argument is a whole array, then the pre-existing distribution of the natural template of the dummy is identical to that of the actual argument.
If the actual argument is an array section, then, from each section-subscript and the distribution format for the corresponding axis of the array being subscripted, one constructs an axis distribution format for the corresponding axis of the natural template:
Here is a typical example of the use of this feature.
The main program has a two-dimensional array TROGGS,
which is to be processed by a subroutine one column at a time.
(Perhaps processing the entire array at once would require
prohibitive amounts of temporary space.)
Each column is to be distributed across many processors.
REAL TROGGS(1024,473)
!HPF DISTRIBUTE GROOVY *(BLOCK) ONTO *
Consider now the ALIGN directive.
The presence or absence of an asterisk at the start of an align-spec
has the same meaning as in a dist-format-clause: it specifies
whether the ALIGN directive is descriptive or prescriptive, respectively.
If an align-spec that does not begin with * is applied to a dummy argument, the meaning is that the dummy argument will be forced to have the specified alignment on entry to the subprogram (which may require temporarily remapping the data of the actual argument or a copy thereof).
Note that a dummy argument may also be used as an align-target.
SUBROUTINE NICHOLAS(TSAR,CZAR)
REAL, DIMENSION(1918) :: TSAR,CZAR
!HPF ALIGN WITH TSAR :: CZAR
In this example the first dummy argument, TSAR,
is allowed to remain aligned
with the corresponding actual argument, while the second dummy argument, CZAR,
is forced to be aligned with the first dummy argument. If the two actual arguments are
already aligned, no remapping of the data will be required at run time;
but the subprogram will operate correctly even if the actual arguments are
not already aligned, at the cost of remapping the data for the second
dummy argument at run time.
If the align-spec begins with ``*'',
then the alignee must be a
dummy argument and the directive must be ALIGN and not REALIGN.
The ``*'' indicates that the ALIGN directive constitutes
a guarantee on the part of the programmer that, on entry to
the subprogram, the indicated alignment
will already be satisfied by the dummy argument, without any action
to remap it required at run time.
For example:
SUBROUTINE GRUNGE(PLUNGE,SPONGE)
REAL PLUNGE(1000),SPONGE(1000)
!HPF ALIGN SQUEEGEE(K) WITH FIJI(2*K)
CALL GRUNGE(FIJI(2002:4000:2),SQUEEGEE(1001:))
it is true that every element of the array section
SQUEEGEE(1001:) is aligned with the corresponding element
of the array section FIJI(2002:4000:2), so the claim made
in subroutine GRUNGE is satisfied by this particular call.
It is not permitted to say simply ``ALIGN WITH *''; an align-target must follow the asterisk. (The proper way to say ``accept any alignment'' is INHERIT.)
If a dummy argument has no explicit ALIGN or DISTRIBUTE attribute, then the compiler provides an implicit alignment and distribution specification, one that could have been described explicitly without any ``assertion asterisks''.
The rules on the interaction of the REALIGN and REDISTRIBUTE directives with a subprogram argument interface are:
An overriding principle is that any mapping or remapping of arguments is not visible to the caller. This is true whether such remapping is implicit (in order to conform to prescriptive directives, which may themselves be explicit or implicit) or explicit (specified by REALIGN or REDISTRIBUTE directives). When the subprogram returns and the caller resumes execution, all objects accessible to the caller after the call are mapped exactly as they were before the call. It is not possible for a subprogram to change the mapping of any object in a manner visible to its caller, not even by means of REALIGN and REDISTRIBUTE.
©2000-2006 Rice University | [ Contact Us | HiPerSoft | Computer Science ] |