Error on a fortran constructor - oop

I want to extend an abstract type and then initialize with a constructor but I got the error (from gfortran)
"Error: No initializer for component 'feature' given in the structure constructor !"
The first module is
module A_Module
implicit none
type A
double precision :: x,y
end type A
contains
end module A_Module
The second module is
module B_module
use A_Module
type, abstract :: B
contains
procedure (Compute_BFeature), deferred :: B_Feat
end type B
abstract interface
function Compute_BFeature(this)
import B
double precision, dimension(:), allocatable :: Compute_BFeature
class (B)::this
end function Compute_BFeature
end interface
type, extends(B) :: B_new
type (A), dimension(2) :: A_list
double precision, dimension(2) :: Feature
contains
procedure :: B_Feat => B_new_Feature
end type B_new
interface B_new
procedure B_new_Constructor
end interface
contains
function B_new_Constructor(this,A_listInput)
type(B_new):: B_new_Constructor
type (A), dimension(2), intent(in) :: A_listInput
B_new_Constructor%A_list = A_listInput
B_new_Constructor%Feature = B_new_Constructor%B_Feat()
end function
function B_new_Feature (this)
double precision, dimension(:) , allocatable :: B_new_Feature
class (B_new) :: this
allocate(B_new_Feature(2))
B_new_Feature(1) = -(this%A_list(2)%y - this%A_list(1)%y)
B_new_Feature(2) = this%A_list(2)%x - this%A_list(1)%x
end function
end module B_module
Instead of
B_new_Constructor%Feature = B_new_Constructor%B_Feat()
I tried using also
B_new_Constructor%Feature(1) = 1.0
B_new_Constructor%Feature(2) = 1.0
but gfortran always returns the same error.
In order to understand wheter the problem is with my B_new_Feature function
I tried to see if the error is with the allocatable statement of the function but, even having Feature as a double precision scalar (and B_new_Feature adjusted accordignly) the compiler still complains the same way.
At this moment after many trials, I cannot find what is the error, any idea?

