background image

Summary of Contents for XDS 5

Page 1: ...Scientific Data Systems A XEROX COMPANY X1ClS SIGMA 5 7 FLAG Reference Manual...

Page 2: ...E MANUAL for XDS SIGMA 5 7 COMPUTERS PRELIMINARY EDITION 90 16 54A September 1969 Price 4 00 Xerox Data Systems 701 South Aviation Boulevard EI Segundo California 90245 1969 Xerox Data Systems Inc Pri...

Page 3: ...st of the function sub programs that are available to FORTRAN IV users These subprograms are listed in Table 9 Intrinsic and Basic External Functions taken from the previously mentioned FORTRAN IV Ref...

Page 4: ...sions 13 Logical Expressions 14 Logical Operators 14 Evaluation Hierarchy 15 Specification Record Separator 51 Parenthesized FORMAT Specifications 52 Adjustable FORMAT Specifications 53 Numeric Input...

Page 5: ...RAMS 80 Processing Mode 97 Main Programs 80 Subprograms 80 Statement Functions 80 FUNCTION Subprograms 81 SUBROUTINE Subprograms 82 TABLES Arguments and Dummies 83 Dummy Scalars 84 l Sample Program 3...

Page 6: ...eference to standard FORTRAN compilers when the user is in the debugging phase of devel oping his program Further it should be the primary FORTRAN compiler system in the typical university environ men...

Page 7: ...L M N 0 P Q R STU V W X Y Z Digits 0123456789 Special characters useful t I blank Special characters II other This character set conforms to the Extended Binary Coded Decimal Interchange Code EBCDIC s...

Page 8: ...tement assigns to FACTOR the value of the current value of FACTOR minus 1 When the GO TO statement is executed an unconditional transfer of control to statement 10 I ine 6 occurs Statement 12 an assig...

Page 9: ...are treated as comments only These statements remain in the listing however and may serve as documentation or checkout procedures Also they may easily be reinstated at any time Continuation lines for...

Page 10: ...nt digit will be accurate while the seventh will sometimes beaccu rate depending on the value assigned to the datum Double precision data may approximate the identical set of values as real data Howev...

Page 11: ...ny real constant may be written in a variety of ways the user has freedom of choice regarding form Examples 5 0 0 01 7 6E 5 6 62E 37 3 141592265358979323846 58785504 Double Precision Constants Double...

Page 12: ...ed the value limits established for double precision data Logical Constants Logical constants may assume either of the two forms TRUE FALSE where these forms have the logical values true and false res...

Page 13: ...bles whose identifiers begin with any other letter are classified as real variables These classifications are referred to as the IIUKLMN rule Consequently double precision complex double complex and l...

Page 14: ...func tion reference constitutes a reference to the value produced by the function when operating on the given argument A function reference is denoted by the identifier that names the function follow...

Page 15: ...ult Arithmetic Expressions An arithmetic expression is a sequence of integer real double preCISion complex and or double complex con stant variabl e or function references connected by arithmetic oper...

Page 16: ...Order Exponentiation 1 highest Multiplication and Division 2 Additi on and Subtracti on 3 Some additional conventions are necessary 1 At anyone level of evaluation operations of the same order of prec...

Page 17: ...x Complex It can be seen that a hierarchy of type and length specifications exists The order of precedence is Type Doubie Compiex Complex or Double Precision Real Integer Precedence 1 highest 2 3 4 DO...

Page 18: ...Relational operators cause comparisons between arithmetic expressions Operator IT LE EQ NE GE GT Examples l LT 6 O GT 8 Meaning less than Less than or equal to Equal to Not equal to I Greater than or...

Page 19: ...sed in parentheses 6 any of the above preceded by the unary logical operator NOT Logical Operators There are three logical operators Operator Type NOT unary AND binary OR binary Table 4 illustrates th...

Page 20: ...is interpreted as L OR NOT M AND X GE Y Note It is permissible to have two contiguous logical operators only when the second operator is NOT i in other words e 1 AND OR e 2 is not valid while e 1 AND...

Page 21: ...riable Then if permissible it is con verted to the type of the variable according to Table 5 and assigned to the variable Table 5 Mixed Variable Types and Expression Modes Expression Mode Variable I T...

Page 22: ...tion of the expression The imaginary part of the variabl e is set to zero The real part of the variable is assigned the double precision approximation of the expression The imaginary part of the varia...

Page 23: ...ir numerical values have no effect on the sequence of statement compilation or execution GO TO Statements GO TO statements transfer control from one point in a program to another FLAG includes three f...

