viegets
viegets

Reputation: 119

Odd behavior of fortran strings in a derived type after accessing the type by a pointer

[Working example at the end of this post!]

I'm trying to write a simple module to handle physical units in arithmetic operations. My aim is to create derived units out of primary ones.

As you can see in the following code, I have a derived type, namely unit_t, which stores a string, representing the unit itself, power of the unit, conversion factor (to convert it to SI), a logical variable to show if the unit is cloned and next and prev pointers which point to the next or previous unit (in case we have a combination of units, for example kg * m / s**2, so basically it's a linked list connecting different units to each other).

I have a function named unit_clone to clone a primary unit. The unit_int_pow function overloads the exponentiation operator (**) and it simply clones a given primary unit and updates its exponent. The units_mul function overloads the multiplication operator (*). This function first check if the two given units are cloned (if not, it clones them) and then just connect them using next and prev pointers.

Here is my code (you should be able to compile it with gfortran)

module units

  implicit none

  type unit_t
    character(len=16) :: symb
    integer :: pow
    real :: conv
    logical :: cloned
    type(unit_t), pointer :: next => null(), prev => null()
  end type unit_t


  ! definitions
  type(unit_t), target :: m = unit_t("m", 1, 1.d0, .false.)
  type(unit_t), target :: km = unit_t("km", 1, 1.d3, .false.)

  type(unit_t), target :: kg = unit_t("kg", 1, 1.d0, .false.)

  type(unit_t), target :: s = unit_t("s", 1, 1.d0, .false.)

  interface operator (**)
    procedure unit_int_pow
  end interface operator (**)


  interface operator (*)
    procedure units_mul
  end interface operator (*)

contains

  !> Cloning a given node (unit)
  function unit_clone(u) result (clone)
    implicit none

    type(unit_t), intent(in) :: u
    type(unit_t), allocatable, target :: clone

    allocate(clone)

    clone%symb = u%symb
    clone%conv = u%conv
    clone%pow = u%pow
    clone%cloned = .true.
    clone%next => u%next
    clone%prev => u%prev
  end function unit_clone


  !> integer powers
  function unit_int_pow(u1, p) result(u)
    implicit none

    type(unit_t), intent(in) :: u1
    integer, intent(in) :: p

    type(unit_t), allocatable, target :: u

    u = unit_clone(u1)
    u%pow = u%pow * p
  end function unit_int_pow


  !> multiplication
  function units_mul (u1, u2) result (u1c)
    implicit none

    type(unit_t), intent(in) :: u1, u2
    type(unit_t), allocatable, target :: u1c, u2c

    if ( u1%cloned ) then
      u1c = u1
    else
      u1c = unit_clone(u1)
    end if

    if ( u2%cloned ) then
      u2c = u2
    else
      u2c = unit_clone(u2)
    end if

    u2c%prev => u1c
    u1c%next => u2c
  end function units_mul
end module units

program test
  use units

  implicit none

  type(unit_t) :: u

  u = kg**2 * m

  print *, u%symb, "^", u%pow, " [expected: kg^2]"
  print *, u%next%symb, "^", u%next%pow, " [expected: m^1]"
  print *, u%next%prev%symb, "^", u%next%prev%pow, " [expected: kg^2]"
end program test

The problem is, I'm getting the following output:

kg            ^           2  [expected: kg^2]
 �ȷ2�U        ^           1  [expected: m^1]
 �ȷ2�U        ^           2  [expected: kg^2]

Apparently, after accessing the next or next%prev unit (which is basically the head of this short linked list), the code outputs random character instead of the symbs. If I change the order of the variables in the derived type, unit_t, for example if I put symb at the end of the derived type, I will get right symbs, but this time wrong pows.

Any idea what is the culprit of this rather odd behavior?


Using Rudrigo's comment below, I rewrote the code, and it works fine now. Just for the reference, the working code is as follows (if you have further suggestion or modification, please let me know, Nombre respository)

module units

  implicit none

  type unit_t
    character(len=16) :: symb
    real :: conv
    real :: pow = 1.d0
    logical :: cloned = .false.
    type(unit_t), pointer :: next => null(), prev => null()
  end type unit_t


  ! units definitions
  type(unit_t), target :: m = unit_t("m", 1.d0)
  type(unit_t), target :: km = unit_t("km", 1.d3)

  type(unit_t), target :: kg = unit_t("kg", 1.d0)

  type(unit_t), target :: s = unit_t("s", 1.d0)


  interface operator (**)
    procedure unit_int_pow
  end interface operator (**)


  interface operator (*)
    procedure units_mul
  end interface operator (*)

contains

  !> Cloning a given node (unit)
  function unit_clone(u) result (clone)
    implicit none

    type(unit_t), intent(in) :: u
    type(unit_t), pointer :: clone

    allocate(clone)

    clone%symb = trim(u%symb)
    clone%conv = u%conv
    clone%pow = u%pow
    clone%cloned = .true.
    clone%next => u%next
    clone%prev => u%prev
  end function unit_clone


  !> integer powers
  function unit_int_pow(u1, p) result(u)
    implicit none

    type(unit_t), intent(in) :: u1
    integer, intent(in) :: p

    type(unit_t), pointer :: u

    if ( u1%cloned ) then
      ! TODO: should be able to handle complex cases like: a * (b * c)**3
      !       most likly, only updating the power of the linked list chain
      !       would do the job
    else
      u => unit_clone(u1)
    end if
    u%pow = u%pow * p
  end function unit_int_pow


  !> multiplication
  function units_mul (u1, u2) result (u2c)
    implicit none

    type(unit_t), intent(in), target :: u1, u2
    type(unit_t), pointer :: u2c


    if ( u2%cloned ) then
      if ( associated(u2%prev) ) then
        u2c => u2%prev%next
      else
        u2c => u2
      end if
    else
      u2c => unit_clone(u2)
    end if


    if ( u1%cloned ) then
      if ( associated(u2%prev) ) then
        u2c%prev => u1%prev%next
      else
        u2c%prev => u1
      end if
    else
      u2c%prev => unit_clone(u1)
    end if

    u2c%prev%next => u2c
  end function units_mul
end module units

Upvotes: 3

Views: 239

Answers (1)

Rodrigo Rodrigues
Rodrigo Rodrigues

Reputation: 8566

A pointer in Fortran has three posible association status:

  • associated: the pointer is actually pointing to a defined and allocated variable / matching data storage (its target);
  • disassociated: it was (or is part of an objects that was) explicitly nullified or deallocated, or its target was properly disassociated.
  • undefined: anything different than the former, e.g. its target is (or became) undefined, or was deallocated by other means than by calling deallocate directly in the pointer itself, among other causes.

When execution of an instance of a subprogram completes (e.g. when function units_mul reaches end function), any unsaved local variable becomes undefined. Also, any allocatable local variable that is not saved or is a function result gets deallocated, and when an allocatable entity is deallocated, it also becomes undefined.

Back to your problem, u2c is an allocatable unsaved local variable inside units_mul function, where you associate u1c%next to it. When this function reaches the end, u2c ends its lifecycle and becomes undefined, bringing u1c%next to become also undefined, in a state referred in the Fortran lingo as dangling pointer.

This a text from the Fortran Standard describing this phenomena (even though it is referring to the case of modules host association, it's the same logic):

Note 19.10

A pointer from a module program unit might be accessible in a subprogram via use association. Such pointers have a lifetime that is greater than targets that are declared in the subprogram, unless such targets are saved. Therefore, if such a pointer is associated with a local target, there is the possibility that when a procedure defined by the subprogram completes execution, the target will cease to exist, leaving the pointer “dangling”. This document considers such pointers to have an undefined association status. They are neither associated nor disassociated. They cannot be used again in the program until their status has been reestablished. A processor is not required to detect when a pointer target ceases to exist.

A dangling pointer is not a reliable pointer, and the compiler has no control over it. They may, by any reason, keep pointing to their last memory address (and accidentally give the expected result in some cases, or the values would be gibberish from random memory address), but it will most certainly break, and the fail can be anything, from just wrong results to a SIGSEG fault or a memory address violation.

See this example code:

program dangling_pointer
  implicit none
  integer, pointer :: p(:)
  integer, allocatable :: a(:)

  call sub1(p)
  print *, 'sub1: ', p
  call sub2(p)
  print *, 'sub2: ', p
  call sub3(p, a)
  print *, 'sub3: ', p
  p => fun4()
  print *, 'fun4: ', p

contains
  subroutine sub1(dummy_p)
    ! the pointer passed as argument outlives the local target
    ! when the procedure ends, it becomes a "dangling pointer"
    integer, pointer :: dummy_p(:)
    integer, allocatable, target :: local_a(:)
    allocate(local_a(5))
    local_a = 100
    dummy_p => local_a
  end
  subroutine sub2(dummy_p)
    ! here the local variable is saved, so it persists. No problem here.
    integer, pointer :: dummy_p(:)
    integer, allocatable, target, save :: saved_a(:)
    allocate(saved_a(5))
    saved_a = 100
    dummy_p => saved_a
  end
  subroutine sub3(dummy_p, out_a)
    ! here the target is a passed argument, so it persists. No problem here.
    integer, pointer :: dummy_p(:)
    integer, allocatable, target :: out_a(:)
    allocate(out_a(5))
    out_a = 100
    dummy_p => out_a
  end
  function fun4() result(result_p)
    ! here the function result will be returned as a pointer. No problem here.
    integer, pointer :: result_p(:)
    allocate(result_p(5))
    result_p = 100
  end
end

With gfortran 9.0.0 I get:

 sub1:     14316208           0    14287184           0         100
 sub2:          100         100         100         100         100
 sub3:          100         100         100         100         100
 fun4:          100         100         100         100         100

Edit

I think this snippet would work for your problem:

allocate(u1c%next)
if (u2%cloned) then
  u1c%next = u2
else
  u1c%next = unit_clone(u2)
end if
u1c%next%prev => u1c

Upvotes: 2

Related Questions