[lldb] Replace deprecated `std::unique_ptr::unique()` to silence a warning with MS...
[llvm-project.git] / flang / docs / ParameterizedDerivedTypes.md
blob34c8894c76918a3e6f33d6eeb3ad63c37743fe85
1 # Parameterized Derived Types (PDTs)
3 Derived types can be parameterized with type parameters. A type parameter is
4 either a kind type parameter or a length type parameter. Both kind and length
5 type parameters are of integer type.
7 This document aims to give insights at the representation of PDTs in FIR and how
8 PDTs related constructs and features are lowered to FIR.
10 # Fortran standard
12 Here is a list of the sections and constraints of the Fortran standard involved
13 for parameterized derived types.
15 - 7.2 Type parameters
16   - C701
17   - C702
18 - 9.4.5: Type parameter inquiry
19 - 9.7.1: ALLOCATE statement
20 - 9.7.2: NULLIFY
21 - 9.7.3: DEALLOCATE
23 The constraints are implemented and tested in flang.
25 ## The two types of PDTs
27 ### PDT with kind type parameter
29 PDTs with kind type parameter are already implemented in flang. Since the kind
30 type parameter shall be a constant expression, it can be determined at
31 compile-time and is folded in the type itself. Kind type parameters also play
32 a role in determining a specific type instance according to the Fortran
33 standard.
35 **Fortran**
36 ```fortran
37 type t(k)
38   integer, kind :: k
39 end type
41 type(t(1)) :: tk1
42 type(t(2)) :: tk2
43 ```
45 In the example above, `tk1` and `tk2` have distinct types.
47 Lowering makes the distinction between the two types by giving them different
48 names `@_QFE.kp.t.1` and `@_QFE.kp.t.2`. More information about the unique names
49 can be found here: `flang/docs/BijectiveInternalNameUniquing.md`
51 ### PDT with length type parameter
53 Two PDTs with the same derived type and the same kind type parameters but
54 different length type parameters are not distinct types. Unlike the kind type
55 parameter, the length type parameters do not play a role in determining a
56 specific type instance.
57 PDTs with length type parameter can be seen as dependent types[1].
59 In the example below, `tk1` and `tk2` have the same type but may have different
60 layout in memory. They have different value for the length type parameter `l`.
61 `tk1` and `tk2` are not convertible unlike `CHARACTER` types.
62 Assigning `tk2` to `tk1` is not a valid program.
64 **Fortran**
65 ```fortran
66 type t(k,l)
67   integer, kind :: k
68   integer, len :: l
69 end type
71 type(t(1, i+1)) :: tk1
72 type(t(1, i+2)) :: tk2
74 ! This is invalid
75 tk2 = tk1
76 ```
78 Components with length type parameters cannot be folded into the type at
79 compile-time like the one with kind type parameters since their size is not
80 known. There are multiple ways to implement length type parameters and here are
81 two possibilities.
83 1. Directly encapsulate the components in the derived type. This will be referred
84    as the "inlined" solution in the rest of the document. The size of the
85    descriptor will not be fixed and be computed at runtime. Size, offset need
86    to be computed at runtime as well.
88 2. Use a level of indirection for the components outside of the descriptor. This
89    will be referred as the "outlined" solution in the rest of the document.
90    The descriptor size will then remain the same.
92 These solutions have pros and cons and more details are given in the next few
93 sections.
95 #### Implementing PDT with inlined components
97 In case of `len_type1`, the size, offset, etc. of `fld1` and `fld2` depend on
98 the runtime values of `i` and `j` when the components are inlined into the
99 derived type. At runtime, this information needs to be computed to be retrieved.
100 While lowering the PDT, compiler generated functions can be created in order to
101 compute this information.
103 Note: The type description tables generated by semantics and used throughout the
104 runtime have component offsets as constants. Inlining component would require
105 this representation to be extended.
107 **Fortran**
108 ```fortran
109 ! PDT with one level of inlined components.
110 type len_type1(i, j)
111   integer, len :: i, j
112   character(i+j) :: fld1
113   character(j-i+2) :: fld2
114 end type
117 #### Implementing PDT with outlined components
119 A level of indirection can be used and `fld1` and `fld2` are then outlined
120 as shown in `len_type2`. _compiler_allocatable_ is here only to show which
121 components have an indirection.
123 **Fortran**
124 ```fortran
125 ! PDT with one level of indirection.
126 type len_type2(i, j)
127   integer, len :: i, j
128   ! The two following components are not directly stored in the type but
129   ! allocatable components managed by the compiler. The
130   ! `compiler_managed_allocatable` is not a proper keyword but just added here
131   ! to have a better understanding.
132   character(i+j), compiler_managed_allocatable :: fld1
133   character(j-i+2), compiler_managed_allocatable :: fld2
134 end type
137 This solution has performance drawback because of the added indirections. It
138 also has to deal with compiler managed allocation/deallocation of the components
139 pointed by the indirections.
141 These indirections are more problematic when we deal with array slice of derived
142 types as it could require temporaries depending how the memory is allocated.
144 The outlined solution is also problematic for unformatted I/O as the
145 indirections need to be followed correctly when reading or writing records.
147 #### Example of nested PDTs
149 PDTs can be nested. Here are some example used later in the document.
151 **Fortran**
152 ```fortran
153 ! PDT with second level of inlined components.
154 type len_type3(i, j)
155   integer, len :: i, j
156   character(2*j) :: name
157   type(len_type1(i*2, j+4)) :: field
158 end type
160 ! PDT with second level of indirection
161 type len_type4(i, j)
162   integer, len :: i, j
163   character(2*j), compiler_allocatable :: name
164   type(len_type2(i-1, 2**j)), compiler_allocatable :: field
165 end type
168 #### Example with array slice
170 Let's take an example with an array slice to see the advantages and
171 disadvantages of the two solutions.
173 For all derived types that do not have LEN type parameter (only have
174 compile-time constants) a standard descriptor can be set with the correct offset
175 and strides such that `array%field%fld2` can be encoded in the descriptor, is
176 not contiguous, and does not require a copy. This is what is implemented in
177 flang.
179 **Fortran**
180 ```fortran
181 ! Declare arrays of PDTs
182 type(len_type3(exp1,exp2)) :: pdt_inlined_array(exp3)
183 type(len_type4(exp1,exp2)) :: pdt_outlined_array(exp3)
185 ! Passing/accessing a slice of PDTs array
186 pdt_inlined_array%field%fld2
189 For a derived type with length type parameters inlined the expression
190 `pdt_inlined_array%field%fld2` can be encoded in the standard descriptor because
191 the components of `pdt_inlined_array` are inlined such that the array is laid
192 out with all its subcomponents in a contiguous range of memory.
194 For the `pdt_outlined_array` array, the implementation has to insert several
195 level of indirections and therefore cannot be encoded in the standard
196 descriptor.
197 The different indirections levels break the property of the large contiguous
198 block in memory if the allocation is done for each components. This would make
199 the `pdt_outlined_array` a ragged array. The memory can also be allocated for
200 components with length type parameters while allocating the base object (in this
201 case the `pdt_outlined_array`).
203 For each non-allocatable/non-pointer leaf automatic component of a PDT base
204 entity (`pdt_outlined_array` here) or a base entity containing PDTs, the
205 initialization will allocate a single block in memory for all the leaf
206 components reachable in the base entity (`pdt_outlined_array(i)%field%fld1`).
207 The size of this block will be `N * sizeof(leaf-component)` where `N` is the
208 multiplication of the size of each part-ref from the base entity to the leaf
209 component. The descriptor for each leaf component can then point to the correct
210 location in the block `block[i*sizeof(leaf-component)]`.
212 Outlining the components has the advantage that the size of the PDTs are
213 compile-time constant as each field is encoded as a descriptor pointing to the
214 data. It has a disadvantage to require non-standard descriptors and comes with
215 additional runtime cost.
217 With components inlining, the size of the PDTs are not compile-time constant.
218 This solution has the advantage to not add a performance drawback with
219 additional indirections but requires to compute the size of the descriptor
220 at runtime.
221 The size of the PDTs need to be computed at runtime. This is already the case
222 for dynamic allocation sizes since it is possible for arrays to have dynamic
223 shapes, etc.
225 ### Support of PDTs in other compilers
227 1) Nested PDTs
228 2) Array of PDTs
229 3) Allocatable array of PDTs
230 4) Pointer to array section
231 5) Formatted I/O
232 6) Unformatted I/O
233 7) User-defined I/O
234 8) FINAL subroutine
235 9) ELEMENTAL FINAL subroutine
237 | Compiler  |   1   |   2   |   3   |   4   |   5   |   6   |   7   |   8   |   9   |
238 | --------- | ----- | ----- | ----- | ----- | ----- | ----- | ----- | ----- | ----- |
239 | gfortran  | crash |   ok  | crash |   ok  |   ok  |   ok  |   no  |   no  |   no  |
240 | nag       |   ok  |   ok  |   ok  | crash |   ok  |   ok  |   ok  |   no  |   no  |
241 | nvfortran | crash |   ok  |   ok  |   ok  |   ok  |   ok  |   ok  |   ok  |   no  |
242 | xlf       |   ok  |   ok  |   ok  |   ok  | wrong |   ok  | wrong |   no  |   no  |
243 | ifort     |   ok  |   ok  |   ok  |   ok  |   ok  |   ok  |   ok  | crash | crash |
245 _Legends of results in the table_
247 ok = compile + run + good result
248 wrong = compile + run + wrong result
249 crash = compiler crash or runtime crash
250 no = doesn't compile with no crash
253 #### Field inlining in lowering
255 A PDT with length type parameters has a list of 1 or more type parameters that
256 are runtime values. These length type parameter values can be present in
257 specification of other type parameters, array bounds expressions, etc.
258 All these expressions are integer specifications expressions and can be
259 evaluated at any given point with the length type parameters value of the PDT
260 instance. This is possible because constraints C750 and C754 from Fortran 2018
261 standard that restrict what can appear in the specification expression.
263 _note: C750 and C754 are partially enforced in the semantic at the moment._
265 These expressions can be lowered into small simple functions. For example,
266 the offset of `fld1` in `len_type1` could be 0; its size would be computed as
267 `sizeof(char) * (i+j)`. `size` can be lowered into a compiler generated
268 function.
270 **FIR**
272 // Example of compiler generated functions to compute offsets, size, etc.
273 // This is just an example and actual implementation might have more functions.
275 // name field offset.
276 func.func @_len_type3.offset.name() -> index {
277   %0 = arith.constant 0 : index
278   return %0 : index
281 // size for `name`: sizeof(char) * (2 * i) + padding
282 func.func @_len_type3.memsize.name(%i: index, %j: index) -> index {
283   %0 = arith.constant 2 : index
284   %1 = arith.constant 8 : index
285   %2 = arith.muli %0, %i : index
286   %3 = arith.muli %1, %2 : index
287   // padding not added here
288   return %3 : index
291 // `fld` field offset.
292 func.func @_len_type3.offset.field(%i: index, %j: index) -> index {
293   %0 = call @_len_type3.offset.name() : () -> index
294   %1 = call @_len_type3.memsize.name(%i, %j) : (index, index) -> index
295   %2 = arith.addi %0, %1 : index
296   return %2 : index
299 // 1st type parameter used for field `fld`: i*2
300 func.func @_len_type3.field.typeparam.1(%i : index, %j : index) -> index {
301   %0 = arith.constant 2 : index
302   %1 = arith.muli %0, %i : index
303   return %1 : index
306 // 2nd type parameter used for field `fld`: j+4
307 func.func @_len_type3.field.typeparam.2(%i : index, %j : index) -> index {
308   %0 = arith.constant 4 : index
309   %1 = arith.addi %j, %0 : index
310   return %1 : index
313 // `fld1` offset in `len_type1`.
314 func.func @_len_type1.offset.fld1() -> index {
315   %0 = arith.constant 0 : index
316   return %0 : index
319 // size for `fld1`.
320 func.func @_len_type1.memsize.fld1(%i : index, %j : index) -> index {
321   %0 = arith.constant 8 : index
322   %1 = arith.addi %i, %j : index
323   %2 = arith.muli %0, %1 : index
324   return %2 : index
327 // `fld2` offset in `len_type1`.
328 func.func @_len_type1.offset.fld2(%i : index, %j : index) -> index {
329   %0 = call @_len_type1.offset.fld1() : () -> index
330   %1 = call @_len_type1.memsize.fld1(%i, %j) : (index, index) -> index
331   %2 = arith.addi %0, %1 : index
332   return %2 : index
336 Access a field
337 ```fortran
338 pdt_inlined_array(1)%field%fld2
341 Example of offset computation in the PDTs.
343 %0 = call @_len_type3.field.typeparam.1(%i, %j) : (index, index) -> index
344 %1 = call @_len_type3.field.typeparam.2(%i, %j) : (index, index) -> index
345 %2 = call @_len_type3.offset.fld(%i, %j) : (index, index) -> index
346 %3 = call @_len_type1.offset.fld2(%0, %1) : (index, index) -> index
347 %offset_of_1st_element = arith.addi %2, %3 : index
348 // Use the value computed offset_of_1st_element
351 In the case where the length type parameters values `(i,j)` are compile-time
352 constants then function inlining and constant folding will transform these
353 dependent types into statically defined types with no runtime cost.
355 **Fortran**
356 ```fortran
357 type t(l)
358   integer, len :: l
359   integer :: i(l)
360 end type
362 type(t(n)), target :: a(10)
363 integer, pointer :: p(:)
364 p => a(:)%i(5)
367 When making a new descriptor like for pointer association, the `field_index`
368 operation can take the length type parameters needed for size/offset
369 computation.
371 **FIR**
373 %5 = fir.field_index i, !fir.type<_QMmod1Tt{l:i32,i:!fir.array<?xi32>}>(%n : i32)
376 ### Length type parameter with expression
378 The component of a PDT can be defined with expressions including the length
379 type parameters.
381 **Fortran**
382 ```fortran
383 type t1(n, m)
384   integer, len :: n = 2
385   integer, len :: m = 4
386   real :: data(n*m)
387 end type
390 The idea would be to replace the expression with an extra length type parameter
391 with a compiler generated name and a default value of `n*m`. All instance of the
392 expression would then reference the new name.
394 **Fortran**
395 ```fortran
396 type t1(n, m)
397   integer, len :: n = 2
398   integer, len :: m = 4
399   integer, len :: t1_n_m_ = 8 ! hidden extra length type parameter
400   real :: data(t1_n_m_)
401 end type
404 At any place where the a PDT is initialized, the lowering would make the
405 evaluation and their values saved in the addendum and pointed to by the
406 descriptor.
408 ### `ALLOCATE`/`DEALLOCATE` statements
410 The allocation and deallocation of PDTs are delegated to the runtime.
412 The corresponding function can be found in
413 `flang/include/flang/Runtime/allocatable.h` and
414 `flang/include/flang/Runtime/pointer.h` for pointer allocation.
416 `ALLOCATE`
418 The `ALLOCATE` statement is lowered to a sequence of function calls as shown in
419 the example below.
421 **Fortran**
422 ```fortran
423 type t1(i)
424   integer, len :: i = 4
425   character(i) :: c
426 end type
428 type(t1), allocatable :: t
429 type(t1), pointer :: p
431 allocate(t1(2)::t)
432 allocate(t1(2)::p)
435 **FIR**
437 // For allocatable
438 %5 = fir.call @_FortranAAllocatableInitDerived(%desc, %type) : (!fir.box<none>, ) -> ()
439 // The AllocatableSetDerivedLength functions is called for each length type parameters.
440 %6 = fir.call @_FortranAAllocatableSetDerivedLength(%desc, %pos, %value) : (!fir.box<none>, i32, i64) -> ()
441 %7 = fir.call @_FortranAAllocatableAllocate(%3) : (!fir.box<none>) -> ()
443 // For pointer
444 %5 = fir.call @_FortranAPointerNullifyDerived(%desc, %type) : (!fir.box<none>, ) -> ()
445 // The PointerSetDerivedLength functions is called for each length type parameters.
446 %6 = fir.call @_FortranAPointerSetDerivedLength(%desc, %pos, %value) : (!fir.box<none>, i32, i64) -> ()
447 %7 = fir.call @_FortranAPointerAllocate(%3) : (!fir.box<none>) -> ()
450 `DEALLOCATE`
452 The `DEALLOCATE` statement is lowered to a runtime call to
453 `AllocatableDeallocate` and `PointerDeallocate` for pointers.
455 **Fortran**
456 ```fortran
457 deallocate(pdt1)
460 **FIR**
462 // For allocatable
463 %8 = fir.call @_FortranAAllocatableDeallocate(%desc1) : (!fir.box<none>) -> (i32)
465 // For pointer
466 %8 = fir.call @_FortranAPointerDeallocate(%desc1) : (!fir.box<none>) -> (i32)
469 ### `NULLIFY`
471 The `NULLIFY` statement is lowered to a call to the corresponding runtime
472 function `PointerNullifyDerived` in `flang/include/flang/Runtime/pointer.h`.
474 **Fortran**
475 ```fortran
476 NULLIFY(p)
479 **FIR**
481 %0 = fir.call @_FortranAPointerNullifyDerived(%desc, %type) : (!fir.box<none>, !fir.tdesc) -> ()
484 ### Formatted I/O
486 The I/O runtime internals are described in this file:
487 `flang/docs/IORuntimeInternals.md`.
489 When an I/O statement with a derived-type is encountered in lowering, the
490 derived-type is emboxed in a descriptor if it is not already and a call to the
491 runtime library is issued with the descriptor (as shown in the example below).
492 The function is `_FortranAioOutputDescriptor`. The call make a call to
493 `FormattedDerivedTypeIO` in `flang/runtime/descriptor-io.h` for derived-type.
494 This function will need to be updated to support the chosen solution for PDTs.
496 **Fortran**
497 ```fortran
498 type t
499   integer, len :: l
500   integer :: i(l) = 42
501 end type
503 ! ...
505 subroutine print_pdt
506   type(t(10)) :: x
507   print*, x
508 end subroutine
511 **FIR**
513 func.func @_QMpdtPprint_pdt() {
514   %l = arith.constant = 10
515   %0 = fir.alloca !fir.type<_QMpdtTt{l:i32,i:!fir.array<?xi32>}> (%l : i32) {bindc_name = "x", uniq_name = "_QMpdt_initFlocalEx"}
516   %1 = fir.embox %0 : (!fir.ref<!fir.type<_QMpdtTt{l:i32,i:!fir.array<?xi32>}>>) (typeparams %l : i32) -> !fir.box<!fir.type<_QMpdt_initTt{l:i32,i:!fir.array<2xi32>}>>
517   %2 = fir.address_of(@_QQcl.2E2F6669725F7064745F6578616D706C652E66393000) : !fir.ref<!fir.char<1,22>>
518   %c8_i32 = arith.constant 8 : i32
519   %3 = fir.convert %1 : (!fir.box<!fir.type<_QMpdtTt{l:i32,i:!fir.array<?xi32>}>>) -> !fir.box<none>
520   %4 = fir.convert %2 : (!fir.ref<!fir.char<1,22>>) -> !fir.ref<i8>
521   %5 = fir.call @_FortranAInitialize(%3, %4, %c8_i32) : (!fir.box<none>, !fir.ref<i8>, i32) -> none
522   %c-1_i32 = arith.constant -1 : i32
523   %6 = fir.address_of(@_QQcl.2E2F6669725F7064745F6578616D706C652E66393000) : !fir.ref<!fir.char<1,22>>
524   %7 = fir.convert %6 : (!fir.ref<!fir.char<1,22>>) -> !fir.ref<i8>
525   %c10_i32 = arith.constant 10 : i32
526   %8 = fir.call @_FortranAioBeginExternalListOutput(%c-1_i32, %7, %c10_i32) : (i32, !fir.ref<i8>, i32) -> !fir.ref<i8>
527   %9 = fir.embox %0 : (!fir.ref<!fir.type<_QMpdt_initTt{l:i32,i:!fir.array<?xi32>}>>) (typeparams %l : i32) -> !fir.box<!fir.type<_QMpdtTt{l:i32,i:!fir.array<?xi32>}>>
528   %10 = fir.convert %9 : (!fir.box<!fir.type<_QMpdt_initTt{l:i32,i:!fir.array<?xi32>}>>) -> !fir.box<none>
529   %11 = fir.call @_FortranAioOutputDescriptor(%8, %10) : (!fir.ref<i8>, !fir.box<none>) -> i1
530   %12 = fir.call @_FortranAioEndIoStatement(%8) : (!fir.ref<i8>) -> i32
531   return
535 ### Unformatted I/O
537 The entry point in the runtime for unformatted I/O is similar than the one for
538 formatted I/O. A call to `_FortranAioOutputDescriptor` with the correct
539 descriptor is also issued by the lowering. For unformatted I/O, the runtime is
540 calling `UnformattedDescriptorIO` from `flang/runtime/descriptor-io.h`.
541 This function will need to be updated to support the chosen solution for PDTs.
543 ### Default component initialization of local variables
545 Default initializers for components with length type parameters need to be
546 processed as the derived type instance is created.
547 The length parameters block must also be created and attached to the addendum.
548 See _New f18addendum_ section for more information.
550 ### Assignment
552 As mentioned in 10.2.1.2 (8), for an assignment, each length type parameter of
553 the variable shall have the same value as the corresponding type parameter
554 unless the lhs is allocatable.
556 **Fortran**
557 ```fortran
558 type t(l)
559   integer, len :: l
560   integer :: i(l)
561 end type
563 ! ...
565 type(t(10)) :: a, b
566 type(t(20)) :: c
567 type(t(:)), allocatable :: d
568 a = b ! Legal assignment
569 c = b ! Illegal assignment because `c` does not have the same length type
570       ! parameter value than `b`.
571 d = c ! Legal because `d` is allocatable
574 A simple intrinsic assignment without allocatable or pointer follows the same
575 path than the traditional derived-type (addressing of component is different)
576 since the length type parameter values are identical and do not need to be
577 copied or reallocated. The length type parameters values are retrieved when
578 copying the data.
580 Assignment of PDTs with allocatable or pointer components are done with the help
581 of the runtime. A call to `_FortranAAssign` is done with the lhs and rhs
582 descriptors. The length type parameters are available in the descriptors.
584 For allocatable PDTs, if the rhs side has different length type parameters than
585 the lhs, it is deallocated first and allocated with the rhs length type
586 parameters information (F'2018 10.2.1.3(3)). There is code in the runtime to
587 handle this already. It will need to be updated for the new f18addendum.
589 ### Finalization
591 A final subroutine is called for a PDT if the subroutine has the same kind type
592 parameters and rank as the entity to be finalized. The final subroutine is
593 called with the entity as the actual argument.
594 If there is an elemental final subroutine whose dummy argument has the same kind
595 type parameters as the entity to be finalized, or a final subroutine whose dummy
596 argument is assumed-rank with the same kind type parameters as the entity to be
597 finalized, the subroutine is called with the entity as the actual argument.
598 Otherwise, no subroutine is called.
600 **Example from the F2018 standard**
601 ```fortran
602 module m
604   type t(k)
605     integer, kind :: k
606     real(k), pointer :: vector(:) => NULL()
607   contains
608     final :: finalize_t1s, finalize_t1v, finalize_t2e
609   end type
611 contains
613   subroutine finalize_t1s(x)
614     type(t(kind(0.0))) x
615     if (associated(x%vector)) deallocate(x%vector)
616   END subroutine
618   subroutine finalize_t1v(x)
619     type(t(kind(0.0))) x(:)
620     do i = lbound(x,1), ubound(x,1)
621       if (associated(x(i)%vector)) deallocate(x(i)%vector)
622     end do
623   end subroutine
625   elemental subroutine finalize_t2e(x)
626     type(t(kind(0.0d0))), intent(inout) :: x
627     if (associated(x%vector)) deallocate(x%vector)
628   end subroutine
629 end module
631 subroutine example(n)
632 use m
634 type(t(kind(0.0))) a, b(10), c(n,2)
635 type(t(kind(0.0d0))) d(n,n)
637 ! Returning from this subroutine will effectively do
638 !    call finalize_t1s(a)
639 !    call finalize_t1v(b)
640 !    call finalize_t2e(d)
641 ! No final subroutine will be called for variable C because the user
642 ! omitted to define a suitable specific procedure for it.
643 end subroutine
646 ### Type parameter inquiry
648 Type parameter inquiry is used to get the value of a type parameter in a PDT.
650 **Fortran**
651 ```fortran
652 module t
653 type t1(i, j)
654   integer, len :: i = 4
655   integer, len :: j = 2
656   character(i*j) :: c
657 end type
660 program main
661 use t
662 type(t1(2, 2)) :: ti
663 print*, ti%c%len
664 print*, ti%i
665 print*, ti%j
668 ! Should print:
669 ! 4
670 ! 2
671 ! 2
674 These values are present in the `f18Addendum` and can be retrieved from it with
675 the correct index. If the length type parameter for a field is an expression,
676 a compiler generated function is used to computed its value.
677 The length type parameters are indexed in declaration order; i.e., 0 is the
678 first length type parameter in the deepest base type.
680 ### PDTs and polymorphism
682 In some cases with polymorphic entities, it is necessary to copy the length
683 type parameters from a descriptor to another. With the current design this is
684 not possible since the descriptor cannot be reallocated and the addendum is
685 allocated with a fixed number of length type parameters.
687 **Fortran**
688 ```fortran
689 ! The example below illustrates a case where the number of length type
690 ! parameters are different and need to be copied to an existing descriptor
691 ! addendum.
692 module m1
693 type t1
694   integer :: i
695 end type
697 ! This type could be defined in another compilation unit.
698 type, extends(t1) :: t2(l1, l2)
699   integer, len :: l1, l2
700 end type
702 contains
704 subroutine reallocate(x)
705   class(t1), allocatable :: x
706   allocate(t2(l1=1, l2=2):: x)
707 end subroutine
709 end module
711 program p
712   use m1
714   class(t1), allocatable :: x
716   call reallocate(x)
717   ! The new length type parameters need to be propagated at this point.
719   ! rest of code using `x`
720 end program
723 The proposed solution is to add indirection in the `f18Addendum` and store the
724 length type parameters in a separate block instead of directly in the addendum.
725 At the moment the storage for the length type parameters is allocated once as
726 a `std::int64_t` array.
728 **New f18Addendum**
729 ```cpp
730 {*derivedType_, *lenParamValues_}
733 Adding the indirection in the descriptor's addendum requires to manage the
734 lifetime of the block holding the length type parameter values.
736 Here are some thoughts of how to manage it:
737 - For allocatables, the space for the LEN parameters can be allocated as part of
738   the same malloc as the payload data.
739 - For automatics, same thing, if we implement automatics as allocatables.
740 - For monomorphic local variables, the LEN parameters would be in a little array
741   on the stack. Or we could treat any variable or component with LEN parameters
742   as being automatic even when it's monomorphic.
743 - For pointers and dummy arguments, we can just copy the pointer in the addendum
744   from the target to the pointer or dummy descriptor.
745 - For dynamically allocated descriptors, the LEN parameter values could just
746   follow the addendum in the same malloc.
748 The addendum of an array sections/sub-objects would point to the same block than
749 the base object.
751 In some special cases, a descriptor needs to be passed between the caller and
752 the callee. This includes array of PDTs and derived-type with PDT components.
753 The example describe one of the corner case where the length type parameter
754 would be lost if the descriptor is not passed.
756 ### Example that require a descriptor
758 Because of the length type parameters store in the addendum, it is required in
759 some case to pass the PDT with a descriptor to preserve the length type
760 parameters information. The example below illustrates such a case.
762 **Fortran**
763 ```fortran
764 module m
765 type t
766  integer :: i
767 end type
769 type, extends(t) :: t2(l)
770   integer, len :: l
771   real :: x(l)
772 end type
774 type base
775   type(t2(20)) :: pdt_component
776 end type
778 class(t), pointer :: p(:)
780 contains
782 subroutine foo(x, n)
783   integer :: n
784   type(base), target :: x(n)
785   ! Without descriptor, the actual argument is a zero-sized array. The length
786   ! type parameters of `x(n)%pdt_component` are not propagated from the caller.
788   ! A descriptor local to this function is created to pass the array section
789   ! in bar. 
790   call bar(x%pdt_component)
791 end subroutine
793 subroutine bar(x)
794   type(t2(*)), target :: x(:)
795   p => x
796 end subroutine
798 subroutine test()
799   type(base), target :: x(100)
800   call foo(x(1:-1:1), 0)
801   select type (p)
802    type is (t2(*))
803     ! This type parameters of x(1:60:3) in foo must still live here
804     print *, p%l
805    class default
806      print *, "something else"
807   end select
808 end subroutine
809 end module
811   use m
812   call test()
816 Because of the use case described above, PDTs, array of PDTs or derived-type
817 with PDT components will be passed by descriptor.
819 ## FIR operations with length type parameters
821 Couple of operations have length type parameters as operands already in their
822 design. For some operations, length type parameters are likely needed with
823 the two proposed solution. Some other operation like the array operations, the
824 operands are not needed when dealing with a descriptor since the length type
825 parameters are in it.
827 The operations will be updated if needed during the implementation of the
828 chosen solution.
830 ### `fir.alloca`
832 This primitive operation is used to allocate an object on the stack. When
833 allocating a PDT, the length type parameters are passed to the
834 operation so its size can be computed accordingly.
836 **FIR**
838 %i = arith.constant 10 : i32
839 %0 = fir.alloca !fir.type<_QMmod1Tpdt{i:i32,data:!fir.array<?xf32>}> (%i : i32)
840 // %i is the ssa value of the length type parameter
843 ### `fir.allocmem`
845 This operation is used to create a heap memory reference suitable for storing a
846 value of the given type. When creating a PDT, the length type parameters are
847 passed so the size can be computed accordingly.
849 **FIR**
851 %i = arith.constant 10 : i32
852 %0 = fir.alloca !fir.type<_QMmod1Tpdt{i:i32,data:!fir.array<?xf32>}> (%i : i32)
853 // ...
854 fir.freemem %0 : !fir.type<_QMmod1Tpdt{i:i32,data:!fir.array<?xf32>}>
857 ### `fir.embox`
859 The `fir.embox` operation create a boxed reference value. In the case of PDTs
860 the length type parameters can be passed as well to the operation.
862 **Fortran**
863 ```fortran
864 subroutine local()
865   type(t(2)) :: x ! simple local PDT
866   ! ...
867 end subroutine
870 **FIR**
872 func.func @_QMpdt_initPlocal() {
873   %c2_i32 = arith.constant 2 : i32
874   %0 = fir.alloca !fir.type<_QMpdt_initTt{l:i32,i:!fir.array<?xi32>}> (%c2 : i32)
875        {bindc_name = "x", uniq_name = "_QMpdt_initFlocalEx"}
876   // The fir.embox operation is responsible to place the provided length type
877   // parameters in the descriptor addendum so they are available to the runtime
878   // call later.
879   %1 = fir.embox %0 : (!fir.ref<!fir.type<_QMpdt_initTt{l:i32,i:!fir.array<?xi32>}>>) (typeparams %c2 : i32)
880        -> !fir.box<!fir.type<_QMpdt_initTt{l:i32,i:!fir.array<?xi32>}>>
881   %2 = fir.address_of(@_QQcl.2E2F6669725F7064745F6578616D706C652E66393000) : !fir.ref<!fir.char<1,22>>
882   %c8_i32 = arith.constant 8 : i32
883   %3 = fir.convert %1 : (!fir.box<!fir.type<_QMpdt_initTt{l:i32,i:!fir.array<?xi32>}>>) -> !fir.box<none>
884   %4 = fir.convert %2 : (!fir.ref<!fir.char<1,22>>) -> !fir.ref<i8>
885   %5 = fir.call @_FortranAInitialize(%3, %4, %c8_i32) : (!fir.box<none>, !fir.ref<i8>, i32) -> none
886   return
890 ### `fir.field_index`
892 The `fir.field_index` operation is used to generate a field offset value from
893 a field identifier in a derived-type. The operation takes length type parameter
894 values with a PDT so it can compute a correct offset.
896 **FIR**
898 %l = arith.constant 10 : i32
899 %1 = fir.field_index i, !fir.type<_QMpdt_initTt{l:i32,i:i32}> (%l : i32)
900 %2 = fir.coordinate_of %ref, %1 : (!fir.type<_QMpdt_initTt{l:i32,i:i32}>, !fir.field) -> !fir.ref<i32>
901 %3 = fir.load %2 : !fir.ref<i32>
902 return %3
905 ### `fir.len_param_index`
907 This operation is used to get the length type parameter offset in from a PDT.
909 **FIR**
911 func.func @_QPpdt_len_value(%arg0: !fir.box<!fir.type<t1{l:i32,!fir.array<?xi32>}>>) -> i32 {
912   %0 = fir.len_param_index l, !fir.box<!fir.type<t1{l:i32,!fir.array<?xi32>}>>
913   %1 = fir.coordinate_of %arg0, %0 : (!fir.box<!fir.type<t1{l:i32,!fir.array<?xi32>}>>, !fir.len) -> !fir.ref<i32>
914   %2 = fir.load %1 : !fir.ref<i32>
915   return %2 : i32
919 ### `fir.save_result`
921 Save the result of a function returning an array, box, or record type value into
922 a memory location given the shape and LEN parameters of the result. Length type
923 parameters is passed if the PDT is not boxed.
925 **FIR**
927 func.func @return_pdt(%buffer: !fir.ref<!fir.type<t2(l1:i32,l2:i32){x:f32}>>) {
928   %l1 = arith.constant 3 : i32
929   %l2 = arith.constant 5 : i32
930   %res = fir.call @foo() : () -> !fir.type<t2(l1:i32,l2:i32){x:f32}>
931   fir.save_result %res to %buffer typeparams %l1, %l2 : !fir.type<t2(l1:i32,l2:i32){x:f32}>, !fir.ref<!fir.type<t2(l1:i32,l2:i32){x:f32}>>, i32, i32
932   return
936 ### `fir.array_*` operations
938 The current design of the different `fir.array_*` operations include length type
939 parameters operands. This is designed to use PDT without descriptor directly in
940 FIR.
942 **FIR**
944 // Operation used with a boxed PDT does not need the length type parameters as
945 // they are directly retrieved from the box.
946 %0 = fir.array_coor %boxed_pdt, %i, %j  (fir.box<fir.array<?x?xfir.type<!fir.type<_QMpdt_initTt{l:i32,i:!fir.array<?xi32>}>>>>, index, index) -> !fir.ref<fir.type<!fir.type<_QMpdt_initTt{l:i32,i:!fir.array<?xi32>}>>>
948 // In case the PDT would not be boxed, the length type parameters are needed to
949 // compute the correct addressing.
950 %0 = fir.array_coor %pdt_base, %i, %j typeparams %l  (fir.ref<fir.array<?x?xfir.type<!fir.type<_QMpdt_initTt{l:i32,i:!fir.array<?xi32>}>>>>, index, index, index) -> !fir.ref<fir.type<PDT>>
955 ## Implementation choice
957 While both solutions have pros and cons, we want to implement the outlined
958 solution.
959 - The runtime was implemented with this solution in mind.
960 - The size of the descriptor does not need to be computed at runtime.
964 # Testing
966 - Lowering part is tested with LIT tests in tree
967 - PDTs involved a lot of runtime information so executable
968   tests will be useful for full testing.
972 # Current TODOs
973 Current list of TODOs in lowering:
974 - `flang/lib/Lower/Allocatable.cpp:461` not yet implement: derived type length parameters in allocate
975 - `flang/lib/Lower/Allocatable.cpp:645` not yet implement: deferred length type parameters
976 - `flang/lib/Lower/Bridge.cpp:454` not yet implemented: get length parameters from derived type BoxValue
977 - `flang/lib/Lower/ConvertExpr.cpp:341` not yet implemented: copy derived type with length parameters
978 - `flang/lib/Lower/ConvertExpr.cpp:993` not yet implemented: component with length parameters in structure constructor
979 - `flang/lib/Lower/ConvertExpr.cpp:1063` not yet implemented: component with length parameters in structure constructor
980 - `flang/lib/Lower/ConvertExpr.cpp:1146` not yet implemented: type parameter inquiry
981 - `flang/lib/Lower/ConvertExpr.cpp:2424` not yet implemented: creating temporary for derived type with length parameters
982 - `flang/lib/Lower/ConvertExpr.cpp:3742` not yet implemented: gather rhs LEN parameters in assignment to allocatable
983 - `flang/lib/Lower/ConvertExpr.cpp:4725` not yet implemented: derived type array expression temp with LEN parameters
984 - `flang/lib/Lower/ConvertExpr.cpp:6400` not yet implemented: PDT size
985 - `flang/lib/Lower/ConvertExpr.cpp:6419` not yet implemented: PDT offset
986 - `flang/lib/Lower/ConvertExpr.cpp:6679` not yet implemented: array expr type parameter inquiry
987 - `flang/lib/Lower/ConvertExpr.cpp:7135` not yet implemented: need to adjust type parameter(s) to reflect the final component
988 - `flang/lib/Lower/ConvertType.cpp:334` not yet implemented: parameterized derived types
989 - `flang/lib/Lower/ConvertType.cpp:370` not yet implemented: derived type length parameters
990 - `flang/lib/Lower/ConvertVariable.cpp:169` not yet implemented: initial-data-target with derived type length parameters
991 - `flang/lib/Lower/ConvertVariable.cpp:197` not yet implemented: initial-data-target with derived type length parameters
992 - `flang/lib/Lower/VectorSubscripts.cpp:121` not yet implemented: threading length parameters in field index op
993 - `flang/lib/Optimizer/Builder/BoxValue.cpp:60` not yet implemented: box value is missing type parameters
994 - `flang/lib/Optimizer/Builder/BoxValue.cpp:67` not yet implemented: mutable box value is missing type parameters
995 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:688` not yet implemented: read fir.box with length parameters
996 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:746` not yet implemented: generate code to get LEN type parameters
997 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:779` not yet implemented: derived type with type parameters
998 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:905` not yet implemented: allocatable and pointer components non deferred length parameters
999 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:917` not yet implemented: array component shape depending on length parameters
1000 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:924` not yet implemented: get character component length from length type parameters
1001 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:934` not yet implemented: lower component ref that is a derived type with length parameter
1002 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:956` not yet implemented: get length parameters from derived type BoxValue
1003 - `flang/lib/Optimizer/Builder/MutableBox.cpp:70` not yet implemented: updating mutablebox of derived type with length parameters
1004 - `flang/lib/Optimizer/Builder/MutableBox.cpp:168` not yet implemented: read allocatable or pointer derived type LEN parameters
1005 - `flang/lib/Optimizer/Builder/MutableBox.cpp:310` not yet implemented: update allocatable derived type length parameters
1006 - `flang/lib/Optimizer/Builder/MutableBox.cpp:505` not yet implemented: pointer assignment to derived with length parameters
1007 - `flang/lib/Optimizer/Builder/MutableBox.cpp:597` not yet implemented: pointer assignment to derived with length parameters
1008 - `flang/lib/Optimizer/Builder/MutableBox.cpp:740` not yet implemented: reallocation of derived type entities with length parameters
1011 Current list of TODOs in code generation:
1013 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:1034` not yet implemented: fir.allocmem codegen of derived type with length parameters
1014 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:1581` not yet implemented: generate call to calculate size of PDT
1015 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:1708` not yet implemented: fir.embox codegen of derived with length parameters
1016 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:1749` not yet implemented: reboxing descriptor of derived type with length parameters
1017 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:2229` not yet implemented: derived type with type parameters
1018 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:2256` not yet implemented: compute size of derived type with type parameters
1019 - `flang/lib/Optimizer/CodeGen/TypeConverter.h:257` not yet implemented: extended descriptor derived with length parameters
1021 Current list of TODOs in optimizations:
1023 - `flang/lib/Optimizer/Transforms/ArrayValueCopy.cpp:1007` not yet implemented: unhandled dynamic type parameters
1027 Resources:
1028 - [0] Fortran standard
1029 - [1] https://en.wikipedia.org/wiki/Dependent_type