This is the mail archive of the fortran@gcc.gnu.org mailing list for the GNU Fortran project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

Re: Error: FUNCTION attribute conflicts with SUBROUTINE attribute


On Mon, May 23, 2011 at 05:23:44PM -0400, J. Scott Evans wrote:
> 
> I have a module that looks similar to the following:
> 
> module test_module
> 
>   type, abstract :: inverse_type
>     private
>     procedure(fwd_model), pointer, nopass :: fwd_model => null()
>   contains
>     private
>     procedure, public :: set_fwd_model
>     procedure, public :: get_fwd_model
>   end type inverse_type
> 
>   interface
>     subroutine fwd_model(x, y, nx, ny)
>       implicit none
>       integer :: nx,ny
>       real*8, intent(in) :: x(nx)
>       real*8, intent(in) :: y(ny)
>     end subroutine fwd_model
>   end interface
> 
> contains
> 
>   subroutine set_fwd_model(this, fwdmod)
>     class(inverse_type), intent(inout) :: this
>     procedure(fwd_model) :: fwdmod
>     this%fwd_model => fwdmod
>   end subroutine set_fwd_model
> 
>   function get_fwd_model(this) result(fwdmod)
>     class(inverse_type), intent(in) :: this
>     procedure(fwd_model), pointer :: fwdmod
>     fwdmod => this%fwd_model
>   end function get_fwd_model
> 
> end module test_module
> 
> I have a second module in a different file with a type that extends the 
> above type. The file with the code above compiles with no errors. When I 
> compile the file with the type that extends the above type, I get the 
> following errors:
> 
> 
> gfortran -c -g -C -ffree-form -fPIC inverse.f
> gfortran -c -g -C -ffree-form -fPIC opt.f
> <During initialization>
> 
> Error: FUNCTION attribute conflicts with SUBROUTINE attribute in 
> 'get_fwd_model' at (1)
> <During initialization>
> 
> Error: FUNCTION attribute conflicts with SUBROUTINE attribute in 
> 'get_fwd_model' at (1)
> 
> 
> I don't understand what this error means, since the offending code at 
> (1) is not shown. And I don't understand why the error is occurring when 
> I compile the second file rather than the first file, since the first 
> file appears to contain the offending code. Is this a compiler error or 
> is the code invalid?
> 

It appears that line 10 in the second module in the other file
is the problem.

-- 
Steve


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]