source: trunk/LMDZ.MARS/libf/dynphy_lonlat/phymars/callphysiq_mod.F90 @ 1564

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

All GCMs:
Further adaptations to keep up with changes in LMDZ5 concerning
physics/dynamics separation (up to rev r2420 of LMDZ5)

  • all physics packages:
  • added module callphysiq_mod.F90 in dynphy_lonlat/phy* which contains the routine "call_physiq" which is called by calfis* and calls the physics. This way different "physiq" routine from different physics packages may be called: The calfis* routines now exposes all available fields that might be transmitted to physiq but which is actually send (ie: expected/needed by physiq) is decided in call_physiq.
  • turned "physiq.F[90]" into module "physiq_mod.F[90]" for better control of "physiq" arguments. for phyvenus/phytitan, extracted gr_fi_ecrit from physiq.F as gr_fi_ecrit.F90 (note that it can only work in serial).
  • misc:
  • updated wxios.F90 to keep up with LMDZ5 modifications.
  • dyn3d_common:
  • infotrac.F90 keep up with LMDZ5 modifications (cosmetics)
  • dyn3d:
  • gcm.F90: cosmetic cleanup.
  • leapfrog.F90: fix computation of date as function of itau.
  • dyn3dpar:
  • gcm.F: cosmetic cleanup.
  • leapfrog_p.F90: fix computation of date as function of itau.

NB: physics are given the date corresponding to the end of the
physics step.

  • dynphy_lonlat:
  • calfis.F : added computation of relative wind vorticity.
  • calfis_p.F: added computation of relative wind vorticity (input required by Earth physics)

EM

File size: 4.0 KB
Line 
1!
2! $Id: $
3!
4MODULE callphysiq_mod
5
6IMPLICIT NONE
7
8CONTAINS
9
10SUBROUTINE call_physiq(klon,llm,nqtot,tname,                              &
11                       debut_split,lafin_split,                           &
12                       jD_cur,jH_cur_split,zdt_split,                     &
13                       zplev_omp,zplay_omp,                               &
14                       zpk_omp,zphi_omp,zphis_omp,                        &
15                       presnivs_omp,                                      &
16                       zufi_omp,zvfi_omp,zrfi_omp,ztfi_omp,zqfi_omp,      &
17                       flxwfi_omp,pducov,                                 &
18                       zdufi_omp,zdvfi_omp,zdtfi_omp,zdqfi_omp,zdpsrf_omp,&
19                       tracerdyn)
20
21  USE control_mod, ONLY: planet_type
22  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
23  USE physiq_mod, ONLY: physiq
24  IMPLICIT NONE
25
26  INTEGER,INTENT(IN) :: klon ! (local) number of atmospheric columns
27  INTEGER,INTENT(IN) :: llm  ! number of atmospheric layers
28  INTEGER,INTENT(IN) :: nqtot ! number of tracers
29  CHARACTER(len=*),INTENT(IN) :: tname(nqtot) ! tracer names
30  LOGICAL,INTENT(IN) :: debut_split ! .true. if very first call to physics
31  LOGICAL,INTENT(IN) :: lafin_split ! .true. if last call to physics
32  REAL,INTENT(IN) :: JD_cur ! Julian day
33  REAL,INTENT(IN) :: JH_cur_split ! Julian hour (fraction of day)
34  REAL,INTENT(IN) :: zdt_split ! time step over which the physics are evaluated
35  REAL,INTENT(IN) :: zplev_omp(klon,llm+1) ! interlayer pressure (Pa)
36  REAL,INTENT(IN) :: zplay_omp(klon,llm) ! mid-layer pressure (Pa)
37  REAL,INTENT(IN) :: zpk_omp(klon,llm)
38  REAL,INTENT(IN) :: zphi_omp(klon,llm) ! geopotential at midlayer
39  REAL,INTENT(IN) :: zphis_omp(klon) ! surface geopotential
40  REAL,INTENT(IN) :: presnivs_omp(llm) ! approximate pressure of atm. layers
41  REAL,INTENT(IN) :: zufi_omp(klon,llm) ! zonal wind (m/s)
42  REAL,INTENT(IN) :: zvfi_omp(klon,llm) ! meridional wind (m/s)
43  REAL,INTENT(IN) :: zrfi_omp(klon,llm) ! relative wind vorticity, in s-1
44  REAL,INTENT(IN) :: ztfi_omp(klon,llm) ! temperature (K)
45  REAL,INTENT(IN) :: zqfi_omp(klon,llm,nqtot) ! tracers (*/kg of air)
46  REAL,INTENT(IN) :: flxwfi_omp(klon,llm) ! Vertical mass flux on lower mesh interfaces (kg/s)
47  REAL,INTENT(IN) :: pducov(nbp_lon+1,nbp_lat,llm) ! dynamical tendency on ucov
48  ! tendencies (in */s) from the physics:
49  REAL,INTENT(OUT) :: zdufi_omp(klon,llm) ! tendency on zonal winds
50  REAL,INTENT(OUT) :: zdvfi_omp(klon,llm) ! tendency on meridional winds
51  REAL,INTENT(OUT) :: zdtfi_omp(klon,llm) ! tendency on temperature
52  REAL,INTENT(OUT) :: zdqfi_omp(klon,llm,nqtot) ! tendency on tracers
53  REAL,INTENT(OUT) :: zdpsrf_omp(klon) ! tendency on surface pressure
54  LOGICAL,INTENT(OUT) :: tracerdyn
55
56  ! Local variables
57  CHARACTER(len=11) :: modname="call_physiq"
58  LOGICAL,SAVE :: firstcall=.true.
59!$OMP THREADPRIVATE(firstcall)
60
61! Sanity check on physics package type
62  IF (firstcall) THEN
63    IF (planet_type.ne."mars") THEN
64      CALL abort_gcm(modname,"wrong planet_type for this physics package",1)
65    ENDIF
66    firstcall=.false.
67  ENDIF
68
69
70! Call physics package with required inputs/outputs
71  CALL physiq(klon,           & ! ngrid
72              llm,            & ! nlayer
73              nqtot,          & ! nq
74              debut_split,    & ! firstcall
75              lafin_split,    & ! lastcall
76              jD_cur,         & ! pday
77              jH_cur_split,   & ! ptime
78              zdt_split,      & ! ptimestep
79              zplev_omp,      & ! pplev
80              zplay_omp,      & ! pplay
81              zphi_omp,       & ! pphi
82              zufi_omp,       & ! pu
83              zvfi_omp,       & ! pv
84              ztfi_omp,       & ! pt
85              zqfi_omp,       & ! pq
86              flxwfi_omp,     & ! flxw
87              zdufi_omp,      & ! pdu
88              zdvfi_omp,      & ! pdv
89              zdtfi_omp,      & ! pdt
90              zdqfi_omp,      & ! pdq
91              zdpsrf_omp,     & ! pdpsrf
92              tracerdyn)        ! tracerdyn (somewhat obsolete)
93
94
95END SUBROUTINE call_physiq
96
97END MODULE callphysiq_mod
Note: See TracBrowser for help on using the repository browser.