OpenVMS


  64-bit Fortran on OpenVMS systems   





This page gives an overview of features, tips , bugs, work-arounds you will probably need when you want to use 64-bit memory addressing in applications compiled with Fortran on OpenVMS systems.
The Fortran compiler used in all the examples below are
        - VSI Fortran V8.3-104957-50Q83 on OpenVMS IA64 V8.4-2L1
        - VSI Fortran V8.3-104958-50R2O on OpenVMS Alpha V8.4-2L1

Please send your comments to joukj@hrem.nano.tudelft.nl

Contents

* How to get variables in 64-bit adressing mode? 
* Simple variables in modules 
* Using ITENT attribute 
* Using automatically allocated arrays in subroutines 
* Derived Data Types 
         * How to get derived data types in 64-bit adressing mode? 
         * The POINTER attribute 
         * Allocatable array of derived type and POINTER elements  
* Pointer assignment
* Subroutine/Function parameters
* Recursive Subroutines/Functions









Items



* How to get variables in 64-bit addressing mode?

The Fortran compiler for OpenVMS has no compiler flag (like the /pointer=64 in C) to use 64-bit pointers to the memory. The only option is to include a complier directive for each variable in the source code (see example below. This is most of the time too much work to do this for all variables. A compiler switch would be more than welcome.
           
            PROGRAM test
            !DEC$ ATTRIBUTES ADDRESS64 :: c64
            REAL ( KIND=4 ) , ALLOCATABLE :: c64( : )
             ....
            END

Demo-code can be downloaded : test_64.f90



* Simple variables in modules

Simple variables in modules seem to get different 64-bit addresses if compiled and linked from separate source files (see example below). The only work around I found was always combining the module and all routines that "use" the module in one source file.

        test.f90 :          
            PROGRAM test
            USE m
            IMPLICIT NONE
            v = 1
            v1 = 2
            write(*,*) v , v1
            call r
            END

        m.f90:
            MODULE m
            !DEC$ ATTRIBUTES ADDRESS64 :: v
            INTEGER , PUBLIC :: v
            INTEGER :: v1
            CONTAINS
            SUBROUTINE r
            WRITE(*,*) v , v1
            END SUBROUTINE
            END MODULE m

Compiling the module and the program seperately yields
:
            $ f90 m
            $ f90 test
            $ link test,m
            $ run test
                 1       2
                 0       2

Resulting in a 0 for v when the subroutine is called, while the value should be 1. When combining the 2 source files into one, the correct result is obtained:

            $ copy m.f90,test.f90 test2.f90
            $ f90 test2.f90
            $ link test2
            $ run test2
                 1       2
                 1       2

Allocatable arrays are tested to be working correctly also when included in a module compiled from anothe source file.

Demo-code can be downloaded : test.f90,  m.f90,  test2.f90




* Using the INTENT attribute

The INTENT attribute cannot be used for variables in 64-address space. They give a compiler arror (see below). Not using the attribute may have only influance on the optimization of the program, but not on the functionality. The only limitation is that you cannot overload operators/assignments with these paramets because these need functions/subroutines with the INTENT attribute. (By the way the same problem occurs with all POINTER variables in VMS-FORTRAN)

            subroutine inten( xin , xout , xinout , x )
            !DEC$ ATTRIBUTES ADDRESS64 :: xin , xout , xinout , x
            real, intent(in) :: xin
            real, intent(out) :: xout
            real, intent(inout) :: xinout
            real :: x
            call www( xin , xout , xinout , x )
            return
            end

            $ f90 intent.f90

            !DEC$ ATTRIBUTES ADDRESS64 :: xin , xout , xinout , x
            ..............................^
            %F90-E-ERROR, Conflicting attributes or multiple declaration of name. [XIN]
            at line number 2 in file $DISK7:[JOUKJ.test]intent.f90;4
           
            !DEC$ ATTRIBUTES ADDRESS64 :: xin , xout , xinout , x
            ....................................^
            %F90-E-ERROR, Conflicting attributes or multiple declaration of name. [XOUT]
            at line number 2 in file $DISK7:[JOUKJ.test]intent.f90;4
           
            !DEC$ ATTRIBUTES ADDRESS64 :: xin , xout , xinout , x
            .............................................^
            %F90-E-ERROR, Conflicting attributes or multiple declaration of name. [XINOUT]
            at line number 2 in file $DISK7:[JOUKJ.test]intent.f90;4

Demo-code can be downloaded : intent.f90




* Using automatically allocated arrays in subroutines

;Automatic allocatable arrays in 64-bit adress space make the compiler crash (see example below). A work-around is expicitly code the (de)allocation.

   auto.f90:
             subroutine a( n )
            integer n
            !DEC$ ATTRIBUTES ADDRESS64 :: b
            real b(n)
            call www( b )
            return
            end

            $ f90 auto.f90
            Assertion failure: Compiler internal error - please submit problem report
            %GEM-F-ASSERTION, Compiler internal error - please submit problem report
            %TRACE-F-TRACEBACK, symbolic stack dump follows
            image            module                     routine                                                        line          rel PC                         abs PC
            F90$MAIN   GEM_DB          GEM_DB_ABORT                                        848 00000000000000D0    0000000000E70FB0
            F90$MAIN   GEM_DB          GEM_DB_ABORT_FAST                            738 0000000000000112     0000000000E70FF2
            F90$MAIN   GEM_IP             PROCESS_VARIABLES                          10514 0000000000014782      0000000000F94E32
            F90$MAIN   GEM_IP             PROCESS_ALL_VARIABLES                10234 0000000000013AC2    0000000000F94172
            F90$MAIN   GEM_IP             PROCESS_ALL_VARIABLES                10243 0000000000013B32     0000000000F941E2
            F90$MAIN   GEM_IP             GEM_IP_DATA_ACCESS_ANALYSIS   2301 0000000000001182      0000000000F81832
            F90$MAIN   GEM_CO           GEM_CO_COMPILE_MODULE              3582 00000000000014B2     00000000010E7992
            F90$MAIN   ME                      generate_code                                            103160 0000000000006042     00000000003F6142
            F90$MAIN   ME                      gem_xx_compile                                       102693 0000000000004AD2   00000000003F4BD2
            F90$MAIN   GEM_CP_VMS GEM_CP_MAIN                                          2629 00000000000027D2    0000000000E65E02
                                                                                                                                            0 FFFFFFFF80A2E1D2 FFFFFFFF80A2E1D2
            DCL                                                                                                                        0 000000000007D072    000000007AE45072
            %TRACE-I-END, end of TRACE stack dump

  but with (de)allocation auto2.f90 gives:

            subroutine a2( n )
            integer n
            !DEC$ ATTRIBUTES ADDRESS64 :: b
            real , allocatable :: b(:)
            allocate(b(n))
            call www( b )
            deallocate(b)
            return
            end

           $ f90 auto2.f90
           $





* Derived Data Types

Derived Data Types are not supported by this version of the Fortran compiler. However, in some cases it works. In this section I will show some cases where I found a workaround to get things working. But... be careful, I know there are more pitfalls. When I figured out what the problem is, I will expand this section.

       * How to get derived data types in 64-bit adressing mode?

Placing Derived Data Types works in the same way as for normnal variables: With a compiler directive you place the whole structure in 64-bit address space (see example below).

  deriv.f90:
           program deriv
            type ttt
            real :: a
            end type
           !DEC$ ATTRIBUTES ADDRESS64 :: tt64
            type(ttt) :: tt , tt64
            write(*,*) %loc( tt%a ) , %loc( tt64%a )
           end

           $ f90 deriv
           $ link deriv
           $ run deriv
                 262152        2147483648




       * The POINTER attribute

When one or more of the elements inside the derived type have the POINTER attribute one has to be careful. Although all variables are placed in 64-bit adress space and when you allocate the pointer it gets a 64-bit address, the compiler only reserves 32-bits for the pointer. A work-around is to use always the SEQUENCE key-word in the derived type and add a few dummy variables, which are never used, after the pointer-variable (see example below). The extra space you need depends on the number of indices of the pointer. If this is n you need 3*n+7 integer*4 variables to get correct allignment for the next variable in the derived type.
  deriv.f90:
           program deriv
            type ttt
            sequence
            real , pointer :: a( : , : )
            real , pointer :: b( : , : )
            end type
            type ttt2
            sequence
            real , pointer :: a( : , : )
            integer*4 dummy1( 13 )
            real , pointer :: b( : , : )
            integer*4 dummy2( 13 )
            end type
           !DEC$ ATTRIBUTES ADDRESS64 :: tt2 , tt
            type(ttt) :: tt
            type(ttt2) :: tt2
            allocate( tt%b( 2 , 2 ) )
            allocate( tt2%b( 2 , 2 ) )
            write(*,*) %loc( tt%b ) , %loc( tt2%b )
            allocate( tt%a( 2 , 2 ) )
            allocate( tt2%a( 2 , 2 ) )
            write(*,*) %loc( tt%b ) , %loc( tt2%b )
           end

           $ f90 deriv

            type ttt
           .......^
           %F90-W-WARNING, The structure contains one or more misaligned fields. [TTT]
           at line number 2 in file $DISK7:[JOUKJ.test]deriv.f90;4
           $ link deriv
           %ILINK-W-COMPWARN, compilation warnings
                              module: DERIV
                              file: $DISK7:[JOUKJ.test]deriv.OBJ;4
           $ run deriv
                     2147508240      2147508288
                     4294967296      2147508288

One sees two problems :
    1) There is some misallignment in the "wrong" derived type
    2) The two lines of the result should be the same but for the "wrong" derived type some results are overwritten by the second allocation

       * Allocatable array of derived type and POINTER elements

