Fortran 90 Tutorial - grdelin

Fortran 90 Tutorial - grdelin Fortran 90 Tutorial - grdelin

kft.umcs.lublin.pl
from kft.umcs.lublin.pl More from this publisher
11.07.2015 Views

Fortran 90 TutorialMichael MetcalfCN Division, CERN, CH 1211, Geneva 23, Switzerland1 Language Elements 12 Expressions and Assignments 63 Control Statements 84 Program Units and Procedures 95 Array handling 126 Pointers 167 Specification Statements 208 Intrinsic Procedures 229 Input/Output 23Index 25Full details of all the items in this tutorial can be found in Fortran 90/95 Explained, byM. Metcalf and J. Reid, (Oxford, 1996), the book upon which it has been based.Fortran 90 contains the whole of FORTRAN 77—only the new features are described inthis tutorial.The tutorial is also available on WWW using the URLhttp://wwwcn.cern.ch/asdoc/f90.html.The author wishes to thank Michel Goossens (CERN/CN) for his helpful and skilful assistancein preparing this tutorial.Version of October 1995

<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong>Michael MetcalfCN Division, CERN, CH 1211, Geneva 23, Switzerland1 Language Elements 12 Expressions and Assignments 63 Control Statements 84 Program Units and Procedures 95 Array handling 126 Pointers 167 Specification Statements 208 Intrinsic Procedures 229 Input/Output 23Index 25Full details of all the items in this tutorial can be found in <strong>Fortran</strong> <strong>90</strong>/95 Explained, byM. Metcalf and J. Reid, (Oxford, 1996), the book upon which it has been based.<strong>Fortran</strong> <strong>90</strong> contains the whole of FORTRAN 77—only the new features are described inthis tutorial.The tutorial is also available on WWW using the URLhttp://wwwcn.cern.ch/asdoc/f<strong>90</strong>.html.The author wishes to thank Michel Goossens (CERN/CN) for his helpful and skilful assistancein preparing this tutorial.Version of October 1995


!"%&;? =:+blank-*/(),.$'(old) (new)<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 11. Language ElementsThe basic components of the <strong>Fortran</strong> language are its character set. The members are:the lettersA...Zanda...z(which are equivalent outside a character context);the numerals0...9;the underscore_andthe special charactersFrom these components, we build the tokens that have a syntactic meaning to the compiler. There are six classes of token:Label:123Operator:.add.FUNCTIONstring_concat(s1,s2)!Thisisacomment ENDFUNCTIONstring_concat TYPE(string),INTENT(IN)::s1,s2 string_concat%string_data=s1%string_data(1:s1%length)//& TYPE(string)string_concatup to 31 characters, including a_).From&_name...'averylong& string_concat%length=s1%length+s2%length s2%string_data(1:s2%length)!Thisisacontinuationthe tokens, we can build statements. These can be coded using the new free source form which does not require positioninga rigid column structure, as follows:&string'start_of&Note the trailing comments and the trailing continuation mark. There may be 39 continuation lines, and 132 characters per line.Blanks are significant. Where a token or character constant is split across two lines:a leading&on the continued line is also required.Automatic conversion of source form for existing programs can be carried out byCONVERT(CERN Program Library Q<strong>90</strong>4). Itsoptions are:significant blank handling;indentation;CONTINUEreplaced byENDDO;Separator:/()(//),==>:::;%Constant:123.456789_longKeyword:ALLOCATABLEName:solve_equation(can havename added to subprogramENDstatement; andINTEGER*2etc. syntax converted.The source code of theCONVERTprogram can be obtained by anonymous ftp tojkr.cc.rl.ac.uk(130.246.8.23). The directoryis/pub/MandRand the file name isconvert.f<strong>90</strong>.


INTEGER 10-99932767+10 INTEGER,PARAMETER::two_bytes=SELECTED_INT_KIND(4) -1234_two_bytes +1_two_bytes<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 2-1234_2<strong>Fortran</strong> has five intrinsic data types. For each there is a corresponding form of literal constant. For the three numeric intrinsictypes they are:KIND(1) KIND(1_two_bytes)Examples are:RANGE(1_two_bytes)for the default kind; but we may also define, for instance for a desired range of104to104, a named constant, saytwo_bytes:B'01010101' O'01234567'that allows us to define constants of the formZ'10fa'Here,two_bytesis the kind type parameter; it can also be a default integer literal constant, likebut use of an explicit literal constant would be non-portable.TheKINDfunctionINTEGER,PARAMETER::long=SELECTED_REAL_KIND(9,99)supplies the value of a kind type parameter:and theRANGEfunction supplies the actual decimal range (so the user must make the actual mapping to bytes):Also, inDATAstatements, binary, octal and hexadecimal constants may be used:COMPLEXKIND(1.7_long) PRECISION(1.7_long) RANGE(1.7_long)REALThere are at least two real kinds – the default, and one with greater precision (this replacesDOUBLEPRECISION). We mightspecifyfor at least 9 decimal digits of precision and a range of1099to1099, allowingDIGITS(X) EPSILON(X)Also, we have the intrinsic functionsHUGE(X) (1,3.7_long)that give in turn the kind type value, the actual precision (here at least 9), and the actual range (here at least 99).RADIX(X) RANGE(X) TINY(X)This data type is built of two integer or real components:The numeric types are based on model numbers with associated inquiry functions (whose values are independent of the valuesof their arguments). These functions are important for writing portable numerical software.Number of significant digitsAlmost negligible compared to one (real)Largest numberMAXEXPONENT(X)Maximum model exponent (real)MINEXPONENT(X)Minimum model exponent (real)PRECISION(X)Decimal precision (real, complex)Base of the modelDecimal exponent rangeSmallest postive number (real)


