[Search for users]
[Overall Top Noters]
[List of all Conferences]
[Download this site]
| Title: | Digital Fortran | 
| Notice: | Read notes 1.* for important information | 
| Moderator: | QUARK::LIONEL | 
|  | 
| Created: | Thu Jun 01 1995 | 
| Last Modified: | Fri Jun 06 1997 | 
| Last Successful Update: | Fri Jun 06 1997 | 
| Number of topics: | 1333 | 
| Total number of notes: | 6734 | 
1276.0. "DF90AO: Problems with NANs" by MGOF01::HSIMON () Wed Apr 30 1997 08:58
A customer has reported several problems with NANs. 
Has somebody general remarks about this problems?
The compiler version is F90 V4.1-270
Regards 
Hans-Werner
---------------------------------------------------------------------------
! Hallo DEC people!
! This program could not be compiled with the xlf-compiler (IBM). They have
! changed the compiler to make it run.
! This program could not be compiled with the CF90-compiler (CRAY). They have
! changed the compiler to make it run.
! This program could not be compiled with Your Fortran 90 compiler. You have
! not yet changed the compiler to make it run.
! I shall send you another Program with this problem. There it may be more
! clear why we would like to initialize with NaNs.
MODULE constants            ! 32 bit word
  INTEGER,PARAMETER ::                  &
          li = SELECTED_INT_KIND(18),   &
          lr = SELECTED_REAL_KIND(15,307)
  REAL,PARAMETER ::                     &
        r_nans = TRANSFER(2140000000,1.)
  REAL(lr),PARAMETER :: d_nans =        &
    TRANSFER(9220000000000000000_li,1D0)
END MODULE constants
PROGRAM nanq_nans
  USE constants
  REAL     :: x = r_nans, y = r_nans, z
  REAL(lr) :: u = d_nans, v = d_nans, w
! --- Next line: x,u newly assigned
  x = 2 ; z = x + 1; u = 2; w = u+1
  WRITE(*,*) x,z,u,w
! --- Next line: y,v only initialized
  z = y + 1; w = v+1 !Operation with NaNS
  WRITE(*,*) y,z,v,w
END PROGRAM nanq_nans
---------------------------------------------------------------------------
! Hallo DEC people!
! In Fortran 95 it is possible to initialize all instances of a defined
! datatype. If all variables of this type are automatic initialized with
! NaNs, we can detect the use of such a variable if it has not become a
! a value by assignment.
! This program detects a second compiler error I have reported.
! The second error is avoided by the !@ lines (comment) .
! Best regards
!     Gerd Groten       ([email protected])
MODULE autoinit
  REAL,PARAMETER :: undef = TRANSFER(2140000000,1.)
! REAL,PARAMETER :: undef = HUGE(1.) ! This works without error
  TYPE,PUBLIC :: sreal
    REAL :: r = undef
  END TYPE sreal
  TYPE(sreal),PARAMETER,PUBLIC :: nans = sreal(undef)
  INTERFACE ASSIGNMENT(=)
    MODULE PROCEDURE r_to_sr
  END INTERFACE
!@  INTERFACE OPERATOR(*)
!@    MODULE PROCEDURE sr_mult_sr
!@  END INTERFACE
  PUBLIC ASSIGNMENT(=)
!@  PUBLIC OPERATOR(*)
  PRIVATE ::  r_to_sr
!@ PRIVATE sr_mult_sr
 CONTAINS
  SUBROUTINE r_to_sr(x,y)
    TYPE(sreal),INTENT(OUT) :: x
    REAL,INTENT(IN)         :: y
    x % r = y
  END SUBROUTINE r_to_sr
!@  FUNCTION sr_mult_sr(x,y) RESULT(z)
!@    TYPE(sreal),INTENT(IN) :: x,y
!@    TYPE(sreal)            :: z
!@    z % r = x % r  *  y % r
!@  END FUNCTION sr_mult_sr
END MODULE autoinit
PROGRAM autoreal
  USE autoinit
  TYPE(sreal) :: u,v
  v = 1.
  WRITE(*,*) nans
  WRITE(*,*) u   ! not initialized : NaNs
!@  u = u*v        ! Operation with NaNs, must cause an error.
  WRITE(*,*) u,v
