- Timestamp:
- May 6, 2015, 12:14:12 PM (10 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
dynamico_lmdz/aquaplanet/LMDZ5/libf/dynlonlat_phylonlat/phylmd/iniphysiq.F90
r3822 r3825 3 3 4 4 5 SUBROUTINE iniphysiq(ii, jj,nlayer,punjours, pdayref,ptimestep, &5 SUBROUTINE iniphysiq(ii, jj, nbp, communicator, nlayer,punjours, pdayref,ptimestep, & 6 6 rlatu,rlatv,rlonu,rlonv,aire,cu,cv, & 7 7 prad,pg,pr,pcpp,iflag_phys) 8 8 9 USE dimphy, ONLY: klev ! number of atmospheric levels 9 USE mod_grid_phy_lmdz, ONLY: klon_glo ! number of atmospheric columns10 ! (on full grid)10 USE mod_grid_phy_lmdz, ONLY: klon_glo, & ! number of atmospheric columns (on full grid) 11 regular_lonlat ! regular longitude-latitude grid type 11 12 USE mod_phys_lmdz_para, ONLY: klon_omp, & ! number of columns (on local omp grid) 12 13 klon_omp_begin, & ! start index of local omp subgrid 13 14 klon_omp_end, & ! end index of local omp subgrid 14 15 klon_mpi_begin ! start indes of columns (on local mpi grid) 15 USE comgeomphy, ONLY: initcomgeomphy, & 16 initcomgeomphy_vert, & 17 initcomgeomphy_horiz,& 18 airephy, & ! physics grid area (m2) 19 cuphy, & ! cu coeff. (u_covariant = cu * u) 20 cvphy, & ! cv coeff. (v_covariant = cv * v) 21 rlond, & ! longitudes 22 rlatd ! latitudes 16 USE geometry_mod, ONLY : init_geometry 17 USE vertical_layers_mod, ONLY : init_vertical_layers 23 18 USE misc_mod, ONLY: debug 24 19 USE infotrac, ONLY: nqtot,nqo,nbtr,tname,ttext,type_trac,& … … 29 24 USE infotrac_phy, ONLY: init_infotrac_phy 30 25 USE phyaqua_mod, ONLY: iniaqua 26 USE physics_distribution_mod, ONLY : init_physics_distribution 27 USE regular_lonlat_mod, ONLY : init_regular_lonlat, east, west, north, south, north_east, north_west, south_west, south_east 28 USE mod_interface_dyn_phys, ONLY : init_interface_dyn_phys 31 29 IMPLICIT NONE 32 30 … … 51 49 INTEGER, INTENT (IN) :: ii ! number of atmospheric columns along longitudes 52 50 INTEGER, INTENT (IN) :: jj ! number of atompsheric columns along latitudes 51 INTEGER, INTENT (IN) :: nbp ! number of physics points (local) 52 INTEGER, INTENT (IN) :: communicator ! mpi communicator 53 53 REAL, INTENT (IN) :: rlatu(jj+1) ! latitudes of the physics grid 54 54 REAL, INTENT (IN) :: rlatv(jj) ! latitude boundaries of the physics grid … … 63 63 64 64 INTEGER :: ibegin, iend, offset 65 INTEGER :: i,j 65 INTEGER :: i,j,k 66 66 CHARACTER (LEN=20) :: modname = 'iniphysiq' 67 67 CHARACTER (LEN=80) :: abort_message 68 68 REAL :: total_area_phy, total_area_dyn 69 69 70 REAL,ALLOCATABLE :: boundslon_reg(:,:) 71 REAL,ALLOCATABLE :: boundslat_reg(:,:) 70 72 71 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(:,:) 72 81 REAL,ALLOCATABLE :: latfi(:) 73 82 REAL,ALLOCATABLE :: lonfi(:) … … 75 84 REAL,ALLOCATABLE :: cvfi(:) 76 85 REAL,ALLOCATABLE :: airefi(:) 77 78 IF (nlayer/=klev) THEN 79 WRITE (lunout, *) 'STOP in ', trim(modname) 80 WRITE (lunout, *) 'Problem with dimensions :' 81 WRITE (lunout, *) 'nlayer = ', nlayer 82 WRITE (lunout, *) 'klev = ', klev 83 abort_message = '' 84 CALL abort_gcm(modname, abort_message, 1) 85 END IF 86 87 !call init_phys_lmdz(ii,jj+1,llm,1,(/(jj-1)*ii+2/)) 86 REAL,ALLOCATABLE :: boundslonfi(:,:) 87 REAL,ALLOCATABLE :: boundslatfi(:,:) 88 89 CALL init_physics_distribution(regular_lonlat, 4, nbp, ii, jj+1, nlayer, communicator) 90 CALL init_interface_dyn_phys 91 92 93 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 94 ! init regular longitude-latitude grid 95 96 ALLOCATE(boundslon_reg(ii,2)) 97 ALLOCATE(boundslat_reg(jj+1,2)) 98 99 DO i=1,ii 100 boundslon_reg(i,east)=rlonu(i) 101 boundslon_reg(i,west)=rlonu(i+1) 102 ENDDO 103 104 boundslat_reg(1,north)= PI/2 105 boundslat_reg(1,south)= rlatv(1) 106 DO j=2,jj 107 boundslat_reg(i,north)=rlatv(j-1) 108 boundslat_reg(i,south)=rlatv(j) 109 ENDDO 110 boundslat_reg(jj+1,north)= rlatv(jj) 111 boundslat_reg(jj+1,south)= -PI/2 112 113 CALL init_regular_lonlat(ii,jj+1, rlonv(1:ii), rlatu, boundslon_reg, boundslat_reg) 114 115 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 88 116 89 117 ! Generate global arrays on full physics grid 118 ALLOCATE(latfi_glo(klon_glo),lonfi_glo(klon_glo),cufi_glo(klon_glo),cvfi_glo(klon_glo)) 119 ALLOCATE(airefi_glo(klon_glo)) 120 ALLOCATE(boundslonfi_glo(klon_glo,4)) 121 ALLOCATE(boundslatfi_glo(klon_glo,4)) 122 90 123 ALLOCATE(latfi(klon_glo),lonfi(klon_glo),cufi(klon_glo),cvfi(klon_glo)) 91 124 ALLOCATE(airefi(klon_glo)) 125 ALLOCATE(boundslonfi(klon_glo,4)) 126 ALLOCATE(boundslatfi(klon_glo,4)) 92 127 93 128 IF (klon_glo>1) THEN ! general case 94 129 ! North pole 95 latfi(1)=rlatu(1) 96 lonfi(1)=0. 97 cufi(1) = cu(1) 98 cvfi(1) = cv(1) 130 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)=0 135 boundslatfi_glo(1,north_east)=PI/2 136 boundslonfi_glo(1,north_west)=2*PI 137 boundslatfi_glo(1,north_west)=PI/2 138 boundslonfi_glo(1,south_west)=2*PI 139 boundslatfi_glo(1,south_west)=rlatv(1) 140 boundslonfi_glo(1,south_east)=0 141 boundslatfi_glo(1,south_east)=rlatv(1) 99 142 DO j=2,jj 100 143 DO i=1,ii 101 latfi((j-2)*ii+1+i)= rlatu(j) 102 lonfi((j-2)*ii+1+i)= rlonv(i) 103 cufi((j-2)*ii+1+i) = cu((j-1)*ii+1+i) 104 cvfi((j-2)*ii+1+i) = cv((j-1)*ii+1+i) 144 k=(j-2)*ii+1+i 145 latfi_glo(k)= rlatu(j) 146 lonfi_glo(k)= rlonv(i) 147 cufi_glo(k) = cu((j-1)*ii+1+i) 148 cvfi_glo(k) = 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) 105 157 ENDDO 106 158 ENDDO 107 159 ! South pole 108 latfi(klon_glo)= rlatu(jj+1) 109 lonfi(klon_glo)= 0. 110 cufi(klon_glo) = cu((ii+1)*jj+1) 111 cvfi(klon_glo) = cv((ii+1)*jj-ii) 160 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)=0 165 boundslatfi_glo(klon_glo,north_east)=rlatv(jj) 166 boundslonfi_glo(klon_glo,north_west)=2*PI 167 boundslatfi_glo(klon_glo,north_west)=rlatv(jj) 168 boundslonfi_glo(klon_glo,south_west)=2*PI 169 boundslatfi_glo(klon_glo,south_west)=-PI/2 170 boundslonfi_glo(klon_glo,south_east)=rlonu(0) 171 boundslatfi_glo(klon_glo,south_east)=-Pi/2 112 172 113 173 ! build airefi(), mesh area on physics grid 114 CALL gr_dyn_fi(1,ii+1,jj+1,klon_glo,aire,airefi )174 CALL gr_dyn_fi(1,ii+1,jj+1,klon_glo,aire,airefi_glo) 115 175 ! Poles are single points on physics grid 116 airefi (1)=sum(aire(1:ii,1))117 airefi (klon_glo)=sum(aire(1:ii,jj+1))176 airefi_glo(1)=sum(aire(1:ii,1)) 177 airefi_glo(klon_glo)=sum(aire(1:ii,jj+1)) 118 178 119 179 ! Sanity check: do total planet area match between physics and dynamics? 120 180 total_area_dyn=sum(aire(1:ii,1:jj+1)) 121 total_area_phy=sum(airefi (1:klon_glo))181 total_area_phy=sum(airefi_glo(1:klon_glo)) 122 182 IF (total_area_dyn/=total_area_phy) THEN 123 183 WRITE (lunout, *) 'iniphysiq: planet total surface discrepancy !!!' … … 132 192 ELSE ! klon_glo==1, running the 1D model 133 193 ! just copy over input values 134 latfi(1)=rlatu(1) 135 lonfi(1)=rlonv(1) 136 cufi(1)=cu(1) 137 cvfi(1)=cv(1) 138 airefi(1)=aire(1,1) 194 latfi_glo(1)=rlatu(1) 195 lonfi_glo(1)=rlonv(1) 196 cufi_glo(1)=cu(1) 197 cvfi_glo(1)=cv(1) 198 airefi_glo(1)=aire(1,1) 199 boundslonfi_glo(1,north_east)=rlonu(1) 200 boundslatfi_glo(1,north_east)=PI/2 201 boundslonfi_glo(1,north_west)=rlonu(2) 202 boundslatfi_glo(1,north_west)=PI/2 203 boundslonfi_glo(1,south_west)=rlonu(2) 204 boundslatfi_glo(1,south_west)=rlatv(1) 205 boundslonfi_glo(1,south_east)=rlonu(1) 206 boundslatfi_glo(1,south_east)=rlatv(1) 139 207 ENDIF ! of IF (klon_glo>1) 140 208 141 209 !$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/) 142 210 ! Now generate local lon/lat/cu/cv/area arrays 143 CALL initcomgeomphy(klon_omp) 211 144 212 145 213 offset = klon_mpi_begin - 1 146 airephy(1:klon_omp) = airefi(offset+klon_omp_begin:offset+klon_omp_end) 147 cuphy(1:klon_omp) = cufi(offset+klon_omp_begin:offset+klon_omp_end) 148 cvphy(1:klon_omp) = cvfi(offset+klon_omp_begin:offset+klon_omp_end) 149 rlond(1:klon_omp) = lonfi(offset+klon_omp_begin:offset+klon_omp_end) 150 rlatd(1:klon_omp) = latfi(offset+klon_omp_begin:offset+klon_omp_end) 214 airefi(1:klon_omp) = airefi_glo(offset+klon_omp_begin:offset+klon_omp_end) 215 cufi(1:klon_omp) = cufi_glo(offset+klon_omp_begin:offset+klon_omp_end) 216 cvfi(1:klon_omp) = cvfi_glo(offset+klon_omp_begin:offset+klon_omp_end) 217 lonfi(1:klon_omp) = lonfi_glo(offset+klon_omp_begin:offset+klon_omp_end) 218 latfi(1:klon_omp) = latfi_glo(offset+klon_omp_begin:offset+klon_omp_end) 219 boundslonfi(1:klon_omp,:) = boundslonfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:) 220 boundslatfi(1:klon_omp,:) = boundslatfi_glo(offset+klon_omp_begin:offset+klon_omp_end,:) 151 221 152 222 ! copy over global grid longitudes and latitudes 153 CALL initcomgeomphy_horiz(iim,jjm,rlonu,rlonv,rlatu,rlatv) 223 CALL init_geometry(lonfi, latfi, boundslonfi, boundslatfi, airefi, cufi, cvfi) 224 154 225 155 226 ! copy over preff , ap(), bp(), etc 156 CALL initcomgeomphy_vert(nlayer,preff,ap,bp,presnivs,pseudoalt) 157 158 ! ! suphel => initialize some physical constants (orbital parameters, 159 ! ! geoid, gravity, thermodynamical constants, etc.) in the 160 ! ! physics 161 ! CALL suphel 227 CALL init_vertical_layers(nlayer,preff,ap,bp,presnivs,pseudoalt) 162 228 163 229 ! Initialize tracer names, numbers, etc. for physics … … 179 245 !!$OMP PARALLEL 180 246 IF (iflag_phys>=100) THEN 181 CALL iniaqua(klon_omp, rlatd, rlond,iflag_phys)247 CALL iniaqua(klon_omp, iflag_phys) 182 248 END IF 183 249 !$OMP END PARALLEL
Note: See TracChangeset
for help on using the changeset viewer.