source: trunk/LMDZ.VENUS/libf/phyvenus/moldiffcoeff_red.F @ 1525

Last change on this file since 1525 was 1442, checked in by slebonnois, 10 years ago

SL: update of the Venus GCM, + corrections on routines used for newstart/start2archive for Titan and Venus, + some modifications on tools

File size: 8.8 KB
Line 
1      subroutine moldiffcoeff_red(dij,indic,gcmind,ncompdiff2)
2
3       USE chemparam_mod
4       USE infotrac
5       USE dimphy   
6       use infotrac
7
8       IMPLICIT NONE
9c=======================================================================
10c   subject:
11c   --------
12c   Computing molecular diffusion coefficients
13c   following Nair 94 (pg 131)
14c   author:  MAC 2002
15c   ------
16c
17c=======================================================================
18!#include "dimensions.h"
19!#include "dimphys.h"
20!#include "callkeys.h"
21!#include "comdiurn.h"
22!#include "chimiedata.h"
23!#include "tracer.h"
24!#include "conc.h"
25#include "diffusion.h"
26
27c-----------------------------------------------------------------------
28c    Input/Output
29c    ------------
30c       integer,parameter :: ncompmoldiff = 12
31      integer ncompdiff2
32      integer gcmind(ncompdiff2)
33      real dij(ncompdiff2,ncompdiff2)
34      integer indic(nqtot)
35
36c    Local variables:
37c    ---------------
38      INTEGER nq, n, nn, i,iq
39cccccccccccccccccccccccccccccccccccccccccccccccccccccccc
40c     tracer numbering in the molecular diffusion
41cccccccccccccccccccccccccccccccccccccccccccccccccccccccc
42
43      real :: dijh2co,dijh2n2,dijh2co2,dijh2o2,dijho,dijref
44!       integer :: i_h2,i_h,i_o
45        integer :: g_h2,g_h,g_o
46!      integer,parameter :: i_o   = 1
47!      integer,parameter :: i_n2   = 2
48!      integer,parameter :: i_co   = 3
49!      integer,parameter :: i_ar  = 4
50!      integer,parameter :: i_h2   = 5
51!      integer,parameter :: i_h    = 6
52!      integer,parameter :: i_o2   = 7
53!      integer,parameter :: i_oh  = 8
54!      integer,parameter :: i_ho2  = 9
55!      integer,parameter :: i_h2o = 10
56!      integer,parameter :: i_h2o2  = 11
57!      integer,parameter :: i_o1d   = 12
58!      integer,parameter :: i_o3   = 13
59!      integer,parameter :: i_n    = 13
60!      integer,parameter :: i_no   = 14
61!      integer,parameter :: i_no2  = 15
62!      integer,parameter :: i_n2d  = 17
63!      integer,parameter :: i_oplus = 18
64!      integer,parameter :: i_co2    = 16
65!      integer,parameter :: i_oplus = 17
66!      integer,parameter :: i_hplus = 18
67
68! Tracer indexes in the GCM:
69!      integer,save :: g_co2=0
70!      integer,save :: g_co=0
71!      integer,save :: g_o=0
72!      integer,save :: g_o1d=0
73!      integer,save :: g_o2=0
74!      integer,save :: g_o3=0
75!      integer,save :: g_h=0
76!      integer,save :: g_h2=0
77!      integer,save :: g_oh=0
78!      integer,save :: g_ho2=0
79!      integer,save :: g_h2o2=0
80!      integer,save :: g_n2=0
81!      integer,save :: g_ar=0
82!      integer,save :: g_h2o=0
83!      integer,save :: g_n=0
84!      integer,save :: g_no=0
85!      integer,save :: g_no2=0
86!      integer,save :: g_n2d=0
87!      integer,save :: g_oplus=0
88!      integer,save :: g_hplus=0
89
90!      integer,save :: gcmind(ncompdiff)
91
92      real dnh
93      logical,save :: firstcall=.true.
94      logical,parameter :: outputcoeffs=.false. ! to output 'coeffs.dat' file,
95                                                ! set outputcoeffs=.true.
96
97! Initializations at first call (and some sanity checks)
98      if (firstcall) then
99        ! identify the indexes of the tracers we'll need
100!        g_co2=igcm_co2
101!        if (g_co2.eq.0) then
102!          write(*,*) "moldiffcoeff: Error; no CO2 tracer !!!"
103!          stop
104!        endif
105!        g_n2=igcm_n2
106!        if (g_n2.eq.0) then
107!          write(*,*) "moldiffcoeff: Error; no N2 tracer !!!"
108!          stop
109!        endif
110!        g_ar=igcm_ar
111!        if (g_ar.eq.0) then
112!          write(*,*) "moldiffcoeff: Error; no Ar tracer !!!"
113!          stop
114!        endif       
115!        g_h2=igcm_h2
116!        if (g_h2.eq.0) then
117!          write(*,*) "moldiffcoeff: Error; no H2 tracer !!!"
118!          stop
119!        endif
120!        g_h=igcm_h
121!        if (g_h.eq.0) then
122!          write(*,*) "moldiffcoeff: Error; no H tracer !!!"
123!          stop
124!        endif
125!        g_co=igcm_co
126!        if (g_co.eq.0) then
127!          write(*,*) "moldiffcoeff: Error; no CO tracer !!!"
128!          stop
129!        endif
130!        g_o2=igcm_o2
131!        if (g_o2.eq.0) then
132!          write(*,*) "moldiffcoeff: Error; no O2 tracer !!!"
133!          stop
134!        endif
135!        g_oh=igcm_oh
136!        if (g_oh.eq.0) then
137!          write(*,*) "moldiffcoeff: Error; no OH tracer !!!"
138!          stop
139!        endif
140!        g_ho2=igcm_ho2
141!        if (g_ho2.eq.0) then
142!          write(*,*) "moldiffcoeff: Error; no HO2 tracer !!!"
143!          stop
144!        endif
145!        g_h2o=igcm_h2o_vap
146!        if (g_h2o.eq.0) then
147!          write(*,*) "moldiffcoeff: Error; no H2O tracer !!!"
148!          stop
149!        endif
150!        g_h2o2=igcm_h2o2
151!        if (g_h2o2.eq.0) then
152!          write(*,*) "moldiffcoeff: Error; no H2O2 tracer !!!"
153!          stop
154!        endif
155!        g_o1d=igcm_o1d
156!        if (g_h.eq.0) then
157!          write(*,*) "moldiffcoeff: Error; no O1d tracer !!!"
158!          stop
159!        endif
160!        g_o3=igcm_o3
161!        if (g_o3.eq.0) then
162!          write(*,*) "moldiffcoeff: Error; no O3 tracer !!!"
163!          stop
164!        endif
165!        g_n=igcm_n
166!        if (g_n.eq.0) then
167!          write(*,*) "moldiffcoeff: Error; no N tracer !!!"
168!          stop
169!        endif
170!        g_no=igcm_no
171!        if (g_no.eq.0) then
172!          write(*,*) "moldiffcoeff: Error; no NO tracer !!!"
173!          stop
174!        endif
175!        g_no2=igcm_no2
176!        if (g_no2.eq.0) then
177!          write(*,*) "moldiffcoeff: Error; no NO2 tracer !!!"
178!          stop
179!        endif
180!        g_n2d=igcm_n2d
181!        if (g_n2d.eq.0) then
182!          write(*,*) "moldiffcoeff: Error; no N2(D) tracer !!!"
183!          stop
184!        endif
185!        g_oplus=igcm_oplus
186!        if (g_oplus .eq. 0) then
187!        write(*,*) "moldiffcoeff: Error; no Oplus tracer !!!"
188!        stop
189!        endif
190!       g_hplus=igcm_hplus
191!        if (g_hplus .eq. 0) then
192!        write(*,*) "moldiffcoeff: Error; no Hplus tracer !!!"
193!        stop
194!        endif
195!        g_o=igcm_o
196!        if (g_o.eq.0) then
197!          write(*,*) "moldiffcoeff: Error; no O tracer !!!"
198!          stop
199!        endif
200       
201c
202cccccccccccccccccccccccccccccccccccccccccccccccccccccccc
203c    fill array to relate local indexes to gcm indexes
204cccccccccccccccccccccccccccccccccccccccccccccccccccccccc
205
206!        gcmind(i_co2)  =   g_co2
207!        gcmind(i_n2)  =   g_n2
208!        gcmind(i_ar)  =   g_ar
209!        gcmind(i_h2) =   g_h2
210!        gcmind(i_h)  =   g_h
211!        gcmind(i_co)   =   g_co
212!        gcmind(i_o2) =   g_o2
213!        gcmind(i_oh)=   g_oh
214!        gcmind(i_ho2)  =   g_ho2
215!        gcmind(i_h2o) = g_h2o
216!        gcmind(i_h2o2)= g_h2o2
217!        gcmind(i_o1d) = g_o1d
218!        gcmind(i_o3) = g_o3
219!        gcmind(i_n)= g_n
220!        gcmind(i_no) = g_no
221!        gcmind(i_no2) = g_no2
222!        gcmind(i_n2d) = g_n2d
223!        gcmind(i_oplus) =  g_oplus
224!        gcmind(i_hplus) = g_hplus
225!        gcmind(i_o)   =   g_o
226
227c
228cccccccccccccccccccccccccccccccccccccccccccccccccccccccc
229        firstcall= .false.
230      endif ! of if (firstcall)
231
232        dijh2co = 0.0000651
233        dijh2n2 = 0.0000674
234        dijh2o2 = 0.0000697
235        dijh2co2 = 0.0000550
236        dijho = 0.000114
237
238!      dij(i_h2,i_co)   = 0.0000651
239!      dij(i_h2,i_n2)   = 0.0000674
240!      dij(i_h2,i_o2)   = 0.0000697
241!      dij(i_h2,i_co2)  = 0.0000550
242!      dij(i_h2,i_h2)   = 0.0
243!      dij(i_h2,i_h)    = 0.0
244!      dij(i_h2,i_h2o)  = 0.0   !0003
245!      dij(i_h2,i_h2o2) = 0.0   !0003
246!      dij(i_h2,i_o3)   = 0.0   !0003
247!      dij(i_h2,i_o)    = 0.0
248!      dij(i_h2,i_ar)   = 0.0
249!      dij(i_h2,i_n)    = 0.0
250
251!c      dij(i_h,i_o)     = 0.0000144
252!      dij(i_h,i_o)     = 0.000114
253
254! find h2, h and o index in gcm
255! these species are used to define the diffusion coefficients
256
257        do n=1,nqtot
258        if (tname(n) .eq. 'h2') g_h2=n
259        if (tname(n) .eq. 'h') g_h=n
260        if (tname(n) .eq. 'o') g_o=n
261        enddo
262        print*,'moldiffcoeff_red: gh2',g_h2,g_h,g_o
263
264       print*,'moldiffcoeff_red: COEFF CALC'
265
266      do n=1,ncompdiff2
267        dijref=0.
268        if (tname(gcmind(n)) .eq. 'co') dijref=dijh2co
269        if (tname(gcmind(n)) .eq. 'n2') dijref=dijh2n2
270        if (tname(gcmind(n)) .eq. 'o2') dijref=dijh2o2
271        if (tname(gcmind(n)) .eq. 'co2') dijref=dijh2co2
272!       print*,'test',n,dijref
273        if (dijref .gt. 0.0) then
274          do nn=n,ncompdiff2
275            dij(nn,n)=dijref
276     &                  *sqrt(M_tr(g_h2)/M_tr(gcmind(nn)))
277           if(n.eq.nn) dij(nn,n)=1.0
278            dij(n,nn)=dij(nn,n)
279          enddo
280        endif
281        if (dijref .eq. 0.0) then
282        dijref=dijho
283          dnh=dijref*sqrt(M_tr(g_o)/M_tr(gcmind(n)))
284          do nn=n,ncompdiff2
285            dij(nn,n)=dnh*sqrt(M_tr(g_h)/M_tr(gcmind(nn)))
286            if(n.eq.nn) dij(nn,n)=1.0
287            dij(n,nn)=dij(nn,n)
288          enddo
289        endif
290      enddo
291     
292      if (outputcoeffs) then
293       ! output coefficients in 'coeffs.dat' file
294       open(56,file='coeffs.dat',status='unknown')
295       do n=1,ncompdiff2
296        do nn=n,ncompdiff2
297          write(56,*) n,nn,dij(n,nn)    !*1.e5/1.381e-23/(273**1.75)
298        enddo
299       enddo
300       close(56)
301      endif
302
303
304      return   
305      end
306     
Note: See TracBrowser for help on using the repository browser.