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

Last change on this file since 5359 was 5323, checked in by abarral, 5 weeks ago

[WIP] add missing reprobus & inca wrappers

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