source: LMDZ5/trunk/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90 @ 2656

Last change on this file since 2656 was 2656, checked in by Ehouarn Millour, 8 years ago

Making the slab work:

  • added a slab_heat_transp_mod module for horizontal diffusion and Ekman transport
  • added storage and output of relevent variables in phyredem, phyetat0, phy_output_ctrlout_mod, phys_output_write_mod
  • moved nslay (number of slab layers) out of dimphy into ocean_slab_mod.

FC

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