Page 24: ...the k control will be transferred I This statement causes control to be transferred to the statement whose label is kj where j is the integer val ue of the variable v for 1 j n If j is not between 1 a...

Page 25: ...ents are used for this purpose There are two forms of IF statements arithmetic and logical Arithmetic IF Statement The format for arithmetic IF statements is where e is an expression of integer real o...

Page 26: ...nts and Dummies Chapter 8 i I A subroutine is similar to a function except that it does not necessarily return a value and must not therefore be used in an expression Furthermore while a function must...

Page 27: ...s used to determine which statement label in the calling argument list will be used as the return The vth asterisk counting from left to right in the SUBROUTINE statement corresponds to the statement...

Page 28: ...ation differently The terminal statement of a DO range i e the statement whose label is k may be any executable statement other than one of the following DO statement GO TO statement Arithmetic IF sta...

Page 29: ...they cannot be overlapped In a nest of DO loops the same statement may be used as the terminal statement for any number of DO ranges however trans fers to this statement can be made only from the inne...

Page 30: ...stant This statement causes the program to cease execution temporarily presumably for the purpose of allowing the com puter operator to perform some specified action The operator can then signal the p...

Page 31: ...that the statement is an END statement and will act accordingly An END statement may not appear on a continuation line This limitation is due to an historic FORTRAN feature namely the way in which con...

Page 32: ...m similar to internal storage For either type of transmission the I O statements refer to external devices lists of data names and for formatted data to format specification statements Input Output li...

Page 33: ...an input list I J A I I 1 J 2 I J A I I 1 J 2 As an output list I J A I 1 l J 2 is not allowed is allowed is allowed 5 The number of items in a single list is limited only by the statement length spe...

Page 34: ...than one record may be processed by these statements if specifically requested by the FORMAT statement However attempting to read or write more characters on a record than are or can be physically pre...

Page 35: ...es which are then assigned to the variables appearing in the list k or the equivalent simple list if k contains a DO implication PUNCH Statement This FORTRAN II output statement has the form PUNCH f k...

Page 36: ...d operations manuals for a description of the format of intermediate binary information This means that the information output by a single binary WRITE state ment must be input by one and only one REA...

Page 37: ...y variable without knowing at compile time which variables it will be desirable to input The NAME LIST variables defined in a program unit are independent of those defined in any other program units E...

Page 38: ...Y 2 1 30000 Complex values are output as complex constants the other data types are also output in natural forms as shown in the following example DOUBLE PRECISION D COMPLEX C LOGICAL L OUTPUT 6 I R...

Page 39: ...list item may consist of a single asterisk which will cause the characters END to be out put on a record This wiii cause an iNPUT statement to terminate reading For exampie OUTPUT 4 X I J AA The actua...

Page 40: ...ner as described for explicit input output lists see IIInput Output Listsll In this case a is an array name c is a constant of an appropriate type and J m is equal to the number of elements in the arr...

Page 41: ...any character string that can be processed by a widthless format that is one in which the letter Tor F appears Such a field is terminated by the first comma or nonleading blank Thus T F TRUE and FALS...

Page 42: ...should be labeled so that references may be made to it by formatted input output state ments An entire FORMAT the parentheses and the items they enc lose may be stored in an array variable through the...

Page 43: ...on values are converted with full precision if sufficient width is specified by w and the value of d a lIows for the appropriate number of digits in the fractiona I portion of the field Output Interna...

Page 44: ...ecified by wand the value of d allows for the appropriate number of digits in the fractiona I portion of the fie Id Output Internal values are converted to real constants of the forms ddd dE ee ddd dE...

Page 45: ...ents specified Examples Input Value Specification Converted to 113409E2 E9 6 11 340900 409385E 03 E 2 4 09385 849935E 02 E10 5 0849935 6851 E O 6851 0 First the decimal point is positioned according t...

Page 46: ...be used instead the number will be normalized and output with a fol lowing exponent To express this algebraically let M represent the magnitude of the value to be output rounded to d significant dig...

Page 47: ...to integer values however the integers may contain as many digits as are specified by w Negative values are preceded by a minus sign and the field wi II be right justified and preceded by the appropr...

Page 48: ...he first non blank character is a comma it terminates the field if it is not a comma the next blank or comma wi II terminate the field The first T or F encountered within the field determines the alue...

Page 49: ...characters For example if the list item is integer and the specification A10 is used ABCDEFGHIJ is converted to GHIJ However when the value of w is less than the number of characters associated with t...

