From: monir on
On Jul 27, 3:57 pm, nos...(a)see.signature (Richard Maine) wrote:
> monir <mon...(a)rogers.com> wrote:
> > On Jul 27, 3:00 pm, nos...(a)see.signature (Richard Maine) wrote:
> > > monir <mon...(a)rogers.com> wrote:
>

Hello;

I'd very much appreciate if someone has the patience to look at the
following abbreviated sample code and identify the problem.
I've tried few "guesses" with no luck!

MODULE nrtype
INTEGER, PARAMETER :: I4B = SELECTED_INT_KIND(9)
INTEGER, PARAMETER :: I2B = SELECTED_INT_KIND(4)
INTEGER, PARAMETER :: I1B = SELECTED_INT_KIND(2)
INTEGER, PARAMETER :: SP = KIND(1.0)
INTEGER, PARAMETER :: DP = KIND(1.0D0)
REAL, ..............................
....................................
END MODULE nrtype

MODULE nr
INTERFACE pythag
Function pythag_dp(a,b)
USE nrtype
REAL(DP), INTENT(IN) :: a,b
REAL(DP) :: pythag_dp
End Function pythag_dp
Function pythag_sp(a,b)
USE nrtype
REAL(SP), INTENT(IN) :: a,b
REAL(SP) :: pythag_sp
End Function pythag_sp
END INTERFACE

INTERFACE svbksb
Subroutine svbksb_dp(u,w,v,b,x)
USE nrtype
REAL(DP), DIMENSION(:,:), INTENT(IN) :: u,v
REAL(DP), DIMENSION(:), INTENT(IN) :: w,b
REAL(DP), DIMENSION(:), INTENT(OUT) :: x
End Subroutine svbksb_dp
Subroutine svbksb_sp(u,w,v,b,x)
USE nrtype
REAL(SP), DIMENSION(:,:), INTENT(IN) :: u,v
REAL(SP), DIMENSION(:), INTENT(IN) :: w,b
REAL(SP), DIMENSION(:), INTENT(OUT) :: x
End Subroutine svbksb_sp
END INTERFACE

INTERFACE svdcmp
Subroutine svdcmp_dp(a,w,v)
USE nrtype
REAL(DP), DIMENSION(:,:), INTENT(INOUT) :: a
REAL(DP), DIMENSION(:), INTENT(OUT) :: w
REAL(DP), DIMENSION(:,:), INTENT(OUT) :: v
End Subroutine svdcmp_dp
Subroutine svdcmp_sp(a,w,v)
USE nrtype
REAL(SP), DIMENSION(:,:), INTENT(INOUT) :: a
REAL(SP), DIMENSION(:), INTENT(OUT) :: w
REAL(SP), DIMENSION(:,:), INTENT(OUT) :: v
End Subroutine svdcmp_sp
END INTERFACE
.........................
END MODULE nr

MODULE nrF90svd_Routines
contains
Subroutine svdcmp_dp(a,w,v)
USE nrtype
USE nr, ONLY : pythag
IMPLICIT NONE
REAL(DP), DIMENSION(:,:), INTENT(INOUT) :: a
REAL(DP), DIMENSION(:), INTENT(OUT) :: w
REAL(DP), DIMENSION(:,:), INTENT(OUT) :: v
INTEGER(I4B) :: i,its,j,k,l,m,n,nm
REAL(DP) :: anorm,c,f,g,h,s,scale,x,y,z
REAL(DP), DIMENSION(size(a,1)) :: tempm
REAL(DP), DIMENSION(size(a,2)) :: rv1,tempn
m= ...
...............
End Subroutine svdcmp_dp
Function pythag_dp(a,b)
USE nrtype
IMPLICIT NONE
REAL(DP), INTENT(IN) :: a,b
REAL(DP) :: pythag_dp
REAL(DP) :: absa,absb
absa= ........
..............
pythag_dp= ...
............
End Function pythag_dp
Subroutine svbksb_dp(u,w,v,b,x)
USE nrtype
REAL(DP), DIMENSION(:,:), INTENT(IN) :: u,v
REAL(DP), DIMENSION(:), INTENT(IN) :: w,b
REAL(DP), DIMENSION(:), INTENT(OUT) :: x
INTEGER(I4B) :: mdum,ndum
REAL(DP), DIMENSION(size(x)) :: tmp
mdum= .......
........................
End Subroutine svbksb_dp
........................
END MODULE nrF90svd_Routines

