[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 | 
1151.0. "FORT-W-UNINIT" by VIRGIN::PFISTERR (Carpe Diem, Memento Mori) Mon Jan 27 1997 10:23
    Hi,
    when I compile the program below just with FORTRAN, I receive some
    FORT-W-UNINIT warnings. If I compile it with /NOOPT, the warnings
    disappears. The variables mentioned in the warning are from $SSDEF and
    IODEF and I can't define them. What could be wrong?
    
    Rene
    
    
    
    Program:
    C
    C
    ***************************************************************************
    C ************************** SUBROUTINE TT_SET
    ******************************
    C
    ***************************************************************************
    C
    C
            SUBROUTINE TT_SET (TMP,SEND)
    C
    C       Erstellt vom Terminal-Setup eine Kopie (TERM_CHAR) und gibt
    diese
    C       ans Hauptprogramm. Diese Kopie wird am Schluss des Programms
    C       von der Subroutine TT_RESET gebraucht, um die Setup-Einstellung
    C       wiederherzustellen.
    C       Danach erstellt die Subroutine die neue Setup-Einstellung.
    C
    C       Bem.: Das Privileg 'PHY_IO' ist fuer den Account notwendig!!
    C
    C       MODIFIKATIONEN:
    C       1.0     : A.Stark       1-JUN-1988
    C       1.1     : R.Eccher      8-JUN-1988   Fehlercode eingefuehrt
    C
    C
            IMPLICIT        INTEGER*4 (A-Z)
            INTEGER*4       SYS$QIOW
            INTEGER*4       NEW_TERMCHAR(2),SETUP
            INTEGER*2       TMP,SEND
    
    C
    C Common  (by Reference Variablen)
    C
            INTEGER*2       CODE                    !Fehler Code
            INTEGER*4       TT_CHAN,                !Kanalnummer
            1               TERMCHAR(2)             !Orig.Terminal Setup
    C
            COMMON  TT_CHAN,TERMCHAR,CODE           ! Sub. TT_SET und
    TT_RESET
    C
    C
    C
            INCLUDE '($IODEF)'
            INCLUDE '($SSDEF)'
    C
    C
            ISTAT = SYS$QIOW(,%VAL(TT_CHAN),%VAL(IO$_SENSEMODE),
            1       ,,,TERMCHAR,%VAL(8),,,,)
            IF (.NOT. ISTAT) THEN
              CODE = 3
              CALL FEHLER (TMP,SEND)
            END IF
    C
            SETUP=TT$M_NOECHO+TT$M_TTSYNC+TT$M_HALFDUP+
            1               TT$M_notypeahd+TT$M_NOBRDCST
    C
    C       TYPE *,'SETUP: ',SETUP
            NEW_TERMCHAR(1)=TERMCHAR(1)
            NEW_TERMCHAR(2)=TERMCHAR(2) .OR. SETUP
    C       TYPE *,'TERMCHAR2: ',TERMCHAR(2)
    C
    C
            ISTAT = SYS$QIOW(,%VAL(TT_CHAN),%VAL(IO$_SETMODE),
            1       ,,,NEW_TERMCHAR,%VAL(8),,,,)
    C       TYPE * ,'SETCHAR:  ',ISTAT
            IF (.NOT. ISTAT) THEN
              CODE = 4
              CALL FEHLER (TMP,SEND)
            END IF
    C
            RETURN
            END
    
    
    
    Output when I compile it with FORTRAN:
    
            SETUP=TT$M_NOECHO+TT$M_TTSYNC+TT$M_HALFDUP+
    ..............^
    %FORT-W-UNINIT, Variable TT$M_NOECHO is used before its value has been
    defined
    at line number 49 in file
    USER6:[PFISTERR.WORK.TEMP.SAMPIERI]TT_SET.FOR;1
    
            SETUP=TT$M_NOECHO+TT$M_TTSYNC+TT$M_HALFDUP+
    ..........................^
    %FORT-W-UNINIT, Variable TT$M_TTSYNC is used before its value has been
    defined
    at line number 49 in file
    USER6:[PFISTERR.WORK.TEMP.SAMPIERI]TT_SET.FOR;1
    
            SETUP=TT$M_NOECHO+TT$M_TTSYNC+TT$M_HALFDUP+
    ......................................^
    %FORT-W-UNINIT, Variable TT$M_HALFDUP is used before its value has been
    defined
    at line number 49 in file
    USER6:[PFISTERR.WORK.TEMP.SAMPIERI]TT_SET.FOR;1
    
            1               TT$M_notypeahd+TT$M_NOBRDCST
    ........................^
    %FORT-W-UNINIT, Variable TT$M_NOTYPEAHD is used before its value has
    been define
    d
    at line number 50 in file
    USER6:[PFISTERR.WORK.TEMP.SAMPIERI]TT_SET.FOR;1
    
            1               TT$M_notypeahd+TT$M_NOBRDCST
    .......................................^
    %FORT-W-UNINIT, Variable TT$M_NOBRDCST is used before its value has
    been defined
    at line number 50 in file
    USER6:[PFISTERR.WORK.TEMP.SAMPIERI]TT_SET.FOR;1
| T.R | Title | User | Personal Name
 | Date | Lines | 
|---|
| 1151.1 |  | TLE::EKLUND | Always smiling on the inside! | Mon Jan 27 1997 10:56 | 10 | 
|  |     	The unitialized variable warnings are only given when you
    optimize (when the compiler does the graphing which allows the
    detection of the problem).  It looks like the names are simply
    not defined in the include files you use.  I don't know whether
    this is a mistake in the system include files or not.  I get
    the same warnings here.
    
    Cheers!
    Dave Eklund
    
 | 
| 1151.2 |  | QUARK::LIONEL | Free advice is worth every cent | Mon Jan 27 1997 11:27 | 5 | 
|  | The identifiers in the warnings are defined in $TTDEF (being TT$ symbols), 
but you didn't INCLUDE $TTDEF, therefore they look like undefined variables.
Add a line to include $TTDEF and you should be fine.
					Steve
 |