1 | ! |
---|
2 | ! $Id: caladvtrac.F 1446 2010-10-22 09:27:25Z emillour $ |
---|
3 | ! |
---|
4 | c |
---|
5 | c |
---|
6 | SUBROUTINE caladvtrac(q,pbaru,pbarv , |
---|
7 | * p ,masse, dq , teta, |
---|
8 | * flxw, pk) |
---|
9 | c |
---|
10 | USE infotrac, ONLY : nqtot |
---|
11 | USE control_mod, ONLY : iapp_tracvl,planet_type, |
---|
12 | & force_conserv_tracer |
---|
13 | USE comconst_mod, ONLY: dtvr |
---|
14 | USE planetary_operations, ONLY: planetary_tracer_amount_from_mass |
---|
15 | IMPLICIT NONE |
---|
16 | c |
---|
17 | c Auteurs: F.Hourdin , P.Le Van, F.Forget, F.Codron |
---|
18 | c |
---|
19 | c F.Codron (10/99) : ajout humidite specifique pour eau vapeur |
---|
20 | c======================================================================= |
---|
21 | c |
---|
22 | c Shema de Van Leer |
---|
23 | c |
---|
24 | c======================================================================= |
---|
25 | |
---|
26 | |
---|
27 | #include "dimensions.h" |
---|
28 | #include "paramet.h" |
---|
29 | |
---|
30 | c Arguments: |
---|
31 | c ---------- |
---|
32 | REAL pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm),masse(ip1jmp1,llm) |
---|
33 | REAL p( ip1jmp1,llmp1),q( ip1jmp1,llm,nqtot) |
---|
34 | real :: dq(ip1jmp1,llm,nqtot) |
---|
35 | REAL teta( ip1jmp1,llm),pk( ip1jmp1,llm) |
---|
36 | REAL :: flxw(ip1jmp1,llm) |
---|
37 | |
---|
38 | c .................................................................. |
---|
39 | c |
---|
40 | c .. dq n'est utilise et dimensionne que pour l'eau vapeur et liqu. |
---|
41 | c |
---|
42 | c .................................................................. |
---|
43 | c |
---|
44 | c Local: |
---|
45 | c ------ |
---|
46 | |
---|
47 | EXTERNAL advtrac,minmaxq, qminimum |
---|
48 | INTEGER ij,l, iq, iapptrac |
---|
49 | REAL finmasse(ip1jmp1,llm), dtvrtrac |
---|
50 | REAL :: totaltracer_old(nqtot),totaltracer_new(nqtot) |
---|
51 | REAL :: ratio |
---|
52 | |
---|
53 | ! Ehouarn : try to fix tracer conservation issues: |
---|
54 | if (force_conserv_tracer) then |
---|
55 | do iq=1,nqtot |
---|
56 | call planetary_tracer_amount_from_mass(masse,q(:,:,iq), |
---|
57 | & totaltracer_old(iq)) |
---|
58 | enddo |
---|
59 | endif |
---|
60 | cc |
---|
61 | c |
---|
62 | ! Earth-specific stuff for the first 2 tracers (water) |
---|
63 | if (planet_type.eq."earth") then |
---|
64 | C initialisation |
---|
65 | ! CRisi: il faut gérer tous les traceurs si on veut pouvoir faire des |
---|
66 | ! isotopes |
---|
67 | ! dq(:,:,1:2)=q(:,:,1:2) |
---|
68 | dq(:,:,1:nqtot)=q(:,:,1:nqtot) |
---|
69 | |
---|
70 | c test des valeurs minmax |
---|
71 | cc CALL minmaxq(q(1,1,1),1.e33,-1.e33,'Eau vapeur (a) ') |
---|
72 | cc CALL minmaxq(q(1,1,2),1.e33,-1.e33,'Eau liquide(a) ') |
---|
73 | endif ! of if (planet_type.eq."earth") |
---|
74 | c advection |
---|
75 | |
---|
76 | CALL advtrac( pbaru,pbarv, |
---|
77 | * p, masse,q,iapptrac, teta, |
---|
78 | . flxw, pk) |
---|
79 | |
---|
80 | c |
---|
81 | |
---|
82 | IF( iapptrac.EQ.iapp_tracvl ) THEN |
---|
83 | if (planet_type.eq."earth") then |
---|
84 | ! Earth-specific treatment for the first 2 tracers (water) |
---|
85 | c |
---|
86 | cc CALL minmaxq(q(1,1,1),1.e33,-1.e33,'Eau vapeur ') |
---|
87 | cc CALL minmaxq(q(1,1,2),1.e33,-1.e33,'Eau liquide ') |
---|
88 | |
---|
89 | cc .... Calcul de deltap qu'on stocke dans finmasse ... |
---|
90 | c |
---|
91 | DO l = 1, llm |
---|
92 | DO ij = 1, ip1jmp1 |
---|
93 | finmasse(ij,l) = p(ij,l) - p(ij,l+1) |
---|
94 | ENDDO |
---|
95 | ENDDO |
---|
96 | |
---|
97 | !write(*,*) 'caladvtrac 87' |
---|
98 | CALL qminimum( q, nqtot, finmasse ) |
---|
99 | !write(*,*) 'caladvtrac 89' |
---|
100 | |
---|
101 | CALL SCOPY ( ip1jmp1*llm, masse, 1, finmasse, 1 ) |
---|
102 | CALL filtreg ( finmasse , jjp1, llm, -2, 2, .TRUE., 1 ) |
---|
103 | c |
---|
104 | c ***** Calcul de dq pour l'eau , pour le passer a la physique ****** |
---|
105 | c ******************************************************************** |
---|
106 | c |
---|
107 | dtvrtrac = iapp_tracvl * dtvr |
---|
108 | c |
---|
109 | DO iq = 1 , nqtot |
---|
110 | DO l = 1 , llm |
---|
111 | DO ij = 1,ip1jmp1 |
---|
112 | dq(ij,l,iq) = ( q(ij,l,iq) - dq(ij,l,iq) ) * finmasse(ij,l) |
---|
113 | * / dtvrtrac |
---|
114 | ENDDO |
---|
115 | ENDDO |
---|
116 | ENDDO |
---|
117 | c |
---|
118 | endif ! of if (planet_type.eq."earth") |
---|
119 | |
---|
120 | ! Ehouarn : try to fix tracer conservation after tracer advection |
---|
121 | if (force_conserv_tracer) then |
---|
122 | do iq=1,nqtot |
---|
123 | call planetary_tracer_amount_from_mass(masse,q(:,:,iq), |
---|
124 | & totaltracer_new(iq)) |
---|
125 | ratio=totaltracer_old(iq)/totaltracer_new(iq) |
---|
126 | q(:,:,iq)=q(:,:,iq)*ratio |
---|
127 | enddo |
---|
128 | endif !of if (force_conserv_tracer) |
---|
129 | |
---|
130 | ELSE ! i.e. iapptrac.NE.iapp_tracvl |
---|
131 | if (planet_type.eq."earth") then |
---|
132 | ! Earth-specific treatment for the first 2 tracers (water) |
---|
133 | dq(:,:,1:nqtot)=0. |
---|
134 | endif ! of if (planet_type.eq."earth") |
---|
135 | ENDIF ! of IF( iapptrac.EQ.iapp_tracvl ) |
---|
136 | |
---|
137 | END |
---|
138 | |
---|
139 | |
---|