CHARACTER 'Astring' "Another" 'A"quote"''' 2_'' KIND('ASCII')<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 3The forms of literal constants for the two non-numeric data types are:.FALSE. .true._one_bit KIND(.TRUE.)(the last being a null string). Other kinds are allowed, especially for support of non-European languages:INTEGER(KIND=2)i REAL(KIND=long)aandCOMPLEXagain the kind value is given by theKINDfunction:LOGICAL CHARACTER(LEN=20)wordLOGICALHere,CHARACTER(LEN=2,KIND=Kanji)kanji_wordthere may also be different kinds (to allow for packing into bits):CHARACTER(2,Kanji)kanji_word current Pravdaand theKINDfunction operates as expected:We can specify scalar variables corresponding to the five intrinsic types:TYPE(person)you,me REAL CHARACTER(10)name agewhere the optionalKINDparameter specifies a non-default kind, and theLEN=specifier replaces the*lenform. The explicitKINDandLENspecifiers are optional and the following works just as well:you%age ENDTYPEpersonFor derived-data types we must first define the form of the type:you=person('Smith',23.5)and then create structures of that type:To select components of a derived type, we use the%qualifier:and the form of a literal constant of a derived type is shown by:which is known as a structure constructor.


TYPE(triangle)t ENDTYPEpointREALx,y TYPE(point)a,b,c<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 4t%at%bt%c ENDTYPEtriangleDefinitions may refer to a previously defined type:t%a%xt%a%yt%b%xetc. REALa(10)and for a variableINTEGER,DIMENSION(0:100,-50:50)::mapof typetriangle, as inwe then have components of typepoint:a(1)which, in turn, have ultimate components of typereal:a(i:j)We note that the%qualifier was chosen rather than.because of ambiguity difficulties.a(map(i,k:l)) map(i:j,k:l:m) a(i*j) !ranktwo !vectorsubscript !rankoneArrays are considered to be variables in their own right. Given(the latter an example of the syntax that allows grouping of attributes to the left of::and of variables sharing those attributesto the right), we have two arrays whose elements are in array element order (column major), but not necessarily in contiguousstorage. Elements are, for example,(/(0.1*i,i=1,10)/) (/(0,i=1,100)/) a(3:2) (/((/1,2,3/),i=1,10)/) (/1,2,3,4,5/) (/(i,i=1,9,2)/) !zerolengthand are scalars. The subscripts may be any scalar integer expression. Sections areWholethatt(2)arrays and array sections are array-valued objects. Array-valued constants (constructors) are available:t(2)%vertex ENDTYPEtriplet TYPE(triplet),DIMENSION(1)::t REAL,DIMENSION(3)::vertex !anarraycomponentofascalarmaking use of the implied-DOloop notation familiar from I/O lists. A derived data type may, of course, contain array compo-sonents:TYPEtriplet !ascalar(astructure)


...=page(j)(i:i) CHARACTER(80),DIMENSION(60)::page '0123456789'(i:i) you%name(1:2) !substringpage(j)(i:i-1)<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 5There are someACHARother interesting character extensions. Just as a substring as inREPEAT LEN_TRIM ADJUSTL !zero-lengthstring IACHAR(forASCIIset) ADJUSTR INDEX(s1,s2,BACK=.TRUE.) SCAN(foroneofaset) VERIFY(forallofaset)was already possible, so now are the substringsAlso, zero-length strings are allowed:Finally, there are some new intrinsic character functions:


