source: trunk/LMDZ.COMMON/libf/dynphy_lonlat/phytitan/iniphysiq_mod.F90 @ 1563

Last change on this file since 1563 was 1563, checked in by aslmd, 9 years ago

iniphysiq in all GCMs


iniphysiq was performing two main tasks

  • one that is planet-independent

i.e. setting the physics grid and geometry
(we checked: the lines of code
in phyxxx/iniphysiq_mod were doing
the exact same things)

  • one that is planet-dependent

i.e. time settings, planetary constants

now the planet-independent
initialization is done by inigeom_mod
which is in dynphy_lonlat

and the planet-dependent
initialization
is done in the respective phyxxx folders

this commit is intended
for interface lisibility
and modular approach
following the framework
adopted by Ehouarn
in the last commits

it paves the path for
a similar (and, now, easy)
counterpart for mesoscale
models

we adopted the sanity convention
ii and jj for dimensions
rlatudyn etc.. for grids
this is to avoid collision with
fields named iim or rlatu
possily defined elsewhere

compilation is OK
running is OK (checked for Mars)
outputs are exactly the same bit-by-bit

thx to Ehouarn and Maxence

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