A very explosive mixture of 32-bit and 64 bit pointer is obtained when placing an allocatable array of a derived type containing pointers to arrays. It appears that after allocation of the array of the derived type a subsequent allocation of  the array with the POINTER attribute gives a 32-bit pointer (which you do not get when the array has a fixed length). However when by first copying the element to an identical non-array variable, allocating and copying back, the allocation in 64-bit space is possible (see example below). However you still have problems when using the variables in the routine where the original declaration was made. You get the correct values after copying an alemanet to another variable or when used in a subroutine.
The same happens if one of the parameters is a pointer to another derived type which includes pointers to arrays (see second ecemple below)

           
            module mod_www
                type www
                sequence
                real :: a1 , a2
                real , pointer :: r(:)
                integer :: dummy(8)
                end type
             end module
           
             program test
             use mod_www
            !DEC$ ATTRIBUTES ADDRESS64 :: r_a , r_a1 , r_a2
             type( www ) , allocatable :: r_a( : )
             type( www) :: r_a1 , r_a2
             allocate( r_a( 5 ) )
             allocate( r_a(3)%r(20 ) )
             Write( * , * ) 'wrong adress in 32-bit space : ' , %loc( r_a(3)%r )
              r_a2 = r_a(4)
             allocate( r_a2%r(20))
             r_a(4) = r_a2
             r_a1 = r_a( 4 )
             write(*,*)
             write(*,*) 'allocation in special routine :'
             write(*,*) 'first location wrong but correct after copying variable'
             write(*,*) loc( r_a(4)%r ) , %loc( r_a1%r )
             call jjj( r_a , 5 )
             call jjj1( r_a(4) )
             end

             subroutine jjj( rrr , n )
             use mod_www
             integer n
             !DEC$ ATTRIBUTES ADDRESS64 :: rrr
             type (www) :: rrr( n )
             write(*,*) 'and also correct when passing the whole array to subroutine'
             write(*,*) loc( rrr(4)%r )
             end

             subroutine jjj1( rrr )
             use mod_www
             integer n
             !DEC$ ATTRIBUTES ADDRESS64 :: rrr
             type (www) :: rrr
             write(*,*) 'and also correct when passing the single element to subroutine'
             write(*,*) loc( rrr%r )
             end  $ f90 test.f90
 $ link test
 $ run test
