Changeset 1563 for trunk/LMDZ.COMMON/libf/dynphy_lonlat/phyvenus
- Timestamp:
- May 19, 2016, 1:10:50 PM (9 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.COMMON/libf/dynphy_lonlat/phyvenus/iniphysiq_mod.F90
r1543 r1563 6 6 CONTAINS 7 7 8 SUBROUTINE iniphysiq(ii m,jjm,nlayer, &8 SUBROUTINE iniphysiq(ii,jj,nlayer, & 9 9 nbp, communicator, & 10 10 punjours, pdayref,ptimestep, & 11 rlatu,rlatv,rlonu,rlonv,aire,cu,cv, & 11 rlatudyn,rlatvdyn,rlonudyn,rlonvdyn, & 12 airedyn,cudyn,cvdyn, & 12 13 prad,pg,pr,pcpp,iflag_phys) 13 USE dimphy, ONLY: init_dimphy 14 USE mod_grid_phy_lmdz, ONLY: klon_glo, & ! number of atmospheric columns (on full grid) 15 regular_lonlat, & ! regular longitude-latitude grid type 16 nbp_lon, nbp_lat, nbp_lev 17 USE mod_phys_lmdz_para, ONLY: klon_omp, & ! number of columns (on local omp grid) 18 klon_omp_begin, & ! start index of local omp subgrid 19 klon_omp_end, & ! end index of local omp subgrid 20 klon_mpi_begin ! start indes of columns (on local mpi grid) 21 USE geometry_mod, ONLY : init_geometry 22 ! USE comgeomphy, ONLY: initcomgeomphy, & 23 ! airephy, & ! physics grid area (m2) 24 ! cuphy, & ! cu coeff. (u_covariant = cu * u) 25 ! cvphy, & ! cv coeff. (v_covariant = cv * v) 26 ! rlond, & ! longitudes 27 ! rlatd ! latitudes 14 28 15 USE temps_mod, ONLY: annee_ref, day_ref, day_ini, day_end 29 16 USE time_phylmdz_mod, ONLY: init_time 30 USE physics_distribution_mod, ONLY : init_physics_distribution31 USE regular_lonlat_mod, ONLY : init_regular_lonlat, &32 east, west, north, south, &33 north_east, north_west, &34 south_west, south_east35 USE mod_interface_dyn_phys, ONLY : init_interface_dyn_phys36 USE nrtype, ONLY: pi37 17 IMPLICIT NONE 38 18 … … 51 31 REAL, INTENT (IN) :: punjours ! length (in s) of a standard day 52 32 INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers 53 INTEGER, INTENT (IN) :: ii m! number of atmospheric columns along longitudes54 INTEGER, INTENT (IN) :: jj m! number of atompsheric columns along latitudes33 INTEGER, INTENT (IN) :: ii ! number of atmospheric columns along longitudes 34 INTEGER, INTENT (IN) :: jj ! number of atompsheric columns along latitudes 55 35 INTEGER, INTENT(IN) :: nbp ! number of physics columns for this MPI process 56 36 INTEGER, INTENT(IN) :: communicator ! MPI communicator 57 REAL, INTENT (IN) :: rlatu (jjm+1) ! latitudes of the physics grid58 REAL, INTENT (IN) :: rlatv (jjm) ! latitude boundaries of the physics grid59 REAL, INTENT (IN) :: rlonv (iim+1) ! longitudes of the physics grid60 REAL, INTENT (IN) :: rlonu (iim+1) ! longitude boundaries of the physics grid61 REAL, INTENT (IN) :: aire (iim+1,jjm+1) ! area of the dynamics grid (m2)62 REAL, INTENT (IN) :: cu ((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u)63 REAL, INTENT (IN) :: cv ((iim+1)*jjm) ! cv coeff. (v_covariant = cv * v)37 REAL, INTENT (IN) :: rlatudyn(jj+1) ! latitudes of the physics grid 38 REAL, INTENT (IN) :: rlatvdyn(jj) ! latitude boundaries of the physics grid 39 REAL, INTENT (IN) :: rlonvdyn(ii+1) ! longitudes of the physics grid 40 REAL, INTENT (IN) :: rlonudyn(ii+1) ! longitude boundaries of the physics grid 41 REAL, INTENT (IN) :: airedyn(ii+1,jj+1) ! area of the dynamics grid (m2) 42 REAL, INTENT (IN) :: cudyn((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u) 43 REAL, INTENT (IN) :: cvdyn((ii+1)*jj) ! cv coeff. (v_covariant = cv * v) 64 44 INTEGER, INTENT (IN) :: pdayref ! reference day of for the simulation 65 45 REAL, INTENT (IN) :: ptimestep !physics time step (s) 66 46 INTEGER, INTENT (IN) :: iflag_phys ! type of physics to be called 67 47 68 INTEGER :: ibegin, iend, offset69 INTEGER :: i,j,k70 48 CHARACTER (LEN=20) :: modname = 'iniphysiq' 71 49 CHARACTER (LEN=80) :: abort_message 72 REAL :: total_area_phy, total_area_dyn73 50 74 ! boundaries, on global grid 75 REAL,ALLOCATABLE :: boundslon_reg(:,:) 76 REAL,ALLOCATABLE :: boundslat_reg(:,:) 51 ! the common part for all planetary physics 52 !------------------------------------------ 53 ! --> initialize physics distribution, global fields and geometry 54 CALL inigeom(ii,jj,nlayer, & 55 nbp, communicator, & 56 rlatudyn,rlatvdyn, & 57 rlonudyn,rlonvdyn, & 58 airedyn,cudyn,cvdyn) 77 59 78 ! global array, on full physics grid: 79 REAL,ALLOCATABLE :: latfi_glo(:) 80 REAL,ALLOCATABLE :: lonfi_glo(:) 81 REAL,ALLOCATABLE :: cufi_glo(:) 82 REAL,ALLOCATABLE :: cvfi_glo(:) 83 REAL,ALLOCATABLE :: airefi_glo(:) 84 REAL,ALLOCATABLE :: boundslonfi_glo(:,:) 85 REAL,ALLOCATABLE :: boundslatfi_glo(:,:) 60 ! the distinct part for all planetary physics 61 !------------------------------------------ 86 62 87 ! local arrays, on given MPI/OpenMP domain: 88 REAL,ALLOCATABLE,SAVE :: latfi(:) 89 REAL,ALLOCATABLE,SAVE :: lonfi(:) 90 REAL,ALLOCATABLE,SAVE :: cufi(:) 91 REAL,ALLOCATABLE,SAVE :: cvfi(:) 92 REAL,ALLOCATABLE,SAVE :: airefi(:) 93 REAL,ALLOCATABLE,SAVE :: boundslonfi(:,:) 94 REAL,ALLOCATABLE,SAVE :: boundslatfi(:,:) 95 !$OMP THREADPRIVATE (latfi,lonfi,cufi,cvfi,airefi,boundslonfi,boundslatfi) 96 97 ! Initialize Physics distibution and parameters and interface with dynamics 98 IF (iim*jjm>1) THEN ! general 3D case 99 CALL init_physics_distribution(regular_lonlat,4, & 100 nbp,iim,jjm+1,nlayer,communicator) 101 ELSE ! For 1D model 102 CALL init_physics_distribution(regular_lonlat,4, & 103 1,1,1,nlayer,communicator) 104 ENDIF 105 CALL init_interface_dyn_phys 106 107 ! init regular global longitude-latitude grid points and boundaries 108 ALLOCATE(boundslon_reg(iim,2)) 109 ALLOCATE(boundslat_reg(jjm+1,2)) 110 111 DO i=1,iim 112 boundslon_reg(i,east)=rlonu(i) 113 boundslon_reg(i,west)=rlonu(i+1) 114 ENDDO 115 116 boundslat_reg(1,north)= PI/2 117 boundslat_reg(1,south)= rlatv(1) 118 DO j=2,jjm 119 boundslat_reg(j,north)=rlatv(j-1) 120 boundslat_reg(j,south)=rlatv(j) 121 ENDDO 122 boundslat_reg(jjm+1,north)= rlatv(jjm) 123 boundslat_reg(jjm+1,south)= -PI/2 124 125 ! Write values in module regular_lonlat_mod 126 CALL init_regular_lonlat(iim,jjm+1, rlonv(1:iim), rlatu, & 127 boundslon_reg, boundslat_reg) 128 129 ! Generate global arrays on full physics grid 130 ALLOCATE(latfi_glo(klon_glo),lonfi_glo(klon_glo)) 131 ALLOCATE(cufi_glo(klon_glo),cvfi_glo(klon_glo)) 132 ALLOCATE(airefi_glo(klon_glo)) 133 ALLOCATE(boundslonfi_glo(klon_glo,4)) 134 ALLOCATE(boundslatfi_glo(klon_glo,4)) 135 136 IF (klon_glo>1) THEN ! general case 137 ! North pole 138 latfi_glo(1)=rlatu(1) 139 lonfi_glo(1)=0. 140 cufi_glo(1) = cu(1) 141 cvfi_glo(1) = cv(1) 142 boundslonfi_glo(1,north_east)=0 143 boundslatfi_glo(1,north_east)=PI/2 144 boundslonfi_glo(1,north_west)=2*PI 145 boundslatfi_glo(1,north_west)=PI/2 146 boundslonfi_glo(1,south_west)=2*PI 147 boundslatfi_glo(1,south_west)=rlatv(1) 148 boundslonfi_glo(1,south_east)=0 149 boundslatfi_glo(1,south_east)=rlatv(1) 150 DO j=2,jjm 151 DO i=1,iim 152 k=(j-2)*iim+1+i 153 latfi_glo(k)= rlatu(j) 154 lonfi_glo(k)= rlonv(i) 155 cufi_glo(k) = cu((j-1)*(iim+1)+i) 156 cvfi_glo(k) = cv((j-1)*(iim+1)+i) 157 boundslonfi_glo(k,north_east)=rlonu(i) 158 boundslatfi_glo(k,north_east)=rlatv(j-1) 159 boundslonfi_glo(k,north_west)=rlonu(i+1) 160 boundslatfi_glo(k,north_west)=rlatv(j-1) 161 boundslonfi_glo(k,south_west)=rlonu(i+1) 162 boundslatfi_glo(k,south_west)=rlatv(j) 163 boundslonfi_glo(k,south_east)=rlonu(i) 164 boundslatfi_glo(k,south_east)=rlatv(j) 165 ENDDO 166 ENDDO 167 ! South pole 168 latfi_glo(klon_glo)= rlatu(jjm+1) 169 lonfi_glo(klon_glo)= 0. 170 cufi_glo(klon_glo) = cu((iim+1)*jjm+1) 171 cvfi_glo(klon_glo) = cv((iim+1)*jjm-iim) 172 boundslonfi_glo(klon_glo,north_east)= 0 173 boundslatfi_glo(klon_glo,north_east)= rlatv(jjm) 174 boundslonfi_glo(klon_glo,north_west)= 2*PI 175 boundslatfi_glo(klon_glo,north_west)= rlatv(jjm) 176 boundslonfi_glo(klon_glo,south_west)= 2*PI 177 boundslatfi_glo(klon_glo,south_west)= -PI/2 178 boundslonfi_glo(klon_glo,south_east)= 0 179 boundslatfi_glo(klon_glo,south_east)= -Pi/2 180 181 ! build airefi(), mesh area on physics grid 182 CALL gr_dyn_fi(1,iim+1,jjm+1,klon_glo,aire,airefi_glo) 183 ! Poles are single points on physics grid 184 airefi_glo(1)=sum(aire(1:iim,1)) 185 airefi_glo(klon_glo)=sum(aire(1:iim,jjm+1)) 186 187 ! Sanity check: do total planet area match between physics and dynamics? 188 total_area_dyn=sum(aire(1:iim,1:jjm+1)) 189 total_area_phy=sum(airefi_glo(1:klon_glo)) 190 IF (total_area_dyn/=total_area_phy) THEN 191 WRITE (lunout, *) 'iniphysiq: planet total surface discrepancy !!!' 192 WRITE (lunout, *) ' in the dynamics total_area_dyn=', total_area_dyn 193 WRITE (lunout, *) ' but in the physics total_area_phy=', total_area_phy 194 IF (abs(total_area_dyn-total_area_phy)>0.00001*total_area_dyn) THEN 195 ! stop here if the relative difference is more than 0.001% 196 abort_message = 'planet total surface discrepancy' 197 CALL abort_gcm(modname, abort_message, 1) 198 ENDIF 199 ENDIF 200 ELSE ! klon_glo==1, running the 1D model 201 ! just copy over input values 202 latfi_glo(1)=rlatu(1) 203 lonfi_glo(1)=rlonv(1) 204 cufi_glo(1)=cu(1) 205 cvfi_glo(1)=cv(1) 206 airefi_glo(1)=aire(1,1) 207 boundslonfi_glo(1,north_east)=rlonu(1) 208 boundslatfi_glo(1,north_east)=PI/2 209 boundslonfi_glo(1,north_west)=rlonu(2) 210 boundslatfi_glo(1,north_west)=PI/2 211 boundslonfi_glo(1,south_west)=rlonu(2) 212 boundslatfi_glo(1,south_west)=rlatv(1) 213 boundslonfi_glo(1,south_east)=rlonu(1) 214 boundslatfi_glo(1,south_east)=rlatv(1) 215 ENDIF ! of IF (klon_glo>1) 216 217 !$OMP PARALLEL 218 ! Now generate local lon/lat/cu/cv/area/bounds arrays 219 ALLOCATE(latfi(klon_omp),lonfi(klon_omp),cufi(klon_omp),cvfi(klon_omp)) 220 ALLOCATE(airefi(klon_omp)) 221 ALLOCATE(boundslonfi(klon_omp,4)) 222 ALLOCATE(boundslatfi(klon_omp,4)) 223 ! CALL initcomgeomphy 224 225 offset = klon_mpi_begin - 1 226 airefi(1:klon_omp) = airefi_glo(offset+klon_omp_begin:offset+klon_omp_end) 227 cufi(1:klon_omp) = cufi_glo(offset+klon_omp_begin:offset+klon_omp_end) 228 cvfi(1:klon_omp) = cvfi_glo(offset+klon_omp_begin:offset+klon_omp_end) 229 lonfi(1:klon_omp) = lonfi_glo(offset+klon_omp_begin:offset+klon_omp_end) 230 latfi(1:klon_omp) = latfi_glo(offset+klon_omp_begin:offset+klon_omp_end) 231 boundslonfi(1:klon_omp,:) = boundslonfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:) 232 boundslatfi(1:klon_omp,:) = boundslatfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:) 233 234 ! copy over local grid longitudes and latitudes 235 CALL init_geometry(klon_omp,lonfi,latfi,boundslonfi,boundslatfi, & 236 airefi,cufi,cvfi) 63 !$OMP PARALLEL 237 64 238 65 ! Initialize some physical constants … … 242 69 CALL init_time(annee_ref,day_ref,day_ini,day_end,ptimestep) 243 70 244 ! Initialize dimphy module 245 CALL Init_dimphy(klon_omp,nlayer) 71 !$OMP END PARALLEL 246 72 247 !$OMP END PARALLEL248 73 249 74 ! check that physical constants set in 'suphec' are coherent
Note: See TracChangeset
for help on using the changeset viewer.