(Because I am still new to Fortran OOP features, the following Answer may contain some big errors, so pls be careful... Tested with gfortran4.8.2)
First in B_new_Constructor(), this is given as the first argument but not declared explicitly (probably a typo). Because there is no implicit none, no error occurs with this implicit this. Also, as far as I understand, Fortran's "constructor" is not a member function of derived type but often refers to a module procedure that is overloaded with the default structure constructor for returning a new object. So there is no need to pass this to the user-defined constructor (here, B_new_Constructor()) but rather it is expected to return a newly constructed object.
With the original code, a main program like this
program main
use B_module, only: A, B_new
type(B_new) :: p, q, r
p = B_new()
print *, "p = ", p
q = B_new( [ A(1.0d0,2.0d0), A(3.0d0,4.0d0) ] )
print *, "q = ", q
r = B_new( [ A(1.0d0,2.0d0), A(3.0d0,4.0d0) ], [ 5.0d0, 6.0d0 ] )
print *, "r = ", r
end
gives an error message like
p = B_new()
1
Error: No initializer for component 'a_list' given in the structure constructor at (1)!
q = B_new( [ A(1.0d0,2.0d0), A(3.0d0,4.0d0) ] )
1
Error: No initializer for component 'feature' given in the structure constructor at (1)!
Now if we attach implicit none at the top of B_module and change B_new_Constructor() as
function B_new_Constructor( A_listInput ) result( ret )
type(A) :: A_listInput( 2 )
type(B_new) :: ret
print *, "modified constructor called (no optional)"
ret% A_list(:) = A_listInput(:)
ret% Feature(:) = ret% B_Feat()
endfunction
we still get the same error for p
p = B_new()
1
Error: No initializer for component 'a_list' given in the structure constructor at (1)!
This is probably because there is no matching procedure for a call with no argument (here we assume that the default structure constructor requires two arguments). One method to deal with this may be to use optional keywords like
function B_new_Constructor( A_listInput , featInput ) result( ret )
type(A), optional :: A_listInput( 2 )
double precision, optional :: featInput( 2 )
type(B_new) :: ret
print *, "modified constructor called"
if ( present( A_listInput ) ) ret% A_list(:) = A_listInput(:)
if ( present( featInput ) ) then
ret% Feature(:) = featInput(:)
else
ret% Feature(:) = ret% B_Feat()
endif
endfunction
Then the program runs as
modified constructor called
p = 1.24543954074099760E-312 1.24546058728534379E-312 1.24543953672918456E-312 2.12199579096527232E-314 1.22424062937569107E-312 -4.01181304423092194E-321
modified constructor called
q = 1.0 2.0 3.0 4.0 -2.0 2.0 !! format slightly changed to fit the terminal
modified constructor called
r = 1.0 2.0 3.0 4.0 5.0 6.0
This output shows that given two arguments, the user-defined constructor has precedence over the default structure constructor.
To avoid optional keywords, we can also use default initializers such that
type A
double precision :: x = 100.0d0, y = 200.0d0
endtype
type, extends(B) :: B_new
type(A) :: A_list(2)
double precision :: Feature(2) = [ 300.0d0, 400.0d0 ]
contains
...
endtype
then the first modified version of B_new_Constructor() (with no optional) works as well
p = 100.0 200.0 100.0 200.0 300.0 400.0
modified constructor called (no optional)
q = 1.0 2.0 3.0 4.0 -2.0 2.0
r = 1.0 2.0 3.0 4.0 5.0 6.0
This output shows that the default structure constructor is called at least for r.
----------
EDIT: If we want to allow only the one-argument constructor (here, A_listInput), there may be two approaches. One is to modify the above B_new_Constructor() with two optional arguments by including the following to prohibit other cases:
if ( ( present( A_listInput ) .and. present( featInput ) ) .or. &
( (.not. present( A_listInput )) .and. (.not. present( featInput )) ) ) then
stop "only one arg permitted"
endif
and the other approach is to define constructors with no argument or two argument as a "dummy":
function B_new_Constructor_arg1 ( A_listInput ) result( ret )
type(A) :: A_listInput( 2 )
type(B_new) :: ret
ret% A_list(:) = A_listInput(:)
ret% Feature(:) = ret% B_Feat()
endfunction
function B_new_Constructor_arg0 () result( ret )
type(B_new) :: ret
stop "constructor with no argument prohibited"
endfunction
function B_new_Constructor_arg2 ( A_listInput, featInput ) result( ret )
type(A) :: A_listInput( 2 )
double precision :: featInput( 2 )
type(B_new) :: ret
stop "constructor with two arguments prohibited"
endfunction
with
interface B_new
procedure B_new_Constructor_arg1
procedure B_new_Constructor_arg0 !! this masks default initializers (if any)
procedure B_new_Constructor_arg2 !! this masks default structure constructor
endinterface
Both approaches seem to work, but both are not very elegant... (hopefully there will be a better way to do this). [And I am sorry to be too long for a single Answer.]

Related

Object Oriented Programming in modern Fortran including a member of function pointers [duplicate]

