@@ -72,16 +72,22 @@ AC_DEFUN([_OMPI_FORTRAN_CHECK_IGNORE_TKR], [
7272 ompi_fortran_ignore_tkr_predecl=!
7373 ompi_fortran_ignore_tkr_type= real
7474
75- # Vendor-neutral, TYPE(*) syntax
75+ # Vendor-neutral, TYPE(*), DIMENSION(..) syntax
7676 OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB(
77- [! ], [type(* )],
78- [TYPE(* ), DIMENSION(* )],
77+ [! ], [type(* ), DIMENSION(..)],[, ASYNCHRONOUS ],
78+ [TYPE(* ), DIMENSION(.. )],
7979 [internal_ignore_tkr_happy= 1], [internal_ignore_tkr_happy= 0])
80+ # Vendor-neutral, TYPE(*), DIMENSION(*) syntax
81+ AS_IF([test $internal_ignore_tkr_happy -eq 0],
82+ [OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB(
83+ [! ], [type(* ), DIMENSION(* )],[],
84+ [TYPE(* ), DIMENSION(* )],
85+ [internal_ignore_tkr_happy= 1], [internal_ignore_tkr_happy= 0])])
8086
8187 # GCC compilers
8288 AS_IF([test $internal_ignore_tkr_happy -eq 0],
8389 [OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB(
84- [! GCC\$ ATTRIBUTES NO_ARG_CHECK ::], [type(* ), dimension(* )],
90+ [! GCC\$ ATTRIBUTES NO_ARG_CHECK ::], [type(* ), dimension(* )],[],
8591 [! GCC\$ ATTRIBUTES NO_ARG_CHECK],
8692 [internal_ignore_tkr_happy= 1], [internal_ignore_tkr_happy= 0])])
8793 # LLVM compilers
@@ -93,27 +99,27 @@ AC_DEFUN([_OMPI_FORTRAN_CHECK_IGNORE_TKR], [
9399 # Intel compilers
94100 AS_IF([test $internal_ignore_tkr_happy -eq 0],
95101 [OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB(
96- [! DEC\$ ATTRIBUTES NO_ARG_CHECK ::], [real, dimension(* )],
102+ [! DEC\$ ATTRIBUTES NO_ARG_CHECK ::], [real, dimension(* )],[],
97103 [! DEC\$ ATTRIBUTES NO_ARG_CHECK],
98104 [internal_ignore_tkr_happy= 1], [internal_ignore_tkr_happy= 0])])
99105 # Solaris Studio compilers
100106 # Note that due to a compiler bug, we have been advised by Oracle to
101107 # use the "character(*)" type
102108 AS_IF([test $internal_ignore_tkr_happy -eq 0],
103109 [OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB(
104- [! \$ PRAGMA IGNORE_TKR], [character(* )],
110+ [! \$ PRAGMA IGNORE_TKR], [character(* )],[],
105111 [! \$ PRAGMA IGNORE_TKR],
106112 [internal_ignore_tkr_happy= 1], [internal_ignore_tkr_happy= 0])])
107113 # Cray compilers
108114 AS_IF([test $internal_ignore_tkr_happy -eq 0],
109115 [OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB(
110- [! DIR\$ IGNORE_TKR], [real, dimension(* )],
116+ [! DIR\$ IGNORE_TKR], [real, dimension(* )],[],
111117 [! DIR\$ IGNORE_TKR],
112118 [internal_ignore_tkr_happy= 1], [internal_ignore_tkr_happy= 0])])
113119 # IBM compilers
114120 AS_IF([test $internal_ignore_tkr_happy -eq 0],
115121 [OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB(
116- [! IBM* IGNORE_TKR], [real, dimension(* )],
122+ [! IBM* IGNORE_TKR], [real, dimension(* )],[],
117123 [! IBM* IGNORE_TKR],
118124 [internal_ignore_tkr_happy= 1], [internal_ignore_tkr_happy= 0])])
119125
@@ -132,13 +138,14 @@ AC_DEFUN([_OMPI_FORTRAN_CHECK_IGNORE_TKR], [
132138# functionality
133139# $1: pre-decl qualifier line -- likely a compiler directive
134140# $2: parameter type
135- # $3: message for AC-MSG-CHECKING
136- # $4: action to take if the test passes
137- # $5: action to take if the test fails
141+ # $3: asynchronous keyword
142+ # $4: message for AC-MSG-CHECKING
143+ # $5: action to take if the test passes
144+ # $6: action to take if the test fails
138145AC_DEFUN([OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB], [
139146 OPAL_VAR_SCOPE_PUSH(msg)
140147 AC_LANG_PUSH([Fortran])
141- AC_MSG_CHECKING([for Fortran compiler support of $3 ])
148+ AC_MSG_CHECKING([for Fortran compiler support of $4 ])
142149 AC_COMPILE_IFELSE(AC_LANG_PROGRAM([],[[!
143150! Autoconf puts " program main" at the top
144151 implicit none
@@ -194,35 +201,35 @@ AC_DEFUN([OMPI_FORTRAN_CHECK_IGNORE_TKR_SUB], [
194201 end program
195202
196203 subroutine force_assumed_shape(a, count)
204+ implicit none
197205 integer :: count
198206 real, dimension(:,:) :: a
199207 call foo(a, count)
200208 end subroutine force_assumed_shape
201209
202- module check_ignore_tkr
203- interface
204- subroutine foobar(buffer, count)
205- $1 buffer
206- $2 , intent(in) :: buffer
210+ module mod
211+ interface
212+ subroutine bar(buffer, count)
213+ $2 , intent(in)$3 :: buffer
207214 integer, intent(in) :: count
208- end subroutine foobar
209- end interface
215+ end subroutine bar
216+ end interface
210217 end module
211218
212- subroutine bar(var )
213- use check_ignore_tkr
214- implicit none
215- real , intent(inout) :: var(:, :, :)
216-
217- call foobar(var(1,1,1), 1 )
219+ subroutine bogus(buffer, count )
220+ use mod, only : bar
221+ implicit none
222+ $2 , intent(in) $3 :: buffer
223+ integer, intent(in) :: count
224+ call bar(buffer, count )
218225! Autoconf puts " end" after the last line
219226]]),
220227 [msg= yes
221228 ompi_fortran_ignore_tkr_predecl= " $1 "
222229 ompi_fortran_ignore_tkr_type= " $2 "
223- $4 ],
230+ $5 ],
224231 [msg= no
225- $5 ])
232+ $6 ])
226233 AC_MSG_RESULT($msg )
227234 AC_LANG_POP([Fortran])
228235 OPAL_VAR_SCOPE_POP
0 commit comments