fortran 90 decision structures - astronomy grouppw31/compastro/lecture_5.pdf · as3013: f90 lecture...

12
AS3013: F90 lecture 5 1 Computational Astrophysics AS 3013 Computational Astrophysics AS 3013 Lecture 5: 1) arrays: rank & dimensions 2) allocatable arrays 3) passing arrays in argument list 4) data modules 5) Q&A concerning exercise 1

Upload: dangbao

Post on 14-Feb-2019

230 views

Category:

Documents


0 download

TRANSCRIPT

AS3013: F90 lecture 5 1

Computational Astrophysics AS 3013Computational Astrophysics AS 3013

Lecture 5:

1) arrays: rank & dimensions2) allocatable arrays 3) passing arrays in argument list4) data modules5) Q&A concerning exercise 1

AS3013: F90 lecture 5 2

• declaration– use dimension attribute

• vectors, matrices, and higher ranks– are arrays of rank 1, rank 2, ...

• using parameters – if you want to change dimension(s),

you need to re-compile

• allocatable arrays– declaration with allocatable

– run-time command allocate

– no need to re-compile!

FORTRAN 90: ArraysFORTRAN 90: Arrays

real :: a(5),b(5)real,dimension(5) :: a,b

integer,parameter :: Ndim=3real :: a(Ndim,Ndim)real,dimension(-1:Ndim) :: b

real :: a(5,5)real,dimension(3,2,7) :: b

integer :: Ndimreal,allocatable :: a(:,:)real,allocatable,dimension(:) :: b...read *,Ndimallocate(a(Ndim,Ndim),b(-1:Ndim))...deallocate(b,a)

AS3013: F90 lecture 5 3

• usage of arrays – simple examples

– calculate (b) = ((A)) * (x)

• implicit loops

– print matrix

– omitting bounds in (:)omitting (:) altogether

integer,parameter :: N=3real :: x(N),b(N),A(N,N)real :: suminteger :: i,jdo i=1,N sum = 0.0 do j=1,N sum = sum + A(i,j)*x(j) enddo b(i) = sumenddo

real :: A(3,3)integer :: ido i=1,3 print *, A(i,1:3)enddo

sum = b(1) + b(2) + b(3)a(i,k) = 2.0*a(i,k-1)

A11 A12 A13A21 A22 A23A31 A32 A33

real,dimension(5) :: bprint *, b(:2),b(3:)print *, b(:)print *, b

AS3013: F90 lecture 5 4

• more about implicit loops– fill an array by one statement

– use old-style implied loops

real,dimension(3) :: bb = (/ 1.0,1.5,2.0 /)

real,dimension(7) :: binteger :: iprint *, (b(i),i=1,7,2)

• array boundary errors– frequent source for errors and crashes

... |a(1)|a(2)|a(3)|...

• array boundary checks– use “gfortran -fbacktrace -fbounds-check MyProg.f90”

– VERY slow

– but great help during program development

real,dimension(3) :: aa(4) = 5.0}

4 bytes

AS3013: F90 lecture 5 5

• short vector and matrix commands

– all elements set to same value

– component-wise multiplication

– all elements operated on byelemental intrinsic function a = sin(b)

a = a*b

real,dimension(3) :: a,ba = 5.0

AS3013: F90 lecture 5 6

• passing arrays in argument list– pass arrays and dimensions

• the lazy option: data modules

integer,parameter :: Ndim=3integer :: Nreal :: dat(Ndim)call INIT(Ndim,N,dat)...SUBROUTINE INIT(Ndim,N,dat) integer,intent(in) :: Ndim,N real,intent(inout) :: dat(Ndim) dat(1:N) = 0.0END

FORTRAN 90: Passing ArraysFORTRAN 90: Passing Arrays

module global integer,parameter :: Ndim=3 real :: dat(Ndim)end module

integer :: Ncall INIT(N)...SUBROUTINE INIT(N) use GLOBAL,only: dat integer,intent(in) :: N dat(1:N) = 0.0END

AS3013: F90 lecture 5 7

• passing allocatable arrays– just pass arrays and dimensions

(define without allocatable-attribute)

