diff --git a/README.md b/README.md index cbb0515664dc24229e006b3819e01e087d65ff98..f81d79c042ac5486a2a93adf41039e290502de1b 100644 --- a/README.md +++ b/README.md @@ -5,3 +5,1032 @@ This is the repository for the training Learning Fortran ### Instructor **Pierre-Yves Barriat** + +###### CISM/CÉCI Training Sessions + +--- + +# Fortran : shall we start ? + +- You know already one computer language ? +- You understand the very basic programming concepts : + - What is a variable, an assignment, function call, etc.? + - Why do I have to compile my code? + - What is an executable? +- You (may) already know some Fortran ? +- How to proceed from old Fortran, to much more modern languages like Fortran 90/2003 ? + +--- + +# Why to learn Fortran ? + +- Because of the execution `speed` of a program +- Well suited for numerical computations : +more than 45% of scientific applications are in Fortran +- `Fast` code : compilers can optimize well +- Optimized `numerical libraries` available +- Fortran is a `simple` langage and it is (kind-of) `easy to learn` + +--- + +# Fortran is simple + +- **We want to get our science done! Not learn languages!** +- How easy/difficult is it really to learn Fortran ? +- The concept is easy: +*variables, operators, controls, loops, subroutines/functions* +- **Invest some time now, gain big later!** + +--- + +# History + +**FOR**mula **TRAN**slation +> invented 1954-8 by John Backus and his team at IBM + +- FORTRAN 66 (ISO Standard 1972) +- FORTRAN 77 (1978) +- Fortran 90 (1991) +- Fortran 95 (1997) +- Fortran 2003 (2004) → `"standard" version` +- Fortran 2008 (2010) +- Fortran 2018 (11/2018) + +--- + +# Starting with Fortran 77 + +- Old Fortran provides only the absolute minimum! +- Basic features : +data containers (integer, float, ...), arrays, basic operators, loops, I/O, subroutines and functions +- But this version has flaws: +no dynamic memory allocation, old & obsolete constructs, “spaghetti†code, etc. +- Is that enough to write code ? + +--- + +# Fortran 77 → Fortran >90 + +- If Fortran 77 is so simple, why is it then so difficult to write good code? +- Is simple really better? +⇒ Using a language allows us to express our thoughts (on a computer) +- A more sophisticated language allows for more complex thoughts +- More language elements to get organized +⇒ Fortran 90/95/2003 (recursive, OOP, etc) + +--- + +# How to Build a FORTRAN Program + +FORTRAN is a compiled language (like C) so the source code (what you write) must be converted into machine code before it can be executed (e.g. Make command) + + + +--- + +# FORTRAN 77 Format + +This version requires a fixed format for programs + + + +- max length variable names is 6 characters +- alphanumeric only, must start with a letter +- character strings are case sensitive + +--- + +# FORTRAN >90 Format + +Versions >90 relaxe these requirements: + +- comments following statements (! delimiter) +- long variable names (31 characters) +- containing only letters, digits or underscore +- max row length is 132 characters +- can be max 39 continuation lines +- if a line is ended with ampersand (&), the line continues onto the next line +- semicolon (;) as a separator between statements on a single line +- allows free field input + +--- + +# Program Organization + +Most FORTRAN programs consist of a main program and one or more subprograms + +There is a fixed order: + +```Fortran90 +Heading +Declarations +Variable initializations +Program code +Format statements + +Subprogram definitions +(functions & subroutines) +``` + +--- + +# Data Type Declarations + +Basic data types are : + +- `INTEGER` : integer numbers (+/-) +- `REAL` : floating point numbers +- `DOUBLE PRECISION` : extended precision floating point +- `CHARACTER*n` : string with up to **n** characters +- `LOGICAL` : takes on values `.TRUE.` or `.FALSE.` + +--- + +# Data Type Declarations + +`INTEGER` and `REAL` can specify number of bytes to use + +- Default is: `INTEGER*4` and `REAL*4` +- `DOUBLE PRECISION` is same as `REAL*8` + +Arrays of any type must be declared: + +- `DIMENSION A(3,5)` - declares a 3 x 5 array +- `CHARACTER*30 NAME(50)` - directly declares a character array with 30 character strings in each element + +--- + +# Data Type Declarations + +FORTRAN >90 allows user defined types + +```fortran +TYPE my_variable + character(30) :: name + integer :: id + real(8) :: value + integer, dimension(3,3) :: dimIndex +END TYPE variable + +type(my_variable) var +var%name = "salinity" +var%id = 1 +``` + +--- + +# Implicit vs Explicit Declarations + +By default, an implicit type is assumed depending on the first letter of the variable name: + +- `A-H, O-Z` define REAL variables +- `I-N` define INTEGER variables + +Can use the IMPLICIT statement: + +```fortran +IMPLICIT REAL (A-Z) +``` + +> makes all variables REAL if not declared + +--- + +# Implicit vs Explicit Declarations + +```fortran +IMPLICIT CHARACTER*2 (W) +``` + +> makes variables starting with W be 2-character strings + +```fortran +IMPLICIT DOUBLE PRECISION (D) +``` + +> makes variables starting with D be double precision + +**Good habit**: force explicit type declarations + +```fortran +IMPLICIT NONE +``` + +> user must explicitly declare all variable types + +--- + +# Assignment Statements + +**Old** assignment statement: `<label>` `<variable>` = `<expression>` + +- `<label>` : statement label number (1 to 99999) +- `<variable>` : FORTRAN variable +(max 6 characters, alphanumeric only for standard FORTRAN 77) + +**Expression**: + +- Numeric expressions: `VAR = 3.5*COS(THETA)` +- Character expressions: `DAY(1:3) = 'TUE'` +- Relational expressions: `FLAG = ANS .GT. 0` +- Logical expressions: `FLAG = F1 .OR. F2` + +--- + +# Numeric Expressions + +Arithmetic operators: precedence: `**` *(high)* → `-` *(low)* + +| Operator | Function | +| ------------ | --------------- | +| `**` | exponentiation | +| `*` | multiplication | +| `/` | division | +| `+` | addition | +| `-` | subtraction | + +--- + +# Numeric Expressions + +Numeric expressions are up-cast to the highest data type in the expression according to the precedence: + +*(low)* logical → integer → real → complex *(high)* + +and smaller byte size *(low)* to larger byte size *(high)* + +## Example: + +> fortran 77 source code [arith.f](https://gogs.elic.ucl.ac.be/pbarriat/learning-fortran/src/master/src/01_arith.f) + +--- + +# Character Expressions + +Only built-in operator is **Concatenation** defined by `//` + +```fortran +'ILL'//'-'//'ADVISED' +``` + +`character` arrays are most commonly encountered + +- treated like any array (indexed using : notation) +- fixed length (usually padded with blanks) + +--- + +# Character Expressions + +Example: + +```fortran +CHARACTER FAMILY*16 +FAMILY = ‘GEORGE P. BURDELL’ + +PRINT*,FAMILY(:6) +PRINT*,FAMILY(8:9) +PRINT*,FAMILY(11:) +PRINT*,FAMILY(:6)//FAMILY(10:) +``` + +```fortran +GEORGE +P. +BURDELL +GEORGE BURDELL +``` + +--- + +# Relational Expressions + +Two expressions whose values are compared to determine whether the relation is true or false + +- may be numeric (common) or non-numeric + +`character` strings can be compared + +- done character by character +- shorter string is padded with blanks for comparison + +--- + +# Relational Expressions + +| Operator | Relationship | +| ------------ | --------------- | +| `.LT.` or `<` | less than | +| `.LE.` or `<=` | less than or equal to | +| `.EQ.` or `==` | equal to | +| `.NE.` or `/=` | not equal to | +| `.GT.` or `>` | greater than | +| `.GE.` or `>=` | greater than or equal to | + +--- + +# Logical Expressions + +Consists of one or more logical operators and logical, numeric or relational operands + +- values are `.TRUE.` or `.FALSE.` +- need to consider overall operator precedence + +> can combine logical and integer data with logical operators but this is tricky (**avoid!**) + +--- + +# Logical Expressions + +| F77 Operator | >F90 Operator | Example | Meaning | +| --------------- | --------------- | ------------ | --------------- | +| `.AND.` | `&&` | `A .AND. B` | logical `AND` | +| `.OR.` | `\|\|` | `A .OR. B` | logical `OR` | +| `.EQV.` | `==` | `A .EQV. B` | logical equivalence | +| `.NEQV.` | `/=` | `A .NEQV. B` | logical inequivalence | +| `.XOR.` | `/=` | `A .XOR. B` | exclusive `OR` (same as `.NEQV.`) | +| `.NOT.` | `!` | `.NOT. A` | logical negation | + +--- + +# Arrays in FORTRAN + +Arrays can be multi-dimensional (up to 7 in F77) and are indexed using `( )`: + +- `TEST(3)` or `FORCE(4,2)` + +> Indices are by default defined as `1...N` + +We can specify index range in declaration + +- `INTEGER K(0:11)` : `K` is dimensioned from `0-11` (12 elements) + +Arrays are stored in column order (1st column, 2nd column, etc) so accessing by incrementing row index first usually is fastest + +Whole array reference (only in >F90): `K(:)=-8` assigns 8 to all elements in K + +> Avoid `K=-8` assignement + +--- + +# Unconditional `GO TO` in F77 + +This is the only GOTO in FORTRAN 77 + +- Syntax: `GO TO label` +- Unconditional transfer to labeled statement + +```fortran + 10 -code- + GO TO 30 + -code that is bypassed- + 30 -code that is target of GOTO- + -more code- + GO TO 10 +``` + +- **Problem** : leads to confusing *"spaghetti code"* :boom: + +--- + +# `IF ELSE IF` Statement + +Basic version: + +```fortran +IF (KSTAT.EQ.1) THEN + CLASS='FRESHMAN' +ELSE IF (KSTAT.EQ.2) THEN + CLASS='SOPHOMORE' +ELSE IF (KSTAT.EQ.3) THEN + CLASS='JUNIOR' +ELSE IF (KSTAT.EQ.4) THEN + CLASS='SENIOR' +ELSE + CLASS='UNKNOWN' +ENDIF +``` + +--- + +# Spaghetti Code in F77 (and before) + +Use of `GO TO` and arithmetic `IF`'s leads to bad code that is very hard to maintain + +Here is the equivalent of an `IF-THEN-ELSE` statement: + +```fortran + 10 IF (KEY.LT.0) GO TO 20 + TEST=TEST-1 + THETA=ATAN(X,Y) + GO TO 30 + 20 TEST=TEST+1 + THETA=ATAN(-X,Y) + 30 CONTINUE +``` + +Now try to figure out what a complex `IF ELSE IF` statement would look like coded with this kind of simple `IF`... + +--- + +# Loop Statements (old versions) + +`DO` loop: structure that executes a specified number of times + +*Spaghetti Code Version* + +```fortran + K=2 + 10 PRINT*,A(K) + K=K+2 + IF (K.LE.11) GO TO 10 + 20 CONTINUE +``` + +*F77 Version* + +```fortran + DO 100 K=2,10,2 + PRINT*,A(K) + 100 CONTINUE +``` + +--- + +# Loop Statements (>F90) + +```fortran +DO K=2,10,2 + WRITE(*,*) A(K) +END DO +``` + +- Loop _control can include variables and a third parameter to specify increments, including negative values +- Loop always executes ONCE before testing for end condition + +```fortran +READ(*,*) R +DO WHILE (R.GE.0) + VOL=2*PI*R**2*CLEN + READ(*,*) R +END DO +``` + +- Loop will not execute at all if logical_expr is not true at start + +--- + +# Comments on Loop Statements + +In old versions: + +- to transfer out (exit loop), use a `GO TO` +- to skip to next loop, use `GO TO` terminating statement (this is a good reason to always make this a `CONTINUE` statement) + +In new versions: + +- to transfer out (exit loop), use `EXIT` statement and control is transferred to statement following loop end. This means you cannot transfer out of multiple nested loops with a single `EXIT` statement (use named loops if needed - `myloop : do i=1,n`). This is much like a `BREAK` statement in other languages. +- to skip to next loop cycle, use `CYCLE` statement in loop. + +--- + +# File-Directed Input and Output + +Much of early FORTRAN was devoted to reading input data +from Cards and writing to a line printer + +Today, most I/O is to and from a file: it requires more extensive I/O capabilities standardized until FORTRAN 77 + +**I/O** = communication between a program and the outside world + +- opening and closing a file with `OPEN` & `CLOSE` +- data reading & writing with `READ` & `WRITE` +- can use **unformatted** `READ` & `WRITE` if no human readable data are involved (much faster access, smaller files) + +--- + +# `OPEN` & `CLOSE` example + +Once opened, file is referred to by an assigned device number (a unique id) + +```fortran +character(len=*) :: x_name +integer :: ierr, iSize, guess_unit +logical :: itsopen, itexists +! +inquire(file=trim(x_name), size=iSize, number=guess_unit, opened=itsopen, exist=itexists) +if ( itsopen ) close(guess_unit, status='delete') +! +open(902,file=trim(x_name),status='new',iostat=ierr) +! +if (iSize <= 0 .OR. .NOT.itexists) then + open(902,file=trim(x_name),status='new',iostat=ierr) + if (ierr /= 0) then + ... + close(902) + endif + ... +endif +``` + +--- + +# `READ` Statement + +- syntax: `READ(dev_no, format_label) variable_list` +- read a record from `dev_no` using `format_label` and assign results to variables in `variable_list` + +```fortran + READ(105,1000) A,B,C + 1000 FORMAT(3F12.4) +``` + +> device numbers 1-7 are defined as standard I/O devices + +- each `READ` reads one or more lines of data and any remaining data in a line that is read is dropped if not translated to one of the variables in the `variable_list` +- `variable_list` can include implied `DO` such as: `READ(105,1000)(A(I),I=1,10)` + +--- + +# `READ` Statement - cont'd + +- input items can be integer, real or character +- characters must be enclosed in `' '` +- input items are separated by commas +- input items must agree in type with variables in `variable_list` +- each `READ` processes a new record (line) + +```fortran +INTEGER K +REAL(8) A,B +OPEN(105,FILE='path_to_existing_file') +READ(105,*) A,B,K +``` + +> read one line and look for floating point values for A and B and an integer for K + +--- + +# `WRITE` Statement + +- syntax: `WRITE(dev_no, format_label) variable_list` +- write variables in `variable_list` to output `dev_no` using format specified in format statement with `format_label` + +```fortran + WRITE(*,1000) A,B,KEY + 1000 FORMAT(F12.4,E14.5,I6) +``` + +```fortran +|----+----o----+----o----+----o----+----| + 1234.5678 -0.12345E+02 12 +``` + +- device number `*` is by default the screen (or *standard output* - also 6) +- each `WRITE` produces one or more output lines as needed to write out `variable_list` using `format` statement +- `variable_list` can include implied `DO` such as: `WRITE(*,2000)(A(I),I=1,10)` + +<!-- _footer: "" --> + +--- + +# `FORMAT` Statement + +| data type | format descriptors | example | +| --------------- | --------------- | ------------ | +| `integer` | `iw` | `write(*,'(i5)') int` | +| `real` (*decimal*) | `fw.d` | `write(*,'(f7.4)') x` | +| `real` (*exponential*) | `ew.d` | `write(*,'(e12.3)') y` | +| `character` | `a, aw` | `write(*,'(a)') string` | +| `logical` | `lw` | `write(*,'(l2)') test` | +| spaces & tabs | `wx` & `tw` | `write (*,'(i3,2x,f6.3)') i, x` | +| linebreak | `/` | `write (*,'(f6.3,/,f6.3)') x, y` | + +--- + +# `NAMELIST` + +It is possible to pre-define the structure of input and output data using `NAMELIST` in order to make it easier to process with `READ` and `WRITE` statements + +- Use `NAMELIST` to define the data structure +- Use `READ` or `WRITE` with reference to `NAMELIST` to handle the data in the specified format + +> This is not part of standard F77 but it is included in >F90 + +On input, the `NAMELIST` data must be structured as follows: + +```fortran +&INPUT + THICK=0.245, + LENGTH=12.34, + WIDTH=2.34, + DENSITY=0.0034 +/ +``` + +<!-- _footer: "" --> + +--- + +# Internal `WRITE` Statement + +Internal `WRITE` does same as `ENCODE` in F77 : **a cast to string** +> `WRITE (dev_no, format_label) var_list` +> write variables in `var_list` to internal storage defined by character variable used as `dev_no` = default character variable (not an array) + +```fortran +INTEGER*4 J,K +CHARACTER*50 CHAR50 +DATA J,K/1,2/ +... +WRITE(CHAR50,*) J,K +``` + +Results: + +```fortran +CHAR50=' 1 2' +``` + +--- + +# Internal `READ` Statement + +Internal `READ` does same as `DECODE` in F77 : **a cast from string** +> `READ (dev_no, format_label) var_list` +> read variables from internal storage specified by character variable used as `dev_no` = default character variable (not an array) + +```fortran +INTEGER K +REAL A,B +CHARACTER*80 REC80 +DATA REC80/'1.2, 2.3, -5'/ +... +READ(REC80,*) A,B,K +``` + +Results: + +```fortran +A=1.2, B=2.3, K=-5 +``` + +<!-- _footer: "" --> + +--- + +# Structured programming + +Structured programming is based on subprograms (functions and subroutines) and control statements (like `IF` statements or loops) : + +- structure the control-flow of your programs (eg, give up the `GO TO`) +- improved readability +- lower level aspect of coding in a smart way + +It is a **programming paradigm** aimed at improving the quality, clarity, and access time of a computer program + +--- + +# Functions and Subroutines + +`FUNCTION` & `SUBROUTINE` are subprograms that allow structured coding + +- `FUNCTION`: returns a single explicit function value for given function arguments + It’s also a variable → so must be declared ! +- `SUBROUTINE`: any values returned must be returned through the arguments (no explicit subroutine value is returned) +- functions and subroutines are **not recursive in F77** + +Subprograms use a separate namespace for each subprogram so that variables are local to the subprogram + +- variables are passed to subprogram through argument list and returned in function value or through arguments +- variables stored in `COMMON` may be shared between namespaces + +<!-- _footer: "" --> + +--- + +# Functions and Subroutines - cont'd + +Subprograms must include at least one `RETURN` (can have more) and be terminated by an `END` statement + +`FUNCTION` example: + +```fortran +REAL FUNCTION AVG3(A,B,C) +AVG3=(A+B+C)/3 +RETURN +END +``` + +Use: + +```fortran +AV = WEIGHT*AVG3(A1,F2,B2) +``` + +> `FUNCTION` type is implicitly defined as REAL + +--- + +# Functions and Subroutines - cont'd + +Subroutine is invoked using the `CALL` statement + +`SUBROUTINE` example: + +```fortran +SUBROUTINE AVG3S(A,B,C,AVERAGE) +AVERAGE=(A+B+C)/3 +RETURN +END +``` + +Use: + +```fortran +CALL AVG3S(A1,F2,B2,AVR) +RESULT = WEIGHT*AVR +``` + +> any returned values must be returned through argument list + +--- + +# Arguments + +Arguments in subprogram are `dummy` arguments used in place of the real arguments + +- arguments are passed by **reference** (memory address) if given as *symbolic* + the subprogram can then alter the actual argument value since it can access it by reference +- arguments are passed by **value** if given as *literal* (so cannot be modified) + +```fortran +CALL AVG3S(A1,3.4,C1,QAV) +``` + +> 2nd argument is passed by value - QAV contains result + +```fortran +CALL AVG3S(A,C,B,4.1) +``` + +> no return value is available since "4.1" is a value and not a reference to a variable! + +--- + +# Arguments - cont'd + +- `dummy` arguments appearing in a subprogram declaration cannot be an individual array element reference, e.g., `A(2)`, or a *literal*, for obvious reasons! +- arguments used in invocation (by calling program) may be *variables*, *subscripted variables*, *array names*, *literals*, *expressions* or *function names* +- using symbolic arguments (variables or array names) is the **only way** to return a value (result) from a `SUBROUTINE` + +> It is considered **BAD coding practice**, but functions can return values by changing the value of arguments + This type of use should be strictly **avoided**! + +--- + +# Arguments - cont'd + +The `INTENT` keyword (>F90) increases readability and enables better compile-time error checking + +```fortran +SUBROUTINE AVG3S(A,B,C,AVERAGE) + IMPLICIT NONE + REAL, INTENT(IN) :: A, B + REAL, INTENT(INOUT) :: C ! default + REAL, INTENT(OUT) :: AVERAGE + + A = 10 ! Compilation error + C = 10 ! Correct + AVERAGE=(A+B+C)/3 ! Correct +END +``` + +> Compiler uses `INTENT` for error checking and optimization + +--- + +# `FUNCTION` versus Array + +`REMAINDER(4,3)` could be a 2D array or it could be a reference to a function + +If the name, including arguments, **matches an array declaration**, then it is taken to be an array, **otherwise**, it is assumed to be a `FUNCTION` + +Be careful about `implicit` versus `explicit` type declarations with `FUNCTION` + +```fortran +PROGRAM MAIN + INTEGER REMAINDER + ... + KR = REMAINDER(4,3) + ... +END + +INTEGER FUNCTION REMAINDER(INUM,IDEN) + ... +END +``` + +<!-- _footer: "" --> + +--- + +# Arrays with Subprograms + +Arrays present special problems in subprograms + +- must pass by reference to subprogram since there is no way to list array values explicitly as literals +- how do you tell subprogram how large the array is ? + +> Answer varies with FORTRAN version and vendor (dialect)... + +When an array element, e.g. `A(1)`, is used in a subprogram invocation (in calling program), it is passed as a reference (address), just like a simple variable + +When an array is used by name in a subprogram invocation (in calling program), it is passed as a reference to the entire array. In this case the array must be appropriately dimensioned in the subroutine (and this can be tricky...) + +--- + +# Arrays - cont'd + +### Data layout in multi-dimensional arrays + +- always increment the left-most index of multi-dimensional arrays in the innermost loop (i.e. fastest) +- **column major** ordering in Fortran vs. **row major** ordering in C +- a compiler (with sufficient optimization flags) may re-order loops automatically + +```fortran +do j=1,M + do i=1,N ! innermost loop + y(i) = y(i)+ a(i,j)*x(j) ! left-most index is i + end do +end do +``` + +--- + +# Arrays - cont'd + +- dynamically allocate memory for arrays using `ALLOCATABLE` on declaration +- memory is allocated through `ALLOCATE` statement in the code and is deallocated through `DEALLOCATE` statement + +```fortran +integer :: m, n +integer, allocatable :: idx(:) +real, allocatable :: mat(:,:) +m = 100 ; n = 200 +allocate( idx(0:m-1)) +allocate( mat(m, n)) +... +deallocate(idx , mat) +``` + +> It exists many array intrinsic functions: SIZE, SHAPE, SUM, ANY, MINVAL, MAXLOC, RESHAPE, DOT_PRODUCT, TRANSPOSE, WHERE, FORALL, etc + +--- + +# `COMMON` & `MODULE` Statement + +The `COMMON` statement allows variables to have a more extensive scope than otherwise + +- a variable declared in a `Main Program` can be made accessible to subprograms (without appearing in argument lists of a calling statement) +- this can be selective (don't have to share all everywhere) +- **placement**: among type declarations, after `IMPLICIT` or `EXPLICIT`, before `DATA` statements +- can group into **labeled** `COMMON` + +With > F90, it's better to use the `MODULE` subprogram instead of the `COMMON` statement + +--- + +# Modular programming (>F90) + +Modular programming is about separating parts of programs into independent and interchangeable modules : + +- improve testability +- improve maintainability +- re-use of code +- higher level aspect of coding in a smart way +- *separation of concerns* + +The principle is that making significant parts of the code independent, replaceable and independently testable makes your programs **more maintainable** + +--- + +# Subprograms type + +`MODULE` are subprograms that allow modular coding and data encapsulation + +The interface of a subprogram type is **explicit** or **implicit** + +Several types of subprograms: + +- `intrinsic`: explicit - defined by Fortran itself (trignonometric functions, etc) +- `module`: explicit - defined with `MODULE` statement and used with `USE` +- `internal`: explicit - defined with `CONTAINS` statement inside (sub)programs +- `external`: implicit (but can be manually (re)defined explicit) - e.g. **libraries** + +Differ with the **scope**: what data and other subprograms a subprogram can access + +--- + +# `MODULE` type + +```fortran +MODULE example + IMPLICIT NONE + INTEGER, PARAMETER :: index = 10 + REAL(8), SAVE :: latitude +CONTAINS + FUNCTION check(x) RESULT(z) + INTEGER :: x, z + ... + END FUNCTION check +END MODULE example +``` + +```fortran +PROGRAM myprog + USE example, ONLY: check, latitude + IMPLICIT NONE + ... + test = check(a) + ... +END PROGRAM myprog +``` + +<!-- _footer: "" --> + +--- + +# `internal` subprogams + +```fortran +program main + implicit none + integer N + real X(20) + ... + write(*,*), 'Processing x...', process() + ... +contains + logical function process() + ! in this function N and X can be accessed directly (scope of main) + ! Please not that this method is not recommended: + ! it would be better to pass X as an argument of process + implicit none + if (sum(x) > 5.) then + process = .FALSE. + else + process = .TRUE. + endif + end function process +end program +``` + +<!-- _footer: "" --> + +--- + +# `external` subprogams + +- `external` subprogams are defined in a separate program unit +- to use them in another program unit, refer with the `EXTERNAL` statement +- compiled separately and linked + +**!!! DO NOT USE THEM**: modules are much easier and more robust :exclamation: + +They are only needed when subprogams are written with different programming language or when using external libraries (such as BLAS) + +> It's **highly** recommended to construct `INTERFACE` blocks for any external subprogams used + +--- + +# `interface` statement + +```fortran +SUBROUTINE nag_rand(table) + INTERFACE + SUBROUTINE g05faf(a,b,n,x) + REAL, INTENT(IN) :: a, b + INTEGER, INTENT(IN) :: n + REAL, INTENT(OUT) :: x(n) + END SUBROUTINE g05faf + END INTERFACE + ! + REAL, DIMENSION(:), INTENT(OUT) :: table + ! + call g05faf(-1.0,-1.0, SIZE(table), table) +END SUBROUTINE nag_rand +``` + +<!-- _footer: "" --> + +--- + +# Conclusions + +- Fortran in all its standard versions and vendor-specific dialects is a rich but confusing language +- Fortran is a modern language that continues to evolve + +- Fortran is still ideally suited for numerical computations in engineering and science + - most new language features have been added since F95 + - "High Performance Fortran" includes capabilities designed for parallel processing diff --git a/assets/FortranCISM.html b/assets/FortranCISM.html new file mode 100644 index 0000000000000000000000000000000000000000..d7595b22669bab9e19c8bbae8a0a0612272b97a3 --- /dev/null +++ b/assets/FortranCISM.html @@ -0,0 +1,1133 @@ +<!DOCTYPE html><html lang="en-US"><head><title>Introduction to structured programming with Fortran</title><meta property="og:title" content="Introduction to structured programming with Fortran"><meta name="author" content="P.Y. Barriat"><meta property="article:author" content="P.Y. Barriat"><meta name="description" content="https://dev.to/nikolab/complete-list-of-github-markdown-emoji-markup-5aia"><meta property="og:description" content="https://dev.to/nikolab/complete-list-of-github-markdown-emoji-markup-5aia"><meta charset="UTF-8"><meta name="viewport" content="width=device-width,height=device-height,initial-scale=1.0"><meta name="apple-mobile-web-app-capable" content="yes"><meta http-equiv="X-UA-Compatible" content="ie=edge"><meta property="og:type" content="website"><meta name="twitter:card" content="summary"><style>@media screen{body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>button,body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>button,body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container button,body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container button{-webkit-tap-highlight-color:transparent;-webkit-appearance:none;-moz-appearance:none;appearance:none;background-color:transparent;border:0;color:inherit;cursor:pointer;font-size:inherit;opacity:.8;outline:none;padding:0;transition:opacity .2s linear}body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>button:disabled,body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>button:disabled,body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container button:disabled,body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container button:disabled{cursor:not-allowed;opacity:.15!important}body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>button:hover,body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>button:hover,body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container button:hover,body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container button:hover{opacity:1}body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>button:hover:active,body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>button:hover:active,body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container button:hover:active,body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container button:hover:active{opacity:.6}body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>button:hover:not(:disabled),body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>button:hover:not(:disabled),body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container button:hover:not(:disabled),body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container button:hover:not(:disabled){transition:none}body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=prev],body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=prev],body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container button.bespoke-marp-presenter-info-page-prev{background:transparent url("data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHZpZXdCb3g9IjAgMCAxMDAgMTAwIj48cGF0aCBmaWxsPSJub25lIiBzdHJva2U9IiNmZmYiIHN0cm9rZS1saW5lY2FwPSJyb3VuZCIgc3Ryb2tlLWxpbmVqb2luPSJyb3VuZCIgc3Ryb2tlLXdpZHRoPSI1IiBkPSJNNjggOTAgMjggNTBsNDAtNDAiLz48L3N2Zz4=") no-repeat 50%;background-size:contain;overflow:hidden;text-indent:100%;white-space:nowrap}body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=next],body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=next],body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container button.bespoke-marp-presenter-info-page-next{background:transparent url("data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHZpZXdCb3g9IjAgMCAxMDAgMTAwIj48cGF0aCBmaWxsPSJub25lIiBzdHJva2U9IiNmZmYiIHN0cm9rZS1saW5lY2FwPSJyb3VuZCIgc3Ryb2tlLWxpbmVqb2luPSJyb3VuZCIgc3Ryb2tlLXdpZHRoPSI1IiBkPSJtMzIgOTAgNDAtNDAtNDAtNDAiLz48L3N2Zz4=") no-repeat 50%;background-size:contain;overflow:hidden;text-indent:100%;white-space:nowrap}body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=fullscreen],body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=fullscreen]{background:transparent url("data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHZpZXdCb3g9IjAgMCAxMDAgMTAwIj48ZGVmcz48c3R5bGU+LmF7ZmlsbDpub25lO3N0cm9rZTojZmZmO3N0cm9rZS1saW5lY2FwOnJvdW5kO3N0cm9rZS1saW5lam9pbjpyb3VuZDtzdHJva2Utd2lkdGg6NXB4fTwvc3R5bGU+PC9kZWZzPjxyZWN0IGNsYXNzPSJhIiB4PSIxMCIgeT0iMjAiIHdpZHRoPSI4MCIgaGVpZ2h0PSI2MCIgcng9IjUuNjciLz48cGF0aCBjbGFzcz0iYSIgZD0iTTQwIDcwSDIwVjUwbTIwIDBMMjAgNzBtNDAtNDBoMjB2MjBtLTIwIDAgMjAtMjAiLz48L3N2Zz4=") no-repeat 50%;background-size:contain;overflow:hidden;text-indent:100%;white-space:nowrap}body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>button.exit[data-bespoke-marp-osc=fullscreen],body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>button.exit[data-bespoke-marp-osc=fullscreen]{background-image:url("data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHZpZXdCb3g9IjAgMCAxMDAgMTAwIj48ZGVmcz48c3R5bGU+LmF7ZmlsbDpub25lO3N0cm9rZTojZmZmO3N0cm9rZS1saW5lY2FwOnJvdW5kO3N0cm9rZS1saW5lam9pbjpyb3VuZDtzdHJva2Utd2lkdGg6NXB4fTwvc3R5bGU+PC9kZWZzPjxyZWN0IGNsYXNzPSJhIiB4PSIxMCIgeT0iMjAiIHdpZHRoPSI4MCIgaGVpZ2h0PSI2MCIgcng9IjUuNjciLz48cGF0aCBjbGFzcz0iYSIgZD0iTTIwIDUwaDIwdjIwbS0yMCAwIDIwLTIwbTQwIDBINjBWMzBtMjAgMEw2MCA1MCIvPjwvc3ZnPg==")}body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=presenter],body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=presenter]{background:transparent url("data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHZpZXdCb3g9IjAgMCAxMDAgMTAwIj48cGF0aCBkPSJNODcuOCA0Ny41Qzg5IDUwIDg3LjcgNTIgODUgNTJIMzVhOC43IDguNyAwIDAgMS03LjItNC41bC0xNS42LTMxQzExIDE0IDEyLjIgMTIgMTUgMTJoNTBhOC44IDguOCAwIDAgMSA3LjIgNC41ek02MCA1MnYzNm0tMTAgMGgyME00NSA0MmgyMCIgZmlsbD0ibm9uZSIgc3Ryb2tlPSIjZmZmIiBzdHJva2UtbGluZWNhcD0icm91bmQiIHN0cm9rZS1saW5lam9pbj0icm91bmQiIHN0cm9rZS13aWR0aD0iNSIvPjwvc3ZnPg==") no-repeat 50%;background-size:contain;overflow:hidden;text-indent:100%;white-space:nowrap}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container button.bespoke-marp-presenter-note-bigger{background:transparent url("data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHZpZXdCb3g9IjAgMCAxMDAgMTAwIj48cGF0aCBkPSJNMTIgNTBoODBNNTIgOTBWMTAiIHN0cm9rZT0iI2ZmZiIgc3Ryb2tlLWxpbmVjYXA9InJvdW5kIiBzdHJva2UtbGluZWpvaW49InJvdW5kIiBzdHJva2Utd2lkdGg9IjUiLz48L3N2Zz4=") no-repeat 50%;background-size:contain;overflow:hidden;text-indent:100%;white-space:nowrap}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container button.bespoke-marp-presenter-note-smaller{background:transparent url("data:image/svg+xml;base64,PHN2ZyB4bWxucz0iaHR0cDovL3d3dy53My5vcmcvMjAwMC9zdmciIHZpZXdCb3g9IjAgMCAxMDAgMTAwIj48cGF0aCBkPSJNMTIgNTBoODAiIGZpbGw9Im5vbmUiIHN0cm9rZT0iI2ZmZiIgc3Ryb2tlLWxpbmVjYXA9InJvdW5kIiBzdHJva2UtbGluZWpvaW49InJvdW5kIiBzdHJva2Utd2lkdGg9IjUiLz48L3N2Zz4=") no-repeat 50%;background-size:contain;overflow:hidden;text-indent:100%;white-space:nowrap}}.bespoke-marp-note,.bespoke-marp-osc,.bespoke-progress-parent{display:none;transition:none}@media screen{body,html{height:100%;margin:0}body{background:#000;overflow:hidden}svg.bespoke-marp-slide{content-visibility:hidden;opacity:0;pointer-events:none;z-index:-1}svg.bespoke-marp-slide.bespoke-marp-active{content-visibility:visible;opacity:1;pointer-events:auto;z-index:0}svg.bespoke-marp-slide.bespoke-marp-active.bespoke-marp-active-ready *{-webkit-animation-name:__bespoke_marp__!important;animation-name:__bespoke_marp__!important}@supports not (content-visibility:hidden){svg.bespoke-marp-slide[data-bespoke-marp-load=hideable]{display:none}svg.bespoke-marp-slide[data-bespoke-marp-load=hideable].bespoke-marp-active{display:block}}[data-bespoke-marp-fragment=inactive]{visibility:hidden}body[data-bespoke-view=""] .bespoke-marp-parent,body[data-bespoke-view=next] .bespoke-marp-parent{bottom:0;left:0;position:absolute;right:0;top:0}body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc,body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc{background:rgba(0,0,0,.65);border-radius:7px;bottom:50px;color:#fff;contain:paint;display:block;font-family:Helvetica,Arial,sans-serif;font-size:16px;left:50%;line-height:0;opacity:1;padding:12px;position:absolute;touch-action:manipulation;transform:translateX(-50%);transition:opacity .2s linear;-webkit-user-select:none;-moz-user-select:none;-ms-user-select:none;user-select:none;white-space:nowrap;will-change:transform;z-index:1}body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>*,body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>*{margin-left:6px}body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>:first-child,body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>:first-child{margin-left:0}body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>span,body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>span{opacity:.8}body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>span[data-bespoke-marp-osc=page],body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>span[data-bespoke-marp-osc=page]{display:inline-block;min-width:140px;text-align:center}body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=fullscreen],body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=next],body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=presenter],body[data-bespoke-view=""] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=prev],body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=fullscreen],body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=next],body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=presenter],body[data-bespoke-view=next] .bespoke-marp-parent>.bespoke-marp-osc>button[data-bespoke-marp-osc=prev]{height:32px;line-height:32px;width:32px}body[data-bespoke-view=""] .bespoke-marp-parent.bespoke-marp-inactive,body[data-bespoke-view=next] .bespoke-marp-parent.bespoke-marp-inactive{cursor:none}body[data-bespoke-view=""] .bespoke-marp-parent.bespoke-marp-inactive>.bespoke-marp-osc,body[data-bespoke-view=next] .bespoke-marp-parent.bespoke-marp-inactive>.bespoke-marp-osc{opacity:0;pointer-events:none}body[data-bespoke-view=""] svg.bespoke-marp-slide,body[data-bespoke-view=next] svg.bespoke-marp-slide{height:100%;left:0;position:absolute;top:0;width:100%}body[data-bespoke-view=""] .bespoke-progress-parent{background:#222;display:flex;height:5px;width:100%}body[data-bespoke-view=""] .bespoke-progress-parent+.bespoke-marp-parent{top:5px}body[data-bespoke-view=""] .bespoke-progress-parent .bespoke-progress-bar{background:#0288d1;flex:0 0 0;transition:flex-basis .2s cubic-bezier(0,1,1,1)}body[data-bespoke-view=next]{background:transparent}body[data-bespoke-view=presenter]{background:#161616}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container{display:grid;font-family:Helvetica,Arial,sans-serif;grid-template:"current dragbar next" minmax(140px,1fr) "current dragbar note" 2fr "info dragbar note" 3em;grid-template-columns:minmax(3px,var(--bespoke-marp-presenter-split-ratio,66%)) 0 minmax(3px,1fr);height:100%;left:0;position:absolute;top:0;width:100%}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-parent{grid-area:current;overflow:hidden;position:relative}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-parent svg.bespoke-marp-slide{height:calc(100% - 40px);left:20px;pointer-events:none;position:absolute;top:20px;-webkit-user-select:none;-moz-user-select:none;-ms-user-select:none;user-select:none;width:calc(100% - 40px)}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-parent svg.bespoke-marp-slide.bespoke-marp-active{filter:drop-shadow(0 3px 10px rgba(0,0,0,.5))}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-dragbar-container{background:#0288d1;cursor:col-resize;grid-area:dragbar;margin-left:-3px;opacity:0;position:relative;transition:opacity .4s linear .1s;width:6px;z-index:10}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-dragbar-container:hover{opacity:1}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-dragbar-container.active{opacity:1;transition-delay:0s}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-next-container{background:#222;cursor:pointer;display:none;grid-area:next;overflow:hidden;position:relative}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-next-container.active{display:block}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-next-container iframe.bespoke-marp-presenter-next{background:transparent;border:0;display:block;filter:drop-shadow(0 3px 10px rgba(0,0,0,.5));height:calc(100% - 40px);left:20px;pointer-events:none;position:absolute;top:20px;-webkit-user-select:none;-moz-user-select:none;-ms-user-select:none;user-select:none;width:calc(100% - 40px)}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container{background:#222;color:#eee;grid-area:note;position:relative;z-index:1}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container button{height:1.5em;line-height:1.5em;width:1.5em}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container .bespoke-marp-presenter-note-wrapper{bottom:0;display:block;left:0;position:absolute;right:0;top:0}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container .bespoke-marp-presenter-note-buttons{background:rgba(0,0,0,.65);border-radius:4px;bottom:0;display:flex;gap:4px;margin:12px;opacity:0;padding:6px;pointer-events:none;position:absolute;right:0;transition:opacity .2s linear}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container .bespoke-marp-presenter-note-buttons:focus-within,body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container .bespoke-marp-presenter-note-wrapper:focus-within+.bespoke-marp-presenter-note-buttons,body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container:hover .bespoke-marp-presenter-note-buttons{opacity:1;pointer-events:auto}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container .bespoke-marp-note{word-wrap:break-word;box-sizing:border-box;font-size:calc(1.1em*var(--bespoke-marp-note-font-scale, 1));height:calc(100% - 40px);margin:20px;overflow:auto;padding-right:3px;scrollbar-color:hsla(0,0%,93%,.5) transparent;scrollbar-width:thin;white-space:pre-wrap;width:calc(100% - 40px)}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container .bespoke-marp-note::-webkit-scrollbar{width:6px}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container .bespoke-marp-note::-webkit-scrollbar-track{background:transparent}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container .bespoke-marp-note::-webkit-scrollbar-thumb{background:hsla(0,0%,93%,.5);border-radius:6px}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container .bespoke-marp-note:empty{pointer-events:none}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container .bespoke-marp-note.active{display:block}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container .bespoke-marp-note p:first-child{margin-top:0}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-note-container .bespoke-marp-note p:last-child{margin-bottom:0}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container{align-items:center;box-sizing:border-box;color:#eee;display:flex;flex-wrap:nowrap;grid-area:info;justify-content:center;overflow:hidden;padding:0 10px}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container .bespoke-marp-presenter-info-page,body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container .bespoke-marp-presenter-info-time,body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container .bespoke-marp-presenter-info-timer{box-sizing:border-box;display:block;padding:0 10px;white-space:nowrap;width:100%}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container button{height:1.5em;line-height:1.5em;width:1.5em}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container .bespoke-marp-presenter-info-page{order:2;text-align:center}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container .bespoke-marp-presenter-info-page .bespoke-marp-presenter-info-page-text{display:inline-block;min-width:120px;text-align:center}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container .bespoke-marp-presenter-info-time{color:#999;order:1;text-align:left}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container .bespoke-marp-presenter-info-timer{color:#999;order:3;text-align:right}body[data-bespoke-view=presenter] .bespoke-marp-presenter-container .bespoke-marp-presenter-info-container .bespoke-marp-presenter-info-timer:hover{cursor:pointer}}@media print{.bespoke-marp-presenter-info-container,.bespoke-marp-presenter-next-container,.bespoke-marp-presenter-note-container{display:none}}</style><style>div#p>svg>foreignObject>section{width:1280px;height:720px;box-sizing:border-box;overflow:hidden;position:relative;scroll-snap-align:center center}div#p>svg>foreignObject>section:after{bottom:0;content:attr(data-marpit-pagination);padding:inherit;pointer-events:none;position:absolute;right:0}div#p>svg>foreignObject>section:not([data-marpit-pagination]):after{display:none}/* Normalization */div#p>svg>foreignObject>section h1{font-size:2em;margin:0.67em 0}div#p>svg>foreignObject>section video::-webkit-media-controls{will-change:transform}@page{size:1280px 720px;margin:0}@media print{body,html{background-color:#fff;margin:0;page-break-inside:avoid;break-inside:avoid-page}div#p>svg>foreignObject>section{page-break-before:always;break-before:page}div#p>svg>foreignObject>section,div#p>svg>foreignObject>section *{-webkit-print-color-adjust:exact!important;animation-delay:0s!important;animation-duration:0s!important;color-adjust:exact!important;transition:none!important}div#p>svg[data-marpit-svg]{display:block;height:100vh;width:100vw}} +/*! + * Marp default theme. + * + * @theme default + * @author Yuki Hattori + * + * @auto-scaling true + * @size 16:9 1280px 720px + * @size 4:3 960px 720px + */div#p>svg>foreignObject>section{-ms-text-size-adjust:100%;-webkit-text-size-adjust:100%;word-wrap:break-word;background-color:#fff;color:#24292f;font-family:-apple-system,BlinkMacSystemFont,Segoe UI,Helvetica,Arial,sans-serif,Apple Color Emoji,Segoe UI Emoji;font-size:16px;line-height:1.5;margin:0}div#p>svg>foreignObject>section{--marpit-root-font-size:16px}div#p>svg>foreignObject>section h1:hover .anchor .octicon-link:before,div#p>svg>foreignObject>section h2:hover .anchor .octicon-link:before,div#p>svg>foreignObject>section h3:hover .anchor .octicon-link:before,div#p>svg>foreignObject>section h4:hover .anchor .octicon-link:before,div#p>svg>foreignObject>section h5:hover .anchor .octicon-link:before,div#p>svg>foreignObject>section h6:hover .anchor .octicon-link:before{background-color:currentColor;content:" ";display:inline-block;height:16px;-webkit-mask-image:url('data:image/svg+xml;charset=utf-8,<svg xmlns="http://www.w3.org/2000/svg" viewBox="0 0 16 16" aria-hidden="true"><path fill-rule="evenodd" d="M7.775 3.275a.75.75 0 0 0 1.06 1.06l1.25-1.25a2 2 0 1 1 2.83 2.83l-2.5 2.5a2 2 0 0 1-2.83 0 .75.75 0 0 0-1.06 1.06 3.5 3.5 0 0 0 4.95 0l2.5-2.5a3.5 3.5 0 0 0-4.95-4.95l-1.25 1.25zm-4.69 9.64a2 2 0 0 1 0-2.83l2.5-2.5a2 2 0 0 1 2.83 0 .75.75 0 0 0 1.06-1.06 3.5 3.5 0 0 0-4.95 0l-2.5 2.5a3.5 3.5 0 0 0 4.95 4.95l1.25-1.25a.75.75 0 0 0-1.06-1.06l-1.25 1.25a2 2 0 0 1-2.83 0z"/></svg>');mask-image:url('data:image/svg+xml;charset=utf-8,<svg xmlns="http://www.w3.org/2000/svg" viewBox="0 0 16 16" aria-hidden="true"><path fill-rule="evenodd" d="M7.775 3.275a.75.75 0 0 0 1.06 1.06l1.25-1.25a2 2 0 1 1 2.83 2.83l-2.5 2.5a2 2 0 0 1-2.83 0 .75.75 0 0 0-1.06 1.06 3.5 3.5 0 0 0 4.95 0l2.5-2.5a3.5 3.5 0 0 0-4.95-4.95l-1.25 1.25zm-4.69 9.64a2 2 0 0 1 0-2.83l2.5-2.5a2 2 0 0 1 2.83 0 .75.75 0 0 0 1.06-1.06 3.5 3.5 0 0 0-4.95 0l-2.5 2.5a3.5 3.5 0 0 0 4.95 4.95l1.25-1.25a.75.75 0 0 0-1.06-1.06l-1.25 1.25a2 2 0 0 1-2.83 0z"/></svg>');width:16px}div#p>svg>foreignObject>section details,div#p>svg>foreignObject>section figcaption,div#p>svg>foreignObject>section figure{display:block}div#p>svg>foreignObject>section summary{display:list-item}div#p>svg>foreignObject>section [hidden]{display:none!important}div#p>svg>foreignObject>section a{background-color:transparent;color:#0969da;text-decoration:none}div#p>svg>foreignObject>section a:active,div#p>svg>foreignObject>section a:hover{outline-width:0}div#p>svg>foreignObject>section abbr[title]{border-bottom:none;-webkit-text-decoration:underline dotted;text-decoration:underline dotted}div#p>svg>foreignObject>section b,div#p>svg>foreignObject>section strong{font-weight:600}div#p>svg>foreignObject>section dfn{font-style:italic}div#p>svg>foreignObject>section h1{border-bottom:1px solid #d8dee4;font-size:2em;font-weight:600;margin:.67em 0;padding-bottom:.3em}div#p>svg>foreignObject>section mark{background-color:#fff8c5;color:#24292f}div#p>svg>foreignObject>section small{font-size:90%}div#p>svg>foreignObject>section sub,div#p>svg>foreignObject>section sup{font-size:75%;line-height:0;position:relative;vertical-align:baseline}div#p>svg>foreignObject>section sub{bottom:-.25em}div#p>svg>foreignObject>section sup{top:-.5em}div#p>svg>foreignObject>section img{background-color:#fff;border-style:none;box-sizing:content-box;max-width:100%}div#p>svg>foreignObject>section code,div#p>svg>foreignObject>section kbd,div#p>svg>foreignObject>section pre,div#p>svg>foreignObject>section samp{font-family:monospace,monospace;font-size:1em}div#p>svg>foreignObject>section figure{margin:1em 40px}div#p>svg>foreignObject>section hr{background:transparent;background-color:#d0d7de;border:0;box-sizing:content-box;height:.25em;margin:24px 0;overflow:hidden;padding:0}div#p>svg>foreignObject>section input{font:inherit;font-family:inherit;font-size:inherit;line-height:inherit;margin:0;overflow:visible}div#p>svg>foreignObject>section [type=button],div#p>svg>foreignObject>section [type=reset],div#p>svg>foreignObject>section [type=submit]{-webkit-appearance:button}div#p>svg>foreignObject>section [type=button]::-moz-focus-inner,div#p>svg>foreignObject>section [type=reset]::-moz-focus-inner,div#p>svg>foreignObject>section [type=submit]::-moz-focus-inner{border-style:none;padding:0}div#p>svg>foreignObject>section [type=button]:-moz-focusring,div#p>svg>foreignObject>section [type=reset]:-moz-focusring,div#p>svg>foreignObject>section [type=submit]:-moz-focusring{outline:1px dotted ButtonText}div#p>svg>foreignObject>section [type=checkbox],div#p>svg>foreignObject>section [type=radio]{box-sizing:border-box;padding:0}div#p>svg>foreignObject>section [type=number]::-webkit-inner-spin-button,div#p>svg>foreignObject>section [type=number]::-webkit-outer-spin-button{height:auto}div#p>svg>foreignObject>section [type=search]{-webkit-appearance:textfield;outline-offset:-2px}div#p>svg>foreignObject>section [type=search]::-webkit-search-cancel-button,div#p>svg>foreignObject>section [type=search]::-webkit-search-decoration{-webkit-appearance:none}div#p>svg>foreignObject>section ::-webkit-input-placeholder{color:inherit;opacity:.54}div#p>svg>foreignObject>section ::-webkit-file-upload-button{-webkit-appearance:button;font:inherit}div#p>svg>foreignObject>section a:hover{text-decoration:underline}div#p>svg>foreignObject>section hr:after,div#p>svg>foreignObject>section hr:before{content:"";display:table}div#p>svg>foreignObject>section hr:after{clear:both}div#p>svg>foreignObject>section table{border-collapse:collapse;border-spacing:0;display:block;max-width:100%;overflow:auto;width:-webkit-max-content;width:-moz-max-content;width:max-content}div#p>svg>foreignObject>section td,div#p>svg>foreignObject>section th{padding:0}div#p>svg>foreignObject>section details summary{cursor:pointer}div#p>svg>foreignObject>section details:not([open])>:not(summary){display:none!important}div#p>svg>foreignObject>section kbd{background-color:#f6f8fa;border:1px solid rgba(175,184,193,.2);border-radius:6px;box-shadow:inset 0 -1px 0 rgba(175,184,193,.2);color:#24292f;display:inline-block;font:11px ui-monospace,SFMono-Regular,SF Mono,Menlo,Consolas,Liberation Mono,monospace;line-height:10px;padding:3px 5px;vertical-align:middle}div#p>svg>foreignObject>section h1,div#p>svg>foreignObject>section h2,div#p>svg>foreignObject>section h3,div#p>svg>foreignObject>section h4,div#p>svg>foreignObject>section h5,div#p>svg>foreignObject>section h6{font-weight:600;line-height:1.25;margin-bottom:16px;margin-top:24px}div#p>svg>foreignObject>section h2{border-bottom:1px solid #d8dee4;font-size:1.5em;font-weight:600;padding-bottom:.3em}div#p>svg>foreignObject>section h3{font-size:1.25em;font-weight:600}div#p>svg>foreignObject>section h4{font-size:1em;font-weight:600}div#p>svg>foreignObject>section h5{font-size:.875em;font-weight:600}div#p>svg>foreignObject>section h6{color:#57606a;font-size:.85em;font-weight:600}div#p>svg>foreignObject>section p{margin-bottom:10px;margin-top:0}div#p>svg>foreignObject>section blockquote{border-left:.25em solid #d0d7de;color:#57606a;margin:0;padding:0 1em}div#p>svg>foreignObject>section ol,div#p>svg>foreignObject>section ul{margin-bottom:0;margin-top:0;padding-left:2em}div#p>svg>foreignObject>section ol ol,div#p>svg>foreignObject>section ul ol{list-style-type:lower-roman}div#p>svg>foreignObject>section ol ol ol,div#p>svg>foreignObject>section ol ul ol,div#p>svg>foreignObject>section ul ol ol,div#p>svg>foreignObject>section ul ul ol{list-style-type:lower-alpha}div#p>svg>foreignObject>section dd{margin-left:0}div#p>svg>foreignObject>section code,div#p>svg>foreignObject>section pre,div#p>svg>foreignObject>section tt{font-family:ui-monospace,SFMono-Regular,SF Mono,Menlo,Consolas,Liberation Mono,monospace;font-size:12px}div#p>svg>foreignObject>section pre{word-wrap:normal;margin-bottom:0;margin-top:0}div#p>svg>foreignObject>section .octicon{fill:currentColor;display:inline-block;overflow:visible!important;vertical-align:text-bottom}div#p>svg>foreignObject>section ::-moz-placeholder{color:#6e7781;opacity:1}div#p>svg>foreignObject>section :-ms-input-placeholder{color:#6e7781;opacity:1}div#p>svg>foreignObject>section ::placeholder{color:#6e7781;opacity:1}div#p>svg>foreignObject>section input::-webkit-inner-spin-button,div#p>svg>foreignObject>section input::-webkit-outer-spin-button{-webkit-appearance:none;appearance:none;margin:0}div#p>svg>foreignObject>section .pl-c{color:#6e7781}div#p>svg>foreignObject>section .pl-c1,div#p>svg>foreignObject>section .pl-s .pl-v{color:#0550ae}div#p>svg>foreignObject>section .pl-e,div#p>svg>foreignObject>section .pl-en{color:#8250df}div#p>svg>foreignObject>section .pl-s .pl-s1,div#p>svg>foreignObject>section .pl-smi{color:#24292f}div#p>svg>foreignObject>section .pl-ent{color:#116329}div#p>svg>foreignObject>section .pl-k{color:#cf222e}div#p>svg>foreignObject>section .pl-pds,div#p>svg>foreignObject>section .pl-s,div#p>svg>foreignObject>section .pl-s .pl-pse .pl-s1,div#p>svg>foreignObject>section .pl-sr,div#p>svg>foreignObject>section .pl-sr .pl-cce,div#p>svg>foreignObject>section .pl-sr .pl-sra,div#p>svg>foreignObject>section .pl-sr .pl-sre{color:#0a3069}div#p>svg>foreignObject>section .pl-smw,div#p>svg>foreignObject>section .pl-v{color:#953800}div#p>svg>foreignObject>section .pl-bu{color:#82071e}div#p>svg>foreignObject>section .pl-ii{background-color:#82071e;color:#f6f8fa}div#p>svg>foreignObject>section .pl-c2{background-color:#cf222e;color:#f6f8fa}div#p>svg>foreignObject>section .pl-sr .pl-cce{color:#116329;font-weight:700}div#p>svg>foreignObject>section .pl-ml{color:#3b2300}div#p>svg>foreignObject>section .pl-mh,div#p>svg>foreignObject>section .pl-mh .pl-en,div#p>svg>foreignObject>section .pl-ms{color:#0550ae;font-weight:700}div#p>svg>foreignObject>section .pl-mi{color:#24292f;font-style:italic}div#p>svg>foreignObject>section .pl-mb{color:#24292f;font-weight:700}div#p>svg>foreignObject>section .pl-md{background-color:#ffebe9;color:#82071e}div#p>svg>foreignObject>section .pl-mi1{background-color:#dafbe1;color:#116329}div#p>svg>foreignObject>section .pl-mc{background-color:#ffd8b5;color:#953800}div#p>svg>foreignObject>section .pl-mi2{background-color:#0550ae;color:#eaeef2}div#p>svg>foreignObject>section .pl-mdr{color:#8250df;font-weight:700}div#p>svg>foreignObject>section .pl-ba{color:#57606a}div#p>svg>foreignObject>section .pl-sg{color:#8c959f}div#p>svg>foreignObject>section .pl-corl{color:#0a3069;text-decoration:underline}div#p>svg>foreignObject>section [data-catalyst]{display:block}div#p>svg>foreignObject>section g-emoji{font-family:Apple Color Emoji,Segoe UI Emoji,Segoe UI Symbol;font-size:1em;font-style:normal!important;font-weight:400;line-height:1;vertical-align:-.075em}div#p>svg>foreignObject>section g-emoji img{height:1em;width:1em}div#p>svg>foreignObject>section:after,div#p>svg>foreignObject>section:before{ + /* content:""; */display:table}div#p>svg>foreignObject>section:after{clear:both}div#p>svg>foreignObject>section>:first-child{margin-top:0!important}div#p>svg>foreignObject>section>:last-child{margin-bottom:0!important}div#p>svg>foreignObject>section a:not([href]){color:inherit;text-decoration:none}div#p>svg>foreignObject>section .absent{color:#cf222e}div#p>svg>foreignObject>section .anchor{float:left;line-height:1;margin-left:-20px;padding-right:4px}div#p>svg>foreignObject>section .anchor:focus{outline:none}div#p>svg>foreignObject>section blockquote,div#p>svg>foreignObject>section details,div#p>svg>foreignObject>section dl,div#p>svg>foreignObject>section ol,div#p>svg>foreignObject>section p,div#p>svg>foreignObject>section pre,div#p>svg>foreignObject>section table,div#p>svg>foreignObject>section ul{margin-bottom:16px;margin-top:0}div#p>svg>foreignObject>section blockquote>:first-child{margin-top:0}div#p>svg>foreignObject>section blockquote>:last-child{margin-bottom:0}div#p>svg>foreignObject>section sup>a:before{content:"["}div#p>svg>foreignObject>section sup>a:after{content:"]"}div#p>svg>foreignObject>section h1 .octicon-link,div#p>svg>foreignObject>section h2 .octicon-link,div#p>svg>foreignObject>section h3 .octicon-link,div#p>svg>foreignObject>section h4 .octicon-link,div#p>svg>foreignObject>section h5 .octicon-link,div#p>svg>foreignObject>section h6 .octicon-link{color:#24292f;vertical-align:middle;visibility:hidden}div#p>svg>foreignObject>section h1:hover .anchor,div#p>svg>foreignObject>section h2:hover .anchor,div#p>svg>foreignObject>section h3:hover .anchor,div#p>svg>foreignObject>section h4:hover .anchor,div#p>svg>foreignObject>section h5:hover .anchor,div#p>svg>foreignObject>section h6:hover .anchor{text-decoration:none}div#p>svg>foreignObject>section h1:hover .anchor .octicon-link,div#p>svg>foreignObject>section h2:hover .anchor .octicon-link,div#p>svg>foreignObject>section h3:hover .anchor .octicon-link,div#p>svg>foreignObject>section h4:hover .anchor .octicon-link,div#p>svg>foreignObject>section h5:hover .anchor .octicon-link,div#p>svg>foreignObject>section h6:hover .anchor .octicon-link{visibility:visible}div#p>svg>foreignObject>section h1 code,div#p>svg>foreignObject>section h1 tt,div#p>svg>foreignObject>section h2 code,div#p>svg>foreignObject>section h2 tt,div#p>svg>foreignObject>section h3 code,div#p>svg>foreignObject>section h3 tt,div#p>svg>foreignObject>section h4 code,div#p>svg>foreignObject>section h4 tt,div#p>svg>foreignObject>section h5 code,div#p>svg>foreignObject>section h5 tt,div#p>svg>foreignObject>section h6 code,div#p>svg>foreignObject>section h6 tt{font-size:inherit;padding:0 .2em}div#p>svg>foreignObject>section ol.no-list,div#p>svg>foreignObject>section ul.no-list{list-style-type:none;padding:0}div#p>svg>foreignObject>section ol[type="1"]{list-style-type:decimal}div#p>svg>foreignObject>section ol[type=a]{list-style-type:lower-alpha}div#p>svg>foreignObject>section ol[type=i]{list-style-type:lower-roman}div#p>svg>foreignObject>section div>ol:not([type]){list-style-type:decimal}div#p>svg>foreignObject>section ol ol,div#p>svg>foreignObject>section ol ul,div#p>svg>foreignObject>section ul ol,div#p>svg>foreignObject>section ul ul{margin-bottom:0;margin-top:0}div#p>svg>foreignObject>section li>p{margin-top:16px}div#p>svg>foreignObject>section li+li{margin-top:.25em}div#p>svg>foreignObject>section dl{padding:0}div#p>svg>foreignObject>section dl dt{font-size:1em;font-style:italic;font-weight:600;margin-top:16px;padding:0}div#p>svg>foreignObject>section dl dd{margin-bottom:16px;padding:0 16px}div#p>svg>foreignObject>section table th{font-weight:600}div#p>svg>foreignObject>section table td,div#p>svg>foreignObject>section table th{border:1px solid #d0d7de;padding:6px 13px}div#p>svg>foreignObject>section table tr{background-color:#fff;border-top:1px solid #d8dee4}div#p>svg>foreignObject>section table tr:nth-child(2n){background-color:#f6f8fa}div#p>svg>foreignObject>section table img{background-color:transparent}div#p>svg>foreignObject>section img[align=right]{padding-left:20px}div#p>svg>foreignObject>section img[align=left]{padding-right:20px}div#p>svg>foreignObject>section .emoji{background-color:transparent;max-width:none;vertical-align:text-top}div#p>svg>foreignObject>section span.frame,div#p>svg>foreignObject>section span.frame>span{display:block;overflow:hidden}div#p>svg>foreignObject>section span.frame>span{border:1px solid #d0d7de;float:left;margin:13px 0 0;padding:7px;width:auto}div#p>svg>foreignObject>section span.frame span img{display:block;float:left}div#p>svg>foreignObject>section span.frame span span{clear:both;color:#24292f;display:block;padding:5px 0 0}div#p>svg>foreignObject>section span.align-center{clear:both;display:block;overflow:hidden}div#p>svg>foreignObject>section span.align-center>span{display:block;margin:13px auto 0;overflow:hidden;text-align:center}div#p>svg>foreignObject>section span.align-center span img{margin:0 auto;text-align:center}div#p>svg>foreignObject>section span.align-right{clear:both;display:block;overflow:hidden}div#p>svg>foreignObject>section span.align-right>span{display:block;margin:13px 0 0;overflow:hidden;text-align:right}div#p>svg>foreignObject>section span.align-right span img{margin:0;text-align:right}div#p>svg>foreignObject>section span.float-left{display:block;float:left;margin-right:13px;overflow:hidden}div#p>svg>foreignObject>section span.float-left span{margin:13px 0 0}div#p>svg>foreignObject>section span.float-right{display:block;float:right;margin-left:13px;overflow:hidden}div#p>svg>foreignObject>section span.float-right>span{display:block;margin:13px auto 0;overflow:hidden;text-align:right}div#p>svg>foreignObject>section code,div#p>svg>foreignObject>section tt{background-color:rgba(175,184,193,.2);border-radius:6px;font-size:85%;margin:0;padding:.2em .4em}div#p>svg>foreignObject>section code br,div#p>svg>foreignObject>section tt br{display:none}div#p>svg>foreignObject>section del code{text-decoration:inherit}div#p>svg>foreignObject>section pre code{font-size:100%}div#p>svg>foreignObject>section pre>code{background:transparent;border:0;margin:0;padding:0;white-space:pre;word-break:normal}div#p>svg>foreignObject>section .highlight{margin-bottom:16px}div#p>svg>foreignObject>section .highlight pre{margin-bottom:0;word-break:normal}div#p>svg>foreignObject>section pre{background-color:#f6f8fa;border-radius:6px;font-size:85%;line-height:1.45;overflow:auto;padding:16px}div#p>svg>foreignObject>section pre code,div#p>svg>foreignObject>section pre tt{word-wrap:normal;background-color:transparent;border:0;display:inline;line-height:inherit;margin:0;max-width:auto;overflow:visible;padding:0}div#p>svg>foreignObject>section .csv-data td,div#p>svg>foreignObject>section .csv-data th{font-size:12px;line-height:1;overflow:hidden;padding:5px;text-align:left;white-space:nowrap}div#p>svg>foreignObject>section .csv-data .blob-num{background:#fff;border:0;padding:10px 8px 9px;text-align:right}div#p>svg>foreignObject>section .csv-data tr{border-top:0}div#p>svg>foreignObject>section .csv-data th{background:#f6f8fa;border-top:0;font-weight:600}div#p>svg>foreignObject>section .footnotes{border-top:1px solid #d0d7de;color:#57606a;font-size:12px}div#p>svg>foreignObject>section div#p>svg>foreignObject>section section.footnotes{--marpit-root-font-size:12px}div#p>svg>foreignObject>section .footnotes ol{padding-left:16px}div#p>svg>foreignObject>section .footnotes li{position:relative}div#p>svg>foreignObject>section .footnotes li:target:before{border:2px solid #0969da;border-radius:6px;bottom:-8px;content:"";left:-24px;pointer-events:none;position:absolute;right:-8px;top:-8px}div#p>svg>foreignObject>section .footnotes li:target{color:#24292f}div#p>svg>foreignObject>section .footnotes .data-footnote-backref g-emoji{font-family:monospace}div#p>svg>foreignObject>section .task-list-item{list-style-type:none}div#p>svg>foreignObject>section .task-list-item label{font-weight:400}div#p>svg>foreignObject>section .task-list-item.enabled label{cursor:pointer}div#p>svg>foreignObject>section .task-list-item+.task-list-item{margin-top:3px}div#p>svg>foreignObject>section .task-list-item .handle{display:none}div#p>svg>foreignObject>section .task-list-item-checkbox{margin:0 .2em .25em -1.6em;vertical-align:middle}div#p>svg>foreignObject>section .contains-task-list:dir(rtl) .task-list-item-checkbox{margin:0 -1.6em .25em .2em}div#p>svg>foreignObject>section ::-webkit-calendar-picker-indicator{filter:invert(50%)}div#p>svg>foreignObject>section .hljs{background:#fff;color:#333;display:block;overflow-x:auto;padding:.5em}div#p>svg>foreignObject>section .hljs-comment,div#p>svg>foreignObject>section .hljs-meta{color:#969896}div#p>svg>foreignObject>section .hljs-emphasis,div#p>svg>foreignObject>section .hljs-quote,div#p>svg>foreignObject>section .hljs-strong,div#p>svg>foreignObject>section .hljs-template-variable,div#p>svg>foreignObject>section .hljs-variable{color:#df5000}div#p>svg>foreignObject>section .hljs-keyword,div#p>svg>foreignObject>section .hljs-selector-tag,div#p>svg>foreignObject>section .hljs-type{color:#d73a49}div#p>svg>foreignObject>section .hljs-attribute,div#p>svg>foreignObject>section .hljs-bullet,div#p>svg>foreignObject>section .hljs-literal,div#p>svg>foreignObject>section .hljs-symbol{color:#0086b3}div#p>svg>foreignObject>section .hljs-name,div#p>svg>foreignObject>section .hljs-section{color:#63a35c}div#p>svg>foreignObject>section .hljs-tag{color:#333}div#p>svg>foreignObject>section .hljs-attr,div#p>svg>foreignObject>section .hljs-selector-attr,div#p>svg>foreignObject>section .hljs-selector-class,div#p>svg>foreignObject>section .hljs-selector-id,div#p>svg>foreignObject>section .hljs-selector-pseudo,div#p>svg>foreignObject>section .hljs-title{color:#6f42c1}div#p>svg>foreignObject>section .hljs-addition{background-color:#eaffea;color:#55a532}div#p>svg>foreignObject>section .hljs-deletion{background-color:#ffecec;color:#bd2c00}div#p>svg>foreignObject>section .hljs-link{text-decoration:underline}div#p>svg>foreignObject>section .hljs-number{color:#005cc5}div#p>svg>foreignObject>section .hljs-string{color:#032f62}div#p>svg>foreignObject>section svg[data-marp-fitting=svg]{max-height:563px}div#p>svg>foreignObject>section h1{color:#246;font-size:1.6em}div#p>svg>foreignObject>section h1,div#p>svg>foreignObject>section h2{border-bottom:none}div#p>svg>foreignObject>section h2{font-size:1.3em}div#p>svg>foreignObject>section h3{font-size:1.1em}div#p>svg>foreignObject>section h4{font-size:1.05em}div#p>svg>foreignObject>section h5{font-size:1em}div#p>svg>foreignObject>section h6{font-size:.9em}div#p>svg>foreignObject>section h1 strong,div#p>svg>foreignObject>section h2 strong,div#p>svg>foreignObject>section h3 strong,div#p>svg>foreignObject>section h4 strong,div#p>svg>foreignObject>section h5 strong,div#p>svg>foreignObject>section h6 strong{color:#48c;font-weight:inherit}div#p>svg>foreignObject>section hr{height:0;padding-top:.25em}div#p>svg>foreignObject>section pre{border:1px solid #999;line-height:1.15;overflow:visible}div#p>svg>foreignObject>section pre code svg[data-marp-fitting=svg]{max-height:529px}div#p>svg>foreignObject>section footer,div#p>svg>foreignObject>section header{color:hsla(0,0%,40%,.75);font-size:18px;left:30px;margin:0;position:absolute}div#p>svg>foreignObject>section header{top:21px}div#p>svg>foreignObject>section footer{bottom:21px}div#p>svg>foreignObject>section{align-items:stretch;background:#fff;display:flex;flex-flow:column nowrap;font-size:29px;height:720px;justify-content:center;padding:78.5px;width:1280px}div#p>svg>foreignObject>section{--marpit-root-font-size:29px}div#p>svg>foreignObject>section>:last-child,div#p>svg>foreignObject>section[data-footer]>:nth-last-child(2){margin-bottom:0}div#p>svg>foreignObject>section>:first-child,div#p>svg>foreignObject>section>header:first-child+*{margin-top:0}div#p>svg>foreignObject>section:after{bottom:21px;color:#777;font-size:24px;padding:0;position:absolute;right:30px}div#p>svg>foreignObject>section:after{--marpit-root-font-size:24px}div#p>svg>foreignObject>section.invert{background-color:#222;color:#e6eaf0}div#p>svg>foreignObject>section.invert:after{color:#999}div#p>svg>foreignObject>section.invert img{background-color:transparent}div#p>svg>foreignObject>section.invert a{color:#50b3ff}div#p>svg>foreignObject>section.invert h1{color:#a3c5e7}div#p>svg>foreignObject>section.invert h2,div#p>svg>foreignObject>section.invert h3,div#p>svg>foreignObject>section.invert h4,div#p>svg>foreignObject>section.invert h5{color:#ebeff5}div#p>svg>foreignObject>section.invert blockquote,div#p>svg>foreignObject>section.invert h6{border-color:#3d3f43;color:#939699}div#p>svg>foreignObject>section.invert h1 strong,div#p>svg>foreignObject>section.invert h2 strong,div#p>svg>foreignObject>section.invert h3 strong,div#p>svg>foreignObject>section.invert h4 strong,div#p>svg>foreignObject>section.invert h5 strong,div#p>svg>foreignObject>section.invert h6 strong{color:#7bf}div#p>svg>foreignObject>section.invert hr{background-color:#3d3f43}div#p>svg>foreignObject>section.invert footer,div#p>svg>foreignObject>section.invert header{color:hsla(0,0%,60%,.75)}div#p>svg>foreignObject>section.invert code,div#p>svg>foreignObject>section.invert kbd{background-color:#111}div#p>svg>foreignObject>section.invert kbd{border-color:#666;box-shadow:inset 0 -1px 0 #555;color:#e6eaf0}div#p>svg>foreignObject>section.invert table tr{background-color:#12181d;border-color:#60657b}div#p>svg>foreignObject>section.invert table tr:nth-child(2n){background-color:#1b2024}div#p>svg>foreignObject>section.invert table td,div#p>svg>foreignObject>section.invert table th{border-color:#5b5e61}div#p>svg>foreignObject>section.invert pre{background-color:#0a0e12;border-color:#777}div#p>svg>foreignObject>section.invert pre code{background-color:transparent}div#p>svg>foreignObject>section[data-color] h1,div#p>svg>foreignObject>section[data-color] h2,div#p>svg>foreignObject>section[data-color] h3,div#p>svg>foreignObject>section[data-color] h4,div#p>svg>foreignObject>section[data-color] h5,div#p>svg>foreignObject>section[data-color] h6{color:currentcolor}div#p>svg>foreignObject>section svg[data-marp-fitting=svg]{display:block;height:auto;width:100%}@supports (-ms-ime-align:auto){div#p>svg>foreignObject>section svg[data-marp-fitting=svg]{position:static}}div#p>svg>foreignObject>section svg[data-marp-fitting=svg].__reflow__{content:""}@supports (-ms-ime-align:auto){div#p>svg>foreignObject>section svg[data-marp-fitting=svg].__reflow__{position:relative}}div#p>svg>foreignObject>section [data-marp-fitting-svg-content]{display:table;white-space:nowrap;width:-webkit-max-content;width:-moz-max-content;width:max-content}div#p>svg>foreignObject>section [data-marp-fitting-svg-content-wrap]{white-space:pre}div#p>svg>foreignObject>section img[data-marp-twemoji]{background:transparent;height:1em;margin:0 .05em 0 .1em;vertical-align:-.1em;width:1em} + +/* @theme tum */div#p>svg>foreignObject>section{ + /*background-color: #fff; + color: #000; + background-image: url('images/TUM_Logo_blau_rgb_s.svg'); + background-repeat: no-repeat; + background-position: right 40px top 40px; + background-size: 8%;*/}div#p>svg>foreignObject>section.lead{ + /*background-image: url('images/TUM_Uhrenturm.png'); + background-position: right; + background-size: 45%;*/}div#p>svg>foreignObject>section h1,div#p>svg>foreignObject>section h2{color:#1f315c}div#p>svg>foreignObject>section a{color:#5fb2e6}div#p>svg>foreignObject>section footer,div#p>svg>foreignObject>section:after{color:#9cb7d4}div#p>svg>foreignObject>section.invert{background-color:#003359;color:#fff + /*background-image: url('images/TUM_Logo_weiss_rgb_s.svg');*/}div#p>svg>foreignObject>section.lead.invert{ + /*background-image: url('images/TUM_Uhrenturm_w.png');*/}div#p>svg>foreignObject>section.invert footer,div#p>svg>foreignObject>section.invert h1,div#p>svg>foreignObject>section.invert:after{color:#fff}div#p>svg>foreignObject>section.invert a{color:#e37222} + +/* Add "Page" prefix and total page number */div#p>svg>foreignObject>section:after{content:attr(data-marpit-pagination) ' / ' attr(data-marpit-pagination-total)} + +/* @theme vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm */div#p>svg>foreignObject>section[data-marpit-advanced-background=background]{columns:initial!important;display:block!important;padding:0!important}div#p>svg>foreignObject>section[data-marpit-advanced-background=background]:after,div#p>svg>foreignObject>section[data-marpit-advanced-background=background]:before,div#p>svg>foreignObject>section[data-marpit-advanced-background=content]:after,div#p>svg>foreignObject>section[data-marpit-advanced-background=content]:before{display:none!important}div#p>svg>foreignObject>section[data-marpit-advanced-background=background]>div[data-marpit-advanced-background-container]{all:initial;display:flex;flex-direction:row;height:100%;overflow:hidden;width:100%}div#p>svg>foreignObject>section[data-marpit-advanced-background=background]>div[data-marpit-advanced-background-container][data-marpit-advanced-background-direction=vertical]{flex-direction:column}div#p>svg>foreignObject>section[data-marpit-advanced-background=background][data-marpit-advanced-background-split]>div[data-marpit-advanced-background-container]{width:var(--marpit-advanced-background-split,50%)}div#p>svg>foreignObject>section[data-marpit-advanced-background=background][data-marpit-advanced-background-split=right]>div[data-marpit-advanced-background-container]{margin-left:calc(100% - var(--marpit-advanced-background-split, 50%))}div#p>svg>foreignObject>section[data-marpit-advanced-background=background]>div[data-marpit-advanced-background-container]>figure{all:initial;background-position:center;background-repeat:no-repeat;background-size:cover;flex:auto;margin:0}div#p>svg>foreignObject>section[data-marpit-advanced-background=content],div#p>svg>foreignObject>section[data-marpit-advanced-background=pseudo]{background:transparent!important}div#p>svg>foreignObject>section[data-marpit-advanced-background=pseudo],div#p>svg[data-marpit-svg]>foreignObject[data-marpit-advanced-background=pseudo]{pointer-events:none!important}div#p>svg>foreignObject>section[data-marpit-advanced-background-split]{width:100%;height:100%}</style></head><body><div class="bespoke-progress-parent"><div class="bespoke-progress-bar"></div></div><div class="bespoke-marp-osc"><button data-bespoke-marp-osc="prev" tabindex="-1" title="Previous slide">Previous slide</button><span data-bespoke-marp-osc="page"></span><button data-bespoke-marp-osc="next" tabindex="-1" title="Next slide">Next slide</button><button data-bespoke-marp-osc="fullscreen" tabindex="-1" title="Toggle fullscreen (f)">Toggle fullscreen</button><button data-bespoke-marp-osc="presenter" tabindex="-1" title="Open presenter view (p)">Open presenter view</button></div><div id="p"><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="1" data-background-image="url('assets/garde.png')" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" style="--background-image:url('assets/garde.png');--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/garde.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1><svg data-marp-fitting="svg"><foreignObject><span data-marp-fitting-svg-content>Introduction to structured programming with <code>Fortran</code></span></foreignObject></svg></h1> +<p><a href="https://gogs.elic.ucl.ac.be/pbarriat/learning-fortran">https://gogs.elic.ucl.ac.be/pbarriat/learning-fortran</a></p> +<p><img src="assets/fortran_logo.png" alt="" style="height:150px;" /></p> +<h3>Pierre-Yves Barriat</h3> +<h5>November 09, 2022</h5> +<h6>CISM/CÉCI Training Sessions</h6> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="2" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="2" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Fortran : shall we start ?</h1> +<ul> +<li>You know already one computer language ?</li> +<li>You understand the very basic programming concepts : +<ul> +<li>What is a variable, an assignment, function call, etc.?</li> +<li>Why do I have to compile my code?</li> +<li>What is an executable?</li> +</ul> +</li> +<li>You (may) already know some Fortran ?</li> +<li>How to proceed from old Fortran, to much more modern languages like Fortran 90/2003 ?</li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="3" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="3" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Why to learn Fortran ?</h1> +<ul> +<li>Because of the execution <code>speed</code> of a program</li> +<li>Well suited for numerical computations :<br /> +more than 45% of scientific applications are in Fortran</li> +<li><code>Fast</code> code : compilers can optimize well</li> +<li>Optimized <code>numerical libraries</code> available</li> +<li>Fortran is a <code>simple</code> langage and it is (kind-of) <code>easy to learn</code></li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="4" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="4" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Fortran is simple</h1> +<ul> +<li><strong>We want to get our science done! Not learn languages!</strong></li> +<li>How easy/difficult is it really to learn Fortran ?</li> +<li>The concept is easy:<br /> +<em>variables, operators, controls, loops, subroutines/functions</em></li> +<li><strong>Invest some time now, gain big later!</strong></li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="5" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="5" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>History</h1> +<p><strong>FOR</strong>mula <strong>TRAN</strong>slation</p> +<blockquote> +<p>invented 1954-8 by John Backus and his team at IBM</p> +</blockquote> +<ul> +<li>FORTRAN 66 (ISO Standard 1972)</li> +<li>FORTRAN 77 (1978)</li> +<li>Fortran 90 (1991)</li> +<li>Fortran 95 (1997)</li> +<li>Fortran 2003 (2004) → <code>"standard" version</code></li> +<li>Fortran 2008 (2010)</li> +<li>Fortran 2018 (11/2018)</li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="6" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="6" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Starting with Fortran 77</h1> +<ul> +<li>Old Fortran provides only the absolute minimum!</li> +<li>Basic features :<br /> +data containers (integer, float, ...), arrays, basic operators, loops, I/O, subroutines and functions</li> +<li>But this version has flaws:<br /> +no dynamic memory allocation, old & obsolete constructs, “spaghetti†code, etc.</li> +<li>Is that enough to write code ?</li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="7" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="7" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Fortran 77 → Fortran >90</h1> +<ul> +<li>If Fortran 77 is so simple, why is it then so difficult to write good code?</li> +<li>Is simple really better?<br /> +⇒ Using a language allows us to express our thoughts (on a computer)</li> +<li>A more sophisticated language allows for more complex thoughts</li> +<li>More language elements to get organized<br /> +⇒ Fortran 90/95/2003 (recursive, OOP, etc)</li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="8" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="8" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>How to Build a FORTRAN Program</h1> +<p>FORTRAN is a compiled language (like C) so the source code (what you write) must be converted into machine code before it can be executed (e.g. Make command)</p> +<p><img src="assets/build_fortran.png" alt="" style="height:400px;" /></p> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="9" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="9" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>FORTRAN 77 Format</h1> +<p>This version requires a fixed format for programs</p> +<p><img src="assets/f77_format.png" alt="" style="height:300px;" /></p> +<ul> +<li>max length variable names is 6 characters</li> +<li>alphanumeric only, must start with a letter</li> +<li>character strings are case sensitive</li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="10" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="10" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>FORTRAN >90 Format</h1> +<p>Versions >90 relaxe these requirements:</p> +<ul> +<li>comments following statements (! delimiter)</li> +<li>long variable names (31 characters)</li> +<li>containing only letters, digits or underscore</li> +<li>max row length is 132 characters</li> +<li>can be max 39 continuation lines</li> +<li>if a line is ended with ampersand (&), the line continues onto the next line</li> +<li>semicolon (;) as a separator between statements on a single line</li> +<li>allows free field input</li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="11" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="11" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Program Organization</h1> +<p>Most FORTRAN programs consist of a main program and one or more subprograms</p> +<p>There is a fixed order:</p> +<pre><code class="language-Fortran90"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap>Heading +Declarations +Variable initializations +Program code +Format statements + +Subprogram definitions +(functions & subroutines) +</span></span></foreignObject></svg></code></pre> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="12" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="12" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Data Type Declarations</h1> +<p>Basic data types are :</p> +<ul> +<li><code>INTEGER</code> : integer numbers (+/-)</li> +<li><code>REAL</code> : floating point numbers</li> +<li><code>DOUBLE PRECISION</code> : extended precision floating point</li> +<li><code>CHARACTER*n</code> : string with up to <strong>n</strong> characters</li> +<li><code>LOGICAL</code> : takes on values <code>.TRUE.</code> or <code>.FALSE.</code></li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="13" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="13" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Data Type Declarations</h1> +<p><code>INTEGER</code> and <code>REAL</code> can specify number of bytes to use</p> +<ul> +<li>Default is: <code>INTEGER*4</code> and <code>REAL*4</code></li> +<li><code>DOUBLE PRECISION</code> is same as <code>REAL*8</code></li> +</ul> +<p>Arrays of any type must be declared:</p> +<ul> +<li><code>DIMENSION A(3,5)</code> - declares a 3 x 5 array</li> +<li><code>CHARACTER*30 NAME(50)</code> - directly declares a character array with 30 character strings in each element</li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="14" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="14" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Data Type Declarations</h1> +<p>FORTRAN >90 allows user defined types</p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">TYPE</span> my_variable + <span class="hljs-keyword">character</span>(<span class="hljs-number">30</span>) :: <span class="hljs-keyword">name</span> + <span class="hljs-keyword">integer</span> :: id + <span class="hljs-keyword">real</span>(<span class="hljs-number">8</span>) :: <span class="hljs-keyword">value</span> + <span class="hljs-keyword">integer</span>, <span class="hljs-keyword">dimension</span>(<span class="hljs-number">3</span>,<span class="hljs-number">3</span>) :: dimIndex +<span class="hljs-keyword">END</span> <span class="hljs-keyword">TYPE</span> variable + +<span class="hljs-keyword">type</span>(my_variable) var +var%<span class="hljs-keyword">name</span> = <span class="hljs-string">"salinity"</span> +var%id = <span class="hljs-number">1</span> +</span></span></foreignObject></svg></code></pre> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="15" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="15" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Implicit vs Explicit Declarations</h1> +<p>By default, an implicit type is assumed depending on the first letter of the variable name:</p> +<ul> +<li><code>A-H, O-Z</code> define REAL variables</li> +<li><code>I-N</code> define INTEGER variables</li> +</ul> +<p>Can use the IMPLICIT statement:</p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">IMPLICIT</span> <span class="hljs-keyword">REAL</span> (A-Z) +</span></span></foreignObject></svg></code></pre> +<blockquote> +<p>makes all variables REAL if not declared</p> +</blockquote> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="16" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="16" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Implicit vs Explicit Declarations</h1> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">IMPLICIT</span> <span class="hljs-keyword">CHARACTER</span>*<span class="hljs-number">2</span> (W) +</span></span></foreignObject></svg></code></pre> +<blockquote> +<p>makes variables starting with W be 2-character strings</p> +</blockquote> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">IMPLICIT</span> <span class="hljs-keyword">DOUBLE</span> <span class="hljs-keyword">PRECISION</span> (D) +</span></span></foreignObject></svg></code></pre> +<blockquote> +<p>makes variables starting with D be double precision</p> +</blockquote> +<p><strong>Good habit</strong>: force explicit type declarations</p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">IMPLICIT</span> <span class="hljs-keyword">NONE</span> +</span></span></foreignObject></svg></code></pre> +<blockquote> +<p>user must explicitly declare all variable types</p> +</blockquote> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="17" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="17" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Assignment Statements</h1> +<p><strong>Old</strong> assignment statement: <code><label></code> <code><variable></code> = <code><expression></code></p> +<ul> +<li><code><label></code> : statement label number (1 to 99999)</li> +<li><code><variable></code> : FORTRAN variable<br /> +(max 6 characters, alphanumeric only for standard FORTRAN 77)</li> +</ul> +<p><strong>Expression</strong>:</p> +<ul> +<li>Numeric expressions: <code>VAR = 3.5*COS(THETA)</code></li> +<li>Character expressions: <code>DAY(1:3) = 'TUE'</code></li> +<li>Relational expressions: <code>FLAG = ANS .GT. 0</code></li> +<li>Logical expressions: <code>FLAG = F1 .OR. F2</code></li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="18" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="18" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Numeric Expressions</h1> +<p>Arithmetic operators: precedence: <code>**</code> <em>(high)</em> → <code>-</code> <em>(low)</em></p> +<table> +<thead> +<tr> +<th>Operator</th> +<th>Function</th> +</tr> +</thead> +<tbody> +<tr> +<td><code>**</code></td> +<td>exponentiation</td> +</tr> +<tr> +<td><code>*</code></td> +<td>multiplication</td> +</tr> +<tr> +<td><code>/</code></td> +<td>division</td> +</tr> +<tr> +<td><code>+</code></td> +<td>addition</td> +</tr> +<tr> +<td><code>-</code></td> +<td>subtraction</td> +</tr> +</tbody> +</table> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="19" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="19" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Numeric Expressions</h1> +<p>Numeric expressions are up-cast to the highest data type in the expression according to the precedence:</p> +<p><em>(low)</em> logical → integer → real → complex <em>(high)</em></p> +<p>and smaller byte size <em>(low)</em> to larger byte size <em>(high)</em></p> +<h2>Example:</h2> +<blockquote> +<p>fortran 77 source code <a href="https://gogs.elic.ucl.ac.be/pbarriat/learning-fortran/src/master/src/01_arith.f">arith.f</a></p> +</blockquote> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="20" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="20" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Character Expressions</h1> +<p>Only built-in operator is <strong>Concatenation</strong> defined by <code>//</code></p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-string">'ILL'</span>//<span class="hljs-string">'-'</span>//<span class="hljs-string">'ADVISED'</span> +</span></span></foreignObject></svg></code></pre> +<p><code>character</code> arrays are most commonly encountered</p> +<ul> +<li>treated like any array (indexed using : notation)</li> +<li>fixed length (usually padded with blanks)</li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="21" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="21" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Character Expressions</h1> +<p>Example:</p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">CHARACTER</span> FAMILY*<span class="hljs-number">16</span> +FAMILY = ‘GEORGE P. BURDELL’ + +<span class="hljs-built_in">PRINT</span>*,FAMILY(:<span class="hljs-number">6</span>) +<span class="hljs-built_in">PRINT</span>*,FAMILY(<span class="hljs-number">8</span>:<span class="hljs-number">9</span>) +<span class="hljs-built_in">PRINT</span>*,FAMILY(<span class="hljs-number">11</span>:) +<span class="hljs-built_in">PRINT</span>*,FAMILY(:<span class="hljs-number">6</span>)//FAMILY(<span class="hljs-number">10</span>:) +</span></span></foreignObject></svg></code></pre> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap>GEORGE +P. +BURDELL +GEORGE BURDELL +</span></span></foreignObject></svg></code></pre> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="22" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="22" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Relational Expressions</h1> +<p>Two expressions whose values are compared to determine whether the relation is true or false</p> +<ul> +<li>may be numeric (common) or non-numeric</li> +</ul> +<p><code>character</code> strings can be compared</p> +<ul> +<li>done character by character</li> +<li>shorter string is padded with blanks for comparison</li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="23" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="23" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Relational Expressions</h1> +<table> +<thead> +<tr> +<th>Operator</th> +<th>Relationship</th> +</tr> +</thead> +<tbody> +<tr> +<td><code>.LT.</code> or <code><</code></td> +<td>less than</td> +</tr> +<tr> +<td><code>.LE.</code> or <code><=</code></td> +<td>less than or equal to</td> +</tr> +<tr> +<td><code>.EQ.</code> or <code>==</code></td> +<td>equal to</td> +</tr> +<tr> +<td><code>.NE.</code> or <code>/=</code></td> +<td>not equal to</td> +</tr> +<tr> +<td><code>.GT.</code> or <code>></code></td> +<td>greater than</td> +</tr> +<tr> +<td><code>.GE.</code> or <code>>=</code></td> +<td>greater than or equal to</td> +</tr> +</tbody> +</table> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="24" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="24" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Logical Expressions</h1> +<p>Consists of one or more logical operators and logical, numeric or relational operands</p> +<ul> +<li>values are <code>.TRUE.</code> or <code>.FALSE.</code></li> +<li>need to consider overall operator precedence</li> +</ul> +<blockquote> +<p>can combine logical and integer data with logical operators but this is tricky (<strong>avoid!</strong>)</p> +</blockquote> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="25" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="25" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Logical Expressions</h1> +<table> +<thead> +<tr> +<th>F77 Operator</th> +<th>>F90 Operator</th> +<th>Example</th> +<th>Meaning</th> +</tr> +</thead> +<tbody> +<tr> +<td><code>.AND.</code></td> +<td><code>&&</code></td> +<td><code>A .AND. B</code></td> +<td>logical <code>AND</code></td> +</tr> +<tr> +<td><code>.OR.</code></td> +<td><code>||</code></td> +<td><code>A .OR. B</code></td> +<td>logical <code>OR</code></td> +</tr> +<tr> +<td><code>.EQV.</code></td> +<td><code>==</code></td> +<td><code>A .EQV. B</code></td> +<td>logical equivalence</td> +</tr> +<tr> +<td><code>.NEQV.</code></td> +<td><code>/=</code></td> +<td><code>A .NEQV. B</code></td> +<td>logical inequivalence</td> +</tr> +<tr> +<td><code>.XOR.</code></td> +<td><code>/=</code></td> +<td><code>A .XOR. B</code></td> +<td>exclusive <code>OR</code> (same as <code>.NEQV.</code>)</td> +</tr> +<tr> +<td><code>.NOT.</code></td> +<td><code>!</code></td> +<td><code>.NOT. A</code></td> +<td>logical negation</td> +</tr> +</tbody> +</table> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="26" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="26" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Arrays in FORTRAN</h1> +<p>Arrays can be multi-dimensional (up to 7 in F77) and are indexed using <code>( )</code>:</p> +<ul> +<li><code>TEST(3)</code> or <code>FORCE(4,2)</code></li> +</ul> +<blockquote> +<p>Indices are by default defined as <code>1...N</code></p> +</blockquote> +<p>We can specify index range in declaration</p> +<ul> +<li><code>INTEGER K(0:11)</code> : <code>K</code> is dimensioned from <code>0-11</code> (12 elements)</li> +</ul> +<p>Arrays are stored in column order (1st column, 2nd column, etc) so accessing by incrementing row index first usually is fastest</p> +<p>Whole array reference (only in >F90): <code>K(:)=-8</code> assigns 8 to all elements in K</p> +<blockquote> +<p>Avoid <code>K=-8</code> assignement</p> +</blockquote> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="27" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="27" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Unconditional <code>GO TO</code> in F77</h1> +<p>This is the only GOTO in FORTRAN 77</p> +<ul> +<li>Syntax: <code>GO TO label</code></li> +<li>Unconditional transfer to labeled statement</li> +</ul> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap> <span class="hljs-number">10</span> -code- + GO TO <span class="hljs-number">30</span> + -code that is bypassed- + <span class="hljs-number">30</span> -code that is <span class="hljs-keyword">target</span> of <span class="hljs-keyword">GOTO</span>- + -more code- + GO TO <span class="hljs-number">10</span> +</span></span></foreignObject></svg></code></pre> +<ul> +<li><strong>Problem</strong> : leads to confusing <em>"spaghetti code"</em> <img class="emoji" draggable="false" alt="💥" src="https://twemoji.maxcdn.com/v/14.0.2/svg/1f4a5.svg" data-marp-twemoji=""/></li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="28" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="28" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1><code>IF ELSE IF</code> Statement</h1> +<p>Basic version:</p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">IF</span> (KSTAT.EQ<span class="hljs-number">.1</span>) <span class="hljs-keyword">THEN</span> + <span class="hljs-keyword">CLASS</span>=<span class="hljs-string">'FRESHMAN'</span> +<span class="hljs-keyword">ELSE</span> <span class="hljs-keyword">IF</span> (KSTAT.EQ<span class="hljs-number">.2</span>) <span class="hljs-keyword">THEN</span> + <span class="hljs-keyword">CLASS</span>=<span class="hljs-string">'SOPHOMORE'</span> +<span class="hljs-keyword">ELSE</span> <span class="hljs-keyword">IF</span> (KSTAT.EQ<span class="hljs-number">.3</span>) <span class="hljs-keyword">THEN</span> + <span class="hljs-keyword">CLASS</span>=<span class="hljs-string">'JUNIOR'</span> +<span class="hljs-keyword">ELSE</span> <span class="hljs-keyword">IF</span> (KSTAT.EQ<span class="hljs-number">.4</span>) <span class="hljs-keyword">THEN</span> + <span class="hljs-keyword">CLASS</span>=<span class="hljs-string">'SENIOR'</span> +<span class="hljs-keyword">ELSE</span> + <span class="hljs-keyword">CLASS</span>=<span class="hljs-string">'UNKNOWN'</span> +<span class="hljs-keyword">ENDIF</span> +</span></span></foreignObject></svg></code></pre> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="29" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="29" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Spaghetti Code in F77 (and before)</h1> +<p>Use of <code>GO TO</code> and arithmetic <code>IF</code>'s leads to bad code that is very hard to maintain</p> +<p>Here is the equivalent of an <code>IF-THEN-ELSE</code> statement:</p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap> <span class="hljs-number">10</span> <span class="hljs-keyword">IF</span> (KEY.LT<span class="hljs-number">.0</span>) GO TO <span class="hljs-number">20</span> + TEST=TEST-<span class="hljs-number">1</span> + THETA=<span class="hljs-built_in">ATAN</span>(X,Y) + GO TO <span class="hljs-number">30</span> + <span class="hljs-number">20</span> TEST=TEST+<span class="hljs-number">1</span> + THETA=<span class="hljs-built_in">ATAN</span>(-X,Y) + <span class="hljs-number">30</span> <span class="hljs-keyword">CONTINUE</span> +</span></span></foreignObject></svg></code></pre> +<p>Now try to figure out what a complex <code>IF ELSE IF</code> statement would look like coded with this kind of simple <code>IF</code>...</p> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="30" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="30" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Loop Statements (old versions)</h1> +<p><code>DO</code> loop: structure that executes a specified number of times</p> +<p><em>Spaghetti Code Version</em></p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap> K=<span class="hljs-number">2</span> + <span class="hljs-number">10</span> <span class="hljs-built_in">PRINT</span>*,A(K) + K=K+<span class="hljs-number">2</span> + <span class="hljs-keyword">IF</span> (K.LE<span class="hljs-number">.11</span>) GO TO <span class="hljs-number">10</span> + <span class="hljs-number">20</span> <span class="hljs-keyword">CONTINUE</span> +</span></span></foreignObject></svg></code></pre> +<p><em>F77 Version</em></p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap> <span class="hljs-keyword">DO</span> <span class="hljs-number">100</span> K=<span class="hljs-number">2</span>,<span class="hljs-number">10</span>,<span class="hljs-number">2</span> + <span class="hljs-built_in">PRINT</span>*,A(K) + <span class="hljs-number">100</span> <span class="hljs-keyword">CONTINUE</span> +</span></span></foreignObject></svg></code></pre> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="31" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="31" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Loop Statements (>F90)</h1> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">DO</span> K=<span class="hljs-number">2</span>,<span class="hljs-number">10</span>,<span class="hljs-number">2</span> + <span class="hljs-built_in">WRITE</span>(*,*) A(K) +<span class="hljs-keyword">END</span> <span class="hljs-keyword">DO</span> +</span></span></foreignObject></svg></code></pre> +<ul> +<li>Loop _control can include variables and a third parameter to specify increments, including negative values</li> +<li>Loop always executes ONCE before testing for end condition</li> +</ul> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap>READ(*,*) R +<span class="hljs-keyword">DO</span> <span class="hljs-keyword">WHILE</span> (R.GE<span class="hljs-number">.0</span>) + VOL=<span class="hljs-number">2</span>*PI*R**<span class="hljs-number">2</span>*CLEN + READ(*,*) R +<span class="hljs-keyword">END</span> <span class="hljs-keyword">DO</span> +</span></span></foreignObject></svg></code></pre> +<ul> +<li>Loop will not execute at all if logical_expr is not true at start</li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="32" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="32" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Comments on Loop Statements</h1> +<p>In old versions:</p> +<ul> +<li>to transfer out (exit loop), use a <code>GO TO</code></li> +<li>to skip to next loop, use <code>GO TO</code> terminating statement (this is a good reason to always make this a <code>CONTINUE</code> statement)</li> +</ul> +<p>In new versions:</p> +<ul> +<li>to transfer out (exit loop), use <code>EXIT</code> statement and control is transferred to statement following loop end. This means you cannot transfer out of multiple nested loops with a single <code>EXIT</code> statement (use named loops if needed - <code>myloop : do i=1,n</code>). This is much like a <code>BREAK</code> statement in other languages.</li> +<li>to skip to next loop cycle, use <code>CYCLE</code> statement in loop.</li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="33" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="33" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>File-Directed Input and Output</h1> +<p>Much of early FORTRAN was devoted to reading input data<br /> +from Cards and writing to a line printer</p> +<p>Today, most I/O is to and from a file: it requires more extensive I/O capabilities standardized until FORTRAN 77</p> +<p><strong>I/O</strong> = communication between a program and the outside world</p> +<ul> +<li>opening and closing a file with <code>OPEN</code> & <code>CLOSE</code></li> +<li>data reading & writing with <code>READ</code> & <code>WRITE</code></li> +<li>can use <strong>unformatted</strong> <code>READ</code> & <code>WRITE</code> if no human readable data are involved (much faster access, smaller files)</li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="34" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="34" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1><code>OPEN</code> & <code>CLOSE</code> example</h1> +<p>Once opened, file is referred to by an assigned device number (a unique id)</p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">character</span>(len=*) :: x_name +<span class="hljs-keyword">integer</span> :: ierr, iSize, guess_unit +<span class="hljs-keyword">logical</span> :: itsopen, itexists +<span class="hljs-comment">!</span> +inquire(<span class="hljs-keyword">file</span>=<span class="hljs-built_in">trim</span>(x_name), <span class="hljs-built_in">size</span>=iSize, <span class="hljs-keyword">number</span>=guess_unit, <span class="hljs-keyword">opened</span>=itsopen, <span class="hljs-keyword">exist</span>=itexists) +<span class="hljs-keyword">if</span> ( itsopen ) close(guess_unit, <span class="hljs-keyword">status</span>=<span class="hljs-string">'delete'</span>) +<span class="hljs-comment">!</span> +open(<span class="hljs-number">902</span>,<span class="hljs-keyword">file</span>=<span class="hljs-built_in">trim</span>(x_name),<span class="hljs-keyword">status</span>=<span class="hljs-string">'new'</span>,<span class="hljs-keyword">iostat</span>=ierr) +<span class="hljs-comment">!</span> +<span class="hljs-keyword">if</span> (iSize <= <span class="hljs-number">0</span> .OR. .NOT.itexists) <span class="hljs-keyword">then</span> + open(<span class="hljs-number">902</span>,<span class="hljs-keyword">file</span>=<span class="hljs-built_in">trim</span>(x_name),<span class="hljs-keyword">status</span>=<span class="hljs-string">'new'</span>,<span class="hljs-keyword">iostat</span>=ierr) + <span class="hljs-keyword">if</span> (ierr /= <span class="hljs-number">0</span>) <span class="hljs-keyword">then</span> + ... + close(<span class="hljs-number">902</span>) + <span class="hljs-keyword">endif</span> + ... +<span class="hljs-keyword">endif</span> +</span></span></foreignObject></svg></code></pre> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="35" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="35" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1><code>READ</code> Statement</h1> +<ul> +<li>syntax: <code>READ(dev_no, format_label) variable_list</code></li> +<li>read a record from <code>dev_no</code> using <code>format_label</code> and assign results to variables in <code>variable_list</code></li> +</ul> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap> READ(<span class="hljs-number">105</span>,<span class="hljs-number">1000</span>) A,B,C + <span class="hljs-number">1000</span> <span class="hljs-keyword">FORMAT</span>(<span class="hljs-number">3</span>F12<span class="hljs-number">.4</span>) +</span></span></foreignObject></svg></code></pre> +<blockquote> +<p>device numbers 1-7 are defined as standard I/O devices</p> +</blockquote> +<ul> +<li>each <code>READ</code> reads one or more lines of data and any remaining data in a line that is read is dropped if not translated to one of the variables in the <code>variable_list</code></li> +<li><code>variable_list</code> can include implied <code>DO</code> such as: <code>READ(105,1000)(A(I),I=1,10)</code></li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="36" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="36" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1><code>READ</code> Statement - cont'd</h1> +<ul> +<li>input items can be integer, real or character</li> +<li>characters must be enclosed in <code>' '</code></li> +<li>input items are separated by commas</li> +<li>input items must agree in type with variables in <code>variable_list</code></li> +<li>each <code>READ</code> processes a new record (line)</li> +</ul> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">INTEGER</span> K +<span class="hljs-keyword">REAL</span>(<span class="hljs-number">8</span>) A,B +OPEN(<span class="hljs-number">105</span>,<span class="hljs-keyword">FILE</span>=<span class="hljs-string">'path_to_existing_file'</span>) +READ(<span class="hljs-number">105</span>,*) A,B,K +</span></span></foreignObject></svg></code></pre> +<blockquote> +<p>read one line and look for floating point values for A and B and an integer for K</p> +</blockquote> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="37" data-background-image="url('assets/back.png')" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="37" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1><code>WRITE</code> Statement</h1> +<ul> +<li>syntax: <code>WRITE(dev_no, format_label) variable_list</code></li> +<li>write variables in <code>variable_list</code> to output <code>dev_no</code> using format specified in format statement with <code>format_label</code></li> +</ul> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap> <span class="hljs-built_in">WRITE</span>(*,<span class="hljs-number">1000</span>) A,B,KEY + <span class="hljs-number">1000</span> <span class="hljs-keyword">FORMAT</span>(F12<span class="hljs-number">.4</span>,E14<span class="hljs-number">.5</span>,I6) +</span></span></foreignObject></svg></code></pre> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap>|----+----o----+----o----+----o----+----| + <span class="hljs-number">1234.5678</span> -<span class="hljs-number">0.12345E+02</span> <span class="hljs-number">12</span> +</span></span></foreignObject></svg></code></pre> +<ul> +<li>device number <code>*</code> is by default the screen (or <em>standard output</em> - also 6)</li> +<li>each <code>WRITE</code> produces one or more output lines as needed to write out <code>variable_list</code> using <code>format</code> statement</li> +<li><code>variable_list</code> can include implied <code>DO</code> such as: <code>WRITE(*,2000)(A(I),I=1,10)</code></li> +</ul> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="38" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="38" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1><code>FORMAT</code> Statement</h1> +<table> +<thead> +<tr> +<th>data type</th> +<th>format descriptors</th> +<th>example</th> +</tr> +</thead> +<tbody> +<tr> +<td><code>integer</code></td> +<td><code>iw</code></td> +<td><code>write(*,'(i5)') int</code></td> +</tr> +<tr> +<td><code>real</code> (<em>decimal</em>)</td> +<td><code>fw.d</code></td> +<td><code>write(*,'(f7.4)') x</code></td> +</tr> +<tr> +<td><code>real</code> (<em>exponential</em>)</td> +<td><code>ew.d</code></td> +<td><code>write(*,'(e12.3)') y</code></td> +</tr> +<tr> +<td><code>character</code></td> +<td><code>a, aw</code></td> +<td><code>write(*,'(a)') string</code></td> +</tr> +<tr> +<td><code>logical</code></td> +<td><code>lw</code></td> +<td><code>write(*,'(l2)') test</code></td> +</tr> +<tr> +<td>spaces & tabs</td> +<td><code>wx</code> & <code>tw</code></td> +<td><code>write (*,'(i3,2x,f6.3)') i, x</code></td> +</tr> +<tr> +<td>linebreak</td> +<td><code>/</code></td> +<td><code>write (*,'(f6.3,/,f6.3)') x, y</code></td> +</tr> +</tbody> +</table> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="39" data-background-image="url('assets/back.png')" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="39" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1><code>NAMELIST</code></h1> +<p>It is possible to pre-define the structure of input and output data using <code>NAMELIST</code> in order to make it easier to process with <code>READ</code> and <code>WRITE</code> statements</p> +<ul> +<li>Use <code>NAMELIST</code> to define the data structure</li> +<li>Use <code>READ</code> or <code>WRITE</code> with reference to <code>NAMELIST</code> to handle the data in the specified format</li> +</ul> +<blockquote> +<p>This is not part of standard F77 but it is included in >F90</p> +</blockquote> +<p>On input, the <code>NAMELIST</code> data must be structured as follows:</p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap>&INPUT + THICK=<span class="hljs-number">0.245</span>, + LENGTH=<span class="hljs-number">12.34</span>, + WIDTH=<span class="hljs-number">2.34</span>, + DENSITY=<span class="hljs-number">0.0034</span> +/ +</span></span></foreignObject></svg></code></pre> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="40" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="40" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Internal <code>WRITE</code> Statement</h1> +<p>Internal <code>WRITE</code> does same as <code>ENCODE</code> in F77 : <strong>a cast to string</strong></p> +<blockquote> +<p><code>WRITE (dev_no, format_label) var_list</code><br /> +write variables in <code>var_list</code> to internal storage defined by character variable used as <code>dev_no</code> = default character variable (not an array)</p> +</blockquote> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">INTEGER</span>*<span class="hljs-number">4</span> J,K +<span class="hljs-keyword">CHARACTER</span>*<span class="hljs-number">50</span> CHAR50 +<span class="hljs-keyword">DATA</span> J,K/<span class="hljs-number">1</span>,<span class="hljs-number">2</span>/ +... +<span class="hljs-built_in">WRITE</span>(CHAR50,*) J,K +</span></span></foreignObject></svg></code></pre> +<p>Results:</p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap>CHAR50=<span class="hljs-string">' 1 2'</span> +</span></span></foreignObject></svg></code></pre> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="41" data-background-image="url('assets/back.png')" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="41" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Internal <code>READ</code> Statement</h1> +<p>Internal <code>READ</code> does same as <code>DECODE</code> in F77 : <strong>a cast from string</strong></p> +<blockquote> +<p><code>READ (dev_no, format_label) var_list</code><br /> +read variables from internal storage specified by character variable used as <code>dev_no</code> = default character variable (not an array)</p> +</blockquote> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">INTEGER</span> K +<span class="hljs-keyword">REAL</span> A,B +<span class="hljs-keyword">CHARACTER</span>*<span class="hljs-number">80</span> REC80 +<span class="hljs-keyword">DATA</span> REC80/<span class="hljs-string">'1.2, 2.3, -5'</span>/ +... +READ(REC80,*) A,B,K +</span></span></foreignObject></svg></code></pre> +<p>Results:</p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap>A=<span class="hljs-number">1.2</span>, B=<span class="hljs-number">2.3</span>, K=-<span class="hljs-number">5</span> +</span></span></foreignObject></svg></code></pre> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="42" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="42" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Structured programming</h1> +<p>Structured programming is based on subprograms (functions and subroutines) and control statements (like <code>IF</code> statements or loops) :</p> +<ul> +<li>structure the control-flow of your programs (eg, give up the <code>GO TO</code>)</li> +<li>improved readability</li> +<li>lower level aspect of coding in a smart way</li> +</ul> +<p>It is a <strong>programming paradigm</strong> aimed at improving the quality, clarity, and access time of a computer program</p> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="43" data-background-image="url('assets/back.png')" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="43" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Functions and Subroutines</h1> +<p><code>FUNCTION</code> & <code>SUBROUTINE</code> are subprograms that allow structured coding</p> +<ul> +<li><code>FUNCTION</code>: returns a single explicit function value for given function arguments<br /> +It’s also a variable → so must be declared !</li> +<li><code>SUBROUTINE</code>: any values returned must be returned through the arguments (no explicit subroutine value is returned)</li> +<li>functions and subroutines are <strong>not recursive in F77</strong></li> +</ul> +<p>Subprograms use a separate namespace for each subprogram so that variables are local to the subprogram</p> +<ul> +<li>variables are passed to subprogram through argument list and returned in function value or through arguments</li> +<li>variables stored in <code>COMMON</code> may be shared between namespaces</li> +</ul> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="44" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="44" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Functions and Subroutines - cont'd</h1> +<p>Subprograms must include at least one <code>RETURN</code> (can have more) and be terminated by an <code>END</code> statement</p> +<p><code>FUNCTION</code> example:</p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">REAL</span> <span class="hljs-function"><span class="hljs-keyword">FUNCTION</span></span> AVG3(A,B,C) +AVG3=(A+B+C)/<span class="hljs-number">3</span> +<span class="hljs-keyword">RETURN</span> +<span class="hljs-keyword">END</span> +</span></span></foreignObject></svg></code></pre> +<p>Use:</p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap>AV = WEIGHT*AVG3(A1,F2,B2) +</span></span></foreignObject></svg></code></pre> +<blockquote> +<p><code>FUNCTION</code> type is implicitly defined as REAL</p> +</blockquote> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="45" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="45" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Functions and Subroutines - cont'd</h1> +<p>Subroutine is invoked using the <code>CALL</code> statement</p> +<p><code>SUBROUTINE</code> example:</p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-function"><span class="hljs-keyword">SUBROUTINE</span></span> AVG3S(A,B,C,AVERAGE) +AVERAGE=(A+B+C)/<span class="hljs-number">3</span> +<span class="hljs-keyword">RETURN</span> +<span class="hljs-keyword">END</span> +</span></span></foreignObject></svg></code></pre> +<p>Use:</p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">CALL</span> AVG3S(A1,F2,B2,AVR) +RESULT = WEIGHT*AVR +</span></span></foreignObject></svg></code></pre> +<blockquote> +<p>any returned values must be returned through argument list</p> +</blockquote> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="46" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="46" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Arguments</h1> +<p>Arguments in subprogram are <code>dummy</code> arguments used in place of the real arguments</p> +<ul> +<li>arguments are passed by <strong>reference</strong> (memory address) if given as <em>symbolic</em><br /> +the subprogram can then alter the actual argument value since it can access it by reference</li> +<li>arguments are passed by <strong>value</strong> if given as <em>literal</em> (so cannot be modified)</li> +</ul> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">CALL</span> AVG3S(A1,<span class="hljs-number">3.4</span>,C1,QAV) +</span></span></foreignObject></svg></code></pre> +<blockquote> +<p>2nd argument is passed by value - QAV contains result</p> +</blockquote> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">CALL</span> AVG3S(A,C,B,<span class="hljs-number">4.1</span>) +</span></span></foreignObject></svg></code></pre> +<blockquote> +<p>no return value is available since "4.1" is a value and not a reference to a variable!</p> +</blockquote> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="47" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="47" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Arguments - cont'd</h1> +<ul> +<li><code>dummy</code> arguments appearing in a subprogram declaration cannot be an individual array element reference, e.g., <code>A(2)</code>, or a <em>literal</em>, for obvious reasons!</li> +<li>arguments used in invocation (by calling program) may be <em>variables</em>, <em>subscripted variables</em>, <em>array names</em>, <em>literals</em>, <em>expressions</em> or <em>function names</em></li> +<li>using symbolic arguments (variables or array names) is the <strong>only way</strong> to return a value (result) from a <code>SUBROUTINE</code></li> +</ul> +<blockquote> +<p>It is considered <strong>BAD coding practice</strong>, but functions can return values by changing the value of arguments<br /> +This type of use should be strictly <strong>avoided</strong>!</p> +</blockquote> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="48" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="48" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Arguments - cont'd</h1> +<p>The <code>INTENT</code> keyword (>F90) increases readability and enables better compile-time error checking</p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-function"><span class="hljs-keyword">SUBROUTINE</span></span> AVG3S(A,B,C,AVERAGE) + <span class="hljs-keyword">IMPLICIT</span> <span class="hljs-keyword">NONE</span> + <span class="hljs-keyword">REAL</span>, <span class="hljs-keyword">INTENT</span>(<span class="hljs-keyword">IN</span>) :: A, B + <span class="hljs-keyword">REAL</span>, <span class="hljs-keyword">INTENT</span>(INOUT) :: C <span class="hljs-comment">! default</span> + <span class="hljs-keyword">REAL</span>, <span class="hljs-keyword">INTENT</span>(<span class="hljs-keyword">OUT</span>) :: AVERAGE + + A = <span class="hljs-number">10</span> <span class="hljs-comment">! Compilation error</span> + C = <span class="hljs-number">10</span> <span class="hljs-comment">! Correct</span> + AVERAGE=(A+B+C)/<span class="hljs-number">3</span> <span class="hljs-comment">! Correct</span> +<span class="hljs-keyword">END</span> +</span></span></foreignObject></svg></code></pre> +<blockquote> +<p>Compiler uses <code>INTENT</code> for error checking and optimization</p> +</blockquote> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="49" data-background-image="url('assets/back.png')" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="49" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1><code>FUNCTION</code> versus Array</h1> +<p><code>REMAINDER(4,3)</code> could be a 2D array or it could be a reference to a function</p> +<p>If the name, including arguments, <strong>matches an array declaration</strong>, then it is taken to be an array, <strong>otherwise</strong>, it is assumed to be a <code>FUNCTION</code></p> +<p>Be careful about <code>implicit</code> versus <code>explicit</code> type declarations with <code>FUNCTION</code></p> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-function"><span class="hljs-keyword">PROGRAM</span></span> MAIN + <span class="hljs-keyword">INTEGER</span> REMAINDER + ... + KR = REMAINDER(<span class="hljs-number">4</span>,<span class="hljs-number">3</span>) + ... +<span class="hljs-keyword">END</span> + +<span class="hljs-keyword">INTEGER</span> <span class="hljs-function"><span class="hljs-keyword">FUNCTION</span></span> REMAINDER(INUM,IDEN) + ... +<span class="hljs-keyword">END</span> +</span></span></foreignObject></svg></code></pre> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="50" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="50" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Arrays with Subprograms</h1> +<p>Arrays present special problems in subprograms</p> +<ul> +<li>must pass by reference to subprogram since there is no way to list array values explicitly as literals</li> +<li>how do you tell subprogram how large the array is ?</li> +</ul> +<blockquote> +<p>Answer varies with FORTRAN version and vendor (dialect)...</p> +</blockquote> +<p>When an array element, e.g. <code>A(1)</code>, is used in a subprogram invocation (in calling program), it is passed as a reference (address), just like a simple variable</p> +<p>When an array is used by name in a subprogram invocation (in calling program), it is passed as a reference to the entire array. In this case the array must be appropriately dimensioned in the subroutine (and this can be tricky...)</p> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="51" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="51" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Arrays - cont'd</h1> +<h3>Data layout in multi-dimensional arrays</h3> +<ul> +<li>always increment the left-most index of multi-dimensional arrays in the innermost loop (i.e. fastest)</li> +<li><strong>column major</strong> ordering in Fortran vs. <strong>row major</strong> ordering in C</li> +<li>a compiler (with sufficient optimization flags) may re-order loops automatically</li> +</ul> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">do</span> j=<span class="hljs-number">1</span>,M + <span class="hljs-keyword">do</span> i=<span class="hljs-number">1</span>,N <span class="hljs-comment">! innermost loop</span> + y(i) = y(i)+ a(i,j)*x(j) <span class="hljs-comment">! left-most index is i</span> + <span class="hljs-keyword">end</span> <span class="hljs-keyword">do</span> +<span class="hljs-keyword">end</span> <span class="hljs-keyword">do</span> +</span></span></foreignObject></svg></code></pre> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="52" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="52" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Arrays - cont'd</h1> +<ul> +<li>dynamically allocate memory for arrays using <code>ALLOCATABLE</code> on declaration</li> +<li>memory is allocated through <code>ALLOCATE</code> statement in the code and is deallocated through <code>DEALLOCATE</code> statement</li> +</ul> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">integer</span> :: m, n +<span class="hljs-keyword">integer</span>, <span class="hljs-keyword">allocatable</span> :: idx(:) +<span class="hljs-keyword">real</span>, <span class="hljs-keyword">allocatable</span> :: mat(:,:) +m = <span class="hljs-number">100</span> ; n = <span class="hljs-number">200</span> +<span class="hljs-built_in">allocate</span>( idx(<span class="hljs-number">0</span>:m-<span class="hljs-number">1</span>)) +<span class="hljs-built_in">allocate</span>( mat(m, n)) +... +<span class="hljs-built_in">deallocate</span>(idx , mat) +</span></span></foreignObject></svg></code></pre> +<blockquote> +<p>It exists many array intrinsic functions: SIZE, SHAPE, SUM, ANY, MINVAL, MAXLOC, RESHAPE, DOT_PRODUCT, TRANSPOSE, WHERE, FORALL, etc</p> +</blockquote> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="53" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="53" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1><code>COMMON</code> & <code>MODULE</code> Statement</h1> +<p>The <code>COMMON</code> statement allows variables to have a more extensive scope than otherwise</p> +<ul> +<li>a variable declared in a <code>Main Program</code> can be made accessible to subprograms (without appearing in argument lists of a calling statement)</li> +<li>this can be selective (don't have to share all everywhere)</li> +<li><strong>placement</strong>: among type declarations, after <code>IMPLICIT</code> or <code>EXPLICIT</code>, before <code>DATA</code> statements</li> +<li>can group into <strong>labeled</strong> <code>COMMON</code></li> +</ul> +<p>With > F90, it's better to use the <code>MODULE</code> subprogram instead of the <code>COMMON</code> statement</p> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="54" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="54" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Modular programming (>F90)</h1> +<p>Modular programming is about separating parts of programs into independent and interchangeable modules :</p> +<ul> +<li>improve testability</li> +<li>improve maintainability</li> +<li>re-use of code</li> +<li>higher level aspect of coding in a smart way</li> +<li><em>separation of concerns</em></li> +</ul> +<p>The principle is that making significant parts of the code independent, replaceable and independently testable makes your programs <strong>more maintainable</strong></p> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="55" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="55" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Subprograms type</h1> +<p><code>MODULE</code> are subprograms that allow modular coding and data encapsulation</p> +<p>The interface of a subprogram type is <strong>explicit</strong> or <strong>implicit</strong></p> +<p>Several types of subprograms:</p> +<ul> +<li><code>intrinsic</code>: explicit - defined by Fortran itself (trignonometric functions, etc)</li> +<li><code>module</code>: explicit - defined with <code>MODULE</code> statement and used with <code>USE</code></li> +<li><code>internal</code>: explicit - defined with <code>CONTAINS</code> statement inside (sub)programs</li> +<li><code>external</code>: implicit (but can be manually (re)defined explicit) - e.g. <strong>libraries</strong></li> +</ul> +<p>Differ with the <strong>scope</strong>: what data and other subprograms a subprogram can access</p> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="56" data-background-image="url('assets/back.png')" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="56" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1><code>MODULE</code> type</h1> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-keyword">MODULE</span> example + <span class="hljs-keyword">IMPLICIT</span> <span class="hljs-keyword">NONE</span> + <span class="hljs-keyword">INTEGER</span>, <span class="hljs-keyword">PARAMETER</span> :: <span class="hljs-built_in">index</span> = <span class="hljs-number">10</span> + <span class="hljs-keyword">REAL</span>(<span class="hljs-number">8</span>), <span class="hljs-keyword">SAVE</span> :: latitude +<span class="hljs-keyword">CONTAINS</span> + <span class="hljs-function"><span class="hljs-keyword">FUNCTION</span></span> check(x) RESULT(z) + <span class="hljs-keyword">INTEGER</span> :: x, z + ... + <span class="hljs-keyword">END</span> <span class="hljs-function"><span class="hljs-keyword">FUNCTION</span></span> check +<span class="hljs-keyword">END</span> <span class="hljs-keyword">MODULE</span> example +</span></span></foreignObject></svg></code></pre> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-function"><span class="hljs-keyword">PROGRAM</span></span> myprog + <span class="hljs-keyword">USE</span> example, <span class="hljs-keyword">ONLY</span>: check, latitude + <span class="hljs-keyword">IMPLICIT</span> <span class="hljs-keyword">NONE</span> + ... + test = check(a) + ... +<span class="hljs-keyword">END</span> <span class="hljs-function"><span class="hljs-keyword">PROGRAM</span></span> myprog +</span></span></foreignObject></svg></code></pre> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="57" data-background-image="url('assets/back.png')" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="57" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1><code>internal</code> subprogams</h1> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-function"><span class="hljs-keyword">program</span></span> main + <span class="hljs-keyword">implicit</span> <span class="hljs-keyword">none</span> + <span class="hljs-keyword">integer</span> N + <span class="hljs-keyword">real</span> X(<span class="hljs-number">20</span>) + ... + <span class="hljs-built_in">write</span>(*,*), <span class="hljs-string">'Processing x...'</span>, process() + ... +<span class="hljs-keyword">contains</span> + <span class="hljs-keyword">logical</span> <span class="hljs-function"><span class="hljs-keyword">function</span></span> process() + <span class="hljs-comment">! in this function N and X can be accessed directly (scope of main)</span> + <span class="hljs-comment">! Please not that this method is not recommended:</span> + <span class="hljs-comment">! it would be better to pass X as an argument of process</span> + <span class="hljs-keyword">implicit</span> <span class="hljs-keyword">none</span> + <span class="hljs-keyword">if</span> (<span class="hljs-built_in">sum</span>(x) > <span class="hljs-number">5.</span>) <span class="hljs-keyword">then</span> + process = .FALSE. + <span class="hljs-keyword">else</span> + process = .TRUE. + <span class="hljs-keyword">endif</span> + <span class="hljs-keyword">end</span> <span class="hljs-function"><span class="hljs-keyword">function</span></span> process +<span class="hljs-keyword">end</span> <span class="hljs-function"><span class="hljs-keyword">program</span></span> +</span></span></foreignObject></svg></code></pre> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="58" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="58" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1><code>external</code> subprogams</h1> +<ul> +<li><code>external</code> subprogams are defined in a separate program unit</li> +<li>to use them in another program unit, refer with the <code>EXTERNAL</code> statement</li> +<li>compiled separately and linked</li> +</ul> +<p><strong>!!! DO NOT USE THEM</strong>: modules are much easier and more robust <img class="emoji" draggable="false" alt="â—" src="https://twemoji.maxcdn.com/v/14.0.2/svg/2757.svg" data-marp-twemoji=""/></p> +<p>They are only needed when subprogams are written with different programming language or when using external libraries (such as BLAS)</p> +<blockquote> +<p>It's <strong>highly</strong> recommended to construct <code>INTERFACE</code> blocks for any external subprogams used</p> +</blockquote> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="59" data-background-image="url('assets/back.png')" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="59" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1><code>interface</code> statement</h1> +<pre><code class="language-fortran"><svg data-marp-fitting="svg" data-marp-fitting-code><foreignObject><span data-marp-fitting-svg-content><span data-marp-fitting-svg-content-wrap><span class="hljs-function"><span class="hljs-keyword">SUBROUTINE</span></span> nag_rand(table) + <span class="hljs-keyword">INTERFACE</span> + <span class="hljs-function"><span class="hljs-keyword">SUBROUTINE</span></span> g05faf(a,b,n,x) + <span class="hljs-keyword">REAL</span>, <span class="hljs-keyword">INTENT</span>(<span class="hljs-keyword">IN</span>) :: a, b + <span class="hljs-keyword">INTEGER</span>, <span class="hljs-keyword">INTENT</span>(<span class="hljs-keyword">IN</span>) :: n + <span class="hljs-keyword">REAL</span>, <span class="hljs-keyword">INTENT</span>(<span class="hljs-keyword">OUT</span>) :: x(n) + <span class="hljs-keyword">END</span> <span class="hljs-function"><span class="hljs-keyword">SUBROUTINE</span></span> g05faf + <span class="hljs-keyword">END</span> <span class="hljs-keyword">INTERFACE</span> + <span class="hljs-comment">!</span> + <span class="hljs-keyword">REAL</span>, <span class="hljs-keyword">DIMENSION</span>(:), <span class="hljs-keyword">INTENT</span>(<span class="hljs-keyword">OUT</span>) :: table + <span class="hljs-comment">!</span> + <span class="hljs-keyword">call</span> g05faf(-<span class="hljs-number">1.0</span>,-<span class="hljs-number">1.0</span>, <span class="hljs-built_in">SIZE</span>(table), table) +<span class="hljs-keyword">END</span> <span class="hljs-function"><span class="hljs-keyword">SUBROUTINE</span></span> nag_rand +</span></span></foreignObject></svg></code></pre> +</section> +</foreignObject></svg><svg data-marpit-svg="" viewBox="0 0 1280 720"><foreignObject width="1280" height="720"><section id="60" data-background-image="url('assets/back.png')" data-footer="09/11/2022 | Introduction to structured programming with Fortran" data-paginate="true" data-theme="vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm" data-marpit-pagination="60" data-marpit-pagination-total="60" style="--background-image:url('assets/back.png');--footer:09/11/2022 | Introduction to structured programming with Fortran;--paginate:true;--theme:vnc6mvbjqstkhfawxx2h2q37lry3esagk64kvzu5xm;background-image:url('assets/back.png');background-position:center;background-repeat:no-repeat;background-size:cover;"> +<h1>Conclusions</h1> +<ul> +<li> +<p>Fortran in all its standard versions and vendor-specific dialects is a rich but confusing language</p> +</li> +<li> +<p>Fortran is a modern language that continues to evolve</p> +</li> +<li> +<p>Fortran is still ideally suited for numerical computations in engineering and science</p> +<ul> +<li>most new language features have been added since F95</li> +<li>"High Performance Fortran" includes capabilities designed for parallel processing</li> +</ul> +</li> +</ul> +<footer>09/11/2022 | Introduction to structured programming with Fortran</footer> +</section> +<script>!function(){"use strict";const t="marpitSVGPolyfill:setZoomFactor,",e=Symbol();let r,o;function n(n){const i="object"==typeof n&&n.target||document,a="object"==typeof n?n.zoom:n;window[e]||(Object.defineProperty(window,e,{configurable:!0,value:!0}),window.addEventListener("message",(({data:e,origin:r})=>{if(r===window.origin)try{if(e&&"string"==typeof e&&e.startsWith(t)){const[,t]=e.split(","),r=Number.parseFloat(t);Number.isNaN(r)||(o=r)}}catch(t){console.error(t)}})));let l=!1;Array.from(i.querySelectorAll("svg[data-marpit-svg]"),(t=>{var e,n,i,s;t.style.transform||(t.style.transform="translateZ(0)");const c=a||o||t.currentScale||1;r!==c&&(r=c,l=c);const d=t.getBoundingClientRect(),{length:f}=t.children;for(let r=0;r<f;r+=1){const o=t.children[r];if(o.getScreenCTM){const t=o.getScreenCTM();if(t){const r=null!==(n=null===(e=o.x)||void 0===e?void 0:e.baseVal.value)&&void 0!==n?n:0,a=null!==(s=null===(i=o.y)||void 0===i?void 0:i.baseVal.value)&&void 0!==s?s:0,l=o.children.length;for(let e=0;e<l;e+=1){const n=o.children[e];if("SECTION"===n.tagName){const{style:e}=n;e.transformOrigin||(e.transformOrigin=`${-r}px ${-a}px`),e.transform=`scale(${c}) matrix(${t.a}, ${t.b}, ${t.c}, ${t.d}, ${t.e-d.left}, ${t.f-d.top}) translateZ(0.0001px)`;break}}}}}})),!1!==l&&Array.from(i.querySelectorAll("iframe"),(({contentWindow:e})=>{null==e||e.postMessage(`${t}${l}`,"null"===window.origin?"*":window.origin)}))}r=1,o=void 0;const i=(t,e,r)=>{if(t.getAttribute(e)!==r)return t.setAttribute(e,r),!0};function a({once:t=!1,target:e=document}={}){const r="Apple Computer, Inc."===navigator.vendor?[n]:[];let o=!t;const a=()=>{for(const t of r)t({target:e});!function(t=document){Array.from(t.querySelectorAll('svg[data-marp-fitting="svg"]'),(t=>{var e;const r=t.firstChild,o=r.firstChild,{scrollWidth:n,scrollHeight:a}=o;let l,s=1;if(t.hasAttribute("data-marp-fitting-code")&&(l=null===(e=t.parentElement)||void 0===e?void 0:e.parentElement),t.hasAttribute("data-marp-fitting-math")&&(l=t.parentElement),l){const t=getComputedStyle(l),e=Math.ceil(l.clientWidth-parseFloat(t.paddingLeft||"0")-parseFloat(t.paddingRight||"0"));e&&(s=e)}const c=Math.max(n,s),d=Math.max(a,1),f=`0 0 ${c} ${d}`;i(r,"width",`${c}`),i(r,"height",`${d}`),i(t,"preserveAspectRatio",getComputedStyle(t).getPropertyValue("--preserve-aspect-ratio")||"xMinYMin meet"),i(t,"viewBox",f)&&t.classList.toggle("__reflow__")}))}(e),o&&window.requestAnimationFrame(a)};return a(),()=>{o=!1}}const l=Symbol(),s=document.currentScript;((t=document)=>{if("undefined"==typeof window)throw new Error("Marp Core's browser script is valid only in browser context.");if(t[l])return t[l];const e=a({target:t}),r=()=>{e(),delete t[l]};Object.defineProperty(t,l,{configurable:!0,value:r})})(s?s.getRootNode():document)}(); +</script></foreignObject></svg></div><div class="bespoke-marp-note" data-index="55" tabindex="0"><p>Notes for presenter.</p><p>```fortran +module subs + +contains + +subroutine asub (i, control) + + implicit none + + integer, intent (in) :: i + logical, intent (in) :: control + + integer, save :: j = 0 + integer :: k + + j = j + i + if ( control ) k = 0 + k = k + i + + write (*, *) 'i, j, k=', i, j, k + +end subroutine asub + +end module subs + +program test_saves + + use subs + implicit none + + call asub ( 3, .TRUE. ) + call asub ( 4, .FALSE. ) + +end program test_saves +``` + +Local variable k of the subroutine is intentionally misused -- in this program it is initialized in the first call since control is TRUE, but on the second call control is FALSE, so k is not redefined. But without the save attribute k is undefined, so the using its value is illegal. + +```fortran + i, j, k= 3 3 3 + i, j, k= 4 7 7 +``` + +Compiling the program with ifort and aggressive optimization options, k lost its value: + +```fortran + i, j, k= 3 3 3 + i, j, k= 4 7 4 +```</p></div><script>/*!! License: https://unpkg.com/@marp-team/marp-cli@1.7.1/lib/bespoke.js.LICENSE.txt */ +!function(){"use strict";const e=document.body,t=(...e)=>history.replaceState(...e),n="presenter",r="next",o=["",n,r],a="data-bespoke-marp-",i=(e,{protocol:t,host:n,pathname:r,hash:o}=location)=>{const a=e.toString();return`${t}//${n}${r}${a?"?":""}${a}${o}`},s=()=>e.dataset.bespokeView,l=e=>new URLSearchParams(location.search).get(e),d=(e,n={})=>{var r;const o={location,setter:t,...n},a=new URLSearchParams(o.location.search);for(const t of Object.keys(e)){const n=e[t];"string"==typeof n?a.set(t,n):a.delete(t)}try{o.setter({...null!==(r=window.history.state)&&void 0!==r?r:{}},"",i(a,o.location))}catch(e){console.error(e)}},c=(()=>{const e="bespoke-marp";try{return localStorage.setItem(e,e),localStorage.removeItem(e),!0}catch(e){return!1}})(),u=e=>{try{return localStorage.getItem(e)}catch(e){return null}},f=(e,t)=>{try{return localStorage.setItem(e,t),!0}catch(e){return!1}},m=e=>{try{return localStorage.removeItem(e),!0}catch(e){return!1}},g=(e,t)=>{const n="aria-hidden";t?e.setAttribute(n,"true"):e.removeAttribute(n)},p=e=>{e.parent.classList.add("bespoke-marp-parent"),e.slides.forEach((e=>e.classList.add("bespoke-marp-slide"))),e.on("activate",(t=>{const n="bespoke-marp-active",r=t.slide,o=r.classList,a=!o.contains(n);if(e.slides.forEach((e=>{e.classList.remove(n),g(e,!0)})),o.add(n),g(r,!1),a){const e=`${n}-ready`;o.add(e),document.body.clientHeight,o.remove(e)}}))},v=e=>{let t=0,n=0;Object.defineProperty(e,"fragments",{enumerable:!0,value:e.slides.map((e=>[null,...e.querySelectorAll("[data-marpit-fragment]")]))});const r=r=>void 0!==e.fragments[t][n+r],o=(r,o)=>{t=r,n=o,e.fragments.forEach(((e,t)=>{e.forEach(((e,n)=>{if(null==e)return;const i=t<r||t===r&&n<=o;e.setAttribute(`${a}fragment`,(i?"":"in")+"active");const s=`${a}current-fragment`;t===r&&n===o?e.setAttribute(s,"current"):e.removeAttribute(s)}))})),e.fragmentIndex=o;const i={slide:e.slides[r],index:r,fragments:e.fragments[r],fragmentIndex:o};e.fire("fragment",i)};e.on("next",(({fragment:a=!0})=>{if(a){if(r(1))return o(t,n+1),!1;const a=t+1;e.fragments[a]&&o(a,0)}else{const r=e.fragments[t].length;if(n+1<r)return o(t,r-1),!1;const a=e.fragments[t+1];a&&o(t+1,a.length-1)}})),e.on("prev",(({fragment:a=!0})=>{if(r(-1)&&a)return o(t,n-1),!1;const i=t-1;e.fragments[i]&&o(i,e.fragments[i].length-1)})),e.on("slide",(({index:t,fragment:n})=>{let r=0;if(void 0!==n){const o=e.fragments[t];if(o){const{length:e}=o;r=-1===n?e-1:Math.min(Math.max(n,0),e-1)}}o(t,r)})),o(0,0)},h=document,y=()=>!(!h.fullscreenEnabled&&!h.webkitFullscreenEnabled),b=()=>!(!h.fullscreenElement&&!h.webkitFullscreenElement),x=e=>{e.fullscreen=()=>{y()&&(async()=>{return b()?null===(e=h.exitFullscreen||h.webkitExitFullscreen)||void 0===e?void 0:e.call(h):((e=h.body)=>{var t;return null===(t=e.requestFullscreen||e.webkitRequestFullscreen)||void 0===t?void 0:t.call(e)})();var e})()},document.addEventListener("keydown",(t=>{"f"!==t.key&&"F11"!==t.key||t.altKey||t.ctrlKey||t.metaKey||!y()||(e.fullscreen(),t.preventDefault())}))},w="bespoke-marp-inactive",k=(e=2e3)=>({parent:t,fire:n})=>{const r=t.classList,o=e=>n(`marp-${e?"":"in"}active`);let a;const i=()=>{a&&clearTimeout(a),a=setTimeout((()=>{r.add(w),o()}),e),r.contains(w)&&(r.remove(w),o(!0))};for(const e of["mousedown","mousemove","touchend"])document.addEventListener(e,i);setTimeout(i,0)},E=["AUDIO","BUTTON","INPUT","SELECT","TEXTAREA","VIDEO"],L=e=>{e.parent.addEventListener("keydown",(e=>{if(!e.target)return;const t=e.target;(E.includes(t.nodeName)||"true"===t.contentEditable)&&e.stopPropagation()}))},$=e=>{window.addEventListener("load",(()=>{for(const t of e.slides){const e=t.querySelector("[data-marp-fitting]")?"":"hideable";t.setAttribute(`${a}load`,e)}}))},S=({interval:e=250}={})=>t=>{document.addEventListener("keydown",(e=>{if(" "===e.key&&e.shiftKey)t.prev();else if("ArrowLeft"===e.key||"ArrowUp"===e.key||"PageUp"===e.key)t.prev({fragment:!e.shiftKey});else if(" "!==e.key||e.shiftKey)if("ArrowRight"===e.key||"ArrowDown"===e.key||"PageDown"===e.key)t.next({fragment:!e.shiftKey});else if("End"===e.key)t.slide(t.slides.length-1,{fragment:-1});else{if("Home"!==e.key)return;t.slide(0)}else t.next();e.preventDefault()}));let n,r,o=0;t.parent.addEventListener("wheel",(a=>{let i=!1;const s=(e,t)=>{e&&(i=i||((e,t)=>((e,t)=>{const n="X"===t?"Width":"Height";return e[`client${n}`]<e[`scroll${n}`]})(e,t)&&((e,t)=>{const{overflow:n}=e,r=e[`overflow${t}`];return"auto"===n||"scroll"===n||"auto"===r||"scroll"===r})(getComputedStyle(e),t))(e,t)),(null==e?void 0:e.parentElement)&&s(e.parentElement,t)};if(0!==a.deltaX&&s(a.target,"X"),0!==a.deltaY&&s(a.target,"Y"),i)return;a.preventDefault();const l=Math.sqrt(a.deltaX**2+a.deltaY**2);if(void 0!==a.wheelDelta){if(void 0===a.webkitForce&&Math.abs(a.wheelDelta)<40)return;if(a.deltaMode===a.DOM_DELTA_PIXEL&&l<4)return}else if(a.deltaMode===a.DOM_DELTA_PIXEL&&l<12)return;r&&clearTimeout(r),r=setTimeout((()=>{n=0}),e);const d=Date.now()-o<e,c=l<=n;if(n=l,d||c)return;let u;(a.deltaX>0||a.deltaY>0)&&(u="next"),(a.deltaX<0||a.deltaY<0)&&(u="prev"),u&&(t[u](),o=Date.now())}))},P=(e=".bespoke-marp-osc")=>{const t=document.querySelector(e);if(!t)return()=>{};const n=(e,n)=>{t.querySelectorAll(`[${a}osc=${JSON.stringify(e)}]`).forEach(n)};return y()||n("fullscreen",(e=>e.style.display="none")),c||n("presenter",(e=>{e.disabled=!0,e.title="Presenter view is disabled due to restricted localStorage."})),e=>{t.addEventListener("click",(t=>{if(t.target instanceof HTMLElement){const{bespokeMarpOsc:n}=t.target.dataset;n&&t.target.blur();const r={fragment:!t.shiftKey};"next"===n?e.next(r):"prev"===n?e.prev(r):"fullscreen"===n?null==e||e.fullscreen():"presenter"===n&&e.openPresenterView()}})),e.parent.appendChild(t),e.on("activate",(({index:t})=>{n("page",(n=>n.textContent=`Page ${t+1} of ${e.slides.length}`))})),e.on("fragment",(({index:t,fragments:r,fragmentIndex:o})=>{n("prev",(e=>e.disabled=0===t&&0===o)),n("next",(n=>n.disabled=t===e.slides.length-1&&o===r.length-1))})),e.on("marp-active",(()=>g(t,!1))),e.on("marp-inactive",(()=>g(t,!0))),y()&&(e=>{for(const t of["","webkit"])h.addEventListener(t+"fullscreenchange",e)})((()=>n("fullscreen",(e=>e.classList.toggle("exit",y()&&b())))))}},T=e=>{window.addEventListener("message",(t=>{if(t.origin!==window.origin)return;const[n,r]=t.data.split(":");if("navigate"===n){const[t,n]=r.split(",");let o=Number.parseInt(t,10),a=Number.parseInt(n,10)+1;a>=e.fragments[o].length&&(o+=1,a=0),e.slide(o,{fragment:a})}}))};var I=["area","base","br","col","command","embed","hr","img","input","keygen","link","meta","param","source","track","wbr"];let N=e=>String(e).replace(/[&<>"']/g,(e=>`&${C[e]};`)),C={"&":"amp","<":"lt",">":"gt",'"':"quot","'":"apos"},A="dangerouslySetInnerHTML",D={className:"class",htmlFor:"for"},M={};function B(e,t){let n=[],r="";t=t||{};for(let e=arguments.length;e-- >2;)n.push(arguments[e]);if("function"==typeof e)return t.children=n.reverse(),e(t);if(e){if(r+="<"+e,t)for(let e in t)!1!==t[e]&&null!=t[e]&&e!==A&&(r+=` ${D[e]?D[e]:N(e)}="${N(t[e])}"`);r+=">"}if(-1===I.indexOf(e)){if(t[A])r+=t[A].__html;else for(;n.length;){let e=n.pop();if(e)if(e.pop)for(let t=e.length;t--;)n.push(e[t]);else r+=!0===M[e]?e:N(e)}r+=e?`</${e}>`:""}return M[r]=!0,r}const K=({children:e})=>B(null,null,...e),O="bespoke-marp-presenter-",q={container:`${O}container`,dragbar:`${O}dragbar-container`,next:`${O}next`,nextContainer:`${O}next-container`,noteContainer:`${O}note-container`,noteWrapper:`${O}note-wrapper`,noteButtons:`${O}note-buttons`,infoContainer:`${O}info-container`,infoPage:`${O}info-page`,infoPageText:`${O}info-page-text`,infoPagePrev:`${O}info-page-prev`,infoPageNext:`${O}info-page-next`,noteButtonsBigger:`${O}note-bigger`,noteButtonsSmaller:`${O}note-smaller`,infoTime:`${O}info-time`,infoTimer:`${O}info-timer`},_=e=>{const{title:t}=document;document.title="[Presenter view]"+(t?` - ${t}`:"");const n={},r=e=>(n[e]=n[e]||document.querySelector(`.${e}`),n[e]);document.body.appendChild((e=>{const t=document.createElement("div");return t.className=q.container,t.appendChild(e),t.insertAdjacentHTML("beforeend",B(K,null,B("div",{class:q.nextContainer},B("iframe",{class:q.next,src:"?view=next"})),B("div",{class:q.dragbar}),B("div",{class:q.noteContainer},B("div",{class:q.noteWrapper}),B("div",{class:q.noteButtons},B("button",{class:q.noteButtonsSmaller,tabindex:"-1",title:"Smaller notes font size"},"Smaller notes font size"),B("button",{class:q.noteButtonsBigger,tabindex:"-1",title:"Bigger notes font size"},"Bigger notes font size"))),B("div",{class:q.infoContainer},B("div",{class:q.infoPage},B("button",{class:q.infoPagePrev,tabindex:"-1",title:"Previous"},"Previous"),B("span",{class:q.infoPageText}),B("button",{class:q.infoPageNext,tabindex:"-1",title:"Next"},"Next")),B("time",{class:q.infoTime,title:"Current time"}),B("time",{class:q.infoTimer,title:"Timer"})))),t})(e.parent)),(e=>{let t=!1;r(q.dragbar).addEventListener("mousedown",(()=>{t=!0,r(q.dragbar).classList.add("active")})),window.addEventListener("mouseup",(()=>{t=!1,r(q.dragbar).classList.remove("active")})),window.addEventListener("mousemove",(e=>{if(!t)return;const n=e.clientX/document.documentElement.clientWidth*100;r(q.container).style.setProperty("--bespoke-marp-presenter-split-ratio",`${Math.max(0,Math.min(100,n))}%`)})),r(q.nextContainer).addEventListener("click",(()=>e.next()));const n=r(q.next),o=(a=n,(e,t)=>{var n;return null===(n=a.contentWindow)||void 0===n?void 0:n.postMessage(`navigate:${e},${t}`,"null"===window.origin?"*":window.origin)});var a;n.addEventListener("load",(()=>{r(q.nextContainer).classList.add("active"),o(e.slide(),e.fragmentIndex),e.on("fragment",(({index:e,fragmentIndex:t})=>o(e,t)))}));const i=document.querySelectorAll(".bespoke-marp-note");i.forEach((e=>{e.addEventListener("keydown",(e=>e.stopPropagation())),r(q.noteWrapper).appendChild(e)})),e.on("activate",(()=>i.forEach((t=>t.classList.toggle("active",t.dataset.index==e.slide())))));let s=0;const l=e=>{s=Math.max(-5,s+e),r(q.noteContainer).style.setProperty("--bespoke-marp-note-font-scale",(1.2**s).toFixed(4))},d=()=>l(1),c=()=>l(-1),u=r(q.noteButtonsBigger),f=r(q.noteButtonsSmaller);u.addEventListener("click",(()=>{u.blur(),d()})),f.addEventListener("click",(()=>{f.blur(),c()})),document.addEventListener("keydown",(e=>{"+"===e.key&&d(),"-"===e.key&&c()}),!0),e.on("activate",(({index:t})=>{r(q.infoPageText).textContent=`${t+1} / ${e.slides.length}`}));const m=r(q.infoPagePrev),g=r(q.infoPageNext);m.addEventListener("click",(t=>{m.blur(),e.prev({fragment:!t.shiftKey})})),g.addEventListener("click",(t=>{g.blur(),e.next({fragment:!t.shiftKey})})),e.on("fragment",(({index:t,fragments:n,fragmentIndex:r})=>{m.disabled=0===t&&0===r,g.disabled=t===e.slides.length-1&&r===n.length-1}));let p=new Date;const v=()=>{const e=new Date,t=e=>`${Math.floor(e)}`.padStart(2,"0"),n=e.getTime()-p.getTime(),o=t(n/1e3%60),a=t(n/1e3/60%60),i=t(n/36e5%24);r(q.infoTime).textContent=e.toLocaleTimeString(),r(q.infoTimer).textContent=`${i}:${a}:${o}`};v(),setInterval(v,250),r(q.infoTimer).addEventListener("click",(()=>{p=new Date}))})(e)},X=e=>{if(!(e=>e.syncKey&&"string"==typeof e.syncKey)(e))throw new Error("The current instance of Bespoke.js is invalid for Marp bespoke presenter plugin.");Object.defineProperties(e,{openPresenterView:{enumerable:!0,value:F},presenterUrl:{enumerable:!0,get:U}}),c&&document.addEventListener("keydown",(t=>{"p"!==t.key||t.altKey||t.ctrlKey||t.metaKey||(t.preventDefault(),e.openPresenterView())}))};function F(){const{max:e,floor:t}=Math,n=e(t(.85*window.innerWidth),640),r=e(t(.85*window.innerHeight),360);return window.open(this.presenterUrl,O+this.syncKey,`width=${n},height=${r},menubar=no,toolbar=no`)}function U(){const e=new URLSearchParams(location.search);return e.set("view","presenter"),e.set("sync",this.syncKey),i(e)}const V=e=>{const t=s();return t===r&&e.appendChild(document.createElement("span")),{"":X,[n]:_,[r]:T}[t]},R=e=>{e.on("activate",(t=>{document.querySelectorAll(".bespoke-progress-parent > .bespoke-progress-bar").forEach((n=>{n.style.flexBasis=100*t.index/(e.slides.length-1)+"%"}))}))},j=e=>{const t=Number.parseInt(e,10);return Number.isNaN(t)?null:t},H=(e={})=>{const t={history:!0,...e};return e=>{let n=!0;const r=e=>{const t=n;try{return n=!0,e()}finally{n=t}},o=(t={fragment:!0})=>{((t,n)=>{const{min:r,max:o}=Math,{fragments:a,slides:i}=e,s=o(0,r(t,i.length-1)),l=o(0,r(n||0,a[s].length-1));s===e.slide()&&l===e.fragmentIndex||e.slide(s,{fragment:l})})((j(location.hash.slice(1))||1)-1,t.fragment?j(l("f")||""):null)};e.on("fragment",(({index:e,fragmentIndex:r})=>{n||d({f:0===r||r.toString()},{location:{...location,hash:`#${e+1}`},setter:(...e)=>t.history?history.pushState(...e):history.replaceState(...e)})})),setTimeout((()=>{o(),window.addEventListener("hashchange",(()=>r((()=>{o({fragment:!1}),d({f:void 0})})))),window.addEventListener("popstate",(()=>{n||r((()=>o()))})),n=!1}),0)}},W=(e={})=>{var n;const r=e.key||(null===(n=window.history.state)||void 0===n?void 0:n.marpBespokeSyncKey)||Math.random().toString(36).slice(2),o=`bespoke-marp-sync-${r}`;var a;a={marpBespokeSyncKey:r},d({},{setter:(e,...n)=>t({...e,...a},...n)});const i=()=>{const e=u(o);return e?JSON.parse(e):Object.create(null)},s=e=>{const t=i(),n={...t,...e(t)};return f(o,JSON.stringify(n)),n},l=()=>{window.removeEventListener("pageshow",l),s((e=>({reference:(e.reference||0)+1})))};return e=>{l(),Object.defineProperty(e,"syncKey",{value:r,enumerable:!0});let t=!0;setTimeout((()=>{e.on("fragment",(e=>{t&&s((()=>({index:e.index,fragmentIndex:e.fragmentIndex})))}))}),0),window.addEventListener("storage",(n=>{if(n.key===o&&n.oldValue&&n.newValue){const r=JSON.parse(n.oldValue),o=JSON.parse(n.newValue);if(r.index!==o.index||r.fragmentIndex!==o.fragmentIndex)try{t=!1,e.slide(o.index,{fragment:o.fragmentIndex})}finally{t=!0}}}));const n=()=>{const{reference:e}=i();void 0===e||e<=1?m(o):s((()=>({reference:e-1})))};window.addEventListener("pagehide",(e=>{e.persisted&&window.addEventListener("pageshow",l),n()})),e.on("destroy",n)}},{PI:Y,abs:J,sqrt:z,atan2:G}=Math,Q={passive:!0},Z=({slope:e=-.7,swipeThreshold:t=30}={})=>n=>{let r;const o=n.parent,a=e=>{const t=o.getBoundingClientRect();return{x:e.pageX-(t.left+t.right)/2,y:e.pageY-(t.top+t.bottom)/2}};o.addEventListener("touchstart",(({touches:e})=>{r=1===e.length?a(e[0]):void 0}),Q),o.addEventListener("touchmove",(e=>{if(r)if(1===e.touches.length){e.preventDefault();const t=a(e.touches[0]),n=t.x-r.x,o=t.y-r.y;r.delta=z(J(n)**2+J(o)**2),r.radian=G(n,o)}else r=void 0})),o.addEventListener("touchend",(o=>{if(r){if(r.delta&&r.delta>=t&&r.radian){const t=(r.radian-e+Y)%(2*Y)-Y;n[t<0?"next":"prev"](),o.stopPropagation()}r=void 0}}),Q)},ee="_tA",te=e=>{const t=document.documentTransition;if(!t)return;let n;e._tP=!1;const r=(n,{back:r,cond:o})=>a=>{var i,s;const l=e.slides[e.slide()].querySelector("section[data-transition]");if(!l)return!0;const d=document.querySelector(".bespoke-marp-osc"),c=d?[d]:void 0;if(e._tP){if(a._tA){e._tP=!1;try{t.start({sharedElements:c}).catch((()=>{}))}catch(e){}return!0}}else{if(!o(a))return!0;const d="transition"+(a.back||r?"Back":""),u=Number.parseInt(null!==(i=l.dataset[`${d}Duration`])&&void 0!==i?i:"",10),f=Number.parseInt(null!==(s=l.dataset[`${d}Delay`])&&void 0!==s?s:"",10),m={};Number.isNaN(u)||(m.duration=u.toString()),Number.isNaN(f)||(m.delay=f.toString()),e._tP=t.prepare({rootTransition:l.dataset[d],rootConfig:m,sharedElements:c}).then((()=>n(a))).catch((()=>n(a)))}return!1};e.on("prev",r((t=>e.prev({...t,[ee]:!0})),{back:!0,cond:e=>{var t;return e.index>0&&!((null===(t=e.fragment)||void 0===t||t)&&n.fragmentIndex>0)}})),e.on("next",r((t=>e.next({...t,[ee]:!0})),{cond:t=>t.index+1<e.slides.length&&!(n.fragmentIndex+1<n.fragments.length)})),setTimeout((()=>{e.on("slide",r((t=>e.slide(t.index,{...t,[ee]:!0})),{cond:t=>{const n=e.slide();return t.index!==n&&(t.back=t.index<n,!0)}}))}),0),e.on("fragment",(e=>{n=e}))};let ne;const re=()=>(void 0===ne&&(ne="wakeLock"in navigator&&navigator.wakeLock),ne),oe=async()=>{const e=re();if(e)try{return await e.request("screen")}catch(e){console.warn(e)}return null},ae=async()=>{if(!re())return;let e;const t=()=>{e&&"visible"===document.visibilityState&&oe()};for(const e of["visibilitychange","fullscreenchange"])document.addEventListener(e,t);return e=await oe(),e};((t=document.getElementById("p"))=>{(()=>{const t=l("view");e.dataset.bespokeView=t===r||t===n?t:""})();const a=(e=>{const t=l(e);return d({[e]:void 0}),t})("sync")||void 0;var i,c,u,f,m,g,h,y,b,w,E,T;i=t,c=((...e)=>{const t=o.findIndex((e=>s()===e));return e.map((([e,n])=>e[t]&&n)).filter((e=>e))})([[1,1,0],W({key:a})],[[1,1,1],V(t)],[[1,1,0],L],[[1,1,1],p],[[1,0,0],k()],[[1,1,1],$],[[1,1,1],H({history:!1})],[[1,1,0],S()],[[1,1,0],x],[[1,0,0],R],[[1,1,0],Z()],[[1,0,0],P()],[[1,0,0],te],[[1,1,1],v],[[1,1,0],ae]),f=1===(i.parent||i).nodeType?i.parent||i:document.querySelector(i.parent||i),m=[].filter.call("string"==typeof i.slides?f.querySelectorAll(i.slides):i.slides||f.children,(function(e){return"SCRIPT"!==e.nodeName})),g={},h=function(e,t){return(t=t||{}).index=m.indexOf(e),t.slide=e,t},w=function(e,t){m[e]&&(u&&b("deactivate",h(u,t)),u=m[e],b("activate",h(u,t)))},E=function(e,t){var n=m.indexOf(u)+e;b(e>0?"next":"prev",h(u,t))&&w(n,t)},T={off:y=function(e,t){g[e]=(g[e]||[]).filter((function(e){return e!==t}))},on:function(e,t){return(g[e]||(g[e]=[])).push(t),y.bind(null,e,t)},fire:b=function(e,t){return(g[e]||[]).reduce((function(e,n){return e&&!1!==n(t)}),!0)},slide:function(e,t){if(!arguments.length)return m.indexOf(u);b("slide",h(m[e],t))&&w(e,t)},next:E.bind(null,1),prev:E.bind(null,-1),parent:f,slides:m,destroy:function(e){b("destroy",h(u,e)),g={}}},(c||[]).forEach((function(e){e(T)})),u||w(0)})()}();</script></body></html> \ No newline at end of file diff --git a/assets/FortranCISM.md b/assets/FortranCISM.md new file mode 100644 index 0000000000000000000000000000000000000000..68ab625d5d6f412bd442f1e0d1e948a1359f9051 --- /dev/null +++ b/assets/FortranCISM.md @@ -0,0 +1,1106 @@ +--- +marp: true +title: Introduction to structured programming with Fortran +author: P.Y. Barriat +description: https://dev.to/nikolab/complete-list-of-github-markdown-emoji-markup-5aia +backgroundImage: url('assets/back.png') +_backgroundImage: url('assets/garde.png') +footer: 09/11/2022 | Introduction to structured programming with Fortran +_footer: "" +paginate: true +_paginate: false +--- + +Introduction to structured programming with `Fortran`<!--fit--> +=== + +https://gogs.elic.ucl.ac.be/pbarriat/learning-fortran + + + +### Pierre-Yves Barriat + +##### November 09, 2022 + +###### CISM/CÉCI Training Sessions + +--- + +# Fortran : shall we start ? + +- You know already one computer language ? +- You understand the very basic programming concepts : + - What is a variable, an assignment, function call, etc.? + - Why do I have to compile my code? + - What is an executable? +- You (may) already know some Fortran ? +- How to proceed from old Fortran, to much more modern languages like Fortran 90/2003 ? + +--- + +# Why to learn Fortran ? + +- Because of the execution `speed` of a program +- Well suited for numerical computations : +more than 45% of scientific applications are in Fortran +- `Fast` code : compilers can optimize well +- Optimized `numerical libraries` available +- Fortran is a `simple` langage and it is (kind-of) `easy to learn` + +--- + +# Fortran is simple + +- **We want to get our science done! Not learn languages!** +- How easy/difficult is it really to learn Fortran ? +- The concept is easy: +*variables, operators, controls, loops, subroutines/functions* +- **Invest some time now, gain big later!** + +--- + +# History + +**FOR**mula **TRAN**slation +> invented 1954-8 by John Backus and his team at IBM + +- FORTRAN 66 (ISO Standard 1972) +- FORTRAN 77 (1978) +- Fortran 90 (1991) +- Fortran 95 (1997) +- Fortran 2003 (2004) → `"standard" version` +- Fortran 2008 (2010) +- Fortran 2018 (11/2018) + +--- + +# Starting with Fortran 77 + +- Old Fortran provides only the absolute minimum! +- Basic features : +data containers (integer, float, ...), arrays, basic operators, loops, I/O, subroutines and functions +- But this version has flaws: +no dynamic memory allocation, old & obsolete constructs, “spaghetti†code, etc. +- Is that enough to write code ? + +--- + +# Fortran 77 → Fortran >90 + +- If Fortran 77 is so simple, why is it then so difficult to write good code? +- Is simple really better? +⇒ Using a language allows us to express our thoughts (on a computer) +- A more sophisticated language allows for more complex thoughts +- More language elements to get organized +⇒ Fortran 90/95/2003 (recursive, OOP, etc) + +--- + +# How to Build a FORTRAN Program + +FORTRAN is a compiled language (like C) so the source code (what you write) must be converted into machine code before it can be executed (e.g. Make command) + + + +--- + +# FORTRAN 77 Format + +This version requires a fixed format for programs + + + +- max length variable names is 6 characters +- alphanumeric only, must start with a letter +- character strings are case sensitive + +--- + +# FORTRAN >90 Format + +Versions >90 relaxe these requirements: + +- comments following statements (! delimiter) +- long variable names (31 characters) +- containing only letters, digits or underscore +- max row length is 132 characters +- can be max 39 continuation lines +- if a line is ended with ampersand (&), the line continues onto the next line +- semicolon (;) as a separator between statements on a single line +- allows free field input + +--- + +# Program Organization + +Most FORTRAN programs consist of a main program and one or more subprograms + +There is a fixed order: + +```Fortran90 +Heading +Declarations +Variable initializations +Program code +Format statements + +Subprogram definitions +(functions & subroutines) +``` + +--- + +# Data Type Declarations + +Basic data types are : + +- `INTEGER` : integer numbers (+/-) +- `REAL` : floating point numbers +- `DOUBLE PRECISION` : extended precision floating point +- `CHARACTER*n` : string with up to **n** characters +- `LOGICAL` : takes on values `.TRUE.` or `.FALSE.` + +--- + +# Data Type Declarations + +`INTEGER` and `REAL` can specify number of bytes to use + +- Default is: `INTEGER*4` and `REAL*4` +- `DOUBLE PRECISION` is same as `REAL*8` + +Arrays of any type must be declared: + +- `DIMENSION A(3,5)` - declares a 3 x 5 array +- `CHARACTER*30 NAME(50)` - directly declares a character array with 30 character strings in each element + +--- + +# Data Type Declarations + +FORTRAN >90 allows user defined types + +```fortran +TYPE my_variable + character(30) :: name + integer :: id + real(8) :: value + integer, dimension(3,3) :: dimIndex +END TYPE variable + +type(my_variable) var +var%name = "salinity" +var%id = 1 +``` + +--- + +# Implicit vs Explicit Declarations + +By default, an implicit type is assumed depending on the first letter of the variable name: + +- `A-H, O-Z` define REAL variables +- `I-N` define INTEGER variables + +Can use the IMPLICIT statement: + +```fortran +IMPLICIT REAL (A-Z) +``` + +> makes all variables REAL if not declared + +--- + +# Implicit vs Explicit Declarations + +```fortran +IMPLICIT CHARACTER*2 (W) +``` + +> makes variables starting with W be 2-character strings + +```fortran +IMPLICIT DOUBLE PRECISION (D) +``` + +> makes variables starting with D be double precision + +**Good habit**: force explicit type declarations + +```fortran +IMPLICIT NONE +``` + +> user must explicitly declare all variable types + +--- + +# Assignment Statements + +**Old** assignment statement: `<label>` `<variable>` = `<expression>` + +- `<label>` : statement label number (1 to 99999) +- `<variable>` : FORTRAN variable +(max 6 characters, alphanumeric only for standard FORTRAN 77) + +**Expression**: + +- Numeric expressions: `VAR = 3.5*COS(THETA)` +- Character expressions: `DAY(1:3) = 'TUE'` +- Relational expressions: `FLAG = ANS .GT. 0` +- Logical expressions: `FLAG = F1 .OR. F2` + +--- + +# Numeric Expressions + +Arithmetic operators: precedence: `**` *(high)* → `-` *(low)* + +| Operator | Function | +| ------------ | --------------- | +| `**` | exponentiation | +| `*` | multiplication | +| `/` | division | +| `+` | addition | +| `-` | subtraction | + +--- + +# Numeric Expressions + +Numeric expressions are up-cast to the highest data type in the expression according to the precedence: + +*(low)* logical → integer → real → complex *(high)* + +and smaller byte size *(low)* to larger byte size *(high)* + +## Example: + +> fortran 77 source code [arith.f](https://gogs.elic.ucl.ac.be/pbarriat/learning-fortran/src/master/src/01_arith.f) + +--- + +# Character Expressions + +Only built-in operator is **Concatenation** defined by `//` + +```fortran +'ILL'//'-'//'ADVISED' +``` + +`character` arrays are most commonly encountered + +- treated like any array (indexed using : notation) +- fixed length (usually padded with blanks) + +--- + +# Character Expressions + +Example: + +```fortran +CHARACTER FAMILY*16 +FAMILY = ‘GEORGE P. BURDELL’ + +PRINT*,FAMILY(:6) +PRINT*,FAMILY(8:9) +PRINT*,FAMILY(11:) +PRINT*,FAMILY(:6)//FAMILY(10:) +``` + +```fortran +GEORGE +P. +BURDELL +GEORGE BURDELL +``` + +--- + +# Relational Expressions + +Two expressions whose values are compared to determine whether the relation is true or false + +- may be numeric (common) or non-numeric + +`character` strings can be compared + +- done character by character +- shorter string is padded with blanks for comparison + +--- + +# Relational Expressions + +| Operator | Relationship | +| ------------ | --------------- | +| `.LT.` or `<` | less than | +| `.LE.` or `<=` | less than or equal to | +| `.EQ.` or `==` | equal to | +| `.NE.` or `/=` | not equal to | +| `.GT.` or `>` | greater than | +| `.GE.` or `>=` | greater than or equal to | + +--- + +# Logical Expressions + +Consists of one or more logical operators and logical, numeric or relational operands + +- values are `.TRUE.` or `.FALSE.` +- need to consider overall operator precedence + +> can combine logical and integer data with logical operators but this is tricky (**avoid!**) + +--- + +# Logical Expressions + +| F77 Operator | >F90 Operator | Example | Meaning | +| --------------- | --------------- | ------------ | --------------- | +| `.AND.` | `&&` | `A .AND. B` | logical `AND` | +| `.OR.` | `\|\|` | `A .OR. B` | logical `OR` | +| `.EQV.` | `==` | `A .EQV. B` | logical equivalence | +| `.NEQV.` | `/=` | `A .NEQV. B` | logical inequivalence | +| `.XOR.` | `/=` | `A .XOR. B` | exclusive `OR` (same as `.NEQV.`) | +| `.NOT.` | `!` | `.NOT. A` | logical negation | + +--- + +# Arrays in FORTRAN + +Arrays can be multi-dimensional (up to 7 in F77) and are indexed using `( )`: + +- `TEST(3)` or `FORCE(4,2)` + +> Indices are by default defined as `1...N` + +We can specify index range in declaration + +- `INTEGER K(0:11)` : `K` is dimensioned from `0-11` (12 elements) + +Arrays are stored in column order (1st column, 2nd column, etc) so accessing by incrementing row index first usually is fastest + +Whole array reference (only in >F90): `K(:)=-8` assigns 8 to all elements in K + +> Avoid `K=-8` assignement + +--- + +# Unconditional `GO TO` in F77 + +This is the only GOTO in FORTRAN 77 + +- Syntax: `GO TO label` +- Unconditional transfer to labeled statement + +```fortran + 10 -code- + GO TO 30 + -code that is bypassed- + 30 -code that is target of GOTO- + -more code- + GO TO 10 +``` + +- **Problem** : leads to confusing *"spaghetti code"* :boom: + +--- + +# `IF ELSE IF` Statement + +Basic version: + +```fortran +IF (KSTAT.EQ.1) THEN + CLASS='FRESHMAN' +ELSE IF (KSTAT.EQ.2) THEN + CLASS='SOPHOMORE' +ELSE IF (KSTAT.EQ.3) THEN + CLASS='JUNIOR' +ELSE IF (KSTAT.EQ.4) THEN + CLASS='SENIOR' +ELSE + CLASS='UNKNOWN' +ENDIF +``` + +--- + +# Spaghetti Code in F77 (and before) + +Use of `GO TO` and arithmetic `IF`'s leads to bad code that is very hard to maintain + +Here is the equivalent of an `IF-THEN-ELSE` statement: + +```fortran + 10 IF (KEY.LT.0) GO TO 20 + TEST=TEST-1 + THETA=ATAN(X,Y) + GO TO 30 + 20 TEST=TEST+1 + THETA=ATAN(-X,Y) + 30 CONTINUE +``` + +Now try to figure out what a complex `IF ELSE IF` statement would look like coded with this kind of simple `IF`... + +--- + +# Loop Statements (old versions) + +`DO` loop: structure that executes a specified number of times + +*Spaghetti Code Version* + +```fortran + K=2 + 10 PRINT*,A(K) + K=K+2 + IF (K.LE.11) GO TO 10 + 20 CONTINUE +``` + +*F77 Version* + +```fortran + DO 100 K=2,10,2 + PRINT*,A(K) + 100 CONTINUE +``` + +--- + +# Loop Statements (>F90) + +```fortran +DO K=2,10,2 + WRITE(*,*) A(K) +END DO +``` + +- Loop _control can include variables and a third parameter to specify increments, including negative values +- Loop always executes ONCE before testing for end condition + +```fortran +READ(*,*) R +DO WHILE (R.GE.0) + VOL=2*PI*R**2*CLEN + READ(*,*) R +END DO +``` + +- Loop will not execute at all if logical_expr is not true at start + +--- + +# Comments on Loop Statements + +In old versions: + +- to transfer out (exit loop), use a `GO TO` +- to skip to next loop, use `GO TO` terminating statement (this is a good reason to always make this a `CONTINUE` statement) + +In new versions: + +- to transfer out (exit loop), use `EXIT` statement and control is transferred to statement following loop end. This means you cannot transfer out of multiple nested loops with a single `EXIT` statement (use named loops if needed - `myloop : do i=1,n`). This is much like a `BREAK` statement in other languages. +- to skip to next loop cycle, use `CYCLE` statement in loop. + +--- + +# File-Directed Input and Output + +Much of early FORTRAN was devoted to reading input data +from Cards and writing to a line printer + +Today, most I/O is to and from a file: it requires more extensive I/O capabilities standardized until FORTRAN 77 + +**I/O** = communication between a program and the outside world + +- opening and closing a file with `OPEN` & `CLOSE` +- data reading & writing with `READ` & `WRITE` +- can use **unformatted** `READ` & `WRITE` if no human readable data are involved (much faster access, smaller files) + +--- + +# `OPEN` & `CLOSE` example + +Once opened, file is referred to by an assigned device number (a unique id) + +```fortran +character(len=*) :: x_name +integer :: ierr, iSize, guess_unit +logical :: itsopen, itexists +! +inquire(file=trim(x_name), size=iSize, number=guess_unit, opened=itsopen, exist=itexists) +if ( itsopen ) close(guess_unit, status='delete') +! +open(902,file=trim(x_name),status='new',iostat=ierr) +! +if (iSize <= 0 .OR. .NOT.itexists) then + open(902,file=trim(x_name),status='new',iostat=ierr) + if (ierr /= 0) then + ... + close(902) + endif + ... +endif +``` + +--- + +# `READ` Statement + +- syntax: `READ(dev_no, format_label) variable_list` +- read a record from `dev_no` using `format_label` and assign results to variables in `variable_list` + +```fortran + READ(105,1000) A,B,C + 1000 FORMAT(3F12.4) +``` + +> device numbers 1-7 are defined as standard I/O devices + +- each `READ` reads one or more lines of data and any remaining data in a line that is read is dropped if not translated to one of the variables in the `variable_list` +- `variable_list` can include implied `DO` such as: `READ(105,1000)(A(I),I=1,10)` + +--- + +# `READ` Statement - cont'd + +- input items can be integer, real or character +- characters must be enclosed in `' '` +- input items are separated by commas +- input items must agree in type with variables in `variable_list` +- each `READ` processes a new record (line) + +```fortran +INTEGER K +REAL(8) A,B +OPEN(105,FILE='path_to_existing_file') +READ(105,*) A,B,K +``` + +> read one line and look for floating point values for A and B and an integer for K + +--- + +# `WRITE` Statement + +- syntax: `WRITE(dev_no, format_label) variable_list` +- write variables in `variable_list` to output `dev_no` using format specified in format statement with `format_label` + +```fortran + WRITE(*,1000) A,B,KEY + 1000 FORMAT(F12.4,E14.5,I6) +``` + +```fortran +|----+----o----+----o----+----o----+----| + 1234.5678 -0.12345E+02 12 +``` + +- device number `*` is by default the screen (or *standard output* - also 6) +- each `WRITE` produces one or more output lines as needed to write out `variable_list` using `format` statement +- `variable_list` can include implied `DO` such as: `WRITE(*,2000)(A(I),I=1,10)` + +<!-- _footer: "" --> + +--- + +# `FORMAT` Statement + +| data type | format descriptors | example | +| --------------- | --------------- | ------------ | +| `integer` | `iw` | `write(*,'(i5)') int` | +| `real` (*decimal*) | `fw.d` | `write(*,'(f7.4)') x` | +| `real` (*exponential*) | `ew.d` | `write(*,'(e12.3)') y` | +| `character` | `a, aw` | `write(*,'(a)') string` | +| `logical` | `lw` | `write(*,'(l2)') test` | +| spaces & tabs | `wx` & `tw` | `write (*,'(i3,2x,f6.3)') i, x` | +| linebreak | `/` | `write (*,'(f6.3,/,f6.3)') x, y` | + +--- + +# `NAMELIST` + +It is possible to pre-define the structure of input and output data using `NAMELIST` in order to make it easier to process with `READ` and `WRITE` statements + +- Use `NAMELIST` to define the data structure +- Use `READ` or `WRITE` with reference to `NAMELIST` to handle the data in the specified format + +> This is not part of standard F77 but it is included in >F90 + +On input, the `NAMELIST` data must be structured as follows: + +```fortran +&INPUT + THICK=0.245, + LENGTH=12.34, + WIDTH=2.34, + DENSITY=0.0034 +/ +``` + +<!-- _footer: "" --> + +--- + +# Internal `WRITE` Statement + +Internal `WRITE` does same as `ENCODE` in F77 : **a cast to string** +> `WRITE (dev_no, format_label) var_list` +> write variables in `var_list` to internal storage defined by character variable used as `dev_no` = default character variable (not an array) + +```fortran +INTEGER*4 J,K +CHARACTER*50 CHAR50 +DATA J,K/1,2/ +... +WRITE(CHAR50,*) J,K +``` + +Results: + +```fortran +CHAR50=' 1 2' +``` + +--- + +# Internal `READ` Statement + +Internal `READ` does same as `DECODE` in F77 : **a cast from string** +> `READ (dev_no, format_label) var_list` +> read variables from internal storage specified by character variable used as `dev_no` = default character variable (not an array) + +```fortran +INTEGER K +REAL A,B +CHARACTER*80 REC80 +DATA REC80/'1.2, 2.3, -5'/ +... +READ(REC80,*) A,B,K +``` + +Results: + +```fortran +A=1.2, B=2.3, K=-5 +``` + +<!-- _footer: "" --> + +--- + +# Structured programming + +Structured programming is based on subprograms (functions and subroutines) and control statements (like `IF` statements or loops) : + +- structure the control-flow of your programs (eg, give up the `GO TO`) +- improved readability +- lower level aspect of coding in a smart way + +It is a **programming paradigm** aimed at improving the quality, clarity, and access time of a computer program + +--- + +# Functions and Subroutines + +`FUNCTION` & `SUBROUTINE` are subprograms that allow structured coding + +- `FUNCTION`: returns a single explicit function value for given function arguments + It’s also a variable → so must be declared ! +- `SUBROUTINE`: any values returned must be returned through the arguments (no explicit subroutine value is returned) +- functions and subroutines are **not recursive in F77** + +Subprograms use a separate namespace for each subprogram so that variables are local to the subprogram + +- variables are passed to subprogram through argument list and returned in function value or through arguments +- variables stored in `COMMON` may be shared between namespaces + +<!-- _footer: "" --> + +--- + +# Functions and Subroutines - cont'd + +Subprograms must include at least one `RETURN` (can have more) and be terminated by an `END` statement + +`FUNCTION` example: + +```fortran +REAL FUNCTION AVG3(A,B,C) +AVG3=(A+B+C)/3 +RETURN +END +``` + +Use: + +```fortran +AV = WEIGHT*AVG3(A1,F2,B2) +``` + +> `FUNCTION` type is implicitly defined as REAL + +--- + +# Functions and Subroutines - cont'd + +Subroutine is invoked using the `CALL` statement + +`SUBROUTINE` example: + +```fortran +SUBROUTINE AVG3S(A,B,C,AVERAGE) +AVERAGE=(A+B+C)/3 +RETURN +END +``` + +Use: + +```fortran +CALL AVG3S(A1,F2,B2,AVR) +RESULT = WEIGHT*AVR +``` + +> any returned values must be returned through argument list + +--- + +# Arguments + +Arguments in subprogram are `dummy` arguments used in place of the real arguments + +- arguments are passed by **reference** (memory address) if given as *symbolic* + the subprogram can then alter the actual argument value since it can access it by reference +- arguments are passed by **value** if given as *literal* (so cannot be modified) + +```fortran +CALL AVG3S(A1,3.4,C1,QAV) +``` + +> 2nd argument is passed by value - QAV contains result + +```fortran +CALL AVG3S(A,C,B,4.1) +``` + +> no return value is available since "4.1" is a value and not a reference to a variable! + +--- + +# Arguments - cont'd + +- `dummy` arguments appearing in a subprogram declaration cannot be an individual array element reference, e.g., `A(2)`, or a *literal*, for obvious reasons! +- arguments used in invocation (by calling program) may be *variables*, *subscripted variables*, *array names*, *literals*, *expressions* or *function names* +- using symbolic arguments (variables or array names) is the **only way** to return a value (result) from a `SUBROUTINE` + +> It is considered **BAD coding practice**, but functions can return values by changing the value of arguments + This type of use should be strictly **avoided**! + +--- + +# Arguments - cont'd + +The `INTENT` keyword (>F90) increases readability and enables better compile-time error checking + +```fortran +SUBROUTINE AVG3S(A,B,C,AVERAGE) + IMPLICIT NONE + REAL, INTENT(IN) :: A, B + REAL, INTENT(INOUT) :: C ! default + REAL, INTENT(OUT) :: AVERAGE + + A = 10 ! Compilation error + C = 10 ! Correct + AVERAGE=(A+B+C)/3 ! Correct +END +``` + +> Compiler uses `INTENT` for error checking and optimization + +--- + +# `FUNCTION` versus Array + +`REMAINDER(4,3)` could be a 2D array or it could be a reference to a function + +If the name, including arguments, **matches an array declaration**, then it is taken to be an array, **otherwise**, it is assumed to be a `FUNCTION` + +Be careful about `implicit` versus `explicit` type declarations with `FUNCTION` + +```fortran +PROGRAM MAIN + INTEGER REMAINDER + ... + KR = REMAINDER(4,3) + ... +END + +INTEGER FUNCTION REMAINDER(INUM,IDEN) + ... +END +``` + +<!-- _footer: "" --> + +--- + +# Arrays with Subprograms + +Arrays present special problems in subprograms + +- must pass by reference to subprogram since there is no way to list array values explicitly as literals +- how do you tell subprogram how large the array is ? + +> Answer varies with FORTRAN version and vendor (dialect)... + +When an array element, e.g. `A(1)`, is used in a subprogram invocation (in calling program), it is passed as a reference (address), just like a simple variable + +When an array is used by name in a subprogram invocation (in calling program), it is passed as a reference to the entire array. In this case the array must be appropriately dimensioned in the subroutine (and this can be tricky...) + +--- + +# Arrays - cont'd + +### Data layout in multi-dimensional arrays + +- always increment the left-most index of multi-dimensional arrays in the innermost loop (i.e. fastest) +- **column major** ordering in Fortran vs. **row major** ordering in C +- a compiler (with sufficient optimization flags) may re-order loops automatically + +```fortran +do j=1,M + do i=1,N ! innermost loop + y(i) = y(i)+ a(i,j)*x(j) ! left-most index is i + end do +end do +``` + +--- + +# Arrays - cont'd + +- dynamically allocate memory for arrays using `ALLOCATABLE` on declaration +- memory is allocated through `ALLOCATE` statement in the code and is deallocated through `DEALLOCATE` statement + +```fortran +integer :: m, n +integer, allocatable :: idx(:) +real, allocatable :: mat(:,:) +m = 100 ; n = 200 +allocate( idx(0:m-1)) +allocate( mat(m, n)) +... +deallocate(idx , mat) +``` + +> It exists many array intrinsic functions: SIZE, SHAPE, SUM, ANY, MINVAL, MAXLOC, RESHAPE, DOT_PRODUCT, TRANSPOSE, WHERE, FORALL, etc + +--- + +# `COMMON` & `MODULE` Statement + +The `COMMON` statement allows variables to have a more extensive scope than otherwise + +- a variable declared in a `Main Program` can be made accessible to subprograms (without appearing in argument lists of a calling statement) +- this can be selective (don't have to share all everywhere) +- **placement**: among type declarations, after `IMPLICIT` or `EXPLICIT`, before `DATA` statements +- can group into **labeled** `COMMON` + +With > F90, it's better to use the `MODULE` subprogram instead of the `COMMON` statement + +--- + +# Modular programming (>F90) + +Modular programming is about separating parts of programs into independent and interchangeable modules : + +- improve testability +- improve maintainability +- re-use of code +- higher level aspect of coding in a smart way +- *separation of concerns* + +The principle is that making significant parts of the code independent, replaceable and independently testable makes your programs **more maintainable** + +--- + +# Subprograms type + +`MODULE` are subprograms that allow modular coding and data encapsulation + +The interface of a subprogram type is **explicit** or **implicit** + +Several types of subprograms: + +- `intrinsic`: explicit - defined by Fortran itself (trignonometric functions, etc) +- `module`: explicit - defined with `MODULE` statement and used with `USE` +- `internal`: explicit - defined with `CONTAINS` statement inside (sub)programs +- `external`: implicit (but can be manually (re)defined explicit) - e.g. **libraries** + +Differ with the **scope**: what data and other subprograms a subprogram can access + +--- + +# `MODULE` type + +```fortran +MODULE example + IMPLICIT NONE + INTEGER, PARAMETER :: index = 10 + REAL(8), SAVE :: latitude +CONTAINS + FUNCTION check(x) RESULT(z) + INTEGER :: x, z + ... + END FUNCTION check +END MODULE example +``` + +```fortran +PROGRAM myprog + USE example, ONLY: check, latitude + IMPLICIT NONE + ... + test = check(a) + ... +END PROGRAM myprog +``` + +<!-- _footer: "" --> + +<!-- Notes for presenter. --> +<!-- +```fortran +module subs + +contains + +subroutine asub (i, control) + + implicit none + + integer, intent (in) :: i + logical, intent (in) :: control + + integer, save :: j = 0 + integer :: k + + j = j + i + if ( control ) k = 0 + k = k + i + + write (*, *) 'i, j, k=', i, j, k + +end subroutine asub + +end module subs + +program test_saves + + use subs + implicit none + + call asub ( 3, .TRUE. ) + call asub ( 4, .FALSE. ) + +end program test_saves +``` + +Local variable k of the subroutine is intentionally misused -- in this program it is initialized in the first call since control is TRUE, but on the second call control is FALSE, so k is not redefined. But without the save attribute k is undefined, so the using its value is illegal. + +```fortran + i, j, k= 3 3 3 + i, j, k= 4 7 7 +``` + +Compiling the program with ifort and aggressive optimization options, k lost its value: + +```fortran + i, j, k= 3 3 3 + i, j, k= 4 7 4 +``` +--> + +--- + +# `internal` subprogams + +```fortran +program main + implicit none + integer N + real X(20) + ... + write(*,*), 'Processing x...', process() + ... +contains + logical function process() + ! in this function N and X can be accessed directly (scope of main) + ! Please not that this method is not recommended: + ! it would be better to pass X as an argument of process + implicit none + if (sum(x) > 5.) then + process = .FALSE. + else + process = .TRUE. + endif + end function process +end program +``` + +<!-- _footer: "" --> + +--- + +# `external` subprogams + +- `external` subprogams are defined in a separate program unit +- to use them in another program unit, refer with the `EXTERNAL` statement +- compiled separately and linked + +**!!! DO NOT USE THEM**: modules are much easier and more robust :exclamation: + +They are only needed when subprogams are written with different programming language or when using external libraries (such as BLAS) + +> It's **highly** recommended to construct `INTERFACE` blocks for any external subprogams used + +--- + +# `interface` statement + +```fortran +SUBROUTINE nag_rand(table) + INTERFACE + SUBROUTINE g05faf(a,b,n,x) + REAL, INTENT(IN) :: a, b + INTEGER, INTENT(IN) :: n + REAL, INTENT(OUT) :: x(n) + END SUBROUTINE g05faf + END INTERFACE + ! + REAL, DIMENSION(:), INTENT(OUT) :: table + ! + call g05faf(-1.0,-1.0, SIZE(table), table) +END SUBROUTINE nag_rand +``` + +<!-- _footer: "" --> + +--- + +# Conclusions + +- Fortran in all its standard versions and vendor-specific dialects is a rich but confusing language +- Fortran is a modern language that continues to evolve + +- Fortran is still ideally suited for numerical computations in engineering and science + - most new language features have been added since F95 + - "High Performance Fortran" includes capabilities designed for parallel processing + diff --git a/assets/FortranCISM.pdf b/assets/FortranCISM.pdf new file mode 100644 index 0000000000000000000000000000000000000000..f7cbc2c7c1475628b2a208f48bc28c143398e590 Binary files /dev/null and b/assets/FortranCISM.pdf differ