MODULE Work_Routines
contains
Subroutine Adjust_Press_UnStdy()
USE nrF90SVD_Routines
implicit none
.............................
.............................
call svdcmp_dp(a,w,v)
call svbksb_dp(a,w,v,bb,x)
.............................
return
End Subroutine Adjust_Press_UnStdy
..............................
END MODULE Work_Routines

PROGRAM Test_M4
USE Work_Routines
implicit none
.............................
.............................
call Adjust_Press_UnStdy()
.............................
End Program Test_M4


The following compilation error is displayed: (g95 compiler)
C:\DOCUME~1\...\Temp/ccoPZ02X.o:Test_M4.F90:(.text+0x280fb): undefined
reference to `_pythag_dp__'

Apart from unobvious problem with the external function "pythag_dp",
can one extract any other info from the above compiler message ??

Thank you kindly for your help.
Monir
From: Richard Maine on
monir <monirg(a)rogers.com> wrote:

> MODULE nr
> INTERFACE pythag
> Function pythag_dp(a,b)
> USE nrtype
> REAL(DP), INTENT(IN) :: a,b
> REAL(DP) :: pythag_dp
> End Function pythag_dp

The above declares pythag_dp to be an external procedure. Recall from
what I said before that

1. Interface bodies specify the external attribute, even though they
don't use the keyword EXTERNAL.

and

2. *NEVER* redeclare module procedures. Any attempt to do so will lead
to nothing but problems.

> MODULE nrF90svd_Routines
> contains
....
> Function pythag_dp(a,b)

Here we see that you have a module procedure named pythag_dp, but I see
no external procedure of that name (and it woudl be darned confusing to
have both a module procedure and an external procedure of the same name.
You can do it if you are careful, but... well, just don't.)

> The following compilation error is displayed: (g95 compiler)
> C:\DOCUME~1\...\Temp/ccoPZ02X.o:Test_M4.F90:(.text+0x280fb): undefined
> reference to `_pythag_dp__'
>
> Apart from unobvious problem with the external function "pythag_dp",
> can one extract any other info from the above compiler message ??

Actually, that's a message from the linker - not the compiler.

You are not going to have any luck at all along these lines until you
*STOP* thinking that module procedures and external procedures are the
same thing. They aren't. There really isn't any point to going any
further until you get that one straight. You don't have an external
procedure named pythag_dp, which is what the message is trying to tell
you. (The extra underscores are "name decoration" that you can mostly
ignore).If it were looking for a module procedure, the module name would
be in in there somewhere (details vary among compilers, but it would be
in there).

If you want to add a module procedure to a generic interface, then

1. Do not redefine the procedure interface by writing an interface body.
NEVER do that for module procedures in any context. If you think you
need to do it somewhere, then you have something else wrong.

2. Do use the "MODULE PROCEDURE" statement instead. That's what it is
for. (Or in f2003, you can take out the MODULE keyword and just use a
PROCEDURE statement; the limitation of that statement to module
procedures in f90/f95 was pointless and counterproductive. It did
nothing useful, but just caused problems.)

3. And you'll have to USE the module if you do this somewhere other than
in the same module. You have to USE the module anywhere that you refer
to something from it. That's what the USE statement is for.

--
Richard Maine | Good judgment comes from experience;
email: last name at domain . net | experience comes from bad judgment.
domain: summertriangle | -- Mark Twain
From: monir on
On Jul 31, 1:25 am, nos...(a)see.signature (Richard Maine) wrote:
> monir <mon...(a)rogers.com> wrote:
>

Hello;

Thank you very much for your very helpful insight.

A) You suggested:
> 2. Do use the "MODULE PROCEDURE" statement instead. That's what it is
> for."
But "MODULE PROCEDURE" must be within an INTERFACE block within MODULE
nrF90svd_Routines.
Can't use INTERFACE in CONTAINS section of a module!!
Correct ??
What name would I give the procedure and still be recognized as
external pythag_dp ??
If I understand you correctly, it is a dangerous practice to use the
same name.

