Trying to understand why my pointer is 'losing' its value

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!

I understand why you want to use pointers for your points. However, in your Line constructor, the target dummy arguments a and b need to be known/defined even after constructor use.
When you use directly the constructor “direct_line = Line(…)”, I’m not sure it is correct.
However, with the indirect construct with “indirect_line = create_line()”, the a and b target are know (although I’m not sure it is correct) in the “create_line” function and this%a and this%b point to the target a and b. Then, outside the “create_line” function, the a and b points are not defined anymore, so get garbage.

To use the points as targets in the line constructor, you need to define a permanent table or a list of points (in your main program or in a module) and then they can be used line constructor.

They are probably other ways to code what you want

The problem is that you are passing temporary Point objects to the line constructor, which are automatically destroyed after the complition of the Line constructor. So, both the direct_line and inderict_line creation are incorrect. This can be fixed with the use of predifined Point objects with the target attribute:

type(Point), allocatable, target :: p1, p2

p1 = Point(0.0d0, 0.0d0, 0.0d0)
p2 = Point(1.0d0, 0.0d0, 0.0d0)

direct_line = Line(p1, p2)

Well that is unexpected for me.

I’m skipping a bit ahead here, because I would like to define a surface (a list of lines forming a loop) and then extrude it to define a volume. Previously i would have wrote a procedure, that has the surface as an argument and then create the new points, lines and surfaces to define the volume. But you are telling me, that any type, that I would create this way, won’t be usable after the procedure ends.

What would be the fix here? Do I have to create some sort of point/line/surface registry, that contains all values on a module scope, and add the data from the extrude procedure to it, so they won’t be lost anymore?

Any pointer indeed becomes undefined when the pointed object goes out of scope.

Putting your list of points in a module is a solution, as module variables never go out of scope.

Or you can pass the list of points down the line to the procedures that constructs the lines etc… The list of points shall have the target attribute all along the line, not only where you are pointing to the points.

That is annoying. Never encountered such an issue with other programming languages… Out of curiosity is there a reason, that fortran works like that?

Anyway I will try my hands on the registry approach, because returning more objects from the procedure will only grow over time and amkes the code unreadable imo.

Thanks for the help though!

AFAIK it would be the same with C++. I imagine you are thinking about languages that have a garbage collector, like Java? Fortran doesn’t have garbage collection.

1 Like

Most languages have the concept of Object lifetime - Wikipedia

By using POINTER you become responsible for managing your references so that they are always legal.

“Do you feel lucky today?”

1 Like

The NAG Fortran Compiler optionally includes a garbage collector in the runtime. There’s nothing in Fortran that forbids garbage collecting, and it is certainly very easy to create copious amounts of garbage.

I meant, the Fortran standard doesn’t require a garbage collector. Without garbage collector, having persistent objects would lead to severe memory leaks, and the user would have no solution to avoid them.

It has been a while since I last used c++ and yes your are correct, that I’m used to Java. It shows, i guess :smiley:

Anyway with this refresher on pointers and reference management, i should be able to fix my problems.

I think any language that has the concept of pointers has the possibility for dangling pointers. In fortran, and also many other languages, temporary objects are created on the stack, and once the stack is popped and those addresses reused for other temporary objects, the pointers to the old targets are no longer valid and their values will appear to change at random.

There are effectively two types of pointers in fortran, those that are declared as allocatable and those that are declared as pointer. The fortran compiler manages the lifetime and scope of the allocatable ones, and the programmer assumes the responsibility for managing the pointer ones. In fortran, as in other languages, it is easy for the programmer to makes scope/lifetime mistakes with both types, but especially the pointer ones.

Btw, I don’t see much purpose with the results of your constructor functions being allocatable, since they are scalars of known type.

What you are doing currently is more like:

struct point { double x, y, z; };

std::shared_ptr<point> constructor(double x, double y, double z) {
   auto a = std::make_shared<point>(); // calls "new"
   a->x = x; a->y = y; a->z = z;
   return a;
}

In fact, for a basic type like Point, you could just use the default structure constructor (which you’ve currently over-written):

integer, parameter :: dp = kind(1.0d0)
type :: point
   real(dp) :: x, y, z 
end type

type(point) :: p

p = point(1.0_dp,1.0_dp,0.0_dp)  ! structure-constructor already available
                                 ! ideally, copy-elision occurs

