- Timestamp:
- May 19, 2016, 1:10:50 PM (9 years ago)
- Location:
- trunk
- Files:
-
- 1 added
- 4 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.COMMON/libf/dynphy_lonlat/phytitan/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 control_mod, ONLY: nday 22 USE geometry_mod, ONLY : init_geometry 23 ! USE comgeomphy, ONLY: initcomgeomphy, & 24 ! airephy, & ! physics grid area (m2) 25 ! cuphy, & ! cu coeff. (u_covariant = cu * u) 26 ! cvphy, & ! cv coeff. (v_covariant = cv * v) 27 ! rlond, & ! longitudes 28 ! rlatd ! latitudes 14 29 15 USE temps_mod, ONLY: annee_ref, day_ref, day_ini, day_end 30 16 USE time_phylmdz_mod, ONLY: init_time 31 USE physics_distribution_mod, ONLY : init_physics_distribution32 USE regular_lonlat_mod, ONLY : init_regular_lonlat, &33 east, west, north, south, &34 north_east, north_west, &35 south_west, south_east36 USE mod_interface_dyn_phys, ONLY : init_interface_dyn_phys37 USE nrtype, ONLY: pi38 17 IMPLICIT NONE 39 18 … … 52 31 REAL, INTENT (IN) :: punjours ! length (in s) of a standard day 53 32 INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers 54 INTEGER, INTENT (IN) :: ii m! number of atmospheric columns along longitudes55 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 56 35 INTEGER, INTENT(IN) :: nbp ! number of physics columns for this MPI process 57 36 INTEGER, INTENT(IN) :: communicator ! MPI communicator 58 REAL, INTENT (IN) :: rlatu (jjm+1) ! latitudes of the physics grid59 REAL, INTENT (IN) :: rlatv (jjm) ! latitude boundaries of the physics grid60 REAL, INTENT (IN) :: rlonv (iim+1) ! longitudes of the physics grid61 REAL, INTENT (IN) :: rlonu (iim+1) ! longitude boundaries of the physics grid62 REAL, INTENT (IN) :: aire (iim+1,jjm+1) ! area of the dynamics grid (m2)63 REAL, INTENT (IN) :: cu ((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u)64 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) 65 44 INTEGER, INTENT (IN) :: pdayref ! reference day of for the simulation 66 45 REAL, INTENT (IN) :: ptimestep !physics time step (s) 67 46 INTEGER, INTENT (IN) :: iflag_phys ! type of physics to be called 68 47 69 INTEGER :: ibegin, iend, offset70 INTEGER :: i,j,k71 48 CHARACTER (LEN=20) :: modname = 'iniphysiq' 72 49 CHARACTER (LEN=80) :: abort_message 73 REAL :: total_area_phy, total_area_dyn74 50 75 ! boundaries, on global grid 76 REAL,ALLOCATABLE :: boundslon_reg(:,:) 77 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) 78 59 79 ! global array, on full physics grid: 80 REAL,ALLOCATABLE :: latfi_glo(:) 81 REAL,ALLOCATABLE :: lonfi_glo(:) 82 REAL,ALLOCATABLE :: cufi_glo(:) 83 REAL,ALLOCATABLE :: cvfi_glo(:) 84 REAL,ALLOCATABLE :: airefi_glo(:) 85 REAL,ALLOCATABLE :: boundslonfi_glo(:,:) 86 REAL,ALLOCATABLE :: boundslatfi_glo(:,:) 60 ! the distinct part for all planetary physics 61 !------------------------------------------ 87 62 88 ! local arrays, on given MPI/OpenMP domain: 89 REAL,ALLOCATABLE,SAVE :: latfi(:) 90 REAL,ALLOCATABLE,SAVE :: lonfi(:) 91 REAL,ALLOCATABLE,SAVE :: cufi(:) 92 REAL,ALLOCATABLE,SAVE :: cvfi(:) 93 REAL,ALLOCATABLE,SAVE :: airefi(:) 94 REAL,ALLOCATABLE,SAVE :: boundslonfi(:,:) 95 REAL,ALLOCATABLE,SAVE :: boundslatfi(:,:) 96 !$OMP THREADPRIVATE (latfi,lonfi,cufi,cvfi,airefi,boundslonfi,boundslatfi) 97 98 ! Initialize Physics distibution and parameters and interface with dynamics 99 IF (iim*jjm>1) THEN ! general 3D case 100 CALL init_physics_distribution(regular_lonlat,4, & 101 nbp,iim,jjm+1,nlayer,communicator) 102 ELSE ! For 1D model 103 CALL init_physics_distribution(regular_lonlat,4, & 104 1,1,1,nlayer,communicator) 105 ENDIF 106 CALL init_interface_dyn_phys 107 108 ! init regular global longitude-latitude grid points and boundaries 109 ALLOCATE(boundslon_reg(iim,2)) 110 ALLOCATE(boundslat_reg(jjm+1,2)) 111 112 DO i=1,iim 113 boundslon_reg(i,east)=rlonu(i) 114 boundslon_reg(i,west)=rlonu(i+1) 115 ENDDO 116 117 boundslat_reg(1,north)= PI/2 118 boundslat_reg(1,south)= rlatv(1) 119 DO j=2,jjm 120 boundslat_reg(j,north)=rlatv(j-1) 121 boundslat_reg(j,south)=rlatv(j) 122 ENDDO 123 boundslat_reg(jjm+1,north)= rlatv(jjm) 124 boundslat_reg(jjm+1,south)= -PI/2 125 126 ! Write values in module regular_lonlat_mod 127 CALL init_regular_lonlat(iim,jjm+1, rlonv(1:iim), rlatu, & 128 boundslon_reg, boundslat_reg) 129 130 ! Generate global arrays on full physics grid 131 ALLOCATE(latfi_glo(klon_glo),lonfi_glo(klon_glo)) 132 ALLOCATE(cufi_glo(klon_glo),cvfi_glo(klon_glo)) 133 ALLOCATE(airefi_glo(klon_glo)) 134 ALLOCATE(boundslonfi_glo(klon_glo,4)) 135 ALLOCATE(boundslatfi_glo(klon_glo,4)) 136 137 IF (klon_glo>1) THEN ! general case 138 ! North pole 139 latfi_glo(1)=rlatu(1) 140 lonfi_glo(1)=0. 141 cufi_glo(1) = cu(1) 142 cvfi_glo(1) = cv(1) 143 boundslonfi_glo(1,north_east)=0 144 boundslatfi_glo(1,north_east)=PI/2 145 boundslonfi_glo(1,north_west)=2*PI 146 boundslatfi_glo(1,north_west)=PI/2 147 boundslonfi_glo(1,south_west)=2*PI 148 boundslatfi_glo(1,south_west)=rlatv(1) 149 boundslonfi_glo(1,south_east)=0 150 boundslatfi_glo(1,south_east)=rlatv(1) 151 DO j=2,jjm 152 DO i=1,iim 153 k=(j-2)*iim+1+i 154 latfi_glo(k)= rlatu(j) 155 lonfi_glo(k)= rlonv(i) 156 cufi_glo(k) = cu((j-1)*(iim+1)+i) 157 cvfi_glo(k) = cv((j-1)*(iim+1)+i) 158 boundslonfi_glo(k,north_east)=rlonu(i) 159 boundslatfi_glo(k,north_east)=rlatv(j-1) 160 boundslonfi_glo(k,north_west)=rlonu(i+1) 161 boundslatfi_glo(k,north_west)=rlatv(j-1) 162 boundslonfi_glo(k,south_west)=rlonu(i+1) 163 boundslatfi_glo(k,south_west)=rlatv(j) 164 boundslonfi_glo(k,south_east)=rlonu(i) 165 boundslatfi_glo(k,south_east)=rlatv(j) 166 ENDDO 167 ENDDO 168 ! South pole 169 latfi_glo(klon_glo)= rlatu(jjm+1) 170 lonfi_glo(klon_glo)= 0. 171 cufi_glo(klon_glo) = cu((iim+1)*jjm+1) 172 cvfi_glo(klon_glo) = cv((iim+1)*jjm-iim) 173 boundslonfi_glo(klon_glo,north_east)= 0 174 boundslatfi_glo(klon_glo,north_east)= rlatv(jjm) 175 boundslonfi_glo(klon_glo,north_west)= 2*PI 176 boundslatfi_glo(klon_glo,north_west)= rlatv(jjm) 177 boundslonfi_glo(klon_glo,south_west)= 2*PI 178 boundslatfi_glo(klon_glo,south_west)= -PI/2 179 boundslonfi_glo(klon_glo,south_east)= 0 180 boundslatfi_glo(klon_glo,south_east)= -Pi/2 181 182 ! build airefi(), mesh area on physics grid 183 CALL gr_dyn_fi(1,iim+1,jjm+1,klon_glo,aire,airefi_glo) 184 ! Poles are single points on physics grid 185 airefi_glo(1)=sum(aire(1:iim,1)) 186 airefi_glo(klon_glo)=sum(aire(1:iim,jjm+1)) 187 188 ! Sanity check: do total planet area match between physics and dynamics? 189 total_area_dyn=sum(aire(1:iim,1:jjm+1)) 190 total_area_phy=sum(airefi_glo(1:klon_glo)) 191 IF (total_area_dyn/=total_area_phy) THEN 192 WRITE (lunout, *) 'iniphysiq: planet total surface discrepancy !!!' 193 WRITE (lunout, *) ' in the dynamics total_area_dyn=', total_area_dyn 194 WRITE (lunout, *) ' but in the physics total_area_phy=', total_area_phy 195 IF (abs(total_area_dyn-total_area_phy)>0.00001*total_area_dyn) THEN 196 ! stop here if the relative difference is more than 0.001% 197 abort_message = 'planet total surface discrepancy' 198 CALL abort_gcm(modname, abort_message, 1) 199 ENDIF 200 ENDIF 201 ELSE ! klon_glo==1, running the 1D model 202 ! just copy over input values 203 latfi_glo(1)=rlatu(1) 204 lonfi_glo(1)=rlonv(1) 205 cufi_glo(1)=cu(1) 206 cvfi_glo(1)=cv(1) 207 airefi_glo(1)=aire(1,1) 208 boundslonfi_glo(1,north_east)=rlonu(1) 209 boundslatfi_glo(1,north_east)=PI/2 210 boundslonfi_glo(1,north_west)=rlonu(2) 211 boundslatfi_glo(1,north_west)=PI/2 212 boundslonfi_glo(1,south_west)=rlonu(2) 213 boundslatfi_glo(1,south_west)=rlatv(1) 214 boundslonfi_glo(1,south_east)=rlonu(1) 215 boundslatfi_glo(1,south_east)=rlatv(1) 216 ENDIF ! of IF (klon_glo>1) 217 218 !$OMP PARALLEL 219 ! Now generate local lon/lat/cu/cv/area/bounds arrays 220 ALLOCATE(latfi(klon_omp),lonfi(klon_omp),cufi(klon_omp),cvfi(klon_omp)) 221 ALLOCATE(airefi(klon_omp)) 222 ALLOCATE(boundslonfi(klon_omp,4)) 223 ALLOCATE(boundslatfi(klon_omp,4)) 224 ! CALL initcomgeomphy 225 226 offset = klon_mpi_begin - 1 227 airefi(1:klon_omp) = airefi_glo(offset+klon_omp_begin:offset+klon_omp_end) 228 cufi(1:klon_omp) = cufi_glo(offset+klon_omp_begin:offset+klon_omp_end) 229 cvfi(1:klon_omp) = cvfi_glo(offset+klon_omp_begin:offset+klon_omp_end) 230 lonfi(1:klon_omp) = lonfi_glo(offset+klon_omp_begin:offset+klon_omp_end) 231 latfi(1:klon_omp) = latfi_glo(offset+klon_omp_begin:offset+klon_omp_end) 232 boundslonfi(1:klon_omp,:) = boundslonfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:) 233 boundslatfi(1:klon_omp,:) = boundslatfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:) 234 235 ! copy over local grid longitudes and latitudes 236 CALL init_geometry(klon_omp,lonfi,latfi,boundslonfi,boundslatfi, & 237 airefi,cufi,cvfi) 63 !$OMP PARALLEL 238 64 239 65 ! Initialize some physical constants … … 243 69 CALL init_time(annee_ref,day_ref,day_ini,day_end,nday,ptimestep) 244 70 245 ! Initialize dimphy module 246 CALL Init_dimphy(klon_omp,nlayer) 71 !$OMP END PARALLEL 247 72 248 !$OMP END PARALLEL249 73 250 74 ! check that physical constants set in 'suphec' are coherent -
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 -
trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/iniphysiq_mod.F90
r1543 r1563 10 10 prad,pg,pr,pcpp,iflag_phys) 11 11 12 use dimphy, only : init_dimphy13 use mod_grid_phy_lmdz, only : klon_glo, & ! number of atmospheric columns (on full grid)14 regular_lonlat ! regular longitude-latitude grid type15 use mod_phys_lmdz_para, only : klon_omp, & ! number of columns (on local omp grid)16 klon_omp_begin, & ! start index of local omp subgrid17 klon_omp_end, & ! end index of local omp subgrid18 klon_mpi_begin ! start indes of columns (on local mpi grid)19 12 use control_mod, only: nday 20 use geometry_mod, only: init_geometry, &21 cell_area, & ! physics grid area (m2)22 longitude, & ! longitudes (rad)23 latitude ! latitudes (rad)24 !use comgeomphy, only : initcomgeomphy, &25 ! cell_area, & ! physics grid area (m2)26 ! dx, & ! cu coeff. (u_covariant = cu * u)27 ! dy, & ! cv coeff. (v_covariant = cv * v)28 ! longitude, & ! longitudes (rad)29 ! latitude ! latitudes (rad)30 13 use surf_heat_transp_mod, only: ini_surf_heat_transp 31 14 use infotrac, only : nqtot ! number of advected tracers … … 33 16 USE comvert_mod, ONLY: ap,bp,preff 34 17 use inifis_mod, only: inifis 35 use physics_distribution_mod, only: init_physics_distribution36 use regular_lonlat_mod, only: init_regular_lonlat, &37 east, west, north, south, &38 north_east, north_west, &39 south_west, south_east40 use mod_interface_dyn_phys, only: init_interface_dyn_phys41 18 use ioipsl_getin_p_mod, only: getin_p 19 20 21 use geometry_mod, only: cell_area, & ! physics grid area (m2) 22 longitude, & ! longitudes (rad) 23 latitude ! latitudes (rad) 24 ! necessary to get klon_omp 25 USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid) 42 26 43 27 implicit none … … 52 36 real,intent(in) :: pcpp ! specific heat Cp 53 37 real,intent(in) :: punjours ! length (in s) of a standard day 54 !integer,intent(in) :: ngrid ! number of horizontal grid points in the physics (full grid)55 38 integer,intent(in) :: nlayer ! number of atmospheric layers 56 39 integer,intent(in) :: ii ! number of atmospheric coulumns along longitudes … … 69 52 integer,intent(in) :: iflag_phys ! type of physics to be called 70 53 71 integer :: ibegin,iend,offset72 integer :: i,j,k73 character(len=20) :: modname='iniphysiq'74 character(len=80) :: abort_message75 real :: total_area_phy, total_area_dyn76 real :: pi77 54 logical :: ok_slab_ocean 78 55 79 ! boundaries, on global grid 80 real,allocatable :: boundslon_reg(:,:) 81 real,allocatable :: boundslat_reg(:,:) 56 ! the common part for all planetary physics 57 !------------------------------------------ 58 ! --> initialize physics distribution, global fields and geometry 59 CALL inigeom(ii,jj,nlayer, & 60 nbp, communicator, & 61 rlatudyn,rlatvdyn, & 62 rlonudyn,rlonvdyn, & 63 airedyn,cudyn,cvdyn) 82 64 83 ! global array, on full physics grid: 84 real,allocatable :: latfi_glo(:) 85 real,allocatable :: lonfi_glo(:) 86 real,allocatable :: cufi_glo(:) 87 real,allocatable :: cvfi_glo(:) 88 real,allocatable :: airefi_glo(:) 89 real,allocatable :: boundslonfi_glo(:,:) 90 real,allocatable :: boundslatfi_glo(:,:) 65 ! the distinct part for all planetary physics 66 !------------------------------------------ 91 67 92 ! local arrays, on given MPI/OpenMP domain: 93 real,allocatable,save :: latfi(:) 94 real,allocatable,save :: lonfi(:) 95 real,allocatable,save :: cufi(:) 96 real,allocatable,save :: cvfi(:) 97 real,allocatable,save :: airefi(:) 98 real,allocatable,save :: boundslonfi(:,:) 99 real,allocatable,save :: boundslatfi(:,:) 100 !$OMP THREADPRIVATE (latfi,lonfi,cufi,cvfi,airefi,boundslonfi,boundslatfi) 68 !$OMP PARALLEL 101 69 102 pi=2.*asin(1.0) 103 104 ! Initialize Physics distibution and parameters and interface with dynamics 105 CALL init_physics_distribution(regular_lonlat,4, & 106 nbp,ii,jj+1,nlayer,communicator) 107 CALL init_interface_dyn_phys 108 109 ! init regular global longitude-latitude grid points and boundaries 110 ALLOCATE(boundslon_reg(ii,2)) 111 ALLOCATE(boundslat_reg(jj+1,2)) 112 113 DO i=1,ii 114 boundslon_reg(i,east)=rlonudyn(i) 115 boundslon_reg(i,west)=rlonudyn(i+1) 116 ENDDO 117 118 boundslat_reg(1,north)= PI/2 119 boundslat_reg(1,south)= rlatvdyn(1) 120 DO j=2,jj 121 boundslat_reg(j,north)=rlatvdyn(j-1) 122 boundslat_reg(j,south)=rlatvdyn(j) 123 ENDDO 124 boundslat_reg(jj+1,north)= rlatvdyn(jj) 125 boundslat_reg(jj+1,south)= -PI/2 126 127 ! Write values in module regular_lonlat_mod 128 CALL init_regular_lonlat(ii,jj+1, rlonvdyn(1:ii), rlatudyn, & 129 boundslon_reg, boundslat_reg) 130 131 ! Generate global arrays on full physics grid 132 allocate(latfi_glo(klon_glo),lonfi_glo(klon_glo)) 133 allocate(cufi_glo(klon_glo),cvfi_glo(klon_glo)) 134 allocate(airefi_glo(klon_glo)) 135 allocate(boundslonfi_glo(klon_glo,4)) 136 allocate(boundslatfi_glo(klon_glo,4)) 137 138 ! North pole 139 latfi_glo(1)=rlatudyn(1) 140 lonfi_glo(1)=0. 141 cufi_glo(1) = cudyn(1) 142 cvfi_glo(1) = cvdyn(1) 143 boundslonfi_glo(1,north_east)=0 144 boundslatfi_glo(1,north_east)=PI/2 145 boundslonfi_glo(1,north_west)=2*PI 146 boundslatfi_glo(1,north_west)=PI/2 147 boundslonfi_glo(1,south_west)=2*PI 148 boundslatfi_glo(1,south_west)=rlatvdyn(1) 149 boundslonfi_glo(1,south_east)=0 150 boundslatfi_glo(1,south_east)=rlatvdyn(1) 151 DO j=2,jj 152 DO i=1,ii 153 k=(j-2)*ii+1+i 154 latfi_glo((j-2)*ii+1+i)= rlatudyn(j) 155 lonfi_glo((j-2)*ii+1+i)= rlonvdyn(i) 156 cufi_glo((j-2)*ii+1+i) = cudyn((j-1)*(ii+1)+i) 157 cvfi_glo((j-2)*ii+1+i) = cvdyn((j-1)*(ii+1)+i) 158 boundslonfi_glo(k,north_east)=rlonudyn(i) 159 boundslatfi_glo(k,north_east)=rlatvdyn(j-1) 160 boundslonfi_glo(k,north_west)=rlonudyn(i+1) 161 boundslatfi_glo(k,north_west)=rlatvdyn(j-1) 162 boundslonfi_glo(k,south_west)=rlonudyn(i+1) 163 boundslatfi_glo(k,south_west)=rlatvdyn(j) 164 boundslonfi_glo(k,south_east)=rlonudyn(i) 165 boundslatfi_glo(k,south_east)=rlatvdyn(j) 166 ENDDO 167 ENDDO 168 ! South pole 169 latfi_glo(klon_glo)= rlatudyn(jj+1) 170 lonfi_glo(klon_glo)= 0. 171 cufi_glo(klon_glo) = cudyn((ii+1)*jj+1) 172 cvfi_glo(klon_glo) = cvdyn((ii+1)*jj-ii) 173 boundslonfi_glo(klon_glo,north_east)= 0 174 boundslatfi_glo(klon_glo,north_east)= rlatvdyn(jj) 175 boundslonfi_glo(klon_glo,north_west)= 2*PI 176 boundslatfi_glo(klon_glo,north_west)= rlatvdyn(jj) 177 boundslonfi_glo(klon_glo,south_west)= 2*PI 178 boundslatfi_glo(klon_glo,south_west)= -PI/2 179 boundslonfi_glo(klon_glo,south_east)= 0 180 boundslatfi_glo(klon_glo,south_east)= -Pi/2 181 182 ! build airefi(), mesh area on physics grid 183 CALL gr_dyn_fi(1,ii+1,jj+1,klon_glo,airedyn,airefi_glo) 184 ! Poles are single points on physics grid 185 airefi_glo(1)=sum(airedyn(1:ii,1)) 186 airefi_glo(klon_glo)=sum(airedyn(1:ii,jj+1)) 187 188 ! Sanity check: do total planet area match between physics and dynamics? 189 total_area_dyn=sum(airedyn(1:ii,1:jj+1)) 190 total_area_phy=sum(airefi_glo(1:klon_glo)) 191 IF (total_area_dyn/=total_area_phy) THEN 192 WRITE (lunout, *) 'iniphysiq: planet total surface discrepancy !!!' 193 WRITE (lunout, *) ' in the dynamics total_area_dyn=', total_area_dyn 194 WRITE (lunout, *) ' but in the physics total_area_phy=', total_area_phy 195 IF (abs(total_area_dyn-total_area_phy)>0.00001*total_area_dyn) THEN 196 ! stop here if the relative difference is more than 0.001% 197 abort_message = 'planet total surface discrepancy' 198 CALL abort_gcm(modname, abort_message, 1) 199 ENDIF 200 ENDIF 201 202 203 !$OMP PARALLEL 204 ! Now generate local lon/lat/cu/cv/area arrays 205 allocate(latfi(klon_omp),lonfi(klon_omp),cufi(klon_omp),cvfi(klon_omp)) 206 allocate(airefi(klon_omp)) 207 allocate(boundslonfi(klon_omp,4)) 208 allocate(boundslatfi(klon_omp,4)) 209 !call initcomgeomphy 210 211 offset=klon_mpi_begin-1 212 airefi(1:klon_omp)=airefi_glo(offset+klon_omp_begin:offset+klon_omp_end) 213 cufi(1:klon_omp)=cufi_glo(offset+klon_omp_begin:offset+klon_omp_end) 214 cvfi(1:klon_omp)=cvfi_glo(offset+klon_omp_begin:offset+klon_omp_end) 215 lonfi(1:klon_omp)=lonfi_glo(offset+klon_omp_begin:offset+klon_omp_end) 216 latfi(1:klon_omp)=latfi_glo(offset+klon_omp_begin:offset+klon_omp_end) 217 boundslonfi(1:klon_omp,:)=boundslonfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:) 218 boundslatfi(1:klon_omp,:)=boundslatfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:) 219 220 ! copy over local grid longitudes and latitudes 221 CALL init_geometry(klon_omp,lonfi,latfi,boundslonfi,boundslatfi, & 222 airefi,cufi,cvfi) 223 224 call init_dimphy(klon_omp,nlayer) ! Initialize dimphy module 70 ! copy some fundamental parameters to physics 71 ! and do some initializations 225 72 226 73 ! copy over preff , ap() and bp() … … 236 83 endif 237 84 238 ! copy some fundamental parameters to physics239 ! and do some initializations240 85 call inifis(klon_omp,nlayer,nqtot,pdayref,punjours,nday,ptimestep, & 241 86 latitude,longitude,cell_area,prad,pg,pr,pcpp) 242 87 88 243 89 !$OMP END PARALLEL 244 245 90 246 91 end subroutine iniphysiq -
trunk/LMDZ.MARS/libf/dynphy_lonlat/phymars/iniphysiq_mod.F90
r1543 r1563 6 6 nbp, communicator, & 7 7 punjours, pdayref,ptimestep, & 8 rlatu,rlatv,rlonu,rlonv,aire,cu,cv, & 8 rlatudyn,rlatvdyn,rlonudyn,rlonvdyn, & 9 airedyn,cudyn,cvdyn, & 9 10 prad,pg,pr,pcpp,iflag_phys) 10 11 11 use dimphy, only : init_dimphy12 use mod_grid_phy_lmdz, only : klon_glo, & ! number of atmospheric columns (on full grid)13 regular_lonlat ! regular longitude-latitude grid type14 use mod_phys_lmdz_para, only : klon_omp, & ! number of columns (on local omp grid)15 klon_omp_begin, & ! start index of local omp subgrid16 klon_omp_end, & ! end index of local omp subgrid17 klon_mpi_begin ! start indes of columns (on local mpi grid)18 use geometry_mod, only: init_geometry19 !use comgeomphy, only : initcomgeomphy, &20 ! cell_area, & ! physics grid area (m2)21 ! dx, & ! cu coeff. (u_covariant = cu * u)22 ! dy, & ! cv coeff. (v_covariant = cv * v)23 ! longitude, & ! longitudes (rad)24 ! latitude ! latitudes (rad)25 12 use infotrac, only : nqtot ! number of advected tracers 26 13 use comgeomfi_h, only: ini_fillgeom 27 14 use temps_mod, only: day_ini, hour_ini 28 15 use phys_state_var_init_mod, only: phys_state_var_init 29 use physics_distribution_mod, only: init_physics_distribution 30 use regular_lonlat_mod, only: init_regular_lonlat, &31 east, west, north, south, &32 north_east, north_west, &33 south_west, south_east 34 use mod_interface_dyn_phys, only: init_interface_dyn_phys 16 17 use geometry_mod, only: cell_area, & ! physics grid area (m2) 18 longitude, & ! longitudes (rad) 19 latitude ! latitudes (rad) 20 ! necessary to get klon_omp 21 USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid) 35 22 36 23 implicit none … … 43 30 real,intent(in) :: pcpp ! specific heat Cp 44 31 real,intent(in) :: punjours ! length (in s) of a standard day 45 !integer,intent(in) :: ngrid ! number of horizontal grid points in the physics (full grid)46 32 integer,intent(in) :: nlayer ! number of atmospheric layers 47 33 integer,intent(in) :: ii ! number of atmospheric coulumns along longitudes … … 49 35 integer,intent(in) :: nbp ! number of physics columns for this MPI process 50 36 integer,intent(in) :: communicator ! MPI communicator 51 real,intent(in) :: rlatu (jj+1) ! latitudes of the physics grid52 real,intent(in) :: rlatv (jj) ! latitude boundaries of the physics grid53 real,intent(in) :: rlonv (ii+1) ! longitudes of the physics grid54 real,intent(in) :: rlonu (ii+1) ! longitude boundaries of the physics grid55 real,intent(in) :: aire (ii+1,jj+1) ! area of the dynamics grid (m2)56 real,intent(in) :: cu ((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u)57 real,intent(in) :: cv ((ii+1)*jj) ! 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) 58 44 integer,intent(in) :: pdayref ! reference day of for the simulation 59 45 real,intent(in) :: ptimestep !physics time step (s) 60 46 integer,intent(in) :: iflag_phys ! type of physics to be called 61 47 62 integer :: ibegin,iend,offset 63 integer :: i,j,k 64 character(len=20) :: modname='iniphysiq' 65 character(len=80) :: abort_message 66 real :: total_area_phy, total_area_dyn 67 real :: pi 48 ! the common part for all planetary physics 49 !------------------------------------------ 50 ! --> initialize physics distribution, global fields and geometry 51 CALL inigeom(ii,jj,nlayer, & 52 nbp, communicator, & 53 rlatudyn,rlatvdyn, & 54 rlonudyn,rlonvdyn, & 55 airedyn,cudyn,cvdyn) 68 56 69 ! boundaries, on global grid 70 real,allocatable :: boundslon_reg(:,:) 71 real,allocatable :: boundslat_reg(:,:) 57 ! the distinct part for all planetary physics 58 !------------------------------------------ 72 59 73 ! global array, on full physics grid: 74 real,allocatable :: latfi_glo(:) 75 real,allocatable :: lonfi_glo(:) 76 real,allocatable :: cufi_glo(:) 77 real,allocatable :: cvfi_glo(:) 78 real,allocatable :: airefi_glo(:) 79 real,allocatable :: boundslonfi_glo(:,:) 80 real,allocatable :: boundslatfi_glo(:,:) 81 82 ! local arrays, on given MPI/OpenMP domain: 83 real,allocatable,save :: latfi(:) 84 real,allocatable,save :: lonfi(:) 85 real,allocatable,save :: cufi(:) 86 real,allocatable,save :: cvfi(:) 87 real,allocatable,save :: airefi(:) 88 real,allocatable,save :: boundslonfi(:,:) 89 real,allocatable,save :: boundslatfi(:,:) 90 !$OMP THREADPRIVATE (latfi,lonfi,cufi,cvfi,airefi,boundslonfi,boundslatfi) 91 92 93 pi=2.*asin(1.0) 94 95 ! Initialize Physics distibution and parameters and interface with dynamics 96 CALL init_physics_distribution(regular_lonlat,4, & 97 nbp,ii,jj+1,nlayer,communicator) 98 CALL init_interface_dyn_phys 99 100 ! init regular global longitude-latitude grid points and boundaries 101 ALLOCATE(boundslon_reg(ii,2)) 102 ALLOCATE(boundslat_reg(jj+1,2)) 60 !$OMP PARALLEL 103 61 104 DO i=1,ii105 boundslon_reg(i,east)=rlonu(i)106 boundslon_reg(i,west)=rlonu(i+1)107 ENDDO108 109 boundslat_reg(1,north)= PI/2110 boundslat_reg(1,south)= rlatv(1)111 DO j=2,jj112 boundslat_reg(j,north)=rlatv(j-1)113 boundslat_reg(j,south)=rlatv(j)114 ENDDO115 boundslat_reg(jj+1,north)= rlatv(jj)116 boundslat_reg(jj+1,south)= -PI/2117 118 ! Write values in module regular_lonlat_mod119 CALL init_regular_lonlat(ii,jj+1, rlonv(1:ii), rlatu, &120 boundslon_reg, boundslat_reg)121 122 ! Generate global arrays on full physics grid123 allocate(latfi_glo(klon_glo),lonfi_glo(klon_glo))124 allocate(cufi_glo(klon_glo),cvfi_glo(klon_glo))125 allocate(airefi_glo(klon_glo))126 allocate(boundslonfi_glo(klon_glo,4))127 allocate(boundslatfi_glo(klon_glo,4))128 129 ! North pole130 latfi_glo(1)=rlatu(1)131 lonfi_glo(1)=0.132 cufi_glo(1) = cu(1)133 cvfi_glo(1) = cv(1)134 boundslonfi_glo(1,north_east)=0135 boundslatfi_glo(1,north_east)=PI/2136 boundslonfi_glo(1,north_west)=2*PI137 boundslatfi_glo(1,north_west)=PI/2138 boundslonfi_glo(1,south_west)=2*PI139 boundslatfi_glo(1,south_west)=rlatv(1)140 boundslonfi_glo(1,south_east)=0141 boundslatfi_glo(1,south_east)=rlatv(1)142 DO j=2,jj143 DO i=1,ii144 k=(j-2)*ii+1+i145 latfi_glo((j-2)*ii+1+i)= rlatu(j)146 lonfi_glo((j-2)*ii+1+i)= rlonv(i)147 cufi_glo((j-2)*ii+1+i) = cu((j-1)*(ii+1)+i)148 cvfi_glo((j-2)*ii+1+i) = cv((j-1)*(ii+1)+i)149 boundslonfi_glo(k,north_east)=rlonu(i)150 boundslatfi_glo(k,north_east)=rlatv(j-1)151 boundslonfi_glo(k,north_west)=rlonu(i+1)152 boundslatfi_glo(k,north_west)=rlatv(j-1)153 boundslonfi_glo(k,south_west)=rlonu(i+1)154 boundslatfi_glo(k,south_west)=rlatv(j)155 boundslonfi_glo(k,south_east)=rlonu(i)156 boundslatfi_glo(k,south_east)=rlatv(j)157 ENDDO158 ENDDO159 ! South pole160 latfi_glo(klon_glo)= rlatu(jj+1)161 lonfi_glo(klon_glo)= 0.162 cufi_glo(klon_glo) = cu((ii+1)*jj+1)163 cvfi_glo(klon_glo) = cv((ii+1)*jj-ii)164 boundslonfi_glo(klon_glo,north_east)= 0165 boundslatfi_glo(klon_glo,north_east)= rlatv(jj)166 boundslonfi_glo(klon_glo,north_west)= 2*PI167 boundslatfi_glo(klon_glo,north_west)= rlatv(jj)168 boundslonfi_glo(klon_glo,south_west)= 2*PI169 boundslatfi_glo(klon_glo,south_west)= -PI/2170 boundslonfi_glo(klon_glo,south_east)= 0171 boundslatfi_glo(klon_glo,south_east)= -Pi/2172 173 ! build airefi(), mesh area on physics grid174 CALL gr_dyn_fi(1,ii+1,jj+1,klon_glo,aire,airefi_glo)175 ! Poles are single points on physics grid176 airefi_glo(1)=sum(aire(1:ii,1))177 airefi_glo(klon_glo)=sum(aire(1:ii,jj+1))178 179 ! Sanity check: do total planet area match between physics and dynamics?180 total_area_dyn=sum(aire(1:ii,1:jj+1))181 total_area_phy=sum(airefi_glo(1:klon_glo))182 IF (total_area_dyn/=total_area_phy) THEN183 WRITE (lunout, *) 'iniphysiq: planet total surface discrepancy !!!'184 WRITE (lunout, *) ' in the dynamics total_area_dyn=', total_area_dyn185 WRITE (lunout, *) ' but in the physics total_area_phy=', total_area_phy186 IF (abs(total_area_dyn-total_area_phy)>0.00001*total_area_dyn) THEN187 ! stop here if the relative difference is more than 0.001%188 abort_message = 'planet total surface discrepancy'189 CALL abort_gcm(modname, abort_message, 1)190 ENDIF191 ENDIF192 193 194 195 !$OMP PARALLEL196 ! Now generate local lon/lat/cu/cv/area arrays197 allocate(latfi(klon_omp),lonfi(klon_omp),cufi(klon_omp),cvfi(klon_omp))198 allocate(airefi(klon_omp))199 allocate(boundslonfi(klon_omp,4))200 allocate(boundslatfi(klon_omp,4))201 !call initcomgeomphy202 203 offset=klon_mpi_begin-1204 airefi(1:klon_omp)=airefi_glo(offset+klon_omp_begin:offset+klon_omp_end)205 cufi(1:klon_omp)=cufi_glo(offset+klon_omp_begin:offset+klon_omp_end)206 cvfi(1:klon_omp)=cvfi_glo(offset+klon_omp_begin:offset+klon_omp_end)207 lonfi(1:klon_omp)=lonfi_glo(offset+klon_omp_begin:offset+klon_omp_end)208 latfi(1:klon_omp)=latfi_glo(offset+klon_omp_begin:offset+klon_omp_end)209 boundslonfi(1:klon_omp,:)=boundslonfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:)210 boundslatfi(1:klon_omp,:)=boundslatfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:)211 212 ! copy over local grid longitudes and latitudes213 CALL init_geometry(klon_omp,lonfi,latfi,boundslonfi,boundslatfi, &214 airefi,cufi,cvfi)215 216 62 ! copy some fundamental parameters to physics 217 63 ! and do some initializations 218 64 219 call init_dimphy(klon_omp,nlayer) ! Initialize dimphy module220 65 call phys_state_var_init(klon_omp,nlayer,nqtot, & 221 66 day_ini,hour_ini,punjours,ptimestep, & 222 67 prad,pg,pr,pcpp) 223 call ini_fillgeom(klon_omp,latfi,lonfi,airefi) 68 call ini_fillgeom(klon_omp,latitude,longitude,cell_area) 69 ! work is needed to put what is in comgeomfi_h in geometry_mod? 70 224 71 call conf_phys(klon_omp,nlayer,nqtot) 225 72 … … 229 76 !$OMP END PARALLEL 230 77 231 232 78 end subroutine iniphysiq 233 79
Note: See TracChangeset
for help on using the changeset viewer.