eal2=integer+real1<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 62. Expressions and AssignmentsIF(a


MODULEstring_type ENDINTERFACE INTERFACEOPERATOR(//) MODULEPROCEDUREstring_concatENDTYPEstring<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 7For the moment, here is an example of an interface for concatenationINTERFACEOPERATOR(//) INTERFACEASSIGNMENT(=)MODULEPROCEDUREc_to_s_assign,s_to_c_assign INTEGERlength CHARACTER(LEN=80)::string_data SUBROUTINEc_to_s_assign(s,c)MODULEPROCEDUREstring_concat TYPE(string),INTENT(OUT)::sCONTAINS ENDINTERFACE s%string_data=c s%length=LEN(c) CHARACTER(LEN=*),INTENT(IN)::cand an example of part of a module containing the definitions of character-to-stringENDFUNCTIONstring_concat ENDSUBROUTINEc_to_s_assign SUBROUTINEs_to_c_assign(c,s) TYPE(string),INTENT(IN)::s c=s%string_data(1:s%length) ENDSUBROUTINEs_to_c_assign FUNCTIONstring_concat(s1,s2) CHARACTER(LEN=*),INTENT(OUT)::c :and character assignment. Theconcatenation function was shown already part 1.str1=string(2,char1//char2)!structureconstructor ENDMODULEstring_typeLOGICAL REAL,DIMENSION(5) REAL,DIMENSION(10,20)::a,b,c ::v,w flag(10,20)Defined operators such as these are required for the expressions that are allowed too in structure constructors (see chapter 1):c(1:8,5:10)=a(2:9,5:10)+b(1:8,15:20)So far we have discussed scalar variables. In the case of arrays, as long as they are of the same shape (conformable), operationsand assignments are extended in an obvious way, an element-by-element basis. Forv(2:5)=v(1:4) c=0. w=v+1. flag=a==b a=b c=a/b w=5/v+a(1:5,5) !arraysectionadditionandassignment !overlappingsectionassignment !wholearrayassignmentofscalarvalue!arraydivision,andadditiontosection !wholearraydivisionandassignment !wholearrayadditiontoscalarvalue !wholearrayrelationaltestandassignmentcan writeCEILING EXPONENT NEAREST SCALE FLOOR FRACTION RRSPACINGSPACING SET_EXPONENTMODULO(alsointeger)The order of expression evaluation is not specified order to allow for optimization on parallel and vector machines. Of course,any operators for arrays of derived type must be defined.There are some new real intrinsic functions that are useful for numeric computations:Like all FORTRAN 77 functions (SIN,ABS, etc., but notLEN), these are array valued for array arguments (i.e. are elemental).


labels:SELECTCASE(number) CASE(:-1) CASE(1:) CASE(0) n_sign=-1 !allvaluesbelow0 !only0 !NUMBERoftypeinteger<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 83. Control StatementsCASE(1,2,7,10:17,23) ENDSELECT n_sign=0 n_sign=1 !allvaluesabove0The CASE construct is a replcement for the computed GOTO, but is better structured and does not require the use of statementinner:DOi=j,k,l outer:DO CASEDEFAULT :IF(...)CYCLEEach selector list may contain a list and/or range of integers, character or logical constants, whose values may not overlapwithin or between selectors::IF(...)EXITouter !onlyintegersA default is available:There is onlytot=0. ENDDOouter ENDDOinnerone evaluation, and only one match.A simplified but sufficient form of the DO construct is illustrated bytot=SUM(a(m:n)) DOi=m,n ENDDO tot=tot+a(i)where we note that loops may be named so that the EXIT and CYCLE statements may specify which loop is meant.Many, but not all, simple loops can be replaced by array expressions and assignments, or by new intrinsic functions. For instancebecomes simply


SUBROUTINEouter<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 9CONTAINS4. Program Units and ProceduresIn order to discuss this topic we need some definitions. In logical terms, an executable program consists of one main programand zero or more subprograms (or procedures) - these do something. Subprograms are either functions or subroutines, whichare eitherENDSUBROUTINEouter REALx,y :ENDSUBROUTINEinner!SUBROUTINEmandatory REALy y=x+1. :external, internal module subroutines. (External subroutines are what we know from FORTRAN 77.)From an organizational point of view, however, a complete program consists of program units. These are either main programs,external subprograms modules can be separately compiled.An internal subprogram is one contained another (at a maximum of one level of nesting) and provides a replacement for thestatement function:MODULEinterval_arithmeticWe say that outer is the host of inner, and that inner obtains access to entities in outer by host association (e.g. to x), whereasy is a local variable to inner. The scope of a named entity is a scoping unit, here outer less inner, and inner.The names of program units and external procedures are global, and the names of implied-DO variables have a scope of thestatement that contains them.Modules are used to packageglobal data (replaces COMMON and BLOCK DATA);typeCONTAINSENDTYPEinterval INTERFACEOPERATOR(+) ENDINTERFACEdefinitions (themselves a scoping unit);subprogramsFUNCTIONadd_intervals(a,b) REALlower,upper(which among other things replaces the use of ENTRY);interface blocks (another scoping unit, see next article);namelistadd_intervals%lower=a%lower+b%lower TYPE(interval)add_intervals MODULEPROCEDUREadd_intervals TYPE(interval),INTENT(IN)::a,bgroups.An example ofadd_intervals%upper=a%upper+b%uppera module containing a type defition, interface block and function subprogram is:USEinterval_arithmetic ENDMODULEinterval_arithmetic ENDFUNCTIONadd_intervals : !FUNCTIONmandatoryand the simple statementprovides use association to all the module’s entities. Module subprograms may, in turn, contain internal subprograms.


SUBROUTINEshuffle(ncards,cards) SUBROUTINEmincon(n,f,x,upper,lower,equalities,inequalities,convex,xstart) INTEGER,INTENT(OUT),DIMENSION(ncards)::cards!outputvalues INTEGER,INTENT(IN)::ncards !inputvalues<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 10.ArgumentsWe may specify the intent of dummy arguments:CALLmincon(n,f,x,upper) REAL,OPTIONAL,DIMENSION::upper,lowerIF(PRESENT(lower))THEN!testforpresenceofactualargumentAlso, INOUT is possible: here the argument must be a variable (unlike the default case where it may be a constant).Arguments may be optional:CALLmincon(n,f,x,equalities=0,xstart=x0)allows us to callminconbyand inminconwe have someting like:!returnstheminimumvalueofthefunctionfunc(x)intheinterval(a,b) REALFUNCTIONminimum(a,b,func)Arguments may be keyword rather than positional (which come first):REAL,INTENT(in)::a,bOptional and keyword arguments are handled by explicit interfaces, that is with internal or module procedures or with interfaceblocks.Interface blocksAny reference to an internal or module subprogram is through an interface that is “explicit” (that is, the compiler can see all thedetails). A reference to an external (or dummy) procedure is usually “implicit” (the compiler assumes the details). However,we canENDFUNCTIONminimum ENDINTERFACE REALf,x :f=func(x)!invocationoftheuserfunction.:ENDFUNCTIONfunc REALFUNCTIONfunc(x) REAL,INTENT(IN)::xprovide an explicit interface this case too. It is a copy the header, specifications andENDstatement of the procedureconcerned, either placed a module or inserted directly:An explicit interface is obligatory for: optional and keyword arguments,POINTERandTARGETarguments (see later article), aPOINTERfunction result (later) and new-style array arguments and array functions (later). It allows full checks at compile timebetween actual and dummy arguments.


ENDINTERFACE INTERFACEgamma FUNCTIONdgamma(X) FUNCTIONsgamma(X) !specificnameforhighprecision !specificnameforlowprecision !genericname<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 11Overloading and generic interfacesInterface blocks provide the mechanism by which we are able to define generic names for procedures:volume=integrate(fy,ybounds) RECURSIVEFUNCTIONintegrate(f,bounds) !Integratef(x)frombounds(1)tobounds(2)where a given set of specific names corresponding to a generic name must all be of functions or all of subroutines.We can use existing names, e.g. SIN, and the compiler sorts out the correct association.We have already seen the use of interface blocks for defined operators and assignment (see Part 2).RecursionIndirect recursion is useful for multi-dimensional integration. To calculateENDFUNCTIONintegrate : ENDINTERFACE REAL,DIMENSION(2),INTENT(IN)::bounds REALintegrateENDFUNCTIONf FUNCTIONf(x) REALf,xwe might haveFUNCTIONfy(y)RECURSIVEFUNCTIONfactorial(n)RESULT(res) USEfunc !modulefunccontainsfunctionfINTEGERres,n REALfy,yIF(n.EQ.1)THEN yval=yELSEres=n*factorial(n-1) res=1and to integrate f(x, y) over a rectangleDirect recursion is when a procedure calls itself, as inENDREAL(SELECTED_REAL_KIND(12))dgamma,x ENDREAL(SELECTED_REAL_KIND(6))sgamma,xENDfy=integrate(f,xbounds)ENDENDIFHere, we note theRESULTclause and termination test.


<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 12DOi=1,n5. Array handlingArray handling is included in <strong>Fortran</strong> <strong>90</strong> for two main reasons:the notational convenience it provides, bringing the code closer to the underlying mathematical form;for the additional optimization opportunities it gives compilers (although there are plenty of opportunities for degradingoptimization too!).At thex(1:0)=3 ENDDO x(i)=b(i)/a(i,i) b(i+1:n)=b(i+1:n)-a(i+1:n,i)*x(i)same time, major extensions of the functionality in this area have been added.We have already met whole arrays in Parts 1 and 2—here we develop the theme.Zero-sized arraysA zero-sized array is handled by <strong>Fortran</strong> <strong>90</strong> as a legitimate object, without special coding by the programmer. Thus, inno special code is required for the final iteration where i = n.We note that a zero-sized array is regarded as being defined; however, an array of shape, say, (0,2) is not conformable with oneofSUBROUTINEsub(da) CALLsub(a) REAL,DIMENSION(0:10,0:20)::a :shape (0,3), whereasis a valid “do nothing” statement.Assumed-shape arraysThese are an extension and replacement for assumed-size arrays. Given an actual argument like:inSUBROUTINEswap(a,b)REAL,DIMENSION(:,:)::dathe corresponding dummy argument specification defines only the type and rank of the array, not its size. This information hasto be made available by an explicit interface, often using an interface block (see part 4). Thus we write justENDSUBROUTINEswap work=a a=b b=work REAL,DIMENSION(SIZE(a))::work!arraycreatedonastack REAL,DIMENSION(:) ::a,band this is as if da were dimensioned (11,21). However, we can specify any lower bound and the array maps accordingly. Theshape, not bounds, is passed, where the default lower bound is 1 and the default upper bound is the corresponding extent.Automatic arraysA partial replacement for the uses to which EQUIVALENCE is put is provided by this facility, useful for local, temporary arrays,as


MODULEwork_array ENDMODULE PROGRAMmain INTEGERn REAL,DIMENSION(:,:,:),ALLOCATABLE::work USEwork_array READ(*,*)n ALLOCATE(work(n,2*n,3*n),STAT=status) :DEALLOCATE(work)<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 13ALLOCATABLE and <strong>Fortran</strong> <strong>90</strong> provides dynamic allocation of storage; it relies on a heap storage mechanism (and replaces another use of EQUIV-ALENCE). An example, for establishing a array for a whole program, isa=0. DEALLOCATE(a,b)b=sqrt(a)!intrinsicfunctionresultasarrayobject REAL,DIMENSION(10)::a,bThePROGRAMtest!scalarbroadcast;elementalassignmentwork array can be propagated through the whole program via a USE statement in each program unit. We may specify anexplicit lower bound and allocate several entities one statement. To free dead storage we write, for instance,We willCONTAINS REAL,DIMENSION(3)::a=(/1.,2.,3./),b=(/2.,2.,2./),rmeet this later, the context of pointers.Elemental operations and assignmentsWe have already met whole array assignments and operations:ENDPROGRAMtest REAL,DIMENSION(:)::c,d r=f(a,b) FUNCTIONf(c,d) PRINT*,r REAL,DIMENSION(SIZE(c))::f f=c*d ENDFUNCTIONf!(orsomemoreusefulfunctionofcandd)In the second assignment, intrinsic function returns array-valued result for array-valued argument. We can write arrayvaluedfunctions ourselves (they require explicit interface):WHERE(a/=0.0)a=1.0/a!avoiddivisionby0WHERE(a/=0.0) ELSEWHEREWHEREENDWHERE a=HUGE(a)b=a a=1.0/aOften, we need to mask an assignment. This we can do using the WHERE, either as a statement:(note: test is element-by-element, not on whole array), or as a construct (all arrays of same shape):


ENDTYPEtripletREAL,DIMENSION(3)::du TYPE(triplet),DIMENSION(10,20)::tar u<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 14Array elementswe can reference a single element ofaas, for instance,a(1,1). For a derived data type likeandtar(n,2)%du(2)we can declare an array of that type:and a reference like[lower]:[upper][:stride]is an element (a scalar!) of type triplet, butis an array of type real,a(i,1:n) a(1:m,j) a(i,:)is an elementa(i,1:n:3)of it. The basic rule to remember is that an array element always has a subscript or subscripts qualifying at leastthe last name.a(i,10:1:-1) a((/1,7,3,2/),1)!vectorsubscriptArray subobjectsa(1,2:11:2)(sections)a(:,1:7) !partofonerow !partofonecolumn !wholerow !everythirdelementofrow !rowinreverseorder !11islegalasnotreferenced !ranktwosectionThe general form of for an array tar%du !illegalNote that a vector subscript with duplicate values cannot appear on the left-hand side of an assignment as it would be ambiguous.is illegal. Also, a section with a vector subscript must not be supplied as an actual argument to anOUTorINOUTdummy argument.Arrays of arrays are not allowed:Simple case: givenREAL,DIMENSION(100,100)::ainREALa(10,10)Thus,b((/1,7,3,7/))=(/1,2,3,4/)as


a(1,1) tar%u a(1:1,1) !scalar(rankzero) !arraysection(rankone)<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 15We noteDOT_PRODUCT tar(1,1)%u !arraysection(structurecomponent) !componentofanarrayelementthat a given value in an can be referenced both as element and as a section:dependingALL MATMULon the circumstances or requirements.By qualifyingANYobjects of derived type, we obtain elements or sections depending the rule stated earlier:COUNT MAXVAL Dotproductof2rank-onearraysMINVAL Trueifallvaluesaretrue Matrixmultiplication Trueifanyvalueistrue.Example:IF(ANY(a>b))THEN Numberoftrueelementsinarray Maximumvalueinanarray MinimumvalueinanarrayArrays intrinsic functionsVector and matrix multiplySIZE ALLOCATED PRODUCT SUM Arrayallocationstatus Productofarrayelements SumofarrayelementsArray reductionMERGE SHAPE UBOUND LBOUND Totalnumberofelementsinanarray Shapeofanarray(orscalar) Upperdimensionboundsofanarray LowerdimensionboundsofanarrayArray inquiryRESHAPE SPREAD UNPACK Mergeundermask Packanarrayintoanarrayofrank Reshapeanarray Replicatearraybyaddingadimension UnpackanarrayofrankoneintoanarrayundermaskArray constructionMINLOC CSHIFT EOSHIFT MAXLOC TRANSPOSE Locationoffirstminimumvalueinanarray Circularshift End-offshift Locationoffirstmaximumvalueinanarray TransposeofanarrayofranktwoArray reshapeArray manipulationArray location


REAL,POINTER::var ALLOCATE(var)<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 16var=var+2.36. PointersBasicsPointers are variables with thePOINTERattribute; they are not a distinct data type (and so no “pointer arithmetic” is possible):They are conceptually a descriptor listing the attributes of the objects (targets) that the pointer may point to, and the address, ifREAL,POINTER::objectany, of a target. They have no associated storage until it is allocated or otherwise associated (by pointer assignment, see below):REAL,TARGET::target_obj var=>object WRITE*,varvar=>target_obj !pointerassignmentand they are dereferenced automatically, so no special symbol is required. Inthe value of the ofvaris used and modified. Pointers cannot be transferred via I/O—the statementwrites the value of the ofvarand not the pointer descriptor itself.A pointer can var=>int_var INTEGER,POINTER::int_var!illegal-typesmustmatchpoint to other pointers, and hence to their targets, to a static object that has the TARGET attribute:but they are strongly typed:TYPE(entry),POINTER::chain REALvalue INTEGERindex TYPE(entry),POINTER::next!noterecursion !typeforsparsematrixand, similarly,chain%value ENDTYPEentryfor arrays the ranks as well as the type must agree.chain%indexA pointer canchain%next chain%next%value chain%next%indexbe a component of a derivedchain%next%nextdata type:and we can define the beginning of a linked of such entries:After suitable allocations and definitions, the first two entries could be addressed asbut we would normally define additional pointers to point at, for instance, the first and current entries in the list.


disassociated:DEALLOCATE(p,q)!forreturningstorage NULLIFY(p,q)!forsettingto'null'<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 17IF(ASSOCIATED(pointer))THENAssociationA pointer’s association status one ofIF(ASSOCIATED(pointer,target))THENundefined (initial state);associated (after allocation a assignment);Some care has to be taken not to leave a “dangling” by use ofDEALLOCATEon any otherpointer referring to it.The intrinsicINTEGERmultfunctionASSOCIATEDcan test the association status of a defined pointer::DOmult=1,2 REAL,POINTER::a(:,:),x(:),y(:) REAL,TARGET::b(10,10),c(10,10),r(10),s(10,z(10)or between a defined and a defined target (which may, itself, be a pointer):Pointers in expressions and assignmentsFor intrinsic types we can “sweep” pointers over different sets of target data using the same code without any data movement.Given the matrix manipulationy=BCz, we can write the following code (although, in this case, the same result could beachieved moreENDIF ELSEy=>s IF(mult==1)THEN a=>b x=>r a=>c x=>z y=>r !nodatamovementsimply by other means):ENDDO TYPE(entry),POINTER::first,current :first=>current y=MATMUL(a,x) !commoncalculationfirst=current first%value=current%value first%index=current%index first%next=>current%nextFor objects of derived data type we have to distinguish between pointer and normal assignment. Inthe assignment causes to point at current, whereascauses to overwrite and is equivalent toits target withoutNULLIFYing


<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 18Pointer argumentsIf an actual argument is a pointer then, if the dummy argument is also a pointer,SUBROUTINEsub(c) CALLsub(a)itREALc(:,:) REAL,POINTER::a(:,:) ALLOCATE(a(80,80)):must have same rank,it receives its association status from the actual argument,it returns its final association status to the actual argument (note: the target may be undefined!),it may not have the INTENT attribute (it would be ambiguous),it requires an interface block.If the dummy argument is not a pointer, it becomes associated with the target of the actual argument:USEdata_handler REALx(100) REAL,POINTER::y(:)Pointer!Aproceduretoremoveduplicatesfromthearrayx FUNCTIONcompact(x) :y=>compact(x)functionsFunction results may also have thePOINTERattribute; this is useful if the result size depends on calculations performed in thefunction, as inENDFUNCTIONcompact INTEGERnREAL,POINTER::compact(:) REALx(:) ALLOCATE(compact(n)) : !Findthenumberofdistinctvalues,n !Copythedistinctvaluesintocompactwhere the moduledata_handlercontainsTYPE(entry)::rows(n)The result can be used in an expression (but must be associated with a defined target).Arrays of pointersThese do not exist as such: giventhenrows%next !illegalwould be such an object, but with an irregular storage pattern. For this reason they are not allowed. However, we can achievethe same effect by defining a derived data type with a pointer as its sole component:


ENDTYPE TYPErow TYPE(row)::s(n),t(n) REAL,POINTER::r(:)DOi=1,n<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 19s=t ALLOCATE(t(i)%r(1:i))!Allocaterowioflengthiand thens(i)%r=>t(i)%r ENDDOdefining arrays of this data type:where the storage for the rows can be allocated by, for instance,REAL,TARGET::table(100,100)The array assignmentis then equivalent to the pointer assignmentsfor allwindow=>table(m:n,p:q)REAL,DIMENSION(:,:),POINTER::window :components.Pointers as dynamic aliasesGiven an arraytar%uthat is frequentlytaru=>tar%ureferenced with the fixed subscriptsthese referencestaru(1,2)may be replaced byThe subscripts of window are1:n-m+1,1:q-p+1. Similarly, for(as defined in chapter 5, page 15), we can use, say,to point at all the u components of tar, and subscript it asThe subscripts are as those of tar itself. (This replaces yet more ofEQUIVALENCE.)The source code of an extended example of the use of pointers to support a data structure can be obtained by anonymous ftp tojkr.cc.rl.ac.uk(130.246.8.23). The directory is/pub/MandRand the file name isappxg.f<strong>90</strong>.


IMPLICITNONE<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 207. Specification StatementsThisTYPE(triplet),PARAMETER REAL,DIMENSION(3),PARAMETER::field=(/0.,1.,2./)part completes what we have learned::t=triplet(0.,(/0.,0.,0./))so far about specification statements.Implicit typingThe implicit typing rules of <strong>Fortran</strong> 77 still hold. However, it is good practice to explicitly type all variables, and this can beforced by inserting the statementat the beginning of each prorgam unit.DATAi,j,k/B'01010101',O'77',Z'ff'/ DATAt1/triplet(0.,(/0.,1.,2./))/,t2%u/0./!onlyonecomponentoft2initialized DATAarray(1:64)/64*0/ TYPE(triplet)::t1,t2attributeA named constant can be specified directly by adding thePARAMETERattribute and the constant values to a type statement:CHARACTER(KIND=kanji,LEN=20),DIMENSION(4,5)::name CHARACTERname(4,5)*20 !onlyasectionofarrayinitializedstatementTheDATAstatement can be used also for arrays and variables of derived type. It is also the way to initialise just parts ofsuch objects, as well as to initialise to binary, octal or hexadecimal values:INTEGER,PARAMETER::long=SELECTED_REAL_KIND(12),array(3)=(/1,2,3/)CharactersThere are many variations the way character arrays may be specified. Among the shortest and longest areSUBROUTINEs(b,m,c)InitializationREAL,DIMENSION(:,:)expressionsThe values used inDATAandPARAMETERstatements, or in specification statements with these attributes, are constant expressionsthat may include references to: and structure constructors, elemental intrinsic functions with integer or characterarguments and results, and the six transformational functionsREPEAT,SELECTED_INT_KIND,TRIM,SELECTED_REAL_KIND, RESHAPEandTRANSFER:REAL(SELECTED_REAL_KIND(2*PRECISION(a)))z!precisionofztwicethatofa USEmod CHARACTER(LEN=m+LEN(c)) CHARACTER(LEN=*) INTEGER REAL,DIMENSION(UBOUND(b,1)+5) ::b!assumed-shapearray ::x!automaticarray mc!assumed-lengthcc!automaticobject !containsaSpecification expressionsIt is possible to specify details of variables using any non-constant, scalar, integer expression that may also include inquiryfunction references:


INTEGER,PRIVATE::u,v,w PRIVATE::u,v,w,ASSIGNMENT(=),OPERATOR(*) REAL,PUBLIC::x,y,z PUBLIC::x,y,z,OPERATOR(.add.) !default<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 21and These attributes are used in specifications in modules to limit the scope of entities. The attribute form isMODULEmine PUBLIC::only_this !setsdefaultformoduleand the statement form The statement form has to be used to limit access to operators, and can also be used to change the overall default:ENDMODULEmine PRIVATE TYPE,PUBLIC::list ENDTYPElist : TYPE(list)::tree REALx,y TYPE(list),POINTER::nextFor a derived data type there are three possibilities: the type and its components are allPUBLIC, the type isPUBLICand itscomponentsPRIVATE(the type only visible and one can change its details easily), or all of it isPRIVATE(for internal use inthe module only):USEmine,local_list=>list USEmine,ONLY:list USEmine,ONLY:local_list=>listUSE statementTo gain access to entities a module, we use theUSEstatement. It has options to resolve name clashes if an imported name isthe same as a one:or to restrict the used entities to a specified set:These may be combined:


CALLDATE_AND_TIME(TIME=t)<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 228. Intrinsic ProceduresWe have already met most of the new intrinsic functions in previous parts of this series. Here, we deal only with their generalclassification and with those that have so far been omitted.BIT_SIZEAll intrinsic procedures can be referenced using keyword arguments:and manyBTESThave optional arguments. They are grouped into four categories:IAND1. elementalIBCLR– work on scalars or arrays, e.g.ABS(a);2. inquiryIBITS– independent of value argument (which maybe undefined), e.g.PRECISION(a);3. transformationalIBSET Numberofbitsinthemodel Bittesting LogicalAND Clearbit Bitextraction– array argumentSetbitwith array result different shape, e.g.RESHAPE(a,b);4. subroutines, e.g.SYSTEM_CLOCK.The procedures not already introduced are:Bit inquiryBitINTEGER::i=TRANSFER('abcd',0)!replacespartofEQUIVALENCE IEOR IOR ISHFTC NOT ExclusiveOR InclusiveOR Logicalshift Circularshift LogicalcomplementmanipulationDATE_AND_TIME MVBITS RANDOM_NUMBER RANDOM_SEED SYSTEM_CLOCK Obtaindateand/ortime Copiesbits Returnspseudorandomnumbers Accesstoseed AccesstosystemclockTransfer function, as inSubroutines


EOR=eor_label SIZE=size ADVANCE='NO' (defaultis'YES') (optional,READonly)<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 239. Input/OutputNon-advancing input/output!keyisnotinonerecordNormally,66key(size+1:)='' READ(unit,'(A3)',ADVANCE='NO',SIZE=size,EOR=66)key CHARACTER(3)key INTEGERunit,sizerecords of external, formatted files are positioned at their ends after a read or write operation. This can now be overriddenwith the additional specifiers:READ(*,'(I10)') WRITE(*,'(A)',ADVANCE='NO')'Enternextprimenumber:' : prime_numberThe next example shows how to read a record three characters at a time, and to take action if there are fewer than three left inthe record:exponent:0.0217-->21.70E-03(EN9.2)This shows how to keep the cursor positioned after a prompt:New edit descriptorsThe firstENDTYPEstringdigit:0.0217-->2.17E-02(ES9.2)three new edit descriptors are modelled theIedit descriptor:Bbinary,READ(*,'(I2,A)')textTYPE(string)::text INTEGERlength CHARACTER(LEN=20)wordOoctal,Zhexadecimal.There are two new descriptors for real numbers:ENengineering, multiple-of-threeESscientific, leading nonzeroand theGedit descriptor is generalized to all intrinsic types (E/F,I,L,A).For entities of derived types, the programmer must elaborate a format for the ultimate components:


PAD DELIM='APOSTROPHE''QUOTE''NONE' ACTION='READ' POSITION='ASIS' 'REWIND''APPEND'<strong>Fortran</strong>READWRITE=) READ=) WRITE=)'YES' ='YES' 'WRITE''READWRITE'<strong>90</strong> <strong>Tutorial</strong> 24New specifiersOn theOPENandINQUIREstatementsINQUIRE(IOLENGTH=length)item1,item2,... 'NO' 'UNKNOWN'there are new specifiers:and on theINQUIREthere are alsoFinally, inquiry by I/O list (unformatted only) is possible:and this is useful to setRECL, or to check that a list is not too long. It is in the same processor-dependent units asRECLand thusis a portability aid.