In your current approach with the allocable result, what likely happens instead is 1) the RHS is allocated, 2) the RHS is copied into the LHS, 3) the RHS is de-allocated. (In principle an optimizing compiler might be able to take a short-cut, but why confuse it for no good reason?)

Returning a scalar allocatable object would make more sense in a factory function, where the return result would be polymorphic, for example:

module shape3d

   type, abstract :: model
   ! ...
   contains
      procedure, deferred :: draw
   end type

   type, extends(model) :: teapot
      ! ...
   end type

   type, extends(model) :: vase
      ! ...
   end type

contains

   function named_model(str) result(m)
      character(len=*), intent(in) :: str
       class(model), allocatable :: m

       if (lower(str) == "teapot") then
          m = teapot(...)
       else if (lower(str) == "vase") then
          m = vase(...)
       else
          error stop "FAILED: The named model "//std//"does not exist."
       end if 
   end function

end module

program draw
   use shape3d

   class(model), allocatable :: m
   character(len=128) :: input

   call get_command_argument(1,input)  ! concrete type only known at runtime

   m = named_model(trim(input))

   select type(m)
   type is (teapot)
      write(*,*) "Drawing a teapot"
   type is (vase)
      write(*,*) "Drawing a vase"
   end select

   call m%draw()

end program

I just tested some code

running this c++ code

#include <iostream>

// Forward declarations
class Point;

// Define a Point class
class Point
{
public:
    // Constructor
    Point(int xCoord, int yCoord) : x(xCoord), y(yCoord) {}

    // Member functions to get coordinates
    int getX() const { return x; }
    int getY() const { return y; }

    // Member functions to set coordinates
    void setX(int newX) { x = newX; }
    void setY(int newY) { y = newY; }

    // Member function to display coordinates
    void display() const
    {
        std::cout << "Point(" << x << ", " << y << ")" << std::endl;
    }

private:
    // Private data members
    int x;
    int y;
};

// Define a Line class that uses pointers for start and end points
class Line
{
public:
    // Constructor taking pointers to two Point objects
    Line(Point *startPoint, const Point *endPoint)
        : start(startPoint), end(endPoint) {}

    // Member function to set the start point to a different Point object
    void setStart(Point *newStartPoint)
    {
        start = newStartPoint;
    }

    // Member function to display line information
    void display() const
    {
        std::cout << "Line from ";
        start->display();
        std::cout << " to ";
        end->display();
    }

private:
    // Private data members
    Point *start;     // Pointer to the start point of the line
    const Point *end; // Pointer to the end point of the line
};

// Function to create a new Line
Line createLine()
{
    Point *startPoint = new Point(0, 1);
    Point *endPoint = new Point(2, 3);

    Line newLine(startPoint, endPoint);

    // Note: Ownership of memory is transferred to the Line object,
    // so there is no need to delete the Point objects here.

    return newLine;
}

int main()
{
    // Create a new Line using the createLine function
    Line myLine1 = createLine();
    Line myLine2 = createLine();

    // Display information about the original Line
    std::cout << "Original Lines: ";
    myLine1.display();
    myLine2.display();

    // Create a new Point and set its x value
    Point newStartPoint(10, 5);

    // Redirect the start point of the Line to the new Point
    myLine1.setStart(&newStartPoint);
    myLine2.setStart(&newStartPoint);

    // Display information about the modified Line
    std::cout << "Modified Line: ";
    myLine1.display();
    myLine2.display();

    // Display information about the modified Line
    newStartPoint.setX(100);
    std::cout << "Changed Point: ";
    myLine1.display();
    myLine2.display();

    return 0;
}

does exactly what I want (i let chatgpt create this code + comments, because it was quicker.)

The equivalent fortran code looks like this

module PointModule
   implicit none

   ! Define a Point class
   TYPE Point

      INTEGER :: x, y

   CONTAINS
      ! Constructor
      PROCEDURE :: InitPoint => InitPoint
      ! Member functions to get coordinates
      PROCEDURE :: GetX => GetX
      PROCEDURE :: GetY => GetY
      ! Member functions to set coordinates
      PROCEDURE :: SetX => SetX
      PROCEDURE :: SetY => SetY
      ! Member function to display coordinates
      PROCEDURE :: DisplayPoint => DisplayPoint
   END TYPE Point