Page 50: ...nks For example list Item Data Type integer real or logical double precision where Externa I String XYINT 85DOUBLE 2 w 4 6 2 none 8 6 10 none 1 represents the Hollerith character blank and z represent...

Page 51: ...ry i e when its magnitude is greater than the number of digits asso ciated with the data type of the corresponding Iist item the Iist item is fi II ed with the rightmost characters in the fi eld When...

Page 52: ...String Resultant Specification 3H123 ABC 3HABC 1OHNOWf IS bTHE 1 TIMEf FOR1 lOHf TlMEf FORf 5HTRUEf FALSE 5HFALSE 6H b1 f f f f RANDOM 6HRANDOM where1S represents the character blank This feature can...

Page 53: ...ng external string WXYZfr Of IJKL where b represents the character blank _A negative value of i causes processing to beck up in the record The next field vIi then begin Ii I ChOicctCiS to the left ass...

Page 54: ...17 Tl2 17 It can be seen from the above example that it is permissible to tab either forward or backward Furthermore a T specification provides a capability that an X specification does not namely tha...

Page 55: ...PFI0 3 000 000 000 000 2PE14 3 27 183E Ol 27 183E Ol OOOE 00 99 990E 03 1PE14 3 2 718E 00 2 718E 00 OOOE 00 9 999E 02 OPE14 3 272E 01 272E 01 OOOE 00 100E 00 1 PE 14 3 027E 02 027E 02 OOOE 00 010E 01...

Page 56: ...rations The same condition can occur when a slash speci fication and either of the parenthesis characters surrounding the field specifications are contiguous a slash preceding the final right parenthe...

Page 57: ...e effect of slash specifications during input operations is similar to the effect for output except that for input records ary ignored in the cases where blank records are created during output For ex...

Page 58: ...ay be N Also there is no limit to the number of N characters that may be used in a FORMAT statement or to the number of quantities replaced by N in a format specification For example 32 FORMAT NX FNA...

Page 59: ...TRUE or FALSE depending on the value of BOOlE Note that although an N cannot replace the n in an H specification the form shown in statement 17 above can be used 7 The value of N may be supplied by an...

Page 60: ...tion of the value is lost A comma may be used to terminate any numeric field as described below Leading blanks are always ignored The interpretation of embedded and trailing blanks depends on whether...

Page 61: ...ent to a zero Care should always be taken to assure that exponents are right justified in their fields Failure to do this is a common pitfall that can also be avoided by using comma termination and or...

Page 62: ...uests a Iisf item If one or more items remain in the Iist the processor per forms the appropriate conversion and proceeds with the next field specification If conversion is not possible because of a c...

Page 63: ...of multi pie records in these cases is described under Memory to Memory Data Conversion FORMATs Stored in Arrays As mentioned previously a FORMAT including the beginning left parenthesis the final ri...

Page 64: ...ctively In an ENCODE DECODE operation however no actual input output takes place data conversion takes place between an input output list and an internal buffer area This buffer area is specified by t...

Page 65: ...y M K 12 L 5 ENCODE l2 3 M K L 3 FORMAT 2H F I 1H I 1H The FORMAT so created would occupy the first three elements of M and would appear as F 12n 56 niSiS where b represents the character blank DECODE...

Page 66: ...of the BUFFER IN or BUFFER OUT operation at some later point in the program The BUFFER IN and BUFFER OUT subroutines are called in the following fashion CALL BUFFER IN u m s w i n and CALL BUFFER OUT...

Page 67: ...llowing statements could be used to list binary tapes in hexadecimal ten words per line preceded by the record length INTEGER BUFFER 5000 1 CALL BUFFER IN 5 1 BUFFER 5000 J N 2 GO TO 2 3 4 3 J 3 M MIN...

Page 68: ...pplicable to them 2 Information is not thought of as being broken into unit records Data is processed exactly as specified with no control words or record boundaries As many locations of the disc or d...

Page 69: ...ake a program that has been written for output on magnetic tape and assign that logi cal unit number to some other device such as a Iine printer Since such programs often write end of fi Ie and re win...

Page 70: ...apply to declared arrays 4 An identifier is a statement function definition if it appears to the left of an equal sign followed by a dummy list enclosed in parentheses It must also comply with the ru...

Page 71: ...s it is placed in storage as a linear string This string contains the array elements in sequence from low address storage toward high address storage such that the leftmost dimension varies with the h...

