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