wrong adress in 32-bit space :                 401424

allocation in special routine :
first location wrong but correct after copying variable
                    0            2147508624
and also correct when passing the whole array to subroutine
           2147508624
and also correct when passing the single element to subroutine
           2147508624


Second example :

            module mod_www
             TYPE www1
             sequence
             INTEGER,POINTER ::NPRO_POS(:)
             integer dummy( 10 )
             END TYPE
             TYPE www21
             TYPE(www1),POINTER:: twww21
             integer dummy( 10 )
             END TYPE
            
             end module
            
             program test2
            
             use mod_www
             !DEC$ ATTRIBUTES ADDRESS64 :: www0 , twww2 , thelp
             type( www21 ) :: www0
             TYPE(www1),target:: twww2
             type(www1) :: thelp
            
             www0%twww21=>twww2
             write(*,*) "correct in 64-bit space : " , %loc( www0%twww21 )
             call jallocate( www0%twww21 , 30 )
             thelp = www0%twww21
             write(*,*) "correct value : " , %loc( thelp%npro_pos )
             write(*,*) "should be the same as above but is not" , %loc( www0%twww21%npro_pos )
             end
            
             subroutine jallocate( wd , n )
             use mod_www
             !DEC$ ATTRIBUTES ADDRESS64 :: wd
             type (www1) :: wd
             allocate( wd%npro_pos( n ) )
             return
             end
  
    $ f90 test
    $ link test
    $ run test
     correct in 64-bit space :             2147483768
     correct value :             2147508240
     should be the same as above but is not                     0


