source: LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90 @ 5186

Last change on this file since 5186 was 5185, checked in by abarral, 9 days ago

Replace REPROBUS CPP KEY by logical using handmade wonky wrapper

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