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

Last change on this file since 3026 was 3015, checked in by emillour, 17 months ago

Mars PCM:
Code cleanup in diffusion, turn variables from diffusion.h into module
variables in moldiff_red.F90 (turn it into a module in the process).
Also turn moldiffcoeff_red.F and thermosphere.F into modules.
EM

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