1 <!--===- docs/FortranFeatureHistory.md
3 Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4 See https://llvm.org/LICENSE.txt for license information.
5 SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
9 # A Fortran feature history cheat sheet
17 ## Original IBM 704 FORTRAN
19 Features marked with asterisks `*` were gone by FORTRAN IV.
21 * Fixed form input with comment and continuation cards
22 * INTEGER and REAL types, implicit naming conventions
23 * DIMENSION and EQUIVALENCE statements
24 * Assignment statements
25 * Arithmetic (3-way) IF statement
26 * IF statements for checking exceptions and sense switches, manipulating lights
27 * GO TO, computed GO TO, ASSIGN, and assigned GO TO statements
28 * DO loops: positive expressions, 1 trip minimum
29 * extended DO loop ranges
30 * PAUSE, STOP, and CONTINUE statements
31 * Formatted I/O: FORMAT, READ, WRITE, PRINT, PUNCH
32 and `*` READ INPUT / WRITE OUTPUT TAPE
33 * Unformatted I/O: READ/WRITE `*` TAPE/DRUM
34 * ENDFILE, REWIND, and BACKSPACE statements
35 * FREQUENCY statement (optimization hint - survived into FORTRAN IV)
37 * Intrinsic functions (all names ending in F`*`)
38 * statement functions (names ending in F only`*`)
41 * SUBROUTINE and FUNCTION subprograms
42 * END statement (with five Sense Switch override argument`*`)
43 (Sense Switch 4, if on: "Causes FORTRAN II to produce a program optimized
44 with respect to index registers.")
45 * CALL and RETURN statements
47 * DOUBLE PRECISION and (single) COMPLEX data types
48 * 6-character identifiers
49 * Bitwise assignment statements with 'B' in column 1 (IBM 7090 only)
50 * Double precision with 'D' in column 1 (ditto); complex with 'I'; funcs with 'F'
55 * BLOCK DATA subprograms
56 * LOGICAL type and expressions, logical IF statement
57 * Removal of weird original features (`*` above)
58 * Quoted character strings
60 * EXTERNAL subprograms for use as actual arguments
61 * alternate RETURN, ENTRY
62 * &666 label actual arguments for assigned GO TO alternate return
63 * implicit RETURN at END
66 * max 3 array dimensions; subscripts only like `C*V+K`; lower bounds all 1
67 * adjustable array dummy arguments (dimension of dummy array is dummy argument)
70 * array dimension lower bounds other than 1
71 * IF THEN / ELSE IF THEN / ELSE / END IF construct
72 * DO loops with negative expressions and zero trip counts
73 * OPEN, CLOSE, and INQUIRE statements
75 * IMPLICIT statement (was in FORTRAN IV)
76 * CHARACTER data type (was in FORTRAN IV)
79 * Generic intrinsic names
80 * lexical string comparisons
81 * Obsolescent or deleted features: Hollerith constants and data; H edit descriptors; overindexing;
82 extended range DO loops
83 * (non-standard option) recursion
85 * implicit RETURN at END
87 ## MIL-STD-1753 Fortran (1978)
88 * DO WHILE, DO / END DO
91 * Bit manipulation intrinsics (IAND, IOR, IEOR, ISHFT, ISHFTC, MVBITS, &c.)
94 * ALLOCATABLE attribute/statement, ALLOCATE and DEALLOCATE statements
95 * keyword= actual arguments
96 * Derived TYPEs, PRIVATE, SEQUENCE; structure components
98 * POINTER and TARGET attributes, NULLIFY statement
102 * Array expressions and assignments
104 * RECURSIVE procedures
107 * operator overloading
108 * new declaration syntax with ::
109 * EXIT and CYCLE statements
110 * SELECT CASE construct
111 * Portable kind specifications
112 * INTENT on arguments
113 * Obsolescent features beyond those removed in Fortran 95 below: alternate
114 return, computed GO TO, statement functions, intermixed DATA,
115 `CHARACTER*x` form, assumed-length `CHARACTER*(*)` functions, fixed form source
117 ## Fortran 95 (acquiring some HPF features)
120 * Default initialization of derived type components
121 * initialization of pointers to NULL()
122 * (clarification) automatic DEALLOCATE at end of scope
123 * extended intrinsics, e.g. DIM= arguments
125 * removed features (obsolescent in Fortran 90): floating-point DO index variables,
126 GO TO an END IF from outside, PAUSE statement, ASSIGN statement and
127 assigned GO TO and formats, H edit descriptor
130 * KIND and LEN parameterized derived types (still not widely available with correct implementations)
131 * PROCEDURE pointers and pointer components
133 * type-bound procedures
136 * type-bound generic OPERATOR(+) and ASSIGNMENT(=)
138 * type-bound procedure overriding; NON_OVERRIDABLE attribute to prevent it
139 * ENUM / ENUMERATOR :: / END ENUM
140 * ASSOCIATE / END ASSOCIATE construct
141 * CLASS polymorphic declarator
142 * SELECT TYPE / END SELECT construct, TYPE IS and CLASS IS clauses
143 * Abstract interface allowed on DEFERRED type-bound procedure meant to be overridden
144 * Structure constructors with keyword=
145 * ALLOCATE statement now works on scalars
146 * Assignment to allocatable array with automatic (re)allocation
147 * CALL MOVE_ALLOC(from, to) intrinsic
148 * Finer-grained PUBLIC/PRIVATE
149 * PROTECTED attribute and statement
150 * USE module, OPERATOR(.foo.) => OPERATOR(.bar.)
151 * Lower bounds on pointer assignment; expansion of
152 vector RHS to multidimensional pointer
153 * INTENT allowed on POINTER dummy argument, defined
154 to pertain to the pointer rather than to its target
156 * IMPORT statement in INTERFACEs
157 * ISO_FORTRAN_ENV intrinsic module
158 * Unicode, SELECTED_CHAR_KIND()
159 * 63-char names and 256-line statements
160 * BOZ constants in INT/REAL/CMPLX/DBLE intrinsic calls
161 * [array constant] with optional [type::...] specifier
162 * Named constants in complex constant values
163 * SYSTEM_CLOCK(COUNT_RATE=real type) now allowed
164 * MAX, MAXLOC, MAXVAL, MIN, MINLOC, MINVAL on CHARACTER
165 * Negative zero on ATAN2, LOG, SQRT
166 * IEEE underflow control
167 * Derived type I/O: DT edit, GENERIC READ/WRITE bindings
168 * ASYNCHRONOUS attribute and I/O, WAIT statement
171 * OPEN(ACCESS='STREAM')
172 * OPEN(ROUND=mode), overrides on READ/WRITE; Rx edits
173 * OPEN(DECIMAL=COMMA/POINT), overrides on READ/WRITE; DC and DP edits
175 * KIND= type parameters allowed on specifiers, e.g. NEXTREC=n
176 for cases where n is not default kind of INTEGER
177 * Recursive I/O (also mentioned in Fortran 2008)
179 * I/O of IEEE-754 negative zero, infinities and NaNs
180 * Fortran 66-style optional comma in 2P[,]2E12.4 edit descriptor
181 * Interoperability with C
184 * SUBMODULE, MODULE PROCEDURE
185 * Coarray references and image control statements
186 * DO CONCURRENT as a non-parallel construct
187 * CONTIGUOUS attribute and statement, IS_CONTIGUOUS() intrinsic
188 * Simply contiguous arrays
189 * Maximum rank now 15
190 * 64-bit INTEGER required as SELECTED_INT_KIND(18)
191 * ALLOCATABLE members with recursive types
192 * Implied-shape array declarations, e.g. `INTEGER :: x(0:*) = [0, 1, 2]`
193 * Pointer association initialization in declaration with => to SAVE target
194 * Generalization of expressions allowed in DATA statement subscripts
195 and implied DO subexpressions
196 * FORALL(INTEGER(kind) :: ...) kind specification
197 * Intrinsic types in TYPE statements, e.g. TYPE(INTEGER)
198 * Multiple type-bound procedures on one PROCEDURE statement
199 * Structure constructors can omit ALLOCATABLE components
200 * ALLOCATE(arr, SOURCE=x or MOLD=x) sets shape without needing
201 explicit bounds on arr
202 * ALLOCATE(polymorphic, MOLD=x) sets type
204 * POINTER-valued functions as variables suitable for LHS of =, &c.
207 * `(*(...))` format item unlimited repetition
210 * EXIT statement for constructs other than DO
211 * STOP statement constant generalized
212 * BGE(), BGT(), BLE(), BLT() unsigned integer comparisons
213 * DSHIFTL(), DSHIFTR()
214 * LEADZ(), POPCNT(), POPPAR(), TRAILZ()
216 * SHIFTL(), SHIFTR(), SHIFTA()
218 * IALL(), IANY(), IPARITY()
219 * STORAGE_SIZE() in bits
220 * RADIX argument to SELECTED_REAL_KIND()
221 * COMPLEX arguments to ACOS et al.
222 * ACOSH(), ASINH(), ATANH()
223 * ATAN(x,y) synonym for ATAN2()
225 * ERF(), ERFC(), ERFC_SCALED(), GAMMA(), HYPOT(), LOG_GAMMA()
228 * CALL EXECUTE_COMMAND_LINE()
229 * MINLOC(BACK=.TRUE.), MAXLOC(BACK=.TRUE.)
231 * More constants and functions in intrinsic module ISO_FORTRAN_ENV.
232 * Implicit SAVE attribute assumed for module/submodule variables,
233 procedure pointers, and COMMON blocks.
234 * CONTAINS section can be empty in a procedure or type.
235 * Internal procedures may be passed as actual arguments and assigned
236 to procedure pointers.
237 * Null pointer or unallocated allocatable may be passed to OPTIONAL dummy
238 argument, which then appears to not be present.
239 * POINTER INTENT(IN) dummy arg may be associated with non-pointer TARGET actual
240 * Refinement of GENERIC resolution rules on pointer/allocatable, data/procedure
241 * IMPURE for ELEMENTAL procedures (still PURE by default of course)
242 * Obsolescence of ENTRY
243 * A source line can begin with a semicolon.
246 * Obsolescence of COMMON, EQUIVALENCE, BLOCK DATA, FORALL, labeled DO,
247 specific names for generic intrinsics
248 * Arithmetic IF and non-block DO deleted
249 * Constant properties of an object can be used in its initialization
250 * Implied DO variables can be typed in array constructors and DATA
251 * Assumed-rank arrays with DIMENSION(..), SELECT RANK construct
252 * A file can be opened on multiple units
253 * Advancing input with SIZE=
254 * G0.d for integer, logical, character
255 * D0.d, E0.d, EN0.d, ES0.d, Ew.dE0, &c.
256 * EX hex floating-point output; hex acceptable for floating-point input
257 * Variable stop code allowed in (ERROR) STOP
258 * new COSHAPE, OUT_OF_RANGE, RANDOM_INIT, REDUCE intrinsics
259 * minor tweaks to extant intrinsics
260 * IMPORT statement for BLOCK and contained subprograms
261 * IMPLICIT NONE can require explicit EXTERNAL
262 * RECURSIVE becomes default; NON_RECURSIVE added
263 * DO CONCURRENT locality clauses