contains

   ! Point class implementation
   SUBROUTINE InitPoint(this, xCoord, yCoord)
      CLASS(Point), INTENT(INOUT) :: this
      INTEGER, INTENT(IN) :: xCoord, yCoord
      this%x = xCoord
      this%y = yCoord
   END SUBROUTINE InitPoint

   FUNCTION GetX(this) RESULT(x)
      CLASS(Point), INTENT(IN) :: this
      INTEGER :: x
      x = this%x
   END FUNCTION GetX

   FUNCTION GetY(this) RESULT(y)
      CLASS(Point), INTENT(IN) :: this
      INTEGER :: y
      y = this%y
   END FUNCTION GetY

   SUBROUTINE SetX(this, newX)
      CLASS(Point), INTENT(INOUT) :: this
      INTEGER, INTENT(IN) :: newX
      this%x = newX
   END SUBROUTINE SetX

   SUBROUTINE SetY(this, newY)
      CLASS(Point), INTENT(INOUT) :: this
      INTEGER, INTENT(IN) :: newY
      this%y = newY
   END SUBROUTINE SetY

   SUBROUTINE DisplayPoint(this)
      CLASS(Point), INTENT(IN) :: this
      PRINT *, "Point(", this%x, ", ", this%y, ")"
   END SUBROUTINE DisplayPoint

end module PointModule
module LineModule
   use PointModule
   implicit none

   ! Define a Line class that uses pointers for start and end points
   TYPE Line
      TYPE(Point), POINTER :: start
      TYPE(Point), POINTER :: end

   CONTAINS
      ! Constructor taking pointers to two Point objects
      PROCEDURE :: InitLine => InitLine
      ! Member function to set the start point to a different Point object
      PROCEDURE :: SetStart => SetStart
      PROCEDURE :: SetEnd => SetEnd
      ! Member function to display line information
      PROCEDURE :: DisplayLine => DisplayLine
   END TYPE Line

contains

! Line class implementation
   SUBROUTINE InitLine(this, startPoint, endPoint)
      CLASS(Line), INTENT(INOUT) :: this
      TYPE(Point), TARGET, INTENT(IN) :: startPoint, endPoint
      this%start => startPoint
      this%end => endPoint
   END SUBROUTINE InitLine

   SUBROUTINE SetStart(this, newStartPoint)
      CLASS(Line), INTENT(INOUT) :: this
      TYPE(Point), TARGET, INTENT(IN) :: newStartPoint
      this%start => newStartPoint
   END SUBROUTINE SetStart

   SUBROUTINE SetEnd(this, newEndPoint)
      CLASS(Line), INTENT(INOUT) :: this
      TYPE(Point), TARGET, INTENT(IN) :: newEndPoint
      this%end => newEndPoint
   END SUBROUTINE SetEnd

   SUBROUTINE DisplayLine(this)
      CLASS(Line), INTENT(IN) :: this
      PRINT *, "Line from "
      CALL this%start%DisplayPoint()
      PRINT *, " to "
      CALL this%end%DisplayPoint()
   END SUBROUTINE DisplayLine

end module LineModule
PROGRAM LinePointExample
   use PointModule
   use LineModule

   ! Main program
   TYPE(Point) :: newStartPoint
   TYPE(Line) :: myLine1, myLine2

   ! Create new Line objects
   myLine1 = CreateLine()
   myLine2 = CreateLine()

   ! Display information about the original Lines
   PRINT *, "Original Lines:"
   CALL myLine1%DisplayLine()
   CALL myLine2%DisplayLine()

   ! Create a new Point and set its x value
   CALL newStartPoint%InitPoint(10, 5)

   ! Redirect the start points of the Lines to the new Point
   CALL myLine1%SetStart(newStartPoint)
   CALL myLine2%SetStart(newStartPoint)

   ! Display information about the modified Lines
   PRINT *
   PRINT *, "Modified Lines:"
   CALL myLine1%DisplayLine()
   CALL myLine2%DisplayLine()

   ! Display information about the modified Lines after changing Point's x value
   CALL newStartPoint%SetX(100)
   PRINT *
   PRINT *, "Changed Point:"
   CALL myLine1%DisplayLine()
   CALL myLine2%DisplayLine()
contains

   ! Function to create a new Line
   FUNCTION CreateLine() RESULT(LinePtr)
      TYPE(Line) :: LinePtr
      TYPE(Point) :: startPoint, endPoint

      ! Create Point objects
      CALL startPoint%InitPoint(0, 1)
      CALL LinePtr%SetStart(startPoint)

      CALL endPoint%InitPoint(2, 3)
      CALL LinePtr%SetEnd(endPoint)

      ! Create Line object
      CALL LinePtr%InitLine(startPoint, endPoint)

   END FUNCTION CreateLine