When the allocatable derived tpye is included in another derived type thing become even more complecated as shown in the example below

$ ty test.f90
module m
  TYPE struct1
    sequence
    REAL,POINTER:: V(:)
    integer*4 dummy1( 10 )
  end type
  type struct
    sequence
     type( struct1 ) , pointer :: str( : )
    integer*4 dummy1( 10 )
  end type
end module m
PROGRAM test
  USE m
  IMPLICIT NONE
  !DEC$ ATTRIBUTES ADDRESS64 :: str1 , str2 , str0 , str00 , ppp
  TYPE (struct1) :: str1 , str2
  TYPE (struct) :: str0 , str00
  real , allocatable , target :: ppp( : )
  allocate( str0%str( 5 ) )
  allocate( str00%str( 5 ) )
  allocate( str00%str(1)%v( 10 ) )
  allocate( ppp ( 10 ) )
  ppp( 1 ) = 10.0
  str1%v => ppp( : )
  str0%str( 1 ) = str1
  str00%str(1)%v( 1 ) = 5.0
  write(*,*) 'location of v in str00 in in 32-bit space'
  write(*,*) loc( str1%v( 1 ) ) , loc( str00%str(1)%v( 1 ) )
  write(*,*) 'location of v in str0 is not ok'
  write(*,*) loc( str0%str(1)%v( 1 ) )
  write(*,*) str1%v( 1 )
  write(*,*) str00%str(1)%v( 1 )
  call test_str( str0 , str00 )
  deallocate( str00%str(1)%v )
  allocate( str2%v( 10 ) )
  str2%v( 1 ) = 5.0
  str00%str(1) = str2
  ! crash on this line (if not commented)
  !write(*,*) str00%str(1)%v( 1 )
  call test_str1( str0 , str00 )
end
subroutine test_str1( str0 , str00 )
  USE m
  !DEC$ ATTRIBUTES ADDRESS64 :: str1 , str0 , str00
  TYPE (struct1) :: str1
  TYPE (struct) :: str0 , str00
  str1 = str0%str(1)
  write(*,*) str1%v( 1 )
  write(*,*) 'location of v in str0 and str00 are not ok'
  write(*,*) loc( str1%v( 1 ) ) , loc( str0%str(1)%v( 1 ) )
  write(*,*) loc( str00%str(1)%v( 1 ) )
  str1 = str00%str(1)
  write(*,*) str1%v( 1 )