This question already has answers here:
Why is the type not accessible?
(2 answers)
Closed 3 years ago.
Now I am training object-oriented programming in FORTRAN, and I would like to make a program using a "type" containing a function pointer like the code shown below. However, intel Fortran compiler (v18) showed compile errors, and said that the first argument in FUNCTION trig(self, x) should be same type with the defined type in type-bound procedure including a pass-bind attribution.
I'm not still familiar with "modern" fortran programming, so that I can not understand the meaning of this compile error. Would you be able to lend your expertise?
MODULE test_mod
!
use iso_fortran_env, only: REAL32, REAL64
!
implicit none
!
private
!
integer, parameter, private :: sp = REAL32
integer, parameter, private :: dp = REAL64
!
type, public :: t_obj
private
real( dp ) :: val = 1.0_dp
procedure( trig ), pass( self ), pointer, public :: trigFunc => null( )
contains
private
procedure, pass( self ), public :: setFunc
end type t_obj
!
ABSTRACT INTERFACE
FUNCTION trig( self, x )
class( t_obj ) :: self
real( kind( 1.0d0 ) ), intent( in ) :: x
real( kind( 1.0d0 ) ) :: trig
END FUNCTION trig
END INTERFACE
!
CONTAINS
!
FUNCTION cosFunc( self, x )
implicit none
class( t_obj ) :: self
real( dp ) :: x
real( dp ) :: cosFunc
cosFunc = cos( x ) * self%val
END FUNCTION cosFunc
!
FUNCTION sinFunc( self, x )
implicit none
class( t_obj ) :: self
real( dp ) :: x
real( dp ) :: sinFunc
sinFunc = sin( x ) * self%val
END FUNCTION sinFunc
!
SUBROUTINE setFunc( self, i )
implicit none
class( t_obj ), intent( inout ) :: self
integer :: i
if( i .eq. 1 ) then
self%trigFunc => cosFunc
else
self%trigFunc => sinFunc
end if
END SUBROUTINE setFunc
!
END MODULE test_mod
!
PROGRAM test_main
!
use test_mod
!
implicit none
type( t_obj ) :: obj
real( kind( 1.0d0 ) ) :: pihalf = datan( 1.0d0 ) * 2.0d0
!
call obj%setFunc( 1 )
write(*,*) obj%trigFunc( pihalf )
call obj%setFunc( 0 )
write(*,*) obj%trigFunc( pihalf )
!
END PROGRAM test_main
Compiling your code with INTEL Fortran gives me this error message
error #8262: For a type-bound procedure that has the PASS binding attribute, the first dummy argument must have the same declared type as the type being defined. [SELF]
related to your function trig( self, x ) in the abstract interface.
As mentioned by francescalus, the import statement is missing in your function.
Adding it will solve your issue:
ABSTRACT INTERFACE
FUNCTION trig( self, x )
import
class( t_obj ) :: self
real( kind( 1.0d0 ) ), intent( in ) :: x
real( kind( 1.0d0 ) ) :: trig
END FUNCTION trig
END INTERFACE
Please read also this post.
Hope it helps?

Initialize a parameter in a derived type

I am still wrapping my head around Fortran with an "object oriented" flavor.
Is it possible to initialize a variable in a derived type, and what if I'd like that variable to be a parameter?
For example, a classic animal, cat, bee set of types that should set the number of legs of each animal:
animal module
module animal_module
implicit none
type, abstract :: animal
private
integer, public :: nlegs = -1
contains
...
cat module
module cat_module
use animal_module, only : animal
implicit none
type, extends(animal) :: cat
private
! error here about redefining nlegs...
integer, public :: nlegs = 4
...
I've found online the keyword initial, but my compiler (Intel) complains about the keyword with a syntax error.
Addendum
I've tried a custom constructor but apparently I am unable to write one for derived types. This is my attempt, only on the cat type:
module cat_module
use animal_module, only : animal
implicit none
type, extends(animal) :: cat
private
real :: hidden = 23.
contains
procedure :: setlegs => setlegs
procedure :: speak
end type cat
interface cat
module procedure init_cat
end interface cat
contains
type(cat) function init_cat(this)
class(cat), intent(inout) :: this
this%nlegs = -4
end function init_cat
...
program oo
use animal_module
use cat_module
use bee_module
implicit none
character(len = 3) :: what = "cat"
class(animal), allocatable :: q
select case(what)
case("cat")
print *, "you will see a cat"
allocate(cat :: q)
...
print *, "this animal has ", q%legs(), " legs."
As the animal type has integer, public :: nlegs = -1, I expected the cat to have -4 legs, but alas, it's still -1.
It is not possible for a component to be a named constant. Also, it isn't possible to declare a component of an abstract type and then define default initialization for its value in an extending type. Attempting to redeclare the component with default initialization leads to the error of the question.
High Performance Mark's comment offers one route: provide a custom constructor for each extending type setting the value appropriately. You can further set the component to private for encapsulation or protection.
Alternatively, you can provide a "getter" type-bound procedure which references a named constant:
module animal_module
implicit none
type, abstract :: animal
contains
procedure(getter), deferred :: nlegs
end type animal
abstract interface
integer function getter(creature)
import animal
class(animal) creature
end function getter
end interface
end module animal_module
module cat_module
use animal_module, only : animal
implicit none
type, extends(animal) :: cat
contains
procedure :: nlegs => nlegs_cat
end type cat
contains
integer function nlegs_cat(creature)
class(cat) creature
integer, parameter :: my_cat_has_legs=3
nlegs_cat = my_cat_has_legs
end function nlegs_cat
end module cat_module
use cat_module
implicit none
class(animal), allocatable :: fido
fido = cat()
print*, "Fido has", fido%nlegs(), "legs"
end
Finally, initial is not standard Fortran (and would have similar problems).

