- 신규로 표시
- 북마크
- 구독
- 소거
- RSS 피드 구독
- 강조
- 인쇄
- 부적절한 컨텐트 신고
Hi, this is my first post in this forum!
I found discussions of similar issues (i.e. leading to the same error message) elsewhere in this forum and online, but they don't cover or offer an explanation for the issue I'm observing.
Consider the following piece of code:
[bash]! Defines a derived type for NxN matrices and
! overloads the intrinsic function CONJG:
MODULE matrices
IMPLICIT NONE
PRIVATE
PUBLIC :: Matrix, conjg
INTEGER, PARAMETER :: sp = KIND(0.e0)
INTEGER, PARAMETER :: n = 7
TYPE :: Matrix
COMPLEX(sp) :: idx(n,n)
END TYPE Matrix
INTERFACE conjg
MODULE PROCEDURE cjg_mat
END INTERFACE conjg
CONTAINS
PURE ELEMENTAL FUNCTION cjg_mat(u) RESULT(v)
TYPE(Matrix), INTENT(in) :: u
TYPE(Matrix) :: v
v%idx = CONJG(TRANSPOSE(u%idx))
END FUNCTION cjg_mat
END MODULE matrices
! Defines a derived type for SU(2) matrices and
! overloads the intrinsic function CONJG:
MODULE SU2_matrices
IMPLICIT NONE
PRIVATE
PUBLIC :: SU2, conjg
INTEGER, PARAMETER :: dp = KIND(0.d0)
TYPE :: SU2
COMPLEX(dp) :: a,b
END TYPE SU2
INTERFACE conjg
MODULE PROCEDURE cjg_SU2
END INTERFACE conjg
CONTAINS
PURE ELEMENTAL FUNCTION cjg_SU2(u) RESULT(v)
TYPE(SU2), INTENT(in) :: u
TYPE(SU2) :: v
v%a = CONJG(u%a)
v%b = -u%b
END FUNCTION cjg_SU2
END MODULE SU2_matrices
! Collects the types and functions for several kinds
! of matrices and makes them PUBLIC (pipelining)
MODULE degrees_of_freedom
USE matrices
USE SU2_matrices
PUBLIC :: Matrix, SU2, conjg
END MODULE degrees_of_freedom
! Defines a derived type for rank-4 arrays of Matrix objects
! and overloads the intrinsic/overloaded elemental function
! CONJG
MODULE fields
USE degrees_of_freedom
! USE matrices
! USE SU2_matrices
IMPLICIT NONE
PRIVATE
PUBLIC :: Matrix_Field, conjg
INTEGER, PARAMETER :: L(4) = 10
TYPE :: Matrix_Field
TYPE(Matrix), DIMENSION(L(1),L(2),L(3),L(4)) :: site
END TYPE Matrix_Field
INTERFACE conjg
MODULE PROCEDURE cjg_matf
END INTERFACE conjg
CONTAINS
PURE ELEMENTAL FUNCTION cjg_matf(u) RESULT(v)
TYPE(Matrix_Field), INTENT(in) :: u
TYPE(Matrix_Field) :: v
v%site = CONJG(u%site)
END FUNCTION cjg_matf
END MODULE fields[/bash]
The code is simple, and all it does is to define two new derived data types in the first two modules, each with an overloading of the intrinsic elemental function CONJG; the third module collects the public definitions of the first two modules; and the fourth module uses the definitions in the third moduleto contruct a new derived data type, and yet another overloading of CONJG.
When I compile this code with ifort -c test.f90, it gives me the following error:
test.f90(57): warning #6738: The type/rank/keyword signature for this specific procedure matches another specific procedure that shares the same generic-name. [DEGREES_OF_FREEDOM^MATRICES^CJG_MAT]
USE degrees_of_freedom
-------^
test.f90(57): warning #6738: The type/rank/keyword signature for this specific procedure matches another specific procedure that shares the same generic-name. [DEGREES_OF_FREEDOM^SU2_MATRICES^CJG_SU2]
USE degrees_of_freedom
-------^
test.f90(74): error #8032: Generic procedure reference has two or more specific procedure with the same type/rank/keyword signature. [CONJG]
v%site = CONJG(u%site)
---------------^
compilation aborted for test.f90 (code 1)
Why does this happen? I thought that the generic interface distinguished arguments by type, which is a common reason for the appearence of this error message, but the types are different (and I even declared their components with different kinds).
If in the MODULE fields I use the first and second modules directly and neglect the third module
[bash]! USE degrees_of_freedom
USE matrices
USE SU2_matrices[/bash]
then the error message disappears and the code compiles successfully.
Also, if I change the name of the overloaded function to something different from CONJG, the code compiles successfully even if I use the third (intermediate) MODULE degrees_of_freedom. The same error message shows up if I replace CONJG by TRANSPOSE, for example.
I know that I can solve the problem by changing the names of the functions, or by neglecting the intermediate module, but I'd still like to know why Intel Fortran returns this error message. Is it predicted in the Fortran Standard, or is it a bug of the compiler. Both GNU and PGI Fortran compilers compile the code succesfully.
Thanks,
_helvio_
1 솔루션
- 신규로 표시
- 북마크
- 구독
- 소거
- RSS 피드 구독
- 강조
- 인쇄
- 부적절한 컨텐트 신고
Ok, that's subtly different - you moved the PUBLIC declarations. With them after the INTERFACE, I see the errors, and I think that's a bug. The workaround is to move the PUBLIC declarations to just after the PRIVATE, as you had in your original post. I will double-check the standard, and if this is a bug, will let the developers know - thanks.
링크가 복사됨
7 응답
- 신규로 표시
- 북마크
- 구독
- 소거
- RSS 피드 구독
- 강조
- 인쇄
- 부적절한 컨텐트 신고
Which compiler version are you using? I can't reproduce an error going back to 12.0.4.
- 신규로 표시
- 북마크
- 구독
- 소거
- RSS 피드 구독
- 강조
- 인쇄
- 부적절한 컨텐트 신고
I am using the Intel Fortran Compiler version 12.1.5 on Linux Ubuntu 12.04 LTS. I installed the most recent version just a week ago or so.
_helvio_
- 신규로 표시
- 북마크
- 구독
- 소거
- RSS 피드 구독
- 강조
- 인쇄
- 부적절한 컨텐트 신고
Can you get the error by compiling just the source you posted? I can't.
- 신규로 표시
- 북마크
- 구독
- 소거
- RSS 피드 구독
- 강조
- 인쇄
- 부적절한 컨텐트 신고
It is weird, I get the same error everytime. I have a very large code that reproduces the same error message, and I created the small example above to show it. I appended a screenshot and the original source.
_helvio_
PS: Hm, I don't know if the files were uploaded correctly, I can't find them in my post...Ok, I think the files are correctly posted now.
- 신규로 표시
- 북마크
- 구독
- 소거
- RSS 피드 구독
- 강조
- 인쇄
- 부적절한 컨텐트 신고
Ok, that's subtly different - you moved the PUBLIC declarations. With them after the INTERFACE, I see the errors, and I think that's a bug. The workaround is to move the PUBLIC declarations to just after the PRIVATE, as you had in your original post. I will double-check the standard, and if this is a bug, will let the developers know - thanks.
- 신규로 표시
- 북마크
- 구독
- 소거
- RSS 피드 구독
- 강조
- 인쇄
- 부적절한 컨텐트 신고
I was careless about which version I pasted, and I didn't notice the location of the PUBLIC statements. I did what you suggested and I don't get an error now. I usually declare PUBLIC statements at the end of the module's global scope for aestetic reasons only, I don't remember any restriction about this in the Fortran standard. Anyway, this is something that occurs only with intrinsic functions (but the error occurs even if I declare INTRINSIC :: CONJG inside the relevant routines).
Many thanks!
_helvio_
- 신규로 표시
- 북마크
- 구독
- 소거
- RSS 피드 구독
- 강조
- 인쇄
- 부적절한 컨텐트 신고
It looks as if we've already fixed this for the 13.0 compiler, due out in about a month.