Changeset 2225 for LMDZ5/trunk/libf/phydev/iniphysiq.F90
- Timestamp:
- Mar 11, 2015, 3:55:23 PM (10 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ5/trunk/libf/phydev/iniphysiq.F90
r1994 r2225 2 2 ! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $ 3 3 ! 4 SUBROUTINE iniphysiq(ngrid, nlayer, punjours, pdayref, ptimestep, plat, plon, & 5 parea, pcu, pcv, prad, pg, pr, pcpp, iflag_phys) 6 USE dimphy, ONLY: klev 7 USE mod_grid_phy_lmdz, ONLY: klon_glo 8 USE mod_phys_lmdz_para, ONLY: klon_omp, klon_omp_begin, klon_omp_end, & 9 klon_mpi_begin 10 USE comgeomphy, ONLY: airephy, cuphy, cvphy, rlond, rlatd 11 USE comcstphy, ONLY: rradius, rg, rr, rcpp 4 SUBROUTINE iniphysiq(iim,jjm,nlayer,punjours, pdayref,ptimestep, & 5 rlatu,rlonv,aire,cu,cv, & 6 prad,pg,pr,pcpp,iflag_phys) 7 USE dimphy, ONLY: klev ! number of atmospheric levels 8 USE mod_grid_phy_lmdz, ONLY: klon_glo ! number of atmospheric columns 9 ! (on full grid) 10 USE mod_phys_lmdz_para, ONLY: klon_omp, & ! number of columns (on local omp grid) 11 klon_omp_begin, & ! start index of local omp subgrid 12 klon_omp_end, & ! end index of local omp subgrid 13 klon_mpi_begin ! start indes of columns (on local mpi grid) 14 USE comgeomphy, ONLY: initcomgeomphy, & 15 airephy, & ! physics grid area (m2) 16 cuphy, & ! cu coeff. (u_covariant = cu * u) 17 cvphy, & ! cv coeff. (v_covariant = cv * v) 18 rlond, & ! longitudes 19 rlatd ! latitudes 12 20 USE phyaqua_mod, ONLY: iniaqua 13 21 IMPLICIT NONE 14 22 ! 15 23 !======================================================================= 16 !17 24 ! Initialisation of the physical constants and some positional and 18 25 ! geometrical arrays for the physics 19 !20 !21 ! ngrid Size of the horizontal grid.22 ! All internal loops are performed on that grid.23 ! nlayer Number of vertical layers.24 ! pdayref Day of reference for the simulation25 !26 26 !======================================================================= 27 27 … … 34 34 REAL,INTENT(IN) :: pcpp ! specific heat Cp 35 35 REAL,INTENT(IN) :: punjours ! length (in s) of a standard day 36 INTEGER, INTENT(IN) :: ngrid ! number of horizontal grid points in the physics37 INTEGER, INTENT(IN) :: nlayer ! number of atmospheric layers38 REAL,INTENT(IN) :: plat(ngrid) ! latitudes of the physics grid39 REAL, INTENT(IN) :: plon(ngrid) ! longitudes of the physics grid40 REAL, INTENT(IN) :: parea(klon_glo) ! area (m2)41 REAL, INTENT(IN) :: pcu(klon_glo) ! cu coeff. (u_covariant = cu * u)42 REAL, INTENT(IN) :: pcv(klon_glo) ! cv coeff. (v_covariant = cv * v)43 INTEGER,INTENT(IN) :: pdayref ! reference day of for the simulation36 INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers 37 INTEGER, INTENT (IN) :: iim ! number of atmospheric coulumns along longitudes 38 INTEGER, INTENT (IN) :: jjm ! number of atompsheric columns along latitudes 39 REAL, INTENT (IN) :: rlatu(jjm+1) ! latitudes of the physics grid 40 REAL, INTENT (IN) :: rlonv(iim+1) ! longitudes of the physics grid 41 REAL, INTENT (IN) :: aire(iim+1,jjm+1) ! area of the dynamics grid (m2) 42 REAL, INTENT (IN) :: cu((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u) 43 REAL, INTENT (IN) :: cv((iim+1)*jjm) ! cv coeff. (v_covariant = cv * v) 44 44 REAL,INTENT(IN) :: ptimestep !physics time step (s) 45 45 INTEGER,INTENT(IN) :: iflag_phys ! type of physics to be called 46 46 47 47 INTEGER :: ibegin,iend,offset 48 INTEGER :: i,j 48 49 CHARACTER (LEN=20) :: modname='iniphysiq' 49 50 CHARACTER (LEN=80) :: abort_message 50 51 REAL :: total_area_phy, total_area_dyn 52 53 54 ! global array, on full physics grid: 55 REAL,ALLOCATABLE :: latfi(:) 56 REAL,ALLOCATABLE :: lonfi(:) 57 REAL,ALLOCATABLE :: cufi(:) 58 REAL,ALLOCATABLE :: cvfi(:) 59 REAL,ALLOCATABLE :: airefi(:) 60 51 61 IF (nlayer.NE.klev) THEN 52 62 WRITE(lunout,*) 'STOP in ',trim(modname) … … 58 68 ENDIF 59 69 60 IF (ngrid.NE.klon_glo) THEN 61 WRITE(lunout,*) 'STOP in ',trim(modname) 62 WRITE(lunout,*) 'Problem with dimensions :' 63 WRITE(lunout,*) 'ngrid = ',ngrid 64 WRITE(lunout,*) 'klon = ',klon_glo 65 abort_message = '' 66 CALL abort_gcm (modname,abort_message,1) 67 ENDIF 70 !call init_phys_lmdz(iim,jjm+1,llm,1,(/(jjm-1)*iim+2/)) 71 72 ! Generate global arrays on full physics grid 73 ALLOCATE(latfi(klon_glo),lonfi(klon_glo),cufi(klon_glo),cvfi(klon_glo)) 74 ALLOCATE(airefi(klon_glo)) 68 75 69 !$OMP PARALLEL PRIVATE(ibegin,iend) & 70 !$OMP SHARED(parea,pcu,pcv,plon,plat) 71 76 ! North pole 77 latfi(1)=rlatu(1) 78 lonfi(1)=0. 79 cufi(1) = cu(1) 80 cvfi(1) = cv(1) 81 DO j=2,jjm 82 DO i=1,iim 83 latfi((j-2)*iim+1+i)= rlatu(j) 84 lonfi((j-2)*iim+1+i)= rlonv(i) 85 cufi((j-2)*iim+1+i) = cu((j-1)*iim+1+i) 86 cvfi((j-2)*iim+1+i) = cv((j-1)*iim+1+i) 87 ENDDO 88 ENDDO 89 ! South pole 90 latfi(klon_glo)= rlatu(jjm+1) 91 lonfi(klon_glo)= 0. 92 cufi(klon_glo) = cu((iim+1)*jjm+1) 93 cvfi(klon_glo) = cv((iim+1)*jjm-iim) 94 95 ! build airefi(), mesh area on physics grid 96 CALL gr_dyn_fi(1,iim+1,jjm+1,klon_glo,aire,airefi) 97 ! Poles are single points on physics grid 98 airefi(1)=sum(aire(1:iim,1)) 99 airefi(klon_glo)=sum(aire(1:iim,jjm+1)) 100 101 ! Sanity check: do total planet area match between physics and dynamics? 102 total_area_dyn=sum(aire(1:iim,1:jjm+1)) 103 total_area_phy=sum(airefi(1:klon_glo)) 104 IF (total_area_dyn/=total_area_phy) THEN 105 WRITE (lunout, *) 'iniphysiq: planet total surface discrepancy !!!' 106 WRITE (lunout, *) ' in the dynamics total_area_dyn=', total_area_dyn 107 WRITE (lunout, *) ' but in the physics total_area_phy=', total_area_phy 108 IF (abs(total_area_dyn-total_area_phy)>0.00001*total_area_dyn) THEN 109 ! stop here if the relative difference is more than 0.001% 110 abort_message = 'planet total surface discrepancy' 111 CALL abort_gcm(modname, abort_message, 1) 112 ENDIF 113 ENDIF 114 115 !$OMP PARALLEL 116 ! Now generate local lon/lat/cu/cv/area arrays 117 CALL initcomgeomphy 118 72 119 offset = klon_mpi_begin - 1 73 airephy(1:klon_omp) = parea(offset+klon_omp_begin:offset+klon_omp_end)74 cuphy(1:klon_omp) = pcu(offset+klon_omp_begin:offset+klon_omp_end)75 cvphy(1:klon_omp) = pcv(offset+klon_omp_begin:offset+klon_omp_end)76 rlond(1:klon_omp) = plon(offset+klon_omp_begin:offset+klon_omp_end)77 rlatd(1:klon_omp) = plat(offset+klon_omp_begin:offset+klon_omp_end)120 airephy(1:klon_omp) = airefi(offset+klon_omp_begin:offset+klon_omp_end) 121 cuphy(1:klon_omp) = cufi(offset+klon_omp_begin:offset+klon_omp_end) 122 cvphy(1:klon_omp) = cvfi(offset+klon_omp_begin:offset+klon_omp_end) 123 rlond(1:klon_omp) = lonfi(offset+klon_omp_begin:offset+klon_omp_end) 124 rlatd(1:klon_omp) = latfi(offset+klon_omp_begin:offset+klon_omp_end) 78 125 79 126 ! copy some fundamental parameters to physics … … 83 130 rcpp=pcpp 84 131 85 132 !$OMP END PARALLEL 86 133 87 134 ! Additional initializations for aquaplanets 88 135 !$OMP PARALLEL 89 136 IF (iflag_phys>=100) THEN 90 137 CALL iniaqua(klon_omp,rlatd,rlond,iflag_phys) 91 138 ENDIF 92 139 !$OMP END PARALLEL 93 140 94 141 END SUBROUTINE iniphysiq
Note: See TracChangeset
for help on using the changeset viewer.