<<

Modern

Support for new Fortran Language Elements by Intel® Fortran Composer XE

Agenda • Introduction – Fortran History – Why Fortran • Modern Fortran – Some selected Features – Array Notation – Object-oriented programming – Do-Concurrent – Coarray Fortran • Intel Fortran Composer XE – Standard Support – Implementation of Coarrays • References/Summary

Credit: Thanks to Mr. Reinhold Bader, LRZ Garching/Germany, who provided some of the slides used here

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Your Memory of Fortran ?

IF (AA(J+L).EQ.0.0)GOTO42 TEST=TEST-1 THETA=ATAN(X,Y) GOTO30 42 TEST=TEST+1 THETA=ATAN(-X,Y) 30 CONTINUE

“GOD is REAL (unless declared INTEGER)."

Copyright© 2012, Intel Corporation. All rights reserved. 4 *Other brands and names are the property of their respective owners. FORTRAN Started 1954 as “ IBM Mathematical Formula Translation System” but abbreviated later to FORmula TRANslation • created by IBM developer John Backus and released to public in 1957 – Now called “Fortran I” • designed for scientific and engineering computation John Backus 1924-2007 • FORTRAN is the oldest programming language actively in use today • FORTRAN is still very popular for new software development in scientific applications • Many FORTRAN programs written +40 years ago are still in active use today!

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. IBM 704 Fortran manual, 1957

Copyright© 2012, Intel Corporation. All rights reserved. 6 *Other brands and names are the property of their respective owners. FORTRAN–History [1]

