[clang][modules] Don't prevent translation of FW_Private includes when explicitly...
[llvm-project.git] / flang / docs / ParameterizedDerivedTypes.md
blob39ba20d232468420f2591f4460f103160e77d420
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 ### PDT with kind type parameter
27 PDTs with kind type parameter are already implemented in flang. Since the kind
28 type parameter shall be a constant expression, it can be determined at
29 compile-time and is folded in the type itself. Kind type parameters also play
30 a role in determining a specific type instance according to the Fortran
31 standard.
33 **Fortran**
34 ```fortran
35 type t(k)
36   integer, kind :: k
37 end type
39 type(t(1)) :: tk1
40 type(t(2)) :: tk2
41 ```
43 In the example above, `tk1` and `tk2` have distinct types.
45 Lowering makes the distinction between the two types by giving them different
46 names `@_QFE.kp.t.1` and `@_QFE.kp.t.2`. More information about the unique names
47 can be found here: `flang/docs/BijectiveInternalNameUniquing.md`
49 ### PDT with length type parameter
51 Two PDTs with the same derived type and the same kind type parameters but
52 different length type parameters are not distinct types. Unlike the kind type
53 parameter, the length type parameters do not play a role in determining a
54 specific type instance.
55 PDTs with length type parameter can be seen as dependent types[1].
57 In the example below, `tk1` and `tk2` have the same type but may have different
58 layout in memory. They have different value for the length type parameter `l`.
59 `tk1` and `tk2` are not convertible unlike `CHARACTER` types.
60 Assigning `tk2` to `tk1` is not a valid program.
62 **Fortran**
63 ```fortran
64 type t(k,l)
65   integer, kind :: k
66   integer, len :: l
67 end type
69 type(t(1, i+1)) :: tk1
70 type(t(1, i+2)) :: tk2
72 ! This is invalid
73 tk2 = tk1
74 ```
76 Components with length type parameters cannot be folded into the type at
77 compile-time like the one with kind type parameters since their size is not
78 known. There are multiple ways to implement length type parameters and here are
79 two possibilities.
81 1. Directly encapsulate the components in the derived type. This will be referred
82    as the "inlined" solution in the rest of the document. The size of the
83    descriptor will not be fixed and be computed at runtime. Size, offset need
84    to be computed at runtime as well.
86 2. Use a level of indirection for the components outside of the descriptor. This
87    will be referred as the "outlined" solution in the rest of the document.
88    The descriptor size will then remain the same.
90 These solutions have pros and cons and more details are given in the next few
91 sections.
93 #### Implementing PDT with inlined components
95 In case of `len_type1`, the size, offset, etc. of `fld1` and `fld2` depend on
96 the runtime values of `i` and `j` when the components are inlined into the
97 derived type. At runtime, this information needs to be computed to be retrieved.
98 While lowering the PDT, compiler generated functions can be created in order to
99 compute this information.
101 Note: The type description tables generated by semantics and used throughout the
102 runtime have component offsets as constants. Inlining component would require
103 this representation to be extended.
105 **Fortran**
106 ```fortran
107 ! PDT with one level of inlined components.
108 type len_type1(i, j)
109   integer, len :: i, j
110   character(i+j) :: fld1
111   character(j-i+2) :: fld2
112 end type
115 #### Implementing PDT with outlined components
117 A level of indirection can be used and `fld1` and `fld2` are then outlined
118 as shown in `len_type2`. _compiler_allocatable_ is here only to show which
119 components have an indirection.
121 **Fortran**
122 ```fortran
123 ! PDT with one level of indirection.
124 type len_type2(i, j)
125   integer, len :: i, j
126   ! The two following components are not directly stored in the type but
127   ! allocatable components managed by the compiler. The
128   ! `compiler_managed_allocatable` is not a proper keyword but just added here
129   ! to have a better understanding.
130   character(i+j), compiler_managed_allocatable :: fld1
131   character(j-i+2), compiler_managed_allocatable :: fld2
132 end type
135 This solution has performance drawback because of the added indirections. It
136 also has to deal with compiler managed allocation/deallocation of the components
137 pointed by the indirections.
139 These indirections are more problematic when we deal with array slice of derived
140 types as it could require temporaries depending how the memory is allocated.
142 The outlined solution is also problematic for unformatted I/O as the
143 indirections need to be followed correctly when reading or writing records.
145 #### Example of nested PDTs
147 PDTs can be nested. Here are some example used later in the document.
149 **Fortran**
150 ```fortran
151 ! PDT with second level of inlined components.
152 type len_type3(i, j)
153   integer, len :: i, j
154   character(2*j) :: name
155   type(len_type1(i*2, j+4)) :: field
156 end type
158 ! PDT with second level of indirection
159 type len_type4(i, j)
160   integer, len :: i, j
161   character(2*j), compiler_allocatable :: name
162   type(len_type2(i-1, 2**j)), compiler_allocatable :: field
163 end type
166 #### Example with array slice
168 Let's take an example with an array slice to see the advantages and
169 disadvantages of the two solutions.
171 For all derived types that do not have LEN type parameter (only have
172 compile-time constants) a standard descriptor can be set with the correct offset
173 and strides such that `array%field%fld2` can be encoded in the descriptor, is
174 not contiguous, and does not require a copy. This is what is implemented in
175 flang.
177 **Fortran**
178 ```fortran
179 ! Declare arrays of PDTs
180 type(len_type3(exp1,exp2)) :: pdt_inlined_array(exp3)
181 type(len_type4(exp1,exp2)) :: pdt_outlined_array(exp3)
183 ! Passing/accessing a slice of PDTs array
184 pdt_inlined_array%field%fld2
187 For a derived type with length type parameters inlined the expression
188 `pdt_inlined_array%field%fld2` can be encoded in the standard descriptor because
189 the components of `pdt_inlined_array` are inlined such that the array is laid
190 out with all its subcomponents in a contiguous range of memory.
192 For the `pdt_outlined_array` array, the implementation has to insert several
193 level of indirections and therefore cannot be encoded in the standard
194 descriptor.
195 The different indirections levels break the property of the large contiguous
196 block in memory if the allocation is done for each components. This would make
197 the `pdt_outlined_array` a ragged array. The memory can also be allocated for
198 components with length type parameters while allocating the base object (in this
199 case the `pdt_outlined_array`).
201 For each non-allocatable/non-pointer leaf automatic component of a PDT base
202 entity (`pdt_outlined_array` here) or a base entity containing PDTs, the
203 initialization will allocate a single block in memory for all the leaf
204 components reachable in the base entity (`pdt_outlined_array(i)%field%fld1`).
205 The size of this block will be `N * sizeof(leaf-component)` where `N` is the
206 multiplication of the size of each part-ref from the base entity to the leaf
207 component. The descriptor for each leaf component can then point to the correct
208 location in the block `block[i*sizeof(leaf-component)]`.
210 Outlining the components has the advantage that the size of the PDTs are
211 compile-time constant as each field is encoded as a descriptor pointing to the
212 data. It has a disadvantage to require non-standard descriptors and comes with
213 additional runtime cost.
215 With components inlining, the size of the PDTs are not compile-time constant.
216 This solution has the advantage to not add a performance drawback with
217 additional indirections but requires to compute the size of the descriptor
218 at runtime.
219 The size of the PDTs need to be computed at runtime. This is already the case
220 for dynamic allocation sizes since it is possible for arrays to have dynamic
221 shapes, etc.
223 ### Support of PDTs in other compilers
225 1) Nested PDTs
226 2) Array of PDTs
227 3) Allocatable array of PDTs
228 4) Pointer to array section
229 5) Formatted I/O
230 6) Unformatted I/O
231 7) User-defined I/O
232 8) FINAL subroutine
233 9) ELEMENTAL FINAL subroutine
235 | Compiler  |   1   |   2   |   3   |   4   |   5   |   6   |   7   |   8   |   9   |
236 | --------- | ----- | ----- | ----- | ----- | ----- | ----- | ----- | ----- | ----- |
237 | gfortran  | crash |   ok  | crash |   ok  |   ok  |   ok  |   no  |   no  |   no  |
238 | nag       |   ok  |   ok  |   ok  | crash |   ok  |   ok  |   ok  |   no  |   no  |
239 | nvfortran | crash |   ok  |   ok  |   ok  |   ok  |   ok  |   ok  |   ok  |   no  |
240 | xlf       |   ok  |   ok  |   ok  |   ok  | wrong |   ok  | wrong |   no  |   no  |
241 | ifort     |   ok  |   ok  |   ok  |   ok  |   ok  |   ok  |   ok  | crash | crash |
243 _Legends of results in the table_
245 ok = compile + run + good result
246 wrong = compile + run + wrong result
247 crash = compiler crash or runtime crash
248 no = doesn't compile with no crash
251 #### Field inlining in lowering
253 A PDT with length type parameters has a list of 1 or more type parameters that
254 are runtime values. These length type parameter values can be present in
255 specification of other type parameters, array bounds expressions, etc.
256 All these expressions are integer specifications expressions and can be
257 evaluated at any given point with the length type parameters value of the PDT
258 instance. This is possible because constraints C750 and C754 from Fortran 2018
259 standard that restrict what can appear in the specification expression.
261 _note: C750 and C754 are partially enforced in the semantic at the moment._
263 These expressions can be lowered into small simple functions. For example,
264 the offset of `fld1` in `len_type1` could be 0; its size would be computed as
265 `sizeof(char) * (i+j)`. `size` can be lowered into a compiler generated
266 function.
268 **FIR**
270 // Example of compiler generated functions to compute offsets, size, etc.
271 // This is just an example and actual implementation might have more functions.
273 // name field offset.
274 func.func @_len_type3.offset.name() -> index {
275   %0 = arith.constant 0 : index
276   return %0 : index
279 // size for `name`: sizeof(char) * (2 * i) + padding
280 func.func @_len_type3.memsize.name(%i: index, %j: index) -> index {
281   %0 = arith.constant 2 : index
282   %1 = arith.constant 8 : index
283   %2 = arith.muli %0, %i : index
284   %3 = arith.muli %1, %2 : index
285   // padding not added here
286   return %3 : index
289 // `fld` field offset.
290 func.func @_len_type3.offset.field(%i: index, %j: index) -> index {
291   %0 = call @_len_type3.offset.name() : () -> index
292   %1 = call @_len_type3.memsize.name(%i, %j) : (index, index) -> index
293   %2 = arith.addi %0, %1 : index
294   return %2 : index
297 // 1st type parameter used for field `fld`: i*2
298 func.func @_len_type3.field.typeparam.1(%i : index, %j : index) -> index {
299   %0 = arith.constant 2 : index
300   %1 = arith.muli %0, %i : index
301   return %1 : index
304 // 2nd type parameter used for field `fld`: j+4
305 func.func @_len_type3.field.typeparam.2(%i : index, %j : index) -> index {
306   %0 = arith.constant 4 : index
307   %1 = arith.addi %j, %0 : index
308   return %1 : index
311 // `fld1` offset in `len_type1`.
312 func.func @_len_type1.offset.fld1() -> index {
313   %0 = arith.constant 0 : index
314   return %0 : index
317 // size for `fld1`.
318 func.func @_len_type1.memsize.fld1(%i : index, %j : index) -> index {
319   %0 = arith.constant 8 : index
320   %1 = arith.addi %i, %j : index
321   %2 = arith.muli %0, %1 : index
322   return %2 : index
325 // `fld2` offset in `len_type1`.
326 func.func @_len_type1.offset.fld2(%i : index, %j : index) -> index {
327   %0 = call @_len_type1.offset.fld1() : () -> index
328   %1 = call @_len_type1.memsize.fld1(%i, %j) : (index, index) -> index
329   %2 = arith.addi %0, %1 : index
330   return %2 : index
334 Access a field
335 ```fortran
336 pdt_inlined_array(1)%field%fld2
339 Example of offset computation in the PDTs.
341 %0 = call @_len_type3.field.typeparam.1(%i, %j) : (index, index) -> index
342 %1 = call @_len_type3.field.typeparam.2(%i, %j) : (index, index) -> index
343 %2 = call @_len_type3.offset.fld(%i, %j) : (index, index) -> index
344 %3 = call @_len_type1.offset.fld2(%0, %1) : (index, index) -> index
345 %offset_of_1st_element = arith.addi %2, %3 : index
346 // Use the value computed offset_of_1st_element
349 In the case where the length type parameters values `(i,j)` are compile-time
350 constants then function inlining and constant folding will transform these
351 dependent types into statically defined types with no runtime cost.
353 **Fortran**
354 ```fortran
355 type t(l)
356   integer, len :: l
357   integer :: i(l)
358 end type
360 type(t(n)), target :: a(10)
361 integer, pointer :: p(:)
362 p => a(:)%i(5)
365 When making a new descriptor like for pointer association, the `field_index`
366 operation can take the length type parameters needed for size/offset
367 computation.
369 **FIR**
371 %5 = fir.field_index i, !fir.type<_QMmod1Tt{l:i32,i:!fir.array<?xi32>}>(%n : i32)
374 ### Length type parameter with expression
376 The component of a PDT can be defined with expressions including the length
377 type parameters.
379 **Fortran**
380 ```fortran
381 type t1(n, m)
382   integer, len :: n = 2
383   integer, len :: m = 4
384   real :: data(n*m)
385 end type
388 The idea would be to replace the expression with an extra length type parameter
389 with a compiler generated name and a default value of `n*m`. All instance of the
390 expression would then reference the new name.
392 **Fortran**
393 ```fortran
394 type t1(n, m)
395   integer, len :: n = 2
396   integer, len :: m = 4
397   integer, len :: _t1_n_m = 8 ! hidden extra length type parameter
398   real :: data(_t1_n_m)
399 end type
402 At any place where the a PDT is initialized, the lowering would make the
403 evaluation and their values saved in the addendum and pointed to by the
404 descriptor.
406 ### `ALLOCATE`/`DEALLOCATE` statements
408 The allocation and deallocation of PDTs are delegated to the runtime.
410 The corresponding function can be found in
411 `flang/include/flang/Runtime/allocatable.h` and
412 `flang/include/flang/Runtime/pointer.h` for pointer allocation.
414 `ALLOCATE`
416 The `ALLOCATE` statement is lowered to a sequence of function calls as shown in
417 the example below.
419 **Fortran**
420 ```fortran
421 type t1(i)
422   integer, len :: i = 4
423   character(i) :: c
424 end type
426 type(t1), allocatable :: t
427 type(t1), pointer :: p
429 allocate(t1(2)::t)
430 allocate(t1(2)::p)
433 **FIR**
435 // For allocatable
436 %5 = fir.call @_FortranAAllocatableInitDerived(%desc, %type) : (!fir.box<none>, ) -> ()
437 // The AllocatableSetDerivedLength functions is called for each length type parameters.
438 %6 = fir.call @_FortranAAllocatableSetDerivedLength(%desc, %pos, %value) : (!fir.box<none>, i32, i64) -> ()
439 %7 = fir.call @_FortranAAllocatableAllocate(%3) : (!fir.box<none>) -> ()
441 // For pointer
442 %5 = fir.call @_FortranAPointerNullifyDerived(%desc, %type) : (!fir.box<none>, ) -> ()
443 // The PointerSetDerivedLength functions is called for each length type parameters.
444 %6 = fir.call @_FortranAPointerSetDerivedLength(%desc, %pos, %value) : (!fir.box<none>, i32, i64) -> ()
445 %7 = fir.call @_FortranAPointerAllocate(%3) : (!fir.box<none>) -> ()
448 `DEALLOCATE`
450 The `DEALLOCATE` statement is lowered to a runtime call to
451 `AllocatableDeallocate` and `PointerDeallocate` for pointers.
453 **Fortran**
454 ```fortran
455 deallocate(pdt1)
458 **FIR**
460 // For allocatable
461 %8 = fir.call @_FortranAAllocatableDeallocate(%desc1) : (!fir.box<none>) -> (i32)
463 // For pointer
464 %8 = fir.call @_FortranAPointerDeallocate(%desc1) : (!fir.box<none>) -> (i32)
467 ### `NULLIFY`
469 The `NULLIFY` statement is lowered to a call to the corresponding runtime
470 function `PointerNullifyDerived` in `flang/include/flang/Runtime/pointer.h`.
472 **Fortran**
473 ```fortran
474 NULLIFY(p)
477 **FIR**
479 %0 = fir.call @_FortranAPointerNullifyDerived(%desc, %type) : (!fir.box<none>, !fir.tdesc) -> ()
482 ### Formatted I/O
484 The I/O runtime internals are described in this file:
485 `flang/docs/IORuntimeInternals.md`.
487 When an I/O statement with a derived-type is encountered in lowering, the
488 derived-type is emboxed in a descriptor if it is not already and a call to the
489 runtime library is issued with the descriptor (as shown in the example below).
490 The function is `_FortranAioOutputDescriptor`. The call make a call to
491 `FormattedDerivedTypeIO` in `flang/runtime/descriptor-io.h` for derived-type.
492 This function will need to be updated to support the chosen solution for PDTs.
494 **Fortran**
495 ```fortran
496 type t
497   integer, len :: l
498   integer :: i(l) = 42
499 end type
501 ! ...
503 subroutine print_pdt
504   type(t(10)) :: x
505   print*, x
506 end subroutine
509 **FIR**
511 func.func @_QMpdtPprint_pdt() {
512   %l = arith.constant = 10
513   %0 = fir.alloca !fir.type<_QMpdtTt{l:i32,i:!fir.array<?xi32>}> (%l : i32) {bindc_name = "x", uniq_name = "_QMpdt_initFlocalEx"}
514   %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>}>>
515   %2 = fir.address_of(@_QQcl.2E2F6669725F7064745F6578616D706C652E66393000) : !fir.ref<!fir.char<1,22>>
516   %c8_i32 = arith.constant 8 : i32
517   %3 = fir.convert %1 : (!fir.box<!fir.type<_QMpdtTt{l:i32,i:!fir.array<?xi32>}>>) -> !fir.box<none>
518   %4 = fir.convert %2 : (!fir.ref<!fir.char<1,22>>) -> !fir.ref<i8>
519   %5 = fir.call @_FortranAInitialize(%3, %4, %c8_i32) : (!fir.box<none>, !fir.ref<i8>, i32) -> none
520   %c-1_i32 = arith.constant -1 : i32
521   %6 = fir.address_of(@_QQcl.2E2F6669725F7064745F6578616D706C652E66393000) : !fir.ref<!fir.char<1,22>>
522   %7 = fir.convert %6 : (!fir.ref<!fir.char<1,22>>) -> !fir.ref<i8>
523   %c10_i32 = arith.constant 10 : i32
524   %8 = fir.call @_FortranAioBeginExternalListOutput(%c-1_i32, %7, %c10_i32) : (i32, !fir.ref<i8>, i32) -> !fir.ref<i8>
525   %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>}>>
526   %10 = fir.convert %9 : (!fir.box<!fir.type<_QMpdt_initTt{l:i32,i:!fir.array<?xi32>}>>) -> !fir.box<none>
527   %11 = fir.call @_FortranAioOutputDescriptor(%8, %10) : (!fir.ref<i8>, !fir.box<none>) -> i1
528   %12 = fir.call @_FortranAioEndIoStatement(%8) : (!fir.ref<i8>) -> i32
529   return
533 ### Unformatted I/O
535 The entry point in the runtime for unformatted I/O is similar than the one for
536 formatted I/O. A call to `_FortranAioOutputDescriptor` with the correct
537 descriptor is also issued by the lowering. For unformatted I/O, the runtime is
538 calling `UnformattedDescriptorIO` from `flang/runtime/descriptor-io.h`.
539 This function will need to be updated to support the chosen solution for PDTs.
541 ### Default component initialization of local variables
543 Default initializers for components with length type parameters need to be
544 processed as the derived type instance is created.
545 The length parameters block must also be created and attached to the addendum.
546 See _New f18addendum_ section for more information.
548 ### Assignment
550 As mentioned in 10.2.1.2 (8), for an assignment, each length type parameter of
551 the variable shall have the same value as the corresponding type parameter
552 unless the lhs is allocatable.
554 **Fortran**
555 ```fortran
556 type t(l)
557   integer, len :: l
558   integer :: i(l)
559 end type
561 ! ...
563 type(t(10)) :: a, b
564 type(t(20)) :: c
565 type(t(:)), allocatable :: d
566 a = b ! Legal assignment
567 c = b ! Illegal assignment because `c` does not have the same length type
568       ! parameter value than `b`.
569 d = c ! Legal because `d` is allocatable
572 A simple intrinsic assignment without allocatable or pointer follows the same
573 path than the traditional derived-type (addressing of component is different)
574 since the length type parameter values are identical and do not need to be
575 copied or reallocated. The length type parameters values are retrieved when
576 copying the data.
578 Assignment of PDTs with allocatable or pointer components are done with the help
579 of the runtime. A call to `_FortranAAssign` is done with the lhs and rhs
580 descriptors. The length type parameters are available in the descriptors.
582 For allocatable PDTs, if the rhs side has different length type parameters than
583 the lhs, it is deallocated first and allocated with the rhs length type
584 parameters information (F'2018 10.2.1.3(3)). There is code in the runtime to
585 handle this already. It will need to be updated for the new f18addendum.
587 ### Finalization
589 A final subroutine is called for a PDT if the subroutine has the same kind type
590 parameters and rank as the entity to be finalized. The final subroutine is
591 called with the entity as the actual argument.
592 If there is an elemental final subroutine whose dummy argument has the same kind
593 type parameters as the entity to be finalized, or a final subroutine whose dummy
594 argument is assumed-rank with the same kind type parameters as the entity to be
595 finalized, the subroutine is called with the entity as the actual argument.
596 Otherwise, no subroutine is called.
598 **Example from the F2018 standard**
599 ```fortran
600 module m
602   type t(k)
603     integer, kind :: k
604     real(k), pointer :: vector(:) => NULL()
605   contains
606     final :: finalize_t1s, finalize_t1v, finalize_t2e
607   end type
609 contains
611   subroutine finalize_t1s(x)
612     type(t(kind(0.0))) x
613     if (associated(x%vector)) deallocate(x%vector)
614   END subroutine
616   subroutine finalize_t1v(x)
617     type(t(kind(0.0))) x(:)
618     do i = lbound(x,1), ubound(x,1)
619       if (associated(x(i)%vector)) deallocate(x(i)%vector)
620     end do
621   end subroutine
623   elemental subroutine finalize_t2e(x)
624     type(t(kind(0.0d0))), intent(inout) :: x
625     if (associated(x%vector)) deallocate(x%vector)
626   end subroutine
627 end module
629 subroutine example(n)
630 use m
632 type(t(kind(0.0))) a, b(10), c(n,2)
633 type(t(kind(0.0d0))) d(n,n)
635 ! Returning from this subroutine will effectively do
636 !    call finalize_t1s(a)
637 !    call finalize_t1v(b)
638 !    call finalize_t2e(d)
639 ! No final subroutine will be called for variable C because the user
640 ! omitted to define a suitable specific procedure for it.
641 end subroutine
644 ### Type parameter inquiry
646 Type parameter inquiry is used to get the value of a type parameter in a PDT.
648 **Fortran**
649 ```fortran
650 module t
651 type t1(i, j)
652   integer, len :: i = 4
653   integer, len :: j = 2
654   character(i*j) :: c
655 end type
658 program main
659 use t
660 type(t1(2, 2)) :: ti
661 print*, ti%c%len
662 print*, ti%i
663 print*, ti%j
666 ! Should print:
667 ! 4
668 ! 2
669 ! 2
672 These values are present in the `f18Addendum` and can be retrieved from it with
673 the correct index. If the length type parameter for a field is an expression,
674 a compiler generated function is used to computed its value.
675 The length type parameters are indexed in declaration order; i.e., 0 is the
676 first length type parameter in the deepest base type.
678 ### PDTs and polymorphism
680 In some cases with polymorphic entities, it is necessary to copy the length
681 type parameters from a descriptor to another. With the current design this is
682 not possible since the descriptor cannot be reallocated and the addendum is
683 allocated with a fixed number of length type parameters.
685 **Fortran**
686 ```fortran
687 ! The example below illustrates a case where the number of length type
688 ! parameters are different and need to be copied to an existing descriptor
689 ! addendum.
690 module m1
691 type t1
692   integer :: i
693 end type
695 ! This type could be defined in another compilation unit.
696 type, extends(t1) :: t2(l1, l2)
697   integer, len :: l1, l2
698 end type
700 contains
702 subroutine reallocate(x)
703   class(t1), allocatable :: x
704   allocate(t2(l1=1, l2=2):: x)
705 end subroutine
707 end module
709 program p
710   use m1
712   class(t1), allocatable :: x
714   call reallocate(x)
715   ! The new length type parameters need to be propagated at this point.
717   ! rest of code using `x`
718 end program
721 The proposed solution is to add indirection in the `f18Addendum` and store the
722 length type parameters in a separate block instead of directly in the addendum.
723 At the moment the storage for the length type parameters is allocated once as
724 a `std::int64_t` array.
726 **New f18Addendum**
727 ```cpp
728 {*derivedType_, *lenParamValues_}
731 Adding the indirection in the descriptor's addendum requires to manage the
732 lifetime of the block holding the length type parameter values.
734 Here are some thoughts of how to manage it:
735 - For allocatables, the space for the LEN parameters can be allocated as part of
736   the same malloc as the payload data.
737 - For automatics, same thing, if we implement automatics as allocatables.
738 - For monomorphic local variables, the LEN parameters would be in a little array
739   on the stack. Or we could treat any variable or component with LEN parameters
740   as being automatic even when it's monomorphic.
741 - For pointers and dummy arguments, we can just copy the pointer in the addendum
742   from the target to the pointer or dummy descriptor.
743 - For dynamically allocated descriptors, the LEN parameter values could just
744   follow the addendum in the same malloc.
746 The addendum of an array sections/sub-objects would point to the same block than
747 the base object.
749 In some special cases, a descriptor needs to be passed between the caller and
750 the callee. This includes array of PDTs and derived-type with PDT components.
751 The example describe one of the corner case where the length type parameter
752 would be lost if the descriptor is not passed.
754 ### Example that require a descriptor
756 Because of the length type parameters store in the addendum, it is required in
757 some case to pass the PDT with a descriptor to preserve the length type
758 parameters information. The example below illustrates such a case.
760 **Fortran**
761 ```fortran
762 module m
763 type t
764  integer :: i
765 end type
767 type, extends(t) :: t2(l)
768   integer, len :: l
769   real :: x(l)
770 end type
772 type base
773   type(t2(20)) :: pdt_component
774 end type
776 class(t), pointer :: p(:)
778 contains
780 subroutine foo(x, n)
781   integer :: n
782   type(base), target :: x(n)
783   ! Without descriptor, the actual argument is a zero-sized array. The length
784   ! type parameters of `x(n)%pdt_component` are not propagated from the caller.
786   ! A descriptor local to this function is created to pass the array section
787   ! in bar. 
788   call bar(x%pdt_component)
789 end subroutine
791 subroutine bar(x)
792   type(t2(*)), target :: x(:)
793   p => x
794 end subroutine
796 subroutine test()
797   type(base), target :: x(100)
798   call foo(x(1:-1:1), 0)
799   select type (p)
800    type is (t2(*))
801     ! This type parameters of x(1:60:3) in foo must still live here
802     print *, p%l
803    class default
804      print *, "something else"
805   end select
806 end subroutine
807 end module
809   use m
810   call test()
814 Because of the use case described above, PDTs, array of PDTs or derived-type
815 with PDT components will be passed by descriptor.
817 ## FIR operations with length type parameters
819 Couple of operations have length type parameters as operands already in their
820 design. For some operations, length type parameters are likely needed with
821 the two proposed solution. Some other operation like the array operations, the
822 operands are not needed when dealing with a descriptor since the length type
823 parameters are in it.
825 The operations will be updated if needed during the implementation of the
826 chosen solution.
828 #### `fir.alloca`
830 This primitive operation is used to allocate an object on the stack. When
831 allocating a PDT, the length type parameters are passed to the
832 operation so its size can be computed accordingly.
834 **FIR**
836 %i = arith.constant 10 : i32
837 %0 = fir.alloca !fir.type<_QMmod1Tpdt{i:i32,data:!fir.array<?xf32>}> (%i : i32)
838 // %i is the ssa value of the length type parameter
841 #### `fir.allocmem`
843 This operation is used to create a heap memory reference suitable for storing a
844 value of the given type. When creating a PDT, the length type parameters are
845 passed so the size can be computed accordingly.
847 **FIR**
849 %i = arith.constant 10 : i32
850 %0 = fir.alloca !fir.type<_QMmod1Tpdt{i:i32,data:!fir.array<?xf32>}> (%i : i32)
851 // ...
852 fir.freemem %0 : !fir.type<_QMmod1Tpdt{i:i32,data:!fir.array<?xf32>}>
855 #### `fir.embox`
857 The `fir.embox` operation create a boxed reference value. In the case of PDTs
858 the length type parameters can be passed as well to the operation.
860 **Fortran**
861 ```fortran
862 subroutine local()
863   type(t(2)) :: x ! simple local PDT
864   ! ...
865 end subroutine
868 **FIR**
870 func.func @_QMpdt_initPlocal() {
871   %c2_i32 = arith.constant 2 : i32
872   %0 = fir.alloca !fir.type<_QMpdt_initTt{l:i32,i:!fir.array<?xi32>}> (%c2 : i32)
873        {bindc_name = "x", uniq_name = "_QMpdt_initFlocalEx"}
874   // The fir.embox operation is responsible to place the provided length type
875   // parameters in the descriptor addendum so they are available to the runtime
876   // call later.
877   %1 = fir.embox %0 : (!fir.ref<!fir.type<_QMpdt_initTt{l:i32,i:!fir.array<?xi32>}>>) (typeparams %c2 : i32)
878        -> !fir.box<!fir.type<_QMpdt_initTt{l:i32,i:!fir.array<?xi32>}>>
879   %2 = fir.address_of(@_QQcl.2E2F6669725F7064745F6578616D706C652E66393000) : !fir.ref<!fir.char<1,22>>
880   %c8_i32 = arith.constant 8 : i32
881   %3 = fir.convert %1 : (!fir.box<!fir.type<_QMpdt_initTt{l:i32,i:!fir.array<?xi32>}>>) -> !fir.box<none>
882   %4 = fir.convert %2 : (!fir.ref<!fir.char<1,22>>) -> !fir.ref<i8>
883   %5 = fir.call @_FortranAInitialize(%3, %4, %c8_i32) : (!fir.box<none>, !fir.ref<i8>, i32) -> none
884   return
888 #### `fir.field_index`
890 The `fir.field_index` operation is used to generate a field offset value from
891 a field identifier in a derived-type. The operation takes length type parameter
892 values with a PDT so it can compute a correct offset.
894 **FIR**
896 %l = arith.constant 10 : i32
897 %1 = fir.field_index i, !fir.type<_QMpdt_initTt{l:i32,i:i32}> (%l : i32)
898 %2 = fir.coordinate_of %ref, %1 : (!fir.type<_QMpdt_initTt{l:i32,i:i32}>, !fir.field) -> !fir.ref<i32>
899 %3 = fir.load %2 : !fir.ref<i32>
900 return %3
903 #### `fir.len_param_index`
905 This operation is used to get the length type parameter offset in from a PDT.
907 **FIR**
909 func.func @_QPpdt_len_value(%arg0: !fir.box<!fir.type<t1{l:i32,!fir.array<?xi32>}>>) -> i32 {
910   %0 = fir.len_param_index l, !fir.box<!fir.type<t1{l:i32,!fir.array<?xi32>}>>
911   %1 = fir.coordinate_of %arg0, %0 : (!fir.box<!fir.type<t1{l:i32,!fir.array<?xi32>}>>, !fir.len) -> !fir.ref<i32>
912   %2 = fir.load %1 : !fir.ref<i32>
913   return %2 : i32
917 #### `fir.save_result`
919 Save the result of a function returning an array, box, or record type value into
920 a memory location given the shape and LEN parameters of the result. Length type
921 parameters is passed if the PDT is not boxed.
923 **FIR**
925 func.func @return_pdt(%buffer: !fir.ref<!fir.type<t2(l1:i32,l2:i32){x:f32}>>) {
926   %l1 = arith.constant 3 : i32
927   %l2 = arith.constant 5 : i32
928   %res = fir.call @foo() : () -> !fir.type<t2(l1:i32,l2:i32){x:f32}>
929   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
930   return
934 #### `fir.array_*` operations
936 The current design of the different `fir.array_*` operations include length type
937 parameters operands. This is designed to use PDT without descriptor directly in
938 FIR.
940 **FIR**
942 // Operation used with a boxed PDT does not need the length type parameters as
943 // they are directly retrieved from the box.
944 %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>}>>>
946 // In case the PDT would not be boxed, the length type parameters are needed to
947 // compute the correct addressing.
948 %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>>
953 ## Implementation choice
955 While both solutions have pros and cons, we want to implement the outlined
956 solution.
957 - The runtime was implemented with this solution in mind.
958 - The size of the descriptor does not need to be computed at runtime.
962 # Testing
964 - Lowering part is tested with LIT tests in tree
965 - PDTs involved a lot of runtime information so executable
966   tests will be useful for full testing.
970 # Current TODOs
971 Current list of TODOs in lowering:
972 - `flang/lib/Lower/Allocatable.cpp:461` not yet implement: derived type length parameters in allocate
973 - `flang/lib/Lower/Allocatable.cpp:645` not yet implement: deferred length type parameters
974 - `flang/lib/Lower/Bridge.cpp:454` not yet implemented: get length parameters from derived type BoxValue
975 - `flang/lib/Lower/ConvertExpr.cpp:341` not yet implemented: copy derived type with length parameters
976 - `flang/lib/Lower/ConvertExpr.cpp:993` not yet implemented: component with length parameters in structure constructor
977 - `flang/lib/Lower/ConvertExpr.cpp:1063` not yet implemented: component with length parameters in structure constructor
978 - `flang/lib/Lower/ConvertExpr.cpp:1146` not yet implemented: type parameter inquiry
979 - `flang/lib/Lower/ConvertExpr.cpp:2424` not yet implemented: creating temporary for derived type with length parameters
980 - `flang/lib/Lower/ConvertExpr.cpp:3742` not yet implemented: gather rhs LEN parameters in assignment to allocatable
981 - `flang/lib/Lower/ConvertExpr.cpp:4725` not yet implemented: derived type array expression temp with LEN parameters
982 - `flang/lib/Lower/ConvertExpr.cpp:6400` not yet implemented: PDT size
983 - `flang/lib/Lower/ConvertExpr.cpp:6419` not yet implemented: PDT offset
984 - `flang/lib/Lower/ConvertExpr.cpp:6679` not yet implemented: array expr type parameter inquiry
985 - `flang/lib/Lower/ConvertExpr.cpp:7135` not yet implemented: need to adjust type parameter(s) to reflect the final component
986 - `flang/lib/Lower/ConvertType.cpp:334` not yet implemented: parameterized derived types
987 - `flang/lib/Lower/ConvertType.cpp:370` not yet implemented: derived type length parameters
988 - `flang/lib/Lower/ConvertVariable.cpp:169` not yet implemented: initial-data-target with derived type length parameters
989 - `flang/lib/Lower/ConvertVariable.cpp:197` not yet implemented: initial-data-target with derived type length parameters
990 - `flang/lib/Lower/VectorSubscripts.cpp:121` not yet implemented: threading length parameters in field index op
991 - `flang/lib/Optimizer/Builder/BoxValue.cpp:60` not yet implemented: box value is missing type parameters
992 - `flang/lib/Optimizer/Builder/BoxValue.cpp:67` not yet implemented: mutable box value is missing type parameters
993 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:688` not yet implemented: read fir.box with length parameters
994 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:746` not yet implemented: generate code to get LEN type parameters
995 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:779` not yet implemented: derived type with type parameters
996 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:905` not yet implemented: allocatable and pointer components non deferred length parameters
997 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:917` not yet implemented: array component shape depending on length parameters
998 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:924` not yet implemented: get character component length from length type parameters
999 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:934` not yet implemented: lower component ref that is a derived type with length parameter
1000 - `flang/lib/Optimizer/Builder/FIRBuilder.cpp:956` not yet implemented: get length parameters from derived type BoxValue
1001 - `flang/lib/Optimizer/Builder/MutableBox.cpp:70` not yet implemented: updating mutablebox of derived type with length parameters
1002 - `flang/lib/Optimizer/Builder/MutableBox.cpp:168` not yet implemented: read allocatable or pointer derived type LEN parameters
1003 - `flang/lib/Optimizer/Builder/MutableBox.cpp:310` not yet implemented: update allocatable derived type length parameters
1004 - `flang/lib/Optimizer/Builder/MutableBox.cpp:505` not yet implemented: pointer assignment to derived with length parameters
1005 - `flang/lib/Optimizer/Builder/MutableBox.cpp:597` not yet implemented: pointer assignment to derived with length parameters
1006 - `flang/lib/Optimizer/Builder/MutableBox.cpp:740` not yet implemented: reallocation of derived type entities with length parameters
1009 Current list of TODOs in code generation:
1011 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:1034` not yet implemented: fir.allocmem codegen of derived type with length parameters
1012 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:1581` not yet implemented: generate call to calculate size of PDT
1013 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:1708` not yet implemented: fir.embox codegen of derived with length parameters
1014 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:1749` not yet implemented: reboxing descriptor of derived type with length parameters
1015 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:2229` not yet implemented: derived type with type parameters
1016 - `flang/lib/Optimizer/CodeGen/CodeGen.cpp:2256` not yet implemented: compute size of derived type with type parameters
1017 - `flang/lib/Optimizer/CodeGen/TypeConverter.h:257` not yet implemented: extended descriptor derived with length parameters
1019 Current list of TODOs in optimizations:
1021 - `flang/lib/Optimizer/Transforms/ArrayValueCopy.cpp:1007` not yet implemented: unhandled dynamic type parameters
1025 Resources:
1026 - [0] Fortran standard
1027 - [1] https://en.wikipedia.org/wiki/Dependent_type