source: LMDZ6/trunk/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90 @ 4056

Last change on this file since 4056 was 4056, checked in by dcugnet, 2 years ago

Most of the changes are intended to help to eventually remove the constraints about the tracers assumptions, in particular water tracers.

  • Remove index tables itr_indice and niadv, replaced by tracers(:)%isAdvected and tracers(:)%isH2OFamily. Most of the loops are now from 1 to nqtot:
    • DO iq=nqo+1,nqtot loops are replaced with: DO iq=1,nqtot

IF(tracers(iq)%isH2Ofamily) CYCLE

  • DO it=1,nbtr; iq=niadv(it+nqo)

and DO it=1,nqtottr; iq=itr_indice(it) loops are replaced with:

it = 0
DO iq = 1, nqtot

IF(.NOT.tracers(iq)%isAdvected .OR. tracers(iq)%isH2Ofamily) CYCLE
it = it+1

  • Move some StratAer? related code from infotrac to infotrac_phy
  • Remove "nqperes" variable:

DO iq=1,nqpere loops are replaced with:
DO iq=1,nqtot

IF(tracers(iq)%parent/='air') CYCLE

  • Cosmetic changes (justification, SELECT CASE instead of multiple IF...) mostly in advtrac* routines.
  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 7.4 KB
Line 
1!
2! $Id: iniphysiq_mod.F90 4056 2022-01-12 21:54:09Z dcugnet $
3!
4MODULE iniphysiq_mod
5
6CONTAINS
7
8SUBROUTINE iniphysiq(ii,jj,nlayer, &
9                     nbp, communicator, &
10                     punjours, pdayref,ptimestep, &
11                     rlatudyn,rlatvdyn,rlonudyn,rlonvdyn,airedyn,cudyn,cvdyn, &
12                     prad,pg,pr,pcpp,iflag_phys)
13  USE dimphy, ONLY: init_dimphy
14  USE inigeomphy_mod, ONLY: inigeomphy
15  USE mod_grid_phy_lmdz, ONLY: nbp_lon,nbp_lat,nbp_lev,klon_glo ! number of atmospheric columns (on full grid)
16  USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid)
17  USE vertical_layers_mod, ONLY : init_vertical_layers
18  USE infotrac, ONLY: nqtot,nqo,nbtr,nqCO2,tracers,type_trac,&
19                      conv_flg,pbl_flg,solsym,&
20                      ok_isotopes,ok_iso_verif,ok_isotrac,&
21                      ok_init_iso,niso_possibles,tnat,&
22                      alpha_ideal,use_iso,iqiso,iso_indnum,&
23                      indnum_fn_num,index_trac,&
24                      niso,ntraceurs_zone,ntraciso,nqtottr
25#ifdef CPP_StratAer
26  USE infotrac_phy, ONLY: nbtr_bin, nbtr_sulgas, id_OCS_strat, &
27                      id_SO2_strat, id_H2SO4_strat, id_BIN01_strat
28
29#endif
30#ifdef REPROBUS
31  USE CHEM_REP, ONLY : Init_chem_rep_phys
32#ifdef CPP_PARA
33  USE parallel_lmdz, ONLY : mpi_size, mpi_rank
34  USE bands, ONLY : distrib_phys
35#endif
36  USE mod_phys_lmdz_omp_data, ONLY: klon_omp
37#endif
38  USE control_mod, ONLY: dayref,anneeref,day_step,nday,offline, iphysiq, config_inca
39  USE inifis_mod, ONLY: inifis
40  USE time_phylmdz_mod, ONLY: init_time
41  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, start_time, calend, year_len
42  USE infotrac_phy, ONLY: init_infotrac_phy
43  USE phystokenc_mod, ONLY: init_phystokenc
44  USE phyaqua_mod, ONLY: iniaqua
45  USE comconst_mod, ONLY: omeg, rad
46#ifdef INCA
47  USE indice_sol_mod, ONLY: nbsrf, is_oce, is_sic, is_ter, is_lic
48#ifdef CPP_PARA
49  USE parallel_lmdz, ONLY : mpi_size, mpi_rank
50  USE bands, ONLY : distrib_phys
51#endif
52  USE mod_phys_lmdz_omp_data, ONLY: klon_omp
53#endif
54  USE ioipsl_getin_p_mod, ONLY: getin_p
55  USE slab_heat_transp_mod, ONLY: ini_slab_transp_geom
56  IMPLICIT NONE
57
58  ! =======================================================================
59  ! Initialisation of the physical constants and some positional and
60  ! geometrical arrays for the physics
61  ! =======================================================================
62
63  include "dimensions.h"
64  include "paramet.h"
65  include "iniprint.h"
66  include "tracstoke.h"
67  include "comgeom.h"
68
69  REAL, INTENT (IN) :: prad ! radius of the planet (m)
70  REAL, INTENT (IN) :: pg ! gravitational acceleration (m/s2)
71  REAL, INTENT (IN) :: pr ! ! reduced gas constant R/mu
72  REAL, INTENT (IN) :: pcpp ! specific heat Cp
73  REAL, INTENT (IN) :: punjours ! length (in s) of a standard day
74  INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers
75  INTEGER, INTENT (IN) :: ii ! number of atmospheric columns along longitudes
76  INTEGER, INTENT (IN) :: jj ! number of atompsheric columns along latitudes
77  INTEGER, INTENT(IN) :: nbp ! number of physics columns for this MPI process
78  INTEGER, INTENT(IN) :: communicator ! MPI communicator
79  REAL, INTENT (IN) :: rlatudyn(jj+1) ! latitudes of the physics grid
80  REAL, INTENT (IN) :: rlatvdyn(jj) ! latitude boundaries of the physics grid
81  REAL, INTENT (IN) :: rlonvdyn(ii+1) ! longitudes of the physics grid
82  REAL, INTENT (IN) :: rlonudyn(ii+1) ! longitude boundaries of the physics grid
83  REAL, INTENT (IN) :: airedyn(ii+1,jj+1) ! area of the dynamics grid (m2)
84  REAL, INTENT (IN) :: cudyn((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u)
85  REAL, INTENT (IN) :: cvdyn((ii+1)*jj) ! cv coeff. (v_covariant = cv * v)
86  INTEGER, INTENT (IN) :: pdayref ! reference day of for the simulation
87  REAL, INTENT (IN) :: ptimestep !physics time step (s)
88  INTEGER, INTENT (IN) :: iflag_phys ! type of physics to be called
89
90  INTEGER :: ibegin, iend, offset
91  INTEGER :: i,j,k
92  CHARACTER (LEN=20) :: modname = 'iniphysiq'
93  CHARACTER (LEN=80) :: abort_message
94 
95  LOGICAL :: slab_hdiff
96  INTEGER :: slab_ekman
97  CHARACTER (LEN = 6) :: type_ocean
98
99#ifndef CPP_PARA
100  INTEGER,PARAMETER :: mpi_rank=0
101  INTEGER, PARAMETER :: mpi_size = 1
102  INTEGER :: distrib_phys(mpi_rank:mpi_rank)=(jjm-1)*iim+2
103#endif
104
105  ! --> initialize physics distribution, global fields and geometry
106  ! (i.e. things in phy_common or dynphy_lonlat)
107  CALL inigeomphy(ii,jj,nlayer, &
108               nbp, communicator, &
109               rlatudyn,rlatvdyn, &
110               rlonudyn,rlonvdyn, &
111               airedyn,cudyn,cvdyn)
112
113  ! --> now initialize things specific to the phylmd physics package
114 
115!!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
116!$OMP PARALLEL DEFAULT(SHARED) &
117!       Copy all threadprivate variables in temps_mod
118!$OMP COPYIN(annee_ref, day_ini, day_ref, start_time)
119
120  ! Initialize physical constants in physics:
121  CALL inifis(punjours,prad,pg,pr,pcpp)
122
123  CALL init_time(annee_ref,day_ref,day_ini,start_time,nday,ptimestep)
124
125  ! Initialize dimphy module (unless in 1D where it has already been done)
126!  IF (klon_glo>1) CALL Init_dimphy(klon_omp,nlayer)
127
128  ! Copy over "offline" settings
129  CALL init_phystokenc(offline,istphy)
130
131  ! Initialization for slab heat transport
132  type_ocean="force"
133  CALL getin_p('type_ocean',type_ocean)
134  slab_hdiff=.FALSE.
135  CALL getin_p('slab_hdiff',slab_hdiff)
136  slab_ekman=0
137  CALL getin_p('slab_ekman',slab_ekman)
138  IF ((type_ocean=='slab').AND.(slab_hdiff.OR.(slab_ekman.GT.0))) THEN
139     CALL ini_slab_transp_geom(ip1jm,ip1jmp1,unsairez,fext,unsaire,&
140                                  cu,cuvsurcv,cv,cvusurcu, &
141                                  aire,apoln,apols, &
142                                  aireu,airev,rlatvdyn,rad,omeg)
143  END IF
144
145  ! Initialize tracer names, numbers, etc. for physics
146  CALL init_infotrac_phy(nqtot,nqo,nbtr,nqtottr,nqCO2,tracers,type_trac,&
147                         conv_flg,pbl_flg,solsym,&
148                         ok_isotopes,ok_iso_verif,ok_isotrac,&
149                         ok_init_iso,niso_possibles,tnat,&
150                         alpha_ideal,use_iso,iqiso,iso_indnum,&
151                         indnum_fn_num,index_trac,&
152                         niso,ntraceurs_zone,ntraciso)
153
154  ! Initializations for Reprobus
155  IF (type_trac == 'repr') THEN
156#ifdef REPROBUS
157    call Init_chem_rep_phys(klon_omp,nlayer)
158    call init_reprobus_para( &
159          nbp_lon,nbp_lat,nbp_lev,klon_glo,mpi_size, &
160          distrib_phys,communicator)
161#endif
162  ENDIF
163!$OMP END PARALLEL
164
165  IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN
166#ifdef INCA
167     call init_const_lmdz( &
168          anneeref,dayref, iphysiq,day_step,nday,  &
169          nbsrf, is_oce,is_sic, is_ter,is_lic, calend, &
170          config_inca)
171     call init_inca_para( &
172          nbp_lon,nbp_lat,nbp_lev,klon_glo,mpi_size, &
173          distrib_phys,communicator)
174#endif
175  END IF
176  IF (type_trac == 'repr') THEN
177#ifdef REPROBUS
178    call init_reprobus_para( &
179          nbp_lon,nbp_lat,nbp_lev,klon_glo,mpi_size, &
180          distrib_phys,communicator)
181#endif
182  ENDIF
183
184!!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
185!$OMP PARALLEL DEFAULT(SHARED)
186  ! Additional initializations for aquaplanets
187  IF (iflag_phys>=100) THEN
188    CALL iniaqua(klon_omp,year_len,iflag_phys)
189  END IF
190
191  IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN
192#ifdef INCA
193     CALL init_inca_dim(klon_omp,nbp_lev,nbp_lon,nbp_lat - 1, &
194          rlonudyn,rlatudyn,rlonvdyn,rlatvdyn)
195#endif
196  END IF
197  IF (type_trac == 'repr') THEN
198#ifdef REPROBUS
199     CALL Init_chem_rep_phys(klon_omp,nbp_lev)
200#endif
201  END IF
202
203!$OMP END PARALLEL
204
205END SUBROUTINE iniphysiq
206
207END MODULE iniphysiq_mod
Note: See TracBrowser for help on using the repository browser.