forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

compiler error when overloading procedures

 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support
View previous topic :: View next topic  
Author Message
dk



Joined: 02 Feb 2007
Posts: 6

PostPosted: Tue Feb 06, 2007 10:18 pm    Post subject: compiler error when overloading procedures Reply with quote

Hi,

I also came across the following spurious error when overloading procedures in FTN95.

Line 44: error 283 - DOT_PRODUCT must appear in a type declaration because IMPLICIT NONE has been used

this is despite the fact that in this example DOT_PRODUCT invokes the intrinsic procedure, not the overloaded extension. Adding DOT_PRODUCT to the use statement removes the error yet, according to the standard, should not be necessary. Not the worst bug possible but a bug nonetheless.

!*****************
module mod
implicit none
private
public::func,dot_product
! this overloads the new routine onto the
! same name as the intrinsic dot_product,
! which is legal F-95.
interface dot_product
module procedure dot_product2
endinterface dot_product
contains
!------
function func(x)
implicit none
real,intent(in)::x
real::func
func=x**2
endfunction func
!------
function dot_product2(x)
implicit none
real,intent(in)::x(:)
real::dot_product2
dot_product2=dot_product(x,x)
endfunction dot_product2
!------
endmodule mod
!*****************
module mod2
use mod,only:func
implicit none
contains
subroutine test(x)
real,intent(inout)::x(:)
x(1)=func(x(1))
! the next call uses the intrinsic dot_product, not the
! overloaded extension. My reading of the F-95 standard
! suggests it is not necessary to declare
! 'dot_product' in the USE statement.
! However when compiling with FTN95 the compiler
! reports an error and asks that dot_product be
! declared. This should not be necessary.
x=dot_product(x,(/3.0,6.0/))
endsubroutine test
endmodule mod2
!*****************
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7926
Location: Salford, UK

PostPosted: Wed Feb 07, 2007 10:46 am    Post subject: Reply with quote

I have logged this as something to investigate.
Back to top
View user's profile Send private message AIM Address
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support All times are GMT + 1 Hour
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group