source: trunk/LMDZ.MARS/libf/aeronomars/thermosphere.F @ 2883

Last change on this file since 2883 was 2823, checked in by emillour, 2 years ago

Mars GCM:
Remove the "tracer" (logical) flag as we now always run with at least
one tracer.
EM

File size: 2.9 KB
Line 
1      subroutine thermosphere(ngrid,nlayer,nq,
2     &     pplev,pplay,dist_sol,
3     $     mu0,ptimestep,ptime,zday,tsurf,zzlev,zzlay,
4     &     pt,pq,pu,pv,pdt,pdq,
5     $     zdteuv,zdtconduc,zdumolvis,zdvmolvis,zdqmoldiff,
6     $     PhiEscH,PhiEscH2,PhiEscD)
7
8      use conc_mod, only: rnew, cpnew
9      USE comcstfi_h, only: r, cpp
10      implicit none
11
12      include "callkeys.h"
13
14      integer,intent(in) :: ngrid ! number of atmospheric columns
15      integer,intent(in) :: nlayer ! number of atmospheric layers
16      integer,intent(in) :: nq ! number of advected tracers
17      REAL,INTENT(in) :: pplay(ngrid,nlayer)
18      REAL,INTENT(in) :: pplev(ngrid,nlayer+1)
19      REAL,INTENT(in) :: zzlay(ngrid,nlayer)
20      REAL,INTENT(in) :: zzlev(ngrid,nlayer+1)
21      REAL,INTENT(in) :: pt(ngrid,nlayer)
22      REAL,INTENT(in) :: zday
23      REAL,INTENT(in) :: dist_sol
24      REAL,INTENT(in) :: mu0(ngrid)
25      REAL,INTENT(in) :: pq(ngrid,nlayer,nq)
26      REAL,INTENT(in) :: ptimestep
27      REAL,INTENT(in) :: ptime
28      REAL,INTENT(in) :: tsurf(ngrid)
29      REAL,INTENT(in) :: pu(ngrid,nlayer),pv(ngrid,nlayer)
30      REAL,INTENT(in) :: pdt(ngrid,nlayer),pdq(ngrid,nlayer,nq)
31
32      REAL,INTENT(out) :: zdteuv(ngrid,nlayer)
33      REAL,INTENT(out) :: zdtconduc(ngrid,nlayer)
34      REAL,INTENT(out) :: zdumolvis(ngrid,nlayer)
35      REAL,INTENT(out) :: zdvmolvis(ngrid,nlayer)
36      REAL,INTENT(out) :: zdqmoldiff(ngrid,nlayer,nq)
37      REAL*8,INTENT(out) :: PhiEscH,PhiEscH2,PhiEscD
38
39      INTEGER :: l,ig
40      logical,save :: firstcall=.true.
41
42!$OMP THREADPRIVATE(firstcall)
43
44      if (firstcall) then
45        rnew(1:ngrid,1:nlayer)=r
46        cpnew(1:ngrid,1:nlayer)=cpp
47        firstcall= .false.
48      endif
49
50      ! initialize tendencies to zero in all cases
51      ! (tendencies are added later on, even if parametrization is not called)
52      zdteuv(1:ngrid,1:nlayer)=0
53      zdtconduc(1:ngrid,1:nlayer)=0
54      zdumolvis(1:ngrid,1:nlayer)=0
55      zdvmolvis(1:ngrid,1:nlayer)=0
56      zdqmoldiff(1:ngrid,1:nlayer,1:nq)=0
57     
58      if (calleuv) then
59        call euvheat(ngrid,nlayer,nq,pt,pdt,pplev,pplay,zzlay,
60     $               mu0,ptimestep,ptime,zday,pq,pdq,zdteuv)
61      endif
62
63      if (callconduct) THEN
64        call conduction(ngrid,nlayer,ptimestep,pplay,pplev,pt,zdteuv,
65     $                   tsurf,zzlev,zzlay,zdtconduc)
66      endif
67
68      if (callmolvis) THEN
69        call molvis(ngrid,nlayer,ptimestep,pplay,pplev,pt,
70     &                zdteuv,zdtconduc,pu,
71     $                   tsurf,zzlev,zzlay,zdumolvis)
72        call molvis(ngrid,nlayer,ptimestep,pplay,pplev,pt,
73     &                zdteuv,zdtconduc,pv,
74     $                   tsurf,zzlev,zzlay,zdvmolvis)
75      endif
76
77      if (callmoldiff) THEN
78        call moldiff_red(ngrid,nlayer,nq,
79     &                   pplay,pplev,pt,pdt,pq,pdq,ptimestep,
80     &                   zzlay,zdteuv,zdtconduc,zdqmoldiff,
81     &                   PhiEscH,PhiEscH2,PhiEscD)
82      endif
83
84      end
85
86
Note: See TracBrowser for help on using the repository browser.