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

Last change on this file since 2808 was 2615, checked in by romain.vande, 3 years ago

LMDZ_MARS RV : Open_MP;
Put all the "save" variables as "!$OMP THREADPRIVATE" in aeronomars

File size: 3.0 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        if (.not. tracer) then
46          do l=1,nlayer
47            do ig=1,ngrid
48              rnew(ig,l)=r
49              cpnew(ig,l)=cpp
50            enddo
51          enddo
52        endif
53        firstcall= .false.
54      endif
55
56      ! initialize tendencies to zero in all cases
57      ! (tendencies are added later on, even if parametrization is not called)
58      zdteuv(1:ngrid,1:nlayer)=0
59      zdtconduc(1:ngrid,1:nlayer)=0
60      zdumolvis(1:ngrid,1:nlayer)=0
61      zdvmolvis(1:ngrid,1:nlayer)=0
62      zdqmoldiff(1:ngrid,1:nlayer,1:nq)=0
63     
64      if (calleuv) then
65        call euvheat(ngrid,nlayer,nq,pt,pdt,pplev,pplay,zzlay,
66     $               mu0,ptimestep,ptime,zday,pq,pdq,zdteuv)
67      endif
68
69      if (callconduct) THEN
70        call conduction(ngrid,nlayer,ptimestep,pplay,pplev,pt,zdteuv,
71     $                   tsurf,zzlev,zzlay,zdtconduc)
72      endif
73
74      if (callmolvis) THEN
75        call molvis(ngrid,nlayer,ptimestep,pplay,pplev,pt,
76     &                zdteuv,zdtconduc,pu,
77     $                   tsurf,zzlev,zzlay,zdumolvis)
78        call molvis(ngrid,nlayer,ptimestep,pplay,pplev,pt,
79     &                zdteuv,zdtconduc,pv,
80     $                   tsurf,zzlev,zzlay,zdvmolvis)
81      endif
82
83      if (callmoldiff) THEN
84        call moldiff_red(ngrid,nlayer,nq,
85     &                   pplay,pplev,pt,pdt,pq,pdq,ptimestep,
86     &                   zzlay,zdteuv,zdtconduc,zdqmoldiff,
87     &                   PhiEscH,PhiEscH2,PhiEscD)
88      endif
89
90      end
91
92
Note: See TracBrowser for help on using the repository browser.