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

Last change on this file since 1564 was 1564, checked in by emillour, 9 years ago

All GCMS:

  • correction wrt previous commit: inigeom is also the name of a routine

in dyn3d_common! To avoid confusion rename inigeom (in dynphy_lonlat)
inigeomphy.

  • cosmetic cleanup in leapfrog ('fake' calls to init_phys_lmdz,

which no longer exists, removed).
EM

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