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