Silverfrost Forums

Welcome to our forums

Why we have to declare random@ ?

5 May 2018 11:27 #22087

It is FTN95 own function, why it was not declared inside its own internals? If it is not declared why it causes access violation CRASH? And at the end why compiler does not warn that it was not declared?

6 May 2018 1:25 #22089

You leave us guessing as to how you reached these conclusions. Example code, please. Do you need to use RANDOM@ at all, instead of calling the standard intrinsic subroutine RANDOM_NUMBER?

I do find some problems with RANDOM@.

program trand
implicit none
real x
x = random@()
print *,x
end program

Compiling and running with /lgo gives:

[FTN95/Win32 Ver. 8.30.169 Copyright (c) Silverfrost Ltd 1993-2018]
    NO ERRORS  [<TRAND> FTN95 v8.30.169]
Creating executable: s:\FTN95\lgotemp@.exe
Program entered
     0.416111

Then, with /64 added:

s:\FTN95>ftn95 /64 xrnd.f90 /lgo
[FTN95/x64 Ver. 8.30.169 Copyright (c) Silverfrost Ltd 1993-2018]
    NO ERRORS  [<TRAND> FTN95 v8.30.169]
[SLINK64 v2.03, Copyright (c) Silverfrost Ltd. 2015-2018]
Loading s:\FTN95\lgotemp@.obj
Creating executable file s:\FTN95\lgotemp@.exe
Program entered
    -1.002545E+26

The following variant

program trand
implicit integer (a-z)
real x
x = random@()
print *,x
end program

gives an FPU stack fault in 32-bit mode and 4.516899E+07 in 64-bit mode.

6 May 2018 7:50 #22090

I tried a few options to get it to work in PLATO with 'Release x64' I needed 'real*8, external :: random@' to get it to work

program trand 
! implicit none
! implicit real (a-h,o-z)
! real, intrinsic :: random@
! real*8, external :: random@      ! this works
 real :: x 
 x = random@() 
 print *,x 
 end program

My view is there are a few FTN95 functions in /64 that should have the intrinsic attribute (or behave like). I can think of the following, but there are probably others. This could include: WINIO@ (integer4) RANDOM@() (real8) RGB@(r,g,b) (integer4) RDTSC_VAL@() (integer8)

FTN95 should recognise the kind for these functions and treat them accordingly.

I notice that the following works with /64:

 integer*4 r, g, b, rgb, rgb2, rgb@
  r = 100
  g = 50
  b = 75
  rgb  = rgb@ (r,g,b)
  rgb2 = rgb@ ( rgb, ishft(rgb,-8), ishft(rgb,-16) )
  write (*,*) rgb
  write (*,*) rgb2
  end
6 May 2018 12:40 #22091

Dan: The FTN95 extensions aren't part of standard-conforming Fortran, and so they do not have the status of intrinsic functions. Their type must therefore be declared, either because you have IMPLICIT NONE or because the name does not follow the implicit naming convention (in the case of WINIO@ or RGB@). INCLUDE <WINDOWS.INS> and other INCLUDEs and USEs etc do the declarations of type for you. Shame there isn't the equivalent for FTN95/77 extensions.

John: RANDOM@ doesn't need EXTERNAL as it is not used in a subprogram call.

Mecej4: one uses the old functions because they were there long before the functions became intrinisic. Incidentally, what did erf and erfc users do before those functions became intrinsic? Calling RANDOM@ as integer is a rather obvious error as a real-ish result is expected (INTEGER would give you 0 or 1 randomly if it was coded to return an INTEGER), and that it returns a result at all is worrying (but somehow not surprising).

Incidentally, the following:

      options (dreal) ! saves me a  lot of typing here ....
      program trand 
      x = random@() 
      call random_number (y)
      write(*,*) x, y
      end

does give different results in 32 and 64 bit mode, which I suppose is unsurprising. But it does give the same result each time the program is run, so perhaps the routines should be called pseudo_random_sequence@. Oddly, the result for y in 32bit mode is the same as for x in 64bit mode, but the other two are different.******

Eddie

6 May 2018 1:15 (Edited: 4 Jan 2022 11:19) #22092

