modula2: Simplify REAL/LONGREAL/SHORTREAL node creation.
[official-gcc.git] / gcc / testsuite / gfortran.dg / merge_init_expr_2.f90
blobf4a838011376a37761cc16a1edd6f8f4523d787c
1 ! { dg-do compile }
2 ! { dg-options "-fdump-tree-original" }
3 ! { dg-require-visibility "" }
5 ! PR fortran/56649
6 ! MERGE was not properly compile-time simplified
8 ! Contributed by Bill Long
10 module m
11 implicit none
13 integer, parameter :: int32 = 4
14 type MPI_Datatype
15 integer :: i
16 end type MPI_Datatype
18 integer,private,parameter :: dik = kind(0)
19 type(MPI_Datatype),parameter,private :: MPIx_I4 = MPI_Datatype( 1275069467)
20 type(MPI_Datatype),parameter,private :: MPIx_I8 = MPI_Datatype( 1275070491)
21 type(MPI_Datatype),parameter :: MPI_INTEGER = merge(MPIx_I4, MPIx_I8, &
22 dik==int32)
23 contains
24 subroutine foo
25 integer :: check1
26 check1 = MPI_INTEGER%i
27 end subroutine foo
28 end module m
30 module m2
31 implicit none
32 integer, parameter :: int32 = 4
33 type MPI_Datatype
34 integer :: i
35 end type MPI_Datatype
37 integer,private,parameter :: dik = kind(0)
38 type(MPI_Datatype),parameter,private :: MPIx_I4 = MPI_Datatype( 1275069467)
39 type(MPI_Datatype),parameter,private :: MPIx_I8 = MPI_Datatype( 1275070491)
40 type(MPI_Datatype),parameter :: MPI_INTEGER(1) = merge([MPIx_I4], [MPIx_I8], &
41 [dik==int32])
42 contains
43 subroutine foo
44 logical :: check2
45 check2 = MPI_INTEGER(1)%i == 1275069467
46 end subroutine foo
47 end module m2
50 subroutine test
51 character(len=3) :: one, three
52 character(len=3), parameter :: two = "def"
53 logical, parameter :: true = .true.
54 three = merge (one, two, true)
55 end subroutine test
57 ! { dg-final { scan-tree-dump-times "check1 = 1275069467;" 1 "original" } }
58 ! { dg-final { scan-tree-dump-times "check2 = 1;" 1 "original" } }
59 ! { dg-final { scan-tree-dump-times "__builtin_memmove ..void .. &three, .void .. &one, 3.;" 1 "original" } }