source: LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/inigeomphy_mod.F90 @ 5134

Last change on this file since 5134 was 5118, checked in by abarral, 2 months ago

Replace iniprint.h by lmdz_iniprint.f90
(lint) along the way

File size: 10.1 KB
Line 
1! $Id: $
2
3MODULE inigeomphy_mod
4
5CONTAINS
6
7  SUBROUTINE inigeomphy(iim, jjm, nlayer, &
8          nbp, communicator, &
9          rlatu, rlatv, rlonu, rlonv, aire, cu, cv)
10    USE lmdz_grid_phy, ONLY: klon_glo, & ! number of atmospheric columns (on full grid)
11            regular_lonlat, &  ! regular longitude-latitude grid type
12            nbp_lon, nbp_lat, nbp_lev
13    USE lmdz_phys_para, ONLY: klon_omp, & ! number of columns (on local omp grid)
14            klon_omp_begin, & ! start index of local omp subgrid
15            klon_omp_end, & ! end index of local omp subgrid
16            klon_mpi_begin ! start indes of columns (on local mpi grid)
17    USE lmdz_geometry, ONLY: init_geometry
18    USE lmdz_physics_distribution, ONLY: init_physics_distribution
19    USE lmdz_regular_lonlat, ONLY: init_regular_lonlat, &
20            east, west, north, south, &
21            north_east, north_west, &
22            south_west, south_east
23    USE mod_interface_dyn_phys, ONLY: init_interface_dyn_phys
24    USE lmdz_physical_constants, ONLY: pi
25    USE comvert_mod, ONLY: preff, ap, bp, aps, bps, presnivs, &
26            scaleheight, pseudoalt, presinter
27    USE lmdz_vertical_layers, ONLY: init_vertical_layers
28    USE lmdz_iniprint, ONLY: lunout, prt_level
29    IMPLICIT NONE
30
31    ! =======================================================================
32    ! Initialisation of the physical constants and some positional and
33    ! geometrical arrays for the physics
34    ! =======================================================================
35
36    INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers
37    INTEGER, INTENT (IN) :: iim ! number of atmospheric columns along longitudes
38    INTEGER, INTENT (IN) :: jjm ! number of atompsheric columns along latitudes
39    INTEGER, INTENT(IN) :: nbp ! number of physics columns for this MPI process
40    INTEGER, INTENT(IN) :: communicator ! MPI communicator
41    REAL, INTENT (IN) :: rlatu(jjm + 1) ! latitudes of the physics grid
42    REAL, INTENT (IN) :: rlatv(jjm) ! latitude boundaries of the physics grid
43    REAL, INTENT (IN) :: rlonv(iim + 1) ! longitudes of the physics grid
44    REAL, INTENT (IN) :: rlonu(iim + 1) ! longitude boundaries of the physics grid
45    REAL, INTENT (IN) :: aire(iim + 1, jjm + 1) ! area of the dynamics grid (m2)
46    REAL, INTENT (IN) :: cu((iim + 1) * (jjm + 1)) ! cu coeff. (u_covariant = cu * u)
47    REAL, INTENT (IN) :: cv((iim + 1) * jjm) ! cv coeff. (v_covariant = cv * v)
48
49    INTEGER :: ibegin, iend, offset
50    INTEGER :: i, j, k
51    CHARACTER (LEN = 20) :: modname = 'inigeomphy'
52    CHARACTER (LEN = 80) :: abort_message
53    REAL :: total_area_phy, total_area_dyn
54
55    ! boundaries, on global grid
56    REAL, ALLOCATABLE :: boundslon_reg(:, :)
57    REAL, ALLOCATABLE :: boundslat_reg(:, :)
58
59    ! global array, on full physics grid:
60    REAL, ALLOCATABLE :: latfi_glo(:)
61    REAL, ALLOCATABLE :: lonfi_glo(:)
62    REAL, ALLOCATABLE :: cufi_glo(:)
63    REAL, ALLOCATABLE :: cvfi_glo(:)
64    REAL, ALLOCATABLE :: airefi_glo(:)
65    REAL, ALLOCATABLE :: boundslonfi_glo(:, :)
66    REAL, ALLOCATABLE :: boundslatfi_glo(:, :)
67
68    ! local arrays, on given MPI/OpenMP domain:
69    REAL, ALLOCATABLE, SAVE :: latfi(:)
70    REAL, ALLOCATABLE, SAVE :: lonfi(:)
71    REAL, ALLOCATABLE, SAVE :: cufi(:)
72    REAL, ALLOCATABLE, SAVE :: cvfi(:)
73    REAL, ALLOCATABLE, SAVE :: airefi(:)
74    REAL, ALLOCATABLE, SAVE :: boundslonfi(:, :)
75    REAL, ALLOCATABLE, SAVE :: boundslatfi(:, :)
76    INTEGER, ALLOCATABLE, SAVE :: ind_cell_glo_fi(:)
77    !$OMP THREADPRIVATE (latfi,lonfi,cufi,cvfi,airefi,boundslonfi,boundslatfi,ind_cell_glo_fi)
78
79    ! Initialize Physics distibution and parameters and interface with dynamics
80    IF (iim * jjm>1) THEN ! general 3D case
81      CALL init_physics_distribution(regular_lonlat, 4, &
82              nbp, iim, jjm + 1, nlayer, communicator)
83    ELSE ! For 1D model
84      CALL init_physics_distribution(regular_lonlat, 4, &
85              1, 1, 1, nlayer, communicator)
86    ENDIF
87    CALL init_interface_dyn_phys
88
89    ! init regular global longitude-latitude grid points and boundaries
90    ALLOCATE(boundslon_reg(iim, 2))
91    ALLOCATE(boundslat_reg(jjm + 1, 2))
92
93    ! specific handling of the -180 longitude scalar grid point boundaries
94    boundslon_reg(1, east) = rlonu(1)
95    boundslon_reg(1, west) = rlonu(iim) - 2 * PI
96    DO i = 2, iim
97      boundslon_reg(i, east) = rlonu(i)
98      boundslon_reg(i, west) = rlonu(i - 1)
99    ENDDO
100
101    boundslat_reg(1, north) = PI / 2
102    boundslat_reg(1, south) = rlatv(1)
103    DO j = 2, jjm
104      boundslat_reg(j, north) = rlatv(j - 1)
105      boundslat_reg(j, south) = rlatv(j)
106    ENDDO
107    boundslat_reg(jjm + 1, north) = rlatv(jjm)
108    boundslat_reg(jjm + 1, south) = -PI / 2
109
110    ! Write values in module lmdz_regular_lonlat
111    CALL init_regular_lonlat(iim, jjm + 1, rlonv(1:iim), rlatu, &
112            boundslon_reg, boundslat_reg)
113
114    ! Generate global arrays on full physics grid
115    ALLOCATE(latfi_glo(klon_glo), lonfi_glo(klon_glo))
116    ALLOCATE(cufi_glo(klon_glo), cvfi_glo(klon_glo))
117    ALLOCATE(airefi_glo(klon_glo))
118    ALLOCATE(boundslonfi_glo(klon_glo, 4))
119    ALLOCATE(boundslatfi_glo(klon_glo, 4))
120
121    IF (klon_glo>1) THEN ! general case
122      ! North pole
123      latfi_glo(1) = rlatu(1)
124      lonfi_glo(1) = 0.
125      cufi_glo(1) = cu(1)
126      cvfi_glo(1) = cv(1)
127      boundslonfi_glo(1, north_east) = PI
128      boundslatfi_glo(1, north_east) = PI / 2
129      boundslonfi_glo(1, north_west) = -PI
130      boundslatfi_glo(1, north_west) = PI / 2
131      boundslonfi_glo(1, south_west) = -PI
132      boundslatfi_glo(1, south_west) = rlatv(1)
133      boundslonfi_glo(1, south_east) = PI
134      boundslatfi_glo(1, south_east) = rlatv(1)
135      DO j = 2, jjm
136        DO i = 1, iim
137          k = (j - 2) * iim + 1 + i
138          latfi_glo(k) = rlatu(j)
139          lonfi_glo(k) = rlonv(i)
140          cufi_glo(k) = cu((j - 1) * (iim + 1) + i)
141          cvfi_glo(k) = cv((j - 1) * (iim + 1) + i)
142          boundslonfi_glo(k, north_east) = rlonu(i)
143          boundslatfi_glo(k, north_east) = rlatv(j - 1)
144          IF (i==1) THEN
145            ! special case for the first longitude's west bound
146            boundslonfi_glo(k, north_west) = rlonu(iim) - 2 * PI
147            boundslonfi_glo(k, south_west) = rlonu(iim) - 2 * PI
148          else
149            boundslonfi_glo(k, north_west) = rlonu(i - 1)
150            boundslonfi_glo(k, south_west) = rlonu(i - 1)
151          endif
152          boundslatfi_glo(k, north_west) = rlatv(j - 1)
153          boundslatfi_glo(k, south_west) = rlatv(j)
154          boundslonfi_glo(k, south_east) = rlonu(i)
155          boundslatfi_glo(k, south_east) = rlatv(j)
156        ENDDO
157      ENDDO
158      ! South pole
159      latfi_glo(klon_glo) = rlatu(jjm + 1)
160      lonfi_glo(klon_glo) = 0.
161      cufi_glo(klon_glo) = cu((iim + 1) * jjm + 1)
162      cvfi_glo(klon_glo) = cv((iim + 1) * jjm - iim)
163      boundslonfi_glo(klon_glo, north_east) = PI
164      boundslatfi_glo(klon_glo, north_east) = rlatv(jjm)
165      boundslonfi_glo(klon_glo, north_west) = -PI
166      boundslatfi_glo(klon_glo, north_west) = rlatv(jjm)
167      boundslonfi_glo(klon_glo, south_west) = -PI
168      boundslatfi_glo(klon_glo, south_west) = -PI / 2
169      boundslonfi_glo(klon_glo, south_east) = PI
170      boundslatfi_glo(klon_glo, south_east) = -Pi / 2
171
172      ! build airefi(), mesh area on physics grid
173      CALL gr_dyn_fi(1, iim + 1, jjm + 1, klon_glo, aire, airefi_glo)
174      ! Poles are single points on physics grid
175      airefi_glo(1) = sum(aire(1:iim, 1))
176      airefi_glo(klon_glo) = sum(aire(1:iim, jjm + 1))
177
178      ! Sanity check: do total planet area match between physics and dynamics?
179      total_area_dyn = sum(aire(1:iim, 1:jjm + 1))
180      total_area_phy = sum(airefi_glo(1:klon_glo))
181      IF (total_area_dyn/=total_area_phy) THEN
182        WRITE (lunout, *) 'inigeomphy: planet total surface discrepancy !!!'
183        WRITE (lunout, *) '     in the dynamics total_area_dyn=', total_area_dyn
184        WRITE (lunout, *) '  but in the physics total_area_phy=', total_area_phy
185        IF (abs(total_area_dyn - total_area_phy)>0.00001 * total_area_dyn) THEN
186          ! stop here if the relative difference is more than 0.001%
187          abort_message = 'planet total surface discrepancy'
188          CALL abort_gcm(modname, abort_message, 1)
189        ENDIF
190      ENDIF
191    ELSE ! klon_glo==1, running the 1D model
192      ! just copy over input values
193      latfi_glo(1) = rlatu(1)
194      lonfi_glo(1) = rlonv(1)
195      cufi_glo(1) = cu(1)
196      cvfi_glo(1) = cv(1)
197      airefi_glo(1) = aire(1, 1)
198      boundslonfi_glo(1, north_east) = rlonu(1)
199      boundslatfi_glo(1, north_east) = PI / 2
200      boundslonfi_glo(1, north_west) = rlonu(2)
201      boundslatfi_glo(1, north_west) = PI / 2
202      boundslonfi_glo(1, south_west) = rlonu(2)
203      boundslatfi_glo(1, south_west) = rlatv(1)
204      boundslonfi_glo(1, south_east) = rlonu(1)
205      boundslatfi_glo(1, south_east) = rlatv(1)
206    ENDIF ! of IF (klon_glo>1)
207
208    !$OMP PARALLEL
209    ! Now generate local lon/lat/cu/cv/area/bounds arrays
210    ALLOCATE(latfi(klon_omp), lonfi(klon_omp), cufi(klon_omp), cvfi(klon_omp))
211    ALLOCATE(airefi(klon_omp))
212    ALLOCATE(boundslonfi(klon_omp, 4))
213    ALLOCATE(boundslatfi(klon_omp, 4))
214    ALLOCATE(ind_cell_glo_fi(klon_omp))
215
216    offset = klon_mpi_begin - 1
217    airefi(1:klon_omp) = airefi_glo(offset + klon_omp_begin:offset + klon_omp_end)
218    cufi(1:klon_omp) = cufi_glo(offset + klon_omp_begin:offset + klon_omp_end)
219    cvfi(1:klon_omp) = cvfi_glo(offset + klon_omp_begin:offset + klon_omp_end)
220    lonfi(1:klon_omp) = lonfi_glo(offset + klon_omp_begin:offset + klon_omp_end)
221    latfi(1:klon_omp) = latfi_glo(offset + klon_omp_begin:offset + klon_omp_end)
222    boundslonfi(1:klon_omp, :) = boundslonfi_glo(offset + klon_omp_begin:offset + klon_omp_end, :)
223    boundslatfi(1:klon_omp, :) = boundslatfi_glo(offset + klon_omp_begin:offset + klon_omp_end, :)
224    ind_cell_glo_fi(1:klon_omp) = (/ (i, i = offset + klon_omp_begin, offset + klon_omp_end) /)
225
226    ! copy over local grid longitudes and latitudes
227    CALL init_geometry(klon_omp, lonfi, latfi, boundslonfi, boundslatfi, &
228            airefi, ind_cell_glo_fi, cufi, cvfi)
229
230    ! copy over preff , ap(), bp(), etc
231    CALL init_vertical_layers(nlayer, preff, scaleheight, &
232            ap, bp, aps, bps, presnivs, presinter, pseudoalt)
233
234    !$OMP END PARALLEL
235
236  END SUBROUTINE inigeomphy
237
238END MODULE inigeomphy_mod
239
Note: See TracBrowser for help on using the repository browser.