end
subroutine test_str( str0 , str00 )
  USE m
  !DEC$ ATTRIBUTES ADDRESS64 :: str1 , str0 , str00
  TYPE (struct1) :: str1
  TYPE (struct) :: str0 , str00
  str1 = str0%str(1)
  write(*,*) str1%v( 1 )
  write(*,*) 'location of v in str0 is not ok'
  write(*,*) loc( str1%v( 1 ) ) , loc( str0%str(1)%v( 1 ) )
  str1 = str00%str(1)
  write(*,*) 'location of v in str00 is in 32-bit space and useable'
  write(*,*) 'while location of v in str1 is in 64-bit space and not useable'
  write(*,*) loc( str1%v( 1 ) ) , loc( str00%str(1)%v( 1 ) )
  write(*,*) str00%str(1)%v( 1 )
end

$ f90 test
$ link test
$ run test
location of v in str00 in in 32-bit space
           2147509008               1908752
location of v in str0 is not ok
                    0
  10.00000
  5.000000
  10.00000
location of v in str0 is not ok
           2147509008                     0
location of v in str00 is in 32-bit space and useable
while location of v in str1 is in 64-bit space and not useable
          17181777932               1908752
  5.000000
  10.00000
location of v in str0 and str00 are not ok
           2147509008                     0
                    0
  5.000000


* Pointer assignment

Be careful with pointers assignments. If not both pointers are in either 32-bit or 64 bit space thing may go wrong as shown in the example below (the first output line is wrong, the second correct) and always give the shapes of the arrays explicitely to avoid confusion on the location:

            module m
            TYPE struct1
            sequence
            REAL(8),POINTER:: V(:,:)
            integer*4 dummy1( 13 )
            END TYPE
           
            TYPE str2
            sequence
            REAL(8),POINTER :: V(:,:)
            integer*4 dummy11( 13 )
            END TYPE
           
            end module m
           
            PROGRAM test
            USE m
            IMPLICIT NONE
            !DEC$ ATTRIBUTES ADDRESS64 :: K
            TYPE (struct1) K , K1
            !DEC$ ATTRIBUTES ADDRESS64 :: W , W2
            TYPE (str2) W , W2
            allocate ( K1%V( 20 , 20 ) )
            W%V =>K1%V
            write(*,*) loc( W%V ) , loc( K1%V )
            allocate ( K%V( 20 , 20 ) )
            W2%V =>K%V
            W%V =>K%V( : , :  )
            do i = 1 , 20
              do j = 1 , 20
                k%V( i , j ) = 1000. * i + j
              end do
            end do
            write(*,*) loc( W%V ) , loc( K1%V )
            allocate ( K%V( 20 , 20 ) )
            W%V =>K%V
            write(*,*) 'next 2 lines wrong'
            write(*,*) k%V( 10 , 10 ) , W2%V( 10 , 10 )
            write(*,*) k%V( 5 , 10 ) , W2%V( 5 , 10 )
            write(*,*) 'next 2 lines correct'
            write(*,*) k%V( 10 , 10 ) , W%V( 10 , 10 )
            write(*,*) k%V( 5 , 10 ) , W%V( 5 , 10 )
            write(*,*) loc( W%V ) , loc( K%V )
            END
           
            $ f90 test
            $ link test
            $ run test
                 34360074088                335888
                   2147508240        2147508240
                 next 2 lines wrong
                    10010.0000000000        1001.00000000000
                    5010.00000000000        1001.00000000000
                 next 2 lines correct
                    10010.0000000000        10010.0000000000
                    5010.00000000000        5010.00000000000



Another problem accurs when a  derived type with allocatable arrays is pointed to as a whole. In thsi case the program crashes when accessing the elements of the allocatable array. Hoowever id the pointer is used as a parameter in a subroutine, inside the subroutine no problems occur:

            module m
            TYPE struct1
            sequence
            REAL(8),POINTER:: V(:,:)
            integer*4 dummy1( 13 )
            END TYPE

            end module m

            PROGRAM test
            USE m
            IMPLICIT NONE
            !DEC$ ATTRIBUTES ADDRESS64 :: K , K1
            TYPE (struct1) , target :: K1
            TYPE (struct1) , pointer :: K
            integer i , j
            allocate ( K1%V( 20 , 20 ) )
            do i = 1 , 20
              do j = 1 , 20
                k1%V( i , j ) = 1000. * i + j
              end do
            end do
            K =>K1
            call nocrash( k1 , k )
            write(*,*) K1%V( 10 , 10 )
            write(*,*) 'Will crash on nect line'
            write(*,*) k%V( 10 , 10 )
          END

          subroutine nocrash( k1 , k )
            USE m
            IMPLICIT NONE
            !DEC$ ATTRIBUTES ADDRESS64 :: K , K1
            TYPE (struct1) :: K1
            TYPE (struct1) :: K
            write(*,*) K1%V( 10 , 10 )
            write(*,*) 'no crash on next line'
            write(*,*) k%V( 10 , 10 )
            return
          end
    

