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

Last change on this file since 3600 was 3579, checked in by Laurent Fairhead, 5 years ago

Make aquaplanets run again (on jean-zay)
EM & MP

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