OpenCores
URL https://opencores.org/ocsvn/openrisc_2011-10-31/openrisc_2011-10-31/trunk

Subversion Repositories openrisc_2011-10-31

[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [gomp/] [allocatable_components_1.f90] - Rev 424

Go to most recent revision | Compare with Previous | Blame | View Log

! { dg-do compile }
!
! PR fortran/32467
! Derived types with allocatable components
!

MODULE test_allocatable_components
  type :: t
    integer, allocatable :: a(:)
  end type

CONTAINS
  SUBROUTINE test_copyin()
    TYPE(t), SAVE :: a

    !$omp threadprivate(a)
    !$omp parallel copyin(a)        ! { dg-error "has ALLOCATABLE components" }
      ! do something
    !$omp end parallel
  END SUBROUTINE

  SUBROUTINE test_copyprivate()
    TYPE(t) :: a

    !$omp single                    ! { dg-error "has ALLOCATABLE components" }
      ! do something
    !$omp end single copyprivate (a)
  END SUBROUTINE

  SUBROUTINE test_firstprivate
    TYPE(t) :: a

    !$omp parallel firstprivate(a)  ! { dg-error "has ALLOCATABLE components" }
      ! do something
    !$omp end parallel
  END SUBROUTINE

  SUBROUTINE test_lastprivate
    TYPE(t) :: a
    INTEGER :: i

    !$omp parallel do lastprivate(a)  ! { dg-error "has ALLOCATABLE components" }
      DO i = 1, 1
      END DO
    !$omp end parallel do
  END SUBROUTINE

  SUBROUTINE test_reduction
    TYPE(t) :: a(10)
    INTEGER :: i

    !$omp parallel do reduction(+: a)   ! { dg-error "must be of numeric type" }
    DO i = 1, SIZE(a)
    END DO
    !$omp end parallel do
  END SUBROUTINE
END MODULE

! { dg-final { cleanup-modules "test_allocatable_components" } }

Go to most recent revision | Compare with Previous | Blame | View Log

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.