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

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

Cleanup in the dynamics: get rid of comconst.h, make it a module comconst_mod.
EM

  • 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: 5.9 KB
Line 
1!
2! $Id: iniphysiq_mod.F90 2597 2016-07-22 06:44:47Z emillour $
3!
4MODULE iniphysiq_mod
5
6CONTAINS
7
8SUBROUTINE iniphysiq(ii,jj,nlayer, &
9                     nbp, communicator, &
10                     punjours, pdayref,ptimestep, &
11                     rlatu,rlatv,rlonu,rlonv,aire,cu,cv,       &
12                     prad,pg,pr,pcpp,iflag_phys)
13  USE dimphy, ONLY: init_dimphy
14  USE inigeomphy_mod, ONLY: inigeomphy
15  USE mod_grid_phy_lmdz, ONLY: klon_glo ! number of atmospheric columns (on full grid)
16  USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid)
17  USE vertical_layers_mod, ONLY : init_vertical_layers
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
27#ifdef REPROBUS
28  USE CHEM_REP, ONLY : Init_chem_rep_phys
29#endif
30  USE control_mod, ONLY: dayref,anneeref,day_step,nday,offline, iphysiq
31  USE inifis_mod, ONLY: inifis
32  USE time_phylmdz_mod, ONLY: init_time
33  USE infotrac_phy, ONLY: init_infotrac_phy
34  USE phystokenc_mod, ONLY: init_phystokenc
35  USE phyaqua_mod, ONLY: iniaqua
36#ifdef INCA
37  USE indice_sol_mod, ONLY: nbsrf, is_oce, is_sic, is_ter, is_lic
38#ifdef CPP_PARA
39  USE parallel_lmdz, ONLY : mpi_size, mpi_rank
40  USE bands, ONLY : distrib_phys
41#endif
42  USE mod_phys_lmdz_omp_data, ONLY: klon_omp
43#endif
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 "comvert.h"
53  include "iniprint.h"
54  include "temps.h"
55  include "tracstoke.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) :: rlatu(jj+1) ! latitudes of the physics grid
68  REAL, INTENT (IN) :: rlatv(jj) ! latitude boundaries of the physics grid
69  REAL, INTENT (IN) :: rlonv(ii+1) ! longitudes of the physics grid
70  REAL, INTENT (IN) :: rlonu(ii+1) ! longitude boundaries of the physics grid
71  REAL, INTENT (IN) :: aire(ii+1,jj+1) ! area of the dynamics grid (m2)
72  REAL, INTENT (IN) :: cu((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u)
73  REAL, INTENT (IN) :: cv((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
84#ifndef CPP_PARA
85  INTEGER,PARAMETER :: mpi_rank=0
86  INTEGER, PARAMETER :: mpi_size = 1
87  INTEGER :: distrib_phys(mpi_rank:mpi_rank)=(jjm-1)*iim+2
88#endif
89
90  ! --> initialize physics distribution, global fields and geometry
91  ! (i.e. things in phy_common or dynphy_lonlat)
92  CALL inigeomphy(ii,jj,nlayer, &
93               nbp, communicator, &
94               rlatu,rlatv, &
95               rlonu,rlonv, &
96               aire,cu,cv)
97
98  ! --> now initialize things specific to the phylmd physics package
99 
100!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
101
102  ! copy over preff , ap(), bp(), etc
103  CALL init_vertical_layers(nlayer,preff,scaleheight, &
104                            ap,bp,presnivs,pseudoalt)
105
106  ! Initialize physical constants in physics:
107  CALL inifis(punjours,prad,pg,pr,pcpp)
108
109  CALL init_time(annee_ref,day_ref,day_ini,start_time,nday,ptimestep)
110
111  ! Initialize dimphy module (unless in 1D where it has already been done)
112  IF (klon_glo>1) CALL Init_dimphy(klon_omp,nlayer)
113
114  ! Copy over "offline" settings
115  CALL init_phystokenc(offline,istphy)
116
117  ! Initialize tracer names, numbers, etc. for physics
118  CALL init_infotrac_phy(nqtot,nqo,nbtr,tname,ttext,type_trac,&
119                         niadv,conv_flg,pbl_flg,solsym,&
120                         nqfils,nqdesc,nqdesc_tot,iqfils,iqpere,&
121                         ok_isotopes,ok_iso_verif,ok_isotrac,&
122                         ok_init_iso,niso_possibles,tnat,&
123                         alpha_ideal,use_iso,iqiso,iso_num,&
124                         iso_indnum,zone_num,phase_num,&
125                         indnum_fn_num,index_trac,&
126                         niso,ntraceurs_zone,ntraciso)
127
128  ! Initializations for Reprobus
129  IF (type_trac == 'repr') THEN
130#ifdef REPROBUS
131    CALL Init_chem_rep_phys(klon_omp,nlayer)
132#endif
133  ENDIF
134!$OMP END PARALLEL
135
136  IF (type_trac == 'inca') THEN
137#ifdef INCA
138     call init_const_lmdz( &
139          anneeref,dayref, iphysiq,day_step,nday,  &
140          nbsrf, is_oce,is_sic, is_ter,is_lic, calend)
141     call init_inca_para( &
142          nbp_lon,nbp_lat,nbp_lev,klon_glo,mpi_size, &
143          distrib_phys,communicator)
144#endif
145  END IF
146!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
147
148  ! Additional initializations for aquaplanets
149  IF (iflag_phys>=100) THEN
150    CALL iniaqua(klon_omp,iflag_phys)
151  END IF
152
153  IF (type_trac == 'inca') THEN
154#ifdef INCA
155     CALL init_inca_dim(klon_omp,nbp_lev,nbp_lon,nbp_lat - 1, &
156          rlonu,rlatu,rlonv,rlatv)
157#endif
158  END IF
159
160!$OMP END PARALLEL
161
162END SUBROUTINE iniphysiq
163
164END MODULE iniphysiq_mod
Note: See TracBrowser for help on using the repository browser.