4 ! Derived types with allocatable components
7 MODULE test_allocatable_components
9 integer, allocatable
:: a(:)
13 SUBROUTINE test_copyin()
16 !$omp threadprivate(a)
17 !$omp parallel copyin(a)
22 SUBROUTINE test_copyprivate()
27 !$omp end single copyprivate (a)
30 SUBROUTINE test_firstprivate
33 !$omp parallel firstprivate(a)
38 SUBROUTINE test_lastprivate
42 !$omp parallel do lastprivate(a)
48 SUBROUTINE test_reduction
52 !$omp parallel do reduction(+: a) ! { dg-error "OMP DECLARE REDUCTION\[^\n\r\]*not found for type" }