[I started composing this response before Eddie's note arrived. Rather than modify what I wrote here, I'll address his comments separately, later.]

John, indeed there are many intrinsic functions and subroutines with names ending in @, but there is none with this ending in SALFLIBC.DLL. The compiler does some name transformation on many (which?) of these intrinsics. For example, a call to the F2008 intrinsic BESSEL_J0 ends up as a reference to DBESSEL_J0# in the OBJ file and DBESSEL_J0@ in the /exp listing file. The corresponding entry points are DBESSEL_J0# in SALFLIBC.DLL and DBESSEL_J0@ in SALFLIBC64.DLL. We have already noted that WINIO@ is replaced by WINDOW_PRINTF@@.

The way the compiler treats user errors in invoking some of these intrinsics is different in 32 and 64 bit programs. For example, with the argument missing in the invocation of BESSEL_J0 in the code

program tbess
   implicit none
!   real, intrinsic :: bessel_j0 ! seems to have no effect
   real :: x
!  x = bessel_j0(1.0)    ! works fine
   x = bessel_j0()      ! compiler crashes
   print *,x
end program

the 32-bit compilation causes the compiler to crash

[FTN95/Win32 Ver. 8.30.169 Copyright (c) Silverfrost Ltd 1993-2018]
0006)    x = bessel_j0()      ! compiler crashes
*** Illegal memory reference
*** Invalid machine instruction generated

whereas the 64-bit program gets compiled and linked, but crashes at run time:

s:\FTN95>ftn95 /64 xbess0.f90 /lgo
[FTN95/x64 Ver. 8.30.169 Copyright (c) Silverfrost Ltd 1993-2018]
    NO ERRORS  [<TBESS> FTN95 v8.30.169]
[SLINK64 v2.01, Copyright (c) Silverfrost Ltd. 2015-2018]
Loading s:\FTN95\lgotemp@.obj
Creating executable file s:\FTN95\lgotemp@.exe
Program entered

Access violation (c0000005) at address 1c022333

Within file SALFLIBC64.DLL
in DBESSEL_J0@ at address ba
Within file lgotemp@.exe
in TBESS at address 1d

Since an intrinsic function is being used, why should the error not be caught at compile time, especially if /check or /checkmate is specified?

Perhaps, we should all adopt Eddie's Law ('Lex Saxonicum' ?):

John, indeed there are many intrinsic functions and subroutines with names ending in @, but there is none with this ending in SALFLIBC.DLL. The compiler does some name transformation on many (which?) of these intrinsics. For example, a call to the F2008 intrinsic BESSEL_J0 ends up as a reference to DBESSEL_J0# in the OBJ file and DBESSEL_J0@ in the /exp listing file. The corresponding entry points are DBESSEL_J0# in SALFLIBC.DLL and DBESSEL_J0@ in SALFLIBC64.DLL. We have already noted that WINIO@ is replaced by WINDOW_PRINTF@@.

The way the compiler treats user errors in invoking some of these intrinsics is different in 32 and 64 bit programs. For example, with the argument missing in the invocation of BESSEL_J0 in the code

program tbess
   implicit none
!   real, intrinsic :: bessel_j0 ! seems to have no effect
   real :: x
!  x = bessel_j0(1.0)    ! works fine
   x = bessel_j0()      ! compiler crashes
   print *,x
end program

the 32-bit compilation causes the compiler to crash

[FTN95/Win32 Ver. 8.30.169 Copyright (c) Silverfrost Ltd 1993-2018]
0006)    x = bessel_j0()      ! compiler crashes
*** Illegal memory reference
*** Invalid machine instruction generated

whereas the 64-bit program gets compiled and linked, but crashes at run time:

s:\FTN95>ftn95 /64 xbess0.f90 /lgo
[FTN95/x64 Ver. 8.30.169 Copyright (c) Silverfrost Ltd 1993-2018]
    NO ERRORS  [<TBESS> FTN95 v8.30.169]
[SLINK64 v2.01, Copyright (c) Silverfrost Ltd. 2015-2018]
Loading s:\FTN95\lgotemp@.obj
Creating executable file s:\FTN95\lgotemp@.exe
Program entered