END PROGRAM autoreal
---------------------------------------------------------------------------
! This program dies with a last chance error at compile time.
! I have send a similar error in the last days.
! I use the V4.1-270 compiler.
! This program and the next letter shall demonstrate that there is an
! inconsistency between the error-prone expression calculated at compile 
! time and the same expression calculated at run time.
PROGRAM mystery
  INTEGER,PARAMETER :: id = PRECISION(1.)/13,     &
                       ik = id*18 + (1-id)*9,     &
                       ip = SELECTED_INT_KIND(ik)
  INTEGER(ip),PARAMETER :: ifac = 1077689403_ip*(4*id) + (1-id)
  INTEGER(ip),PARAMETER :: myst = ifac*2139095041_ip
  REAL,PARAMETER    :: nans = TRANSFER(myst,1.)       ! <<< ---
  REAl              :: a
  WRITE(*,'(" 0 or 1 :")',ADVANCE='NO')
  READ(*,*) i
  IF (i==0) THEN
    a = nans
  ELSE
    a = 1
  END IF
  WRITE(*,*) 'After assignment'
  a = a*a
  WRITE(*,*) 'After operation'
  WRITE(*,*) a
END PROGRAM mystery
---------------------------------------------------------------------------
! A remark to the problem with the NaNs (the name of the program I have
! mailed first was "mystery").
! Initializing with NaNs would be usefull to detect errors.
! In Fortran 95 I could define a type
!     TYPE,PUBLIC :: myreal
!       r = NaNs
!     END TYPE myreal
! Any use of a variable of this type would cause an error if nothing
! is assigned to the variable.
! Many of our users miss the possibility to detect undefined variables
! or undefined elements of an array. The realisation with "myreal"
! would solve the problem on a Fortran95 base, not only for a special
! compiler ( such as Watfiv in the past ).
! In addition, there is an  i n c o n s i s t e n c y  between the usage 
! of my NaNs expression in defining a named constant (at compile time) 
! and the usage in defining a variable at execution time.
! This is the execution time version. It works as expected.
! The following changed "mystery" shows the effect.
!    Best regards
!                 Gerd Groten         ([email protected])
PROGRAM mystery2
  INTEGER,PARAMETER :: id = PRECISION(1.)/13,     &
                       ik = id*18 + (1-id)*9,     &
                       ip = SELECTED_INT_KIND(ik)
  INTEGER(ip),PARAMETER :: ifac = 1077689403_ip*(4*id) + (1-id)
! INTEGER(ip),PARAMETER :: myst = ifac*2139095041_ip ! old version, crucial
  INTEGER(ip)           :: myst = ifac*2139095041_ip ! new version
! REAL,PARAMETER    :: nans = TRANSFER(myst,1.)      ! old version, wrong now
  REAL              :: nans
  REAl              :: a
  nans = TRANSFER(myst,1.)           ! not wrong if myst is a variable !
  WRITE(*,'(" 0 or 1 :")',ADVANCE='NO')
  READ(*,*) i
  IF (i==0) THEN
    a = nans                                    ! not wrong
  ELSE
    a = 1
  END IF
  WRITE(*,*) '!!!!!!! ----> After assignments <---- !!!!!!!'
  a = a + a                                     !  crash
  WRITE(*,*) '!!!!!!! ----> After operation   <---- !!!!!!!'
  WRITE(*,*) a                                  ! second crash
END PROGRAM mystery2
| T.R | Title | User | Personal Name
 | Date | Lines | 
|---|
| 1276.1 | Looks like a bug(s) | TLE::EKLUND | Always smiling on the inside! | Wed Apr 30 1997 13:37 | 10 | 
|  |     	I looked at the first example briefly, and can reproduce the
    symptom as you described (last chance handler during compilation).
    That's not good.  We'll take a look at how to fix this.  I have
    not yet looked at the other examples.
    
    	Thanks for the simple examples!
    
    Cheers!
    Dave Eklund
    
 | 
| 1276.2 |  | TLE::EKLUND | Always smiling on the inside! | Thu May 01 1997 11:28 | 7 | 
|  |     	The program "mystery" seems to be the same failure as "nanq_nans".
    The Last chance handler gets provoked at the same place in the
    compiler.
    
    Cheers!
    Dave Eklund
    
 |