source: trunk/LMDZ.MARS/libf/dynphy_lonlat/inigeomphy_mod.F90 @ 2322

Last change on this file since 2322 was 1682, checked in by emillour, 8 years ago

All GCMs: set things up to enable pluging physics with dynamico

  • dyn3d
  • gcm.F90 : move I/O initialization (dates) to be done before physics

initialization

  • dyn3dpar
  • gcm.F : move I/O initialization (dates) to be done before physics

initialization

  • dynphy_lonlat:
  • inigeomphy_mod.F90 : add ind_cell_glo computation and transfer

to init_geometry

  • phy_common:
  • geometry_mod.F90 : add ind_cell_glo module variable to store global

column index

  • print_control_mod.F90 : make initialization occur via init_print_control_mod

to avoid circular module dependencies

  • init_print_control_mod.F90 : added to initialize print_control_mod module

variables

  • mod_phys_lmdz_mpi_data.F90 : use print_control_mod (rather than iniprint.h)
  • mod_phys_lmdz_para.F90 : use print_control_mod (rather than iniprint.h)
  • mod_phys_lmdz_omp_data.F90 : add is_omp_master (alias of is_omp_root) module

variable and use print_control_mod (rather than
iniprint.h)

  • physics_distribution_mod.F90 : add call to init_dimphy in

init_physics_distribution

  • xios_writefield.F90 : generic routine to output field with XIOS (for debug)
  • misc:
  • handle_err_m.F90 : call abort_physic, rather than abort_gcm
  • wxios.F90 : updates to enable unstructured grids

set module variable g_ctx_name to "LMDZ"
wxios_init(): remove call to wxios_context_init
wxios_context_init(): call xios_context_initialize with COMM_LMDZ_PHY
add routine wxios_set_context() to get handle and set context to XIOS
wxios_domain_param(): change arguments and generate the domain in-place
add wxios_domain_param_unstructured(): generate domain for unstructured case

NB: access is via "domain group" (whereas it is via "domain" in

wxios_domain_param)

  • dynphy_lonlat/phy[std|mars|venus|titan]:
  • iniphysiq_mod.F90 : Remove call to init_dimphy (which is now done in

phy_common/physics_distribution_mod.F90)

EM

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