Microsoft Fortran v3.13

This commit is contained in:
davidly 2024-07-22 14:02:22 -07:00
parent 7c3ef00237
commit 52e1245d2c
19 changed files with 2144 additions and 0 deletions

View File

@ -0,0 +1,46 @@
C Bubble Sort Demonstration Program
C Microsoft FORTRAN77
C 4 October 1982
C
C The main routine reads from the terminal an array
C of ten real numbers in F8.0 format and calls the
C subroutine BUBBLE to sort them.
C
REAL R(10)
INTEGER I
WRITE (*,001)
001 FORMAT(1X,'Bubble Sort Demonstration Program.')
100 DO 103 I=1,10
WRITE (*,101) I
101 FORMAT(1X,'Please input real number no. ',I2)
READ (*,102) R(I)
102 FORMAT(F8.0)
103 CONTINUE
CALL BUBBLE(R,10)
WRITE (*,002)
002 FORMAT(/1X,'The sorted ordering from lowest to highest is:')
WRITE (*,003) (R(I),I = 1,10)
003 FORMAT(2(1x,5F13.3/))
STOP
END
C
C Subroutine BUBBLE performs a bubble sort on a
C one-dimensional real array of arbitrary length. It sorts
C the array in asscending order.
SUBROUTINE BUBBLE(X,J)
INTEGER J,A1,A2
REAL X(J),TEMP
100 IF (J .LE. 1) GOTO 101
200 DO 201 A1 = 1,J-1
300 DO 301 A2 = A1 + 1,J
400 IF (X(A1) .LE. X(A2)) GOTO 401
TEMP = X(A1)
X(A1) = X(A2)
X(A2) = TEMP
401 CONTINUE
301 CONTINUE
201 CONTINUE
101 CONTINUE
RETURN
END


View File

@ -0,0 +1,36 @@
program e
integer*2 high, n, x
integer*2 a(200)
high = 200
x = 0
n = high - 1
150 if ( n .le. 0 ) goto 200
a( n + 1 ) = 1
n = n - 1
goto 150
200 a( 2 ) = 2
a( 1 ) = 0
220 if ( high .le. 9 ) goto 400
high = high - 1
n = high
240 if ( n .eq. 0 ) goto 300
a( n + 1 ) = MOD( x, n )
x = ( 10 * a( n ) ) + ( x / n )
n = n - 1
goto 240
300 if ( x .ge. 10 ) goto 320
write( *, 2000 ) x
goto 220
320 write( *, 2001 ) x
goto 220
400 write( *, 2010 )
2000 format( '+', I1 )
2001 format( '+', I2 )
2010 format( ' done' )
end

View File

@ -0,0 +1,337 @@
NAME ENTX
; Microsoft MS-DOS Runtime System Control Source.
; Version 3.11 (C) Copyright 1982 by Microsoft, Inc.
;8086 Standard Runtime System Control
;Memory Layout:
;
; Hi -> COMMAND (may be overlayed)
; HIMEM segment class HIMEM (always empty)
; <name> segment(s) class COMMON (not DGROUP)
; DGROUP, COMMQQ segment class COMMON
; DGROUP, CONST segment class CONST
; DGROUP, COMADS segment class COMADS
; DGROUP, DATA segment class DATA
; DGROUP, STACK segment class STACK
; DGROUP, MEMORY segment class MEMORY
; DGROUP, HEAP segment class MEMORY
; CODE segments
; Lo -> DOS code and data (fixed)
;
;The linker is told to load low and use DS allocation. Only 256 bytes
;of initial stack are allocated, and no heap at all. BEGXQQ moves all
;DGROUP to high memory, making a gap in which the stack grows downward
;and the heap grows upward. The heap can grow downward over code too.
EXTRN ENTGQQ:FAR ;main program entry point
EXTRN INIUQQ:FAR,ENDUQQ:FAR ;file system initialize/terminate
EXTRN ENDYQQ:FAR ;file system close all open files
EXTRN BEGOQQ:FAR,ENDOQQ:FAR ;user system initialize/terminate
;First dummy code segment tells linker to load code lowest
;
INIXQQ SEGMENT 'CODE'
INIXQQ ENDS
;Heap segment definition (lowest of the DGROUP segments)
;
HEAP SEGMENT PUBLIC 'MEMORY'
MEMLO EQU THIS BYTE ;lowest data byte address
HEAP ENDS
;Memory segment definition (special purpose zero length)
;
MEMORY SEGMENT PUBLIC 'MEMORY'
MEMORY ENDS
;Stack segment definition (fixed initial minimal length)
;
STACK SEGMENT STACK 'STACK'
DB 256 DUP (?)
SKTOP EQU THIS BYTE
STACK ENDS
;System resident public data
;
DATA SEGMENT PUBLIC 'DATA'
PUBLIC CSXEQQ ;pointer to sourcef context list
CSXEQQ DW 0
PUBLIC CLNEQQ ;last line number encountered
CLNEQQ DW 0
PUBLIC PNUXQQ ;pointer to unit initialization list
PNUXQQ DW 0
PUBLIC HDRFQQ ;Unit F open file list header
HDRFQQ DW 0
PUBLIC HDRVQQ ;Unit V open file list header
HDRVQQ DW 0
PUBLIC RESEQQ ;machine error context, stack ptr
RESEQQ DW 0
PUBLIC REFEQQ ;machine error context, frame ptr
REFEQQ DW 0
PUBLIC REPEQQ ;machine error context, program offset
REPEQQ DW 0
PUBLIC RECEQQ ;machine error context, program segment
RECEQQ DW 0
PUBLIC UPCX87 ;offset address of 8087 error context
UPCX87 DW 0
PUBLIC BEGHQQ ;first header word in heap
BEGHQQ DW 0
PUBLIC CURHQQ ;pointer to current heap item
CURHQQ DW 0
PUBLIC ENDHQQ ;just past end of the heap
ENDHQQ DW 0
PUBLIC STKBQQ ;stack start, to fix long GOTO
STKBQQ DW 0
PUBLIC STKHQQ ;stack limit, to check overflow
STKHQQ DW 0
PUBLIC BEGMQQ ;first group header in long heap
BEGMQQ DW 0
PUBLIC ENDMQQ ;segment past end of used memory
ENDMQQ DW 0
PUBLIC MAXMQQ ;segment past end of available memory
MAXMQQ DW 0
PUBLIC DGRMQQ ;segment of DGROUP
DGRMQQ DW 0
PUBLIC DOSEQQ ;DOS return code
DOSEQQ DW 0
PUBLIC CRCXQQ ;value of CX for DOS call
CRCXQQ DW 0
PUBLIC CRDXQQ ;value of DX for DOS call
CRDXQQ DW 0
PUBLIC CESXQQ ;DOS saved ES value (for command line)
DOSOFF DW 0
CESXQQ DW 0
DATA ENDS
;Common address segment definition
;
COMADS SEGMENT PUBLIC 'COMADS'
COMHI EQU THIS BYTE ;highest comads address
COMADS ENDS
;Segment used to drag in 8087 emulator if necesary
;
EINQQQ SEGMENT WORD COMMON 'DATA'
InitializeCodeAddress DD 1 DUP(?)
ExitCodeAddress DD 1 DUP(?)
EINQQQ ENDS
;Constant segment definition
;
CONST SEGMENT PUBLIC 'CONST'
CONST ENDS
;Blank common block segment
;
COMMQQ SEGMENT PUBLIC 'COMMON'
COMMQQ ENDS
;End of memory segment definition
;
HIMEM SEGMENT PUBLIC 'HIMEM'
HIMEM ENDS
;Code for this module
;
ENTXQQ SEGMENT 'CODE'
DGROUP GROUP DATA,STACK,CONST,EINQQQ,HEAP,MEMORY,COMADS,COMMQQ
ASSUME CS:ENTXQQ,DS:DGROUP,ES:DGROUP,SS:DGROUP
PUBLIC BEGXQQ,ENDXQQ,DOSXQQ ;main entry and exit points
; Start with error routine invoked if not enough memory
MSGERR DB 'Not Enough Memory$'
EXIERR DW 0
EXSERR DW 0
MEMERR LABEL NEAR
PUSH CS ;message segment
POP DS ;parameter to DOS
MOV DX,OFFSET ENTXQQ:MSGERR
MOV AH,9 ;command, type string
INT 33 ;go give error message
MOV EXSERR,ES ;terminate segment
JMP DWORD PTR EXIERR ;exit to DOS
;BEGXQQ: Initialization code
; - move DGROUP up as much as possible to get gap
; - set initial stackpointer, framepointer, STKBQQ
; - set BEGHQQ, CURHQQ, ENDHQQ, STKHQQ (heap init)
; - clear RESEQQ (machine error context)
; - clear CSXEQQ (sourcef error context)
; - clear PNUXQQ (unit init list header)
; - clear HDRFQQ and HDRVQQ (open file headers)
; - clear DOSEQQ (DOS error return code)
; - call INIX87 (real initialization if it is linked in)
; - call INIUQQ (file initialization)
; - call BEGOQQ (user initialization)
; - call ENTGQQ (main program entry)
;
BEGXQQ PROC FAR
MOV DX,OFFSET DGROUP:MEMLO ;DS offset to lowest byte
SHR DX,1 ;make into word offset address
MOV CX,32768 ;highest word address possible
SUB CX,DX ;CX is count of words in DGROUP segment
SHR DX,1 ;make word
SHR DX,1 ; count into
SHR DX,1 ; paragraph count
INC DX ;round; number of para's could use
MOV AX,ES:2 ;DOS end paragraph (first segment not free)
MOV BP,AX ;(save for later long heap initialization)
SUB AX,HIMEM ;this is number of para's available total
JB MEMERR ;if negative amount available, error
XOR BX,BX ;assume all para's in DGROUP can be used
SUB AX,DX ;if positive, more available than can use
JAE MEMA ;if negative, minus number of para's unused
SUB BX,AX ;BX is number of para's unused in DGROUP
MEMA: SUB DX,BX ;DX is number of para's to move DGROUP
;
;save incomming ES value, fixup addresses of named common
MOV AX,DGROUP ;get assumed DGROUP segment value
MOV DS,AX ;this is the old, source segment
MOV CESXQQ,ES ;save incomming ES value in DS
MOV SI,COMADS ;first common segment address
SUB SI,AX ;make into paragraph offset
SHL SI,1 ;make
SHL SI,1 ; into
SHL SI,1 ; byte
SHL SI,1 ; offset
COMA: CMP SI,OFFSET DGROUP:COMHI ;last+ common address offset
JAE CAMA ;jump out if all addresses are fixed
ADD 2[SI],DX ;fix segment part of address
ADD SI,4 ;to next common segment+offset address
JMP COMA ;repeat
;
;move all of DGROUP higher in memory, making room for stack and heap
CAMA: ADD DX,AX ;old segment plus para's used
MOV ES,DX ;makes new, target segment
MOV SI,65534 ;source offset
MOV DI,SI ;target offset
STD ;set direction flag
REP MOVSW ;move DS:SI-- to ES:DI-- until CX-=0
CLD ;leave direction clear
MOV DS,DX ;final DS value (may be negative)
;
;initialize stack segment and pointer
CLI ;no interrupts (no stack)
MOV SS,DX ;initialize stack segment
MOV SP,OFFSET DGROUP:SKTOP ;set stackpointer
STI ;interrupts ok (stack ok)
MOV STKBQQ,SP ;to re-init BP after long GOTO
SUB STKBQQ,6 ;contains address of main frame
;
;initialize short heap control addresses
SHL BX,1 ;make count of
SHL BX,1 ; unused paragraphs
SHL BX,1 ; into DS offset to
SHL BX,1 ; first data byte
MOV BEGHQQ,BX ;start of heap DS offset
MOV CURHQQ,BX ;current heap item DS offset
MOV WORD PTR[BX],1 ;current header; free
ADD BX,2 ;byte after end of heap
MOV ENDHQQ,BX ;DS offset after end of heap
ADD BX,384 ;comfortable boundary
MOV STKHQQ,BX ;stack overflow DS offset
;
;initialize long heap control addresses
MOV DGRMQQ,DX ;DGROUP segment
SUB DX,DGROUP ;number of paragraphs shifted
ADD DX,HIMEM ;plus old end of used memory segment
MOV ENDMQQ,DX ;segment past end of used memory
MOV MAXMQQ,BP ;segment past end of all memory (from above)
XOR BP,BP ;get a zero (also initial framepointer)
MOV BEGMQQ,BP ;initial long heap group header
;
;initialize various list headers
MOV RESEQQ,BP ;machine error context zero
MOV CSXEQQ,BP ;sourcef error context NIL
MOV PNUXQQ,BP ;unit init list header NIL
MOV HDRFQQ,BP ;Unit F open file header NIL
MOV HDRVQQ,BP ;Unit V open file header NIL
MOV DOSEQQ,BP ;DOS error return value
PUSH DS ; Make sure that DS and ES are the same.
POP ES ; Some of our initialization code assumes
; that they are.
;
;call real, file, and user initialization, call main program
;call real number initialization
CMP WORD PTR InitializeCodeAddress,0 ; Was exit code linked in?
JZ DoneInitialize
CALL DWORD PTR InitializeCodeAddress
DoneInitialize:
CALL INIUQQ ;initialize file system
CALL BEGOQQ ;initialize user system
CALL ENTGQQ ;call main program
;
;ENDXQQ: Termination code
; - call ENDOQQ (user termination)
; - call ENDYQQ (close open files)
; - call ENDUQQ (file termination)
; - call ENDX87 (real termination if it is linked in)
; - return to operating system
;
ENDXQQ LABEL FAR ;termination entry point
CALL ENDOQQ ;user system termination
CALL ENDYQQ ;close all open files
CALL ENDUQQ ;file system termination
;real system termination
CMP WORD PTR ExitCodeAddress,0 ; Was exit code linked in?
JZ DoneExit
CALL DWORD PTR ExitCodeAddress
DoneExit:
;
; MS-DOS function code equates.
;
MSDOSINT EQU 21H ; MS-DOS interrupt call.
EXITOP EQU 4CH ; Get exit call.
;
; Use kill process function under 2.0 and greater MS-DOS. CS is assumed
; to be pointing to the Program Segment Prefix in force at ENTXQQ entry.
;
MOV AH,EXITOP ; No-op code under 1.25 MS-DOS.
MOV AL,BYTE PTR DOSEQQ ; Forward DOSEQQ value to DOS.
INT MSDOSINT ; We should never return to OS from here.
;
; Drop through and use 1.25 return method.
;
MOV DOSOFF,0 ; Make sure jump offset zero.
JMP DWORD PTR DOSOFF ; Return to DOS.
BEGXQQ ENDP
;DOSXQQ: Call DOS Operating System
;
DOSXQQ PROC FAR
POP SI ;get return ads
POP DI ;get return ads
POP DX ;get address parameter
POP AX ;get function parameter
MOV AH,AL ;must be in high half
MOV CX,CRCXQQ ;need CX for some functions
PUSH DI ;save return ads
PUSH SI ;save return ads
PUSH BP ;have to save this one
INT 33 ;onward to DOS
;
; Carry will be set if dos error.
;
MOV CRCXQQ,CX ;return CX value
MOV CRDXQQ,DX ;return DX value
POP BP ;restore frame pointer
RET ;return (DOS ret in AX)
DOSXQQ ENDP
ENTXQQ ENDS
END BEGXQQ

