source: trunk/LMDZ.MARS/libf/aeronomars/euvheat.F @ 134

Last change on this file since 134 was 38, checked in by emillour, 14 years ago

Ajout du modè Martien (mon LMDZ.MARS.BETA, du 28/01/2011) dans le rértoire mars, pour pouvoir suivre plus facilement les modifs.
EM

File size: 5.8 KB
Line 
1      SUBROUTINE euvheat(pt,pdt,pplev,pplay,zzlay,dist_sol,
2     $     mu0,ptimestep,ptime,zday,pq,pdq,pdteuv)
3
4       IMPLICIT NONE
5c=======================================================================
6c   subject:
7c   --------
8c   Computing heating rate due to EUV absorption
9c
10c   author:  MAC 2002
11c   ------
12c
13c   input:
14c   -----
15c   dist_sol              sun-Mars distance (AU)
16c   mu0(ngridmx)           
17c   pplay(ngrid,nlayer)   pressure at middle of layers (Pa)
18c
19c   output:
20c   -------
21c
22c   pdteuv(ngrid,nlayer)      Heating rate (K/s)
23c
24c=======================================================================
25c
26c    0.  Declarations :
27c    ------------------
28c
29#include "dimensions.h"
30#include "dimphys.h"
31#include "comcstfi.h"
32#include "callkeys.h"
33#include "comdiurn.h"
34#include "param.h"
35#include "param_v3.h"
36#include "chimiedata.h"
37#include "tracer.h"
38#include "conc.h"
39c-----------------------------------------------------------------------
40c    Input/Output
41c    ------------
42
43      REAL pplay(ngridmx,nlayermx)
44      REAL zzlay(ngridmx,nlayermx)
45      real pplev(ngridmx,nlayermx+1)
46      REAL pt(ngridmx,nlayermx)
47      REAL pdt(ngridmx,nlayermx)
48      real zday
49      REAL dist_sol
50      real mu0(ngridmx)
51      real pq(ngridmx,nlayermx,nqmx)
52      real pdq(ngridmx,nlayermx,nqmx)
53      real ptimestep,ptime
54
55
56      REAL pdteuv(ngridmx,nlayermx)
57c
58c    Local variables :
59c    -----------------
60      integer nespeuv
61      parameter (nespeuv=6)
62
63      INTEGER l,iq,ig,n,inif ! , ngrid, nlayer
64      real rm(nlayermx,nespeuv)         ! number density (cm-3)
65      real zq(ngridmx,nlayermx,nqmx) ! local updated tracer quantity
66      real zt(ngridmx,nlayermx) ! local updated atmospheric temperature
67      real zlocal(nlayermx)
68      real zenit
69      real aux1(nlayermx)
70      real aux2(nlayermx)
71      real jtot(nlayermx)
72      real dens                                         ! amu/cm-3
73      real tx(nlayermx)
74      real tmean
75     
76! tracer indexes for the EUV heating:
77      integer,parameter :: i_co2=1
78      integer,parameter :: i_o2=2
79      integer,parameter :: i_o=3
80      integer,parameter :: i_h2=4
81      integer,parameter :: i_h2o=5
82      integer,parameter :: i_h2o2=6
83     
84! Tracer indexes in the GCM:
85      integer,save :: g_co2=0
86      integer,save :: g_o=0
87      integer,save :: g_o2=0
88      integer,save :: g_h2=0
89      integer,save :: g_h2o2=0
90      integer,save :: g_h2o=0
91
92
93      logical,save :: firstcall=.true.
94
95! Initializations and sanity checks:
96
97      if (firstcall) then
98        if ((nespeuv.gt.nqmx).or.(nespeuv.gt.ncomp)) then
99          print*,'******* Dimension problem in EUVHEAT ********'
100          STOP
101        endif
102
103        ! identify the indexes of the tracers we'll need
104        g_co2=igcm_co2
105        if (g_co2.eq.0) then
106          write(*,*) "euvheat: Error; no CO2 tracer !!!"
107          stop
108        endif
109        g_o=igcm_o
110        if (g_o.eq.0) then
111          write(*,*) "euvheat: Error; no O tracer !!!"
112          stop
113        endif
114        g_o2=igcm_o2
115        if (g_o2.eq.0) then
116          write(*,*) "euvheat: Error; no O2 tracer !!!"
117          stop
118        endif
119        g_h2=igcm_h2
120        if (g_h2.eq.0) then
121          write(*,*) "euvheat: Error; no H2 tracer !!!"
122          stop
123        endif
124        g_h2o2=igcm_h2o2
125        if (g_h2o2.eq.0) then
126          write(*,*) "euvheat: Error; no H2O2 tracer !!!"
127          stop
128        endif
129        g_h2o=igcm_h2o_vap
130        if (g_h2o.eq.0) then
131          write(*,*) "euvheat: Error; no water vapor tracer !!!"
132          stop
133        endif
134       
135        firstcall= .false.
136!        print*,'EUV',nlayer,nlayermx,ngrid,ngridmx   
137      endif ! of if (firstcall)
138
139c
140cccccccccccccccccccccccccccccccccccccccccccccccccccccccc
141      ! build local updated values of tracers and temperature
142      do l=1,nlayermx
143        do ig=1,ngridmx
144          ! chemical species
145          zq(ig,l,g_co2)=pq(ig,l,g_co2)+pdq(ig,l,g_co2)*ptimestep
146          zq(ig,l,g_o2)=pq(ig,l,g_o2)+pdq(ig,l,g_o2)*ptimestep
147          zq(ig,l,g_o)=pq(ig,l,g_o)+pdq(ig,l,g_o)*ptimestep
148          zq(ig,l,g_h2)=pq(ig,l,g_h2)+pdq(ig,l,g_h2)*ptimestep
149          zq(ig,l,g_h2o2)=pq(ig,l,g_h2o2)+pdq(ig,l,g_h2o2)*ptimestep
150          zq(ig,l,g_h2o)=pq(ig,l,g_h2o)+pdq(ig,l,g_h2o)*ptimestep
151          ! atmospheric temperature
152          zt(ig,l)=pt(ig,l)+pdt(ig,l)*ptimestep
153        enddo
154      enddo
155
156      call flujo(solarcondate)
157c     call flujo(solarcondate+zday/365.) ! version with EUV time evolution
158
159      do ig=1,ngridmx
160
161        zenit=acos(mu0(ig))*180./acos(-1.)
162 
163        do l=1,nlayermx
164          dens=pplay(ig,l)/(rnew(ig,l)*zt(ig,l)) / 1.66e-21
165          rm(l,i_co2)  = zq(ig,l,g_co2)  * dens / mmol(g_co2)
166          rm(l,i_o2)   = zq(ig,l,g_o2)   * dens / mmol(g_o2)
167          rm(l,i_o)    = zq(ig,l,g_o)    * dens / mmol(g_o)
168          rm(l,i_h2)   = zq(ig,l,g_h2)   * dens / mmol(g_h2)
169          rm(l,i_h2o)  = zq(ig,l,g_h2o)  * dens / mmol(g_h2o)
170          rm(l,i_h2o2) = zq(ig,l,g_h2o2) * dens / mmol(g_h2o2)
171        enddo
172
173c        zlocal(1)=-log(pplay(ig,1)/pplev(ig,1))
174c     &            *Rnew(ig,1)*zt(ig,1)/g
175        zlocal(1)=zzlay(ig,1)
176        zlocal(1)=zlocal(1)/1000.
177        tx(1)=zt(ig,1)
178
179        do l=2,nlayermx
180          tx(l)=zt(ig,l)
181          tmean=tx(l)
182          if(tx(l).ne.tx(l-1))
183     &    tmean=(tx(l)-tx(l-1))/log(tx(l)/tx(l-1))
184c          zlocal(l)= zlocal(l-1)
185c     &   -log(pplay(ig,l)/pplay(ig,l-1))*Rnew(ig,l-1)*tmean/g/1000.
186        zlocal(l)=zzlay(ig,l)/1000.
187        enddo
188
189        call hrtherm (rm(1,i_co2),rm(1,i_o2),rm(1,i_o),
190     &                rm(1,i_h2),rm(1,i_h2o),rm(1,i_h2o2),
191     &                aux1,aux2,tx,nlayermx,zlocal,
192     &                solarcondate+zday/365.,zenit,jtot)
193
194        do l=1,nlayermx
195          pdteuv(ig,l)=0.16*jtot(l)/10.
196     &            /(cpnew(ig,l)*pplay(ig,l)/(rnew(ig,l)*zt(ig,l)))
197     &                  *(1.52/dist_sol)**2
198
199        enddo   
200
201      enddo  ! of do ig=1,ngridmx
202
203      return
204      end
Note: See TracBrowser for help on using the repository browser.