Commit aa81272c by Ilmir Usmanov Committed by Cesar Philippidis

re PR fortran/63858 (fixed form OpenACC directive ICE with -fopenacc -fopenmp)

	PR fortran/63858

	gcc/fortran/
	* scanner.c (skip_oacc_attribute): Remove continue_flag parameter.
	Rename as ...
	(skip_free_oacc_sentinel): ... this.
	(skip_omp_attribute): Remove continue_flag parameter. Rename as ...
	(skip_free_omp_sentinel): ... this.
	(skip_free_comments): Update to call skip_free_oacc_sentinel and
	skip_free_omp_sentinel.
	(skip_fixed_omp_sentinel): New function.
	(skip_fixed_oacc_sentinel): New function.
	(skip_fixed_comments): Fix mix of OpenACC and OpenMP sentinels in
	continuation.

	gcc/testsuite/
	* goacc/omp-fixed.f: New test.
	* goacc/omp.f95: Add check for mis-matched omp and acc continuations.


Co-Authored-By: Cesar Philippidis <cesar@codesourcery.com>

From-SVN: r230872
parent af11fcfd
2015-11-25 Ilmir Usmanov <me@ilmir.us>
Cesar Philippidis <cesar@codesourcery.com>
PR fortran/63858
* scanner.c (skip_oacc_attribute): Remove continue_flag parameter.
Rename as ...
(skip_free_oacc_sentinel): ... this.
(skip_omp_attribute): Remove continue_flag parameter. Rename as ...
(skip_free_omp_sentinel): ... this.
(skip_free_comments): Update to call skip_free_oacc_sentinel and
skip_free_omp_sentinel.
(skip_fixed_omp_sentinel): New function.
(skip_fixed_oacc_sentinel): New function.
(skip_fixed_comments): Fix mix of OpenACC and OpenMP sentinels in
continuation.
2015-11-24 Steven G. Kargl <kargl@gcc.gnu.org>
PR fortran/68486
......
2015-11-25 Ilmir Usmanov <me@ilmir.us>
Cesar Philippidis <cesar@codesourcery.com>
PR fortran/63858
* goacc/omp-fixed.f: New test.
* goacc/omp.f95: Add check for mis-matched omp and acc continuations.
2015-11-25 Richard Biener <rguenther@suse.de>
PR middle-end/68528
......
! { dg-do compile }
! { dg-additional-options "-fopenmp" }
SUBROUTINE ICHI
INTEGER :: ARGC
ARGC = COMMAND_ARGUMENT_COUNT ()
!$OMP PARALLEL
!$ACC PARALLEL &
!$ACC& COPYIN(ARGC) ! { dg-error "directive cannot be specified within" }
IF (ARGC .NE. 0) THEN
CALL ABORT
END IF
!$ACC END PARALLEL
!$OMP END PARALLEL
END SUBROUTINE ICHI
SUBROUTINE NI
IMPLICIT NONE
INTEGER :: I
!$ACC PARALLEL &
!$OMP& DO ! { dg-error "Wrong OpenACC continuation" }
DO I = 1, 10
ENDDO
!$OMP PARALLEL &
!$ACC& LOOP ! { dg-error "Wrong OpenMP continuation" }
DO I = 1, 10
ENDDO
END SUBROUTINE NI
......@@ -63,4 +63,12 @@ contains
!$omp end parallel
!$acc end data
end subroutine roku
end module test
\ No newline at end of file
subroutine nana
!$acc parallel &
!$omp do ! { dg-error "Wrong OpenACC continuation" }
!$omp parallel &
!$acc loop ! { dg-error "Wrong OpenMP continuation" }
end subroutine nana
end module test
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment