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

Last change on this file since 3493 was 3466, checked in by emillour, 2 months ago

Mars PCM:
More tidying in aeronomars:

  • remove unused "inv.F" and remove "dtridgl.F" which is not used here and is a duplicate of the "dtridgl" routine in phymars/swr_toon.F
  • turn aeronomars routines to modules, for those which aren't in modules yet.

EM

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