– really need allocatable-attribute?→ complicated, needs “interface”→ FORTRAN 2003 standard

– maybe better use a data module!

integer :: Ndimreal,allocatable :: a(:)read *,Ndimallocate(a(Ndim))call CALCUL(Ndim,a)...SUBROUTINE CALCUL(N,a) integer,intent(in) :: N real,intent(inout) :: a(N) a(:) = 1.0 + a(:)**2END

integer :: Ndimreal,allocatable :: a(:)interface subroutine ALLOCA(N,a) integer,intent(in) :: N real,allocatable,intent(inout) :: a(:) end subroutine ALLOCAend interfaceread *,Ndimcall ALLOCA(N,a)...SUBROUTINE ALLOCA(N,a) integer,intent(in) :: N real,allocatable,intent(inout) :: a(:) allocate(a(N))END

AS3013: F90 lecture 5 8

• data module = block of memory for variables

– declare before main programmodule name … end module name

– replaces old F77 COMMON-blocks

– individual access rights to begranted for every subroutine

use name or use name,ONLY:list

– VERY practical, and fast

FORTRAN 90: data modulesFORTRAN 90: data modules

module MyData real :: array(50,20,100) real,allocatable :: b(:)end module MyData

program MyProg use MyData,ONLY: b call INITVAR print *, b(:)end program MyProg

subroutine INITVAR use MyData integer :: i array(:,:,:) = 0.0 allocate(b(100)) b(:) = (/ (i,i=1,199,2) /)end subroutine INITVAR

AS3013: F90 lecture 5 9

• data modules,

another example

http://www-star.st-and.ac.uk/~pw31/

/CompuAstro/UseModule.f90

!------------------------------------------------------------------- module NATURE !------------------------------------------------------------------- real :: hplanck,cl,bk,elad,grav,pi,NA,sig_SB,Rgas real :: Msun,Lsun,Rsun,amu,mel,yr,km,AU,pc,Ang,nm,mic real :: Mearth,Mjup,Ws,Wm2Hz,eV,Jansky,Mbarn end module NATURE

!------------------------------------------------------------------- program MyProg !------------------------------------------------------------------- implicit none call INIT_NATURE ! initialize nature constants !... end program MYPROG

!------------------------------------------------------------------- subroutine MyPhysics(nu,Temp) !------------------------------------------------------------------- use NATURE,ONLY: hplanck,bk implicit none real,intent(in) :: nu ! photon frequency [Hz] real,intent(out) :: Temp ! equivalent energy [K] Temp = hplanck*nu/bk end subroutine MYPHYSICS

!------------------------------------------------------------------- subroutine INIT_NATURE !------------------------------------------------------------------- ! *** initialize nature constants and other units than cgs *** !------------------------------------------------------------------- use NATURE implicit none !-------------------------------------------- ! *** fundamental nature constants [cgs] *** !-------------------------------------------- cl = 2.9979245800000E+10 ! speed of light hplanck = 6.6260755400000E-27 ! Planck's constant bk = 1.3806581200000E-16 ! Boltzmann's constant elad = 4.8032068150000E-10 ! electron charge grav = 6.6725985000000E-08 ! gravitational constant NA = 6.0221417900000E+23 ! Avogadro constant pi = ACOS(-1.0) !--------------------------- ! *** derived constants *** !--------------------------- sig_SB = (2.0*pi**5*bk**4)/(15.0*hplanck**3*cl**2) Rgas = bk*NA !--------------------------- ! *** other units [cgs] *** !--------------------------- Msun = 1.988922500E+33 ! solar mass Mearth = 5.974200000E+27 ! mass of Earth Mjup = 1.898600000E+30 ! mass of Jupiter Lsun = 3.846000000E+33 ! solar luminosity (NASA solar physics division) Rsun = 6.959900000E+10 ! solar radius (Brown & Christensen-Dalsgaard 1998) amu = 1.660531000E-24 ! atomar mass unit mel = 9.109389754E-28 ! electron mass end subroutine INIT_NATURE

AS3013: F90 lecture 5 10

Q&A exercise 1Q&A exercise 1

AS3013: F90 lecture 5 11

AS3013: F90 lecture 5 12