source: LMDZ5/branches/IPSLCM5A2.1/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90 @ 3629

Last change on this file since 3629 was 3629, checked in by acozic, 4 years ago

Add new grid, new axis and new variables for cmip protocole and dr2xml

  • field_group id="coord_hyb"
  • grid_ref="klevp1_bnds"
  • grid_ref="klev_bnds"
  • domain id="greordered"
  • axis id="axis_lat"
  • axis id="bnds"
  • axis id="klevp1"
  • axis id="klev"
  • 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 3629 2020-02-10 08:54:26Z acozic $
[2347]3!
4MODULE iniphysiq_mod
[1671]5
[2347]6CONTAINS
[1671]7
[2351]8SUBROUTINE iniphysiq(ii,jj,nlayer, &
9                     nbp, communicator, &
10                     punjours, pdayref,ptimestep, &
[2346]11                     rlatu,rlatv,rlonu,rlonv,aire,cu,cv,       &
[2225]12                     prad,pg,pr,pcpp,iflag_phys)
[2351]13  USE dimphy, ONLY: init_dimphy
[3629]14  USE comvert_mod, ONLY: preff, ap, bp, aps, bps, presnivs, &
15                         scaleheight, pseudoalt
[2588]16  USE inigeomphy_mod, ONLY: inigeomphy
[2608]17  USE mod_grid_phy_lmdz, ONLY: nbp_lon,nbp_lat,nbp_lev,klon_glo ! number of atmospheric columns (on full grid)
[2588]18  USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid)
[2315]19  USE vertical_layers_mod, ONLY : init_vertical_layers
[2320]20  USE infotrac, ONLY: nqtot,nqo,nbtr,tname,ttext,type_trac,&
21                      niadv,conv_flg,pbl_flg,solsym,&
22                      nqfils,nqdesc,nqdesc_tot,iqfils,iqpere,&
23                      ok_isotopes,ok_iso_verif,ok_isotrac,&
24                      ok_init_iso,niso_possibles,tnat,&
25                      alpha_ideal,use_iso,iqiso,iso_num,&
26                      iso_indnum,zone_num,phase_num,&
27                      indnum_fn_num,index_trac,&
28                      niso,ntraceurs_zone,ntraciso
[2351]29#ifdef REPROBUS
30  USE CHEM_REP, ONLY : Init_chem_rep_phys
31#endif
[2609]32  USE control_mod, ONLY: dayref,anneeref,day_step,nday,offline, iphysiq, config_inca
[2311]33  USE inifis_mod, ONLY: inifis
[2343]34  USE time_phylmdz_mod, ONLY: init_time
[2610]35  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, start_time, calend
[2320]36  USE infotrac_phy, ONLY: init_infotrac_phy
[2343]37  USE phystokenc_mod, ONLY: init_phystokenc
[1992]38  USE phyaqua_mod, ONLY: iniaqua
[2372]39#ifdef INCA
40  USE indice_sol_mod, ONLY: nbsrf, is_oce, is_sic, is_ter, is_lic
[2457]41#ifdef CPP_PARA
42  USE parallel_lmdz, ONLY : mpi_size, mpi_rank
[2372]43  USE bands, ONLY : distrib_phys
[2457]44#endif
[2372]45  USE mod_phys_lmdz_omp_data, ONLY: klon_omp
46#endif
[1992]47  IMPLICIT NONE
[1671]48
[1992]49  ! =======================================================================
50  ! Initialisation of the physical constants and some positional and
51  ! geometrical arrays for the physics
52  ! =======================================================================
[1403]53
[2315]54  include "dimensions.h"
[1992]55  include "iniprint.h"
[2343]56  include "tracstoke.h"
[1992]57
58  REAL, INTENT (IN) :: prad ! radius of the planet (m)
59  REAL, INTENT (IN) :: pg ! gravitational acceleration (m/s2)
60  REAL, INTENT (IN) :: pr ! ! reduced gas constant R/mu
61  REAL, INTENT (IN) :: pcpp ! specific heat Cp
62  REAL, INTENT (IN) :: punjours ! length (in s) of a standard day
63  INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers
[2315]64  INTEGER, INTENT (IN) :: ii ! number of atmospheric columns along longitudes
65  INTEGER, INTENT (IN) :: jj ! number of atompsheric columns along latitudes
[2351]66  INTEGER, INTENT(IN) :: nbp ! number of physics columns for this MPI process
67  INTEGER, INTENT(IN) :: communicator ! MPI communicator
[2315]68  REAL, INTENT (IN) :: rlatu(jj+1) ! latitudes of the physics grid
[2346]69  REAL, INTENT (IN) :: rlatv(jj) ! latitude boundaries of the physics grid
[2315]70  REAL, INTENT (IN) :: rlonv(ii+1) ! longitudes of the physics grid
[2346]71  REAL, INTENT (IN) :: rlonu(ii+1) ! longitude boundaries of the physics grid
[2315]72  REAL, INTENT (IN) :: aire(ii+1,jj+1) ! area of the dynamics grid (m2)
73  REAL, INTENT (IN) :: cu((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u)
74  REAL, INTENT (IN) :: cv((ii+1)*jj) ! cv coeff. (v_covariant = cv * v)
[1992]75  INTEGER, INTENT (IN) :: pdayref ! reference day of for the simulation
76  REAL, INTENT (IN) :: ptimestep !physics time step (s)
77  INTEGER, INTENT (IN) :: iflag_phys ! type of physics to be called
78
79  INTEGER :: ibegin, iend, offset
[2351]80  INTEGER :: i,j,k
[1992]81  CHARACTER (LEN=20) :: modname = 'iniphysiq'
82  CHARACTER (LEN=80) :: abort_message
83
[2225]84
[2457]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
[2588]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               rlatu,rlatv, &
96               rlonu,rlonv, &
97               aire,cu,cv)
[2346]98
[2588]99  ! --> now initialize things specific to the phylmd physics package
[2351]100 
[2601]101!!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
102!$OMP PARALLEL DEFAULT(SHARED) &
103!       Copy all threadprivate variables in temps_mod
104!$OMP COPYIN(annee_ref, day_ini, day_ref, start_time)
[2351]105
[3629]106  ! copy over preff , ap(), bp(), etc
[2351]107  CALL init_vertical_layers(nlayer,preff,scaleheight, &
[3629]108                            ap,bp,aps,bps,presnivs,pseudoalt)
[2351]109
[2311]110  ! Initialize physical constants in physics:
111  CALL inifis(punjours,prad,pg,pr,pcpp)
[2351]112
[2343]113  CALL init_time(annee_ref,day_ref,day_ini,start_time,nday,ptimestep)
114
[2354]115  ! Initialize dimphy module (unless in 1D where it has already been done)
116  IF (klon_glo>1) CALL Init_dimphy(klon_omp,nlayer)
[2351]117
[2343]118  ! Copy over "offline" settings
119  CALL init_phystokenc(offline,istphy)
120
[2320]121  ! Initialize tracer names, numbers, etc. for physics
122  CALL init_infotrac_phy(nqtot,nqo,nbtr,tname,ttext,type_trac,&
123                         niadv,conv_flg,pbl_flg,solsym,&
124                         nqfils,nqdesc,nqdesc_tot,iqfils,iqpere,&
125                         ok_isotopes,ok_iso_verif,ok_isotrac,&
126                         ok_init_iso,niso_possibles,tnat,&
127                         alpha_ideal,use_iso,iqiso,iso_num,&
128                         iso_indnum,zone_num,phase_num,&
129                         indnum_fn_num,index_trac,&
130                         niso,ntraceurs_zone,ntraciso)
131
[2351]132  ! Initializations for Reprobus
133  IF (type_trac == 'repr') THEN
134#ifdef REPROBUS
135    CALL Init_chem_rep_phys(klon_omp,nlayer)
136#endif
137  ENDIF
[2372]138!$OMP END PARALLEL
[2225]139
[2372]140  IF (type_trac == 'inca') THEN
141#ifdef INCA
142     call init_const_lmdz( &
[2457]143          anneeref,dayref, iphysiq,day_step,nday,  &
[2609]144          nbsrf, is_oce,is_sic, is_ter,is_lic, calend, &
145          config_inca)
[2372]146     call init_inca_para( &
147          nbp_lon,nbp_lat,nbp_lev,klon_glo,mpi_size, &
[2457]148          distrib_phys,communicator)
[2372]149#endif
150  END IF
151
[2601]152!!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
153!$OMP PARALLEL DEFAULT(SHARED)
[2311]154  ! Additional initializations for aquaplanets
[1992]155  IF (iflag_phys>=100) THEN
[2351]156    CALL iniaqua(klon_omp,iflag_phys)
[1992]157  END IF
[2372]158
159  IF (type_trac == 'inca') THEN
160#ifdef INCA
161     CALL init_inca_dim(klon_omp,nbp_lev,nbp_lon,nbp_lat - 1, &
162          rlonu,rlatu,rlonv,rlatv)
163#endif
164  END IF
165
[2225]166!$OMP END PARALLEL
[1992]167
168END SUBROUTINE iniphysiq
[2347]169
170END MODULE iniphysiq_mod
Note: See TracBrowser for help on using the repository browser.