source: trunk/LMDZ.PLUTO/libf/phypluto/moldiffcoeff_red.F @ 3558

Last change on this file since 3558 was 3455, checked in by afalco, 3 months ago

Pluto PCM: added conduction & molvis.
AF

File size: 3.1 KB
Line 
1      subroutine moldiffcoeff_red(nq,dij,gcmind,ncompdiff2)
2
3       use diffusion_h
4       use tracer_h, only: noms, mmol
5       IMPLICIT NONE
6c=======================================================================
7c   subject:
8c   --------
9c   Computing molecular diffusion coefficients
10c   following Nair 94 (pg 131)
11c   author:  MAC 2002
12c   ------
13c
14c=======================================================================
15#include "dimensions.h"
16
17c-----------------------------------------------------------------------
18c    Input/Output
19c    ------------
20c       integer,parameter :: ncompmoldiff = 12
21        integer ncompdiff2
22        integer gcmind(ncompdiff2)
23      real dij(ncompdiff2,ncompdiff2)
24
25c    Local variables:
26c    ---------------
27      INTEGER nq, n, nn, i,iq
28cccccccccccccccccccccccccccccccccccccccccccccccccccccccc
29c     tracer numbering in the molecular diffusion
30cccccccccccccccccccccccccccccccccccccccccccccccccccccccc
31
32!      real :: dijh2co,dijh2n2,dijh2co2,dijh2o2,dijho,dijref,dijch4n2
33       real :: dijref,dijch4n2,dijch4co  !TB16
34!       integer :: g_h2,g_h,g_o
35       integer :: g_ch4,g_n2   ! TB16
36!       integer :: i_h2,i_h,i_o
37!      integer,parameter :: i_ch4 = 1
38
39      real dnh
40      logical,save :: firstcall=.true.
41      logical,parameter :: outputcoeffs=.false. ! to output 'coeffs.dat' file,
42                                                ! set outputcoeffs=.true.
43
44! Initializations at first call (and some sanity checks)
45      if (firstcall) then
46        ! identify the indexes of the tracers we'll need
47!        g_n2=igcm_n2
48!        if (g_n2.eq.0) then
49!          write(*,*) "moldiffcoeff: Error; no N2 tracer !!!"
50!          stop
51!        endif
52
53cccccccccccccccccccccccccccccccccccccccccccccccccccccccc
54c    fill array to relate local indexes to gcm indexes
55cccccccccccccccccccccccccccccccccccccccccccccccccccccccc
56
57!        gcmind(i_n2)  =   g_n2
58c
59cccccccccccccccccccccccccccccccccccccccccccccccccccccccc
60        firstcall= .false.
61      endif ! of if (firstcall)
62
63       dijch4n2 = 0.000018524
64       dijch4co = 0.000018524
65
66! find h2, h and o index in gcm
67! these species are used to define the diffusion coefficients
68
69        do n=1,nq
70        if (noms(n) .eq. 'ch4_gas') g_ch4=n
71        if (noms(n) .eq. 'n2') g_n2=n
72        enddo
73
74       print*,'moldiffcoeff_red: COEFF CALC'
75
76
77      do n=1,ncompdiff2
78        dijref=0.
79        if (noms(gcmind(n)) .eq. 'n2') dijref=dijch4n2
80        if (noms(gcmind(n)) .eq. 'co_gas') dijref=dijch4co
81
82        if (dijref .gt. 0.0) then
83          do nn=n,ncompdiff2
84            dij(nn,n)=dijref
85     &                  *sqrt(mmol(g_ch4)/mmol(gcmind(nn)))
86            if(n.eq.nn) dij(nn,n)=1.0
87            if(mmol(gcmind(n)).eq.mmol(gcmind(nn))) dij(nn,n)=1.0
88            dij(n,nn)=dij(nn,n)
89          enddo
90        endif
91
92        if (dijref .eq. 0.0) then
93        dijref=dijch4n2
94          dnh=dijref*sqrt(mmol(g_n2)/mmol(gcmind(n)))
95          do nn=n,ncompdiff2
96            dij(nn,n)=dnh*sqrt(mmol(g_ch4)/mmol(gcmind(nn)))
97            if(n.eq.nn) dij(nn,n)=1.0
98            dij(n,nn)=dij(nn,n)
99          enddo
100        endif
101
102      enddo
103      print*, 'TB16: dij=',dij(1,:)
104      print*, 'TB16: dij=',dij(2,:)
105      print*, 'TB16: dij=',dij(3,:)
106
107
108      return
109      end
110
Note: See TracBrowser for help on using the repository browser.