Extending an object and overriding a procedure without being deferred in Fortran

I have a code with lots of different features and methods. Some methods are all for the same feature, i.e. only one among a selection can be selected.
Furthermore, depending on a feature I might need to do modify subroutines elsewhere. So in a loop in routine inject I might have a small if statement asking if I have used feature A, then do a few extra operations.
This is very frustating since different features seems to be connected with others routines very arbirarirly, and can be difficult to maintain.
I have decided to do following to avoid this:
I define an object t_inject with the purpose to execture routine inject. I rewrite my routine inject such that it contains only the code that is common for all different scenarios.
type t_inject
contains
procedure,nopass :: inject => inject_default
end type
Now I have another object to handle my feature A in case it is selected.
type,extends(t_inject) :: t_inject_a
contains
procedure, nopass :: inject => inject_a
end type
My subroutines inject_a and inject have same interface. E.g.
subroutine inject_a( part )
type(t_part) , intent(inout) :: part % an external data type
call inject(part)
! do the extra bit of stuff you need to do
end subroutine
subroutine inject( part)
type(t_part) , intent(inout) :: part % an external data type
! carry out the default stuff
end subroutine
Now in my main program
class(t_inject) :: inj
allocate(inj :: t_inject_a)
call inj% inject ( part)
Is that the way you would do it and is it valid?
I initially thought of doing an abstract declared type with a deferred inject procedure where I then could extent.
But for a very trivial problem I might not need that - I am also wondering whether my call call inj% inject(part) is sufficient for the compiler to know to where to go. Sometimes I see codes which need the class is condition before making the call.
I think three points should be modified:
The type-bound procedures need to refer to actual procedure names (via =>). So, I have changed the name of a module procedure inject() to inject_default(). (But please see test2.f90 also).
We need to attach allocatable to a class variable (e.g., inj2) to allocate it with a concrete type (e.g., t_inject_a).
In the allocate statement, the name of a concrete type should appear before ::, such that allocate( t_inject_a :: inj2 ).
The modified code may look like this:
!! test.f90
module test_mod
implicit none
type t_inject
contains
procedure, nopass :: inject => inject_default
endtype
type, extends(t_inject) :: t_inject_a
contains
procedure, nopass :: inject => inject_a
endtype
type t_part !! some other type
integer :: x = 100, y = 200
endtype
contains
subroutine inject_default( part )
type(t_part), intent(inout) :: part
print *, "x = ", part % x
endsubroutine
subroutine inject_a( part )
type(t_part), intent(inout) :: part
call inject_default( part )
print *, "y = ", part % y
endsubroutine
end
program main
use test_mod
implicit none
class( t_inject ), allocatable :: inj1, inj2
type( t_part ) :: part
!! Polymorphic allocation with concrete types.
allocate( t_inject :: inj1 )
allocate( t_inject_a :: inj2 )
print *, "inj1:"
call inj1 % inject( part )
print *, "inj2:"
call inj2 % inject( part )
end
"gfortran-8 test.90 && ./a.out" gives
inj1:
x = 100
inj2:
x = 100
y = 200
We can also use a module procedure inject() (rather than inject_default()) by using procedure, nopass :: inject, for example:
!! test2.f90
module test_mod
implicit none
type t_inject
contains
procedure, nopass :: inject
! procedure, nopass :: inject => inject !! this also works
endtype
type, extends(t_inject) :: t_inject_a
contains
procedure, nopass :: inject => inject_a
endtype
type t_part !! some other type
integer :: x = 100, y = 200
endtype
contains
subroutine inject( part )
type(t_part), intent(inout) :: part
print *, "x = ", part % x
endsubroutine
subroutine inject_a( part )
type(t_part), intent(inout) :: part
call inject( part )
print *, "y = ", part % y
endsubroutine
end
!! The remaining part (and the result) is the same...
In addition, one can also separate actual procedures like inject() in a different file and use them to define new types like t_inject (see mylib.f90 and test3.f90 below). This might be useful to reuse routines in some library file.
!! mylib.f90
module mylib
implicit none
type t_part !! some other type
integer :: x = 100, y = 200
endtype
contains
subroutine inject( part )
type(t_part), intent(inout) :: part
print *, "x = ", part % x
end
subroutine inject_a( part )
type(t_part), intent(inout) :: part
call inject( part )
print *, "y = ", part % y
end
end
!! test3.f90
module test_mod
use mylib
implicit none
type t_inject
contains
procedure, nopass :: inject
endtype
type, extends(t_inject) :: t_inject_a
contains
procedure, nopass :: inject => inject_a
endtype
end
!! The main program is the same as test.f90.
!! compile: gfortran-8 mylib.f90 test3.f90

