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

Last change on this file since 5927 was 5927, checked in by Sebastien Nguyen, 3 weeks ago

Changes to compile LMDZ-OR-ISO and wrtie output variables Rsol isotopes soil ratio) xtevap xtcoastal xtrivflu. Changes from CA and ND to write output variables xtprw (precipitatble water) uxt and vxt (meridional and zonal advected humidity) Rlandice and xtsnow.

  • 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: 6.3 KB
Line 
1!
2! $Id: iniphysiq_mod.F90 5927 2025-12-12 16:26:10Z snguyen $
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: nbtr, type_trac
19  USE infotrac_phy, ONLY: nbtr_bin, nbtr_sulgas, id_OCS_strat, &
20                      id_SO2_strat, id_H2SO4_strat, id_BIN01_strat
21  USE lmdz_reprobus_wrappers, ONLY : init_chem_rep_phys, init_reprobus_para
22#ifdef CPP_PARA
23  USE parallel_lmdz, ONLY : mpi_size, mpi_rank
24  USE bands, ONLY : distrib_phys
25#endif
26  USE mod_phys_lmdz_omp_data, ONLY: klon_omp
27  USE control_mod, ONLY: dayref,anneeref,day_step,nday,offline, iphysiq
28  USE inifis_mod, ONLY: inifis
29  USE time_phylmdz_mod, ONLY: init_time
30  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, start_time, calend, year_len
31  USE infotrac_phy, ONLY: init_infotrac_phy
32  USE phystokenc_mod, ONLY: init_phystokenc
33  USE phyaqua_mod, ONLY: iniaqua
34  USE comconst_mod, ONLY: omeg, rad
35  USE indice_sol_mod, ONLY: nbsrf, is_oce, is_sic, is_ter, is_lic
36#ifdef CPP_PARA
37  USE parallel_lmdz, ONLY : mpi_size, mpi_rank
38  USE bands, ONLY : distrib_phys
39#endif
40  USE tracstoke_mod_h
41  USE iniprint_mod_h
42  USE comgeom_mod_h
43  USE mod_phys_lmdz_omp_data, ONLY: klon_omp
44  USE ioipsl_getin_p_mod, ONLY: getin_p
45  USE slab_heat_transp_mod, ONLY: ini_slab_transp_geom
46  USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA, CPPKEY_REPROBUS
47  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
48  USE paramet_mod_h
49
50  IMPLICIT NONE
51
52  ! =======================================================================
53  ! Initialisation of the physical constants and some positional and
54  ! geometrical arrays for the physics
55  ! =======================================================================
56
57
58
59
60  REAL, INTENT (IN) :: prad ! radius of the planet (m)
61  REAL, INTENT (IN) :: pg ! gravitational acceleration (m/s2)
62  REAL, INTENT (IN) :: pr ! ! reduced gas constant R/mu
63  REAL, INTENT (IN) :: pcpp ! specific heat Cp
64  REAL, INTENT (IN) :: punjours ! length (in s) of a standard day
65  INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers
66  INTEGER, INTENT (IN) :: ii ! number of atmospheric columns along longitudes
67  INTEGER, INTENT (IN) :: jj ! number of atompsheric columns along latitudes
68  INTEGER, INTENT(IN) :: nbp ! number of physics columns for this MPI process
69  INTEGER, INTENT(IN) :: communicator ! MPI communicator
70  REAL, INTENT (IN) :: rlatudyn(jj+1) ! latitudes of the physics grid
71  REAL, INTENT (IN) :: rlatvdyn(jj) ! latitude boundaries of the physics grid
72  REAL, INTENT (IN) :: rlonvdyn(ii+1) ! longitudes of the physics grid
73  REAL, INTENT (IN) :: rlonudyn(ii+1) ! longitude boundaries of the physics grid
74  REAL, INTENT (IN) :: airedyn(ii+1,jj+1) ! area of the dynamics grid (m2)
75  REAL, INTENT (IN) :: cudyn((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u)
76  REAL, INTENT (IN) :: cvdyn((ii+1)*jj) ! cv coeff. (v_covariant = cv * v)
77  INTEGER, INTENT (IN) :: pdayref ! reference day of for the simulation
78  REAL, INTENT (IN) :: ptimestep !physics time step (s)
79  INTEGER, INTENT (IN) :: iflag_phys ! type of physics to be called
80
81  INTEGER :: ibegin, iend, offset
82  INTEGER :: i,j,k
83  CHARACTER (LEN=20) :: modname = 'iniphysiq'
84  CHARACTER (LEN=80) :: abort_message
85 
86  LOGICAL :: slab_hdiff
87  INTEGER :: slab_ekman
88  CHARACTER (LEN = 6) :: type_ocean
89
90#ifndef CPP_PARA
91  INTEGER,PARAMETER :: mpi_rank=0
92  INTEGER, PARAMETER :: mpi_size = 1
93  INTEGER :: distrib_phys(mpi_rank:mpi_rank)=(jjm-1)*iim+2
94#endif
95
96  ! --> initialize physics distribution, global fields and geometry
97  ! (i.e. things in phy_common or dynphy_lonlat)
98  CALL inigeomphy(ii,jj,nlayer, &
99               nbp, communicator, &
100               rlatudyn,rlatvdyn, &
101               rlonudyn,rlonvdyn, &
102               airedyn,cudyn,cvdyn)
103
104  ! --> now initialize things specific to the phylmd physics package
105 
106!!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
107!       Copy all threadprivate variables in temps_mod
108!$OMP PARALLEL DEFAULT(SHARED) COPYIN(annee_ref,day_ini,day_ref,start_time)
109
110  ! Initialize physical constants in physics:
111  CALL inifis(punjours,prad,pg,pr,pcpp)
112
113  CALL init_time(annee_ref,day_ref,day_ini,start_time,nday,ptimestep)
114
115  ! Initialize dimphy module (unless in 1D where it has already been done)
116!  IF (klon_glo>1) CALL Init_dimphy(klon_omp,nlayer)
117
118  ! Copy over "offline" settings
119  CALL init_phystokenc(offline,istphy)
120
121  ! Initialization for slab heat transport
122  type_ocean="force"
123  CALL getin_p('type_ocean',type_ocean)
124  slab_hdiff=.FALSE.
125  CALL getin_p('slab_hdiff',slab_hdiff)
126  slab_ekman=0
127  CALL getin_p('slab_ekman',slab_ekman)
128  IF ((type_ocean=='slab').AND.(slab_hdiff.OR.(slab_ekman.GT.0))) THEN
129     CALL ini_slab_transp_geom(ip1jm,ip1jmp1,unsairez,fext,unsaire,&
130                                  cu,cuvsurcv,cv,cvusurcu, &
131                                  aire,apoln,apols, &
132                                  aireu,airev,rlatvdyn,rad,omeg)
133  END IF
134
135  ! Initialize tracer names, numbers, etc. for physics
136  CALL init_infotrac_phy
137
138  ! Initializations for Reprobus
139  IF (type_trac == 'repr') THEN
140IF (CPPKEY_REPROBUS) THEN
141    call Init_chem_rep_phys(klon_omp,nlayer)
142    call init_reprobus_para( &
143          nbp_lon,nbp_lat,nbp_lev,klon_glo,mpi_size, &
144          distrib_phys,communicator)
145END IF
146  ENDIF
147!$OMP END PARALLEL
148
149
150  IF (type_trac == 'repr') THEN
151IF (CPPKEY_REPROBUS) THEN
152    call init_reprobus_para( &
153          nbp_lon,nbp_lat,nbp_lev,klon_glo,mpi_size, &
154          distrib_phys,communicator)
155END IF
156  ENDIF
157
158!!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
159!$OMP PARALLEL DEFAULT(SHARED)
160  ! Additional initializations for aquaplanets
161  IF (iflag_phys>=100) THEN
162    CALL iniaqua(klon_omp,year_len,iflag_phys)
163  END IF
164
165  IF (ANY(type_trac == ['inca','inco'])) THEN
166IF (CPPKEY_INCA) THEN
167     CALL init_inca_dim_reg(nbp_lon, nbp_lat - 1, &
168          rlonudyn, rlatudyn, rlonvdyn, rlatvdyn)
169END IF
170  END IF
171
172!$OMP END PARALLEL
173
174END SUBROUTINE iniphysiq
175
176END MODULE iniphysiq_mod
Note: See TracBrowser for help on using the repository browser.