Is a variable exactly one of Pointer, Value or Unspecified?

When I define a variable (local in a subroutine, module/program variable, dummy argument) then my understanding is that I choose exactly one of the following cases:

integer :: x
integer, pointer :: x
integer, value :: x

Is that correct?

The value attribute can only be used for dummy arguments. The pointer and “unspecified” can be used for any variable.

Furthermore, when I have a pointer variable, and I use it in an expression, then the result is not a pointer, correct? For example, if I have a subroutine like this:

subroutine f2(x)
integer, pointer, intent(in) :: x
print *, x
end subroutine

Then I am required to call it with a pointer variable, such as:

integer, pointer :: y
allocate(y)
y = 5
call f2(y)

And that works, but the following does not work:

call f2(y+y)

Nor:

call f2((y))

From this I concluded that when a variable becomes an expression, it is effectively a “value”, even though you can’t actually declare a variable to have a value attribute outside a dummy argument. Is that correct?

So the rules of pointers are roughly:

  • If a pointer variable is used in an expression, it is automatically “dereferenced” and it becomes a value
  • The result of an expression is a value
  • When a value is assigned (using =) to a pointer variable, the pointer variable first gets “dereferenced” before assigning the value to it
  • When a dummy argument is:
    • a pointer: then the actual argument must also be a pointer — so you cannot pass in an expression
    • a value: then the actual argument gets “dereferenced” first, and in bind(c) procedures the argument is passed by value
    • unspecified: then the compiler is free to pass either by value or by reference internally (i.e., the user does not see that, you can pass in an expression), but in bind(c) procedures, it is passed by reference

Is there any other catch, or is that it?

Last question: Besides bind(c), is there any difference between the following two procedures from a user perspective:

subroutine g1(x)
integer, value, intent(in) :: x
print *, x
end subroutine

subroutine g2(x)
integer, intent(in) :: x
print *, x
end subroutine

In other words, is the value attribute only useful for the bind(c) subroutines? The value attribute is described in the section “8.5.18 VALUE attribute” of the Fortran 2018 standard. It says that “An entity with the VALUE attribute shall be a dummy data object.”. It says “dummy data object is a dummy argument that is a data object”. Finally, a “data object is a constant (7.1.4), variable (9), or subobject of a constant (5.4.3.2.4)”.

@certik, a lot of great questions. Of course, the best reference for your inquiries is the standard itself and, as needed, for any really confusing or error-prone situations, the standard committee and possibly the Interp subgroup.

Let us consider your first question. Naturally the place to start will be Section 8.2 Type declaration statement where you will find various attributes all mixed in with categories of objects to give a fairly long list:

and you have to wade through various sections to capture what is allowed and disallowed e.g.,

  • an object without the TARGET attribute nominally is not a valid target for an object with a POINTER attribute,
  • an object cannot have both the POINTER and the TARGET attributes even though the former can be a valid target!
  • an object cannot have both the POINTER and the ALLOCATABLE attributes even though the former can appear in an ALLOCATE statement!
  • an object with an ALLOCATABLE attribute springs into existence as unallocated but an object with a POINTER attribute has an undefined status until it is associated with a valid target or disassociated. Many find this confusing!
  • and on and on

My point being if one tries to summarize the rules and constraints in connection with data objects with Fortran, one will likely end up with something nearly as long as the standard itself but with a language that is not as precise as the standard and which can then be confusing for compiler implementors :frowning:

1 Like

First please note in Fortran, a variable with a POINTER attribute must be associated with a valid target for it to be referenced in an expression. Then the reference in the expression is to that target. So in that sense, a POINTER in Fortran can be seen as an alias to a target.

If you have code like so:

   integer, pointer :: x
   allocate( x, source=42 )
   print *, x
end

It’s as though the above were equivalent to the following:

   integer, pointer :: x
   integer, allocatable, target :: anonymous_object
   allocate( anonymous_object, source=42 )
   x => anonymous_object
   print *, anonymous_object
   ! but with no automatic deallocation stipulated for `anonymous_object`
end

As stated before, please note a reference to an associated pointer is to its target.

In terms of “catch”, please note a couple of intricacies with Fortran:

  • a data assignment using “=” to a variable with a POINTER attribute is different from a pointer assignment using “=>”.
  • Starting with Fortran 2008, there is also automatic targeting whereby an actual argument can have the TARGET attribute when the corresponding dummy argument has the POINTER attribute along with INTENT(IN).

