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

Last change on this file since 3436 was 3175, checked in by emillour, 11 months ago

Pluto PCM:
Add the old Pluto LMDZ for reference (required prior step to making
an LMDZ.PLUTO using the same framework as the other physics packages).
TB+EM

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