3

Generally speaking I want to rename allocatable variables in a derived type that are passed through subroutine arguments. Writing everything with 'derived%type_xx' is not so pleasant. Besides, I don't want to spend extra memory on copying the values of the derived type to a new variable which costs new allocated memory. Furthermore, I know allocatable arrays are preferred than pointers for many reasons. I try to define pointers to the allocatable variable, but failed. I tried this because I want to simplify my code, both to be readable and not to be too long. I wonder if there's a way of achieving the goal? Thanks.

Here's the demonstration code:

Module module_type
IMPLICIT NONE
    TYPE type_1
        REAL,ALLOCATABLE                  ::      longname_1(:), longname_2(:)
    END TYPE
END MODULE

!------------------------------------------------------------------------------------------
SUBROUTINE TEST(input)
    USE MODULE module_type
IMPLICIT NONE
    TYPE(type_1)                          ::      input
    input%longname_1 = input%longname_1 + input%longname_2   ! Use one line to show what I mean
END SUBROUTINE

And here's what failed:

Module module_type
IMPLICIT NONE
    TYPE type_1
        REAL,ALLOCATABLE                  ::      longname_1(:), longname_2(:)
    END TYPE
END MODULE

!------------------------------------------------------------------------------------------
SUBROUTINE TEST(input)
    USE MODULE module_type
IMPLICIT NONE
    TYPE(type_1),TARGET                    ::      input

    REAL,POINTER                           ::      a => input%longname_1 &
                                                 & b => input%longname_2

    a = a + b   ! much better for reading
END SUBROUTINE

It seems like a small issue, but I'd like to read my code without too much pain in the future. So what's the best option? Thanks a lot.

Ruizhi
  • 87
  • 10

2 Answers2

5

You can use the ASSOCIATE construct to associate a simple name with a more complex designator or expression.

You could also use the subobjects of the derived type as actual arguments to a procedure that carried out the operation.

You pointer approach failed because you had a rank mismatch - you were attempting to associate scalar pointers with array targets. You may also have had problems if an explicit interface to your procedure was not available in the calling scope. An explicit interface is required for procedures with dummy arguments with the TARGET attribute.

Use of pointers for this sort of simple name aliasing may reduce the ability of the compiler to optimize the code. Something like ASSOCIATE should be preferred.

IanH
  • 21,026
  • 2
  • 37
  • 59
4

Update: After @IanH made his comment, I have gone back to check: I was completely and utterly wrong on why your code failed. As he pointed out in his answer, the main issue is that pointer and target have to have the same rank, so you'd have to declare a and b as:

real, pointer :: a(:), b(:)

Secondly, before you can actually point these pointers to the targets, the targets have to be allocated. Here's an example that works:

program allocatable_target

    implicit none
    type :: my_type
        integer, allocatable :: my_array(:)
    end type my_type
    type(my_type), target :: dummy
    integer, pointer :: a(:)

    allocate(dummy%my_array(10))
    a => dummy%my_array
    a = 10
    print *, dummy%my_array

end program allocatable_target

If you have a Fortran 2003 compatible compiler, you can use associate -- which is specifically meant for this kind of issue. Here's an example:

program associate_example

    implicit none
    type :: my_type
        integer, allocatable :: long_name_1(:), long_name_2(:)
    end type my_type

    type(my_type) :: input

    integer :: i
    allocate(input%long_name_1(100), input%long_name_2(100))

    associate (a=>input%long_name_1, b=>input%long_name_2)
        a = (/ (i, i = 1, 100, 1) /)
        b = (/ (2*i+4, i = 1, 100, 1) /)
        a = a + b
    end associate

    print *, input%long_name_1

end program associate_example

Inside the associate block, you can use a and b as a shortform for the declared longer named variables.

But other than that, I suggest you get an editor with proper code completion, then long variable names are not that much of an issue any more. At the moment I'm trying out Atom and am quite happy with it. But I have used vim with the proper expansions for a long time.

chw21
  • 7,970
  • 1
  • 16
  • 31
  • Thank you for showing the detailed use of associated construct! – Ruizhi Aug 12 '16 at 02:18
  • WARNING: If the selector has the `allocatable` or `pointer` attribute, associate_name does not inherit the attribute. However, if the selector is an array, associate_name will assume the same rank and upper and lower bounds of each dimension and if the selector is a dummy variable and has the `intent`, `target`, or `volatile` attribute, associate_name assumes the same attribute. – jlokimlin Aug 13 '16 at 02:22