• FORTRAN 1957 (“Fortran I”) • FORTRAN II, III – Clean up, separate module compilation • FORTRAN IV – IF statement, type declarations • FORTRAN 66 - ANSI Standard of 1966 – Clean up of FORTRAN IV • FORTRAN 77 - ANSI Standard released 1978 – CHARACTER data type, new DO-Loop semantic, IF-THEN-ELSE • FORTRAN 90 – ANSI Standard released 1992 – Free form, array section, dynamic memory allocation, derived types, modular programming • FORTRAN 95 – ANSI Standard released 1997 – Minor update of FORTRAN90; FORALL, PURE and ELEMENTAL routines

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. FORTRAN– History [2] • FORTRAN 2003 – ANSI Standard released 2003 – Object-oriented programming, -interoperability, IEEE- arithmetic, parameterized derived types, ASSOCIATE, procedure pointers, … • FORTRAN 2008 – latest ANSI standard, released June 2010 – Coarrays, DO-CONCURRENT, bit manipulation intrinsics, sub-module concept Many dialects influenced FORTRAN standardization and all support some non-standard extensions of these dialects – Cray Fortran (“Cray Pointers”) – DEC Fortran Some too progressive extensions like HPF-High Performance Fortran did not find much attention outside of academic research

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Why Fortran? A few Selected Arguments • Arrays are not only part of the language syntax but have representation in run-time environment – Different from C/C++ – Implies: – Easier programming (e.g. multi-dimensional array procedure arguments with variable bounds) – Better code generation (faster code) • Safer (more restrictive) semantic – POINTER much safer than for C/C++ – Aliasing of procedure arguments limited – Implies: More optimizations, thus faster code • Module concept • Portability – 32 to 64 bit porting -> no changes needed ! – No problem to compile +40 year old programs • Existing code base

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Sample: Triade in Fortran and C C/C++ : void triade( int a[], int b[], int c[], int n) { Both vectorize int j; but C-version for (j=0; j

Fortran does triade(a, b, n) not allow 2 integer n arguments to integer, dimension (1:n) :: a,b,c do j = 1,n alias in case a(j) = b(j) + 3.14 * c(j) one is modified: end do Code is faster end subroutine triade

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Agenda • Introduction – Fortran History – Why Fortran • Modern Fortran – Some selected Features – Array Notation – Object-oriented programming – Do-Concurrent – Coarray Fortran • Intel® Fortran Composer XE – Standard Support – Implementation of Coarrays • References/Summary

Credit: Thanks to Mr. Reinhold Bader, LRZ Garching/Germany, who provided some of the slides used here

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Array Sections • Introduced by FORTRAN90 • Similar to array notation of Intel® Plus introduced 20 years later as C/C++ extension – But syntax different: : [:] – And semantic for assignment different: LHS and RHS may overlap in Fortran, not in Cilk Plus !! A(1:10, 1:3) A(1:10:2, 1:10:2) 1 2 3 4 5 6 7 8 9 1 2 3 4 5 6 7 8 9 1 1 Example 2 2 3 3 REAL :: A(10, 10) 4 4 5 5 6 6 7 7 8 8 9 9

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Modules in Fortran module mymodule ! My very own module use m1 ! import all objects of module m1 use m2, only : x, y ! import only x, y from module m2 implicit none !! Module variables go here real , dimension (20) :: x

subroutine s1(a, b) ! An external procedure contains subroutine s2(foo , bar) ! An internal procedure end subroutine s2 end subroutine s2 end module mymodule

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Interoperation with C Portable, Standardized Invoke C functions in a standard- Example C prototype defined way • Today (F2003) focusing on Fortran using C- void My_C_Subr(int, double *); objects • Future standard: Both directions

program myprog use, intrinsic :: iso_c_binding • Invocation from Fortran: integer( c_int ) :: ic C intrinsic type matching: c_int, c_real … real( c_real ) :: rc4 real( c_double ), allocatable :: dc(:) character( c_char ) :: cc interface subroutine my_c_subr(i, ) bind(c, name=' My_C_Subr ') use, intrinsic :: iso_c_binding integer(c_int), value :: i • Suppress Fortran real(c_double) :: d(*) • Mixed case name resolution end subroutine my_c_subr end interface ic = … ; allocate(dc(ic)) • ic passed by value call my_c_subr(ic, dc) • address of first element of dc end program passed to subprogram

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Fortran 2003 OOP (1)

Type extension Polymorphic entities • new kind of dynamic storage type :: body declared type body real :: mass : ! position, velocity class (body), & end type allocatable :: balloon

type, extends (body) :: & typed allocation charged_body allocate(body :: balloon) charged_body real :: charge : ! send balloon on trip end type if (hit_by_lightning()) then : ! save balloon data type(charged_body) :: & deallocate(balloon) proton allocate( & must be an extension charged_body :: balloon) etc_body inherited balloon = … proton%mass = … ! balloon data + charge proton%charge = … end if : ! continue trip if possible

change not only size, but also Single inheritance – always a DAG (dynamic) type of object during execution of program

15 Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Fortran 2003 OOP (2)

Associate procedures with type Run time type/class resolution • make components of dynamic type accessible type :: body object-bound procedure (pointer) : ! data components procedure(p), pointer :: print polymorphic entity contains select type (balloon) procedure :: dp type-bound type is (body) end type procedure (TBP) : ! balloon non-polymorphic here class is (rotating_body) subroutine dp(this, kick) : ! declared type lifted class (body), intent(inout) :: this class default real, intent(in) :: kick(3) : ! implementation incomplete? : ! give body a kick end select end subroutine • at most one is executed • polymorphic dummy argument required for inheritance • same mechanism is used (internally) to resolve type-bound procedure calls • TBP can be overridden by extension (must specify essentially same interface, down to keywords)

balloon%print => p_formatted call balloon%print() call balloon%dp(mykick) balloon matches this

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. F2008 DO CONCURRENT A new Parallel Loop Construct Syntax uses elements of Fortran 90 FORALL DO [,] CONCURRENT

Semantically there is a key difference to FORALL however : A variable referenced can only be defined in the very same iteration or outside of the loop body • This excludes dependencies between different loop iterations

The implementation in Intel® Compiler will execute the iterations in parallel using OpenMP* run-time system • requires compiler switch –parallel DO CONCURRENT (I = 1:N) ! Not conforming BLOCK REAL :: T DO CONCURRENT (I=1:N) T = A(I) + B(I) A(I+1) = A(I) + 3.145 C(I) = T + SQRT(T) END BLOCK END DO END DO

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Agenda • Introduction – Fortran History – Why Fortran • Modern Fortran – Some selected Features – Array Notation – Object-oriented programming – Do-Concurrent – Coarray Fortran • Intel Fortran Composer XE – Standard Support – Implementation of Coarrays • References/Summary

Credit: Thanks to Mr. Reinhold Bader, LRZ Garching/Germany, who provided some of the slides used here

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Coarray Fortran (CAF) – Design Goals

Coarrays were designed to answer the question:

What is the smallest change required to convert Fortran into a robust and efficient parallel language?

The answer: a simple syntactic extension implementing a PGAS ( Partioned Global Address Space) model

“It looks and feels like Fortran and requires Fortran programmers to learn only a few new rules."

John Reid ” ISO Fortran Convener

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. PGAS – Partioned Global Address Space

Global address space for each partioned into local and global space Global space accessible by each process Can be realized via shared and Sample PGAS languages: X10, UPC, Fortress, Titanium, Chapel, … and CAF !

P1 P2 Pn

P1_Y P2_Y Pn_Y Shared

Glocal X X X Private = address space address

20

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Coarray Fortran Fundamentals

Simple extension to Fortran to make Fortran into a robust and efficient parallel programming language

Single-Program, Multiple-Data programming model (SPMD). • Single program is replicated a fixed number of times • Each program instance has it’s own set of data objects – called an “IMAGE” • Each image executes asynchronously and normal Fortran rules apply • Extensions to normal Fortran array syntax to allow images to reference data in other image(s) • Variables can be replicated to all or a subset of the images by using the CODIMENSION declaration

21 Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Codimensions Declaration A Simple Scalar Example A variable can be declared with a CODIMENSION real, codimension[*] :: x real :: y[*]

X, Y are real scalar variables; the “codimension” can be used to reference copies of X & Y on remote images • E.g. x[12] = y[4] would get value of y on image 4 and assign it to scalar variable x on image 12; the statement can be executed on each image

Similar to assumed size array syntax, “[*]” means as many copies as there are images, one copy per image • “*” can ONLY be used on last codimension for the object – Ex: [*,2] is illegal, but [2,*] is valid: means a 2D ordering of images. 20 images would have object with [2,10] codimension. 30 images would have object with [2,15] codimensions

22 Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Dimensions Declaration A Simple (Co-) Array Example real :: A(3)[*] or real codimension[*] :: B(3)

A program with e.g. 4 images will have 4 copies of array a each with 3 elements Local access – as usual: A on A on A on A on Image 1 Image 2 Image 3 Image 4 A(:) = (/ 1, 2, 3 /) A(1)[1] A(1)[2] A(1)[3] A(1)[4] Remote access: A(2)[1] A(2)[2] A(2)[3] A(2)[4] if (this_image () == 1) then A(3)[1] A(3)[2] A(3)[3] A(3)[4] B(:) = A(:) [2] end if

Coarrays can have normal F2008 attributes: ALLOCATABLE, POINTER, have multiple dimensions, be part of a derived type, etc. real, allocatable :: a(:)[*], b(:)[*] allocate( b(100)[*], b(100)[0:*] )

23 Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. CAF Memory Model real :: A(n)[ ∗∗∗] image p image q

A(1) A(1) A(1) A(1)[q] A(1) A(1)

A(n)[p] A(n) A(n) A(n) A(n) A(n)

Copyright© 2012, Intel Corporation. All rights reserved. 24 *Other brands and names are the property of their respective owners. UPC versus CAF – Boundary Exchange CAF – simple and easy to code: integer a(N,M )[*] a(1:N,1:2) = a(1:N,M-1:M )[this_image()-1]

UPC – low level, error-prone address computation shared int *a;

upc_memget (&a[N*M* MYTHREAD ],&a[N*M* MYTHREAD -2*N], 2*N*sizeof(int));

M N

P1 P2 PN

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Synchronization Primitives Synchronization • SYNC ALL ! Synchronization across all images • SYNC IMAGES ! Synchronization on a list of images • SYNC MEMORY ! Memory barrier Image serialization • CRITICAL ! Allows one image to execute the block at a time • LOCK/UNLOCK ! fine-grained data access

Some statements may imply synchronization • SYNC ALL implied when the application starts

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Synchronisation Sample Enforce Ordering me = this_image() ne = num_images() if(me==1) then p = 1 else sync images ( me-1 ) p = p[me-1] + 1 end if if(me

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. MPI Versus Coarray – Sample

• Domain decomposed for parallel execution – one domain per process (rank, image) • Subdomains must exchange information across the boundaries, called halo communication – Implemented via a ‘ghost’ layer/boundary • Halo communication is often the bulk of inter-processor communication in parallel code

5-point stencil

-1 -1 4 -1 -1

E.g. stencil computation update as used in a 2-D Jacobi iteration: A_New(I,j) = 1/4 * (A(i-1,j) + A(i,j-1) + A(i+1,j) + A(I,j+1) )

28 Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Message Passing Interface (MPI) Model

4/23/2012

29 Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Coarray Fortran Model

4/23/2012

30 Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. MPI Loop for Halo-Exchange

real :: data(0:nx+1,0:ny+1,0:nz+1) integer :: mype, ier, nx, right, left integer :: stag, rtag, stat, iz ...

! Exchange halo cell data with “left” and “right” processors do iz = 1, nz ! Send and receive a vector of nx values at a time stag = stag + 1 rtag = rtag + 1 call MPI_sendrecv (data(1,ny,iz), nx, MPI_REAL8, right, stag data(1,0,iz), nx, MPI_REAL8, left, rtag, MPI_COMM_WORLD, stat, ier) stag = stag + 1 rtag = rtag + 1 call MPI_sendrecv (data(1,1,iz), nx, MPI_REAL8, left, stag data(1,ny+1,iz), nx, MPI_REAL8, right, rtag, MPI_COMM_WORLD, stat, ier) enddo

31 Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Coarray Loop for Halo Exchange

real :: data(0:nx+1,0:ny+1,0:nz+1) integer :: myleft, myright, me, ix, iz ... ! Exchange halo cell data with “left” and “right” processors do iz = 1, nz do ix = 1, nx data (ix, 0, iz) = data (ix, ny, iz)[myleft] data (ix, ny+1, iz) = data (ix, 1, iz)[myright] end do end do

32 Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Coarray and MPI Compared

• Both support shared and distributed memory • Both are defined by standards • Coarray coding much more intuitive than MPI – MPI very low level – some kind of ‘assembler programming’ for distributed programs

• Coarray model requires less data copy-in/out operations for Fortran: – MPI implemented in C and thus Fortran array sections can not be passed without copy operations

• At least today: MPI more mature, good choice of sophisticated and optimized implementations (better performance), wider distribution, better acceptance – Available code base !

• Move from MPI to Coarray Fortran can be done incrementally !

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Agenda • Introduction – Fortran History – Why Fortran • Modern Fortran – Some selected Features – Array Notation – Object-oriented programming – Do-Concurrent – Coarray Fortran • Intel® Fortran Composer XE – Standard Support – Implementation of Coarrays • References/Summary

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Intel ® Parallel Studio XE 2011 Powerful Tools Provide Comprehensive Coverage

Phase Productivity Tool Feature Benefit

Intel® Parallel • Simplifies, demystifies, and speeds Advisor parallel application design Design Threading design assistant • Available for Intel® Parallel Studio XE for C++ Windows and Intel® C++ Studio Windows Windows (ESD) C/C++ and Fortran compilers and performance libraries • Intel® Integrated Performance • Enabling solution to achieve the Build & Intel ® Primitives application performance and • Intel® Math Kernel Library benefits of multicore and Debug Composer XE • Intel® Threading Building Blocks • Intel® Debugger (Linux) + forward scale to manycore Intel® Parallel Debugger Extension (Window)

Memory & threading dynamic • Increased productivity, code quality, Intel ® analysis for code quality and lowers cost Verify Inspector XE Static Security Analysis for code • Finds memory, threading , and security defects before they happen quality (Studio products only)

Performance Profiler for Intel ® VTune™ • Remove guesswork, saves time, makes Tune optimizing application it easier to find performance and Amplifier XE performance and scalability scalability bottlenecks

35 Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Intel® Fortran Compiler History

Compaq Fortran 6.6 Intel Fortran 7.x

Language Code Language Code Libraries Libraries Parallel Features Gen Features Gen

Language Code Libraries Parallel Features Gen

Intel Fortran 8.0

Copyright© 2012, Intel Corporation. All rights reserved. 36 *Other brands and names are the property of their respective owners. Fortran 2003/2008 Support in 12.1 Fortran 2003 implementation almost complete • Added in Composer XE: – Complete type-bound procedures (GENERIC, OPERATOR,..) – FINAL procedures – Bounds remapping on pointer assignments • Remaining features of F2003 to be done in a later release: – User-defined derived type I/O – Parameterized derived types – A very few more, minor items need to be completed Fortran 2008 features • Coarrays • DO CONCURRENT • CONTIGUOUS • I/O enhancements • New constants in ISO_FORTRAN_ENV • New intrinsic functions • Increase maximum rank from 7 to 31 ( F2008 requires 15)

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Intel Extensions: Module Procedures Additional modules provided: • IFPORT ‰ portability routines • IFPOSIX ‰ POSIX interfaces • IFCORE ‰ access to run time library internals MS Windows only • IFNLS ‰ national language support • IFCOM ‰ COM support • IFAUTO ‰ automatization server • IFQWIN ‰ QuickWin GUI • IFLOGM ‰ Dialogue interface

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Coarray Fortran by Intel® Fortran Compiler

• Functional, almost complete implementation • Target execution environment: – A processor system (SMP, multi-core system) – A distributed memory platform ( “cluster”) – Linux* or Windows* – Only Intel 64; neither Itanium nor 32bit x86 (IA32) • Implementation uses – direct memory access for SMP – Intel® MPI for cluster targets – must be release 4.0.x – No need for additional MPI installation - all run time components are included in Composer distribution • License requirements: – None additionally for SMP – Intel® Cluster Studio [XE] license needed too for cluster target – only the license is needed – no additional bits have to be installed ! • Composer 12.1 ( not 12.0 ) allows MPI calls and CAF constructs to co-exist in same code

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Coarray Fortran by Intel® Fortran Compiler

• Compilation: – ifort –coarray ! Linux – ifort -/Qcoarray ! Windows – ifort –coarray=shared ! shared memory target – ifort –coarray=distributed ! Distributed memory target – ifort –coarray –coarray-num-images=x – Sets number of images to ‘x’; default is number of – logical – cores on shared memory targets; for clusters, it uses same conventions and defaults as Intel® MPI – For SMP, this can be set too by environment variable FOR_COARRAY_NUM_IMAGES (no need for re-compilation !) – ifort –coarray=distributed -coarray-config-file= – Any configuration parameter valid for ‘mpiexec’ can be listed in and will then control the application launch. While the name is fixed at compilation time, the content of this file can be changed from run to run w/o re-compilation • Execution: – Shared memory target: Just as any other application – Cluster: – MPI daemon has to be started first (mpdboot) – Application is started too as any other application: No need to use ‘mpirun’ or ‘mpiexec’

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. “Hello World” Sample (Linux) Simple hello world: program hello_image write(*,*) "Hello from image ", this_image(), &

"out of ", num_images()," total images“ end program hello_image

$ ifort –coarray –o hello_image hello_image.f90 ./hello_image Hello from image 1 out of 4 total images Hello from image 4 out of 4 total images Hello from image 2 out of 4 total images Hello from image 3 out of 4 total images

$ export FOR_COARRAY_NUM_IMAGES=2 ./hello_image Hello from image 2 out of 2 total images Hello from image 1 out of 2 total images

Copyright© 2012, Intel Corporation. All rights reserved. 41 *Other brands and names are the property of their respective owners. Feature Comparison For independent comparison of Fortran 2003/2008 features see ACM Fortran Forum, December 2011, ”Compiler Support for the Fortran 2003 and 2008 Standards, Revision 8”

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. New in Version 13.0

Alignment control • In particular a switch –align arrayNbyte will allow to globally align arrays on boundaries 8,16, 32, 64, 256

Handling of standard violations • New switch “-assume [no]std_intent_in” – Support correct compilation of incorrect code : Some applications like Socorro from SPEC suite modify “intent in” arguments which cause to produce “incorrect” code

F2008 • AtomicDefine and AtomicRef for Co-Arrays

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Agenda • Introduction – Fortran History – Why Fortran • Modern Fortran – Some selected Features – Array Notation – Object-oriented programming – Do-Concurrent – Coarray Fortran • Intel® Fortran Composer XE – Standard Support – Implementation of Coarrays • References/Summary

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Sample Case from Industry - ESI

ESI announces pilot version of Adjoint Solver for design optimization: Intel applauds advances made with the help of its Fortran compiler Validation example of ESI’s Adjoint Optimization Solver. In this example, the solver helped reduce the vehicle drag by 13% after a single optimization cycle.

Paris, France – 15 March, 2012 – ESI Group , pioneer and world-leading solution provider in virtual prototyping for manufacturing industries, announces the launch of the pilot version of its Adjoint Optimization Solver, developed over the past 2 years thanks to a close collaboration between ESI and Intel . This mutually beneficial project brings the Intel Fortran compiler to a unique level of performance, allowing the use of adjoint-based optimization methods across a wide range of industry sectors. … http://www.esi-group.com/corporate/news-media/press-releases/2012-english-pr/esi-announces-pilot- version-of-adjoint-solver-for-design-optimization-intel-applauds-advances-made-with-the-help-of-its- fortran-90-compiler-2

Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. New Books

Two new books on ‘Modern Fortran’ published in last few months / to be published soon • Both cover Fortran 2008 / Coarray Fortran

46 Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. References

History of Fortran • http://en.wikipedia.org/wiki/Fortran

Coarrays in the next Fortran Standard • ftp://ftp.nag.co.uk/sc22wg5/N1801-N1850/N1824.pdf

Fortran 2008 Standard (last draft) • http://j3-fortran.org/doc/standing/links/007.pdf

Intel® Fortran Composer • http://software.intel.com/en-us/articles/fortran-compilers/

47 Copyright© 2012, Intel Corporation. All rights reserved. *Other brands and names are the property of their respective owners. Legal Disclaimer & Optimization Notice

INFORMATION IN THIS DOCUMENT IS PROVIDED “AS IS”. NO LICENSE, EXPRESS OR IMPLIED, BY ESTOPPEL OR OTHERWISE, TO ANY INTELLECTUAL PROPERTY RIGHTS IS GRANTED BY THIS DOCUMENT. INTEL ASSUMES NO LIABILITY WHATSOEVER AND INTEL DISCLAIMS ANY EXPRESS OR IMPLIED WARRANTY, RELATING TO THIS INFORMATION INCLUDING LIABILITY OR WARRANTIES RELATING TO FITNESS FOR A PARTICULAR PURPOSE, MERCHANTABILITY, OR INFRINGEMENT OF ANY PATENT, COPYRIGHT OR OTHER INTELLECTUAL PROPERTY RIGHT.

Performance tests and ratings are measured using specific computer systems and/or components and reflect the approximate performance of Intel products as measured by those tests. Any difference in system hardware or or configuration may affect actual performance. Buyers should consult other sources of information to evaluate the performance of systems or components they are considering purchasing. For more information on performance tests and on the performance of Intel products, reference www.intel.com/software/products .

Copyright © , Intel Corporation. All rights reserved. Intel, the Intel logo, Xeon, Core, VTune, and Cilk are trademarks of Intel Corporation in the U.S. and other countries. *Other names and brands may be claimed as the property of others.

Optimization Notice Intel’s compilers may or may not optimize to the same degree for non-Intel microprocessors for optimizations that are not unique to Intel microprocessors. These optimizations include SSE2, SSE3, and SSSE3 instruction sets and other optimizations. Intel does not guarantee the availability, functionality, or effectiveness of any optimization on microprocessors not manufactured by Intel. Microprocessor-dependent optimizations in this product are intended for use with Intel microprocessors. Certain optimizations not specific to Intel microarchitecture are reserved for Intel microprocessors. Please refer to the applicable product User and Reference Guides for more information regarding the specific instruction sets covered by this notice. Notice revision #20110804

Copyright© 2012, Intel Corporation. All rights reserved. 48 *Other brands and names are the property of their respective owners. 49