Please note however those steeped in “standardese” will tell you the VALUE attribute in Fortran is a different concept specific to argument association that has deep semantic implications in the language since FORTRAN I.

With the combination of INTENT(IN) and VALUE and outside of BIND(C), a user’s perspective may depend on the processor in use i.e., a user can possibly come away with an impression of YMMV with the processor as to what it does in terms of effective argument association in the 2 instances you list. But I admit there now tends to be a convergence in implementation approaches and most processors tend to do similar things, meaning in this instance the user will likely perceive the 2 subroutines you list as behaving similarly.

Please see this thread. If you have users wanting to minimize the use of local variables and see some value (pun intended!) with perhaps improved code readability with mutable dummy arguments a la C-based and C-inspired languages, then they might do the following and employ the VALUE attribute in contexts outside of interoperability with C!!

module euclid_m
contains
   elemental function gcd( m, n )
   ! Find the greatest common advisor of two positive integers
      ! Argument list
      integer, value :: m, n
      ! Function result
      integer :: gcd
      ! Local variables
      integer :: tmp
      if ( (m <= 0).or.(n <= 0) ) error stop "m,n must be positive."
      loop_gcd: do
         if ( m == 0 ) exit loop_gcd
         if ( m < n ) then 
            tmp = m
            m = n
            n = tmp
         end if
         m = mod( m, n )
      end do loop_gcd
      gcd = n
   end function 
end module

With the following test driver,

   use euclid_m
   print *, "gcd(46332, 71162) = ", gcd(46332, 71162), "; expected result is 26" 
end

C:\temp>Euclid.exe
gcd(46332, 71162) = 26 ; expected result is 26

1 Like

bind(c) procedures are pass by reference, unless the argument is declared with the value attribute.

In observable behavior, no, not in this case. Implementations are allowed to pass by reference (bind(c) procedures must pass by reference, unless the value attribute is specified), and most do. The value, attribute means that a copy must be made, as it enforces pass by value. As @FortranFan’s example demonstrates, the “capability” that value allows is for one to NOT specify an argument’s intent, and you can then modify the dummy argument inside the body of the procedure, but the actual argument is not modified.

2 Likes

Thanks @kargl, @FortranFan and @everythingfunctional for all the feedback.

The reason I am asking these questions is to see whether the internal LFortran’s representation (we call it ASR – Abstract Semantic Representation) can be simplified using some of the constraints in the standard. Here is the actual issue at hand for me: ASR: move IntegerPointer, RealPointer, ... into a boolean argument for Variable (#557) · Issues · lfortran / lfortran · GitLab

These design decisions do not really influence the actual behavior of the compiler, since we ensure all the rules are properly implemented either way. But it’s always nice to represent things in a way that feels natural and that “encodes” some of the constrains by design.

Currently we encode the pointer attribute as a type, i.e., IntegerPointer. It seems more natural to just add the pointer attribute to the variable in the symbol table, because in an expression it seems the “type” of the intermediate is really just Integer.

We already have a value boolean in the symbol table, so we can add a pointer boolean. But I thought — since the standard says these two are mutually exclusive, then I can encode it by having an enum type with values Pointer, Value and Unspecified. This representation has the advantage that by the nature of it, it does not even allow you to have both the Pointer and a Value attribute.

However, even though in this particular case this might work, it seems the semantics of all these attributes is really complex.

So I am thinking of simply adding a boolean for each such attribute, and implement the proper checks of all the constrains (such as no pointer and value attribute at the same time) as regular checks for now, but not encoding these relationships in the representation itself.

After we can compile all codes, we can revisit this and see if there is a way to simplify the internal representation to be more “natural”.

Regarding this, is that what we should recommend people to write? It’s yet another feature to learn and get used to. I really like the intent(in / out / inout) approach. Now we have a value approach which is like intent(in) except that you can modify the argument internally. It seems a better approach would have been something like integer, value, intent(in) :: x, that would still be an intent(in) argument, but allows you to modify it inside, because it is passed by value.

I generally don’t because, as you said, it’s yet another feature to learn, and it would be more obvious to more readers that I’m making a local copy to modify if I use intent(in) and a local variable. I also don’t do modification very often, so I don’t usually need it anyway.

2 Likes

If you want to program C in Fortran, then yes. Otherwise, no. :slightly_smiling_face:

3 Likes