END PROGRAM LinePointExample

and it does not do, what i want. Again, i do understand that the reference of startPoint and endPoint created in the CreateLine method are out of scope once the function finishes and that in fortran the memory is freed, which results in the garbage data i get in the main programm. Accodring to chatgpt ‘Ownership of memory is transferred to the Line object’, which means, that in c++ the memory stays intact after leaving the function.

How can I fix the fortran code without adding startPoint and endPoint as function parameters with intent (out) to the createLine function?

Like this:

   ! Function to create a new Line
   FUNCTION CreateLine() RESULT(LinePtr)
      TYPE(Line) :: LinePtr
      TYPE(Point), pointer :: startPoint, endPoint

      allocate( startPoint, endPoint )

      ! Create Point objects
      CALL startPoint%InitPoint(0, 1)
      CALL LinePtr%SetStart(startPoint)

      CALL endPoint%InitPoint(2, 3)
      CALL LinePtr%SetEnd(endPoint)

      ! Create Line object
      CALL LinePtr%InitLine(startPoint, endPoint)

   END FUNCTION CreateLine

startPoint and endPoint being pointers, the pointed object is not automatically deallocated upon exit of the function. This is quite equivalent to the C++ Point *startPoint = new Point(0, 1);.

That said IMHO this is a questionable design., but it should work.

Thank you for the answer. It does indeed work.

Could you elaborate, why this is bad design? I assume it would make my code vulnerable to memory issues, if I’m not carefull with deallocating. What would be the better approach?

I didn’t say “bad”, just “questionable” :slight_smile: . As you have experienced, this is very easy to get screwed with pointing garbage data if you’re not careful with the scope of everything…

At first glance perhaps, but you have a memory leak. When the Line objects are destroyed they do not deallocate the points created in the createLine function. In the equivalent Fortran code, where the points are given the pointer attribute, you have the same problem. When dealing with pointers in languages that do not have garbage collection the programmer is obligated to think in terms of data ownership. If you want to really learn this concept, Rust is a language which really helps (forces) the programmer to fully comprehend it.

Just to make clear that there is no “easy” way in Fortran to get this right in the general case.

module example
  type :: point
    real :: x, y, z
  end type

  type :: line
    type(point), pointer :: a, b
  end type
contains
  subroutine do_stuff
    type(point), pointer :: p1, p2
    type(line) :: my_line

    allocate(p1, p2)
    p1 = point(1., 2., 3.)
    p2 = point(4., 5., 6.)
    my_line = line(p1, p2)
    print *, my_line
  end subroutine
end module

use example

call do_stuff
end

The above has a memory leak. Compile it and run it with Valgrind to see. One might be tempted to try the following, but you’ll see that it does not work either, because the points are deallocated too soon, on the right hand side of the assignment.

module example
  type :: point
    real :: x, y, z
  end type

  type :: line
    type(point), pointer :: a, b
  contains
    final :: line_final
  end type
contains
  subroutine do_stuff
    type(point), pointer :: p1, p2
    type(line) :: my_line

    allocate(p1, p2)
    p1 = point(1., 2., 3.)
    p2 = point(4., 5., 6.)
    my_line = line(p1, p2)
    print *, my_line
  end subroutine

  subroutine line_final(l)
    type(line), intent(inout) :: l

    if (associate(l%a)) then
      deallocate(l%a)
      nullify(l%a)
    end if
    if (associate(l%b)) then
      deallocate(l%b)
      nullify(l%b)
    end if
end module

use example

call do_stuff
end

I understand that I would currently run into memory leaks. However I don’t fully understand the issue with the second code snippet. Is it because it is possible to free the memory even though a pointer could still be pointing at it?

Here a short set up, what i mean:

subroutine do_stuff
    type(point), pointer :: p1, p2, p3
    type(line) :: l1, l2

    allocate(p1, p2, p3)
    p1 = point(1., 2., 3.)
    p2 = point(4., 5., 6.)
    p3 = point(7., 8., 9.)
    l1= line(p1, p2)
    l2= line(p2, p3)
  end subroutine

If I would now destroy l1, would that mean, that the start point of l2 would point at garbage? I assume there is not an easy way to check if something still points at p2 before deallocating it, correct? C++ has the std::shared_ptr that would usually handle cases like this (if i remember correctly, lol).