Hello!
I’m quite new to fortran and wrote some code, that is not really doing what I would expected it to do. I have 2 modules, each one is for a custom type (later they shall also have type bound procedures).
module PointModule
implicit none
private :: constructor
public
type :: Point
real*8 :: x, y, z
end type Point
interface Point
module procedure :: constructor
end interface Point
contains
function constructor(x, y, z) result(this)
type(Point), allocatable :: this
real*8 :: x, y, z
allocate (this)
this%x = x
this%y = y
this%z = z
end function constructor
end module PointModule
module LineModule
use PointModule
implicit none
private :: constructor
public
type :: Line
type(Point), pointer :: a, b
end type Line
interface Line
procedure :: constructor
end interface Line
contains
function constructor(a, b) result(this)
type(Line), allocatable :: this
type(Point), target :: a, b
allocate (this)
this%a => a
this%b => b
end function constructor
end module LineModule
In my main i currently run the following programm
PROGRAM main
use PointModule
use LineModule
implicit none
type(Line) :: direct_line
type(Line) :: indirect_line
direct_line = Line(Point(0.0d0, 0.0d0, 0.0d0), Point(1.0d0, 0.0d0, 0.0d0))
indirect_line = create_line()
call print_line(direct_line, 'direct_line ')
call print_line(indirect_line, 'indirect_line ')
contains
function create_line() result(line_)
type(Line), allocatable :: line_
line_ = Line(Point(0.0d0, 0.0d0, 0.0d0), Point(1.0d0, 0.0d0, 0.0d0))
end function create_line
subroutine print_line(line_, prefix)
type(Line) :: line_
character(len=*) :: prefix
print *, &
prefix, &
' a: (', &
line_%a%x, &
', ', &
line_%a%y, &
', ', &
line_%a%z, &
')'
print *, &
prefix, &
' b: (', &
line_%b%x, &
', ', &
line_%b%y, &
', ', &
line_%b%z, &
')'
end subroutine print_line
END
And i get the following output
direct_line a: ( 0.0000000000000000 , 0.0000000000000000 , 0.0000000000000000 )
direct_line b: ( 1.0000000000000000 , 0.0000000000000000 , 0.0000000000000000 )
indirect_line a: ( 1.0987901263882183E-311 , 6.9528545173887663E-310 , -4.8366978272229995E-026 )
indirect_line b: ( 0.0000000000000000 , 0.0000000000000000 , 0.0000000000000000 )
So somehow the point pointers of the line, that is create by the function, somehow are not pointing to the correct values anymore.
If I remove ‘pointer’ from the declaration of a and b, the code runs fine and i get the expected output.
direct_line a: ( 0.0000000000000000 , 0.0000000000000000 , 0.0000000000000000 )
direct_line b: ( 1.0000000000000000 , 0.0000000000000000 , 0.0000000000000000 )
indirect_line a: ( 0.0000000000000000 , 0.0000000000000000 , 0.0000000000000000 )
indirect_line b: ( 1.0000000000000000 , 0.0000000000000000 , 0.0000000000000000 )
But it is kinda crucial, that these values stay pointers, since later i will have multiple lines, that might share a point. Any help is much appreciated!