Access violation (c0000005) at address 1c022333

Within file SALFLIBC64.DLL
in DBESSEL_J0@ at address ba
Within file lgotemp@.exe
in TBESS at address 1d

Since an intrinsic function is being used, why should the error not be caught at compile time, especially if /check or /checkmate is specified?

Perhaps, we should all adopt Eddie's Law ('Lex Saxonicum' ?):

John, indeed there are many intrinsic functions and subroutines with names ending in @, but there is none with this ending in SALFLIBC.DLL. The compiler does some name transformation on many (which?) of these intrinsics. For example, a call to the F2008 intrinsic BESSEL_J0 ends up as a reference to DBESSEL_J0# in the OBJ file and DBESSEL_J0@ in the /exp listing file. The corresponding entry points are DBESSEL_J0# in SALFLIBC.DLL and DBESSEL_J0@ in SALFLIBC64.DLL. We have already noted that WINIO@ is replaced by WINDOW_PRINTF@@.

The way the compiler treats user errors in invoking some of these intrinsics is different in 32 and 64 bit programs. For example, with the argument missing in the invocation of BESSEL_J0 in the code

program tbess
   implicit none
!   real, intrinsic :: bessel_j0 ! seems to have no effect
   real :: x
!  x = bessel_j0(1.0)    ! works fine
   x = bessel_j0()      ! compiler crashes
   print *,x
end program

the 32-bit compilation causes the compiler to crash

[FTN95/Win32 Ver. 8.30.169 Copyright (c) Silverfrost Ltd 1993-2018]
0006)    x = bessel_j0()      ! compiler crashes
*** Illegal memory reference
*** Invalid machine instruction generated

whereas the 64-bit program gets compiled and linked, but crashes at run time:

s:\FTN95>ftn95 /64 xbess0.f90 /lgo
[FTN95/x64 Ver. 8.30.169 Copyright (c) Silverfrost Ltd 1993-2018]
    NO ERRORS  [<TBESS> FTN95 v8.30.169]
[SLINK64 v2.01, Copyright (c) Silverfrost Ltd. 2015-2018]
Loading s:\FTN95\lgotemp@.obj
Creating executable file s:\FTN95\lgotemp@.exe
Program entered

Access violation (c0000005) at address 1c022333

Within file SALFLIBC64.DLL
in DBESSEL_J0@ at address ba
Within file lgotemp@.exe
in TBESS at address 1d

Since an intrinsic function is being used, why should the error not be caught at compile time, especially if /check or /checkmate is specified?

Perhaps, we should all adopt Eddie's Law ('Lex Saxonicum' ?):

John, indeed there are many intrinsic functions and subroutines with names ending in @, but there is none with this ending in SALFLIBC.DLL. The compiler does some name transformation on many (which?) of these intrinsics. For example, a call to the F2008 intrinsic BESSEL_J0 ends up as a reference to DBESSEL_J0# in the OBJ file and DBESSEL_J0@ in the /exp listing file. The corresponding entry points are DBESSEL_J0# in SALFLIBC.DLL and DBESSEL_J0@ in SALFLIBC64.DLL. We have already noted that WINIO@ is replaced by WINDOW_PRINTF@@.

The way the compiler treats user errors in invoking some of these intrinsics is different in 32 and 64 bit programs. For example, with the argument missing in the invocation of BESSEL_J0 in the code

program tbess
   implicit none
!   real, intrinsic :: bessel_j0 ! seems to have no effect
   real :: x
!  x = bessel_j0(1.0)    ! works fine
   x = bessel_j0()      ! compiler crashes
   print *,x
end program

the 32-bit compilation causes the compiler to crash

[FTN95/Win32 Ver. 8.30.169 Copyright (c) Silverfrost Ltd 1993-2018]
0006)    x = bessel_j0()      ! compiler crashes
*** Illegal memory reference
*** Invalid machine instruction generated

whereas the 64-bit program gets compiled and linked, but crashes at run time:

s:\FTN95>ftn95 /64 xbess0.f90 /lgo
[FTN95/x64 Ver. 8.30.169 Copyright (c) Silverfrost Ltd 1993-2018]
    NO ERRORS  [<TBESS> FTN95 v8.30.169]