$ f90 test
$ link test
$ run test
  10010.0000000000
no crash on next line
  10010.0000000000
  10010.0000000000
Will crash on nect line
%SYSTEM-F-ACCVIO, access violation, reason mask=00, virtual address=0000000014000000, PC=0000000000020C11, PS=0000001B
%TRACE-F-TRACEBACK, symbolic stack dump follows
image     module    routine               line      rel PC                          abs PC
test              M       TEST                   27    0000000000000C11       0000000000020C11
                                                             0     FFFFFFFF80A2E1D2   FFFFFFFF80A2E1D2
DCL                                                     0     000000000007D072      000000007AE45072
%TRACE-I-END, end of TRACE stack dump



* Subroutine/Function parameters

Not in all cases (i.e. arrays) the  parametrs of subroutine and functions are passed correctly.
To be on the safe side ensure that both on the calling and the excecuting side the parameres are in the same memory area.


The case of character typed parameters is special, due to the fact that they are passed by descriptor.
To be on the safe side use a module to call them (see example below).

$ type test.f90 module tc
contains
subroutine testc( c )
!DEC$ ATTRIBUTES ADDRESS64 :: c
character ( len = * ) c
write(*,*) c
end subroutine
end module tc
program test
use tc
!DEC$ ATTRIBUTES ADDRESS64 :: a , b
character*5 a , b , d
a = 'aaaaa'
b = 'bbbbb'
d = 'ddddd'
write(*,*) 'correct'
call testc( a )
call testc( b )
call testc( 'cccccccccc' )
call testc( d )
write(*,*)
write(*,*) 'line 1&2 correct line 3&4 wrong'
call testc2( a )
call testc2( b )
call testc2( 'cccccccccc' )
call testc2( d )
end
subroutine testr( r )
!DEC$ ATTRIBUTES ADDRESS64 :: r
real r
write(*,*) r
end
subroutine testc2( c )
!DEC$ ATTRIBUTES ADDRESS64 :: c
character ( len = * ) c
write(*,*) c
end subroutine
$ f90 test.f90
$ link test.f90
$ run test
correct
aaaaa
bbbbb
cccccccccc
ddddd

line 1&2 correct line 3&4 wrong
aaaaa
bbbbb
bbbbb
bbbbb


* Recursive Subroutines/Functions

Local variables in recursive subroutines/functions may not behave as local variables as can bee seen in the following example (This is sure a bug of the Fortran compiler)

$ type recur_64.f90
module lev
  integer :: level = 0
end module
recursive subroutine rec( n )
  use lev
!DEC$ ATTRIBUTES ADDRESS64 :: n1 , n , n2
  integer n , n1 , n2
  if ( n <= 1 ) return
  level = level + 1
  n1 = n / 2
  n2 = n1
  write(*,*) 'in  : ' , level , n , n1 , n2
  call rec( n1 )
  write(*,*) 'out : ' , level , n , n1 , n2
  level = level - 1
  return
end
program test
  call rec( 8 )
end

$ f90 recur_64
$ link recur_64
$ run recur_64
in  :            1           8           4           4
in  :            2           4           2           2
in  :            3           2           1           1
out :            3           2           1           1
out :            2           4           1           2
out :            1           8           1           4

The last 2 collumns should be equal be are not: the third collumn is wrong.



But when leaving n , n1 and n2 in 32-bit space, the third collumn is correct:

in  :            1           8           4           4
in  :            2           4           2           2
in  :            3           2           1           1
out :            3           2           1           1
out :            2           4           2           2
out :            1           8           4           4

Demo-code can be downloaded : recur_64.f90,  recur_32.f90