PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / structure_constructor_5.f03
blobe81203f6199eb46a4a9b4fe81823cf23460f5b4f
1 ! { dg-do run }
2 ! Structure constructor with default initialization.
4 PROGRAM test
5   IMPLICIT NONE
7   ! Type with all default values
8   TYPE :: quasiempty_t
9     CHARACTER(len=5) :: greeting = "hello"
10   END TYPE quasiempty_t
12   ! Structure of basic data types
13   TYPE :: basics_t
14     INTEGER :: i = 42
15     REAL :: r
16     COMPLEX :: c = (0., 1.)
17   END TYPE basics_t
19   TYPE(quasiempty_t) :: empty
20   TYPE(basics_t) :: basics
22   empty = quasiempty_t ()
23   IF (empty%greeting /= "hello") THEN
24     STOP 1
25   END IF
27   basics = basics_t (r = 1.5)
28   IF (basics%i /= 42 .OR. basics%r /= 1.5 .OR. basics%c /= (0., 1.)) THEN
29     STOP 2
30   END IF
32   basics%c = (0., 0.) ! So we see it's surely gotten re-initialized
33   basics = basics_t (1, 5.1)
34   IF (basics%i /= 1 .OR. basics%r /= 5.1 .OR. basics%c /= (0., 1.)) THEN
35     STOP 3
36   END IF
38 END PROGRAM test