- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I have a module with a number of subroutines. Some of the subroutines use calls to the two-argument bessel function bessel_jn(n, x). When I add a new subroutine to the module that uses the three-argument bessel function bessel_jn(m1, m2, x), the compiler tells me that this function is not recognized and is therefore assumed to be external. Why is it refusing to recognize the three-argument bessel function?
Thanks!
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
My guess is the the type/kind of the parameters and result variable are not correct
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I think that the Bessel functions J and Y were added to the list of intrinsic functions in Fortran 2008; they were not present in Fortran 2003. Which version of the compiler did you use? Please show enough of the source code to help us see what went wrong. In particular, show the function references, and show the declarations of the arguments and the function, if any.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Please also show the complete and exact text of ALL the error messages. The one you mention is usually preceded by another which is much more detailed.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Below is the relevant text of the problematic subroutine I was adding to the module. When I attempt to compile it (Intel Parallel Studio XE 2018 in Visual Studio 2015), I get the following error messages:
subroutine CCBesselChebMoments(n, a, b, gamm, NM, J, ErrFlag)
!------------------------------------------------------------------------------
! Evaluates the Bessel-Chebyshev moments between a and b of orders 0:NM
! as functions of gamma:
!
! J(k) = integral from r = a to r = b of Tk(x) * Jn(gamm*r)
!
! where x = 2*(r - a)/(b - a) - 1, 0 <= k <= NM.
!------------------------------------------------------------------------------
use MKL_DFT_TYPE !For FFT
use MKL_DFTI !For FFT
implicit none
integer, intent(in) :: n !Bessel function order
real*8, intent(in) :: a, b !Endpoints of region of integration
real*8, intent(in) :: gamm !Value of the moment variable
integer, intent(in) :: NM !Maximum order of the moments
real*8, dimension(:), allocatable, intent(out) :: J !The moments
integer, intent(out) :: ErrFlag
!-----Local variables.
integer status, NQ, k
type(DFTI_DESCRIPTOR), POINTER :: FFT_Handle
real*8, dimension(:), allocatable :: aux, w
real*8 h2, xq, rq, JB(n+1)
!
!-----Initialize.
!
ErrFlag = 0
if (allocated(J)) deallocate (J)
allocate (J(0:NM))
J = 0.d0
if (b .le. a) return
h2 = (b - a)/2.d0
!
!-----Set number of Clenshaw-Curtis quadrature points.
!-----Note: The choice below for NQ assumes Jn can be represented by a polynomial of order ceiling(gamma*h)
!
NQ = NM + ceiling(gamm*2.d0*h2)
NQ = NQ + mod(NQ, 2) !NQ must be an even number
!
!-----Quadrature.
!
call CCWts(-1.d0, 1.d0, NQ, w, ErrFlag) !Evaluate Clenshaw-Curtis quadrature weights
if (ErrFlag .ne. 0) then
return
end if
allocate (aux(0:2*NQ+2)) !Storage for array to be transformed
aux = 0.d0
do k = 0, NQ
xq = cos(pi*k/dble(NQ))
rq = a + h2*(1.d0 + xq)
xq = gamm*rq
JB = bessel_jn(0, n, xq)
aux(k) = w(NQ-k)*JB(n+1)
end do
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I added "RETURN" and "END" to the code that you gave, and I find that the 2016U8 and 2018U3 compilers compiled the subroutine code without any messages.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Yes, I have only observed this compiler problem when this subroutine is included in a module and the module has other subroutines that use the two-argument bessel_jn. For example, if you copy the subroutine I posted (and add the return and end subroutine statements as you did) into a module, and compile the module, it compiles without a problem. But if you then paste another copy of this subroutine into the module, (with a different subroutine name) and change the three-argement bessel_jn to a two-argument bessel_jn in this new subroutine, the resulting module will not compile and will return the error messages I posted in my previous message. It appears that a module can only use either the two-argument bessel_jn, or the three-argument bessel_jn, but not both.
Thanks,
steve j
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Here is a simplified code sample that produces the error. The first subroutine in the module uses the two-argument bessel_jn while the second subroutine uses the three-argument version. When I attempt to compile this module, I get the errors I posted previously.
steve j
module Test_bessel_jn
contains
!------------------------------------------------------------------------------
subroutine Sub1(n, x, J)
!------------------------------------------------------------------------------
implicit none
integer, intent(in) :: n
real*8, intent(in) :: x
real*8, intent(out) :: J
!
J = bessel_jn(n, x)
return
end subroutine
!------------------------------------------------------------------------------
subroutine Sub2(n, x, J)
!------------------------------------------------------------------------------
implicit none
integer, intent(in) :: n
real*8, intent(in) :: x
real*8, intent(out) :: J
real*8 JB(n+1)
!
JB = bessel_jn(0, n, x)
J = JB(n+1)
return
end subroutine
end module
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I agree that this is a compiler bug. The compiler is getting confused by the appearance of two different forms of BESSEL_JN in the compilation. Please report this to Intel at https://supporttickets.intel.com/?lang=en-US
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page