<<

ComputationalComputational AstrophysicsAstrophysics ASAS 30133013

Lecture 5:

1) arrays: rank & dimensions 2) allocatable arrays 3) passing arrays in argument list 4) data modules 5) Q&A concerning exercise 1

AS3013: F90 lecture 5 1 FORTRANFORTRAN 90:90: ArraysArrays • declaration real :: a(5),b(5) – use dimension attribute real,dimension(5) :: a,b

• vectors, matrices, and higher ranks – are arrays of rank 1, rank 2, ... real :: a(5,5) real,dimension(3,2,7) :: b • using parameters integer,parameter :: Ndim=3 – if you want to change dimension(s), real :: a(Ndim,Ndim) you need to re-compile real,dimension(-1:Ndim) :: b

• allocatable arrays integer :: Ndim real,allocatable :: a(:,:) – declaration with allocatable real,allocatable,dimension(:) :: b – run-time command allocate ... read *,Ndim – no need to re-compile! allocate(a(Ndim,Ndim),b(-1:Ndim)) ... deallocate(b,a)

AS3013: F90 lecture 5 2 • usage of arrays sum = b(1) + b(2) + b(3) – simple examples a(i,k) = 2.0*a(i,k-1)

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

• implicit loops real :: A(3,3) integer :: i A11 A12 A13 do i=1,3 print *, A(i,1:3) – print matrix A21 A22 A23 enddo  A31 A32 A33

real,dimension(5) :: b – omitting bounds in (:) print *, b(:2),b(3:) omitting (:) altogether print *, b(:) print *, b

AS3013: F90 lecture 5 3 • more about implicit loops – fill an array by one statement real,dimension(3) :: b b = (/ 1.0,1.5,2.0 /)

– use old-style implied loops real,dimension(7) :: b integer :: i print *, (b(i),i=1,7,2) • array boundary errors

– frequent source for errors and crashes real,dimension(3) :: a ... |a(1)|a(2)|a(3)|... a(4) = 5.0

} 4 bytes

• array boundary checks – use “gfortran -g -fbacktrace -fcheck=all MyProg.f90” – VERY slow – but great help during program development

AS3013: F90 lecture 5 4

• short vector and matrix commands

real,dimension(3) :: a,b – all elements set to same value a = 5.0 – component-wise multiplication a = a*b – all elements operated on by elemental a = sin(b)

AS3013: F90 lecture 5 5 FORTRANFORTRAN 90:90: PassingPassing ArraysArrays

• passing arrays in argument list integer,parameter :: Ndim=10 real :: dat(Ndim) – pass arrays and dimensions call INIT(Ndim,3,dat) ... SUBROUTINE INIT(Ndim,N,dat) integer,intent(in) :: Ndim,N real,intent(inout) :: dat(Ndim) dat(1:N) = 0.0 END

module global integer,parameter :: Ndim=10 • the lazy option: data modules real :: dat(Ndim) end module

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

AS3013: F90 lecture 5 6 integer :: Ndim • passing allocatable arrays real,allocatable :: a(:) – read *,Ndim just pass arrays and dimensions allocate(a(Ndim)) (re-define without allocatable-attribute) call CALCUL(Ndim,a) ... SUBROUTINE CALCUL(N,a) integer,intent(in) :: N real,intent(inout) :: a(N) a(:) = 1.0 + a(:)**2 END

– really need allocatable-attribute? integer :: Ndim real,allocatable :: a(:) → complicated, needs “” interface → 2003 standard subroutine ALLOCA(N,a) integer,intent(in) :: N real,allocatable,intent(inout) :: a(:) end subroutine ALLOCA end interface read *,Ndim call ALLOCA(N,a) – easier to use a data module! ... SUBROUTINE ALLOCA(N,a) integer,intent(in) :: N real,allocatable,intent(inout) :: a(:) allocate(a(N)) END

AS3013: F90 lecture 5 7 FORTRANFORTRAN 90:90: datadata modulesmodules

• data module = block of memory for variables

module MyData – declare before main program real :: array(50,20,100) module name … end module name real,allocatable :: b(:) end module MyData

program MyProg – replaces old F77 COMMON-blocks use MyData,ONLY: b call INITVAR print *, b(:) – individual access rights to be end program MyProg

granted for every subroutine subroutine INITVAR use name or use name,ONLY:list use MyData integer :: i array(:,:,:) = 0.0 allocate(b(100)) – VERY practical, and fast b(:) = (/ (i,i=1,199,2) /) end subroutine INITVAR

AS3013: F90 lecture 5 8 !------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 • data modules, !------program MyProg !------implicit none call INIT_NATURE ! initialize nature constants another example !... end program MYPROG

!------subroutine MyPhysics(nu,Temp) !------http://www-star.st-and.ac.uk/~pw31/ use NATURE,ONLY: hplanck,bk implicit none real,intent(in) :: nu ! photon frequency [Hz] real,intent(out) :: Temp ! equivalent energy [K] /CompuAstro/UseModule.f90 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 AS3013: F90 lecture 5 mel = 9.109389754E-28 ! electron mass 9 end subroutine INIT_NATURE Q&AQ&A exerciseexercise 11

AS3013: F90 lecture 5 10 not real*16 !!!

AS3013: F90 lecture 5 11 AS3013: F90 lecture 5 12 AS3013: F90 lecture 5 13