1 ! RUN: %python %S/test_errors.py %s %flang_fc1 -fopenmp
3 ! 2.11.3 allocate Directive
4 ! A type parameter inquiry cannot appear in an allocate directive.
8 type my_type(kind_param
, len_param
)
9 INTEGER, KIND
:: kind_param
10 INTEGER, LEN
:: len_param
14 type(my_type(2, 4)) :: my_var
16 CHARACTER(LEN
=32) :: w
17 INTEGER, DIMENSION(:), ALLOCATABLE
:: y
19 !ERROR: A type parameter inquiry cannot appear on the ALLOCATE directive
20 !$omp allocate(x%KIND)
22 !ERROR: A type parameter inquiry cannot appear on the ALLOCATE directive
25 !ERROR: A type parameter inquiry cannot appear on the ALLOCATE directive
26 !$omp allocate(y%KIND)
28 !ERROR: A type parameter inquiry cannot appear on the ALLOCATE directive
29 !$omp allocate(my_var%kind_param)
31 !ERROR: A type parameter inquiry cannot appear on the ALLOCATE directive
32 !$omp allocate(my_var%len_param)
34 end subroutine allocate