Indexactual argument, 10, 12, 18aliases, 19ALLOCATE, 13argument, 10array construction, 15array constructors, 4array elements, 14array inquiry, 15array location, 15array manipulation, 15array reduction, 15array reshape, 15array sections, 4array subobjects, 14arrays, 4arrays intrinsic functions, 15arrays of pointers, 18assignment, 6, 13association, 17assumed-shape arrays, 12automatic arrays, 12binary, 2, 20bit inquiry, 22bit manipulation, 22blank, 1CASE construct, 8CHARACTER, 3, 20comments, 1COMPLEX, 2components, 3constant expressions, 20continuation, 1conversion, 1cursor, 23DATA, 20defined operators, 7derived data type, 14, 16, 17, 21DO construct, 8dummy argument, 10, 12, 18edit descriptors, 23element, 4, 14elemental, 7elemental operation, 13explicit interface, 10expressionsinitialization of ˜, 20specification of ˜, 20formatted files, 23generic interfaces, 11generic names, 11heap storage, 1325hexadecimal, 2, 20implicit typing, 20initializationof expressions, 20input/outputnew edit descriptors, 23new specifiers, 24non-advancing ˜, 23inquiry functions, 2INTEGER, 2INTENT, 1, 7, 9interface, 6interface block, 10, 11, 18intrinsic functions, 7, 15, 17, 20, 22keyword, 22kind type parameter, 2letters, 1linked chain, 16LOGICAL, 3lower bound, 12, 13matrix multiply, 15model numbers, 2modules, 7, 9, 10, 21named constant, 2named operators, 6numerals, 1octal, 2, 20operator, 6optional, 22overloading, 11PARAMETER, 20parentheses, 6POINTER, 16pointer˜s as dynamic aliases, 19˜s in expressions and assignments, 17arguments, 18arrays of ˜s, 18functions, 18pointer assignment, 16, 17, 19precedence, 6PRIVATE, 21prompt, 23PUBLIC, 21range, 2rank, 12, 18REAL, 2recursion, 11scope, 21


<strong>Fortran</strong> <strong>90</strong> <strong>Tutorial</strong> 26section, 14shape, 7significant blank, 1special characters, 1statements, 1structure constructor, 3structures, 3subscripts, 4, 19targets, 16unary operator, 6underscore, 1upper bound, 12USE, 21vector multiply, 15vector subscript, 14WHERE, 13zero-length strings, 5zero-sized arrays, 12

Hooray! Your file is uploaded and ready to be published.

Saved successfully!

Ooh no, something went wrong!