diff --git a/data/learning.yml b/data/learning.yml index 6d1bcfca763..0e81269b8ab 100644 --- a/data/learning.yml +++ b/data/learning.yml @@ -286,6 +286,23 @@ books: - /learn/oop_features_in_fortran/object_oriented_programming_techniques - /learn/oop_features_in_fortran/performance_and_ease_of_use + - title: Fortran 95 language features + description: Wikipedia's article about the Fortran 95 standard + category: Fortran Documentation + link: /learn/f95_features + pages: + - /learn/f95_features/ + - /learn/f95_features/language_elments + - /learn/f95_features/expressions_and_assignments + - /learn/f95_features/control_statements + - /learn/f95_features/programm_units_and_procedures + - /learn/f95_features/array_handling + - /learn/f95_features/pointers + - /learn/f95_features/intrinsic_procedures + - /learn/f95_features/data_transfer + - /learn/f95_features/operations_on_external_files + - /learn/f95_features/bibliography + # Web links listed at the bottom of the 'Learn' landing page # reference-links: diff --git a/source/learn.md b/source/learn.md index a39a7db5025..89414770716 100644 --- a/source/learn.md +++ b/source/learn.md @@ -186,4 +186,5 @@ learn/best_practices/index learn/intrinsics/index learn/rosetta_stone learn/oop_features_in_fortran/index +learn/f95_features/index ::: diff --git a/source/learn/f95_features/array_handling.md b/source/learn/f95_features/array_handling.md new file mode 100644 index 00000000000..72c9abf32b1 --- /dev/null +++ b/source/learn/f95_features/array_handling.md @@ -0,0 +1,422 @@ +# Array handling + +Array handling is included in Fortran for two main reasons: + +- the notational convenience it provides, bringing the code closer to + the underlying mathematical form; +- for the additional optimization opportunities it gives compilers + (although there are plenty of opportunities for degrading + optimization too!). + +At the same time, major extensions of the functionality in this area +have been added. We have already met whole arrays above +<a href="#Arrays" class="wikilink" title="#Arrays 1">#Arrays 1</a> and +here +<a href="#Arrays_2" class="wikilink" title="#Arrays 2">#Arrays 2</a> - +now we develop the theme. + +## Zero-sized arrays + +A zero-sized array is handled by Fortran as a legitimate object, without +special coding by the programmer. Thus, in + +```f90 +do i = 1, n + x(i) = b(i) / a(i, i) + b(i + 1:n) = b(i + 1:n) - a(i + 1:n, i) * x(i) +end do +``` + +no special code is required for the final iteration where `i = n`. We +note that a zero-sized array is regarded as being defined; however, an +array of shape `(0,2)` is not conformable with one of shape `(0,3)`, +whereas + +```f90 +x(1:0) = 3 +``` + +is a valid 'do nothing' statement. + +## Assumed-shape arrays + +These are an extension and replacement for assumed-size arrays. Given an +actual argument like: + +```f90 +real, dimension(0:10, 0:20) :: a +: +call sub(a) +``` + +the corresponding dummy argument specification defines only the type and +rank of the array, not its shape. This information has to be made +available by an explicit interface, often using an interface block (see +[Interface blocks](interface_blocks)). +Thus we write just + +```f90 +subroutine sub(da) + real, dimension(:, :) :: da +``` + +and this is as if `da` were dimensioned `(11,21)`. However, we can +specify any lower bound and the array maps accordingly. + +```f90 +real, dimension(0:, 0:) :: da +``` + +The shape, not bounds, is passed, where the default lower bound is 1 and +the default upper bound is the corresponding extent. + +## Automatic arrays + +A partial replacement for the uses to which `equivalence` was put is +provided by this facility, useful for local, temporary arrays, as in + +```f90 +subroutine swap(a, b) + real, dimension(:) :: a, b + real, dimension(size(a)) :: work + work = a + a = b + b = work +end subroutine swap +``` + +The actual storage is typically maintained on a stack. + +## `allocatable` and `allocate` + +Fortran provides dynamic allocation of storage; it relies on a heap +storage mechanism (and replaces another use of `equivalence`). An +example for establishing a work array for a whole program is + +```f90 +module work_array + integer n + real, dimension(:, :, :), allocatable :: work +end module + +program main + use work_array + read (input, *) n + allocate (work(n, 2 * n, 3 * n), stat=status) + : + deallocate (work) +``` + +The work array can be propagated through the whole program via a `use` +statement in each program unit. We may specify an explicit lower bound +and allocate several entities in one statement. To free dead storage we +write, for instance, + +```f90 +deallocate(a, b) +``` + +Deallocation of arrays is automatic when they go out of scope. + +## Elemental operations, assignments and procedures + +We have already met whole array assignments and operations: + +```f90 +real, dimension(10) :: a, b +a = 0. ! scalar broadcast; elemental assignment +b = sqrt(a) ! intrinsic function result as array object +``` + +In the second assignment, an intrinsic function returns an array-valued +result for an array-valued argument. We can write array-valued functions +ourselves (they require an explicit interface): + +```f90 +program test + real, dimension(3) :: a = (/1., 2., 3./), & + b = (/2., 2., 2./), r + r = f(a, b) + print*,r +contains + function f(c, d) + real, dimension(:) :: c, d + real, dimension(size(c)) :: f + f = c * d ! (or some more useful function of c and d) + end function f +end program test +``` + +Elemental procedures are specified with scalar dummy arguments that may +be called with array actual arguments. In the case of a function, the +shape of the result is the shape of the array arguments. + +Most intrinsic functions are elemental and Fortran 95 extends this +feature to non-intrinsic procedures, thus providing the effect of +writing, in Fortran 90, 22 different versions, for ranks 0-0, 0-1, 1-0, +1-1, 0-2, 2-0, 2-2, ... 7-7, and is further an aid to optimization on +parallel processors. An elemental procedure must be pure. + +```f90 +elemental subroutine swap(a, b) + real, intent(inout) :: a, b + real :: work + work = a + a = b + b = work +end subroutine swap +``` + +The dummy arguments cannot be used in specification expressions (see +<a href="#Specification_expressions" class="wikilink" +title="above">above</a>) except as arguments to certain intrinsic +functions (`bit_size`, `kind`, `len`, and the numeric inquiry ones, (see +<a href="#Intrinsic_data_types" class="wikilink" title="below">below</a>). + +## `where` + +Often, we need to mask an assignment. This we can do using the `where`, +either as a statement: + +```f90 +where (a /= 0.0) a = 1.0 / a ! avoid division by 0 +``` + +(note: the test is element-by-element, not on whole array), or as a +construct: + +```f90 +where (a /= 0.0) + a = 1.0 / a + b = a ! all arrays same shape +end where +``` + +or + +```f90 +where (a /= 0.0) + a = 1.0 / a +elsewhere + a = huge(a) +end where +``` + +Further: + +- it is permitted to mask not only the `where` statement of the + `where` construct, but also any `elsewhere` statement that it + contains; +- a `where` construct may contain any number of masked `elsewhere` + statements but at most one `elsewhere` statement without a mask, and + that must be the final one; +- `where` constructs may be nested within one another, just `forall` + constructs; +- a `where` assignment statement is permitted to be a defined + assignment, provided that it is elemental; +- a `where` construct may be named in the same way as other + constructs. + +## The `forall` statement and construct + +When a `do` construct is executed, each successive iteration is +performed in order and one after the otheran impediment to optimization +on a parallel processor. + +```f90 +forall (i=1:n) a(i, i) = x(i) +``` + +where the individual assignments may be carried out in any order, and +even simultaneously. The `forall` may be considered to be an array +assignment expressed with the help of indices. + +```f90 +forall (i=1:n, j=1:n, y(i, j) /= 0.) x(j, i) = 1.0 / y(i, j) +``` + +with masking condition. + +The `forall` construct allows several assignment statements to be +executed in order. + +```f90 +a(2:n - 1, 2:n - 1) = a(2:n - 1, 1:n - 2) + a(2:n - 1, 3:n) + & + & a(1:n - 2, 2:n - 1) + a(3:n, 2:n - 1) +b(2:n - 1, 2:n - 1) = a(2:n - 1, 2:n - 1) +``` + +is equivalent to the array assignments + +```f90 +forall (i=2:n - 1, j=2:n - 1) + a(i, j) = a(i, j - 1) + a(i, j + 1) + a(i - 1, j) + a(i + 1, j) + b(i, j) = a(i, j) +end forall +``` + +The `forall` version is more readable. + +Assignment in a `forall` is like an array assignment: as if all the +expressions were evaluated in any order, held in temporary storage, then +all the assignments performed in any order. The first statement must +fully complete before the second can begin. + +A `forall` may be nested, and may include a `where`. Procedures +referenced within a `forall` must be pure. + +## Array elements + +For a simple case, given + +```f90 +real, dimension(100, 100) :: a +``` + +we can reference a single element as, for instance, `a(1, 1)`. For a +derived-data type like + +```f90 +type fun_del + real :: u + real, dimension(3) :: du +end type fun_del +``` + +we can declare an array of that type: + +```f90 +type(fun_del), dimension(10, 20) :: tar +``` + +and a reference like + +```f90 +tar(n, 2) +``` + +is an element (a scalar!) of type `fun_del`, but + +```f90 +tar(n, 2)%du +``` + +is an array of type `real`, and + +```f90 +tar(n, 2)%du(2) +``` + +is an element of it. The basic rule to remember is that an array element +always has a subscript or subscripts qualifying at least the last name. + +## Array subobjects (sections) + +The general form of subscript for an array section is +`[lower]:[upper][:stride]` +(where `[...]` indicates an optional item) as in + +```f90 +real a(10, 10) +a(i, 1:n) ! part of one row +a(1:m, j) ! part of one column +a(i, :) ! whole row +a(i, 1:n:3) ! every third element of row +a(i, 10:1:-1) ! row in reverse order +a( (/ 1, 7, 3, 2 /), 1) ! vector subscript +a(1, 2:11:2) ! 11 is legal as not referenced +a(:, 1:7) ! rank two section +``` + +Note that a vector subscript with duplicate values cannot appear on the +left-hand side of an assignment as it would be ambiguous. Thus, + +```f90 +b( (/ 1, 7, 3, 7 /) ) = (/ 1, 2, 3, 4 /) +``` + +is illegal. Also, a section with a vector subscript must not be supplied +as an actual argument to an `out` or `inout` dummy argument. Arrays of +arrays are not allowed: + +```f90 +tar%du ! illegal +``` + +We note that a given value in an array can be referenced both as an +element and as a section: + +```f90 +a(1, 1) ! scalar (rank zero) +a(1:1, 1) ! array section (rank one) +``` + +depending on the circumstances or requirements. By qualifying objects of +derived type, we obtain elements or sections depending on the rule +stated earlier: + +```f90 +tar%u ! array section (structure component) +tar(1, 1)%u ! component of an array element +``` + +## Arrays intrinsic functions + +### Vector and matrix multiply + +```{csv-table} +`dot_product`, "Dot product of 2 rank-one arrays" +`matmul`, "Matrix multiplication" +``` + +### Array reduction + +```{csv-table} +`all`, "True if all values are true" +`any`, "True if any value is true. Example: `if (any( a > b)) then`" +`count`, "Number of true elements in array" +`maxval`, "Maximum value in an array" +`minval`, "Minimum value in an array" +`product`, "Product of array elements" +`sum`, "Sum of array elements" +``` + +### Array inquiry + +```{csv-table} +`allocated`, "Array allocation status" +`lbound`, "Lower dimension bounds of an array" +`shape`, "Shape of an array (or scalar)" +`size`, "Total number of elements in an array" +`ubound`, "Upper dimension bounds of an array" +``` + +### Array construction + +```{csv-table} +`merge`, "Merge under mask" +`pack`, "Pack an array into an array of rank one under a mask" +`spread`, "Replicate array by adding a dimension" +`unpack`, "Unpack an array of rank one into an array under mask" +``` + +### Array reshape + +```{csv-table} +`reshape`, "Reshape an array" +``` + +### Array manipulation + +```{csv-table} +`cshift`, "Circular shift" +`eoshift`, "End-off shift" +`transpose`, "Transpose of an array of rank two" +``` + +### Array location + +```{csv-table} +`maxloc`, "Location of first maximum value in an array" +`minloc`, "Location of first minimum value in an array" +``` diff --git a/source/learn/f95_features/bibliography.md b/source/learn/f95_features/bibliography.md new file mode 100644 index 00000000000..0715fe82db5 --- /dev/null +++ b/source/learn/f95_features/bibliography.md @@ -0,0 +1,20 @@ +# Bibliography + +* Metcalf, Michael; Reid, John; Cohen, Malcolm (2004-06-17), + *Fortran 95/2003 Explained*, Oxford University PressOxford, + <doi:10.1093/oso/9780198526926.003.0001>, ISBN 978-0-19-852692-6. +* [Introduction to Modern Fortran](https://doi.org/10.1007/0-387-28123-1_2), + Statistics and Computing, New York: Springer-Verlag, 2005, + <doi:10.1007/0-387-28123-1_2>, ISBN 0-387-23817-4 +* Gehrke, Wilhelm (1996). + [Fortran 95 Language Guide](https://doi.org/10.1007/978-1-4471-1025-5). + <doi:10.1007/978-1-4471-1025-5>. ISBN 978-3-540-76062-7 +* Chivers, Ian; Sleightholme, Jane (2000), + [Fortran 2000 and Various Fortran Dialects](https://doi.org/10.1007/978-1-4471-0403-2_29), + in *Introducing Fortran 95*, London: Springer London, pp. 377–388, + <doi:10.1007/978-1-4471-0403-2_29>, ISBN 978-1-85233-276-1 +* Counihan, Martin (2006). *Fortran 95* (2nd ed.). CRC Press. ISBN 9780203978467 +* Ramaraman, V. (1997). *Computer programming in FORTRAN 90 and 95*. + PHI Learning Pvt. Ltd. ISBN 9788120311817. +* Joshi, Yogendra Prasad. *An Introduction to Fortran 90/95: Syntax and + Programming.* Allied Publishers. ISBN 9788177644746. diff --git a/source/learn/f95_features/control_statements.md b/source/learn/f95_features/control_statements.md new file mode 100644 index 00000000000..9adbf8e0714 --- /dev/null +++ b/source/learn/f95_features/control_statements.md @@ -0,0 +1,97 @@ +# Control statements + +## Branching and conditions + +The simple `go to` *label* exists, but is usually avoided in most cases, +a more specific branching construct will accomplish the same logic with +more clarity. + +The simple conditional test is the `if` statement: + +```f90 +if (a > b) x = y +``` + +A full-blown `if` construct is illustrated by + +```f90 +if (i < 0) then + if (j < 0) then + x = 0. + else + z = 0. + end if +else if (k < 0) then + z = 1. +else + x = 1. +end if +``` + +## `case` construct + +The `case` construct is a replacement for the computed `goto`, but is +better structured and does not require the use of statement labels: + +```f90 +select case (number) ! number of type integer +case (:-1) ! all values below 0 + n_sign = -1 +case (0) ! only 0 + n_sign = 0 +case (1:) ! all values above 0 + n_sign = 1 +end select +``` + +Each `case` selector list may contain a list and/or range of integers, +character or logical constants, whose values may not overlap within or +between selectors: + +```f90 +case (1, 2, 7, 10:17, 23) +``` + +A default is available: + +```f90 +case default +``` + +There is only one evaluation, and only one match. + +## `do` construct + +A simplified but sufficient form of the `do` construct is illustrated by + +```f90 +outer: do + inner: do i = j, k, l ! from j to k in steps of l (l is optional) + : + if (...) cycle + : + if (...) exit outer + : + end do inner +end do outer +``` + +where we note that loops may be optionally named so that any `exit` or +`cycle` statement may specify which loop is meant. + +Many, but not all, simple loops can be replaced by array expressions and +assignments, or by new intrinsic functions. For instance + +```f90 +tot = 0. + +do i = m, n + tot = tot + a(i) +end do +``` + +becomes simply + +```f90 +tot = sum(a(m:n)) +``` diff --git a/source/learn/f95_features/data_transfer.md b/source/learn/f95_features/data_transfer.md new file mode 100644 index 00000000000..2bc24f36837 --- /dev/null +++ b/source/learn/f95_features/data_transfer.md @@ -0,0 +1,296 @@ +# Data transfer + +## Formatted input/output + +These examples illustrate various forms of I/O lists with some simple +formats (see [below](edit_descriptors)): + +```f90 +integer :: i +real, dimension(10) :: a +character(len=20) :: word +print "(i10)", i +print "(10f10.3)", a +print "(3f10.3)", a(1), a(2), a(3) +print "(a10)", word(5:14) +print "(3f10.3)", a(1) * a(2) + i, sqrt(a(3:4)) +``` + +Variables, but not expressions, are equally valid in input statements +using the `read` statement: + +```f90 +read "(i10)", i +``` + +If an array appears as an item, it is treated as if the elements were +specified in array element order. + +Any pointers in an I/O list must be associated with a target, and +transfer takes place between the file and the targets. + +An item of derived type is treated as if the components were specified +in the same order as in the type declaration, so + +```f90 +read "(8f10.5)", p, t ! types point and triangle +``` + +has the same effect as the statement + +```f90 +read "(8f10.5)", p%x, p%y, t%a%x, t%a%y, t%b%x, & + t%b%y, t%c%x, t%c%y +``` + +An object in an I/O list is not permitted to be of a derived type that +has a pointer component at any level of component selection. + +Note that a zero-sized array may occur as an item in an I/O list. Such +an item corresponds to no actual data transfer. + +The format specification may also be given in the form of a character +expression: + +```f90 +character(len=*), parameter :: form = "(f10.3)" +: +print form, q +``` + +or as an asterisk this is a type of I/O known as *list-directed* I/O +(see [below](list-directed-i/o), +in which the format is defined by the computer system: + +```f90 +print *, "Square-root of q = ", sqrt(q) +``` + +Input/output operations are used to transfer data between the storage of +an executing program and an external medium, specified by a *unit +number*. However, two I/O statements, `print` and a variant of `read`, +do not reference any unit number: this is referred to as terminal I/O. +Otherwise the form is: + +```f90 +read (unit=4, fmt="(f10.3)") q +read (unit=newunit, fmt="(f10.3)") q +read (unit=4 * i + j, fmt="(f10.3)") a +``` + +where `unit=` is optional. The value may be any nonnegative integer +allowed by the system for this purpose (but `0`, `5` and `6` often +denote the error, keyboard and terminal, respectively). + +An asterisk is a variantagain from the keyboard: + +```f90 +read (unit=*, fmt="(f10.3)") q +``` + +A read with a unit specifier allows +[exception handling](https://en.wikipedia.org/wiki/Exception_handling): + +```f90 +read (unit=nunit, fmt="(3f10.3)", iostat=ios) a, b, c +if (ios == 0) then + ! Successful read - continue execution. + : +else + ! Error condition - take appropriate action. + call error(ios) +end if +``` + +There is a second type of formatted output statement, the `write` +statement: + +```f90 +write (unit=nout, fmt="(10f10.3)", iostat=ios) a +``` + +## Internal files + +These allow format conversion between various representations to be +carried out by the program in a storage area defined within the program +itself. + +```f90 +integer, dimension(30) :: ival +integer :: key +character(len=30) :: buffer +character(len=6), dimension(3), parameter :: form = (/"(30i1)", & + "(15i2)", "(10i3)"/) + +read (unit=*, fmt="(a30,i1)") buffer, key +read (unit=buffer, fmt=form(key)) ival(1:30 / key) +``` + +If an internal file is a scalar, it has a single record whose length is +that of the scalar. + +If it is an array, its elements, in array element order, are treated as +successive records of the file and each has length that of an array +element. + +An example using a `write` statement is + +```f90 +integer :: day +real :: cash +character(len=50) :: line +: +! write into line +write (unit=line, fmt="(a, i2, a, f8.2, a)") "Takings for day ", day, & + " are ", cash, " dollars" +``` + +that might write + +```shell +Takings for day 3 are 4329.15 dollars +``` + +## List-directed I/O + +An example of a read without a specified format for input is + +```f90 +integer :: i +real :: a +complex, dimension(2) :: field +logical :: flag +character(len=12) :: title +character(len=4) :: word +: +read *,i, a, field, flag, title, word +``` + +If this reads the input record + +```f90 +10 6.4(1.0, 0.0) (2.0, 0.0) t test / +``` + +(in which blanks are used as separators), then `i`, `a`, `field`, +`flag`, and `title` will acquire the values 10, 6.4, (1.0,0.0) and +(2.0,0.0), `.true.` and `test` respectively, while `word` remains +unchanged. + +Quotation marks or apostrophes are required as delimiters for a string +that contains a blank. + +## Non-advancing I/O + +This is a form of reading and writing without always advancing the file +position to ahead of the next record. Whereas an advancing I/O statement +always repositions the file after the last record accessed, a +non-advancing I/O statement performs no such repositioning and may +therefore leave the file positioned within a record. + +```f90 +character(len=3) :: key +integer :: u, s, ios +: +read (unit=u, fmt="(a3)", advance="no", size=s, iostat=ios) key +if (ios == 0) then + : +else + ! key is not in one record + key(s + 1:) = "" + : +end if +``` + +A non-advancing read might read the first few characters of a record and +a normal read the remainder. + +In order to write a prompt to a terminal screen and to read from the +next character position on the screen without an intervening line-feed, +we can write + +```f90 +write (unit=*, fmt="(a)", advance="no") "enter next prime number:" +read (unit=*, fmt="(i10)") prime_number +``` + +Non-advancing I/O is for external files, and is not available for +list-directed I/O. + +## Edit descriptors + +It is possible to specify that an edit descriptor be repeated a +specified number of times, using a *repeat count*: `10f12.3` + +The slash edit descriptor (see +[below](control-edit-descriptors)) +may have a repeat count, and a repeat count can +also apply to a group of edit descriptors, enclosed in parentheses, with +nesting: + +```f90 +print "(2(2i5,2f8.2))", i(1),i(2),a(1),a(2), i(3),i(4),a(3),a(4) +``` + +Entire format specifications can be repeated: + +```f90 +print "(10i8)", (/ (i(j), j=1,200) /) +``` + +writes 10 integers, each occupying 8 character positions, on each of 20 +lines (repeating the format specification advances to the next line). + +### Data edit descriptors + +### Control edit descriptors + +*Control edit descriptors setting conditions*: *Control edit descriptors +for immediate processing*: + +## Unformatted I/O + +This type of I/O should be used only in cases where the records are +generated by a program on one computer, to be read back on the same +computer or another computer using the same internal number +representations: + +```f90 +open (unit=4, file='test', form='unformatted') +read (unit=4) q +write (unit=nout, iostat=ios) a ! no fmt= +``` + +## Direct-access files + +This form of I/O is also known as random access or indexed I/O. Here, +all the records have the same length, and each record is identified by +an index number. It is possible to write, read, or re-write any +specified record without regard to position. + +```f90 +integer, parameter :: nunit = 2, length = 100 +real, dimension(length) :: a +real, dimension(length + 1:2*length) :: b +integer :: i, rec_length +: +inquire (iolength=rec_length) a +open (unit=nunit, access="direct", recl=rec_length, status="scratch", & + action="readwrite") +: +! Write array b to direct-access file in record 14 +write (unit=nunit, rec=14) b +: +! Read the array back into array a +read (unit=nunit, rec=14) a + +do i = 1, length / 2 + a(i) = i +end do + +! Replace modified record +write (unit=nunit, rec=14) a +``` + +The file must be an external file and list-directed formatting and +non-advancing I/O are unavailable. diff --git a/source/learn/f95_features/expressions_and_assignments.md b/source/learn/f95_features/expressions_and_assignments.md new file mode 100644 index 00000000000..487c1f1fb16 --- /dev/null +++ b/source/learn/f95_features/expressions_and_assignments.md @@ -0,0 +1,297 @@ +# Expressions and assignments + +## Scalar numeric + +The usual arithmetic operators are available `+`, `-`, `*`, `/`, and +`**` (given here in increasing order of precedence). + +Parentheses are used to indicate the order of evaluation where +necessary: + +```f90 +a*b + c ! * first +a*(b + c) ! + first +``` + +The rules for *scalar numeric* expressions and assignments accommodate +the non-default kinds. Thus, the mixed-mode numeric expression and +assignment rules incorporate different kind type parameters in an +expected way: + +```f90 +real2 = integer0 + real1 +``` + +converts `integer0` to a real value of the same kind as `real1`; the +result is of same kind, and is converted to the kind of `real2` for +assignment. + +These functions are available for controlled +[rounding](https://en.wikipedia.org/wiki/Rounding) +of real numbers to integers: + +- `nint`: round to nearest integer, return integer result +- `anint`: round to nearest integer, return real result +- `int`: truncate (round towards zero), return integer result +- `aint`: truncate (round towards zero), return real result +- `ceiling`: smallest integral value not less than argument (round up) + (Fortran-90) +- `floor`: largest integral value not greater than argument (round + down) (Fortran-90) + +## Scalar relational operations + +For *scalar relational* operations of numeric types, there is a set of +built-in operators: + +`< <= == /= > >=` +`.lt. .le. .eq. .ne. .gt. .ge.` + +(the forms above are new to Fortran-90, and older equivalent forms are +given below them). Example expressions: + +```f90 +a < b .and. i /= j ! for numeric variables +flag = a == b ! for logical variable flags +``` + +### Scalar characters + +In the case of *scalar characters* and given `character(8) result` +it is legal to write + +```f90 +result(3:5) = result(1:3) ! overlap allowed +result(3:3) = result(3:2) ! no assignment of null string +``` + +Concatenation is performed by the operator `//`. + +```f90 +result = 'abcde'//'123' +filename = result//'.dat' +``` + +## Derived-data types + +No built-in operations (except assignment, defined on component-by +component basis) exist between *derived data types* mutually or with +intrinsic types. The meaning of existing or user-specified operators can +be (re)defined though: + +```f90 +type string80 + integer :: length + character(80) :: value +end type string80 + +character :: char1, char2, char3 +type(string80) :: str1, str2, str3 +``` + +we can write + +```f90 +str3 = str1//str2 ! must define operation +str3 = str1.concat.str2 ! must define operation +char3 = char2//char3 ! intrinsic operator only +str3 = char1 ! must define assignment +``` + +Notice the +["overloaded"](https://en.wikipedia.org/wiki/Operator_overloading) +use of the intrinsic symbol `//` and +the named operator, `.concat.` . A difference between the two cases is +that, for an intrinsic operator token, the usual precedence rules apply, +whereas for named operators, precedence is the highest as a unary +operator or the lowest as a binary one. In + +```f90 +vector3 = matrix * vector1 + vector2 +vector3 =(matrix .times. vector1) + vector2 +``` + +the two expressions are equivalent only if appropriate parentheses are +added as shown. In each case there must be defined, in a +[module](modules), +procedures defining the operator and assignment, and corresponding +operator-procedure association, as follows: + +```f90 +interface operator(//) ! Overloads the // operator as + ! invoking string_concat procedure + module procedure string_concat +end interface +``` + +The string concatenation function is a more elaborated version of that +shown already in +[Basics](Basics). +Note that +in order to handle the error condition that arises when the two strings +together exceed the preset 80-character limit, it would be safer to use +a subroutine to perform the concatenation (in this case +operator-overloading would not be applicable.) + +```f90 +module string_type + implicit none + + type string80 + integer length + character(len=80) :: string_data + end type string80 + + interface assignment(=) + module procedure c_to_s_assign, s_to_c_assign + end interface + + interface operator(//) + module procedure string_concat + end interface + +contains + subroutine c_to_s_assign(s, c) + type(string80), intent(out) :: s + character(LEN=*), intent(in) :: c + s%string_data = c + s%length = len(c) + end subroutine c_to_s_assign + + subroutine s_to_c_assign(c, s) + type(string80), intent(in) :: s + character(len=*), intent(out) :: c + c = s%string_data(1:s%length) + end subroutine s_to_c_assign + + type(string80) function string_concat(s1, s2) + type(string80), intent(in) :: s1, s2 + type(string80) :: s + integer :: n1, n2 + character(160) :: ctot + n1 = len_trim(s1%string_data) + n2 = len_trim(s2%string_data) + + if (n1 + n2 <= 80) then + s%string_data = s1%string_data(1:n1)//s2%string_data(1:n2) + else ! This is an error condition which should be handled - for now just truncate + ctot = s1%string_data(1:n1)//s2%string_data(1:n2) + s%string_data = ctot(1:80) + end if + + s%length = len_trim(s%string_data) + string_concat = s + end function string_concat +end module string_type + +program main + use string_type + type(string80) :: s1, s2, s3 + call c_to_s_assign(s1, 'My name is') + call c_to_s_assign(s2, ' Linus Torvalds') + s3 = s1//s2 + write (*, *) 'Result: ', s3%string_data + write (*, *) 'Length: ', s3%length +end program +``` + +Defined operators such as these are required for the expressions that +are allowed also in structure constructors (see +[Derived-data types](derived-data-types)): + +```f90 +str1 = string(2, char1//char2) ! structure constructor +``` + +## Arrays + +In the case of arrays then, as long as they are of the same shape +(conformable), operations and assignments are extended in an obvious +way, on an element-by-element basis. For example, given declarations of + +```f90 +real, dimension(10, 20) :: a, b, c +real, dimension(5) :: v, w +logical :: flag(10, 20) +``` + +it can be written: + +```f90 +a = b ! whole array assignment +c = a/b ! whole array division and assignment +c = 0. ! whole array assignment of scalar value +w = v + 1. ! whole array addition to scalar value +w = 5/v + a(1:5, 5) ! array division, and addition to section +flag = a==b ! whole array relational test and assignment +c(1:8, 5:10) = a(2:9, 5:10) + b(1:8, 15:20) ! array section addition and assignment +v(2:5) = v(1:4) ! overlapping section assignment +``` + +The order of expression evaluation is not specified in order to allow +for optimization on parallel and vector machines. Of course, any +operators for arrays of derived type must be defined. + +Some real intrinsic functions that are useful for numeric computations +are + +- `ceiling` +- `floor` +- `modulo` + (also integer) +- `exponent` +- `fraction` +- `nearest` +- `rrspacing` +- `spacing` +- `scale` +- `set_exponent` + +These are array valued for array arguments (`elemental`), like all +[FORTRAN 77](https://en.wikipedia.org/wiki/FORTRAN_77) +functions (except `len`): + +- `int` +- `real` +- `cmplx` +- `aint` +- `anint` +- `nint` +- `abs` +- `mod` +- `sign` +- `dim` +- `max` +- `min` + +Powers, logarithms, and trigonometric functions: + +- `sqrt` +- `exp` +- `log` +- `log10` +- `sin` +- `cos` +- `tan` +- `asin` +- `acos` +- `atan` +- `atan2` +- `sinh` +- `cosh` +- `tanh` + +Complex numbers: + +- `aimag` +- `conjg` + +The following are for characters: + +- `lge` +- `lgt` +- `lle` +- `llt` +- `ichar` +- `char` +- `index` diff --git a/source/learn/f95_features/fprettify.rc b/source/learn/f95_features/fprettify.rc new file mode 100644 index 00000000000..82b2e3549c7 --- /dev/null +++ b/source/learn/f95_features/fprettify.rc @@ -0,0 +1,36 @@ +# style configuration file for fprettify +# original source: https://github.com/PHOTOX/ABIN/blob/master/.fprettify.rc +# original author: Daniel Hollas +# original licence: GPL v3 +# +# minor edits to the original to fit better the pattern other booklets use + +# Replace Fortran-style relational operators with C-style +# to make our code more readable for non-Fortran programmers +# for example '.lt.' to '<' +enable-replacements=False # in the original: True +c-relations=False # in the original: True + +# White space settings +indent=2 # in the original 3 +line-length=132 +strict-indent=True +strip-comments=True +whitespace-relational=True +whitespace-logical=True +whitespace-plusminus=True +whitespace-multdiv=True +whitespace-comma=True +whitespace-intrinsics=True +whitespace-print=False +whitespace-type=False + +# Control whitespace around '::' declarations +whitespace-decl=True +enable-decl=False # in the original: True (then lines shrink) + +# Don't indent pre-processor statements +disable-fypp=True + +case=[1,1,1,2] +exclude=[random.F90,fftw3.F90,force_cp2k.F90, h2o_schwenke.f, h2o_cvrqd.f] diff --git a/source/learn/f95_features/index.md b/source/learn/f95_features/index.md new file mode 100644 index 00000000000..7e8e1e099c8 --- /dev/null +++ b/source/learn/f95_features/index.md @@ -0,0 +1,74 @@ +# Fortran 95 language features + +:::{toctree} +:maxdepth: 2 +:hidden: +Language elements <language_elements> +Expressions and assignments <expressions_and_assignments> +Control statements <control_statements> +Program units and procedures <program_units_and_procedures> +Array handling <array_handling> +Pointers <pointers> +Intrinsic procedures <intrinsic_procedures> +Data transfer <data_transfer> +Operations on external files <operations_on_external_files> +Bibliography <bibliography> +::: + +This is an overview of **Fortran 95 language features** which is based +upon the standards document[^iso_1539_1997] which has been replaced byi +a newer version.[^iso_1539_2023] Included are the additional features of +TR-15581:Enhanced Data Type Facilities, which have been universally +implemented. Old features that have been superseded by new ones are not +described few of those historic features are used in modern programs +although most have been retained in the language to maintain +[backward_compatibility](https://en.wikipedia.org/wiki/Backward_compatibility). +The additional features of subsequent standards, up to Fortran 2023, are +described in the Fortran 2023 standard document, ISO/IEC +1539-1:2023.[^iso_1539_2023] Some of its new features are still being +implemented in compilers.[^Fortran_plus] Details can also be found in a +range of textbooks, for instance[^OOPvF][^OOPC][^Chapman] and see the +list at Fortran Resources.[^Fortran_plus_18] Sources for the description +in the sections below can be found in the standards +documents,[^iso_1539_2023] textbooks[^OOPvF][^OOPC][^Chapman] as well as +the +[bibliography](bibliography). + +The booklet is based on Wikipedia's article +[Fortran 95 language +features](https://en.wikipedia.org/wiki/Fortran_95_language_features), +last edit by February 25, 2025 16:08 UTC. + +[^mfe]: + Metcalf, Michael; Reid, John; Cohen, Malcolm; Bader, Reinhold (2023). + _Modern Fortran Explained._ Numerical Mathematics and Scientific Computation. + Oxford University Press. + [ISBN 978-0-19-887657-1](https://en.wikipedia.org/wiki/Special:BookSources/978-0-19-887657-1). + +[^iso_1539_1997]: + [ISO/IEC 1539-1:1997](https://www.iso.org/standard/26933.html) + +[^iso_1539_2023]: + [ISO/IEC 1539-1:2023](https://www.iso.org/standard/82170.html) + +[^Fortran_plus]: + [Fortranplus | Fortran information](http://www.fortranplus.co.uk/fortran-information/) + +[^OOPvF]: + ["Features of Programming Languages"](https://doi.org/10.1017/cbo9780511530111.005), + Object-Oriented Programming via Fortran 90/95, Cambridge University Press, + pp. 56–118. + +[^OOPC]: + ["Object-Oriented Programming Concepts"](https://doi.org/10.1017/cbo9780511530111.004), + Object-Oriented Programming via Fortran 90/95, Cambridge University Press, + pp. 36–55 + +[^Chapman]: + Chapman, Stephen J. (2004). + [Fortran 90/95 for scientists and engineers](https://www.worldcat.org/title/ocm52465017) + (2nd ed.). Boston: McGraw-Hill Higher Education. ISBN 978-0-07-282575-6. + +[^Fortran_plus_18]: + [Fortranplus | Fortran information](http://www.fortranplus.co.uk/fortran-information/), + p. 18 diff --git a/source/learn/f95_features/intrinsic_procedures.md b/source/learn/f95_features/intrinsic_procedures.md new file mode 100644 index 00000000000..37b41bcfb96 --- /dev/null +++ b/source/learn/f95_features/intrinsic_procedures.md @@ -0,0 +1,63 @@ +# Intrinsic procedures + +Most of the intrinsic functions have already been mentioned. Here, we +deal only with their general classification and with those that have so +far been omitted. All intrinsic procedures can be used with keyword +arguments: + +```f90 +call date_and_time(TIME=t) +``` + +and many have optional arguments. + +The intrinsic procedures are grouped into four categories: + +1. elemental - work on scalars or arrays, e.g. `abs(a)`; +1. inquiry - independent of value of argument (which may be undefined), + e.g. `precision(a)`; +1. transformational - array argument with array result of different + shape, e.g. `reshape(a, b)`; +1. subroutines, e.g. `system_clock`. + +The procedures not already introduced are + +Bit inquiry + +```{csv-table} +`bit_size`, "Number of bits in the model" +``` + +Bit manipulation + +```{csv-table} +`btest`, "Bit testing" +`iand`, "Logical AND" +`ibclr`, "Clear bit" +`ibits`, "Bit extraction" +`ibset`, "Set bit" +`ieor`, "Exclusive OR" +`ior`, "Inclusive OR" +`ishft`, "Logical shift" +`ishftc`, "Circular shift" +`not`, "Logical complement" +``` + +Transfer function, as in + +```f90 +integer :: i = transfer('abcd', 0) +``` + +(replaces part of `equivalence`) + +Subroutines + +```{csv-table} +`date_and_time`, "Obtain date and/or time" +`mvbits`, "Copies bits" +`random_number`, "Returns pseudorandom numbers" +`random_seed`, "Access to seed" +`system_clock`, "Access to system clock" +`cpu_time`, "Returns processor time in seconds" +``` diff --git a/source/learn/f95_features/language_elements.md b/source/learn/f95_features/language_elements.md new file mode 100644 index 00000000000..00c89bcb1ae --- /dev/null +++ b/source/learn/f95_features/language_elements.md @@ -0,0 +1,527 @@ +# Language elements + +Fortran is +[case-insensitive](https://en.wikipedia.org/wiki/Case_sensitivity) +The convention of writing +Fortran keywords in upper case and all other names in lower case is +adopted in this article; except, by way of contrast, in the input/output +descriptions +([Data transfer](data_transfer) +and +[Operations on external files](operations_on_external_files)). + +## Basics + +The basic component of the Fortran language is its *character set*. Its +members are + +- the letters A ... Z and a ... z (which are equivalent outside a + character context) +- the numerals 0 ... 9 +- the underscore \_ +- the special characters + `= : + blank - * / ( ) [ ] , . $ ' ! " % & ; < > ?` + +[Tokens](https://en.wikipedia.org/wiki/Token_(parser)) +that +have a syntactic meaning to the compiler are built from those +components. There are six classes of tokens: + +```{csv-table} +Label, "`123`" +Constant, "`123.456789_long`" +Keyword, "`allocatable`" +Operator, "`.add.`" +Name, "`solve_equation` (up to 31 characters, including \_)" +Separator, "`/ ( ) (/ /) [ ] , = => : :: ; %`" +``` + +From the tokens, +[statements](https://en.wikipedia.org/wiki/Statement_(programming)) +are built. These can be coded using the +new free *source form* which does not require positioning in a rigid +column structure: + +```f90 +function string_concat(s1, s2) ! This is a comment + type(string), intent(in) :: s1, s2 + type(string) :: string_concat + string_concat%string_data = s1%string_data(1:s1%length) // & + s2%string_data(1:s2%length) ! This is a continuation + string_concat%length = s1%length + s2%length +end function string_concat +``` + +Note the trailing comments and the trailing continuation mark. There may +be 39 continuation lines, and 132 characters per line. Blanks are +significant. Where a token or character constant is split across two +lines: + +```f90 + ... start_of& + &_name + ... 'a very long & + &string' +``` + +a leading `&` on the continued line is also required. + +## Intrinsic data types + +Fortran has five *intrinsic data types*: `integer`, `real`, `complex`, +`logical` and `character`. Each of those types can be additionally +characterized by a *kind*. Kind, basically, defines internal +representation of the type: for the three numeric types, it defines the +precision and range, and for the other two, the specifics of storage +representation. Thus, it is an abstract concept which models the limits +of data types' representation; it is expressed as a member of a set of +whole numbers (e.g. it may be {1, 2, 4, 8} for integers, denoting bytes +of storage), but those values are not specified by the Standard and not +portable. For every type, there is a *default kind*, which is used if no +kind is explicitly specified. For each intrinsic type, there is a +corresponding form of *literal constant*. The numeric types `integer` +and `real` can only be signed (there is no concept of sign for type +`complex`). + +### Literal constants and kinds + +#### `integer` + +Integer literal constants of the default kind take the form + +```f90 +1 0 -999 32767 +10 +``` + +`kind` can be defined as a named constant. If the desired range is +±10<sup>kind</sup>, the portable syntax for defining the appropriate +kind, `two_bytes` is + +```f90 +integer, parameter :: two_bytes = selected_int_kind(4) +``` + +that allows subsequent definition of constants of the form + +```f90 +-1234_two_bytes +1_two_bytes +``` + +Here, `two_bytes` is the kind type parameter; it can also be an explicit +default integer literal constant, like `-1234_2` but such use is +non-portable. + +The `kind` function supplies the value of a kind type parameter: + +```f90 +kind(1) kind(1_two_bytes) +``` + +and the `range` function supplies the actual decimal range (so the user +must make the actual mapping to bytes): + +```f90 +range(1_two_bytes) +``` + +Also, in +[`data` (initialization) statements](data_statement), +binary (`B`), octal (`O`) and hexadecimal (`Z`) constants +may be used (often informally referred to as "BOZ constants"): + +```f90 +B'01010101' O'01234567' Z'10fa' +``` + +#### `real` + +There are at least two real kinds - the default and one with greater +precision (this replaces `double precision`). `selected_real_kind` +functions returns the kind number for desired range and precision; for +at least 9 decimal digits of precision and a range of 10<sup>−99</sup> +to 10<sup>99</sup>, it can be specified as: + +```f90 +integer, parameter :: long = selected_real_kind(9, 99) +``` + +and literals subsequently specified as `1.7_long`. + +Also, there are the intrinsic functions + +```f90 +kind(1.7_long) precision(1.7_long) range(1.7_long) +``` + +that give in turn the kind type value, the actual precision (here at +least `9`), and the actual range (here at least `99`). + +#### `complex` + +`complex` data type is built of two integer or real components: + +```f90 +(1, 3.7_long) +``` + +#### `logical` + +There are only two basic values of logical constants: `.true.` and +`.false.`. Here, there may also be different kinds. Logicals don't have +their own kind inquiry functions, but use the kinds specified for +`integer`s; default kind of `logical` is the same as of `integer`. + +```f90 +.false. .true._one_byte +``` + +and the `kind` function operates as expected: + +```f90 +kind(.true.) +``` + +#### `character` + +The forms of literal constants for `character` data type are + +```f90 +'A string' "Another" 'A "quote"' ''''''' +``` + +(the last being an empty string). Different kinds are allowed (for +example, to distinguish +[ASCII](https://en.wikipedia.org/wiki/ASCII) +and +[UNICODE](https://en.wikipedia.org/wiki/UNICODE) +strings), +but not widely supported by compilers. Again, the kind value is given by +the `kind` function: + +```f90 +kind('ASCII') +``` + +### Number model and intrinsic functions + +The numeric types are based on number models with associated inquiry +functions (whose values are independent of the values of their +arguments; arguments are used only to provide kind). These functions are +important for portable numerical software: + +```{csv-table} +`digits(x)`, "Number of significant digits" +`epsilon(x)`, "Almost negligible compared to one (real)" +`huge(x)`, "Largest number" +`maxexponent(x)`, "Maximum model exponent (real)" +`minexponent(x)`, "Minimum model exponent (real)" +`precision(x)`, "Decimal precision (real, complex)" +`radix(x)`, "Base of the model" +`range(x)`, "Decimal exponent range" +`tiny(x)`, "Smallest positive number (real)" +``` + +## Scalar variables + +Scalar +[variables](https://en.wikipedia.org/wiki/Variable_(programming)) +corresponding to the five intrinsic +types are specified as follows: + +```f90 +integer(kind=2) :: i +real(kind=long) :: a +complex :: current +logical :: Pravda +character(len=20) :: word +character(len=2, kind=Kanji) :: kanji_word +``` + +where the optional `kind` parameter specifies a non-default kind, and +the `::` notation delimits the type and attributes from variable name(s) +and their optional initial values, allowing full variable specification +and initialization to be typed in one statement (in previous standards, +attributes and initializers had to be declared in several statements). +While it is not required in above examples (as there are no additional +attributes and initialization), most Fortran-90 programmers acquire the +habit to use it everywhere. + +The `len=` specifier is applicable only to `character`s and specifies +the string length (replacing the older `*len` form). The explicit +`kind=` and `len=` specifiers are optional: + +```f90 +character(2, kanji) :: kanji_word +``` + +works just as well. + +There are some other interesting character features. Just as a substring +as in + +```f90 +character(80) :: line +... = line(i:i) ! substring +``` + +was previously possible, so now is the substring + +```f90 +'0123456789'(i:i) +``` + +Also, zero-length strings are allowed: + +```f90 +line(i:i-1) ! zero-length string +``` + +Finally, there is a set of intrinsic character functions, examples being + +```{csv-table} +`achar`, "`iachar` (for ASCII set)" +`adjustl`, "`adjustr`" +`len_trim`, "`index(s1, s2, back=.true.)`" +`repeat`, "`scan`(for one of a set)" +`trim`, "`verify`(for all of a set)" +``` + +## Derived data types + +For derived data types, the form of the type must be defined first: + +```f90 +type person + character(10) :: name + real :: age +end type person +``` + +and then, variables of that type can be defined: + +```f90 +type(person) :: you, me +``` + +To select components of a derived type, `%` qualifier is used: + +```f90 +you%age +``` + +Literal constants of derived types have the form +`TypeName(1stComponentLiteral, 2ndComponentLiteral, ...)`: + +```f90 +you = person("Smith", 23.5) +``` + +which is known as a *structure constructor*. Definitions may refer to a +previously defined type: + +```f90 +type point + real :: x, y +end type point + +type triangle + type(point) :: a, b, c +end type triangle +``` + +and for a variable of `type triangle`, as in + +```f90 +type(triangle) :: t +``` + +each component of type `point` is accessed as + +```f90 +t%a t%b t%c +``` + +which, in turn, have ultimate components of `type real`: + +```f90 +t%a%x t%a%y t%b% +``` + +etc. (Note that the `%` qualifier was chosen rather than dot (`.`) +because of potential ambiguity with operator notation, like `.OR.`). + +## Implicit and explicit typing + +Unless specified otherwise, all variables starting with letters `i`, +`j`, `k`, `l`, `m` and `n` default to `integer`, and all others are +default `real`; +other data types must be explicitly declared. This is known as *implicit +typing* and is a heritage of early FORTRAN days. Those defaults can be +overridden by `implicit TypeName (CharacterRange)` statements, like: + +```f90 +implicit complex(z) +implicit character(a-b) +implicit real(c-h,n-y) +``` + +However, it is a good practice to explicitly type all variables, and +this can be forced by inserting the statement `implicit none` at the +beginning of each program unit. + +## Arrays + +Arrays are considered to be variables in their own right. Every array is +characterized by its +[type](https://en.wikipedia.org/wiki/Type_(computer_programming)), +[rank](https://en.wikipedia.org/wiki/Rank_(computer_programming)), +and *shape* (which defines the extents of each +dimension). Bounds of each dimension are by default `1` and *size*, but +arbitrary bounds can be explicitly specified. The `dimension` keyword is +optional and considered an attribute; if omitted, the array shape must +be specified after array-variable name. For example, + +```f90 +real :: a(10) +integer, dimension(0:100, -50:50) :: map +``` + +declares two arrays, `rank-1` and `rank-2`, whose elements are in +[column-major order](https://en.wikipedia.org/wiki/Column-major_order). +Elements are, for example, + +```f90 +a(1) a(i*j) +``` + +and are scalars. The subscripts may be any scalar integer expression. + +*Sections* are parts of the array variables, and are arrays themselves: + +```f90 +a(i:j) ! rank one +map(i:j, k:l:m) ! rank two +a(map(i, k:l)) ! vector subscript +a(3:2) ! zero length +``` + +Whole arrays and array sections are array-valued objects. Array-valued +constants (constructors) are available, enclosed in `(/ ... /)`: + +```f90 +(/ 1, 2, 3, 4 /) +(/ ( (/ 1, 2, 3 /), i = 1, 4) /) +(/ (i, i = 1, 9, 2) /) +(/ (0, i = 1, 100) /) +(/ (0.1*i, i = 1, 10) /) +``` + +making use of an implied-`do loop` notation. Fortran 2003 allows the use +of brackets: `[1, 2, 3, 4]` and `[([1,2,3], i=1,4)]` instead of the +first two examples above, and many compilers support this now. A derived +data type may, of course, contain array components: + +```f90 +type triplet + real, dimension(3) :: vertex +end type triplet +type(triplet), dimension(4) :: t +``` + +so that + +- `t(2)` is a scalar (a structure) +- `t(2)%vertex` is an array component of a scalar + +## Data initialization + +Variables can be given initial values as specified in a specification +statement: + +```f90 +real, dimension(3) :: a = (/ 0.1, 0.2, 0.3 /) +``` + +and a default initial value can be given to the component of a derived +data type: + +```f90 +type triplet + real, dimension(3) :: vertex = 0.0 +end type triplet +``` + +When local variables are initialized within a procedure they implicitly +acquire the `save` attribute: + +```f90 +real, dimension(3) :: point = (/0.0, 1.0, -1.0/) +``` + +This declaration is equivalent to + +```f90 +real, dimension(3), save :: point = (/0.0, 1.0, -1.0/) +``` + +for local variables within a subroutine or function. The `save` +attribute causes local variables to retain their value after a procedure +call and then to initialize the variable to the saved value upon +returning to the procedure. + +### `parameter` attribute + +A named constant can be specified directly by adding the `parameter` +attribute and the constant values to a type statement: + +```f90 +real, dimension(3), parameter :: field = (/0., 1., 2./) +type(triplet), parameter :: t = triplet((/0., 0., 0./)) +``` +(data_statement)= +### `data` statement + +The `data` statement can be used for scalars and also for arrays and +variables of derived type. It is also the only way to initialise just +parts of such objects, as well as to initialise to binary, octal or +hexadecimal values: + +```f90 +type(triplet) :: t1, t2 +data t1/triplet((/0., 1., 2./))/, t2%vertex(1)/123./ +data array(1:64)/64*0/ +data i, j, k/B'01010101', O'77', Z'ff'/ +``` + +### Initialization expressions + +The values used in `data` and `parameter` statements, or with these +attributes, are constant expressions that may include references to: +array and structure constructors, elemental intrinsic functions with +integer or character arguments and results, and the six transformational +functions `repeat`, `selected_int_kind`, `trim`, `selected_real_kind`, +`reshape`, and `transfer` (see +[Intrinsic procedures](intrinsic_procedures)): + +```f90 +integer, parameter :: long = selected_real_kind(12), & + array(3) = (/1, 2, 3/) +``` + +## Specification expressions + +It is possible to specify details of variables using any non-constant, +scalar, integer expression that may also include inquiry function +references: + +```f90 +subroutine s(b, m, c) + use mod ! contains a + real, dimension(:, :) :: b + real, dimension(ubound(b, 1) + 5) :: x + integer :: m + character(len=*) :: c + character(len=m + len(c)) :: cc + real(selected_real_kind(2*precision(a))) :: z +end subroutine +``` diff --git a/source/learn/f95_features/operations_on_external_files.md b/source/learn/f95_features/operations_on_external_files.md new file mode 100644 index 00000000000..7aa8f16b8d0 --- /dev/null +++ b/source/learn/f95_features/operations_on_external_files.md @@ -0,0 +1,98 @@ +# Operations on external files + +Once again, this is an overview only. + +## File positioning statements + +## The `open` statement + +The statement is used to connect an external file to a unit, create a +file that is preconnected, or create a file and connect it to a unit. +The syntax is + +```f90 +open (unit=u, status=st, action=act[, olist]) +``` + +where `olist` is a list of optional specifiers. The specifiers may +appear in any order. + +```f90 +open (unit=2, iostat=ios, file="cities", status="new", access="direct", & + action="readwrite", recl=100) +``` + +Other specifiers are `form` and `position`. + +## The `close` statement + +This is used to disconnect a file from a unit. + +```f90 +close (unit=u[, iostat=ios] [, status=st]) +``` + +as in + +```f90 +close (unit=2, iostat=ios, status="delete") +``` + +## The `inquire` statement + +At any time during the execution of a program it is possible to inquire +about the status and attributes of a file using this statement. + +Using a variant of this statement, it is similarly possible to determine +the status of a unit, for instance whether the unit number exists for +that system. + +Another variant permits an inquiry about the length of an output list +when used to write an unformatted record. + +For inquire by unit + +```f90 +inquire (unit=u, ilist) +``` + +or for inquire by file + +```f90 +inquire (file=fln, ilist) +``` + +or for inquire by I/O list + +```f90 +inquire (iolength=length) olist +``` + +As an example + +```f90 +logical :: ex, op +character(len=11) :: nam, acc, seq, frm +integer :: irec, nr +inquire (unit=2, exist=ex, opened=op, name=nam, access=acc, sequential=seq, & + form=frm, recl=irec, nextrec=nr) +``` + +yields + +```f90 +ex .true. +op .true. +nam cities +acc direct +seq no +frm unformatted +irec 100 +nr 1 +``` + +(assuming no intervening read or write operations). + +Other specifiers are +`iostat`, `opened`, `number`, `named`, `formatted`, `position`, `action`, +`read`, `write`, `readwrite`. diff --git a/source/learn/f95_features/pointers.md b/source/learn/f95_features/pointers.md new file mode 100644 index 00000000000..d487d8a2dcc --- /dev/null +++ b/source/learn/f95_features/pointers.md @@ -0,0 +1,332 @@ +# Pointers + +## Basics + +Pointers are variables with the `pointer` attribute; they are not a +distinct data type (and so no 'pointer arithmetic' is possible). + +```f90 +real, pointer :: var +``` + +They are conceptually a descriptor listing the attributes of the objects +(targets) that the pointer may point to, and the address, if any, of a +target. They have no associated storage until it is allocated or +otherwise associated (by pointer assignment, see +[Pointers in expressions and assignments](pointers_in_expressions_and_assignments)): + +```f90 +allocate (var) +``` + +and they are dereferenced automatically, so no special symbol required. +In + +```f90 +var = var + 2.3 +``` + +the value of the target of var is used and modified. Pointers cannot be +transferred via I/O. The statement + +```f90 +write *, var +``` + +writes the value of the target of var and not the pointer descriptor +itself. + +A pointer can point to another pointer, and hence to its target, or to a +static object that has the `target` attribute: + +```f90 +real, pointer :: object +real, target :: target_obj +var => object ! pointer assignment +var => target_obj +``` + +but they are strongly typed: + +```f90 +integer, pointer :: int_var +var => int_var ! illegal - types must match +``` + +and, similarly, for arrays the ranks as well as the type must agree. + +A pointer can be a component of a derived type: + +```f90 +type entry ! type for sparse matrix + real :: value + integer :: index + type(entry), pointer :: next ! note recursion +end type entry +``` + +and we can define the beginning of a linked chain of such entries: + +```f90 +type(entry), pointer :: chain +``` + +After suitable allocations and definitions, the first two entries could +be addressed as + +```f90 +chain%value chain%next%value +chain%index chain%next%index +chain%next chain%next%next +``` + +but we would normally define additional pointers to point at, for +instance, the first and current entries in the list. + +## Association + +A pointer's association status is one of Some care has to be taken not +to leave a pointer 'dangling' by use of `deallocate` on its target +without nullifying any other pointer referring to it. + +The intrinsic function `associated` can test the association status of a +defined pointer: + +```f90 +if (associated(ptr)) then +``` + +or between a defined pointer and a defined target (which may, itself, be +a pointer): + +```f90 +if (associated(ptr, target)) then +``` + +An alternative way to initialize a pointer, also in a specification +statement, is to use the `null` function: + +```f90 +real, pointer, dimension(:) :: vector => null() ! compile time +vector => null() ! run time +``` + +## Pointers in expressions and assignments + +For intrinsic types we can 'sweep' pointers over different sets of +target data using the same code without any data movement. Given the +matrix manipulation *y = B C z*, we can write the following code +(although, in this case, the same result could be achieved more simply +by other means): + +```f90 +real, target :: b(10, 10), c(10, 10), r(10), s(10), z(10) +real, pointer :: a(:, :), x(:), y(:) +integer :: mult +: +do mult = 1, 2 + if (mult == 1) then + y => r ! no data movement + a => c + x => z + else + y => s ! no data movement + a => b + x => r + end if + y = matmul(a, x) ! common calculation +end do +``` + +For objects of derived type we have to distinguish between pointer and +normal assignment. In + +```f90 +type(entry), pointer :: first, current +: +first => current +``` + +the assignment causes first to point at current, whereas + +```f90 +first = current +``` + +causes current to overwrite first and is equivalent to + +```f90 +first%value = current%value +first%index = current%index +first%next => current%next +``` + +## Pointer arguments + +If an actual argument is a pointer then, if the dummy argument is also a +pointer, + +- it must have same rank, +- it receives its association status from the actual argument, +- it returns its final association status to the actual argument + (note: the target may be undefined!), +- it may not have the `intent` attribute (it would be ambiguous), +- it requires an interface block. + +If the dummy argument is not a pointer, it becomes associated with the +target of the actual argument: + +```f90 +real, pointer :: a(:, :) +: +allocate (a(80, 80)) +: +call sub(a) +: +subroutine sub(c) + real c(:, :) +``` + +## Pointer functions + +Function results may also have the `pointer` attribute; this is useful +if the result size depends on calculations performed in the function, as +in + +```f90 +use data_handler +real :: x(100) +real, pointer :: y(:) +: +y => compact(x) +``` + +where the module `data_handler` contains + +```f90 +function compact(x) + real, pointer :: compact(:) + real :: x(:) + ! A procedure to remove duplicates from the array x + integer n + : ! Find the number of distinct values, n + allocate (compact(n)) + : ! Copy the distinct values into compact +end function compact +``` + +The result can be used in an expression (but must be associated with a +defined target). + +## Arrays of pointers + +These do not exist as such: given + +```f90 +type(entry) :: rows(n) +``` + +then + +```f90 +rows%next ! illegal +``` + +would be such an object, but with an irregular storage pattern. For this +reason they are not allowed. However, we can achieve the same effect by +defining a derived data type with a pointer as its sole component: + +```f90 +type row + real, pointer :: r(:) +end type +``` + +and then defining arrays of this data type + +```f90 +type(row) :: s(n), t(n) +``` + +where the storage for the rows can be allocated by, for instance, + +```f90 +do i = 1, n + allocate (t(i)%r(1:i)) ! Allocate row i of length i +end do +``` + +The array assignment `s = t` is then equivalent to the pointer +assignments + +```f90 +s(i)%r => t(i)%r +``` + +for all components. + +## Pointers as dynamic aliases + +Given an array + +```f90 +real, target :: table(100, 100) +``` + +that is frequently referenced with the fixed subscripts + +```f90 +table(m:n, p:q) +``` + +these references may be replaced by + +```f90 +real, dimension(:, :), pointer :: window + : +window => table(m:n, p:q) +``` + +The subscripts of window are `1:n - m + 1, 1:q - p + 1`. +Similarly, for `tar%u` (as defined in +[Array elements](array_elements)), +we can use, say, `taru => tar%u` +to point at all the u components of tar, and subscript it as +`taru(1, 2)`. +The subscripts are as those of tar itself. (This replaces yet more of +`equivalence`.) + +In the pointer association `pointer => array_expression` +the lower bounds for `pointer` are determined as if `lbound` was applied +to `array_expression`. Thus, when a pointer is assigned to a whole array +variable, it inherits the lower bounds of the variable, otherwise, the +lower bounds default to `1`. + +[Fortran 2003](https://en.wikipedia.org/wiki/Fortran#Fortran_2003) +allows specifying arbitrary lower bounds on pointer +association, like + +```f90 +window(r:, s:) => table(m:n, p:q) +``` + +so that the bounds of `window` become `r:r + n - m, s:s + q - p`. +[Fortran 95](https://en.wikipedia.org/wiki/Fortran_95) +does not have this feature; however, it can be simulated using the +following trick (based on the pointer association rules for assumed +shape array dummy arguments): + +```f90 +function remap_bounds2(lb1, lb2, array) result(ptr) + integer, intent(in) :: lb1, lb2 + real, dimension(lb1:, lb2:), intent(in), target :: array + real, dimension(:, :), pointer :: ptr + ptr => array +end function +: +window => remap_bounds2(r, s, table(m:n, p:q)) +``` + +The source code of an extended example of the use of pointers to support +a data structure is in +[pointer.f90](ftp://ftp.numerical.rl.ac.uk/pub/MRandC/pointer.f90). diff --git a/source/learn/f95_features/program_units_and_procedures.md b/source/learn/f95_features/program_units_and_procedures.md new file mode 100644 index 00000000000..aaa19179f78 --- /dev/null +++ b/source/learn/f95_features/program_units_and_procedures.md @@ -0,0 +1,377 @@ +# Program units and procedures + +## Definitions + +In order to discuss this topic we need some definitions. In logical +terms, an executable program consists of one *main program* and zero or +more *subprograms* (or *procedures*) - these do something. Subprograms +are either *functions* or *subroutines*, which are either *external, +internal* or *module* subroutines. (External subroutines are what we +knew from FORTRAN 77.) + +From an organizational point of view, however, a complete program +consists of *program units*. These are either *main programs, external +subprograms* or *modules* and can be separately compiled. + +An example of a main (and complete) program is + +```f90 +program test + print*,'Hello world!' +end program test +``` + +An example of a main program and an external subprogram, forming an +executable program, is + +```f90 +program test + call print_message +end program test + +subroutine print_message + print*,'Hello world!' +end subroutine print_message +``` + +The form of a function is + +```f90 +function name(arg1, arg2) ! zero or more arguments + : + name = ... + : +end function name +``` + +The form of reference of a function is `x = name(a, b)`. + +## Internal procedures + +An internal subprogram is one *contained* in another (at a maximum of +one level of nesting) and provides a replacement for the statement +function: + +```f90 +subroutine outer + real x, y + : +contains + subroutine inner + real y + y = x + 1. + : + end subroutine inner ! subroutine mandatory +end subroutine outer +``` + +We say that `outer` is the *host* of `inner`, and that `inner` obtains +access to entities in `outer` by *host association* (e.g. to `x`), +whereas `y` is a *local* variable to `inner`. + +The *scope* of a named entity is a *scoping unit*, here `outer` less +`inner`, and `inner`. + +The names of program units and external procedures are *global*, and the +names of implied-DO variables have a scope of the statement that +contains them. + +(modules)= +## Modules + +Modules are used to package + +- global data (replaces `COMMON` and `BLOCK DATA` from FORTRAN 77); +- type definitions (themselves a scoping unit); +- subprograms (which among other things replaces the use of `ENTRY` from + FORTRAN 77); +- interface blocks (another scoping unit, see + [Interface blocks](interface-blocks)); +- namelist groups (see any textbook). + +An example of a module containing a type definition, interface block and +function subprogram is + +```f90 +module interval_arithmetic + type interval + real lower, upper + end type interval + interface operator(+) + module procedure add_intervals + end interface + : +contains + function add_intervals(a, b) + type(interval), intent(IN) :: a, b + type(interval) add_intervals + add_intervals%lower = a%lower + b%lower + add_intervals%upper = a%upper + b%upper + end function add_intervals ! function mandatory + : +end module interval_arithmetic +``` + +and the simple statement + +```f90 + +use interval_arithmetic +``` + +provides *use association* to all the module's entities. Module +subprograms may, in turn, contain internal subprograms. + +## Controlling accessibility + +The `public` and `private` attributes are used in specifications in +modules to limit the scope of entities. The attribute form is + +```f90 +real, public :: x, y, z ! default +integer, private :: u, v, w +``` + +and the statement form is + +```f90 +public :: x, y, z, operator(.add.) +private :: u, v, w, assignment(=), operator(*) +``` + +The statement form has to be used to limit access to operators, and can +also be used to change the overall default: + +```f90 +private ! sets default for module +public :: only_this +``` + +For derived types there are three possibilities: the type and its +components are all `public`, the type is `public` and its components +`private` (the type only is visible and one can change its details +easily), or all of it is `private` (for internal use in the module +only): + +```f90 +module mine + private + type, public :: list + real x, y + type(list), pointer :: next + end type list + type(list) :: tree + : +end module mine +``` + +The `use` statement's purpose is to gain access to entities in a module. +It has options to resolve name clashes if an imported name is the same +as a local one: + +```f90 +use mine, local_list => list +``` + +or to restrict the used entities to a specified set: + +```f90 +use mine, only : list +``` + +These may be combined: + +```f90 +use mine, only : local_list => list +``` + +## Arguments + +We may specify the intent of dummy arguments: + +```f90 +subroutine shuffle(ncards, cards) + integer, intent(in) :: ncards + integer, intent(out), dimension(ncards) :: cards +``` + +Also, `inout` is possible: here the actual argument must be a variable +(unlike the default case where it may be a constant). + +Arguments may be optional: + +```f90 +subroutine mincon(n, f, x, upper, lower, equalities, inequalities, & + convex, xstart) + real, optional, dimension :: upper, lower + : + if (present(lower)) then ! test for presence of actual argument + : +``` + +allows us to call `mincon` by + +```f90 +call mincon(n, f, x, upper) +``` + +Arguments may be keyword rather than positional (which come first): + +```f90 +call mincon(n, f, x, equalities=0, xstart=x0) +``` + +Optional and keyword arguments are handled by explicit interfaces, that +is with internal or module procedures or with interface blocks. + +## Interface blocks + +Any reference to an internal or module subprogram is through an +interface that is 'explicit' (that is, the compiler can see all the +details). A reference to an external (or dummy) procedure is usually +'implicit' (the compiler assumes the details). However, we can provide +an explicit interface in this case too. It is a copy of the header, +specifications and `end` statement of the procedure concerned, either +placed in a module or inserted directly: + +```f90 +real function minimum(a, b, func) + ! returns the minimum value of the function func(x) + ! in the interval (a,b) + real, intent(in) :: a, b + interface + real function func(x) + real, intent(in) :: x + end function func + end interface + real f, x + : + f = func(x) ! invocation of the user function. + : +end function minimum +``` + +An explicit interface is obligatory for + +- optional and keyword arguments; +- `pointer` and `target` arguments (see + [Pointers](pointers)); +- `pointer` function result; +- new-style array arguments and array functions + ([Array handling](array_handling)). + +It allows full checks at compile time between actual and dummy +arguments. + +**In general, the best way to ensure that a procedure interface is +explicit is either to place the procedure concerned in a module or to +use it as an internal procedure.** + +## Overloading and generic interfaces + +Interface blocks provide the mechanism by which we are able to define +generic names for specific procedures: + +```f90 +interface gamma ! generic name + function sgamma(X) ! specific name + real(selected_real_kind(6)) sgamma, x + end + function dgamma(X) ! specific name + real(selected_real_kind(12)) dgamma, x + end +end interface gamma +``` + +where a given set of specific names corresponding to a generic name must +all be of functions or all of subroutines. If this interface is within a +module, then it is simply + +```f90 +interface gamma + module procedure sgamma, dgamma +end interface +``` + +We can use existing names, e.g. SIN, and the compiler sorts out the +correct association. + +We have already seen the use of interface blocks for defined operators +and assignment (see +[Modules](Modules)). + +## Recursion + +Indirect recursion is useful for multi-dimensional integration. For + +```f90 +volume = integrate(fy, ybounds) +``` + +We might have + +```f90 +recursive function integrate(f, bounds) + ! Integrate f(x) from bounds(1) to bounds(2) + real integrate + interface + function f(x) + real f, x + end function f + end interface + real, dimension(2), intent(in) :: bounds + : +end function integrate +``` + +and to integrate `f(x, y)` over a rectangle: + +```f90 +function fy(y) + use func ! module func contains function f + real fy, y + yval = y + fy = integrate(f, xbounds) +end +``` + +Direct recursion is when a procedure calls itself, as in + +```f90 +recursive function factorial(n) result(res) + integer res, n + if (n .eq. 0) then + res = 1 + else + res = n * factorial(n - 1) + end if +end +``` + +Here, we note the `result` clause and termination test. + +## Pure procedures + +This is a feature for parallel computing. + +In +[the `forall` statement and construct](forall-statement), +any side effects in a function can impede optimization on +a parallel processor the order of execution of the assignments could +affect the results. To control this situation, we add the `pure` keyword +to the `subroutine` or `function` statement an assertion that the +procedure (expressed simply): + +- alters no global variable, +- performs no I/O, +- has no saved variables (variables with the `save` attribute that + retains values between invocations), and +- for functions, does not alter any of its arguments. + +A compiler can check that this is the case, as in + +```f90 +pure function calculate(x) +``` + +All the intrinsic functions are `pure`. diff --git a/source/learn/oop_features_in_fortran/object_based_programming_techniques.md b/source/learn/oop_features_in_fortran/object_based_programming_techniques.md index a366b15ccb5..bfb0da458e4 100644 --- a/source/learn/oop_features_in_fortran/object_based_programming_techniques.md +++ b/source/learn/oop_features_in_fortran/object_based_programming_techniques.md @@ -151,9 +151,9 @@ to be aware of: 1. If all type components have the `private` attribute i.e., the type is **opaque** (not a Fortran term), it can only be used if the type declaration is accessed by host association (this is the same as for - nonallocatable/nonpointer components); -2. especially for container-like types, its semantics may be - incompatible with the programmers intentions for how the objects + nonallocatable/nonpointer components). +2. Especially for container-like types, its semantics may be + incompatible with the programmer's intentions for how the objects should be used. Item 2 is illustrated by the above object setups, specifically: @@ -479,7 +479,7 @@ case of polymorphic objects. ### Implementing move semantics Sometimes it may be necessary to make use of move instead of copy -semantics i.e., create a copy of an object and then getting rid of the +semantics i.e., create a copy of an object and then get rid of the original. The simplest way of doing this is to make use of allocatable (scalar or array) objects,