Page 72: ...L DOUBLE PRECISION DOUBLE COMPLEX c J is a single alphabetic character or two such characters separated by a dash minus sign the second character must follow the first in alphabetic sequence For examp...

Page 73: ...is an array decla ration Optionally a scalar array or array declaration may be followed by a DATA constant list enclosed in slashes for the purpose of defining initial values for the variables In oth...

Page 74: ...owever this option is used to change ieci to double piecision and complex to double complex as shown below Standard Optional Type Size bytes Size bytes Integer 4 Real 4 8 Complex 8 16 Logical 4 Double...

Page 75: ...ments are used to arrange variable storage in special ways as required by the programmer If no storage allocation information is provided the compiler allocates all variables within the program in an...

Page 76: ...LEX G F ll COMMON SET l G F Both references to the COMMON block SET 1 correspond in size That is both subprograms define the block SET1 as containing 24 words the definition in subroutine A specifies...

Page 77: ...rom low address storage toward high address storage The first variable to be declared as being in a particular section is contained in the low address word or words of that section Array variables are...

Page 78: ...thus allow ing a variable of any length to be the first assigned within a block To obtain the correct displacement for other variables in the same block it may be necessary to insert an unused variabl...

Page 79: ...he location of the first element of the array is denoted as position 1 the element immedi ately following is position 2 and so on Thus if X is a 3 x 3 array X l means the same as X l 1 X 3 is two elem...

Page 80: ...ing allocations of COMMON storage that is two variables in the same COMMON block or in different COMMON blocks can not be made equivalent It is permissible for an EQUIVALENCE to cause a segment of the...

Page 81: ...iable or a user supplied subprogram BLOCK DATA Subprograms FLAG permits variables in labeled COMMON to be initialized in a special program called a BLOCK DATA sub program which begins with a statement...

Page 82: ...array must be initial ized each time into the routine using assignment statements such as C O 0 C l 1243549945 C 2 2447786631 etc Here the DATA statement can be used to great advantage It is not recom...

Page 83: ...s 4 characters a complex variable 8 characters and a double complex variable 16 characters Variable items will be initialized as required to use up the characters specified If there are insufficient c...

Page 84: ...prior to the appearance of the first executable statement within a program 2 Declaration statements if present should appear in the following order within a program subprogram declaration statement I...

Page 85: ...programs Subprograms are programs which may be called by other programs they fall into the two broad classes of functions and subroutines t These may be further classified as follows Functions Stateme...

Page 86: ...t type statements The statement function itself is typed like any other identifier it may appear in an explicit type statement if it does not it will acquire implicit type see Implicit Declarations in...

Page 87: ...DO 5 J N 10 M M J 5 GAMMA GAMMA Z J GA V VA M N Z GAMtv A RETURN END SUBROUTINE Subprograms SUBROUTINE subprogramsr like FUNCTION subprogramsr are self contained programmed procedures Unlike FUNCTION...

Page 88: ...tually exist and no stor age is reserved for it it is only a name used to identify an argument in the calling program An argument may be any of the following a scalar variable an array element an arra...

Page 89: ...argument has no type 2 A SUBROUTINE name as opposed to a FUNCTION name has no type All arithmetic or logical expressions appearing as actual arguments in the calling program are first evaluated and t...

Page 90: ...t occupies more than one word per elementt e g double precision may result in dummy elements that are only partially defined For this reason integer arrays are recommended If an array corresponds to s...

Page 91: ...SQRT DSQRT Y DIFF DABS F Z DF DBLE Z RETURN END The programmer must provide the functions SIN DSIN SQRT and DSQRT A subprogram identifier to be passed as an argument must previously appear in an EXTE...

Page 92: ...mum value All arguments are con verted to and compared as real values Maximum value All arguments are con verted to and compared as integer values Minimum value All arguments are con verted to and com...

Page 93: ...x 16 Complex 16 Double complex natural logarithm base e See CLOG CDSIN 1 Complex 16 Complex 16 Double complex sine See CSIN CDSINH 1 Complex 16 Complex 16 Double complex hyperbolic sine See rC rio II...

Page 94: ...nt in radians DATAN2 See ATAN DBLE 1 Real Real 8 Argument converted to a val ue with double precision DCMPLX 2 Real 8 Complex 16 Converts two noncomplex numbers to a double complex number See CMPLX DC...

Page 95: ...s DSIN 1 Real 8 I Real 8 Double precision sine of angle in radians DSINH 1 Real 8 Real 8 Double precision hyperbolic sine DSQRT 1 Real 8 Real 8 Double precision square root positive value DTAN 1 Rea 8...

