summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/pr105152.f90
diff options
context:
space:
mode:
authorPaul Thomas <pault@gcc.gnu.org>2023-05-16 06:35:40 +0100
committerPaul Thomas <pault@gcc.gnu.org>2023-05-16 06:36:48 +0100
commit6c95fe9bc0553743098eeaa739f14b885050fa42 (patch)
tree09c84526255be12917976b667835c8b2036854f0 /gcc/testsuite/gfortran.dg/pr105152.f90
parent1c6ebfdf033d17db80d3723883f02dfaf612c29e (diff)
downloadgcc-6c95fe9bc0553743098eeaa739f14b885050fa42.tar.gz
Fortran: Fix an assortment of bugs
2023-05-16 Paul Thomas <pault@gcc.gnu.org> gcc/fortran PR fortran/105152 * interface.cc (gfc_compare_actual_formal): Emit an error if an unlimited polymorphic actual is not matched either to an unlimited or assumed type formal argument. PR fortran/100193 * resolve.cc (resolve_ordinary_assign): Emit an error if the var expression of an ordinary assignment is a proc pointer component. PR fortran/87496 * trans-array.cc (gfc_walk_array_ref): Provide assumed shape arrays coming from interface mapping with a viable arrayspec. PR fortran/103389 * trans-expr.cc (gfc_conv_intrinsic_to_class): Tidy up flagging of unlimited polymorphic 'class_ts'. (gfc_conv_gfc_desc_to_cfi_desc): Assumed type is unlimited polymorphic and should accept any actual type. PR fortran/104429 (gfc_conv_procedure_call): Replace dreadful kludge with a call to gfc_finalize_tree_expr. Avoid dereferencing a void pointer by giving it the pointer type of the actual argument. PR fortran/82774 (alloc_scalar_allocatable_subcomponent): Shorten the function name and replace the symbol argument with the se string length. If a deferred length character length is either not present or is not a variable, give the typespec a variable and assign the string length to that. Use gfc_deferred_strlen to find the hidden string length component. (gfc_trans_subcomponent_assign): Convert the expression before the call to alloc_scalar_allocatable_subcomponent so that a good string length is provided. (gfc_trans_structure_assign): Remove the unneeded derived type symbol from calls to gfc_trans_subcomponent_assign. gcc/testsuite/ PR fortran/105152 * gfortran.dg/pr105152.f90 : New test PR fortran/100193 * gfortran.dg/pr100193.f90 : New test PR fortran/87946 * gfortran.dg/pr87946.f90 : New test PR fortran/103389 * gfortran.dg/pr103389.f90 : New test PR fortran/104429 * gfortran.dg/pr104429.f90 : New test PR fortran/82774 * gfortran.dg/pr82774.f90 : New test
Diffstat (limited to 'gcc/testsuite/gfortran.dg/pr105152.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/pr105152.f9019
1 files changed, 19 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/pr105152.f90 b/gcc/testsuite/gfortran.dg/pr105152.f90
new file mode 100644
index 00000000000..561b2a6c75d
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr105152.f90
@@ -0,0 +1,19 @@
+! { dg-do compile }
+!
+! Contributed by Gerhard Steinmetz <gscfq@t-online.de>
+!
+program p
+ use iso_c_binding
+ type, bind(c) :: t
+ integer(c_int) :: a
+ end type
+ interface
+ function f(x) bind(c) result(z)
+ import :: c_int, t
+ type(t) :: x(:)
+ integer(c_int) :: z
+ end
+ end interface
+ class(*), allocatable :: y(:)
+ n = f(y) ! { dg-error "either an unlimited polymorphic or assumed type" }
+end