Overloading the equals operator in Fortran

Is there a way to overload the = operator so that you can write an assignment like in this example:
module constants_mod
integer,parameter :: dpn = selected_real_kind(14)
end module
module vectorField_mod
use constants_mod
implicit none
private
public :: vectorField
public :: allocateX,allocateY,allocateZ
public :: delete
! public :: operator(=)
type vectorField
integer,dimension(3) :: sx,sy,sz
real(dpn),dimension(:,:,:),allocatable :: x,y,z
end type
interface delete
module procedure deallocateVectorField
end interface
! interface operator (=)
! module procedure vectorAssign
! end interface
contains
! function vectorAssign(f) result(q)
! implicit none
! real(dpn),intent(in) :: f
! type(vectorField) :: q
! q%x = f; q%y = f; q%z = f
! end function
! subroutine vectorAssign(f,g)
! implicit none
! type(vectorField),intent(inout) :: f
! real(dpn),intent(in) :: g
! f%x = g; f%y = g; f%z = g
! end subroutine
subroutine allocateX(field,Nx,Ny,Nz)
implicit none
type(vectorField),intent(inout) :: field
integer,intent(in) :: Nx,Ny,Nz
if (allocated(field%x)) deallocate(field%x)
allocate(field%x(Nx,Ny,Nz))
field%sx = shape(field%x)
end subroutine
subroutine allocateY(field,Nx,Ny,Nz)
implicit none
type(vectorField),intent(inout) :: field
integer,intent(in) :: Nx,Ny,Nz
if (allocated(field%y)) deallocate(field%y)
allocate(field%y(Nx,Ny,Nz))
field%sy = shape(field%y)
end subroutine
subroutine allocateZ(field,Nx,Ny,Nz)
implicit none
type(vectorField),intent(inout) :: field
integer,intent(in) :: Nx,Ny,Nz
if (allocated(field%z)) deallocate(field%z)
allocate(field%z(Nx,Ny,Nz))
field%sz = shape(field%z)
end subroutine
subroutine deallocateVectorField(field)
implicit none
type(vectorField),intent(inout) :: field
deallocate(field%x,field%y,field%z)
field%sx = 0; field%sy = 0; field%sz = 0
end subroutine
end module
program test
use constants_mod
use vectorField_mod
implicit none
type(vectorField) :: a
integer :: N = 1
real(dpn) :: dt = 0.1
call allocateX(a,N,N,N)
call allocateY(a,N,N,N)
call allocateZ(a,N,N,N)
a%x = dble(1.0) ! want to avoid this
a%y = dble(1.0) ! want to avoid this
a%z = dble(1.0) ! want to avoid this
a = real(1.0,dpn) ! want this instead (does not compile)
call delete(a)
end program
I've tried two different ways (shown in comments) but I get errors saying that there is a syntax error in generic specification (for publicizing the = operator).
= is not an operator, it is an assignment in Fortran and they are very different beasts.
To the classical possibility found in Fortran 90 and explained well in other answers, Fortran 2003 added a better possibility to bind the overloaded operators and assignments with the derived type.
This way you are sure you will not import the type without the assignment (beware of public and private statement in this case!). It can have very unpleasant consequences and can be hard to debug:
type vectorField
integer,dimension(3) :: sx,sy,sz
real(dpn),dimension(:,:,:),allocatable :: x,y,z
contains
procedure :: assignVector
generic :: assignment(=) => assignVector
end type
This way you do not have to be that careful to not forget the public :: assignment (=)
For defined assignment operator(=) is not correct, but assignment(=) is: see Fortran 2008 12.4.3.4.3. So you instead want the two lumps
public :: assignment (=)
and
interface assignment (=)
module procedure vectorAssign
end interface
Note that the correct way to define the assignment is by the subroutine as you have it (although the assignee could have intent(out) instead of intent(inout)).
Yes, you can overload the assignment operator. The syntax and requirements are different for the assignment operator than for other operators because the semantics are fundamentally different: all other operators compute a new value based on one or two arguments, without changing the arguments, whereas assignment changes the value of the left-hand argument.
In your case, I think it should look like this:
module vectorField_mod
! ...
interface assignment (=)
module procedure vectorAssign
end interface
contains
! ...
subroutine vectorAssign(f,g)
implicit none
type(vectorField),intent(out) :: f
real(kind = dpn), intent(in) :: g
f%x = g
f%y = g
f%z = g
end subroutine vectorAssign
end module vectorField_mod

