[to-be-committed] [RISC-V] Use Zbkb for general 64 bit constants when profitable
[official-gcc.git] / gcc / testsuite / gfortran.dg / structure_constructor_4.f03
blob8a5aaa7a23f9f9e3da25216f9fdc94964abc472d
1 ! { dg-do compile }
2 ! Structure constructor with component naming, test that an error is emitted if
3 ! a component is given two initializers.
5 PROGRAM test
6   IMPLICIT NONE
8   ! Structure of basic data types
9   TYPE :: basics_t
10     INTEGER :: i
11     REAL :: r
12   END TYPE basics_t
14   TYPE(basics_t) :: basics
16   basics = basics_t (42, r=1.5, i=15) ! { dg-error "'i' is initialized twice" }
17   basics = basics_t (42, r=1., r=-2.) ! { dg-error "has already appeared in the current argument list" }
19 END PROGRAM test