Binary file not shown.

Binary file not shown.

Binary file not shown.

View File

@ -0,0 +1,533 @@
$V2_ERROR......rtim6 $V2_EXIT.......rtim6
$V2_EXIT2......rtim6 $V2_OK.........rtim6
A2DRQQ.........tsdr A2SRQQ.........tsdr
ABS4...........intrns ABSTQQ.........intr7
ACDRQQ.........tsdr ACSRQQ.........tsdr
ADPTQQ.........intr7 AGOEQQ.........fore
AIDRQQ.........misr7 AINT4..........intrns
AISRQQ.........misr7 ALLHQQ.........heah
AMOD4..........intrns ANDRQQ.........stdr
ANINT4.........intrns ANSRQQ.........stsr
ASDRQQ.........tsdr ASMGQQ.........misg6
ASNEQQ.........erree ASNGQQ.........misg6
ASSRQQ.........tsdr ATDRQQ.........tsdr
ATSRQQ.........tsdr AUXVQQ.........auxv
AVAGQQ.........misg6 BADTQQ.........intr7
BAKVQQ.........auxv BASTQQ.........intr7
BCDTQQ.........intr7 BCSTQQ.........intr7
BDDTQQ.........intr7 BDSTQQ.........intr7
BEGHQQ.........entx6l BEGMQQ.........entx6l
BEGOQQ.........miso BEGXQQ.........entx6l
BIDTQQ.........intr7 BISTQQ.........intr7
BLDTQQ.........intr7 BLSTQQ.........intr7
BMDTQQ.........intr7 BMSTQQ.........intr7
BODTQQ.........intr7 BOSTQQ.........intr7
BRDTQQ.........intr7 BRSTQQ.........intr7
BRTEQQ.........misg6 BSDTQQ.........intr7
BSSTQQ.........intr7 BTDTQQ.........intr7
BTSTQQ.........intr7 BUFVQQ.........manv
BZFVQQ.........manv BZLVQQ.........manv
CDDDQQ.........cmpd7 CDDRQQ.........cmpr7
CDEDQQ.........cmpd7 CDERQQ.........cmpr7
CESGQQ.........misg6 CESXQQ.........entx6l
CHDRQQ.........tsdr CHPRQQ.........comr7
CHSRQQ.........tsdr CHSTQQ.........intr7
CINSQQ.........misg6 CLDUQQ.........filuxm
CLNEQQ.........entx6l CLOSE..........rtim6
CLSGQQ.........misg6 CLSUQQ.........filuxm
CLSVQQ.........manv CMPWQQ.........forw6
CNDRQQ.........tsdr CNSRQQ.........tsdr
CNVEQQ.........erree COLVQQ.........manv
CONUXM.........conuxm CRCXQQ.........entx6l
CRDXQQ.........entx6l CREAT..........rtim6
CRNVQQ.........manv CSDDQQ.........cmpd7
CSDRQQ.........cmpr7 CSEDQQ.........cmpd7
CSERQQ.........cmpr7 CSXEQQ.........entx6l
CTCR87.........oemr7 CURHQQ.........entx6l
CUTHQQ.........mishm DABS8..........intrns
DATE...........tidgl DDEC87.........dedr7
DDECQQ.........dedr7 DDIM8..........intrns
DEBEQQ.........debe DENC87.........dedr7
DENCQQ.........lonc DGRMQQ.........entx6l
DIFUQQ.........foruxm DIG2...........tidgl
DIM4...........intrns DINT8..........intrns
DMOD8..........intrns DNINT8.........intrns
DNRE87.........misg6 DNREQQ.........erree
DOSEQQ.........entx6l DOSXQQ.........entx6l
DPCRQQ.........dedr7 DPROD8.........intrns
DPSVQQ.........dpsv DRPTQQ.........intr7
DSIGN8.........intrns DUPTQQ.........intr7
DVPTQQ.........intr7 DZIEQQ.........erree
DZNEQQ.........erree DZRE87.........misg6
DZREQQ.........erree DZWEQQ.........erree
EEDCQQ.........dedr7 EFEVQQ.........ermv
EFLVQQ.........manv EIGRQQ.........dedr7
EMSEQQ.........erre ENDHQQ.........entx6l
ENDMQQ.........entx6l ENDOQQ.........miso
ENDUQQ.........conuxm ENDX87.........comr7
ENDXQQ.........entx6l ENDYQQ.........misy
ENFVQQ.........auxv ENNCQQ.........lonc
ENRVQQ.........manv ENTEQQ.........debe
EOFUQQ.........foruxm EOFVQQ.........auxv
EREVQQ.........ermv ERFVQQ.........manv
ERHVQQ.........erhv ERLVQQ.........manv
ERREQQ.........erre ERRNO..........rtim6
ERRVQQ.........manv ERTEQQ.........misg6
ERUVQQ.........manv EXCX87.........oemr7
EXDRQQ.........tsdr EXIT...........rtim6
EXPEQQ.........erree EXSRQQ.........tsdr
EXTEQQ.........debe EXTVQQ.........ermv
FDUVQQ.........manv FIDRQQ.........intr7
FIERQQ.........intr7 FILKQQ.........misy
FILLC..........misg6 FILLSC.........misg6
FILUQQ.........filuxm FILVQQ.........manv
FIWRQQ.........intr7 FLBUQQ.........filuxm
FLBVQQ.........manv FLGX87.........intr7
FLRVQQ.........manv FMDVQQ.........manv
FMRC...........fmrc FMRCQQ.........fmrc
FMTVQQ.........fmtv FNSUQQ.........filuxm
FONG...........fong FOREQQ.........fore
FORUXM.........foruxm FPSUQQ.........foruxm
FRXDQQ.........mp2r7 GETHQQ.........heah
GETUQQ.........filuxm GETVQQ.........manv
GFNUQQ.........filuxm GFTVQQ.........fmtv
GHIEQQ.........erree GHSEQQ.........erree
GHVEQQ.........erree GLDVQQ.........liov
GLFVQQ.........liov GLIVQQ.........liov
GOFVQQ.........fmtv GOIVQQ.........fmtv
GOUVQQ.........manv GROHQQ.........mishm
GTMVQQ.........manv GTUVQQ.........manv
GTYUQQ.........conuxm HDRFQQ.........entx6l
HDRVQQ.........entx6l HEAHQQ.........heah
I24IQQ.........rtim6 I2MSQQ.........msfr7
I3EX87.........comr7 IABS2..........intrns
IABS4..........intrns IACVQQ.........liov
IADVQQ.........rliv IAIVQQ.........iliv
IALVQQ.........lliv IAMVQQ.........lliv
IANVQQ.........iliv IARVQQ.........rliv
ICLRER.........erhv IDIM2..........intrns
IDIM4..........intrns IDNIN2.........intrns
IDNIN4.........intrns IGETER.........erhv
IINVQQ.........iinv IIOVQQ.........manv
ILIVQQ.........iliv ILOVQQ.........ilov
INARQQ.........dedr7 INIUQQ.........conuxm
INIVQQ.........manv INIX87.........intr7
INPUQQ.........filuxm INRE87.........misg6
INREQQ.........erree INTR87.........comr7
IOCTL..........rtim6 IOCUQQ.........foruxm
IOCVQQ.........manv IOPVQQ.........iopv
ISIGN2.........intrns ISIGN4.........intrns
ISIWQQ.........fong ITCVQQ.........liov
ITDVQQ.........rliv ITIVQQ.........iliv
ITLVQQ.........lliv ITMVQQ.........lliv
ITNVQQ.........iliv ITRVQQ.........rliv
KBBVQQ.........manv KBPVQQ.........manv
KBRVQQ.........manv LADDOK.........long6
LCWRQQ.........lscw7 LDCVQQ.........liov
LDDRQQ.........tsdr LDLG2..........dedr7
LDNGQQ.........long6 LDSRQQ.........tsdr
LINVQQ.........linv LIOVQQ.........liov
LLIVQQ.........lliv LLOVQQ.........llov
LMNGQQ.........long6 LMULOK.........long6
LNDRQQ.........tsdr LNEEQQ.........erree
LNSRQQ.........tsdr LNTEQQ.........debe
LOCKED.........misg6 LONCQQ.........lonc
LOPVQQ.........lopv LRNGQQ.........long6
LSEEK..........rtim6 LSOVQQ.........manv
LSWRQQ.........lscw7 M2ISQQ.........msfr7
MAXMQQ.........entx6l MDDRQQ.........stdr
MDSRQQ.........stsr MIN8...........tidgl
MINCQQ.........lonc MISHQQ.........mishm
MISOQQ.........miso MISYQQ.........misy
MNDRQQ.........stdr MNNGQQ.........forw6
MNSRQQ.........stsr MOD2...........intrns
MOD4...........intrns MOVEL..........misg6
MOVER..........misg6 MOVESL.........misg6
MOVESR.........misg6 MP2DQQ.........mp2r7
MP2SQQ.........mp2r7 MPBRQQ.........intr7
MPDRQQ.........intr7 MPHRQQ.........intr7
MPIRQQ.........intr7 MPPRQQ.........intr7
MPSRQQ.........intr7 MTBUQQ.........misg6
MUPTQQ.........intr7 MXDRQQ.........stdr
MXNGQQ.........forw6 MXSRQQ.........stsr
NANRQQ.........dedr7 NAOGQQ.........long6
NDZGQQ.........long6 NEFUQQ.........foruxm
NFMVQQ.........manv NINT2..........intrns
NINT4..........intrns NOREQQ.........erree
NSNWQQ.........fong NXRVQQ.........manv
NXTUQQ.........filuxm OACVQQ.........liov
OADVQQ.........rlov OAIVQQ.........ilov
OALVQQ.........llov OAMVQQ.........llov
OANVQQ.........ilov OARVQQ.........rlov
OEMS87.........oemr7 OEMX87.........oemr7
OIFVQQ.........liov ONERQQ.........dedr7
OPEN...........rtim6 OPNUQQ.........filuxm
OPNVQQ.........manv OTCVQQ.........liov
OTDVQQ.........rlov OTIVQQ.........ilov
OTLVQQ.........llov OTMVQQ.........llov
OTNVQQ.........ilov OTRVQQ.........rlov
OUTUQQ.........filuxm OVIEQQ.........erree
OVNEQQ.........erree OVRE87.........misg6
OVREQQ.........erree OVWEQQ.........erree
PBFUQQ.........conuxm PBLVQQ.........manv
PCCUQQ.........filuxm PCTVQQ.........manv
PERUQQ.........filuxm PFNUQQ.........filuxm
PIDRQQ.........tsdr PISRQQ.........tsdr
PLDVQQ.........liov PLYUQQ.........conuxm
PNUXQQ.........entx6l POSVQQ.........dpsv
PPMUQQ.........filuxm PRDRQQ.........tsdr
PREE87.........misg6 PREEQQ.........erree
PRSRQQ.........tsdr PSTVQQ.........fmtv
PTUVQQ.........manv PTYUQQ.........conuxm
PUTUQQ.........filuxm PUTVQQ.........manv
PWRRQQ.........dedr7 PWTRQQ.........dedr7
RACVQQ.........fmtv RADTQQ.........intr7
RADVQQ.........rinv RAIVQQ.........iinv
RALVQQ.........linv RAMVQQ.........linv
RANVQQ.........iinv RARVQQ.........rinv
RASTQQ.........intr7 RCDTQQ.........intr7
RCSTQQ.........intr7 RDDTQQ.........intr7
RDGVQQ.........manv RDSTQQ.........intr7
READ...........rtim6 RECEQQ.........entx6l
REFEQQ.........entx6l REPEQQ.........entx6l
RESEQQ.........entx6l RESX87.........comr7
REWVQQ.........auxv RFDR...........stdr
RFSR...........stsr RIDTQQ.........intr7
RINVQQ.........rinv RISTQQ.........intr7
RLDTQQ.........intr7 RLIVQQ.........rliv
RLOVQQ.........rlov RLSTQQ.........intr7
RLTTQQ.........intr7 RMDTQQ.........intr7
RMSTQQ.........intr7 RNBX87.........intr7
RNDCQQ.........rndc7 RNDRQQ.........rndc7
RNPEQQ.........erree RODTQQ.........intr7
ROPVQQ.........ropv ROSTQQ.........intr7
RRDTQQ.........intr7 RRSTQQ.........intr7
RSDTQQ.........intr7 RSSTQQ.........intr7
RSTTQQ.........intr7 RTCVQQ.........fmtv
RTDTQQ.........intr7 RTDVQQ.........rinv
RTIVQQ.........iinv RTLVQQ.........linv
RTMVQQ.........linv RTNVQQ.........iinv
RTRVQQ.........rinv RTSTQQ.........intr7
S24IQQ.........rtim6 SADDOK.........misg6
SADTQQ.........intr7 SAOGQQ.........misg6
SASTQQ.........intr7 SBPTQQ.........intr7
SCAC87.........dedr7 SCDTQQ.........intr7
SCSTQQ.........intr7 SCWRQQ.........lscw7
SDDTQQ.........intr7 SDSTQQ.........intr7
SDZGQQ.........misg6 SEKUQQ.........filuxm
SEKVQQ.........auxv SHDRQQ.........tsdr
SHRUQQ.........rtim6 SHSRQQ.........tsdr
SIDTQQ.........intr7 SIGN4..........intrns
SINEQQ.........erree SISTQQ.........intr7
SLDTQQ.........intr7 SLSTQQ.........intr7
SLTTQQ.........intr7 SMDTQQ.........intr7
SMSTQQ.........intr7 SMULOK.........misg6
SNDRQQ.........tsdr SNSRQQ.........tsdr
SODTQQ.........intr7 SOSTQQ.........intr7
SOVEQQ.........erree SOVGQQ.........misg6
SRDRQQ.........tsdr SRDTQQ.........intr7
SRPTQQ.........intr7 SRSRQQ.........tsdr
SRSTQQ.........intr7 SRTEQQ.........erree
SSDTQQ.........intr7 SSSTQQ.........intr7
SSTTQQ.........intr7 SSWRQQ.........lscw7
STBIQQ.........rtim6 STDTQQ.........intr7
STKBQQ.........entx6l STKHQQ.........entx6l
STPRQQ.........dedr7 STPVQQ.........auxv
STSTQQ.........intr7 TANEQQ.........erree
TENRQQ.........dedr7 TFCUQQ.........conuxm
TFDUQQ.........foruxm THDRQQ.........tsdr
THSRQQ.........tsdr TICS...........tidgl
TIDGQQ.........tidgl TIME...........tidgl
TNDRQQ.........tsdr TNSRQQ.........tsdr
TOORQQ.........dedr7 TRAEQQ.........debe
TRMVQQ.........manv TRTRQQ.........intr7
TSIR87.........oemr7 TSRR87.........oemr7
TUGRQQ.........intr7 U24IQQ.........rtim6
UADDOK.........misg6 UAOGQQ.........misg6
UDZGQQ.........misg6 UERE87.........misg6
UEREQQ.........erree UM46OK.........utlx
UMULOK.........misg6 UNLINK.........rtim6
UNLOCK.........misg6 UNRE87.........misg6
UNREQQ.........erree UPCX87.........entx6l
UTLXQQ.........utlx VASGQQ.........misg6
WACVQQ.........fmtv WADVQQ.........ropv
WAIVQQ.........iopv WALVQQ.........lopv
WAMVQQ.........lopv WANVQQ.........iopv
WARVQQ.........ropv WEFUQQ.........filuxm
WRFVQQ.........fmtv WRITE..........rtim6
WRUVQQ.........manv WTCVQQ.........fmtv
WTDVQQ.........ropv WTIVQQ.........iopv
WTLVQQ.........lopv WTMVQQ.........lopv
WTNVQQ.........iopv WTRVQQ.........ropv
XTPRQQ.........dedr7 YTPRQQ.........dedr7
Z4TRQQ.........dedr7 Z5TRQQ.........dedr7
ZPIEQQ.........erree ZPNEQQ.........erree
ZPREQQ.........erree
mishm Offset: 200H Code and data size: A7
CUTHQQ GROHQQ MISHQQ
conuxm Offset: 600H Code and data size: 165
CONUXM ENDUQQ GTYUQQ INIUQQ
PBFUQQ PLYUQQ PTYUQQ TFCUQQ
filuxm Offset: A00H Code and data size: E1A
CLDUQQ CLSUQQ FILUQQ FLBUQQ
FNSUQQ GETUQQ GFNUQQ INPUQQ
NXTUQQ OPNUQQ OUTUQQ PCCUQQ
PERUQQ PFNUQQ PPMUQQ PUTUQQ
SEKUQQ WEFUQQ
entx6l Offset: 1E00H Code and data size: 27F
BEGHQQ BEGMQQ BEGXQQ CESXQQ
CLNEQQ CRCXQQ CRDXQQ CSXEQQ
CURHQQ DGRMQQ DOSEQQ DOSXQQ
ENDHQQ ENDMQQ ENDXQQ HDRFQQ
HDRVQQ MAXMQQ PNUXQQ RECEQQ
REFEQQ REPEQQ RESEQQ STKBQQ
STKHQQ UPCX87
utlx Offset: 2400H Code and data size: 131
UM46OK UTLXQQ
cmpd7 Offset: 2800H Code and data size: EB
CDDDQQ CDEDQQ CSDDQQ CSEDQQ
cmpr7 Offset: 2A00H Code and data size: BD
CDDRQQ CDERQQ CSDRQQ CSERQQ
debe Offset: 2C00H Code and data size: C6
DEBEQQ ENTEQQ EXTEQQ LNTEQQ
TRAEQQ
dedr7 Offset: 3000H Code and data size: 86C
DDEC87 DDECQQ DENC87 DPCRQQ
EEDCQQ EIGRQQ INARQQ LDLG2
NANRQQ ONERQQ PWRRQQ PWTRQQ
SCAC87 STPRQQ TENRQQ TOORQQ
XTPRQQ YTPRQQ Z4TRQQ Z5TRQQ
intr7 Offset: 4000H Code and data size: 18D
ABSTQQ ADPTQQ BADTQQ BASTQQ
BCDTQQ BCSTQQ BDDTQQ BDSTQQ
BIDTQQ BISTQQ BLDTQQ BLSTQQ
BMDTQQ BMSTQQ BODTQQ BOSTQQ
BRDTQQ BRSTQQ BSDTQQ BSSTQQ
BTDTQQ BTSTQQ CHSTQQ DRPTQQ
DUPTQQ DVPTQQ FIDRQQ FIERQQ
FIWRQQ FLGX87 INIX87 MPBRQQ
MPDRQQ MPHRQQ MPIRQQ MPPRQQ
MPSRQQ MUPTQQ RADTQQ RASTQQ
RCDTQQ RCSTQQ RDDTQQ RDSTQQ
RIDTQQ RISTQQ RLDTQQ RLSTQQ
RLTTQQ RMDTQQ RMSTQQ RNBX87
RODTQQ ROSTQQ RRDTQQ RRSTQQ
RSDTQQ RSSTQQ RSTTQQ RTDTQQ
RTSTQQ SADTQQ SASTQQ SBPTQQ
SCDTQQ SCSTQQ SDDTQQ SDSTQQ
SIDTQQ SISTQQ SLDTQQ SLSTQQ
SLTTQQ SMDTQQ SMSTQQ SODTQQ
SOSTQQ SRDTQQ SRPTQQ SRSTQQ
SSDTQQ SSSTQQ SSTTQQ STDTQQ
STSTQQ TRTRQQ TUGRQQ
erre Offset: 4800H Code and data size: 296
EMSEQQ ERREQQ
erree Offset: 4E00H Code and data size: 359
ASNEQQ CNVEQQ DNREQQ DZIEQQ
DZNEQQ DZREQQ DZWEQQ EXPEQQ
GHIEQQ GHSEQQ GHVEQQ INREQQ
LNEEQQ NOREQQ OVIEQQ OVNEQQ
OVREQQ OVWEQQ PREEQQ RNPEQQ
SINEQQ SOVEQQ SRTEQQ TANEQQ
UEREQQ UNREQQ ZPIEQQ ZPNEQQ
ZPREQQ
fmrc Offset: 5600H Code and data size: 2F6
FMRC FMRCQQ
fong Offset: 5C00H Code and data size: 2D4
FONG ISIWQQ NSNWQQ
heah Offset: 6200H Code and data size: 1A5
ALLHQQ GETHQQ HEAHQQ
lonc Offset: 6600H Code and data size: 3BF
DENCQQ ENNCQQ LONCQQ MINCQQ
long6 Offset: 6C00H Code and data size: 1C9
LADDOK LDNGQQ LMNGQQ LMULOK
LRNGQQ NAOGQQ NDZGQQ
lscw7 Offset: 7000H Code and data size: 34
LCWRQQ LSWRQQ SCWRQQ SSWRQQ
misg6 Offset: 7200H Code and data size: 35C
ASMGQQ ASNGQQ AVAGQQ BRTEQQ
CESGQQ CINSQQ CLSGQQ DNRE87
DZRE87 ERTEQQ FILLC FILLSC
INRE87 LOCKED MOVEL MOVER
MOVESL MOVESR MTBUQQ OVRE87
PREE87 SADDOK SAOGQQ SDZGQQ
SMULOK SOVGQQ UADDOK UAOGQQ
UDZGQQ UERE87 UMULOK UNLOCK
UNRE87 VASGQQ
miso Offset: 7A00H Code and data size: 38
BEGOQQ ENDOQQ MISOQQ
misr7 Offset: 7C00H Code and data size: 44
AIDRQQ AISRQQ
misy Offset: 7E00H Code and data size: CA
ENDYQQ FILKQQ MISYQQ
mp2r7 Offset: 8200H Code and data size: B0
FRXDQQ MP2DQQ MP2SQQ
msfr7 Offset: 8400H Code and data size: 50
I2MSQQ M2ISQQ
oemr7 Offset: 8600H Code and data size: 127
CTCR87 EXCX87 OEMS87 OEMX87
TSIR87 TSRR87
rndc7 Offset: 8A00H Code and data size: 65
RNDCQQ RNDRQQ
rtim6 Offset: 8C00H Code and data size: D6
$V2_ERROR $V2_EXIT $V2_EXIT2 $V2_OK
CLOSE CREAT ERRNO EXIT
I24IQQ IOCTL LSEEK OPEN
READ S24IQQ SHRUQQ STBIQQ
U24IQQ UNLINK WRITE
stdr Offset: 9000H Code and data size: 1BD
ANDRQQ MDDRQQ MNDRQQ MXDRQQ
RFDR
stsr Offset: 9600H Code and data size: 1BC
ANSRQQ MDSRQQ MNSRQQ MXSRQQ
RFSR
tsdr Offset: 9C00H Code and data size: 7AE
A2DRQQ A2SRQQ ACDRQQ ACSRQQ
ASDRQQ ASSRQQ ATDRQQ ATSRQQ
CHDRQQ CHSRQQ CNDRQQ CNSRQQ
EXDRQQ EXSRQQ LDDRQQ LDSRQQ
LNDRQQ LNSRQQ PIDRQQ PISRQQ
PRDRQQ PRSRQQ SHDRQQ SHSRQQ
SNDRQQ SNSRQQ SRDRQQ SRSRQQ
THDRQQ THSRQQ TNDRQQ TNSRQQ
tidgl Offset: B000H Code and data size: 1A1
DATE DIG2 MIN8 TICS
TIDGQQ TIME
foruxm Offset: B400H Code and data size: 38E
DIFUQQ EOFUQQ FORUXM FPSUQQ
IOCUQQ NEFUQQ TFDUQQ
auxv Offset: BA00H Code and data size: 553
AUXVQQ BAKVQQ ENFVQQ EOFVQQ
REWVQQ SEKVQQ STPVQQ
dpsv Offset: C400H Code and data size: C8
DPSVQQ POSVQQ
erhv Offset: C800H Code and data size: 13E
ERHVQQ ICLRER IGETER
ermv Offset: CC00H Code and data size: 54
EFEVQQ EREVQQ EXTVQQ
fmtv Offset: CE00H Code and data size: A58
FMTVQQ GFTVQQ GOFVQQ GOIVQQ
PSTVQQ RACVQQ RTCVQQ WACVQQ
WRFVQQ WTCVQQ
fore Offset: E000H Code and data size: 9B
AGOEQQ FOREQQ
forw6 Offset: E200H Code and data size: DF
CMPWQQ MNNGQQ MXNGQQ
iinv Offset: E400H Code and data size: 216
IINVQQ RAIVQQ RANVQQ RTIVQQ
RTNVQQ
iliv Offset: EA00H Code and data size: 17D
IAIVQQ IANVQQ ILIVQQ ITIVQQ
ITNVQQ
ilov Offset: EE00H Code and data size: 18C
ILOVQQ OAIVQQ OANVQQ OTIVQQ
OTNVQQ
intrns Offset: F200H Code and data size: 706
ABS4 AINT4 AMOD4 ANINT4
DABS8 DDIM8 DIM4 DINT8
DMOD8 DNINT8 DPROD8 DSIGN8
IABS2 IABS4 IDIM2 IDIM4
IDNIN2 IDNIN4 ISIGN2 ISIGN4
MOD2 MOD4 NINT2 NINT4
SIGN4
iopv Offset: 10000H Code and data size: 1BD
IOPVQQ WAIVQQ WANVQQ WTIVQQ
WTNVQQ
linv Offset: 10400H Code and data size: 1D3
LINVQQ RALVQQ RAMVQQ RTLVQQ
RTMVQQ
liov Offset: 10800H Code and data size: 597
GLDVQQ GLFVQQ GLIVQQ IACVQQ
ITCVQQ LDCVQQ LIOVQQ OACVQQ
OIFVQQ OTCVQQ PLDVQQ
lliv Offset: 11200H Code and data size: 181
IALVQQ IAMVQQ ITLVQQ ITMVQQ
LLIVQQ
llov Offset: 11600H Code and data size: 12B
LLOVQQ OALVQQ OAMVQQ OTLVQQ
OTMVQQ
lopv Offset: 11A00H Code and data size: 14B
LOPVQQ WALVQQ WAMVQQ WTLVQQ
WTMVQQ
manv Offset: 11E00H Code and data size: 12B4
BUFVQQ BZFVQQ BZLVQQ CLSVQQ
COLVQQ CRNVQQ EFLVQQ ENRVQQ
ERFVQQ ERLVQQ ERRVQQ ERUVQQ
FDUVQQ FILVQQ FLBVQQ FLRVQQ
FMDVQQ GETVQQ GOUVQQ GTMVQQ
GTUVQQ IIOVQQ INIVQQ IOCVQQ
KBBVQQ KBPVQQ KBRVQQ LSOVQQ
NFMVQQ NXRVQQ OPNVQQ PBLVQQ
PCTVQQ PTUVQQ PUTVQQ RDGVQQ
TRMVQQ WRUVQQ
rinv Offset: 13A00H Code and data size: 32F
RADVQQ RARVQQ RINVQQ RTDVQQ
RTRVQQ
rliv Offset: 14000H Code and data size: 266
IADVQQ IARVQQ ITDVQQ ITRVQQ
RLIVQQ
rlov Offset: 14600H Code and data size: 25F
OADVQQ OARVQQ OTDVQQ OTRVQQ
RLOVQQ
ropv Offset: 14C00H Code and data size: 32B
ROPVQQ WADVQQ WARVQQ WTDVQQ
WTRVQQ
comr7 Offset: 15200H Code and data size: 1D7
CHPRQQ ENDX87 I3EX87 INTR87
RESX87


