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

Last change on this file since 5111 was 5110, checked in by abarral, 2 months ago

Rename modules properly (mod_* -> lmdz_*) in phy_common

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