B) If it's not too much trouble or time consuming, could you please
edit the top 3 lines of:
Function pythag_dp(a,b) in MODULE nrF90svd_Routines
as you see fit.

C) Here's the abbreviated sample code as posted earlier:

MODULE nrtype
INTEGER, PARAMETER :: I4B = SELECTED_INT_KIND(9)
INTEGER, PARAMETER :: I2B = SELECTED_INT_KIND(4)
INTEGER, PARAMETER :: I1B = SELECTED_INT_KIND(2)
INTEGER, PARAMETER :: SP = KIND(1.0)
INTEGER, PARAMETER :: DP = KIND(1.0D0)
REAL, .........................
....................................
END MODULE nrtype

MODULE nr
INTERFACE pythag
Function pythag_dp(a,b)
USE nrtype
REAL(DP), INTENT(IN) :: a,b
REAL(DP) :: pythag_dp
End Function pythag_dp
......................
INTERFACE svbksb
Subroutine svbksb_dp(u,w,v,b,x)
USE nrtype
REAL(DP), DIMENSION(:,:), INTENT(IN) :: u,v
REAL(DP), DIMENSION(:), INTENT(IN) :: w,b
REAL(DP), DIMENSION(:), INTENT(OUT) :: x
End Subroutine svbksb_dp
.....................
END INTERFACE
INTERFACE svdcmp
Subroutine svdcmp_dp(a,w,v)
USE nrtype
REAL(DP), DIMENSION(:,:), INTENT(INOUT) :: a
REAL(DP), DIMENSION(:), INTENT(OUT) :: w
REAL(DP), DIMENSION(:,:), INTENT(OUT) :: v
End Subroutine svdcmp_dp
END INTERFACE
.........................
END MODULE nr

MODULE nrF90svd_Routines
contains
Subroutine svdcmp_dp(a,w,v)
USE nrtype
USE nr, ONLY : pythag
IMPLICIT NONE
...............
End Subroutine svdcmp_dp
!$$$
Function pythag_dp(a,b)
USE nrtype
IMPLICIT NONE
REAL(DP), INTENT(IN) :: a,b
REAL(DP) :: pythag_dp
REAL(DP) :: absa,absb
..............
pythag_dp= ...
............
End Function pythag_dp
!$$$
Subroutine svbksb_dp(u,w,v,b,x)
USE nrtype
REAL(DP), DIMENSION(:,:), INTENT(IN) :: u,v
REAL(DP), DIMENSION(:), INTENT(IN) :: w,b
REAL(DP), DIMENSION(:), INTENT(OUT) :: x
INTEGER(I4B) :: mdum,ndum
REAL(DP), DIMENSION(size(x)) :: tmp
mdum= .......
........................
End Subroutine svbksb_dp
........................
END MODULE nrF90svd_Routines

MODULE Work_Routines
contains
Subroutine Adjust_Press_UnStdy()
USE nrF90SVD_Routines
implicit none
.............................
.............................
call svdcmp_dp(a,w,v)
call svbksb_dp(a,w,v,bb,x)
.............................
return
End Subroutine Adjust_Press_UnStdy
..............................
END MODULE Work_Routines

PROGRAM Test_M4
USE Work_Routines
implicit none
.............................
.............................
call Adjust_Press_UnStdy()
.............................
End Program Test_M4


Thank you once again for you help.
Monir
From: Richard Maine on
monir <monirg(a)rogers.com> wrote:

> On Jul 31, 1:25 am, nos...(a)see.signature (Richard Maine) wrote:

> A) You suggested:
> > 2. Do use the "MODULE PROCEDURE" statement instead. That's what it is
> > for."
> But "MODULE PROCEDURE" must be within an INTERFACE block within MODULE
> nrF90svd_Routines.

False. It requires only that the procedure that it specifies be an
accessible module procedure. The USE statement, which I mentioned that
you need, is what makes the procedure accessible. There is nothing
anywhere about it having to be in the particular module
nrf90svd_routines. I can only speculate that perhaps you incorrectly
concluded that was the reason for an error that was actually cause by
your omission of a needed USE.

> Can't use INTERFACE in CONTAINS section of a module!!
> Correct ??

False. Sort of. I don't understand what you are getting at with that
question anyway. You can't put anything other than procedures in the
CONTAINS section of a module, but you can put an interface in a
procedure that is in the contains section.