View File

@ -0,0 +1,561 @@
$V2_ERROR......rtim6 $V2_EXIT.......rtim6
$V2_EXIT2......rtim6 $V2_OK.........rtim6
A2DRQQ.........tsdr A2SRQQ.........tsdr
ABS4...........intrns ABSTQQ.........emur7
ACDRQQ.........tsdr ACSRQQ.........tsdr
ADDRQQ.........emur7 ADPTQQ.........emur7
AGOEQQ.........fore AIDRQQ.........misr7
AINT4..........intrns AISRQQ.........misr7
ALLHQQ.........heah AMOD4..........intrns
ANDRQQ.........stdr ANINT4.........intrns
ANSRQQ.........stsr ASDRQQ.........tsdr
ASMGQQ.........misg6 ASNEQQ.........erree
ASNGQQ.........misg6 ASSRQQ.........tsdr
ATDRQQ.........tsdr ATSRQQ.........tsdr
AUXVQQ.........auxv AVAGQQ.........misg6
BADTQQ.........emur7 BAKVQQ.........auxv
BASTQQ.........emur7 BASX87.........emur7
BCDTQQ.........emur7 BCSTQQ.........emur7
BDDTQQ.........emur7 BDSTQQ.........emur7
BEGHQQ.........entx6l BEGMQQ.........entx6l
BEGOQQ.........miso BEGXQQ.........entx6l
BIDTQQ.........emur7 BISTQQ.........emur7
BLDTQQ.........emur7 BLSTQQ.........emur7
BMDTQQ.........emur7 BMSTQQ.........emur7
BODTQQ.........emur7 BOSTQQ.........emur7
BRDTQQ.........emur7 BRSTQQ.........emur7
BRTEQQ.........misg6 BSDTQQ.........emur7
BSSTQQ.........emur7 BTDTQQ.........emur7
BTSTQQ.........emur7 BUFVQQ.........manv
BZFVQQ.........manv BZLVQQ.........manv
CDDDQQ.........cmpd7 CDDRQQ.........cmpr7
CDEDQQ.........cmpd7 CDERQQ.........cmpr7
CESGQQ.........misg6 CESXQQ.........entx6l
CFERQQ.........emur7 CHDRQQ.........tsdr
CHIX87.........emur7 CHPRQQ.........comr7
CHSRQQ.........tsdr CHSTQQ.........emur7
CINSQQ.........misg6 CLDUQQ.........filuxm
CLNEQQ.........entx6l CLOSE..........rtim6
CLSGQQ.........misg6 CLSUQQ.........filuxm
CLSVQQ.........manv CMPWQQ.........forw6
CNDRQQ.........tsdr CNSRQQ.........tsdr
CNVEQQ.........erree COLVQQ.........manv
CONUXM.........conuxm CRCXQQ.........entx6l
CRDXQQ.........entx6l CREAT..........rtim6
CRNVQQ.........manv CSDDQQ.........cmpd7
CSDRQQ.........cmpr7 CSEDQQ.........cmpd7
CSERQQ.........cmpr7 CSXEQQ.........entx6l
CTCR87.........oemr7 CURHQQ.........entx6l
CURX87.........emur7 CUTHQQ.........mishm
CWDX87.........emur7 DABS8..........intrns
DATE...........tidgl DDEC87.........dedr7
DDECQQ.........dedr7 DDIM8..........intrns
DEBEQQ.........debe DENC87.........dedr7
DENCQQ.........lonc DGRMQQ.........entx6l
DIDRQQ.........emur7 DIFUQQ.........foruxm
DIG2...........tidgl DIM4...........intrns
DINT8..........intrns DMOD8..........intrns
DNINT8.........intrns DNRE87.........misg6
DNREQQ.........erree DOSEQQ.........entx6l
DOSXQQ.........entx6l DPCRQQ.........dedr7
DPROD8.........intrns DPSVQQ.........dpsv
DRDRQQ.........emur7 DRPTQQ.........emur7
DSIGN8.........intrns DSTRQQ.........emur7
DUPTQQ.........emur7 DVPTQQ.........emur7
DZIEQQ.........erree DZNEQQ.........erree
DZRE87.........misg6 DZREQQ.........erree
DZWEQQ.........erree EEDCQQ.........dedr7
EFEVQQ.........ermv EFLVQQ.........manv
EIGRQQ.........dedr7 EMSEQQ.........erre
ENDHQQ.........entx6l ENDMQQ.........entx6l
ENDOQQ.........miso ENDUQQ.........conuxm
ENDX87.........comr7 ENDXQQ.........entx6l
ENDYQQ.........misy ENFVQQ.........auxv
ENNCQQ.........lonc ENRVQQ.........manv
ENTEQQ.........debe EOFUQQ.........foruxm
EOFVQQ.........auxv EREVQQ.........ermv
ERFVQQ.........manv ERHVQQ.........erhv
ERLVQQ.........manv ERREQQ.........erre
ERRNO..........rtim6 ERRVQQ.........manv
ERTEQQ.........misg6 ERUVQQ.........manv
EXCX87.........oemr7 EXDRQQ.........tsdr
EXIT...........rtim6 EXPEQQ.........erree
EXSRQQ.........tsdr EXTEQQ.........debe
EXTVQQ.........ermv FDUVQQ.........manv
FIDRQQ.........emur7 FIERQQ.........emur7
FILKQQ.........misy FILLC..........misg6
FILLSC.........misg6 FILUQQ.........filuxm
FILVQQ.........manv FIWRQQ.........emur7
FLBUQQ.........filuxm FLBVQQ.........manv
FLGX87.........emur7 FLRVQQ.........manv
FMDVQQ.........manv FMRC...........fmrc
FMRCQQ.........fmrc FMTVQQ.........fmtv
FNSUQQ.........filuxm FONG...........fong
FOREQQ.........fore FORUXM.........foruxm
FPSUQQ.........foruxm FRXDQQ.........mp2r7
GETHQQ.........heah GETUQQ.........filuxm
GETVQQ.........manv GFNUQQ.........filuxm
GFTVQQ.........fmtv GHIEQQ.........erree
GHSEQQ.........erree GHVEQQ.........erree
GLDVQQ.........liov GLFVQQ.........liov
GLIVQQ.........liov GOFVQQ.........fmtv
GOIVQQ.........fmtv GOUVQQ.........manv
GROHQQ.........mishm GTMVQQ.........manv
GTUVQQ.........manv GTYUQQ.........conuxm
HDRFQQ.........entx6l HDRVQQ.........entx6l
HEAHQQ.........heah I24IQQ.........rtim6
I2MSQQ.........msfr7 I3EX87.........comr7
IABS2..........intrns IABS4..........intrns
IACVQQ.........liov IADVQQ.........rliv
IAIVQQ.........iliv IALVQQ.........lliv
IAMVQQ.........lliv IANVQQ.........iliv
IARVQQ.........rliv ICLRER.........erhv
IDIM2..........intrns IDIM4..........intrns
IDNIN2.........intrns IDNIN4.........intrns
IGETER.........erhv IINVQQ.........iinv
IIOVQQ.........manv ILIVQQ.........iliv
ILOVQQ.........ilov INARQQ.........dedr7
INDX87.........emur7 INIUQQ.........conuxm
INIVQQ.........manv INPUQQ.........filuxm
INRE87.........misg6 INREQQ.........erree
INTR87.........comr7 IOCTL..........rtim6
IOCUQQ.........foruxm IOCVQQ.........manv
IOPVQQ.........iopv ISIGN2.........intrns
ISIGN4.........intrns ISIWQQ.........fong
ITCVQQ.........liov ITDVQQ.........rliv
ITIVQQ.........iliv ITLVQQ.........lliv
ITMVQQ.........lliv ITNVQQ.........iliv
ITRVQQ.........rliv KBBVQQ.........manv
KBPVQQ.........manv KBRVQQ.........manv
LADDOK.........long6 LCWRQQ.........lscw7
LDCVQQ.........liov LDDRQQ.........tsdr
LDLG2..........dedr7 LDNGQQ.........long6
LDSRQQ.........tsdr LIMX87.........emur7
LINVQQ.........linv LIOVQQ.........liov
LLIVQQ.........lliv LLOVQQ.........llov
LMNGQQ.........long6 LMULOK.........long6
LNDRQQ.........tsdr LNEEQQ.........erree
LNSRQQ.........tsdr LNTEQQ.........debe
LOCKED.........misg6 LONCQQ.........lonc
LOPVQQ.........lopv LRNGQQ.........long6
LSEEK..........rtim6 LSOVQQ.........manv
LSWRQQ.........lscw7 M2ISQQ.........msfr7
MAXMQQ.........entx6l MDDRQQ.........stdr
MDSRQQ.........stsr MIN8...........tidgl
MINCQQ.........lonc MISHQQ.........mishm
MISOQQ.........miso MISYQQ.........misy
MNDRQQ.........stdr MNNGQQ.........forw6
MNSRQQ.........stsr MOD2...........intrns
MOD4...........intrns MOVEL..........misg6
MOVER..........misg6 MOVESL.........misg6
MOVESR.........misg6 MOVRQQ.........emur7
MP2DQQ.........mp2r7 MP2SQQ.........mp2r7
MPBRQQ.........emus7 MPDRQQ.........emur7
MPHRQQ.........emur7 MPIRQQ.........emus7
MPPRQQ.........emur7 MPSRQQ.........emus7
MSKX87.........emur7 MTBUQQ.........misg6
MUDRQQ.........emur7 MUPTQQ.........emur7
MXDRQQ.........stdr MXNGQQ.........forw6
MXSRQQ.........stsr NANRQQ.........dedr7
NAOGQQ.........long6 NDZGQQ.........long6
NEFUQQ.........foruxm NEWX87.........emur7
NFMVQQ.........manv NINT2..........intrns
NINT4..........intrns NOREQQ.........erree
NSNWQQ.........fong NXRVQQ.........manv
NXTUQQ.........filuxm OACVQQ.........liov
OADVQQ.........rlov OAIVQQ.........ilov
OALVQQ.........llov OAMVQQ.........llov
OANVQQ.........ilov OARVQQ.........rlov
OEMS87.........oemr7 OEMX87.........oemr7
OIFVQQ.........liov OLDX87.........emur7
ONERQQ.........dedr7 OP1RQQ.........emur7
OPEN...........rtim6 OPNUQQ.........filuxm
OPNVQQ.........manv OTCVQQ.........liov
OTDVQQ.........rlov OTIVQQ.........ilov
OTLVQQ.........llov OTMVQQ.........llov
OTNVQQ.........ilov OTRVQQ.........rlov
OUTUQQ.........filuxm OVIEQQ.........erree
OVNEQQ.........erree OVRE87.........misg6
OVREQQ.........erree OVWEQQ.........erree
PBFUQQ.........conuxm PBLVQQ.........manv
PCCUQQ.........filuxm PCTVQQ.........manv
PERUQQ.........filuxm PFNUQQ.........filuxm
PIDRQQ.........tsdr PISRQQ.........tsdr
PLDVQQ.........liov PLYUQQ.........conuxm
PNUXQQ.........entx6l POSVQQ.........dpsv
PPMUQQ.........filuxm PRDRQQ.........tsdr
PREE87.........misg6 PREEQQ.........erree
PRSRQQ.........tsdr PSTVQQ.........fmtv
PTUVQQ.........manv PTYUQQ.........conuxm
PUTUQQ.........filuxm PUTVQQ.........manv
PWRRQQ.........dedr7 PWTRQQ.........dedr7
RABRQQ.........emur7 RACVQQ.........fmtv
RADRQQ.........emur7 RADTQQ.........emur7
RADVQQ.........rinv RAIVQQ.........iinv
RALVQQ.........linv RAMVQQ.........linv
RANVQQ.........iinv RARVQQ.........rinv
RASTQQ.........emur7 RCDTQQ.........emur7
RCSTQQ.........emur7 RDBRQQ.........emur7
RDDRQQ.........emur7 RDDTQQ.........emur7
RDGVQQ.........manv RDSTQQ.........emur7
READ...........rtim6 RECEQQ.........entx6l
REFEQQ.........entx6l REPEQQ.........entx6l
RESEQQ.........entx6l RESX87.........comr7
REWVQQ.........auxv RFDR...........stdr
RFSR...........stsr RIDTQQ.........emur7
RINVQQ.........rinv RISTQQ.........emur7
RLDTQQ.........emur7 RLIVQQ.........rliv
RLOVQQ.........rlov RLSTQQ.........emur7
RLTTQQ.........emur7 RMBRQQ.........emur7
RMDRQQ.........emur7 RMDTQQ.........emur7
RMSTQQ.........emur7 RNDCQQ.........rndc7
RNDRQQ.........rndc7 RNPEQQ.........erree
RODTQQ.........emur7 ROPVQQ.........ropv
ROSTQQ.........emur7 RRDTQQ.........emur7
RRSTQQ.........emur7 RSDTQQ.........emur7
RSSTQQ.........emur7 RSTTQQ.........emur7
RTCVQQ.........fmtv RTDTQQ.........emur7
RTDVQQ.........rinv RTIVQQ.........iinv
RTLVQQ.........linv RTMVQQ.........linv
RTNVQQ.........iinv RTRVQQ.........rinv
RTSTQQ.........emur7 S24IQQ.........rtim6
SADDOK.........misg6 SADTQQ.........emur7
SAOGQQ.........misg6 SASTQQ.........emur7
SBPTQQ.........emur7 SCAC87.........dedr7
SCDTQQ.........emur7 SCSTQQ.........emur7
SCWRQQ.........lscw7 SDDTQQ.........emur7
SDSTQQ.........emur7 SDZGQQ.........misg6
SEKUQQ.........filuxm SEKVQQ.........auxv
SHDRQQ.........tsdr SHRUQQ.........rtim6
SHSRQQ.........tsdr SIDTQQ.........emur7
SIGN4..........intrns SINEQQ.........erree
SISTQQ.........emur7 SLDTQQ.........emur7
SLOX87.........emur7 SLSTQQ.........emur7
SLTTQQ.........emur7 SMDTQQ.........emur7
SMSTQQ.........emur7 SMULOK.........misg6
SNDRQQ.........tsdr SNSRQQ.........tsdr
SODTQQ.........emur7 SOSTQQ.........emur7
SOVEQQ.........erree SOVGQQ.........misg6
SRDRQQ.........tsdr SRDTQQ.........emur7
SRPTQQ.........emur7 SRSRQQ.........tsdr
SRSTQQ.........emur7 SRTEQQ.........erree
SSDTQQ.........emur7 SSSTQQ.........emur7
SSTTQQ.........emur7 SSWRQQ.........lscw7
STBIQQ.........rtim6 STDTQQ.........emur7
STKBQQ.........entx6l STKHQQ.........entx6l
STPRQQ.........dedr7 STPVQQ.........auxv
STSTQQ.........emur7 SUDRQQ.........emur7
SVDRQQ.........emur7 TAJRQQ.........emur7
TANEQQ.........erree TASRQQ.........emur7
TDJRQQ.........emur7 TDSRQQ.........emur7
TENRQQ.........dedr7 TFCUQQ.........conuxm
TFDUQQ.........foruxm THDRQQ.........tsdr
THSRQQ.........tsdr TICS...........tidgl
TIDGQQ.........tidgl TIME...........tidgl
TMJRQQ.........emur7 TMSRQQ.........emur7
TNDRQQ.........tsdr TNSRQQ.........tsdr
TOORQQ.........dedr7 TRAEQQ.........debe
TRMVQQ.........manv TRTRQQ.........emur7
TSIR87.........oemr7 TSRR87.........oemr7
TUGRQQ.........emtr7 U24IQQ.........rtim6
UADDOK.........misg6 UAOGQQ.........misg6
UDZGQQ.........misg6 UERE87.........misg6
UEREQQ.........erree UM46OK.........utlx
UMULOK.........misg6 UNLINK.........rtim6
UNLOCK.........misg6 UNRE87.........misg6
UNREQQ.........erree UPCX87.........entx6l
UTLXQQ.........utlx VASGQQ.........misg6
WACVQQ.........fmtv WADVQQ.........ropv
WAIVQQ.........iopv WALVQQ.........lopv
WAMVQQ.........lopv WANVQQ.........iopv
WARVQQ.........ropv WEFUQQ.........filuxm
WRFVQQ.........fmtv WRITE..........rtim6
WRUVQQ.........manv WTCVQQ.........fmtv
WTDVQQ.........ropv WTIVQQ.........iopv
WTLVQQ.........lopv WTMVQQ.........lopv
WTNVQQ.........iopv WTRVQQ.........ropv
XTPRQQ.........dedr7 YTPRQQ.........dedr7
Z4TRQQ.........dedr7 Z5TRQQ.........dedr7
ZPIEQQ.........erree ZPNEQQ.........erree
ZPREQQ.........erree
mishm Offset: 200H Code and data size: A7
CUTHQQ GROHQQ MISHQQ
conuxm Offset: 600H Code and data size: 165
CONUXM ENDUQQ GTYUQQ INIUQQ
PBFUQQ PLYUQQ PTYUQQ TFCUQQ
filuxm Offset: A00H Code and data size: E1A
CLDUQQ CLSUQQ FILUQQ FLBUQQ
FNSUQQ GETUQQ GFNUQQ INPUQQ
NXTUQQ OPNUQQ OUTUQQ PCCUQQ
PERUQQ PFNUQQ PPMUQQ PUTUQQ
SEKUQQ WEFUQQ
entx6l Offset: 1E00H Code and data size: 27F
BEGHQQ BEGMQQ BEGXQQ CESXQQ
CLNEQQ CRCXQQ CRDXQQ CSXEQQ
CURHQQ DGRMQQ DOSEQQ DOSXQQ
ENDHQQ ENDMQQ ENDXQQ HDRFQQ
HDRVQQ MAXMQQ PNUXQQ RECEQQ
REFEQQ REPEQQ RESEQQ STKBQQ
STKHQQ UPCX87
utlx Offset: 2400H Code and data size: 131
UM46OK UTLXQQ
cmpd7 Offset: 2800H Code and data size: EB
CDDDQQ CDEDQQ CSDDQQ CSEDQQ
cmpr7 Offset: 2A00H Code and data size: BD
CDDRQQ CDERQQ CSDRQQ CSERQQ
debe Offset: 2C00H Code and data size: C6
DEBEQQ ENTEQQ EXTEQQ LNTEQQ
TRAEQQ
dedr7 Offset: 3000H Code and data size: 86C
DDEC87 DDECQQ DENC87 DPCRQQ
EEDCQQ EIGRQQ INARQQ LDLG2
NANRQQ ONERQQ PWRRQQ PWTRQQ
SCAC87 STPRQQ TENRQQ TOORQQ
XTPRQQ YTPRQQ Z4TRQQ Z5TRQQ
erre Offset: 4000H Code and data size: 296
EMSEQQ ERREQQ
erree Offset: 4600H Code and data size: 359
ASNEQQ CNVEQQ DNREQQ DZIEQQ
DZNEQQ DZREQQ DZWEQQ EXPEQQ
GHIEQQ GHSEQQ GHVEQQ INREQQ
LNEEQQ NOREQQ OVIEQQ OVNEQQ
OVREQQ OVWEQQ PREEQQ RNPEQQ
SINEQQ SOVEQQ SRTEQQ TANEQQ
UEREQQ UNREQQ ZPIEQQ ZPNEQQ
ZPREQQ
fmrc Offset: 4E00H Code and data size: 2F6
FMRC FMRCQQ
fong Offset: 5400H Code and data size: 2D4
FONG ISIWQQ NSNWQQ
heah Offset: 5A00H Code and data size: 1A5
ALLHQQ GETHQQ HEAHQQ
lonc Offset: 5E00H Code and data size: 3BF
DENCQQ ENNCQQ LONCQQ MINCQQ
long6 Offset: 6400H Code and data size: 1C9
LADDOK LDNGQQ LMNGQQ LMULOK
LRNGQQ NAOGQQ NDZGQQ
lscw7 Offset: 6800H Code and data size: 34
LCWRQQ LSWRQQ SCWRQQ SSWRQQ
misg6 Offset: 6A00H Code and data size: 35C
ASMGQQ ASNGQQ AVAGQQ BRTEQQ
CESGQQ CINSQQ CLSGQQ DNRE87
DZRE87 ERTEQQ FILLC FILLSC
INRE87 LOCKED MOVEL MOVER
MOVESL MOVESR MTBUQQ OVRE87
PREE87 SADDOK SAOGQQ SDZGQQ
SMULOK SOVGQQ UADDOK UAOGQQ
UDZGQQ UERE87 UMULOK UNLOCK
UNRE87 VASGQQ
miso Offset: 7200H Code and data size: 38
BEGOQQ ENDOQQ MISOQQ
misr7 Offset: 7400H Code and data size: 44
AIDRQQ AISRQQ
misy Offset: 7600H Code and data size: CA
ENDYQQ FILKQQ MISYQQ
mp2r7 Offset: 7A00H Code and data size: B0
FRXDQQ MP2DQQ MP2SQQ
msfr7 Offset: 7C00H Code and data size: 50
I2MSQQ M2ISQQ
oemr7 Offset: 7E00H Code and data size: 127
CTCR87 EXCX87 OEMS87 OEMX87
TSIR87 TSRR87
rndc7 Offset: 8200H Code and data size: 65
RNDCQQ RNDRQQ
rtim6 Offset: 8400H Code and data size: D6
$V2_ERROR $V2_EXIT $V2_EXIT2 $V2_OK
CLOSE CREAT ERRNO EXIT
I24IQQ IOCTL LSEEK OPEN
READ S24IQQ SHRUQQ STBIQQ
U24IQQ UNLINK WRITE
stdr Offset: 8800H Code and data size: 1BD
ANDRQQ MDDRQQ MNDRQQ MXDRQQ
RFDR
stsr Offset: 8E00H Code and data size: 1BC
ANSRQQ MDSRQQ MNSRQQ MXSRQQ
RFSR
tsdr Offset: 9400H Code and data size: 7AE
A2DRQQ A2SRQQ ACDRQQ ACSRQQ
ASDRQQ ASSRQQ ATDRQQ ATSRQQ
CHDRQQ CHSRQQ CNDRQQ CNSRQQ
EXDRQQ EXSRQQ LDDRQQ LDSRQQ
LNDRQQ LNSRQQ PIDRQQ PISRQQ
PRDRQQ PRSRQQ SHDRQQ SHSRQQ
SNDRQQ SNSRQQ SRDRQQ SRSRQQ
THDRQQ THSRQQ TNDRQQ TNSRQQ
tidgl Offset: A800H Code and data size: 1A1
DATE DIG2 MIN8 TICS
TIDGQQ TIME
foruxm Offset: AC00H Code and data size: 38E
DIFUQQ EOFUQQ FORUXM FPSUQQ
IOCUQQ NEFUQQ TFDUQQ
auxv Offset: B200H Code and data size: 553
AUXVQQ BAKVQQ ENFVQQ EOFVQQ
REWVQQ SEKVQQ STPVQQ
dpsv Offset: BC00H Code and data size: C8
DPSVQQ POSVQQ
erhv Offset: C000H Code and data size: 13E
ERHVQQ ICLRER IGETER
ermv Offset: C400H Code and data size: 54
EFEVQQ EREVQQ EXTVQQ
fmtv Offset: C600H Code and data size: A58
FMTVQQ GFTVQQ GOFVQQ GOIVQQ
PSTVQQ RACVQQ RTCVQQ WACVQQ
WRFVQQ WTCVQQ
fore Offset: D800H Code and data size: 9B
AGOEQQ FOREQQ
forw6 Offset: DA00H Code and data size: DF
CMPWQQ MNNGQQ MXNGQQ
iinv Offset: DC00H Code and data size: 216
IINVQQ RAIVQQ RANVQQ RTIVQQ
RTNVQQ
iliv Offset: E200H Code and data size: 17D
IAIVQQ IANVQQ ILIVQQ ITIVQQ
ITNVQQ
ilov Offset: E600H Code and data size: 18C
ILOVQQ OAIVQQ OANVQQ OTIVQQ
OTNVQQ
intrns Offset: EA00H Code and data size: 706
ABS4 AINT4 AMOD4 ANINT4
DABS8 DDIM8 DIM4 DINT8
DMOD8 DNINT8 DPROD8 DSIGN8
IABS2 IABS4 IDIM2 IDIM4
IDNIN2 IDNIN4 ISIGN2 ISIGN4
MOD2 MOD4 NINT2 NINT4
SIGN4
iopv Offset: F800H Code and data size: 1BD
IOPVQQ WAIVQQ WANVQQ WTIVQQ
WTNVQQ
linv Offset: FC00H Code and data size: 1D3
LINVQQ RALVQQ RAMVQQ RTLVQQ
RTMVQQ
liov Offset: 10000H Code and data size: 597
GLDVQQ GLFVQQ GLIVQQ IACVQQ
ITCVQQ LDCVQQ LIOVQQ OACVQQ
OIFVQQ OTCVQQ PLDVQQ
lliv Offset: 10A00H Code and data size: 181
IALVQQ IAMVQQ ITLVQQ ITMVQQ
LLIVQQ
llov Offset: 10E00H Code and data size: 12B
LLOVQQ OALVQQ OAMVQQ OTLVQQ
OTMVQQ
lopv Offset: 11200H Code and data size: 14B
LOPVQQ WALVQQ WAMVQQ WTLVQQ
WTMVQQ
manv Offset: 11600H Code and data size: 12B4
BUFVQQ BZFVQQ BZLVQQ CLSVQQ
COLVQQ CRNVQQ EFLVQQ ENRVQQ
ERFVQQ ERLVQQ ERRVQQ ERUVQQ
FDUVQQ FILVQQ FLBVQQ FLRVQQ
FMDVQQ GETVQQ GOUVQQ GTMVQQ
GTUVQQ IIOVQQ INIVQQ IOCVQQ
KBBVQQ KBPVQQ KBRVQQ LSOVQQ
NFMVQQ NXRVQQ OPNVQQ PBLVQQ
PCTVQQ PTUVQQ PUTVQQ RDGVQQ
TRMVQQ WRUVQQ
rinv Offset: 13200H Code and data size: 32F
RADVQQ RARVQQ RINVQQ RTDVQQ
RTRVQQ
rliv Offset: 13800H Code and data size: 266
IADVQQ IARVQQ ITDVQQ ITRVQQ
RLIVQQ
rlov Offset: 13E00H Code and data size: 25F
OADVQQ OARVQQ OTDVQQ OTRVQQ
RLOVQQ
ropv Offset: 14400H Code and data size: 32B
ROPVQQ WADVQQ WARVQQ WTDVQQ
WTRVQQ
emtr7 Offset: 14A00H Code and data size: 749
TUGRQQ
emur7 Offset: 15800H Code and data size: 1B98
ABSTQQ ADDRQQ ADPTQQ BADTQQ
BASTQQ BASX87 BCDTQQ BCSTQQ
BDDTQQ BDSTQQ BIDTQQ BISTQQ
BLDTQQ BLSTQQ BMDTQQ BMSTQQ
BODTQQ BOSTQQ BRDTQQ BRSTQQ
BSDTQQ BSSTQQ BTDTQQ BTSTQQ
CFERQQ CHIX87 CHSTQQ CURX87
CWDX87 DIDRQQ DRDRQQ DRPTQQ
DSTRQQ DUPTQQ DVPTQQ FIDRQQ
FIERQQ FIWRQQ FLGX87 INDX87
LIMX87 MOVRQQ MPDRQQ MPHRQQ
MPPRQQ MSKX87 MUDRQQ MUPTQQ
NEWX87 OLDX87 OP1RQQ RABRQQ
RADRQQ RADTQQ RASTQQ RCDTQQ
RCSTQQ RDBRQQ RDDRQQ RDDTQQ
RDSTQQ RIDTQQ RISTQQ RLDTQQ
RLSTQQ RLTTQQ RMBRQQ RMDRQQ
RMDTQQ RMSTQQ RODTQQ ROSTQQ
RRDTQQ RRSTQQ RSDTQQ RSSTQQ
RSTTQQ RTDTQQ RTSTQQ SADTQQ
SASTQQ SBPTQQ SCDTQQ SCSTQQ
SDDTQQ SDSTQQ SIDTQQ SISTQQ
SLDTQQ SLOX87 SLSTQQ SLTTQQ
SMDTQQ SMSTQQ SODTQQ SOSTQQ
SRDTQQ SRPTQQ SRSTQQ SSDTQQ
SSSTQQ SSTTQQ STDTQQ STSTQQ
SUDRQQ SVDRQQ TAJRQQ TASRQQ
TDJRQQ TDSRQQ TMJRQQ TMSRQQ
TRTRQQ
emus7 Offset: 18E00H Code and data size: 2A4
MPBRQQ MPIRQQ MPSRQQ
comr7 Offset: 19400H Code and data size: 1D7
CHPRQQ ENDX87 I3EX87 INTR87
RESX87


Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

