1 <!--===- docs/AssumedRank.md
3 Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4 See https://llvm.org/LICENSE.txt for license information.
5 SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
10 An assumed-rank dummy data object is a dummy argument that takes its rank from
11 its effective argument. It is a dummy argument, or the associated entity of a
12 SELECT RANK in the `RANK DEFAULT` block. Its rank is not known at compile
13 time. The rank can be anything from 0 (scalar) to the maximum allowed rank in
14 Fortran (currently 15 according to Fortran 2018 standard section 5.4.6 point
17 This document summarizes the contexts where assumed-rank objects can appear,
18 and then describes how they are implemented and lowered to HLFIR and FIR. All
19 section references are made to the Fortran 2018 standard.
21 ## Fortran Standard References
23 Here is a list of sections and constraints from the Fortran standard involving
28 - 7.5.6.1 FINAL statement
30 - 8.5.7 CONTIGUOUS attribute
32 - 8.5.8 DIMENSION attribute
33 - 8.5.8.7 Assumed-rank entity
38 - 15.5.2.13 Restrictions on entities associated with dummy arguments
41 - 15.5.2.4 Ordinary dummy variables - point 17
42 - 18 Interoperability with C
45 ### Summary of the constraints:
48 - be pointers, allocatables (or have neither of those atttributes).
49 - be monomorphic or polymorphic (both `TYPE(*)` and `CLASS(*)`)
50 - have all the attributes, except VALUE and CODIMENSION (C837). Notably, they
51 can have the CONTIGUOUS or OPTIONAL attributes (C830).
52 - appear as an actual argument of an assumed-rank dummy (C838)
53 - appear as the selector of SELECT RANK (C838)
54 - appear as the argument of C_LOC and C_SIZEOF from ISO_C_BINDING (C838)
55 - appear as the first argument of inquiry intrinsic functions (C838). These
56 inquiry functions listed in table 16.1 are detailed in the "Assumed-rank
57 features" section below.
58 - appear in BIND(C) and non BIND(C interface (18.1 point 3)
59 - be finalized on entry as INTENT(OUT) under some conditions that prevents the
60 assumed-rank to be associated with an assumed-size.
61 - be associated with any kind of scalars and arrays, including assumed-size.
65 - have the VALUE attribute (C837)
66 - be something that is not a named variable (they cannot be the result of a
67 function or a component reference)
68 - appear in a designator other than the case listed above (C838). Notably, they
69 cannot be directly addressed, they cannot be used in elemental operations or
70 transformational intrinsics, they cannot be used in IO, they cannot be
72 - be finalized on entry as INTENT(OUT) if it could be associated with an
74 - be used in a reference to a procedure without an explicit interface
75 (15.4.2.2. point 3 (c)).
77 With regard to aliasing, assumed-rank dummy objects follow the same rules as
78 for assumed shapes, with the addition of 15.5.2.13 (c) which adds a rule when
79 the actual is a scalar (adding that TARGET assumed-rank may alias if the actual
80 argument is a scalar even if they have the CONTIGUOUS attribute, while it is OK
81 to assume that CONTIGUOUS TARGET assumed shape do not alias with other
86 ## Assumed-Rank Representations in Flang
88 ### Representation in Semantics
89 In semantics (there is no concept of assumed-rank expression needed in
90 `evaluate::Expr`). Such symbols have either `semantics::ObjectEntityDetails` (
91 dummy data objects) with a `semantics::ArraySpec` that encodes the
92 "assumed-rank-shape" (can be tested with IsAssumedRank()), or they have
93 `semantics::AssocEntityDetails` (associated entity in the RANK DEFAULT case).
95 Inside a select rank, a `semantics::Symbol` is created for the associated
96 entity with `semantics::AssocEntityDetails` that points to the the selector
97 and holds the rank outside of the RANK DEFAULT case.
99 Assumed-rank dummies are also represented in the
100 `evaluate::characteristics::TypeAndShape` (with the AssumedRank attribute) to
101 represent assumed-rank in procedure characteristics.
103 ### Runtime Representation of Assumed-Ranks
104 Assumed-ranks are implemented as CFI_cdesc_t (18.5.3) with the addition of an
105 f18 specific addendum when required for the type. This is the usual f18
106 descriptor, and no changes is required to represent assumed-ranks in this data
107 structure. In fact, there is no difference between the runtime descriptor
108 created for an assumed shape and the runtime descriptor created when the
109 corresponding entity is passed as an assumed-rank.
111 This means that any descriptor can be passed to an assumed-rank dummy (with
112 care to ensure that the POINTER/ALLOCATABLE attribute match the dummy argument
113 attributes as usual). Notably, any runtime interface that takes descriptor
114 arguments of any ranks already work with assumed-rank entities without any
115 changes or special cases.
117 This also implies that the runtime cannot tell that an entity is an
118 assumed-rank based on its descriptor, but there seems to be not need for this
119 so far ("rank based" dispatching for user defined assignments and IO is not
120 possible with assumed-ranks, and finalization is possible, but there is no need
121 for the runtime to distinguish between finalization of an assumed-rank and
122 finalization of other entities: only the runtime rank matters).
124 The only difference and difficulty is that descriptor storage size of
125 assumed-rank cannot be precisely known at compile time, and this impacts the
126 way descriptor copies are generated in inline code. The size can still be
127 maximized using the maximum rank, which the runtime code already does when
128 creating temporary descriptor in many cases. Inline code also needs care if it
129 needs to access the descriptor addendum (like the type descriptor), since its
130 offset will not be a compile time constant as usual.
132 Note that an alternative to maximizing the allocation of assumed-rank temporary
133 descriptor could be to use automatic allocation based on the rank of the input
134 descriptor, but this would make stack allocation analysis more complex (tools
135 will likely not have the Fortran knowledge that this allocation size is bounded
136 for instance) while the stack "over" allocation is likely reasonable (24 bytes
137 per dimension). Hence the selection of the simple approach using static size
138 allocation to the maximum rank.
140 ### Representation in FIR and HLFIR
141 SSA values for assumed-rank entities have an MLIR type containing a
142 `!fir.array<*xT>` sequence type wrapped in a `!fir.box` or `!fir.class` type
143 (additionally wrapped in a `!fir.ref` type for pointers and allocatables).
146 `INTEGER :: x(..)` -> `!fir.box<!fir.array<* x i32>>`
147 `CLASS(*) :: x(..)` -> `!fir.class<!fir.array<* x none>>`
148 `TYPE(*) :: x(..)` -> `!fir.box<!fir.array<* x none>>`
149 `REAL, ALLOCATABLE :: x(..)` -> `!fir.ref<!fir.box<!fir.heap<!fir.array<* x f32>>>>`
150 `TYPE(t), POINTER :: x(..)` -> `!fir.ref<!fir.box<!fir.ptr<!fir.array<* x !fir.type<t>>>>>`
152 All these FIR types are implemented as the address of a CFI_cdesc_t in code
155 There is no need to allow assumed-rank "expression" in HLFIR (hlfir.expr) since
156 assumed-rank cannot appear in expressions (except as the actual argument to an
157 assumed-rank dummy). Assumed-rank are variables. Also, since they cannot have
158 the VALUE attribute, there is no need to use the hlfir.as_expr +
159 hlfir.associate idiom to make copies for them.
161 FIR/HLFIR operation where assumed-rank may appear:
162 - as `hlfir.declare` and `fir.declare` operand and result.
163 - as `fir.convert` operand and/or result.
164 - as `fir.load` operand and result (POINTER and ALLOCATABLE dereference).
165 - as a block argument (dummy argument).
166 - as `fir.rebox_assumed_rank` operand/result (new operation to change some
167 fields of assumed-rank descriptors).
168 - as `fir.box_rank` operand (rank inquiry).
169 - as `fir.box_dim` operand (brutal user inquiry about the bounds of an
170 assumed-rank in a compile time constant dimension).
171 - as `fir.box_addr` operand (to get the base address in inlined code for
173 - as `fir.box_elesize` operand (to implement LEN and STORAGE_SIZE).
174 - as `fir.absent` result (passing absent actual to OPTIONAL assumed-rank dummy)
175 - as `fir.is_present` operand (PRESENT inquiry)
176 - as `hlfir.copy_in` and `hlfir.copy_out` operand and result (copy in and
177 copy-out of assumed-rank)
178 - as `fir.alloca` type and result (when creating an assumed-rank POINTER dummy
179 from a non POINTER dummy).
180 - as `fir.store` operands (same case as `fir.alloca`).
182 FIR/HLFIR Operations that should not need to accept assumed-ranks but where it
183 could still be relevant:
184 - `fir.box_tdesc` and `fir.box_typecode` (polymorphic assumed-rank cannot
185 appear in a SELECT TYPE directly without using a SELECT RANK). Given the
186 CFI_cdesc_t structure, no change would be needed for `fir.box_typecode` to
187 support assumed-ranks, but `fir.box_tdesc` would require change since the
188 position of the type descriptor pointer depends on the rank.
189 - as `fir.allocmem` / `fir.global` result (assumed-ranks are never local/global
191 - as `fir.embox` result (When creating descriptor for an explicit shape, the
192 descriptor can be created with the entity rank, and then casted via
195 It is not expected for any other FIR or HLFIR operations to handle assumed-rank
198 #### Summary of the impact in FIR
199 One new operation is needed, `fir.rebox_assumed_rank`, the rational being that
200 fir.rebox codegen is already quite complex and not all the aspects of fir.rebox
201 matters for assumed-ranks (only simple field changes are required with
202 assumed-ranks). Also, this operation will be allowed to take an operand in
203 memory to avoid expensive fir.load of pointer/allocatable inputs. The operation
204 will also allow creating rank-one assumed-size descriptor from an input
205 assumed-rank descriptor to cover the SELECT RANK `RANK(*)` case.
207 It is proposed that the FIR descriptor inquiry operation (fir.box_addr,
208 fir.box_rank, fir.box_dim, fir.box_elesize at least) be allowed to take
209 fir.ref<fir.box> arguments (allocatable and pointer descriptors) directly
210 instead of generating a fir.load first. A conditional "read" effect will be
211 added in such case. Again, the purpose is to avoid generating descriptor copies
212 for the sole purpose of satisfying the SSA IR constraints. This change will
213 likely benefit the non assumed-rank case too (even though LLVM is quite good at
214 removing pointless descriptor copies in these cases).
216 It will be ensured that all the operation listed above accept assumed-rank
217 operands (both the verifiers and coedgen). The codegen of `fir.load`,
218 `fir.alloca`, `fir.store`, `hlfir.copy_in` and `hlfir.copy_out` will need
219 special handling for assumed-ranks.
221 ### Representation in LLVM IR
223 Assumed-rank descriptor types are lowered to the LLVM type of a CFI_cdesc_t
224 descriptor with no dimension array field and no addendum. That way, any inline
225 code attempt to directly access dimensions and addendum with constant offset
226 will be invalid for more safety, but it will still be easy to generate LLVM GEP
227 to address the first descriptor fields in LLVM (to get the base address, rank,
228 type code and attributes).
230 `!fir.box<!fir.array<* x i32>>` -> `!llvm.struct<(ptr, i64, i32, i8, i8, i8, i8>`
232 ## Assumed-rank Features
234 This section list the different Fortran features where assumed-rank objects are
235 involved and describes the related implementation design.
237 ### Assumed-rank in procedure references
238 Assumed-rank arguments are implemented as being the address of a CFI_cdesc_t.
240 When passing an actual argument to an assumed-rank dummy, the following points
241 need special attention and are further described below:
242 - Copy-in/copy-out when required
243 - Creation of forwarding of the assumed-rank dummy descriptor (including when
244 the actual is an assumed-size).
245 - Finalization, deallocation, and initialization of INTENT(OUT) assumed-rank
248 OPTIONAL assumed-ranks are implemented like other non assumed-rank OPTIONAL
249 objects passed by descriptor: an absent assumed-rank is represented by a null
250 pointer to a CFI_cdesc_t.
252 The passing interface for assumed-rank described above and below is compliant
253 by default with the BIND(C) case, except for the assumed-rank dummy descriptor
254 lower bounds, which are only set to zeros in BIND(C) interface because it
255 implies in most of the cases to create a new descriptor.
257 VALUE is forbidden for assumed-rank dummies, so there is nothing to be done for
258 it (although since copy-in/copy-out is possible, the compiler must anyway deal
259 with creating assumed-rank copies, so it would likely not be an issue to relax
262 #### Copy-in and Copy out
263 Copy-in and copy-out is required when passing an actual that is not contiguous
264 to a non POINTER CONTIGUOUS assumed-rank.
266 When the actual argument is ranked, the copy-in/copy-out can be performed on
267 the ranked actual argument where the dynamic type has been aligned with the
268 dummy type if needed (passing CLASS(T) to TYPE(T)) as illustrated below.
281 Â Â type(t), contiguous :: x(..)
284 Â ! copy-in and copy-out is required aroud bar
290 When the actual is also an assumed-rank special the same copy-in/copy-out need
291 may arise, and the `hlfir.copy_in` and `hlfir.copy_out` are also used to cover
292 this case. The `hlfir.copy_in`operation is implemented using the `IsContiguous`
293 runtime (can be used as-is) and the `AssignTemporary` temporary runtime.
295 The difference with the ranked case is that more care is needed to create the
296 output descriptor passed to `AssignTemporary`: it must be allocated to the
297 maximum rank with the same type as the input descriptor and only the descriptor
298 fields prior to the array dimensions will be initialized to those of an
299 unallocated descriptor prior to the runtime call (`AssignTemporary` copies the
308 Â Â type(t), contiguous :: x(..)
311 Â ! copy-in and copy-out is required aroud bar
315 #### Creating the descriptor for assumed-rank dummies
317 There are four cases to distinguish:
318 1. Actual does not have a descriptor (and is therefore ranked)
319 2. Actual has a descriptor that can be forwarded for the dummy
320 3. Actual has a ranked descriptor that cannot be forwarded for the dummy
321 4. Actual has an assumed-rank descriptor that cannot be forwarded for the dummy
323 For the first case, a descriptor will be created for the dummy with `fir.embox`
324 has if it has the rank of the actual argument. This is the same logic as when
325 dealing with assumed shape or INTENT(IN) POINTER dummy arguments, except that
326 an extra cast to the assumed-rank descriptor type is added (no-op at runtime).
327 Care must be taken to set the final dimension extent to -1 in the descriptor
328 created for an assumed-size actual argument. Note that the descriptor created
329 for an assumed-size still has the rank of the assumed-size, a rank-one
330 descriptor will be created for it if needed in a RANK(*) block (nothing says
331 that an assumed-size should be passed as a rank-one array in 15.5.2.4 point 17).
333 For the second case, a cast is added to assumed-rank descriptor type if it is
334 not one already and the descriptor is forwarded.
336 For the third case, a new ranked descriptor with the dummy attribute/lower
337 bounds is created from the actual argument descriptor with `fir.rebox` as it is
338 done when passing to an assume shape dummy, and a cast to the assumed-rank
339 descriptor is added .
341 The last case is the same as the third one, except the that the descriptor
342 manipulation is more complex since the storage size of the descriptor is
343 unknown. `fir.rebox` codegen is already quite complex since it deals with
344 creating descriptor for descriptor based array sections and pointer remapping.
345 Both of those are meaningless in this case where the output descriptor is the
346 same as the input one, except for the lower bounds, attribute, and derived type
347 pointer field that may need to be changed to match the values describing the
348 dummy. A simpler `fir.rebox_assumed_rank` operation is added for this use case.
349 Notably, this operation can take fir.ref<fir.box> inputs to avoid creating an
350 expensive and useless fir.load of POINTER/ALLOCATABLE descriptors.
352 Fortran requires the compiler to fall in the 3rd and 4th case and create
353 descriptor temporary for the dummy a lot more than one would think and hope. An
354 annex section below discusses cases that force the compiler to create a new
355 descriptor for the dummy even if the actual already has a descriptor. These are
356 the same situations than with non assumed-rank arguments, but when passing
357 assumed-rank to assumed-ranks, the cost of this extra copy is higher.
359 #### Intent(out) assumed-rank finalization, deallocation, initialization
361 The standard prevents INTENT(OUT) assumed-rank requiring finalization to be
362 associated with assumed-size arrays (C839) because there would be no way to
363 finalize such entities. But INTENT(OUT) finalization is still possible if the
364 actual is not an assumed-size and not a nonpointer nonallocatable assumed-rank.
366 Flang therefore needs to implement finalization, deallocation and
367 initialization of INTENT(OUT) as usual. Non pointer non allocatable INTENT(OUT)
368 finalization is done via a call to `Destroy` runtime API that takes a
369 descriptor and can be directly used with an assumed-rank descriptor with no
370 change. The initialization is done via a call to the `Initialize` runtime API
371 that takes a descriptor and can also directly be used with an assumed
372 descriptor. Conditional deallocation of INTENT(OUT) allocatable is done via an
373 inline allocation status check and either an inline deallocate for intrinsic
374 types, or a runtime call to `Deallocate` for the other cases. For
375 assumed-ranks, the runtime call is always used regardless of the type to avoid
376 inline descriptor manipulations. `Deallocate` runtime API also works with
377 assumed-rank descriptors with no changes (like any runtime API taking
378 descriptors of any rank).
382 Â class(*), allocatable :: x(..)
385 Â Â class(*), intent(out) :: x(..)
388 Â ! x may require finalization and initialization on bar entry.
392 Â class(*), intent(out) :: x(..)
397 Select rank is implemented with a rank inquiry (and last extent for `RANK(*)`),
398 followed by a jump in the related block where the selector descriptor is cast
399 to a descriptor with the associated entity rank for the current block for the
400 `RANK(cst)` cases. In the `RANK DEFAULT`, the input descriptor is kept with no
401 cast, and in the RANK(*), a rank-one descriptor is created with the same
402 dynamic type as the input.
403 These new descriptor values are mapped to the associated entity symbol and
404 lowering precede as usual. This is very similar to how Select Type is
405 implemented. The `RANK(*)` is a bit odd, it detects assumed-ranks associated
406 with an assumed-size arrays regardless of the rank, and takes precedence over
407 any rank based matching.
409 Note that `-1` is a magic extent number that encodes that a descriptor describes
410 an entity that is an assumed-size (user specified extents of explicit shape
411 arrays are always normalized to zero when negative, so `-1` is a safe value to
412 identify a descriptor created for an assumed-size). It is actually well
413 specified for the BIND(C) (18.5.2 point 1.) and is always used as such in flang
416 The implementation of SELECT RANK is done as follow:
417 - Read the rank `r` in the descriptor
418 - If there is a `RANK(*)`, read the extent in dimension `r`. If it is `-1`,
419 jump to the `RANK(*)` block. Otherwise, continue to the steps below.
420 - For each `RANK(constant)` case, compare `constant` to `r`. Stop at first
421 match and jump to related block. The order of the comparisons does not matter
422 (there cannot be more than one match).
423 - Jump to `RANK DEFAULT` block is any. Otherwise jump to the end of the
426 The blocks for each cases jumps at the end of the construct at the end. As
427 opposed to SELECT TYPE, no clean-up should be needed at the construct level
428 since the select-rank selector is a named entity and cannot be a temporary with
429 a lifetime of the construct.
431 Except for the `RANK(*)` case, the branching logic is implemented in FIR with a
432 `fir.select_case` operating on the rank.
439 subroutine assumed_size(x)
445 subroutine rank_one(x)
448 subroutine many_dim_array(x)
462 call many_dim_array(y)
467 Pseudo FIR for the example (some converts and SSA constants creation are not shown for more clarity):
470 func.func @_QPtest(%arg0: !fir.box<!fir.array<?xf32>>) {
471 %x:2 = hlfir.declare %arg0 {uniq_name = "_QFtestEx"} : (!fir.box<!fir.array<*xf32>>) -> (!fir.box<!fir.array<*xf32>>, !fir.box<!fir.array<*xf32>>)
472 %r = fir.box_rank %x#1 : (!fir.box<!fir.array<*xf32>>) -> i32
473 %last_extent = fir.call @_FortranASizeDim(%x#1, %r, %sourcename, %sourceline)
474 %is_assumed_size = arith.cmpi eq %last_extent, %c-1: (i64, i64) -> i1
475 cf.cond_br %is_assumed_size, ^bb_assumed_size, ^bb_not_assumed_size
477 %r1_box = fir.rebox_assumed_rank %x#0 : (!fir.box<!fir.array<*xf32>>) -> !fir.box<!fir.array<?xf32>>
478 %addr = fir.box_addr %addr, !fir.box<!fir.array<?xf32>> -> !fir.ref<!fir.array<?xf32>>
479 fir.call @_QPassumed_size(%addr) (!fir.ref<!fir.array<?xf32>>) -> ()
481 ^bb_not_assumed_size:
482 fir.select_case %3 : i32 [#fir.point, %c0, ^bb_scalar, #fir.point, %c1, ^bb_rank1, unit, ^bb_default]
484 %scalar_cast = fir.convert %x#1 : (!fir.box<!fir.array<*xf32>>) -> !fir.box<f32>
485 %x_scalar = fir.box_addr %scalar_cast: (!fir.box<f32>) -> !fir.ref<f32>
486 fir.call @_QPscalar(%x_scalar) (!fir.ref<f32>) -> ()
489 %rank1_cast = fir.convert %x#1 : (!fir.box<!fir.array<*xf32>>) -> !fir.box<!fir.array<?xf32>>
490 fir.call @_QPrank_one(%rank1_cast) (!fir.box<!fir.array<?xf32>>) -> ()
493 fir.call @_QPmany_dim_array(%x#1) (!fir.box<!fir.array<*xf32>>) -> ()
500 ### Inquiry intrinsic functions
501 #### ALLOCATED and ASSOCIATED
502 Implemented inline with `fir.box_addr` (reading the descriptor first address
503 inline). Currently, FIR descriptor inquiry happens at the "descriptor value"
504 level (require a fir.load of the POINTER or ALLOCATABLE !fir.ref<!fir.box<>>),
505 to satisfy the SSA value semantics, the fir.load creates a copy of the
506 underlying descriptor storage. With assume ranks, this copy will be "expensive"
507 and harder to optimize out given the descriptor storage size is not a compile
508 time constant. To avoid this extra cost, ALLOCATABLE and POINTER assumed-ranks
509 will be cast to scalar descriptors before the `fir.load`.
512 real, allocatable :: x(..)
513 print *, allocated(x)
517 %1 = fir.convert %x : (!fir.ref<!fir.box<!fir.heap<!fir.array<* x f32>>>>) -> !fir.ref<!fir.box<!fir.heap<f32>>>
518 %2 = fir.load %x : !fir.ref<!fir.box<!fir.heap<f32>>>
519 %addr = fir.box_addr %2 : (!fir.box<!fir.heap<f32>>) -> fir.ref<f32>
520 # .... "addr != null" as usual
522 #### LEN and STORAGE_SIZE
523 Implemented inline with `fir.box_elesize` with the same approach as
524 ALLOCATED/ASSOCIATED when dealing with fir.box load for POINTERS and
528 character(*) :: x(..)
533 %ele_size = fir.box_elesize %x : (!fir.box<!fir.array<*x!fir.char<?>>>) -> i64
534 # .... divide by character KIND byte size if needed as usual
537 Implemented inline with `fir.is_present` which ends-up implemented as a check
538 that the descriptor address is not null just like with OPTIONAL assumed shapes
539 and OPTIONAL pointers and allocatables.
542 real, optional :: x(..)
547 %is_present = fir.is_prent %x : (!fir.box<!fir.array<*xf32>>) -> i1
550 Implemented inline with `fir.box_rank` which simply reads the descriptor rank
559 %rank = fir.box_rank %x : (!fir.box<!fir.array<*xf32>>) -> i32
562 Using the runtime can be queried as it is done for assumed shapes. When DIM is
563 present and is constant, `fir.box_dim` can also be used with the option to add
564 a runtime check that RANK <= DIM. Pointers and allocatables are dereferenced,
565 which in FIR currently creates a descriptor copy that cannot be simplified
566 like for the previous inquiries by inserting a cast before the fir.load (the
567 dimension info must be correctly copied).
569 #### LBOUND, SHAPE, and UBOUND
570 When DIM is present an is present, the runtime can be used as it is currently
571 with assumed shapes. When DIM is absent, the result is a rank-one array whose
572 extent is the rank. The runtime has an entry for UBOUND that takes a descriptor
573 and allocate the result as needed, so the same logic as for assumed shape can
576 There is no such entry for LBOUND/SHAPE currently, it would likely be best to
577 add one rather than to jungle with inline code. Pointers and allocatables
578 dereference is similar as with SIZE.
580 #### EXTENDS_TYPE_OF, SAME_TYPE_AS, and IS_CONTIGUOUS
581 Using the runtime as it is done currently with assumed shapes. Pointers and
582 allocatables dereference is similar as with SIZE.
584 #### C_LOC from ISO_C_BINDING
585 Implemented with `fir.box_addr` as with other C_LOC cases for entities that
588 #### C_SIZE_OF from ISO_C_BINDING
589 Implemented as STORAGE_SIZE * SIZE.
591 #### Floating point inquiries and NEW_LINE
592 BIT_SIZE, DIGITS, EPSILON, HUGE, KIND, MAXEXPONENT, MINEXPONENT, NEW_LINE,
593 PRECISION, RADIX, RANGE, TINY all accept assumed-rank, but are always constant
594 folded by semantics based on the type and lowering does not need to deal with
597 #### Coarray inquiries
598 Assumed-rank cannot be coarrays (C837), but they can still technically appear
599 in COSHAPE (which should obviously return zero). They cannot appear in LBOUND,
600 LCOBOUND, UBOUND, UCOBOUND that require the argument to be a coarray.
602 ## Annex 1 - Descriptor temporary for the dummy arguments
604 When passing an actual argument that is descriptor to a dummy that must be
605 passed by descriptor, one could expect that the descriptor of the actual can
606 just be forwarded to the dummy, but this is unfortunately not possible in quite
607 some cases. This is not specific to assumed-ranks, but since the cost of
608 descriptor temporaries is higher for assumed-ranked, it is discussed here.
610 Below are the reasons for which a new descriptor may be required:
611 1. passing a POINTER to a non POINTER
612 2. setting the descriptor CFI_cdesc_t `attribute` according to the dummy
613 POINTER/ALLOCATABLE attributes (18.3.6 point 4 for the BIND(C) case).
614 3. setting the CFI_cdesc_t lower bounds to zero for a BIND(C) assumed
615 shape/rank dummy (18.5.3 point 3).
616 4. setting the derived type pointer to the dummy dynamic type when passing a
617 CLASS() actual to a TYPE() dummy.
620 When passing a POINTER to a non POINTER, the target of the pointer is passed,
621 and nothing prevents the association status of the actual argument to change
622 during the call (e.g. if the POINTER is another argument of the call, or is a
623 module variable, it may be re-associated in the call). These association status
624 change of the actual should not impact the dummy, so they must not share the
628 In the BIND(C) case, this is required by 18.3.6 point 4. Outside of the BIND(C)
629 case, this should still be done because any runtime call where the dummy
630 descriptor is forwarded may misbehave if the ALLOCATABLE/POINTER attribute is
631 not the one of the dummy (e.g. reallocation could be triggered instead of
632 padding/trimming characters).
638 If the descriptor derived type info pointer is not the one of the dummy dynamic
639 type, many runtime call like IO and assignment will misbehave when being
640 provided the dummy descriptor.
642 For point 2., 3., and 4., one could be tempted to change the descriptor fields
643 before and after the call, but this is risky since this would assume nothing
644 will access the actual argument descriptor during the call. And even without
645 bringing any potential asynchronous behavior of OpenMP/OpenACC/Cuda Fortran
646 extensions, the actual argument descriptor may be passed inside a call in
647 another arguments with "different" lower bounds POINTER or ALLOCATABLE (but
648 could also be accessed via host of use association in general).
651 ## Annex 2 - Assumed-Rank Objects and IGNORE_TKR
654 - Set IGNORE_TKR(TK) on assumed-rank dummies (but TYPE(*) is better when
656 - Pass an assumed-rank to an IGNORE_TKR(R) dummy that is not passed
657 by descriptor (explicit shape and assumed-size). Note that copy-in and
658 copy-out will be performed for the dummy
660 It is not possible to:
661 - Set IGNORE_TKR(R) on an assumed-rank dummy.
666 subroutine test(assumed_rank_actual)
668 subroutine assumed_size_dummy(x)
669 !dir$ ignore_tkr(tkr) x
672 subroutine any_type_assumed_rank(x)
673 !dir$ ignore_tkr(tk) x
677 real :: assumed_rank_actual(..)
678 call assumed_size_dummy(assumed_rank_actual) !OK
679 call any_type_assumed_rank(assumed_rank_actual) !OK
683 ## Annex 3 - Test Plan
685 MPI_f08 module makes usage of assumed-rank (see
686 https://www.mpi-forum.org/docs/mpi-3.1/mpi31-report.pdf). As such compiling
687 MPI_f08 modules of MPI libraries and some applications making usage of MPI_f08
688 will be a good test for the implementation of this feature.