libgfortran/ChangeLog:
[official-gcc.git] / gcc / testsuite / gfortran.dg / merge_init_expr_2.f90
blob9b20310caf583c5f92dbbadbfec60fd632327414
1 ! { dg-do compile }
2 ! { dg-options "-fdump-tree-original" }
4 ! PR fortran/56649
5 ! MERGE was not properly compile-time simplified
7 ! Contributed by Bill Long
9 module m
10 implicit none
12 integer, parameter :: int32 = 4
13 type MPI_Datatype
14 integer :: i
15 end type MPI_Datatype
17 integer,private,parameter :: dik = kind(0)
18 type(MPI_Datatype),parameter,private :: MPIx_I4 = MPI_Datatype( 1275069467)
19 type(MPI_Datatype),parameter,private :: MPIx_I8 = MPI_Datatype( 1275070491)
20 type(MPI_Datatype),parameter :: MPI_INTEGER = merge(MPIx_I4, MPIx_I8, &
21 dik==int32)
22 contains
23 subroutine foo
24 integer :: check1
25 check1 = MPI_INTEGER%i
26 end subroutine foo
27 end module m
29 module m2
30 implicit none
31 integer, parameter :: int32 = 4
32 type MPI_Datatype
33 integer :: i
34 end type MPI_Datatype
36 integer,private,parameter :: dik = kind(0)
37 type(MPI_Datatype),parameter,private :: MPIx_I4 = MPI_Datatype( 1275069467)
38 type(MPI_Datatype),parameter,private :: MPIx_I8 = MPI_Datatype( 1275070491)
39 type(MPI_Datatype),parameter :: MPI_INTEGER(1) = merge([MPIx_I4], [MPIx_I8], &
40 [dik==int32])
41 contains
42 subroutine foo
43 logical :: check2
44 check2 = MPI_INTEGER(1)%i == 1275069467
45 end subroutine foo
46 end module m2
49 subroutine test
50 character(len=3) :: one, two, three
51 logical, parameter :: true = .true.
52 three = merge (one, two, true)
53 end subroutine test
55 ! { dg-final { scan-tree-dump-times "check1 = 1275069467;" 1 "original" } }
56 ! { dg-final { scan-tree-dump-times "check2 = 1;" 1 "original" } }
57 ! { dg-final { scan-tree-dump-times "__builtin_memmove ..void .. &three, .void .. &one, 3.;" 1 "original" } }
58 ! { dg-final { cleanup-tree-dump "original" } }