View File

@ -0,0 +1,368 @@
1.0 INTRODUCTION
This describes changes to MS-FORTRAN Version 3.13 that
were made too late to be described in either the reference
manual or the User's Guide and its addendum. It also
outlines differences between versions 3.13 and 3.10.
2.0 DIFFERENCE FROM VERSION 3.13
2.1 Enhancements
The following changes are made to the way the compiler
and runtime behave:
a. The default setting of the 8087 control word enables
NAN, divide-by-zero and infinity exceptions. These will now
give a runtime error. Use LCWRQQ if you preferred the 3.10
behavior.
b. Most incorrect format strings in FORMAT, READ and WRITE
statements now give warning messages.
c. The compiler front end is smaller and, on systems with
limited memory, should compile larger programs.
d. NULR7.OBJ is no longer required, since floating point
code is only included with your program if it is actually
needed.
e. The compiler sets an exit status to MSDOS 2.0.
2.2 Corrections
The following errors in version 3.10 have been
corrected:
Incorrect code was being generated for comparisons of reals
in named common.
External and actual functions of the same type gave an ERROR
33
An error on the last line of a formatted input file would
'create' an extra (empty) line. Errors were also caused if
a file did not end in a <Control Z>.
List directed format choices for real numbers were not
triggered by the ranges documented.
INTEGER*4 conversions to real were sometimes incorrectly
rounded.
Page 2
G format choices were not triggered by the ranges
documented.
READ or WRITE of an adjustable array caused a compile time
error 151.
Reading a real with list directed input would not accept a
null item.
Statement function actual and formal parameter sizes were
sometimes incorrectly matched.
PAS2 looped indefinitely for c=amin0(-5,min0(0,1))
The last record output to the printer was not printed on
certain types of printer.
INTEGER*4 exponentiation was truncated to 16-bits under some
circumstances.
PAS2 sometimes gave incorrect integer overflow message.
FOR1 was not deleting intermediate files if it detected a
compile error.
Incorrect code might be generated for multiple
multi-dimensioned array references.
If the result of an expression was assigned to an INTEGER*2,
divides of INTEGER*4 values were done with 16-bit division.
DEXP(X) sometimes returned zero.
amin0(i,i) caused a PAS2 loop.
An erroneous compile time error 71 sometimes occurred.
3.0 NULR7.OBJ
This module is not supplied with this version since the
Real Math Package is only included in your program if you
actually use floating point operations.
4.0 COMPILE TIME FORMAT CHECKING.
A special warning message will be displayed by the
compiler if a format specification contains certain errors.
This has the form:
***** Warning -- Invalid Format, Error n, Line m
Page 3
Where n is one of the following runtime error codes:
1200
1204..1213
1215..1224
1226..1228
1232
and m is the line number of the offending statement.
5.0 EXIT STATUS
The compiler supplies an exit status to MSDOS 2.0 that
can be accessed via the "IF ERRORLEVEL n" batch command.
The vaules returned by the compiler are:
n Value Meaning
0 No warning or errors issued
1 Warnings messges were issued
2 Fatal errors were encountered
6.0 ALTERNATIVE LINKER
Two versions of the MS-LINK utility are provided with
this version of MS Fortran. The first, named LINK.V1 is the
most current linker for MS-DOS versions 1.25 and below. It
will run under MS-DOS 2.0 but cannot accept pathnames or
subdirectories. The other is named LINK.V2 and will run
only on MS-DOS 2.0. The limits on program size,
relocations, externals per module etc., are bigger for
LINK.V2 than for either LINK.V1 or the linker usually
supplied with MS-DOS 2.0. The interface to both linkers is
identical and is as described in the linker documentation.
You should rename the one you want to use LINK.EXE.
7.0 EXTENDED NON-DECIMAL NUMBERS
Although the maximum 32-bit integer value is defined as
2**31-1, the compiler and runtime will read greater values
which are nominally in the range upto 2**32 without giving
an error if (and only if) the radix is other than 10. They
will be interpreted as the negative numbers with the
corresponding internal representation. For example,
16#FFFFFFFF will result in all the bits in the 32-bit
integer result being set, and will have an arithmetic value
of -1.
Page 4
8.0 $MESSAGE METACOMMAND
The $MESSAGE metacommand can be used to send messages
to the standard output device when running the Fortran front
end, for example:
$MESSAGE: 'This is displayed when you run FOR1'
The message string must be 40 characters or fewer.
9.0 FLOATING POINT OPERATIONS
Most users of MS-Fortran will find the default behavior
of the floating point operations will provide extremely
accurate, consistent and efficient processing of their
algorithms, whether they have an 8087 installed or not. If
this is the case for you, you need not be concerned with the
issues described either below or in the addendum to the
User's Guide.
However, those who wish to take advantage of the full
power and flexiblity of the proposed IEEE Real Math Standard
should read both the addendum and the following description
carefully.
9.1 Math Package Size
The REAL arithmetic support routines contribute about
6.5k bytes to your program and not 4.5k as specified in the
addendum.
9.2 $FLOATCALLS And The 8087
Contrary to the description in the addendum to the
Fortran User's Guide, programs compiled with the $FLOATCALLS
option, linked with the emulator library and run on a
machine with an 8087, will use the 8087 to do the actual
arithmetic. This means that using this option will result
in a much smaller performance penalty, when you have an
8087, than suggested in the addendum.
9.3 Environment Control And Exception Handling For 8087 Math
There are five exceptions required by the IEEE
standard. The "Control Word" defines what response is made
to each exception (see below for a description of the
Control Word and how to access it). The exceptions and the
default and alternative responses are as follows:
Page 5
1. Invalid Operation - any operation involving a NAN (Not A
a number), SQRT (-1), 0*infinity etc.
Default Action - Enabled: gives runtime error 2136.
Alternate Action - Disabled: returns a NAN
2. Divide by Zero - r/0.0
Default Action - Enabled: gives runtime error 2100
Alternate Action - Disabled: returns a properly signed
INF (infinity)
3. Overflow - Operation results in a number greater
than maximum representable number.
Default Action - Enabled: gives runtime error 2101.
Alternate Action - Disabled: returns INF.
4. Underflow - Operation results in a number smaller
than minimum representable number.
Default Action - Disabled: returns zero.
Alternate Action - Enabled: gives runtime error 2135.
5. Precision Loss - When a result is subject to rounding
error, means result is not exact.
Default Action - Disabled: Returns properly rounded
result.
Alternate Action - Enabled: gives runtime error 2139
Note that if you have masked the exceptions, you may
get not-a-number values. If you write these values with
formatted i/o, you will either get asterisks, or, more
usually, the letters INF - for infinity, IND - for
indefinite, and NAN - for not-a-number will appear, usually
in the fractional part of the field.
Contrary to the description in the MS-Fortran reference
(Section 6.2.1) the $DEBUG metacommand does not control the
handling of the exceptions (you should continue to use it to
control Integer aritmetic errors, however). Instead, there
are two memory locations that control both processors.
These are called the CONTROL and STATUS words. (You can
access or change the control and status words by using one
of the procedures described below). When one of the
exceptional conditions occurs, the appropriate bit in the
status word is set. This flag will remain set to indicate
that the exception occurred until cleared by the user. If
the bit in the control word relating to a given exception is
set then that exception is masked and the operation proceeds
with a supplied default. If the bit is unset any exception
of that type generates an error message, halts the operation
and your program will stop. In either case the exception is
ORed into the STATUS word.
The CONTROL word is also used to set modes for the
internal arithmetic required by the IEEE standard. These
are:
Page 6
Rounding Control - round to nearest (or even), Up,
Down, or Chop
Precision Control - Determines at which bit of the
manstissa rounding should take place. (24, 53,
or 64). Note all results are done to 64 bits
regardless of the precision control. It only
affects the rounding in the internal form.
On storage any result is again rounded to the
storage precision.
Infinity Control - Affine mode is the familar + and
- INF style of arithmetic. Projective mode is a
mode where + and - INF are considered to be the
same number. The principal effect is to change the
nature of comparisons (Projective INF does not
compare with anything but itself).
Format for STATUS BYTE and CONTROL WORD
15 8 7 6 5 4 3 2 1 0
STATUS | hi byte unused | | |PE|UE|OE|ZE| |IE|
| | | | |
Precision Exception -------------------+ | | | |
Underflow Exception ----------------------+ | | |
Overflow Exception --------------------------+ | |
Zero Divide Exception --------------------------+ |
Invalid Exception ------------------------------------+
(All other bits unused, may be either 1 or 0)
15 14 15 12 11-10 9-8 7 6 5 4 3 2 1 0
CONTROL | | | |IC| RC | PC | | |PM|UM|OM|ZM| |IM|
| | | | | | | |
Infinity Control -+ | | | | | | |
Round Control --------+ | | | | | |
Precision Control ----------+ | | | | |
| | | | |
Precision Mask ------------------------+ | | | |
Underflow Mask ---------------------------+ | | |
Overflow Mask -------------------------------+ | |
Zero Divide Mask -------------------------------+ |
Invalid Mask -----------------------------------------+
(All other bits unused, may be either 1 or 0)
Infinity Control
0 = Projective
1 = Affine
Round Control
00 = Round nearest or even
01 = Round down (toward -INF)
Page 7
10 = Round up (toward +INF)
11 = Chop (Truncate toward 0)
Precision Control
00 = 24 bits of mantissa
01 = (reserved)
10 = 53 bits of mantissa
11 = 64 bits of mantissa
You can read or set the value of the control word and
read the status word using the following subroutines:
C Load Control Word
SUBROUTINE LCWRQQ (CW)
INTEGER*2 CW
C Sets the control word to the value in CW
C Store Control Word
INTEGER*2 FUNCTION SCWRQQ
C Returns the value of the control word
C Store Status Word
INTEGER*2 FUNCTION SSWRQQ
C Returns the value of the status word


View File

@ -0,0 +1,28 @@
C Eratosthenes Sieve from BYTE magazine
program sieve
logical flags( 8191 )
integer*2 i, prime, k, count
integer*2 iter
write( *, 50 )
50 format( ' 10 iterations' )
do 92 iter = 1, 10
count = 0
do 10 i = 0, 8190
10 flags( i ) = .true.
do 91 i = 0, 8190
if ( .not. flags( i ) ) go to 91
prime = i + i + 3
k = i + prime
20 if ( k .gt. 8190 ) go to 90
flags( k ) = .false.
k = k + prime
go to 20
90 count = count + 1
91 continue
92 continue
write( *, 200 ) count
200 format( 1X, I6, ' primes' )
stop
100 format( 1X, I6 )
end

View File

@ -0,0 +1,210 @@
C fortran version of proving you can't win at tic-tac-toe if the opponent is competent
C constants:
C score win: 6
C score tie: 5
C score lose: 4
C score max: 9
C score min: 2
C piece X: 1
C piece O: 2
C piece blank: 0
program ttt
integer*4 moves
integer*2 b(9), sp(10), sv(10), sa(10), sb(10), sm(10)
integer*2 mc, l
integer*2 alpha, beta, wi, st, sc, v, p, pm, m
common /area/ b,sp,sv,sa,sb,sm,mc,alpha,beta,wi,st,sc,v,p,pm,m
integer*2 system
do 6 l = 1, 9, 1
b( l ) = 0
6 continue
moves = 0
do 10 l = 1, 10, 1
C do 10 l = 1, 1, 1
mc = 0
m = 1
call runmm
m = 2
call runmm
m = 5
call runmm
moves = moves + mc
10 continue
write( *, 20 ) moves
20 format( ' moves: ', I6 )
end
1000 subroutine runmm
integer*2 b(9), sp(10), sv(10), sa(10), sb(10), sm(10)
integer*2 mc, l
integer*2 alpha, beta, wi, st, sc, v, p, pm, m
common /area/ b,sp,sv,sa,sb,sm,mc,alpha,beta,wi,st,sc,v,p,pm,m
alpha = 2
beta = 9
p = m
b(m) = 1
call minmax
b(m) = 0
return
end
2000 subroutine winner
integer*2 b(9), sp(10), sv(10), sa(10), sb(10), sm(10)
integer*2 mc, l
integer*2 alpha, beta, wi, st, sc, v, p, pm, m
common /area/ b,sp,sv,sa,sb,sm,mc,alpha,beta,wi,st,sc,v,p,pm,m
wi = b( 1 )
if ( 0 .eq. wi ) go to 2100
if ( ( wi .eq. b( 2 ) ) .and. ( wi .eq. b( 3 ) ) ) return
if ( ( wi .eq. b( 4 ) ) .and. ( wi .eq. b( 7 ) ) ) return
2100 wi = b( 4 )
if ( 0 .eq. wi ) go to 2200
if ( ( wi .eq. b( 5 ) ) .and. ( wi .eq. b( 6 ) ) ) return
2200 wi = b( 7 )
if ( 0 .eq. wi ) go to 2300
if ( ( wi .eq. b( 8 ) ) .and. ( wi .eq. b( 9 ) ) ) return
2300 wi = b( 2 )
if ( 0 .eq. wi ) go to 2400
if ( ( wi .eq. b( 5 ) ) .and. ( wi .eq. b( 8 ) ) ) return
2400 wi = b( 3 )
if ( 0 .eq. wi ) go to 2500
if ( ( wi .eq. b( 6 ) ) .and. ( wi .eq. b( 9 ) ) ) return
2500 wi = b( 5 )
if ( 0 .eq. wi ) return
if ( ( wi .eq. b( 1 ) ) .and. ( wi .eq. b( 9 ) ) ) return
if ( ( wi .eq. b( 3 ) ) .and. ( wi .eq. b( 7 ) ) ) return
wi = 0
end
4000 subroutine minmax
integer*2 b(9), sp(10), sv(10), sa(10), sb(10), sm(10)
integer*2 mc, l
integer*2 alpha, beta, wi, st, sc, v, p, pm, m
common /area/ b,sp,sv,sa,sb,sm,mc,alpha,beta,wi,st,sc,v,p,pm,m
st = 0
v = 0
4100 mc = mc + 1
if ( st .lt. 4 ) go to 4150
C the computed goto is about 20% faster than calling winner
C call winner
go to ( 5010, 5020, 5030, 5040, 5050, 5060, 5070, 5080, 5090 ), p
4110 if ( wi .eq. 0 ) go to 4140
if ( wi .ne. 1 ) go to 4130
sc = 6
go to 4280
4130 sc = 4
go to 4280
4140 if ( st .ne. 8 ) go to 4150
sc = 5
go to 4280
4150 if ( b( p ) .eq. 1 ) go to 4160
v = 2
pm = 1
go to 4170
4160 v = 9
pm = 2
4170 p = 1
4180 if ( b( p ) .ne. 0 ) go to 4500
b( p ) = pm
4182 st = st + 1
sp( st ) = p
sv( st ) = v
sa( st ) = alpha
sb( st ) = beta
sm( st ) = pm
go to 4100
4280 p = sp( st )
v = sv( st )
alpha = sa( st )
beta = sb( st )
pm = sm( st )
st = st - 1
b( p ) = 0
if ( pm .eq. 1 ) go to 4340
if ( sc .eq. 4 ) go to 4530
if ( sc .lt. v ) v = sc
if ( v .lt. beta ) beta = v
if ( beta .le. alpha ) go to 4520
go to 4500
4340 if ( sc .eq. 6 ) go to 4530
if ( sc .gt. v ) v = sc
if ( v .gt. alpha ) alpha = v
if ( alpha .ge. beta ) go to 4520
4500 p = p + 1
if ( p .lt. 10 ) go to 4180
4520 sc = v
4530 if ( st .eq. 0 ) return
go to 4280
5010 wi = b(1)
if ( ( wi .eq. b(2) ) .and. ( wi .eq. b(3) ) ) goto 4110
if ( ( wi .eq. b(4) ) .and. ( wi .eq. b(7) ) ) goto 4110
if ( ( wi .eq. b(5) ) .and. ( wi .eq. b(9) ) ) goto 4110
wi = 0
go to 4110
5020 wi = b(2)
if ( ( wi .eq. b(1) ) .and. ( wi .eq. b(3) ) ) goto 4110
if ( ( wi .eq. b(5) ) .and. ( wi .eq. b(8) ) ) goto 4110
wi = 0
go to 4110
5030 wi = b(3)
if ( ( wi .eq. b(1) ) .and. ( wi .eq. b(2) ) ) goto 4110
if ( ( wi .eq. b(6) ) .and. ( wi .eq. b(9) ) ) goto 4110
if ( ( wi .eq. b(5) ) .and. ( wi .eq. b(7) ) ) goto 4110
wi = 0
go to 4110
5040 wi = b(4)
if ( ( wi .eq. b(5) ) .and. ( wi .eq. b(6) ) ) goto 4110
if ( ( wi .eq. b(1) ) .and. ( wi .eq. b(7) ) ) goto 4110
wi = 0
go to 4110
5050 wi = b(5)
if ( ( wi .eq. b(1) ) .and. ( wi .eq. b(9) ) ) goto 4110
if ( ( wi .eq. b(3) ) .and. ( wi .eq. b(7) ) ) goto 4110
if ( ( wi .eq. b(2) ) .and. ( wi .eq. b(8) ) ) goto 4110
if ( ( wi .eq. b(4) ) .and. ( wi .eq. b(6) ) ) goto 4110
wi = 0
go to 4110
5060 wi = b(6)
if ( ( wi .eq. b(4) ) .and. ( wi .eq. b(5) ) ) goto 4110
if ( ( wi .eq. b(3) ) .and. ( wi .eq. b(9) ) ) goto 4110
wi = 0
go to 4110
5070 wi = b(7)
if ( ( wi .eq. b(8) ) .and. ( wi .eq. b(9) ) ) goto 4110
if ( ( wi .eq. b(1) ) .and. ( wi .eq. b(4) ) ) goto 4110
if ( ( wi .eq. b(5) ) .and. ( wi .eq. b(3) ) ) goto 4110
wi = 0
go to 4110
5080 wi = b(8)
if ( ( wi .eq. b(7) ) .and. ( wi .eq. b(9) ) ) goto 4110
if ( ( wi .eq. b(2) ) .and. ( wi .eq. b(5) ) ) goto 4110
wi = 0
go to 4110
5090 wi = b(9)
if ( ( wi .eq. b(7) ) .and. ( wi .eq. b(8) ) ) goto 4110
if ( ( wi .eq. b(3) ) .and. ( wi .eq. b(6) ) ) goto 4110
if ( ( wi .eq. b(1) ) .and. ( wi .eq. b(5) ) ) goto 4110
wi = 0
go to 4110
end

View File

@ -0,0 +1,25 @@
@echo off
setlocal
del %1.exe 1>nul 2>nul
del %1.lst 1>nul 2>nul
del %1.map 1>nul 2>nul
del %1.obj 1>nul 2>nul
del %1.cod 1>nul 2>nul
rem compile
ntvdm -r:. for1 %1,%1,%1,%1
if %ERRORLEVEL% NEQ 0 goto eof
ntvdm -r:. pas2
ntvdm -r:. pas3
rem link
ntvdm -r:. -f link %1,%1,%1,fortran.lem
del %1.lst 1>nul 2>nul
del %1.map 1>nul 2>nul
del %1.obj 1>nul 2>nul
del %1.cod 1>nul 2>nul
:eof