[SLINK64 v2.01, Copyright (c) Silverfrost Ltd. 2015-2018]
Loading s:\FTN95\lgotemp@.obj
Creating executable file s:\FTN95\lgotemp@.exe
Program entered

Access violation (c0000005) at address 1c022333

Within file SALFLIBC64.DLL
in DBESSEL_J0@ at address ba
Within file lgotemp@.exe
in TBESS at address 1d

Since an intrinsic function is being used, why should the error not be caught at compile time, especially if /check or /checkmate is specified?

Perhaps, we should all adopt Eddie's Law ('Lex Saxonicum' ?): [quote:777aa5b48d]If a feature is present, it ought to work.

to which I'd like to add the request [quote:777aa5b48d] and its behavior should be documented.

7 May 2018 2:41 (Edited: 7 May 2018 6:48) #22097

Eddie, your points are well taken. Nonstandard functions, if provided by a vendor, need not be intrinsic. If they are not, and they are not also generic, the user must provide a type declaration if implicit typing is off. It is in this aspect that we may object to how RANDOM@ is implemented. The program

program krnd
implicit none
!real*8, external :: random@
print *,kind(random@())
end

should be rejected by the compiler if RANDOM@ is not intrinsic, especially if /check is also specified. The program prints out '1', which clashes with the documented value of 2 in FTN95.CHM.

The curious coincidence that you noticed (between sequences produced by RANDOM@ and RANDOM_NUMBER) actually runs deeper. as the program

      program trand
      implicit none
      integer i, N
      integer, allocatable :: seed(:)
      real*8 xd,random@
      !call set_seed@(0.2718281828d0)
      do i=1,5
         xd=random@()
         write(*,'(ES12.4)')xd
      end do
      print *
      call random_seed(size=N)
      allocate(seed(n))
      !seed=(/ 1911729,1921729,1931729 /)
      !call random_seed(put=seed)
      do i=1,5
         call random_number(xd)
         write(*,'(ES13.5)') xd
      end do
      end program

demonstrates. The five numbers returned by RANDOM@ in 64-bit mode are the same as the five numbers returned by RANDOM_NUMBER in 32-bit mode.

If the seeding calls in this program are activated, you find that the 32-bit and 64-bit versions of RANDOM@ do not return the same numbers even if the user set the seed to a single definite value in advance.

7 May 2018 6:17 #22098

There are a couple of issues that have come to light from this thread and that need investigating...

  1. The addition to FTN95 of bessel_j0 etc. from the 2003/2008 standard is incomplete - optional arguments are not currently implemented. (Note that /F2K is now set true by default.)

  2. The fact that FTN95 gives no warning when IMPLICIT NONE is used and the function ends with @ is a little strange and needs to be reviewed. In this respect it is worth noting that, in the 1995 Standard, IMPLICIT NONE relates to 'data entities' so maybe not function return values. Either way, it appears that FTN95 is not entirely consistent in this respect. In theory at least, /DCLVAR should give a more comprehensive test but this also needs reviewing.

7 May 2018 6:23 #22099

Quoted from mecej4 RANDOM@ ... which clashes with the documented value of 2 in FTN95.HLP.

I was struggling to find where the kind for random@ is now documented. I finally found it listed as RANDOM.

The following program works with or without line 3 for 32-bit (supporting kind=1 or kind=2), but does not work for /64 and kind=1.

program krnd 
 implicit none 
! real*8, external :: random@ 
 print *,kind(random@()) 
 print *,random@()
 end

Who chose random@ as an example !!

Eddie,

I use EXTERNAL, mainly for documentation. I think the main use is for:

  1. identifying a routine argument as a function, or
  2. removing an intrinsic name, when an external function is provided (changing the name would be better ?)
7 May 2018 8:50 #22101

John, Don't forget use No 3, which is to specify the name of a named BLOCK DATA subroutine so that the linker looks for it (it is otherwise not explicitly mentioned, and may be missed if it is in a separately compiled file that isn't loaded).

