SS 4068 Fortran Programming C. H. Patterson Hilary Term 2008 Recommended text: Computing for Scientists: Principles of Programming with Fortran 90 and C++ Barlow and Barnett Variables and Operators Data Structure Control Subprograms: Functions and Subroutines Characters and Strings Pointers Input and Output Chapter 2 Variables and Operators Fortran Programme Syntax Programmes begin with the PROGRAM statement e.g. PROGRAM HELLO_WORLD Programmes end with STOP END Programme statements begin in the 7th column and end without a semicolon in the 72nd column There is usually only one statement per line but f90 statements on the same line can be separated by ; Lines are continued with & in the 6th column of the following line In f90 the comment symbol is ! It replaces // in C ! THIS IS A COMMENT Variable names can be up to 31 characters in length Begin with a letter Not case sensitive There are no reserved words Write to screen with the PRINT statement PRINT *, x writes the variable x to the screen. * is otherwise the unit number of the file to be written to. Read from Keyboard with the READ statement READ *, y Reads variable y from the keyboard. Variable Declaration Fortran allows for variables to be used without declaration and uses the convention that variables with names beginning a-h or o-z are REAL variables while those beginning with i-n are INTEGER. This language feature can be disabled by typing IMPLICIT NONE after the PROGRAM statement. This avoids many possible programme bugs. Variables are declared in C++ and f90 by separating variables from the variable type as follows: float int x_data; mindex; REAL INTEGER :: x_data :: height Variables can be initialised at the same time as they are declared Float y_data = 0.3; REAL :: y_data = 0.3 In C++ there are short, int and long integer variable types. In Fortran the KIND distinguishes them. (See next section). In f90 attributes of variables are specified after the variable type INTEGER, PARAMETER :: m = 100 ! m is a parameter, value 100 Note position of :: In order to declare an array which is to be dynamically allocated, it is declared with the attribute ALLOCATABLE REAL, DIMENSION(:), ALLOCATABLE :: zdata READ *,n ALLOCATE (zdata(1:n)) READ *, (zdata(i),i=1,n) … DEALLOCATE(zdata) The code above declares a 1D, allocatable array with name zdata. The value of the dimension is read in the second line, the array is allocated in the third and values of array elements are read in the fourth. After use the array is deallocated. Note round brackets for array indices rather than square brackets in C++. In C++ floating point numbers come in types float and double. In f90 the equivalents are REAL (which we have already met) and DOUBLE PRECISION. To create a double precision constant, the assigned value must end with the D form for the exponent. DOUBLE PRECISION :: two_thirds_d = 0.666666666666666D0 Type conversion It is frequently necessary to convert between variable types, e.g. from an integer to a double in C++. In f90 these conversions are achieved as follows: int jmin; float xmin; … xmin = float(jmin); INTEGER REAL :: jmax :: xmax xmax = REAL(jmax) Operators A list of operators and their precedence in f90 and in C++ is given on pp 47 and 48 in Tables 2.5 and 2.6 of BB. Operations such as addition, subtraction, multiplication and addition have the same symbols in f90 and C++. However, there is no incrementation operator (i++) nor += operation to replace x = x + 1 in f90, as there is in C++. Exponentiation in f90 is achieved with a double asterisk **. AREA = PI * R**2 Logical operators in f90 include == (logical equals) /= (logical not equals) < (less than) <= (less than or equals) > (greater than) and >= (greater than or equals). Exercise 1. Write a programme to read in a REAL and a DOUBLE PRECISION variable, add them as DOUBLE PRECISION variables and WRITE them to screen. Chapter 3 Data Structure Data Type: Integer In C++ there are long, short, and signed, unsigned integer types besides the usual int integer type. int is a 2 byte, signed integer and ranges from -32768 to 32767 but this can vary on some machines and with some compilers. long int (or simply long) integer variables are 4 byte integer variables and range from -2147483648 to 2146483647. unsigned short integer variables also contain 2 bytes and range from 0 to 65535. See Table 3.1 on p58 BB. In f90 the number of bytes to be used is determined by the KIND attribute. The function SELECTED_INT_KIND(n) gives the KIND parameter for integers large enough to represent n decimal digits. Here is an example of the use of this function together with the KIND parameter. INTEGER, PARAMETER INTEGER, PARAMETER INTEGER (KIND = small) INTEGER (KIND = large) :: large = SELECTED_INT_KIND(9) :: small = SELECTED_INT_KIND(5) :: my_salary :: your_salary Note KIND is not an attribute and so is separated by () rather than , before ::. Data Type: Float and Real Single precision floating point numbers are stored in 4 bytes as Number = mantissa . 2exponent The mantissa is a number between 1 and 2 and the exponent lies between -127 and +128 so that the range of numbers that can be represented is 2-127 to 2+128. In base 10 the range of numbers that can be represented in this way is 5.9 E-39 to 3.4 E+38 Here the notation E means ‘10 to the power of’. The smallest change (1 bit) is 2-24 (6.0E-08) which means that single precision numbers have roughly 7 significant figures. Double precision floating point numbers are stored in 8 bytes. The mantissa occupies 53 bits and the exponent 11 bits. In f90 these variables are declared as DOUBLE PRECISION. More variation in the precision can be obtained using the SELECTED_KIND_REAL(n,m) function. This returns the KIND value required to store numbers with n decimal digits of precision in the range E±m. Currently many systems use KIND=1,2 for the two precisions. The following code illustrates the use of these functions here. INTEGER, PARAMETER REAL(KIND = dble) REAL(dble) DOUBLE PRECISION :: dble = SELECTED_REAL_KIND(15,300) :: BIG1 ! Approved :: BIG2 ! Also OK :: BIG3 ! Alternative The KIND of a real number is found using KIND(x). e.g. single = KIND(0.0E0) double = KIND(0.0D0) Note that D and E notations in exponent indicate double and single precision numbers. The function xdouble = REAL(x,KIND=double) allows for conversion between different real data types. In C++ the equivalents are float, double and long double. The precision of the long double type is compiler and machine dependent. Data Type: Complex In f90 a complex number can be represented by specifying the real and imaginary parts or using the function CMPLX. Everything pertinent to real number representations also applies (twice) to the complex data type. The following piece of code illustrates declaration and use of the complex data type. COMPLEX COMPLEX(KIND(0.D0)) z1 = CMPLX(2.0,3.5) arg_z1 = ATAN2(AIMAG(z1),REAL(z1)) z2 = i**i PRINT, * AIMAG(z2) :: z1, i = (0., 1.) :: z2 ! z1 = 2 + 3.5 i ! angle of z1 ! = exp(-pi/2) = 0.2078796 ! expect 0.0 in this case Data Type: Logical In f90 there is a LOGICAL data type used in conjunction with Boolean algebra for decision making. These variables can take the values .TRUE. or .FALSE. (note the periods beginning and ending these values). In C++ there is a data type bool which is the equivalent to the LOGICAL data type. Operators for LOGICAL variables are given in Table 2.5 p47 of BB. The code example below checks whether a number lies between 10 and 20. INTEGER :: n LOGICAL :: LARGE_ENOUGH LOGICAL :: SMALL_ENOUGH LOGICAL :: VALID PRINT *,’Enter a value for n which lies between 10 and 20’ READ *,n LARGE_ENOUGH = (n>=10) SMALL_ENOUGH=(n<=20) VALID =(LARGE_ENOUGH .AND. SMALL_ENOUGH) IF (VALID == .TRUE. ) THEN PRINT *, n, ‘is acceptable’ ELSE PRINT *, n, ‘is not acceptable’ ENDIF STOP END Data Type: Character C++ defines the type char which is an 8-bit integer. Literal constants are written with single quotes, ‘n’, ‘o’, ‘w’, etc. C++ uses arrays of type char to represent strings. f90 there is a string type called CHARACTER but no single letter type. The length of a particular CHARACTER variable is specified in its declaration as CHARACTER :: alphabet*26 alphabet = ‘abcdefghijklmnopqrstuvwxyz’ PRINT *, alphabet Will print out the alphabet as a single ‘word’. Strings such as alphabet can be manipulated using the appropriate string operators (Table 2.5 p 47 BB). Structures Structures will be familiar to you from C. They also exist in f90 where they are denoted by the symbol TYPE. Here is an example of equivalent structures in C++ and f90. struct element { char symbol[3]; int atomic_number; float atomic_weight; }; TYPE ELEMENT CHARACTER :: SYMBOL*2 INTEGER :: ATOMIC_NUMBER REAL :: ATOMIC_WEIGHT END TYPE ELEMENT Initialisation is done as follows: element carbon = {“C”,12,12.0} ; // double quotes for a string in C++ TYPE(ELEMENT) :: CARBON=ELEMENT(‘C’,12,12.0) Example of use of structures: element hydrogen, oxygen; TYPE(ELEMENT):: HYDROGEN,OXYGEN float water_weight; REAL :: WATER_WEIGHT water_weight = WATER_WEIGHT = 2.0*hydrogen.atomic_weight 2.0*HYDROGEN%ATOMIC_WEIGHT + oxygen.atomic_weight ; + OXYGEN%ATOMIC_WEIGHT Arrays 1D arrays in f90 can be declared using either of the methods below: REAL :: a(8) REAL(KIND(0.0D0)), DIMENSION(8) :: profile Note that f90 uses round brackets () to indicate array elements whereas C++ uses square brackets []. By default f90 begins labelling array elements at (1) whereas C++ begins labelling at [0]. However, f90 allows array elements to be labelled beginning at other numbers. For example REAL :: a(1:8) ! equivalent to a(8) REAL :: b(0:7) ! like C++ REAL :: c(12:20) ! are all 8 element arrays This flexibility in f90 allows arrays to be used without an offset. They can be initialised when they are declared. INTEGER INTEGER :: d(4) = (/1,2,3,4/) :: e(6) = (/(2*I-1,I=1,3),3*0/) ! sets 1,3,5,0,0,0 In f90 an array can be constructed using a list of values separated by commas beginning and ending with the bracket-slash combination shown. Higher-dimensional arrays are declared in a similar way. There is a limit of 7 dimensions in f90. REAL :: P(1:5,1:3), Q(0:4,0:2), R(2,3,4,5,6,7) Elements of an array are referred to as e.g. P(2,3) for the 2,3 element P(2,:) for the second row P(2:4,1:2) for a sub-block containing the elements indicated A very important difference in f90 and C++ which affects the speed of execution when large arrays are being handled is the order of elements in memory. In f90 the first index (row index) runs fastest while in C++ the first index runs slowest. If an array being used in a calculation is so large that it is not all cached at once, then a loop which consecutively accesses array elements which are not simultaneously cached will run relatively slowly because of time spent fetching data to cache.Chapter 4 Control Control in a programme is achieved using conditional statements such as the IF statement. In both C++ and f90 the syntax for the simplest use of the IF statement is the same (and obvious). if (condition) statement ; IF (condition) statement In both languages the IF statement evaluates a logical expression which contains logical variables. These take the value .TRUE. or .FALSE. in f90. In C++ there is no logical variable type and so types int or char are used instead. A logical or Boolean operator acts on logical variables. The logical operators in C++ and f90 syntax in order of precedence are ! && .NOT. .AND. || .OR. See Table 4.1 on p78 of BB for the truth table for these operators. Logical expressions can also involve relational operations which act on ordinary variables (int, float etc.) but may appear in conjunction with logical operators. These operators are < > <= >= == != (/= in f90). f90 also recognises relational operators of f77. .LT. .GT. .LE. .GE. .EQ. .NE. For example if (i < 3> && (j >=4) statement IF (i > 3) .AND. (j >=4) statement If statement runs to more than one line then statement is enclosed in {} (C++) or is replaced by THEN with statements on following lines and terminated by ENDIF (f90). IF (i > 3) .AND. (j >=4) THEN DO THIS DO THAT ENDIF See ch4_1.f and ch4_2.f for illustration. The compound IF-ELSE statement allows more than one distinct conditions to be tested. if (dev < tol) cout <<”converged\n”; else cout << “no convergence\n”; IF (dev < tol) THEN !condition TRUE PRINT *,'converged' ELSE !must be on its own line PRINT *,'no convergence' ENDIF IF and IF-ELSE statements can be nested and f90 provides the ELSE IF statement, which is equivalent to ELSE followed by IF on a separate line. Multiway choices: switch/CASE When a variable can take a discrete range of values (say from a menu of 5 choices) then nested IF statements can become unwieldy and are replaced by CASE (f90) or switch (C++). switch(option) { case 'A': analyse(); break; case 'S': SELECT CASE(option) CASE('A') CALL analyse CASE('S') store(); break; case 'Q' CALL store case 'E': exit(); default: cout<<”Invalid Option\n”; } CASE('Q') STOP 'Q Entered' CASE('E') STOP 'E Entered' CASE DEFAULT PRINT *, 'Invalid Option' END SELECT There is an important difference between the way in which C++ and f90 handle the case statement. In C++, control is transferred to the point : where the appropriate statement is to be executed and a break; statement then returns control to the point immediately after that statement. In f90 control only passes back after the END SELECT statement. Indefinite iteration and while loops The while or DO WHILE statement acts like an IF statement which is applied repeatedly until it returns .TRUE.. while (size > storage) getmore(storage) ; DO WHILE (size > storage) CALL getmore(storage) ENDDO Testing can also be done at the end of a loop in C++. do { error = refit(data); } while (error > tolerance); Indexed Iteration In f90 indexed iteration is achieved with a DO/ENDDO loop and in C++ it is achieved with a for loop. for (i=1;i<4;i++) { a(i) = 2*i; a(i) = 2*i + 1; i++;} DO I = 1,10,2 !increment in steps of A(I) = 2*I A(I+1) = 2*I + 1 ENDDO In both C++ and f90 i, I must be an integer. Both languages provide means of escaping from a block of code. Using CYCLE in f90 and continue in C++ makes the programme skip to the next iteration in a loop; using EXIT and break take you out of the whole loop. Chapter 5 Subprograms: Functions and Subroutines Functions and Subroutines Many computer programs employ repetition of a particular task many times and any repeated task may be required in different parts of the program. To mimise the size of a program, avoid errors in entering the program, etc. it is essential to use a subprogram for such tasks. Subprograms are independent program units which communicate via arguments, a return value (if applicable) and possibly also global data. In f90 there are two varieties of subprogram, functions and subroutines while in C++ there are only functions. A f90 function returns only a single result (e.g. floating point number, but not a matrix). When more than one result is returned a subroutine must be used. In C++ a function can return single results (through the return statement) as well as matrices, etc. (when they are included in the argument list). The following program in C++ and f90 illustrate this. #include <iostream.h> //function prototypes void get_data(float data[], int n); float mean(float data[], int n); PROGRAM analysis REAL,DIMENSION(100) :: data REAL, EXTERNAL :: mean CALL get_data(data,100) PRINT *,'Average', mean(data,100) STOP 'normal exit : analysis' END PROGRAM analysis //main program main() { float data[100]; get_data(data, 100); cout <<”Average” << mean(data,100); } void get_data(float d[], int n) { for(int i=0; i<n;i++) cin >> d[i]; // get data } float mean(float a[], int m) { float sum = 0.0 ; for(int i=0; i<m; i++) sum += a[i]; return sum /float(m); } SUBROUTINE get_data(dat,n) INTEGER :: j, n REAL, DIMENSION(:) :: dat DO j=1, n READ *, dat(j) ENDDO RETURN END SUBROUTINE get_data REAL FUNCTION mean(a, m) INTEGER :: j, m REAL, DIMENSION(:) :: a REAL :: sum = 0.0 DO j=1,m sum = sum + a(j) ENDDO mean = sum /REAL(m) RETURN END FUNCTION mean In the f90 program above get_data is a subroutine while mean is a function. The arguments to get_data are a REAL array data and an integer n. The names of the argument variables where the subroutine (or function) is called and the name of the variables in the subroutine (or function) do not have to be the same (and naming them differently avoids confusion when the subroutine is called using different arrays in the argument list from other points in the program). The code above is as it appears in BB on p 104. However, this code as is gives a segmentation fault (memory) error when it is compiled and run with pgf90. This problem is fixed by giving the arrays dat and a fixed dimensions, with the same size as data in the main body of the program. This code is in ch5_1.f. Another way to dimension arrays in this program is to declare data to be ALLOCATABLE and then read in the dimension of data from the keyboard at runtime. data should then be DEALLOCATEd when the array is no longer needed. The code for this is in ch5_1a.f. Note how dat and a used in get_data and mean are declared. When get_data is called, dat is uninitialised; get_data returns returns the array dat initialised with values entered from the keyboard. Since an array is returned rather than a single result a subroutine must be used. The function mean returns a single result (the mean value, called mean) and so a function can be used instead. Program control is passed back to the calling program by the RETURN statement. It must appear just before the END statement but it can also appear more than once in a subroutine, for example, in conjunction with a CASE statement or IF statement. In the analysis program, the function mean returns what was last assigned to mean within the function. (In this case this is in the line mean = sum / REAL(m)). Subroutines are invoked using the CALL statement while functions are not called explicitly, they are just used in an expression. Arguments, prototyping and interface blocks Arguments in subroutines and functions are used to pass information from the calling program to the function or subroutine, and sometimes vice versa. This is therefore an important means of sharing data. Other methods are: global variables, modules and internal subprograms. When there are no arguments, argument brackets are omitted (unlike C++ where they are retained in that case). It is important that the types of data, array sizes, etc. passed as arguments in subroutines and functions are consistent between the CALL and the SUBROUTINE itself, for every instance where a subroutine is called. In C++ this is achieved using prototypes in header files (xxx.h), or at the beginning of small programs before the main() function. In f90 this is done using an INTERFACE block. This contains a copy of the subprogram statement and the declarations of its arguments. Interface definitions can be kept in a separate file and read at compile time using INCLUDE <filename>. INTERFACE SUBROUTINE out(z) REAL :: z END SUBROUTINE END INTERFACE Call by reference, call by value When a variable is specified as an argument in a subprogram it can either be passed to the subprogram as the address of the variable or its current value. The former is called call by reference, the latter, call by value. If the actual argument in the call is a variable (including arrays, structures, etc.) then a call by reference allows data in the variable at the time of the call to be modified, whereas a call by value does not, because only a copy of the current value of the variable is passed. f90 arguments are called by reference whereas in C++ they are called by value, unless the address of the variable is passed explicitly by passing a pointer to the variable. Modules A module comprises a collection of subprograms, type definitions and data that will be shared by the subprograms and can be made use of by more than one program, allowing programming to be modularised. Modules can be compiled separately and result in .mod as well as .o files as output. Another program can invoke a module with the USE statement. Modules can be nested using nested USE statements. A module begins with type definitions, variable declarations and interface blocks and then after, the CONTAINS statement, subprograms are given. file ch5_2.f PROGRAM testplot USE graph_ps ! define 8 pointed star TYPE(point) :: star(8) INTEGER :: i,j REAL :: theta ! open file for output OPEN(graphics_unit,file='plot01.ps') WRITE(graphics_unit,*)'%!PS' WRITE(graphics_unit,*)'gsave' DO i = 1,8 ! define 8 points theta = (REAL(i)-0.5)*3.14159/4. star(i)%x = 0.5 + 0.5*cos(theta) star(i)%y = 0.5 + 0.5*sin(theta) ENDDO ! draw 8 circles DO i = 1,8 CALL circle(star(i),0.05) ENDDO ! draw lots of lines DO i = 2,8 DO j = 1,i CALL line(star(i),star(j)) ENDDO ENDDO WRITE(graphics_unit,*)'showpage grestore' END PROGRAM testplot file ch5_2_mod.f MODULE graph_ps ! type definition TYPE point REAL :: x,y END TYPE point ! global data REAL :: scale = 400.0 INTEGER :: graphics_unit = 20 CONTAINS SUBROUTINE circle(p,r) TYPE(point) :: p REAL :: r CHARACTER :: form*7 = '(3I8,A)' WRITE(graphics_unit, form) NINT(p%x*scale),NINT(p%y*scale), *NINT(scale*r),' 0 360 arc stroke' RETURN END SUBROUTINE circle SUBROUTINE line(from, to) TYPE(point) :: from, to CHARACTER :: form*7 = '(2I8,A)' WRITE(graphics_unit, form) NINT(scale*from%x),NINT(scale*from%y), *' moveto' WRITE(graphics_unit, form) NINT(scale*to%x),NINT(scale*to%y), *' lineto stroke' RETURN END SUBROUTINE line END MODULE graph_ps Compile and run this program using the compiler command pgf90 -o ch5_2 ch5_2_mod.f ch5_2.f The order _mod.f first then calling programme second is important as the latter needs the compiled module in its compilation. Chapter 6 Characters and Strings Character sets in C++ and f90 Fortran a-z A-Z 0-9 , . ; : ? ! ' “ () <> / + - = # % & * $ _ C++ a-z A-Z 0-9 , . ; : ? ! ' “ () [] {} < > | / \ ~ + - = # % & ^ * _ Converting characters to integers ACHAR(n) n INTEGER returns CHARACTER character corresponding to n in ASCII character set CHAR(n) n INTEGER returns CHARACTER character corresponding to n in your system's character set IACHAR(c) c CHARACTER returns INTEGER integer corresponding to c in ASCII character set ICHAR(c) c CHARACTER returns INTEGER integer corresponding to c in ASCII character set Strings of several characters A continuous collection of characters is known as a string, for example, 'Hello World' (including the space) is a string. C++ uses double quotes to enclose strings whereas f90 uses single quotes. #include <iostream.h> cout << “Hello World\n”; #include <stdio.h> printf(“Hello World\n”); PRINT *, ' Hello World' WRITE(*,*) ' Hello World' The \n control sequence is needed in C or C++ to begin a new line after printing the string. Fortran includes the new line control sequence automatically. To print a string in f90 which is longer than 80 characters use the continuation character at the end of the first line and the beginning of the second. PRINT *, ' hello, hello, hello, & & you big wide wonderful world' String variables String variables are collections of characters which we want to treat symbolically. In C++ this is done using an array of type char , i.e. a collection of one-byte integers consecutive in memory. Fortran does not handle single characaters separately but treats them as CHARACTER variables of size one. char alphabet[27] ; CHARACTER :: alphabet*26 C++ requires an extra memory allocation because the C++ string contains an extra termination character \0 that marks the end of the string. Elements of the string alphabet can be accessed as members of the array (e.g. alphabet[0] is “a”). In f90 this is done using substrings (see below). When passing a string as an argument to a functionor subroutine it is passed with brackets but no size is specified. int query(char q[]) LOGICAL FUNCTION query(q) // Library function that prints a query CHARACTER :: q*(*), reply*20 // obtains a yes or no answer DO WHILE (.True.) // and returns true or false PRINT *, q { READ *, reply char reply; SELECT CASE(reply) while (cout << q) CASE('Y'); query = .True. { // repeat until satisfied CASE('y'); query = .True. cin >> reply ; CASE('N'); query = .False. switch (toupper(reply)) CASE('n'); query = .False. {case 'Y' : CASE DEFAULT return 1; PRINT *, ' Sorry?', & case 'N' : & ' Please reply Y or N' return 0; CYCLE } END SELECT cout << “Eh? Please reply Y or N\n”;RETURN } ENDDO } END FUNCTION query toupper() converts to upper case. The C++ program reads only the first character (reply is char reply) so yes will be read as a Y, etc. String expressions Two Fortran strings may be joined using the concatenation operator // CHARACTER :: forename*10, surname*10, fullname*20 fullname = forename // surname Additional string manipulation function in Fortran are REPEAT(s,n) TRIM(s) ADJUSTL(s) ADJUSTR(s) string s repeated n times s with trailing blanks removed s with leading blanks removed s with trailing blanks removed and inserted at beginning Substrings In Fortran part of a string can be accessed by specifying a particular range of characters in the string. CHARACTER timeofday*30 CHARACTER mess*30 = 'Good Morning' mess(6:8) = 'Eve' timeofday = mess(6:12) mess(:4) will extract the first 4 characters of mess and mess(6:) will extract the last characters neginning at 6. String comparison: equality and sorting The f90 function LEN(string) returns the declared length of a string LEN_TRIM(string) returns the length of a string not counting trailing blanks. String comparison in Fortran is easy. The usual relational operators can be used so that you can say, for example, IF(answer == 'YES') ... If strings of different length are compared the shorter one is padded with trailing blanks before the comparison is made, so that “Hello” and “Hello “ are equal in Fortran. Fortran provides a set of functions for comparing strings according to the ASCII character set. LGE(SA, SB) LGT(SA,SB) LLE(SA,SB) is lexically greater than or equal to is lexically greater than is lexically less than or equal to To find whether one short string occurs in another longer string use INDEX(string, substring) returns an integer which is the position of the first appearance of substring in string SCAN(string1, string2) returns the location of the first character in string1 which is also in string2. Chapter 7 Pointers Pointers are variables which can be set to contain the addresses of other variables. This provides a very direct way of moving about in arrays. Pointer features of the language are better developed in C++than in f90 so we will review pointers in C++ first. Pointer declaration and initialisation float *pointx; int *pointj; shape *pointsh; // pointer to a float // pointer to an int // pointer to a structure declared earlier Pointers may also be declared using the syntax float* pointx; when only a single pointer is being declared. Pointers must be initialised before being used, i.e. they must be made to point to an object (variable, array, function, etc. ) whose type they have been initialised for. For variables this is accomplished using the 'address-of' unary operator &. int i = 100; int *p; p = &i; // p is a pointer to an int // p now points to i To access the value of the variable which a pointer points to we use the 'value-of' or dereferencing operator *. int j, k = 10; j = *p; *p = k; // takes value of i (= 100) // i is assigned value of k (= 10) The name of an array is synonymous to a pointer to the array. int a[10], i; i = a[0]; i = *a; // these two statements are equivalent as a is a pointer to a[0]; Pointers can be incremented and decremented and compared int *p = a; // pointer p initialised to start of array a[0] int *p = a+5; // pointer q initialised to a[5] q[3] = 17; // set a[8] to 17 if (p == q) { p +=1 ; } Pointers to functions C++ pointers can point to functions which are, after all, an area of memory containing instructions to be executed. When a pointer points to a function, the return type and the type of each parameter must be specified. the address-of operators is used on the name of the function being pointed to. double (*trigfun)(double); trigfun = &sin; // declare trigfun double y = (*trigfun)(1.24); // y = sin(1.24); Pointers in f90 f90 provides for dynamic allocation of data but few facilities for pointer manipulation. Instead of declaring the pointer, you declare an object of the type pointed to with the pointer attribute. This means that the declaration does not allocate space for the actual object, but provides a handle to get at an object which will be associated to an actual object later, by allocation or assignment. REAL, POINTER :: p ! p declared but not allocated ALLOCATE(p) ! p now allocated p = 13.7 ! p used like any other real DEALLOCATE(p) ! free the memory Allocating and deallocating a single variable isn't particularly useful. They are needed when large arrays or user-defined structures are used. Types must match in pointer assignments. Pointers declared as real can only be assigned to reals, inegers to integers, and so on. REAL, DIMENSION(:,:,:), POINTER :: cube .... N = 50 ALLOCATE(cube(N,N,N)) .... DEALLOCATE(cube) Assignment associates a pointer to an already existing object (as opposed to allocation, which associates it to a new one). Because the usual expression syntax assumes that we want to refer to the object pointed at rather than the pointer itself, a special operator is needed. This is the pointer assignment operator => REAL, TARGET :: x,y REAL, POINTER :: p,q .... y = 1.234 p=> x ! pointer assign p to x p=y ! normal assignment of y to p PRINT *,x ! will give 1.234 q => p ! x, q and p are now equivalent The TARGET attribute in the declaration of x and y is a sign to the compiler that x and y may be accessed in non-obvious ways and that the compiler should not be too clever in performing code optimisation steps. Chapter 8 Input and Output Format strings, formatted input and output When a variable or an expression is sent to the output stream its value has to be formatted as a string of characters. Formatted output may include extra words to help the user understand the output, such as, 'The zero in the function occurs at'. The type of variable (REAL, DOUBLE PRECISION, etc) must be specified and the details of how the output is actually to be written. 12.34, 12.340000, 0.1234E+02 or 12.3. To write to the screen (as we have been doing already) we simply use the PRINT statement in f90 and replace the * by a format string. The following code illustrates how C++ and f90 handle various formatting features. printf(“Goodbye World \n”); PRINT '(“Green World”)' printf(“Answer %8.3f \n”, x); PRINT'(“Answer “, F6.3)', x printf(“Answers %4i %9.4f %6.3f \n”,j,x,y); PRINT'(“Answers”,I4,F9.4,F8.3)'j,x,y printf(“For %4i hits \nQ= %9.2f \n”,n,Q); PRINT'(“For”,I4, “hits “,/,”Q = “,F9.2)',n,Q Since format strings are strings they can be stored in string variables, often with a noticeable gain in clarity. char fmt1[]=”Values %4i %9.4f %6.3f \n”; CHARACTER :: fmt1*30 printf(fmt1,j,x,y); fmt1='( “Values ”, I4,F9.4,F8.3)' PRINT fmt1, j, x, y A format specification in C++ consists of a string containing ordinary characters, data descriptors and escape sequence characters. In f90 it consists of text strings, data descriptors and control descriptors. ordinary characters/text strings go directly to the output for printing/writing to a file data descriptors determine exactly how various variables are prionted/written control descriptors insert new lines, new pages, etc. Table 8.1 data f90 C++ Integer I i or d Binary B none Octal O o Hex Z x or X Floating point F f fixed point representation e.g. 123.456 Floating point E e or E exponent representation e.g. 1.23456E2 Floating point G g or G fixed point or exponent rep'n according to size Unsigned character none u Character none c String A s Logical L none prints T or F (C++ type bool will do this) The width w of an item and precision p is optional in C++ but is necessary in f90 (except for type A) and is specified as w.p. e.g. to write a floating point number which occupies 8 spaces and contains 4 decimal places (dp) use F8.4 in f90 or %8.4f in C++. The 4 places not used for the dp are used for the decimal point, leading digit, sign and a space to separate that number from adjacent numbers. If you don't leave enough spaces for the number, f90 will fill the specified format with asterisks whereas C++ will expand the number of digits as necessary to print the number. In C++ you must specify the newline control sequence \n at the end of a format string in order to begin the next output on a newline. f90 provides a new line at the end of a PRINT statement automatically. If a width (Aw, e.g. A10) is specified with a string the extra blanks will be inserted (if w is greater than the string length) or only part of the string is printed (if w is shorter than the string). The format string can be given in place of the * in a PRINT statement or it can be given separately in a FORMAT statement 100 FORMAT'(“The answer is “, F6.3)' PRINT 100, x ! we see that using * in PRINT *, x uses the default format PRINT 'The answer is', F6.3, x ! alternative The format statement with label 100 can be used in more than one PRINT statement The WRITE statement writes output to a file which may have the default format or a format WRITE(6,*) start WRITE(6,100) finish The WRITE statement contains an integer which is assigned to a particular file when it is opened (see below) followed by the format to be used. Units 5 and 6 usually are reserved for keyboard (standard input) and the screen (standard output), although 1 and 2 are used on some computers. So WRITEing to unit 6 is equivalent to PRINTing. f90 allows for loops to be included in WRITE statements which is handy for writing out elements of arrays. WRITE(6,'(8I5)') (ind(j), j = 1,8) WRITE(6,'(“ “,5F8.3)') (( array(j,k), k = 1,5) , j = 1,3) In order to read data from keyboard or a file we use the READ statement. Reading data from the keyboard can usually be done with the default format (*) (so long as the data you enter makes sense, given the variable type it is being read into) but a format must usually be specified when data are read from a formatted file (see below). An exception would be when data consist of single numbers on lines separated by line breaks, when the default format * could be used. However, files frequently contain several columns of data separated by spaces and these must be specified in the format statement. READ '(10X,I2)', n ! reads an integer of up to 2 digits after 10 spaces ! x is the miss a character format decsriptor, on output it ! produces a space Files, streams and records In Fortran, I/O is based on the concept of records which, by default, contain 80 characters. This is a legacy of Fortran's history as one of the first compiled languages and is a consequence of the need for backwards compatibility of the language. In Fortran, data is read or written to a file one record at a time. On the other hand the stream based I/O of C and C++ works one byte at a time. In Fortran, files are opened and closed with the OPEN and CLOSE statements. The OPEN statement assigns a unique integer to the file unit number. INTEGER :: file1 = 22 OPEN(21,FILE='measurements.dat') OPEN(file1,FILE='results.dat') CLOSE(21) CLOSE(22) ! uses the unit number directly ! uses an integer containing the unit number There are additional arguments to OPEN which specify RECL = 20 ! Records for output are 20 characters rather than the default 80 ACTION = 'READ' ! Open existing file for reading, also READWRITE, WRITE STATUS = 'OLD' ! File exists, also NEW, UNKNOWN, REPLACE ACCESS = 'DIRECT' ! Direct access file (see below) also SEQUENTIAL (default) POSITION = 'APPEND' ! Additional WRITEs go at end of existing file IOSTAT = J ! variable is set to zero if file opened successfully ERR = 999 ! On return from unsuccessful open will jump to this label FORM = 'FORMATTED' ! Default (ASCII), also UNFORMATTED or binary file 999 PRINT *, 'File opening error ', J Formatted versus unformatted files Formatted files written by Fortran programs consist of 80 character sequences by default (unless a RECL control keyword is used) and consequently do not make the best use of disk space and are written and read relatively slowly compared to unformatted (or binary) files in which the contents of memory are (effectively) dumped to disk. These files are only machine readable and may not transfer between different computers (i.e. a binary file created under one system may not be readable by another). If you attempt to open one of these files with an editor the screen will contain a scramble of characters. They are therefore commonly used for large temporary (or scratch) files created while a program is executing and may be deleted immediately on termination of the program. To open an unformatted file: OPEN(12,FILE='raw.data',FORM='UNFORMATTED',RECL=50) WRITE(12) x, y, z ! WRITEs the READs 3 numbers in binary format from unit 12 REWIND(12) READ(12) x, y, z CLOSE(12) Moving about in files As we see from the last example, it is necessary to be able to determine where we begin reading from or writing to files. The simplest change in where we begin reading or writing uses the REWIND control keyword and the action of this is simply to reposition the file so that we access data at the very beginning of the file. ENDFILE(12) will move to the end of file with unit number 12. BACKSPACE(12) will move the access point back one record, so that you could, for example, reread a particular record. For some applications, such as retrieving data from a database, it is necessary to have more specific control over file access. This can be done in a direct access file, which can be opened using OPEN(67, FILE='database.dat',ACCESS='DIRECT') The alternative access type is SEQUENTIAL and one can use REWIND, BACKSPACE with this default ACCESS type. Direct access files are written and read using the WRITE and READ statements (same as for SEQUENTIAL files) but the record number must also be specified. READ(67,'(I8)',REC=94) J ! Formatted read of integer written with format I8 into ! variable J from unit 67 DO j = 1,10 WRITE(68, REC=j+17) value(j) ! Unformatted write of value(j) to record j+17 ENDDO Closing files Closing files written by Fortran programs is achieved with the CLOSE statement. It must have the file unit number as an argument and can also have IOSTAT, ERR and STATUS = 'KEEP' or STATUS='DELETE' as arguments.