Page 96: ...of arg with sign of arg2 If arg2 is zero the sign IS positive Arg2 is not converted to integer Integer shift logical Arg1 is shifted left logically the number of bits specified in arg2 If arg 2 is neg...

Page 97: ...lights will be turned Offi if n is 1 2 3 or 4 the corresponding sense light will be turned on OVERFL Floating Overflow Test Form CALL OVERFL s where is an integer variable into which will be stored t...

Page 98: ...clamation mark must be placed in column 1 The FLAG control command is usually begun in column 2 though it may begin in any column after the character The optioni are option codes that control processi...

Page 99: ...untered Then the series will be executed if appropriate This option is mainly intended for use where a main program and subprograms are to be compiled as a unit but have been stored on magnetic tape a...

Page 100: ...ource program listing When attempting to run very large programs it is sometimes a good idea to make the first compilation using the NOGO and M9 options When NOGO is specified no machine in structions...

Page 101: ...the user elects compilation and execution in debug mode see FLAG DB option the FLAG compiler will generate extra instructions in the compiled program so that program errors that cannot be detected du...

Page 102: ...Figure 4 FLAG Job Setup Multiple Programs in Batch Processing Mode FLAG Debug Mode 97...

Page 103: ...E END END FILE EQUIVALENCE EXTERNAL FORMAT FUNCTION GOTO IF IMPLICIT INPUT INTEGER LOGICAL NAMELIST 98 Appendix A APPENDIX A FLAG STATEMENTS Executable NonexecutabIe Page X 19 X 16 X 64 X 76 X 21 X 70...

Page 104: ...cutable Page OUTPUT X 33 PAUSE X 25 PRINT X 30 31 PUNCH X 30 READ X 29 32 READ DISC X 63 REAL X 68 RETURN X 22 REWIND X 64 STOP X 25 SUBROUTINE X 82 Statement Function X 80 Definition WRITE X 29 31 WR...

Page 105: ...UCTION X ddddd ARGUMENT NUMBER ARITH OVRFL ARITHMETIC ASSIGNMENT STATEMENT ARRAYS TOO LARGE ASSIGN MISSPELLED ASSIGNMENT MEMORY SIZE BACKSPACE MISSPELLED BAD HOLLERITH COUNT BAD REPEAT COUNT BLANK CAR...

Page 106: ...RIPT VALUE ILLEGAL TRAP JOB ABORTED ILLEGAL TYPE WITH RELATIONAL ILLEGAL USE OF NOT ILLEGAL USE OF COMMA ILLEGAL USE OF DIMENSIONED VARIABLE ILLOGICAL EXPRESSION IMPLICIT MISPLACED IMPLICIT MISSPELLED...

Page 107: ...MY VARIABLE NAMELIST MISSPELLED NAME PREVIOUSLY USED AS FUNCTION NO DIMENSIONING INFORMATION NO to lAIN PROGRAM NON ALPHABETIC ORDER NON DIMENSIONED VARIABLE HAS SUBSCRIPT NON DUMMY HAS VARIABLE DIMEN...

Page 108: ...D VARIABLE UNIMPLEMENTED SIZE IGNORED UNIMPLEMENTED STATEMENT UNNUMBERED CONTINUE STMNT UNNUMBERED STMNT FOLLOWS RETURN UNNUMBERED STMNT FOLLOWS STOP UNNUMBERED STMNT FOLLOWS TRANSFER UNRECOGNIZABLE S...

Page 109: ...ts 63 27 B BACKSPACE 64 END FILE 64 REWIND 64 BACKSPACE statement 64 62 basic external functions 80 BCD record size 29 blank COMMON 70 71 79 blanks 2 7 8 BLOCK DATA statement 76 80 subprogram 76 79 BU...

Page 110: ...nt 81 array 84 85 86 list 65 scalars 84 subprograms 86 E format 39 41 42 EBCDIC character set 2 ENCODE statement 60 37 59 END and ERR forms of READ statements 32 END FILE statement 64 END statement 26...

Page 111: ...explicit type statement 68 IMPLICIT type declaration 67 type specification 81 4 size specification 69 integer constants 5 78 integer data 5 integer variables 36 intermediate storage 61 internal buffer...

Page 112: ...to array elements 66 relational expression 13 14 relational operators 13 RETURN statement 22 81 82 REWIN D statement 64 s scalar variable 8 scale factor 49 self identified input 35 simplified input ou...

Reviews: