diff --git a/Microsoft Fortran v331/DEMO.FOR b/Microsoft Fortran v331/DEMO.FOR new file mode 100644 index 0000000..bc385b4 --- /dev/null +++ b/Microsoft Fortran v331/DEMO.FOR @@ -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 ascending 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 + diff --git a/Microsoft Fortran v331/DEMOEXEC.FOR b/Microsoft Fortran v331/DEMOEXEC.FOR new file mode 100644 index 0000000..01b2403 --- /dev/null +++ b/Microsoft Fortran v331/DEMOEXEC.FOR @@ -0,0 +1,47 @@ +c DEMOEXEC.FOR - demonstration program for calling C library functions +c +c Microsoft FORTRAN77 release 3.30 can call large model C functions. +c Please read FOREXEC.INC for more details on interlanguage calling. +c +c To compile and link DEMOEXEC.FOR +c +c for1 demoexec; +c pas2 +c link demoexec,,,cexec; (must search CEXEC.LIB) + +$include : 'forexec.inc' + +c declare return types of the 2 C functions + + integer*2 system, spawn + +c invoke command.com with a command line +c +c dir *.for + + i = system('dir *.for'c) + write (*,*) 'system return code = ',i + write (*,*) + +c invoke a child process +c +c exemod (display usage line only) + + i = spawn(0,loc('exemod'c),loc('exemod'c), + + int4(0)) + write (*,*) 'spawn return code =',i + write (*,*) + +c invoke an overlay process (chaining) +c +c exemod demoexec.exe + + i = spawn(2,loc('exemod'c),loc('exemod'c), + + loc('demoexec.exe'c),int4(0)) + +c we should never see this if spawn (overlay) is successful + + write (*,*) 'spawn return code =',i + write (*,*) + + end diff --git a/Microsoft Fortran v331/E.FOR b/Microsoft Fortran v331/E.FOR new file mode 100644 index 0000000..1cde1b0 --- /dev/null +++ b/Microsoft Fortran v331/E.FOR @@ -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 + + + diff --git a/Microsoft Fortran v331/EGATEST.FOR b/Microsoft Fortran v331/EGATEST.FOR new file mode 100644 index 0000000..de1685c --- /dev/null +++ b/Microsoft Fortran v331/EGATEST.FOR @@ -0,0 +1,11 @@ + PROGRAM EGATEST +C + INTEGER X,Y,PIXVAL +C +100 WRITE(*,*) 'X,Y,PIXEL VALUE ' + READ(*,*) X,Y,PIXVAL + CALL EGADOT(X,Y,PIXVAL) + GOTO 100 +C + END + \ No newline at end of file diff --git a/Microsoft Fortran v331/EGATEST2.FOR b/Microsoft Fortran v331/EGATEST2.FOR new file mode 100644 index 0000000..7142321 --- /dev/null +++ b/Microsoft Fortran v331/EGATEST2.FOR @@ -0,0 +1,14 @@ + PROGRAM EGATEST2 +C + INTEGER X,Y,PIXVAL +C +100 WRITE(*,*) 'X,Y,PIXEL VALUE ' + READ(*,*) X,Y,PIXVAL + WRITE(*,*) X,Y,PIXVAL + PAUSE 11 + CALL EGA2(X,Y,PIXVAL) + PAUSE 12 + GOTO 100 +C + END + \ No newline at end of file diff --git a/Microsoft Fortran v331/EGATEST3.FOR b/Microsoft Fortran v331/EGATEST3.FOR new file mode 100644 index 0000000..d8853f3 --- /dev/null +++ b/Microsoft Fortran v331/EGATEST3.FOR @@ -0,0 +1,21 @@ + PROGRAM DKF +C + INTEGER X,Y,PIX +C + Y = 50 +C + DO 200 PIX = 1,15 + Y=Y+10 + DO 100 X = 0,638 + CALL EGADOT(X,Y,PIX) +100 CONTINUE +200 CONTINUE +C + DO 400 PIX = 1,15 + Y=Y+10 + DO 300 X = 0,348 + CALL EGADOT(Y,X,PIX) +300 CONTINUE +400 CONTINUE + END + \ No newline at end of file diff --git a/Microsoft Fortran v331/EGATEST4.FOR b/Microsoft Fortran v331/EGATEST4.FOR new file mode 100644 index 0000000..28fef28 --- /dev/null +++ b/Microsoft Fortran v331/EGATEST4.FOR @@ -0,0 +1,19 @@ + PROGRAM DKF +C + INTEGER X,Y,PIX +C +55 CALL SETCUR(4,0) + WRITE(*,*) 'R,C' + READ(*,*) R,PIX + THETA = -0.5 +C + DO 200 I = 0,231 + THETA = THETA + 0.25 + X=R*COS(THETA)+320.0 + Y=.78*(R*SIN(THETA))+175.0 + CALL EGADOT(X,Y,PIX) +200 CONTINUE + GOTO 55 +C + END + \ No newline at end of file diff --git a/Microsoft Fortran v331/EGATEST5.FOR b/Microsoft Fortran v331/EGATEST5.FOR new file mode 100644 index 0000000..6aa5ca4 --- /dev/null +++ b/Microsoft Fortran v331/EGATEST5.FOR @@ -0,0 +1,13 @@ + PROGRAM DDSK +C + INTEGER X1,Y1,X2,Y2,COLOR +C +10 WRITE(*,*) 'X1,Y1,X2,Y2,COLOR = ' + READ(*,*) X1,Y1,X2,Y2,COLOR +C + CALL ELSUB(X1,Y1,X2,Y2,COLOR) +C + CALL SETCUR(4,0) + GOTO 10 + END + \ No newline at end of file diff --git a/Microsoft Fortran v331/EGATEST6.FOR b/Microsoft Fortran v331/EGATEST6.FOR new file mode 100644 index 0000000..cbde0e2 --- /dev/null +++ b/Microsoft Fortran v331/EGATEST6.FOR @@ -0,0 +1,14 @@ + PROGRAM XXC +C + INTEGER A,B,F +C + CALL EGASCR +C +10 WRITE(*,*) 'ROW,COL,RAD,THS,THE,COL' + READ(*,*) A,B,C,D,E,F +C + CALL EGAARC(A,B,C,D,E,F) +C + GOTO 10 + END + \ No newline at end of file diff --git a/Microsoft Fortran v331/EGATEST7.FOR b/Microsoft Fortran v331/EGATEST7.FOR new file mode 100644 index 0000000..92b945b --- /dev/null +++ b/Microsoft Fortran v331/EGATEST7.FOR @@ -0,0 +1,14 @@ + PROGRAM DKJFS +C + INTEGER AX,AY,AX1,AY1,COLO +C + CALL EGASCR +C +10 WRITE(*,*) 'AX,AY,AX1,AY1,COLO' + READ(*,*) AX,AY,AX1,AY1,COLO +C + CALL EBOX(AX,AY,AX1,AY1,COLO) +C + GOTO 10 + END + \ No newline at end of file diff --git a/Microsoft Fortran v331/EGATEST8.FOR b/Microsoft Fortran v331/EGATEST8.FOR new file mode 100644 index 0000000..db5bf06 --- /dev/null +++ b/Microsoft Fortran v331/EGATEST8.FOR @@ -0,0 +1,16 @@ + PROGRAM BOILPUS +C + INTEGER A,B,C,D,E,F +C + CALL EGASCR +C +10 WRITE(*,*) 'X,Y,X1,Y1,COLOR = ' + READ(*,*) A,B,C,D,E +C + CALL EFBOX(A,B,C,D,E) +C + CALL SETCUR(2,0) + GOTO 10 +C + END + \ No newline at end of file diff --git a/Microsoft Fortran v331/EXEMOD.EXE b/Microsoft Fortran v331/EXEMOD.EXE new file mode 100644 index 0000000..36c9445 Binary files /dev/null and b/Microsoft Fortran v331/EXEMOD.EXE differ diff --git a/Microsoft Fortran v331/EXEPACK.EXE b/Microsoft Fortran v331/EXEPACK.EXE new file mode 100644 index 0000000..2261ab8 Binary files /dev/null and b/Microsoft Fortran v331/EXEPACK.EXE differ diff --git a/Microsoft Fortran v331/FOR1.EXE b/Microsoft Fortran v331/FOR1.EXE new file mode 100644 index 0000000..776769a Binary files /dev/null and b/Microsoft Fortran v331/FOR1.EXE differ diff --git a/Microsoft Fortran v331/FOREXEC.INC b/Microsoft Fortran v331/FOREXEC.INC new file mode 100644 index 0000000..b9bc9db --- /dev/null +++ b/Microsoft Fortran v331/FOREXEC.INC @@ -0,0 +1,113 @@ +c FOREXEC.INC - interface file for C library routines + +c This include file along with the CEXEC.LIB library has been included +c with your FORTRAN 3.30 to show you how easy it is to call routines +c written in our new C 3.00 release. The CEXEC.LIB contains several +c routines from the C library which we think you will find useful in +c extending the power of your FORTRAN programs. +c +c The new Microsoft FORTRAN 3.30, PASCAL 3.30, and C 3.00 releases +c have been designed so that libraries or subprograms can be written +c in any one of these languages and used in any other. +c +c Try compiling and running the demonstration program DEMOEXEC.FOR +c to see some actual examples. + +c C function +c +c int system(string) +c char *string; +c +c The system() function passes the given C string (00hex terminated) +c to the DOS command interpreter (COMMAND.COM), which interprets and +c executes the string as an MS-DOS command. This allows MS-DOS commands +c (i.e., DIR or DEL), batch files, and programs to be executed. +c +c Example usage in FORTRAN +c +c integer*2 system (the return type must be declared) +c ... +c i = system('dir *.for'c) (notice the C literal string '...'c) +c +c The interface to system is given below. The [c] attribute is given +c after the function name. The argument string has the attribute +c [reference] to indicate that the argument is passed by reference. +c Normally, arguments are passed to C procedures by value. + + interface to integer*2 function system [c] + + (string[reference]) + character*1 string + end + + +c C function +c +c int spawnlp(mode,path,arg0,arg1,...,argn) +c int mode; /* spawn mode */ +c char *path; /* pathname of program to execute */ +c char *arg0; /* should be the same as path */ +c char *arg1,...,*argn; /* command line arguments */ +c /* argn must be NULL */ +c +c The spawnlp (to be referenced in FORTRAN as spawn) creates and +c executes a new child process. There must be enough memory to load +c and execute the child process. The mode argument determines which +c form of spawn is executed as follows: +c +c Value Action +c +c 0 Suspend parent program and execute the child program. +c When the child program terminates, the parent program +c resumes execution. The return value from spawn is -1 +c if an error has occured or if the child process has +c run, the return value is the child processes return +c code. +c +c 2 Overlay parent program with the child program. The +c child program is now the running process and the +c parent process is terminated. spawn only returns +c a value if there has been a recoverable error. Some +c errors can not be recovered from and execution will +c terminate by safely returning to DOS. This might +c happen if there is not enough memory to run the new +c process. +c +c The path argument specifies the file to be executed as the child +c process. The path can specify a full path name (from the root +c directory \), a partial path name (from the current working directory), +c or just a file name. If the path argument does not have a filename +c extension or end with a period (.), the spawn call first appends +c the extension ".COM" and searches for the file; if unsuccessful, the +c extension ".EXE" is tried. The spawn routine will also search for +c the file in any of the directories specified in the PATH environment +c variable (using the same procedure as above). +c +c Example usage in FORTRAN +c +c integer*2 spawn (the return type must be declared) +c ... +c i = spawn(0, loc('exemod'c), loc('exemod'c), +c + loc('demoexec.exe'c), int4(0)) (execute as a child) +c +c The interface to spawnlp is given below. The [c] attribute is given +c after the function name. The [varying] attribute indicates that a +c variable number of arguments may be given to the function. The +c [alias] attribute has to be used because the C name for the function +c spawnlp has 7 characters. Names in FORTRAN are only significant to +c 6 characters, so we 'alias' the FORTRAN name spawn to the actual C +c name spawnlp. Notice in the example above the C strings are passed +c differently from the system function. This is because the string +c arguments to spawn are undeclared in the interface below and assumed +c to be passed by value. The C spawnlp function is expecting the +c addresses of the strings (not the actual characters), so we use the +c LOC() function to pass the address (remember that functions with the +c [c] attribute pass arguments by value). The last parameter to the +c spawn routine must be a C NULL pointer which is a 32-bit integer 0, +c so we use the INT4(0) function to pass this number by value as the +c last parameter. + + interface to integer*2 function spawn + + [c,varying,alias:'spawnlp'] + + (mode) + integer*2 mode + end diff --git a/Microsoft Fortran v331/GS.EXE b/Microsoft Fortran v331/GS.EXE new file mode 100644 index 0000000..d88179a Binary files /dev/null and b/Microsoft Fortran v331/GS.EXE differ diff --git a/Microsoft Fortran v331/INS.EXE b/Microsoft Fortran v331/INS.EXE new file mode 100644 index 0000000..5b6345a Binary files /dev/null and b/Microsoft Fortran v331/INS.EXE differ diff --git a/Microsoft Fortran v331/LIB.EXE b/Microsoft Fortran v331/LIB.EXE new file mode 100644 index 0000000..d2cd188 Binary files /dev/null and b/Microsoft Fortran v331/LIB.EXE differ diff --git a/Microsoft Fortran v331/LIBS/8087.LIB b/Microsoft Fortran v331/LIBS/8087.LIB new file mode 100644 index 0000000..0fed01c Binary files /dev/null and b/Microsoft Fortran v331/LIBS/8087.LIB differ diff --git a/Microsoft Fortran v331/LIBS/ALTMATH.LIB b/Microsoft Fortran v331/LIBS/ALTMATH.LIB new file mode 100644 index 0000000..c2dc982 Binary files /dev/null and b/Microsoft Fortran v331/LIBS/ALTMATH.LIB differ diff --git a/Microsoft Fortran v331/LIBS/CEXEC.LIB b/Microsoft Fortran v331/LIBS/CEXEC.LIB new file mode 100644 index 0000000..f8abb8a Binary files /dev/null and b/Microsoft Fortran v331/LIBS/CEXEC.LIB differ diff --git a/Microsoft Fortran v331/LIBS/DECMATH.LIB b/Microsoft Fortran v331/LIBS/DECMATH.LIB new file mode 100644 index 0000000..83f973e Binary files /dev/null and b/Microsoft Fortran v331/LIBS/DECMATH.LIB differ diff --git a/Microsoft Fortran v331/LIBS/FORTRAN.LIB b/Microsoft Fortran v331/LIBS/FORTRAN.LIB new file mode 100644 index 0000000..200a333 Binary files /dev/null and b/Microsoft Fortran v331/LIBS/FORTRAN.LIB differ diff --git a/Microsoft Fortran v331/LIBS/GRAPHICS.LIB b/Microsoft Fortran v331/LIBS/GRAPHICS.LIB new file mode 100644 index 0000000..967a74f Binary files /dev/null and b/Microsoft Fortran v331/LIBS/GRAPHICS.LIB differ diff --git a/Microsoft Fortran v331/LIBS/MATH.LIB b/Microsoft Fortran v331/LIBS/MATH.LIB new file mode 100644 index 0000000..3bb018d Binary files /dev/null and b/Microsoft Fortran v331/LIBS/MATH.LIB differ diff --git a/Microsoft Fortran v331/LIBS/SUPPORT.LIB b/Microsoft Fortran v331/LIBS/SUPPORT.LIB new file mode 100644 index 0000000..ae97187 Binary files /dev/null and b/Microsoft Fortran v331/LIBS/SUPPORT.LIB differ diff --git a/Microsoft Fortran v331/LINK.EXE b/Microsoft Fortran v331/LINK.EXE new file mode 100644 index 0000000..9695288 Binary files /dev/null and b/Microsoft Fortran v331/LINK.EXE differ diff --git a/Microsoft Fortran v331/PAS2.EXE b/Microsoft Fortran v331/PAS2.EXE new file mode 100644 index 0000000..3ca13fc Binary files /dev/null and b/Microsoft Fortran v331/PAS2.EXE differ diff --git a/Microsoft Fortran v331/PAS3.EXE b/Microsoft Fortran v331/PAS3.EXE new file mode 100644 index 0000000..52f104f Binary files /dev/null and b/Microsoft Fortran v331/PAS3.EXE differ diff --git a/Microsoft Fortran v331/README.DOC b/Microsoft Fortran v331/README.DOC new file mode 100644 index 0000000..c56128b --- /dev/null +++ b/Microsoft Fortran v331/README.DOC @@ -0,0 +1,537 @@ + FORTRAN v 3.31 - README File + 8/30/85 + +This document presents product information that supercedes +or is not covered in the regular documentation. In +particular, this document covers product changes and +enhancements made immediately prior to release. It is +recommended that the user review the document immediately. + + +------------------------------------------------------------ +Differences between version 3.31 and version 3.30 +------------------------------------------------------------ + +A. Stack size of the compiler has been increased. By using + the included EXEMOD utility, you can specify the amount of + stack space to be available during compilation. If you + specify a bigger stack, you can compile larger programs, + but you will need more memory for the compiler to run. + + The compiler comes initially configured with a 40K stack. + + If the compiler does not run on your machine, because of + limited memory, you may wish to change the stack size to + some smaller amount. For many programs, a stack size of + 10K proves to be ample. You can use EXEMOD to decrease + the stack size. + + If the compiler fails with an "out of memory" error, the + stack is too small for the program you are attempting to + compile. You can use EXEMOD to increase the stack size. + + +B. A non-character expression can no longer be assigned to a + character variable. The following is no longer permitted: + + REAL R + CHARACTER*5 C + C = R + 1.0 + + Direct assignments (not involving expressions) are permit- + ted: + + REAL R + CHARACTER*5 C + C = R + + +C. The linker has been changed so that if it is directed to + combine code segments into a physical segment whose size + is within 36 bytes of the 64K limit, it will issue a warn- + ing message: "Segment longer than reliable size." This is + to protect against a bug in the Intel 80286 processor. + However, the message is only a warning. The executible + file will still be created. An attempt to build any seg- + ment, code or data, longer than 64K will still result in a + fatal error. + + +------------------------------------------------------------ +Differences between version 3.30 and version 3.20 +------------------------------------------------------------ + +A. The following sections have been modified or added to the + Microsoft FORTRAN User's Guide. + + Update: Microsoft FORTRAN 3.3 + + Appendix A - Differences Between Versions 3.2 and 3.3 + + Appendix G - Mixed-Language Programming + + Appendix H - Error Messages + + Microsoft LIB - Library Manager Reference Manual + + +B. The following files are provided with the FORTRAN v 3.3 + release, but are not completely documented in the User's + Guide. Whatever (additional) information is required to + use these files is provided in this document. + + EXEPACK.EXE - Utility for packing .EXE files in order to + reduce their size and allow faster loading (refer to + subsection A.10 of the Microsoft FORTRAN User's Guide). + + EXEMOD.EXE - Utility for viewing and modifying certain + header information in .EXE files (refer to subsection + A.10 of the Microsoft FORTRAN User's Guide). + + CEXEC.LIB - Portion of Microsoft C library providing + routines to support the use of the MS-DOS 'exec' + function (function call 4B hex). + + FOREXEC.INC - Interface declarations and documentation + for routines in CEXEC.LIB + + DEMOEXEC.FOR - Example program demonstrating how to use + the routines provided in CEXEC.LIB. + + EMOEM.ASM - Customization for the 8087. + + DATTIM.FOR - Example demonstrating how to access the MS- + DOS date and time. + + Please refer to the update notice at the beginning of the + User's Guide for a complete list of the files which have + been added to the FORTRAN v 3.3 release. + + +C. If your machine has an 8087 or an 80287, you should read + this closely to see if this pertains to your hardware + configuration. All Microsoft languages which support the + 8087 need to intercept 8087 exceptions in order to + properly detect error conditions and provide reliable + accurate results. The math libraries which contain the + 8087 exception handler and emulator (MATH.LIB and + 8087.LIB) are designed to work without modification with + the following machines: + + IBM PC family and compatibles, Wang PC + (any machine which uses NMI for 8087 exceptions) + Texas Instruments Professional Computer + + There is a source file EMOEM.ASM included with the release + that can be modified. Any machine which sends the 8087 + exception to an 8259 Priority Interrupt Controller (master + or master/slave) should be easily supported by a simple + table change to the EMOEM.ASM module. In the file there + are further instructions on how to modify the file and + patch libraries and executables. + + If your computer is not listed, and you need to modify the + EMOEM.ASM program, please contact your hardware + manufacturer for the specific information on the 8087 and + what needs to be modified. If your hardware manufacturer + is not aware of the changes that need to be made they + should contact the Microsoft OEM Group. + + Microsoft Retail Product Support is not equipped to help + out in the customization of the EMOEM.ASM program. + + +D. The library file, CEXEC.LIB, contains the following + routines extracted from the Microsoft C compiler library + (Version 3.0). + + system - Invokes COMMAND.COM with a user-specified command + line. + + spawn - Loads and executes a specified .COM or .EXE file + (i.e., executes a child process). + + The file FOREXEC.INC contains INTERFACE declarations + allowing these routines to be called from FORTRAN and + extensive comments explaining how to use them. + + The file DEMOEXEC.FOR contains an example program + demonstrating the use of these routines. + + +E. This section notes corrections to the documentation. + + 1. Microsoft FORTRAN User's Guide, page 144 (Appendix A - + Differences Versions 3.2 and 3.3): + + The example program needs two additional lines to be + complete, as is shown below. + + CHARACTER A*12, B*20, C*32 + A='Now is the t' + B='ime for all good men' + C(1:12) = A + C(13:12+20) = B + write (*,*) 'C=',C + end + + This will yield the output: + + C=Now is the time for all good men + + + 2. Microsoft FORTRAN User's Guide, page 143 (Appendix A - + Differences Between Versions 3.2 and 3.3): + + In the character substrings description, the syntax for + arrays is shown as: + + array (sub1, [,sub2])([first]:[last]) + + It should be: + + array (sub1 [,sub2])([first]:[last]) + + the comma after "sub1" is incorrect, and should be + deleted. + + 3. Microsoft FORTRAN User's Guide, page 155 (Appendix A - + Differences Between Versions 3.2 and 3.3): + + The first paragraph starts out: + + "The memory allocation is pre-set to 6144 (6K) bytes." + + This paragraph is actually referring to the stack size + and the 6K is incorrect. To verify the actual stack size + for the compiler passes, use the EXEMOD utility to + display the header fields of FOR1.EXE and PAS2.EXE. + + 4. Microsoft FORTRAN User's Guide - page 161 (Appendix A - + Differences Between Versions 3.2 and 3.3): + + The segment contents for a FORTRAN program in memory are + listed below (from the highest memory location to the + lowest). + + Heap - The "heap" is the area of the default data + segment (DGROUP) that is available for dynamic + allocation by the runtime support routines (e.g., for + file buffers). It does not belong to a named segment and + will not show up on a link map. + + STACK - The STACK segment contains the user's stack, + which is used for function/subroutine calls and for + local, temporary variable storage in certain runtime + support routines. + + _BSS - The _BSS segment contains all UNINITIALIZED + STATIC DATA (i.e., all uninitialized FORTRAN variables). + + EEND, EDATA - Defined and used by the runtime library. + + CONST - The CONST segment contains all CONSTANTS. + + P3CE, P3C, P3CB, P2CE, P2C, P2CB, P1CE, P1C, P1CB, P3IE, + P3I, P3IB, P2IE, P2I, P2IB, P1IE, P1I, P1IB, XCE, XC, + XCB, XIE, XI, XIB - Defined and used by the runtime + library. + + COMADS - Holds information needed to reference COMMON + blocks. + + _DATA - The DATA segment is the default data segment. + All INITIALIZED GLOBAL AND STATIC data (i.e., all + initialized variables in FORTRAN) reside in this + segment. + + NULL - The NULL segment is a special purpose segment + that occurs at the beginning of DGROUP. The NULL segment + contains the compiler copyright notice. This segment is + checked before and after the program executes. If the + contents of the NULL segment change in the course of + program execution, it means that the program has written + to this area. This will normally not occur in FORTRAN + but may arise if, for example, a C function is called + that uses an uninitialized pointer. The error message + "Null pointer assignment" is displayed to notify the + user. + + __FBSS - Not used. Part of C runtime support. + + Segments for COMMON and LARGE variables - Segments + allocated for COMMON blocks or LARGE variables will + normally occur here. However, this dependent on the link + order and they may occur above __FBSS if the + corresponding declarations do not occur in the first + .OBJ file in the link sequence. + + C_ETEXT - The C_ETEXT segment marks the end of the code + segments. It contains no data and is therefore a segment + of zero length. + + Code segments (listed as "module" in the illustration + on page 161) - Each module is allocated its own code + segment (also called a text segment). Code segments are + not combined, so there are multiple code segments. + However, all code segments have class CODE. + + When implementing an assembly language routine to call + or be called from a FORTRAN program, you will probably + refer to the code and _DATA segments most frequently. + The code for the assembly language routine should be + placed in a user-defined segment with class CODE. Data + should be placed in whichever segment is appropriate to + their use, as described above. Usually this is the + default segment _DATA. + + If linking with MS-C (3.0) routines, data segments, + outside of DGROUP, required for the C routines normally + occur between __FBSS and NULL. These segments will have + class name FAR_DATA or FAR_BSS depending on whether they + hold initialized C variables or uninitialized C + variables. + + 5. Microsoft FORTRAN User's Guide - page 164 (Appendix A - + Differences Between 3.2 and 3.3): + + The following instructions in the entry and exit + sequences are NOT required: + + inc bp + dec bp + + The following instructions are included in order to + maintain compatibility with XENIX C, and therefore they + are OPTIONAL: + + extrn __chkstk:far + call __chkstk + + The following instructions are included in order to + maintain compatibility with MS-DOS C modules, and + therefore they are OPTIONAL: + + push di + push si + pop di + pop si + + + 6. Microsoft FORTRAN User's Guide, page 182 (Appendix F - + Exception Handling for 8087 Math): + + It is not permitted to mask the invalid operation bit of + the 8087 control word. + + 7. Microsoft FORTRAN Reference Manual, page 107 + (Statements): + + Coercions from double to single precision are not + permitted in DATA statements. That is, if the variable + or array element in nlist is single precision then, the + corresponding value in clist cannot be double precision. + + 8. Microsoft FORTRAN Reference Manual, page 107 + (Statements): + + SEQUENTIAL=logical-sequential + DIRECT=logical-direct + FORMATTED=logical-formatted + UNFORMATTED=logical-unformatted + + The stand-in variable names (logical-sequential etc) + should be changed to some other form such as + SEQUENTIAL=seqvar because these qualifiers yield + CHARACTER values, not LOGICAL ones. + + 9. Microsoft FORTRAN Reference Manual, page 186 + (Metacommands): + + The correct syntax for the $LARGE metacommand is as + follows. + + $[NOT]LARGE[: name[, name]....] + + Note that if the metacommand is given with arguments, + the colon (":") is required. + + +F. This section documents product features which are not + described in the User's Guide or Reference Manual. + + 1. Both the FORTRAN compiler and the runtime library + associate the name "ERR" with the MS-DOS standard error + device handle (generally abbreviated as stderr). Recall + that stderr is mapped to the physical console and, + unlike stdin and stdout, is not redirectable. Thus, the + command syntax: + + FOR1 ERR; + + will cause the FORTRAN compiler to expect source code + from the keyboard rather than a file named err.for. + Similarly, the command syntax: + + FOR1 TEST,,ERR; + + will cause the source listing output to written to the + console screen rather than a file named ERR.LST. + Finally, note that any OPEN statement, specifying "FILE + = 'ERR'", attaches the associated unit number to stderr, + hence to the physical console. + + 2. Both the compiler and the runtime use the Xenix + compatible I/O system in MS-DOS 2.xx/3.xx (MS-DOS 1.xx + is no longer supported). Thus, both the compiler and the + user's program will access files in other directories if + the proper pathnames are specified. + + Since MS-DOS has a limit on the number of 'handles' that + may be simultaneously open for I/O, the user may + occasionally encounter an error 1034 ("too many open + files"). This may happen during execution of FOR1.EXE, + if there are nested include files. It may also occur at + runtime if the user tries to have too many files open at + the same time. In most cases, the problem is easily + circumvented using the "FILES = " statement in + the CONFIG.SYS file (see your MS-DOS manual for + details). However, there is a fixed upper limit in MS- + DOS of 20 handles (five preassigned plus 15 others) that + any single program may have open simultaneously. + + 3. There have been several recent changes to the behavior + and capabilities of the EXEMOD and EXEPACK utilities + provided on this release which are not covered in the + printed manuals. + + EXEPACK attempts to prevent you from compressing a file + onto itself. It is not infallible - it can be fooled by + a statement of the form: + + EXEPACK TEST.EXE .\TEST.EXE + + If it detects an attempt to compress a file onto itself + it will issue the message: + + exepack: cannot pack file onto itself + + and exit with return code 1. Also, when using EXEPACK + to compress an .EXE file with overlays, the compressed + file should be renamed back to the original name of the + linked file to avoid the overlay manager prompt (see + Overlays in the User Guide). + + EXEMOD has an undocumented switch, /h, which can be seen + in the usage prompt (it is not shown in the Users Guide + description of the usage prompt). This option CANNOT be + used with any of the other options, and it is equivalent + to typing: + + EXEMOD PROG.EXE + + That is, it simply displays the header fields of the + .EXE file without modifying them. + + EXEMOD has also been modified to work correctly on + packed (via EXEPACK) files. When it recognizes a packed + file, it will print the message: + + exemod: (warning) packed file + + If the stack value is changed, it modifies the value + that SP will have AFTER expansion. If either min or + stack is set, min will be corrected as necessary to + accomodate unpacking or stack. Setting max operates as + it would for unpacked files. + + If the header of a packed file is displayed, the CS:IP + and SS:SP values are displayed as they will be after + expansion, which is not the same as the actual values in + the header. + + The compiler executable files (FOR1, PAS2, and PAS3) are + not packed on the distribution diskettes. We recommend + that when you set up your own diskettes (as recommended + in the manual or otherwise), you run EXEPACK on all the + compiler executable files. You'll notice that the + savings is not great on most of them. + + Note: Refer to the MS-DOS Programmer's Reference manual + for further information on .EXE file headers. + + 4. Controlling the Stack Size - the /STACK Linker option: + + /STACK:number + + The /STACK option allows you to specify the size of the + stack for your program. The number is any positive + value (decimal, octal, or hexadecimal) up to 65,536 + (decimal). It represents the size, in bytes, of the + stack. + + Note: The EXEMOD utility, can also be used to change the + default stack size. + + +G. The following public variables, defined in ENTX6L.ASM in + earlier versions of MS-FORTRAN, no longer exist in version + 3.3. + + BEGHQQ + BEGMQQ + CURHQQ + ENDHQQ + ENDMQQ + MAXMQQ + + The following public variables, defined in ENTX6L.ASM in + earlier versions of MS-FORTRAN, still exist in version + 3.30. Note, however, that only CESXQQ, CRCXQQ, CRDXQQ and + DOSEQQ are intended for direct access by the user. + + CESXQQ - DOS saved ES value (for command line) + CLNEQQ - last line number encountered + CRCXQQ - value of CX for DOS call + CRDXQQ - value of DX for DOS call + CSXEQQ - pointer to sourcef context list + DGRMQQ - segment of DGROUP + DOSEQQ - DOS return code + HDRFQQ - Unit F open file list header + HDRVQQ - Unit V open file list header + PNUXQQ - pointer to unit initialization list + RECEQQ - machine error context, program segment + REFEQQ - machine error context, frame ptr + REPEQQ - machine error context, program offset + RESEQQ - machine error context, stack ptr + STKBQQ - stack start, to fix long GOTO + STKHQQ - stack limit, to check overflow + UPCX87 - offset address of 8087 error context + + +H. When reporting a suspected problem with the compiler to + the Retail Product Support Group, we ask that you please + provide the following information to help us in tracking + down the problem. + + 1. The smallest possible example which can be used to + demonstrate the alleged problem (the example should be + provided in source code, on a standard 5 1/4" MS-DOS + disk or a hard copy listing if it is very short). + + 2. A complete description of the symptoms of the problem + including complete directions on reproducing these + effects with the supplied example (compilation options + used, libraries linked with,...,etc.). + + 3. The compiler version number (from the logo that is + printed out when you run FOR1). + + 4. Your system configuration, both hardware (machine, + total memory, coprocessor,...,etc.) and software + (version of DOS, terminate-and-stay-resident utilities + or unusual system software, free memory as indicated by + chkdsk,...,etc.). + + Having this information will be of immense help to us in + our effort to diagnose and solve your problem. diff --git a/Microsoft Fortran v331/SIEVE.FOR b/Microsoft Fortran v331/SIEVE.FOR new file mode 100644 index 0000000..8a13ffa --- /dev/null +++ b/Microsoft Fortran v331/SIEVE.FOR @@ -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 diff --git a/Microsoft Fortran v331/TPHI.FOR b/Microsoft Fortran v331/TPHI.FOR new file mode 100644 index 0000000..5d54c34 --- /dev/null +++ b/Microsoft Fortran v331/TPHI.FOR @@ -0,0 +1,29 @@ +C should tend towards 1.61803398874989484820458683436563811772030 + program phi + real*8 d, d1, d2 + integer*4 prev2, prev1, next + integer i + + write( *, 1005 ) + prev2 = 1 + prev1 = 1 + + do 10 i = 1, 40, 1 + next = prev1 + prev2 + prev2 = prev1 + prev1 = next + + d2 = prev2 + d1 = prev1 + d = d1 / d2 + + write( *, 1000 ) i, d +10 continue + + write( *, 1003 ) +1000 format( 5X, 'iteration ', I4, ' r8: ', F18.16 ) +1003 format( ' complete' ) +1005 format( ' should tend towards 1.61803398874989484820458683436563 + c811772030' ) + end + diff --git a/Microsoft Fortran v331/TTT.FOR b/Microsoft Fortran v331/TTT.FOR new file mode 100644 index 0000000..8d60082 --- /dev/null +++ b/Microsoft Fortran v331/TTT.FOR @@ -0,0 +1,214 @@ +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 + +$include : 'forexec.inc' + + 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 + + l = system('tm'c) + moves = 0 + + do 10 l = 1, 100, 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 + + l = system('tm'c) + 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 + + diff --git a/Microsoft Fortran v331/m.bat b/Microsoft Fortran v331/m.bat new file mode 100644 index 0000000..09be13e --- /dev/null +++ b/Microsoft Fortran v331/m.bat @@ -0,0 +1,14 @@ +del %1.rel 1>nul 2>nul +del %1.com 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:. -e:LIB=libs -f link %1,%1,%1,fortran.lib+cexec.lib + +:eof +