Hmm. I didn't notice before that your procedure svdcmp_dp is in
nrf90svd_routines and has a USE of nr. I don't understand what that is
about, as you don't show the code that references anything from that
USE, but you won't be able to do that once you correctly add the USE for
nrf90svd_routines into nr. You can't have circular module dependencies
like that.

> What name would I give the procedure and still be recognized as
> external pythag_dp ??

Let me repeat yet again. A module procedure *IS NOT* an external
procedure. There is nothing you can do to make it one. I don't know what
you mean by "be recognized as external pythag_dp". It is not an external
procedure, so nothing you can do is going to make it recognized as one.
There are no external procedures at all in the code you showed. Nor is
there reason for there to be one.

> If I understand you correctly, it is a dangerous practice to use the
> same name.

I was talking about actually having two different procedures with the
same name. I probably should not even have mentioned it. Forget I ever
did. In addition to being dangerous, it has nothing to do with what you
are trying to do. It is what you have managed to make the compiler think
you are trying to do, but it is not what you are trying to do.

>
> B) If it's not too much trouble or time consuming, could you please
> edit the top 3 lines of:
> Function pythag_dp(a,b) in MODULE nrF90svd_Routines
> as you see fit.

I have no idea what you are talking about... and I more than begin to
suspect that the converse is also true. Nothing I have said has anything
to do with editing anything within pythag_dp. I have no idea why you
would want to do that. I certainly have no particular way inwhich I see
it fit.

--
Richard Maine | Good judgment comes from experience;
email: last name at domain . net | experience comes from bad judgment.
domain: summertriangle | -- Mark Twain
From: Steven Correll on
Maybe it will help to take the opposite tack. Fortran provides both
external procedures and module procedures. They live in different
worlds, and it's perfectly legal for a program to have an external
procedure and a module procedure with the same name. (As Richard Maine
says, it's unwise to do this because it makes your program confusing,
and confusion leads to bugs.) I've appended an example which shows
external and module procedures can coexist in the same program. Notice
that:

1. Module procedures are declared between the "contains" and "end
module" statements, and never appear between "interface" and "end
interface" except through the "module procedure" statement. A
procedure which wants to call a module procedure employs a "use"
statement, not an interface block.

2. External procedures are declared outside of any module, and their
interfaces can appear between "interface" and "end interface". A
procedure which wants to call an external procedure employs an
interface block (although under some conditions--look up "explicit
interface" in a Fortran text--it can omit the interface block and use
an "external" declaration or even use no declaration at all.)

So how does the compiler keep separate two procedures with the same
name? On Linux, try this:

% gfortran myprogram.f90
% nm a.out | grep mysub
000000000040091b T __mymodule__mysubi
00000000004007e8 T __mymodule__mysubr
0000000000400a4e T mysubi_
0000000000400b81 T mysubr_
% ./a.out
I am a module procedure 7
I am a module procedure too 8
I am an external procedure 7
I am an external procedure too 8

module mymodule
implicit none
interface mysub
module procedure mysubi, mysubr
end interface mysub
contains
subroutine mysubi(arg)
integer :: arg(:)
print *, 'I am a module procedure', size(arg)
end subroutine mysubi
subroutine mysubr(arg)
real :: arg(:)
print *, 'I am a module procedure too', size(arg)
end subroutine mysubr
end module mymodule

subroutine mysubi(arg)
implicit none
integer :: arg(:)
print *, 'I am an external procedure', size(arg)
end subroutine mysubi

subroutine mysubr(arg)
implicit none
real :: arg(:)
print *, 'I am an external procedure too', size(arg)
end subroutine mysubr

program myprog
implicit none
integer :: myint(7)
real :: myreal(8)
call call_module_procedures()
call call_external_procedures()
contains
subroutine call_module_procedures()
use mymodule
call mysub(myint)
call mysub(myreal)
end subroutine call_module_procedures
subroutine call_external_procedures()
interface mysub
subroutine mysubi(arg)
integer :: arg(:)
end subroutine mysubi
subroutine mysubr(arg)
real :: arg(:)
end subroutine mysubr
end interface mysub
call mysub(myint)
call mysub(myreal)
end subroutine call_external_procedures
end program myprog