Skip to content

Commit

Permalink
configury: check for modern type(*), dimension(..) syntax
Browse files Browse the repository at this point in the history
First try if "type(*), dimension(..) :: foo" works as-is
(e.g. without any pragma/directive).

Thanks Chris Parrott for bringing this to our attention

Refs. #11582

Signed-off-by: Gilles Gouaillardet <[email protected]>
  • Loading branch information
ggouaillardet authored and jsquyres committed Jul 9, 2024
1 parent 8d91c0a commit 1ce3f29
Showing 1 changed file with 34 additions and 27 deletions.
61 changes: 34 additions & 27 deletions config/ompi_fortran_check_ignore_tkr.m4
Original file line number Diff line number Diff line change
Expand Up @@ -72,16 +72,22 @@ AC_DEFUN([_OMPI_FORTRAN_CHECK_IGNORE_TKR], [
ompi_fortran_ignore_tkr_predecl=!
ompi_fortran_ignore_tkr_type=real

# Vendor-neutral, TYPE(*) syntax
# Vendor-neutral, TYPE(*), DIMENSION(..) syntax
OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB(
[!], [type(*)],
[TYPE(*), DIMENSION(*)],
[!], [type(*), DIMENSION(..)],[, ASYNCHRONOUS],
[TYPE(*), DIMENSION(..)],
[internal_ignore_tkr_happy=1], [internal_ignore_tkr_happy=0])
# Vendor-neutral, TYPE(*), DIMENSION(*) syntax
AS_IF([test $internal_ignore_tkr_happy -eq 0],
[OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB(
[!], [type(*), DIMENSION(*)],[],
[TYPE(*), DIMENSION(*)],
[internal_ignore_tkr_happy=1], [internal_ignore_tkr_happy=0])])

# GCC compilers
AS_IF([test $internal_ignore_tkr_happy -eq 0],
[OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB(
[!GCC\$ ATTRIBUTES NO_ARG_CHECK ::], [type(*), dimension(*)],
[!GCC\$ ATTRIBUTES NO_ARG_CHECK ::], [type(*), dimension(*)],[],
[!GCC\$ ATTRIBUTES NO_ARG_CHECK],
[internal_ignore_tkr_happy=1], [internal_ignore_tkr_happy=0])])
# LLVM compilers
Expand All @@ -93,27 +99,27 @@ AC_DEFUN([_OMPI_FORTRAN_CHECK_IGNORE_TKR], [
# Intel compilers
AS_IF([test $internal_ignore_tkr_happy -eq 0],
[OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB(
[!DEC\$ ATTRIBUTES NO_ARG_CHECK ::], [real, dimension(*)],
[!DEC\$ ATTRIBUTES NO_ARG_CHECK ::], [real, dimension(*)],[],
[!DEC\$ ATTRIBUTES NO_ARG_CHECK],
[internal_ignore_tkr_happy=1], [internal_ignore_tkr_happy=0])])
# Solaris Studio compilers
# Note that due to a compiler bug, we have been advised by Oracle to
# use the "character(*)" type
AS_IF([test $internal_ignore_tkr_happy -eq 0],
[OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB(
[!\$PRAGMA IGNORE_TKR], [character(*)],
[!\$PRAGMA IGNORE_TKR], [character(*)],[],
[!\$PRAGMA IGNORE_TKR],
[internal_ignore_tkr_happy=1], [internal_ignore_tkr_happy=0])])
# Cray compilers
AS_IF([test $internal_ignore_tkr_happy -eq 0],
[OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB(
[!DIR\$ IGNORE_TKR], [real, dimension(*)],
[!DIR\$ IGNORE_TKR], [real, dimension(*)],[],
[!DIR\$ IGNORE_TKR],
[internal_ignore_tkr_happy=1], [internal_ignore_tkr_happy=0])])
# IBM compilers
AS_IF([test $internal_ignore_tkr_happy -eq 0],
[OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB(
[!IBM* IGNORE_TKR], [real, dimension(*)],
[!IBM* IGNORE_TKR], [real, dimension(*)],[],
[!IBM* IGNORE_TKR],
[internal_ignore_tkr_happy=1], [internal_ignore_tkr_happy=0])])

Expand All @@ -132,13 +138,14 @@ AC_DEFUN([_OMPI_FORTRAN_CHECK_IGNORE_TKR], [
# functionality
# $1: pre-decl qualifier line -- likely a compiler directive
# $2: parameter type
# $3: message for AC-MSG-CHECKING
# $4: action to take if the test passes
# $5: action to take if the test fails
# $3: asynchronous keyword
# $4: message for AC-MSG-CHECKING
# $5: action to take if the test passes
# $6: action to take if the test fails
AC_DEFUN([OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB], [
OPAL_VAR_SCOPE_PUSH(msg)
AC_LANG_PUSH([Fortran])
AC_MSG_CHECKING([for Fortran compiler support of $3])
AC_MSG_CHECKING([for Fortran compiler support of $4])
AC_COMPILE_IFELSE(AC_LANG_PROGRAM([],[[!
! Autoconf puts "program main" at the top
implicit none
Expand Down Expand Up @@ -194,35 +201,35 @@ AC_DEFUN([OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB], [
end program

subroutine force_assumed_shape(a, count)
implicit none
integer :: count
real, dimension(:,:) :: a
call foo(a, count)
end subroutine force_assumed_shape

module check_ignore_tkr
interface
subroutine foobar(buffer, count)
$1 buffer
$2, intent(in) :: buffer
module mod
interface
subroutine bar(buffer, count)
$2, intent(in)$3 :: buffer
integer, intent(in) :: count
end subroutine foobar
end interface
end subroutine bar
end interface
end module

subroutine bar(var)
use check_ignore_tkr
implicit none
real, intent(inout) :: var(:, :, :)

call foobar(var(1,1,1), 1)
subroutine bogus(buffer, count)
use mod, only : bar
implicit none
$2, intent(in)$3 :: buffer
integer, intent(in) :: count
call bar(buffer, count)
! Autoconf puts "end" after the last line
]]),
[msg=yes
ompi_fortran_ignore_tkr_predecl="$1"
ompi_fortran_ignore_tkr_type="$2"
$4],
$5],
[msg=no
$5])
$6])
AC_MSG_RESULT($msg)
AC_LANG_POP([Fortran])
OPAL_VAR_SCOPE_POP
Expand Down

0 comments on commit 1ce3f29

Please sign in to comment.