Type bound procedure encapsulation

How to pass an encapsulated type bound function? I played with the example from the Modern Fortran Explained book (Metcalf, Reid and Cohen) and this is what I did:
module mod_polynoms_abstract
use mod_geometrics
implicit none
type, abstract :: bound_user_polynom
! No data
contains
procedure(user_polynom_interface), deferred :: eval
end type bound_user_polynom
abstract interface
real function user_polynom_interface(poly, pt)
import :: bound_user_polynom, point
class(bound_user_polynom) :: poly
type(point), intent(in) :: pt
end function user_polynom_interface
end interface
contains
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!Integral driver/chooser function
real function integral(userfun, options,status)
class(bound_user_polynom) :: userfun
integer, intent(in) :: options
real, intent(out) :: status
select case( options )
case (1)
integral = first_integral(userfun)
case (2)
integral = second_integral(userfun)
case default
integral = def_integral(userfun)
end select
end function
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!1. integration
real function first_integral(userfun)
class(bound_user_polynom),intent(in) :: userfun
first_integral= 1.0 * userfun%eval(point(x=2.,y=2.,z=0.))
end function
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!2. integration
real function second_integral(userfun)
class(bound_user_polynom),intent(in) :: userfun
second_integral= 2.0 * userfun%eval(point(x=2.,y=2.,z=0.))
end function
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!default integration
real function def_integral(userfun)
class(bound_user_polynom) :: userfun
def_integral= 0.0 * userfun%eval(point(x=2.,y=2.,z=0.))
end function
end module
This compiles, but when I run the program I get different results.
When I call the function, maybe like this:
integral_result = integral(poly, 2 , status)
I get sometimes the right result, which is computed with the second_integral(userfun)
function. But sometimes the result is wrong.
The function can't calculate userfun%eval(point(x=2.,y=2.,z=0.)) correctly, but I don't know why.
Is this the correct way to do this?
Edit:
I use :
COLLECT_GCC=gfortran4.8
COLLECT_LTO_WRAPPER=/usr/local/libexec/gcc/x86_64-unknown-linux-gnu/4.8.0/lto-wrapper
Ziel: x86_64-unknown-linux-gnu
Konfiguriert mit: ./configure --disable-multilib
Thread-Modell: posix
gcc-Version 4.8.0 (GCC)
The correct result of userfun%eval(point(x=2.,y=2.,z=0.)) is 0.962435484
So integral(poly, 2 , status) must give me 1.92487097.
But when I execute the program several times I got:
first run : 1.92487097
second run: 54877984.0
... : 1.92487097
... : 2.55142141E+27
... : 4.19146938E+33
... : 1.95548379
and so on ..
Edit 2:
The type polynom is defined as:
type, extends(bound_user_polynom) :: polynom
real(kind=kind(1.0D0)), allocatable, dimension(:) :: coeff
type(monomial),allocatable, dimension(:) :: monom
contains
procedure :: eval => poly_eval
procedure, private :: p_add
generic :: operator(+) => p_add
procedure, private :: p_subs
generic :: operator(-) => p_subs
end type
!constructor
interface polynom
module procedure construct_poly
end interface
and in my main program i call:
integral_result = integral(p(2), 2 , status)
Found the error with some help from comp.fortan:
in:
userfun%eval(point(x=2.,y=2.,z=0.))
i had one uninitialized variable which gave me this strange results.
Is seems there is nothing wrong with the rest of the code.
Thank You,
Jan