modula2: Simplify REAL/LONGREAL/SHORTREAL node creation.
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_alloc_comp_8.f08
blob679bec3290221bd1df0e78c9aa158af9b150637f
1 ! { dg-do run }
2 ! { dg-options "-fcoarray=lib -lcaf_single" }
3 ! { dg-additional-options "-latomic" { target libatomic_available } }
5 ! Check that type conversion during caf_sendget_by_ref is done for components.
7 program main
9   implicit none
11   type :: mytype
12     integer :: i
13     integer :: i4 
14     integer(kind=1) :: i1
15     real :: r8
16     real(kind=4) :: r4
17     integer :: arr_i4(4)
18     integer(kind=1) :: arr_i1(4)
19     real :: arr_r8(4)
20     real(kind=4) :: arr_r4(4)
21   end type
23   type T
24     type(mytype), allocatable :: obj
25   end type T
27   type(T), save :: bar[*]
28   integer :: i4, arr_i4(4)
29   integer(kind=1) :: i1, arr_i1(4)
30   real :: r8, arr_r8(4)
31   real(kind=4) :: r4, arr_r4(4)
33   bar%obj = mytype(42, 4, INT(1, 1), 8.0, REAL(4.0, 4), (/ 1,2,3,4 /), &
34   &       INT((/ 5,6,7,8 /), 1), (/ 1.2,3.4,5.6,7.8 /), REAL( &
35   &       (/ 8.7,6.5,4.3,2.1 /), 4))
37   bar[1]%obj%i1 = bar[1]%obj%r4
38   if (bar%obj%i1 /= 4) stop 1
39   bar[1]%obj%i4 = bar[1]%obj%r8
40   if (bar%obj%i4 /= 8) stop 2
41   bar[1]%obj%arr_i1 = bar[1]%obj%arr_r4
42   if (any(bar%obj%arr_i1 /= (/ 8,6,4,2 /))) stop 3
43   bar[1]%obj%arr_i4 = bar[1]%obj%arr_r8
44   if (any(bar%obj%arr_i4 /= (/ 1,3,5,7 /))) stop 4
46   bar%obj%i1 = INT(1, 1)
47   bar%obj%i4 = 4
48   bar%obj%arr_i1 = INT((/ 5,6,7,8 /), 1)
49   bar%obj%arr_i4 = (/ 1,2,3,4 /)
50   bar[1]%obj%r4 = bar[1]%obj%i1
51   if (abs(bar%obj%r4 - 1.0) > 1E-4) stop 5
52   bar[1]%obj%r8 = bar[1]%obj%i4
53   if (abs(bar%obj%r8 - 4.0) > 1E-6) stop 6
54   bar[1]%obj%arr_r4 = bar[1]%obj%arr_i1
55   if (any(abs(bar%obj%arr_r4 - REAL((/ 5,6,7,8 /), 4)) > 1E-4)) stop 7
56   bar[1]%obj%arr_r8 = bar[1]%obj%arr_i4
57   if (any(abs(bar%obj%arr_r8 - (/ 1,2,3,4 /)) > 1E-6)) stop 8
58 end program