Not that I'd do that, because BLOCK DATA is stupid, named or not. Passing a function name as a parameter is unnecessary in most codes (WINIO@ excluded). There may not be any reserved names in Fortran, but knowingly using an intrinsic subprogram name is a bit daft (although new Fortran standards may steal a name you chose already).

Use No 4 is to obfuscate your source code, so that it puzzles people who shouldn't be reading it ...

So all in all, as far as I'm concerned and with the exception of WINIO@, EXTERNAL might as well not exist!

FTN95.CHM refers to both RANDOM and RANDOM@.

It took all of my self-control not to start a thread entitled 'When is random not random', subtitled 'Some randoms are more random than other randoms'. It is only a matter of time before someone writes in to complain that the random sequences aren't the same ... I suppose the random number sequences are not the same between compilers, either.

Eddie

7 May 2018 3:00 #22102

Quoted from LitusSaxonicum It took all of my self-control not to start a thread entitled 'When is random not random', subtitled 'Some randoms are more random than other randoms'. Eddie

Sorry, George Marsaglia beat you to it, 'Random numbers fall mainly in the planes' : http://www.pnas.org/content/pnas/61/1/25.full.pdf (1968).

8 May 2018 11:05 #22104

Ten library functions have been identified that have names coded with a trailing @ symbol. The list includes RANDOM@. They are functions that in one sense do not need to be declared (because, by default, any arguments have the expected type) but whose default return type is 'wrong'. These are not FTN95 intrinsics as such but can be elevated to an equivalent status.

These ten functions will have this elevated status in the next release of FTN95. If the change proves successful then it will provide only a modest gain since all the other user-accessible library routines must still be declared.

Incidentally, in my Fortran programs I have habitually declared winio@ as having INTEGER return type. This turns out to be quite unnecessary because FTN95 knows this.

Here is a list of the ten functions...

DOT_PRODUCT4@
DOT_PRODUCT8@
FEXISTS@
FILE_EXISTS@
GLOBALMEMORYSTATUS@
HIGH_RES_CLOCK@
PROCESSMEMORYINFO@
RANDOM@
RGB@
USE_AVX@
8 May 2018 2:25 #22105

Paul,

Thanks for considering these 'special' functions.

I am not sure how extensive a longer list could be, but could the following be included: real10 function CPU_CLOCK@() integer8 function RDTSC_VAL@()

It is interesting that RANDOM@ works as both real4 and real8 for 32-bit ( if I tested it correctly)

8 May 2018 4:00 #22106

Quoted from JohnCampbell It is interesting that RANDOM@ works as both real4 and real8 for 32-bit ( if I tested it correctly)

That is the way that the 80X87 coprocessor behaves. You can often declare in the caller a wrong size of a real function and still get the correct result. Here is a test program, with the source split into two files.

real function funr(t)
implicit none
double precision t
funr=sqrt(t)
return
end

real function fund(t) ! invoked as double precision!
implicit none
double precision t
fund=sqrt(t)
return
end

The calling program:

program trealx
implicit none
real y,funr
double precision t,z,fund
t=1d-1
y=funr(t)
z=fund(t)
write(*,'(2ES22.15)')y,z
end program

Try running without and with /64.

9 May 2018 12:21 #22107

Dan,

You should review this above example of using inconsistent kind definitions for reals. Looks like another piece of devilry waiting to happen when converting to /64

9 May 2018 6:13 #22108

Thanks John. It turns out that CPU_CLOCK@() and RDTSC_VAL@() are FTN95 intrinsics and so do not need to be added to the list.

9 May 2018 8:08 #22109

All of the issues raised on this thread have now been reviewed and resolved in one way or another. This includes kind(random@()) which somehow came out in the wash with the value 2. I didn't know you could write this.

  1. Ten nominal FTN95 intrinsics have been added.
  2. Bessel function called with no arguments - crash fixed.
  3. Fortran 2008 intrinsics erf, erfc etc. tested for compliance with the 2008 standard.

The Fortran 2008 intrinsics in (c) are all fully supported (they are elemental as expected by the standard). The only exception is that bessel_jn and bessel_yn can only take 2 arguments and not 3 as the standard allows.

Please login to reply.