tree-optimization/113385 - wrong loop father with early exit vectorization
[official-gcc.git] / gcc / testsuite / gfortran.dg / gomp / declare-variant-19.f90
blobd387f5e90659de5acd1cb1aec03c3880826f466e
1 ! { dg-do compile }
3 ! Test Fortran-specific compilation failures.
5 module main
6 implicit none
8 interface base_gen
9 subroutine base_gen_int (x)
10 integer :: x
11 end subroutine
13 subroutine base_gen_real (x)
14 real :: x
15 end subroutine
16 end interface
18 interface
19 subroutine base_p ()
20 end subroutine
21 end interface
23 procedure (base_p), pointer :: base_proc_ptr
25 !$omp declare variant (base_entry: variant) match (construct={parallel}) ! { dg-error "The base name at .1. must not be an entry name" }
26 !$omp declare variant (base_proc_ptr: variant) match (construct={parallel}) ! { dg-error "The base name at .1. must not be a procedure pointer" }
27 !$omp declare variant (base_gen: variant2) match (construct={parallel}) ! { dg-error "The base name at .1. must not be a generic name" }
28 !$omp declare variant (variant) match (construct={parallel}) ! { dg-error "The base name for 'declare variant' must be specified at .1." }
30 contains
31 subroutine base ()
32 entry base_entry
33 end subroutine
35 subroutine base2 ()
36 !$omp declare variant (variant2) match (construct={parallel}) ! { dg-error "variant .variant2. and base .base2. at .1. have incompatible types: .variant2. has the wrong number of arguments" }
37 end subroutine
39 subroutine base3 ()
40 !$omp declare variant (base: variant2) match (construct={parallel}) ! { dg-error "The base name at .1. does not match the name of the current procedure" }
41 end subroutine
43 subroutine variant ()
44 end subroutine
46 subroutine variant2 (x)
47 integer :: x
48 end subroutine
49 end module