source: trunk/LMDZ.COMMON/libf/dynphy_lonlat/phyvenus/iniphysiq_mod.F90 @ 2236

Last change on this file since 2236 was 2135, checked in by slebonnois, 6 years ago

SL, Venus: new keys for flexibility cp0/cp(T) and Held-Suarez type physics

File size: 5.7 KB
Line 
1!
2! $Id: iniphysiq.F90 2225 2015-03-11 14:55:23Z 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, &
12                     airedyn,cudyn,cvdyn, &
13                     prad,pg,pr,pcpp,iflag_phys)
14
15  USE temps_mod, ONLY: annee_ref, day_ref, day_ini, day_end
16  USE comconst_mod, ONLY: nu_venus, t0_venus
17  USE cpdet_phy_mod, ONLY: init_cpdet_phy
18  USE infotrac, ONLY: nqtot, tname, ttext
19  USE logic_mod, ONLY: iflag_trac
20  USE infotrac_phy, ONLY: init_infotrac_phy
21  USE time_phylmdz_mod, ONLY: init_time
22  USE inigeomphy_mod, ONLY: inigeomphy
23  USE dimphy, ONLY: init_dimphy
24  USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid)
25  IMPLICIT NONE
26
27  ! =======================================================================
28  ! Initialisation of the physical constants and some positional and
29  ! geometrical arrays for the physics
30  ! =======================================================================
31
32  include "YOMCST.h"
33  include "iniprint.h"
34
35  REAL, INTENT (IN) :: prad ! radius of the planet (m)
36  REAL, INTENT (IN) :: pg ! gravitational acceleration (m/s2)
37  REAL, INTENT (IN) :: pr ! ! reduced gas constant R/mu
38  REAL, INTENT (IN) :: pcpp ! specific heat Cp
39  REAL, INTENT (IN) :: punjours ! length (in s) of a standard day
40  INTEGER, INTENT (IN) :: nlayer ! number of atmospheric layers
41  INTEGER, INTENT (IN) :: ii ! number of atmospheric columns along longitudes
42  INTEGER, INTENT (IN) :: jj ! number of atompsheric columns along latitudes
43  INTEGER, INTENT(IN) :: nbp ! number of physics columns for this MPI process
44  INTEGER, INTENT(IN) :: communicator ! MPI communicator
45  REAL, INTENT (IN) :: rlatudyn(jj+1) ! latitudes of the physics grid
46  REAL, INTENT (IN) :: rlatvdyn(jj) ! latitude boundaries of the physics grid
47  REAL, INTENT (IN) :: rlonvdyn(ii+1) ! longitudes of the physics grid
48  REAL, INTENT (IN) :: rlonudyn(ii+1) ! longitude boundaries of the physics grid
49  REAL, INTENT (IN) :: airedyn(ii+1,jj+1) ! area of the dynamics grid (m2)
50  REAL, INTENT (IN) :: cudyn((ii+1)*(jj+1)) ! cu coeff. (u_covariant = cu * u)
51  REAL, INTENT (IN) :: cvdyn((ii+1)*jj) ! cv coeff. (v_covariant = cv * v)
52  INTEGER, INTENT (IN) :: pdayref ! reference day of for the simulation
53  REAL, INTENT (IN) :: ptimestep !physics time step (s)
54  INTEGER, INTENT (IN) :: iflag_phys ! type of physics to be called
55
56  CHARACTER (LEN=20) :: modname = 'iniphysiq'
57  CHARACTER (LEN=80) :: abort_message
58
59  ! the common part for all planetary physics
60  !------------------------------------------
61  ! --> initialize physics distribution, global fields and geometry
62  ! (i.e. things in phy_common or dynphy_lonlat)
63  CALL inigeomphy(ii,jj,nlayer, &
64               nbp, communicator, &
65               rlatudyn,rlatvdyn, &
66               rlonudyn,rlonvdyn, &
67               airedyn,cudyn,cvdyn)
68
69  ! the distinct part for all planetary physics (ie. things in phyvenus)
70  !------------------------------------------
71
72!$OMP PARALLEL
73
74  ! Initialize dimphy module => Now done in physics_distribution_mod
75  !call init_dimphy(klon_omp,nlayer)
76
77  ! Initialize some physical constants
78  call suphec(pcpp)
79
80  ! Initialize cpdet_phy module
81  call init_cpdet_phy(pcpp,nu_venus,t0_venus)
82 
83  ! Initialize some "temporal and calendar" related variables
84  CALL init_time(annee_ref,day_ref,day_ini,day_end,ptimestep)
85 
86  ! Initialize tracers in physics
87  CALL init_infotrac_phy(iflag_trac,nqtot,tname,ttext)
88
89!$OMP END PARALLEL
90
91
92  ! check that physical constants set in 'suphec' are coherent
93  ! with values set in the dynamics:
94  IF (rday/=punjours) THEN
95    WRITE (lunout, *) 'iniphysiq: length of day discrepancy!!!'
96    WRITE (lunout, *) '  in the dynamics punjours=', punjours
97    WRITE (lunout, *) '   but in the physics RDAY=', rday
98    IF (abs(rday-punjours)>0.01*punjours) THEN
99        ! stop here if the relative difference is more than 1%
100      abort_message = 'length of day discrepancy'
101      CALL abort_gcm(modname, abort_message, 1)
102    END IF
103  END IF
104
105  IF (rg/=pg) THEN
106    WRITE (lunout, *) 'iniphysiq: gravity discrepancy !!!'
107    WRITE (lunout, *) '     in the dynamics pg=', pg
108    WRITE (lunout, *) '  but in the physics RG=', rg
109    IF (abs(rg-pg)>0.01*pg) THEN
110        ! stop here if the relative difference is more than 1%
111      abort_message = 'gravity discrepancy'
112      CALL abort_gcm(modname, abort_message, 1)
113    END IF
114  END IF
115  IF (ra/=prad) THEN
116    WRITE (lunout, *) 'iniphysiq: planet radius discrepancy !!!'
117    WRITE (lunout, *) '   in the dynamics prad=', prad
118    WRITE (lunout, *) '  but in the physics RA=', ra
119    IF (abs(ra-prad)>0.01*prad) THEN
120        ! stop here if the relative difference is more than 1%
121      abort_message = 'planet radius discrepancy'
122      CALL abort_gcm(modname, abort_message, 1)
123    END IF
124  END IF
125  IF (rd/=pr) THEN
126    WRITE (lunout, *) 'iniphysiq: reduced gas constant discrepancy !!!'
127    WRITE (lunout, *) '     in the dynamics pr=', pr
128    WRITE (lunout, *) '  but in the physics RD=', rd
129    IF (abs(rd-pr)>0.01*pr) THEN
130        ! stop here if the relative difference is more than 1%
131      abort_message = 'reduced gas constant discrepancy'
132      CALL abort_gcm(modname, abort_message, 1)
133    END IF
134  END IF
135  IF (rcpd/=pcpp) THEN
136    WRITE (lunout, *) 'iniphysiq: specific heat discrepancy !!!'
137    WRITE (lunout, *) '     in the dynamics pcpp=', pcpp
138    WRITE (lunout, *) '  but in the physics RCPD=', rcpd
139    IF (abs(rcpd-pcpp)>0.01*pcpp) THEN
140        ! stop here if the relative difference is more than 1%
141      abort_message = 'specific heat discrepancy'
142      CALL abort_gcm(modname, abort_message, 1)
143    END IF
144  END IF
145
146END SUBROUTINE iniphysiq
147
148END MODULE iniphysiq_mod
Note: See TracBrowser for help on using the repository browser.