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

Last change on this file since 1573 was 1573, checked in by emillour, 8 years ago

All GCMS:
Cleanup concerning iniphysiq/inigeomphy initializations: initializations
related to routines in phy_common or dynphy_lonlat can be done in
inigeomphy, but any initialization for modules/routines in a physics
package (directory phy*) must be done in the related phy*/iniphysiq
routine.
EM

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