nvptx, libgfortran: Switch out of "minimal" mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / structure_constructor_6.f03
blob9952e2e7c93c929a2efaf70c5ace409a08ac6cf7
1 ! { dg-do compile }
2 ! Structure constructor with default initialization, test that an error is
3 ! emitted for components without default initializer missing value.
5 PROGRAM test
6   IMPLICIT NONE
8   ! Structure of basic data types
9   TYPE :: basics_t
10     INTEGER :: i = 42
11     REAL :: r
12     COMPLEX :: c = (0., 1.)
13   END TYPE basics_t
15   TYPE(basics_t) :: basics
17   basics = basics_t (i = 42) ! { dg-error "No initializer for component 'r'" }
18   basics = basics_t (42) ! { dg-error "No initializer for component 'r'" }
20 END PROGRAM test