~ubuntu-branches/ubuntu/precise/code-saturne/precise

« back to all changes in this revision

Viewing changes to src/comb/cs_fuel_noxst.f90

  • Committer: Package Import Robot
  • Author(s): Sylvestre Ledru
  • Date: 2011-11-24 00:00:08 UTC
  • mfrom: (6.1.9 sid)
  • Revision ID: package-import@ubuntu.com-20111124000008-2vo99e38267942q5
Tags: 2.1.0-3
Install a missing file

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
!-------------------------------------------------------------------------------
 
2
 
 
3
! This file is part of Code_Saturne, a general-purpose CFD tool.
 
4
!
 
5
! Copyright (C) 1998-2011 EDF S.A.
 
6
!
 
7
! This program is free software; you can redistribute it and/or modify it under
 
8
! the terms of the GNU General Public License as published by the Free Software
 
9
! Foundation; either version 2 of the License, or (at your option) any later
 
10
! version.
 
11
!
 
12
! This program is distributed in the hope that it will be useful, but WITHOUT
 
13
! ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
 
14
! FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
 
15
! details.
 
16
!
 
17
! You should have received a copy of the GNU General Public License along with
 
18
! this program; if not, write to the Free Software Foundation, Inc., 51 Franklin
 
19
! Street, Fifth Floor, Boston, MA 02110-1301, USA.
 
20
 
 
21
!-------------------------------------------------------------------------------
 
22
 
 
23
subroutine cs_fuel_noxst &
 
24
!=======================
 
25
 
 
26
 ( ncelet , ncel   ,                                                      &
 
27
   indpdf ,                                                               &
 
28
   pdfm1  , pdfm2  , doxyd  , dfuel  , hrec ,                             &
 
29
   f3m    , f4m    , f5m    , f6m    , f7m  , f8m , f9m ,                 &
 
30
   fs3no  , fs4no  , yfs4no , enthox ,                                    &
 
31
   rtp    , propce )
 
32
 
 
33
!===============================================================================
 
34
! FONCTION :
 
35
! --------
 
36
! CALCUL DE :
 
37
!
 
38
!           K1 exp(-E1/RT)   (conversion HCN en N2)
 
39
!           K2 exp(-E2/RT)   (conversion HCN en NO)
 
40
!           K3 exp(-E3/RT)   (NO thermique)
 
41
!
 
42
!----------------
 
43
! Arguments
 
44
!__________________.____._____.________________________________________________.
 
45
! name             !type!mode ! role                                           !
 
46
!__________________!____!_____!________________________________________________!
 
47
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
 
48
! ncel             ! i  ! <-- ! number of cells                                !
 
49
! indpdf           ! te ! <-- ! passage par les pdf                            !
 
50
!__________________!____!_____!________________________________________________!
 
51
 
 
52
!     TYPE : E (ENTIER), R (REEL), A (ALPHAMNUMERIQUE), T (TABLEAU)
 
53
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
 
54
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
 
55
!            --- tableau de travail
 
56
!===============================================================================
 
57
 
 
58
!==============================================================================
 
59
! Module files
 
60
!==============================================================================
 
61
 
 
62
use paramx
 
63
use numvar
 
64
use optcal
 
65
use cstphy
 
66
use cstnum
 
67
use entsor
 
68
use parall
 
69
use pointe
 
70
use ppppar
 
71
use ppthch
 
72
use coincl
 
73
use cpincl
 
74
use ppincl
 
75
use ppcpfu
 
76
use cs_fuel_incl
 
77
 
 
78
 
 
79
!===============================================================================
 
80
 
 
81
implicit none
 
82
 
 
83
! Arguments
 
84
 
 
85
integer          ncelet , ncel
 
86
integer          indpdf(ncel)
 
87
 
 
88
double precision pdfm1(ncel) , pdfm2(ncel) , dfuel(ncel)
 
89
double precision f3m(ncel)   , f4m(ncel)   , f5m(ncel)
 
90
double precision f6m(ncel)   , f7m(ncel)   , f8m(ncel) ,f9m(ncel)
 
91
double precision doxyd(ncel) , hrec(ncel)
 
92
double precision fs3no(ncel) , fs4no(ncel) , yfs4no(ncel,ngazg)
 
93
double precision enthox(ncel)
 
94
 
 
95
double precision rtp(ncelet,*), propce(ncelet,*)
 
96
!
 
97
! VARIABLES LOCALES
 
98
!
 
99
integer          iel , icla , i
 
100
integer          ipdf1 , ipdf2 , ipdf3
 
101
integer          iexp1 , iexp2 , iexp3
 
102
integer          ipctem
 
103
integer          npart
 
104
parameter        (npart = 200 )
 
105
 
 
106
double precision ee1,ee2,ee3,kk1,kk2,kk3
 
107
double precision wmo2,tg,xo2,bb,xmx2
 
108
double precision bb1 , bb2 , bb3 , bb4
 
109
double precision dirac , tfuel , tmpgaz , lrf ,lro
 
110
double precision qqq , rrr  , sss , ttt , uuu
 
111
double precision gt1,gt2,gt3,gt10,gt20,gt30
 
112
double precision ts4,ts4num,ts4den
 
113
double precision dgs
 
114
double precision val(npart+1),tt(npart+1) , gs(npart+1) , yyo2(npart+1)
 
115
!
 
116
integer          icha,ige,numcha,mode
 
117
double precision xxf , hhf , hfuel,tfs4ad,hfs4ad
 
118
double precision xhf1,xhf2 , aa , den
 
119
double precision xesp(ngazem),coefe(ngazem),f1mc(ncharm),f2mc(ncharm)
 
120
double precision yo2moy,yo2ox,yo2cb,yo24den,yo24num,yo2s4,yo2
 
121
double precision toxyd,hoxyd , som , react , deltamol
 
122
!
 
123
integer          i300 ,i000 ,imini,i2500,i2600,i2700,i2800,i3000,i3500
 
124
integer          i4000,i5000,imaxi,inok
 
125
integer          nbpt , nbclip1 , nbclip2
 
126
integer          nbclip30,nbclip31
 
127
double precision ts4min,ts4max
 
128
double precision somm  , sommax , sommin , ts4admin,ts4admax
 
129
double precision yo2min,yo2max,yo2min1,yo2max1
 
130
double precision yo2oxmin,yo2oxmax
 
131
double precision toxmin,toxmax
 
132
!
 
133
!
 
134
!===============================================================================
 
135
! 1. CALCULS PRELIMINAIRES
 
136
!===============================================================================
 
137
 
 
138
! --- Masses molaires
 
139
!
 
140
wmo2   = wmole(io2  )
 
141
!
 
142
! --- pointeurs
 
143
!
 
144
iexp1 = ipproc(ighcn1)
 
145
iexp2 = ipproc(ighcn2)
 
146
iexp3 = ipproc(ignoth)
 
147
!
 
148
! Parametres des lois d'Arrhenius
 
149
!
 
150
kk1 = 3.0e12
 
151
ee1 = 3.0e4
 
152
kk2 = 1.2e10
 
153
ee2 = 3.35e4
 
154
kk3 = 3.4e12
 
155
ee3 = 6.69e4
 
156
!
 
157
! Pour les termes, indicateur de calcul par PDF ou non
 
158
!       = 1 --> passage par pdf
 
159
!       = 0 --> on ne passe pas par les pdf
 
160
!
 
161
ipdf1 = 0
 
162
ipdf2 = 0
 
163
ipdf3 = 1
 
164
!
 
165
! Initialisation
 
166
!
 
167
do iel = 1, ncel
 
168
  propce(iel,iexp1)  = zero
 
169
  propce(iel,iexp2)  = zero
 
170
  propce(iel,iexp3)  = zero
 
171
enddo
 
172
 
 
173
!===============================================================================
 
174
! 2. CALCUL SANS LES PDF
 
175
!===============================================================================
 
176
 
 
177
do iel = 1, ncel
 
178
!
 
179
  tg  = propce(iel,ipproc(itemp1))
 
180
  yo2 = propce(iel,ipproc(iym1(io2)))
 
181
  xo2 = yo2*propce(iel,ipproc(immel))/wmo2
 
182
!
 
183
! Reaction HCN + NO + 1/4 O2 ---> N2 + 1/2 H2O + CO
 
184
!
 
185
  propce(iel,iexp1)  = kk1*exp(-ee1/tg)
 
186
!
 
187
! Reaction HCN + 5/4 O2 --> NO + 1/2 H2O  + CO
 
188
!
 
189
  if ( xo2 .gt. 0.018d0 ) then
 
190
    bb = 0.d0
 
191
  else if ( xo2 .lt. 0.0025d0 ) then
 
192
    bb= 1.d0
 
193
  else
 
194
    bb=(0.018d0-xo2)/(0.018d0-0.0025d0)
 
195
  endif
 
196
  propce(iel,iexp2)  = kk2*exp(-ee2/tg)*(xo2**bb)
 
197
!
 
198
! No thermique : Zeldovich
 
199
!
 
200
  propce(iel,iexp3)  = kk3*exp(-ee3/tg)*(xo2**0.5d0)
 
201
!
 
202
enddo
 
203
!
 
204
!===============================================================================
 
205
! 3. CALCUL AVEC LES PDF
 
206
!===============================================================================
 
207
!
 
208
if ( ipdf1 .eq. 1 .or. ipdf2 .eq. 1 .or. ipdf3 .eq. 1 ) then
 
209
!
 
210
  inok = 0
 
211
  i300 = 0
 
212
  i000 = 0
 
213
  imini= 0
 
214
  i2500= 0
 
215
  i2600= 0
 
216
  i2700= 0
 
217
  i2800= 0
 
218
  i3000= 0
 
219
  i3500= 0
 
220
  i4000= 0
 
221
  i5000= 0
 
222
  imaxi= 0
 
223
  nbpt = 0
 
224
  nbclip1 =0
 
225
  nbclip2 = 0
 
226
  ts4min= 1.d+20
 
227
  ts4max=-1.d+20
 
228
  sommin= 1.d+20
 
229
  sommax=-1.d+20
 
230
  ts4admin= 1.d+20
 
231
  ts4admax=-1.d+20
 
232
  toxmin = 1.d+20
 
233
  toxmax =-1.d+20
 
234
  yo2oxmin= 1.d+20
 
235
  yo2oxmax=-1.d20
 
236
!
 
237
  nbclip30 = 0
 
238
  nbclip31 = 0
 
239
  yo2min  = 1.d+20
 
240
  yo2max  =-1.d+20
 
241
  yo2min1 = 1.d+20
 
242
  yo2max1 =-1.d+20
 
243
!
 
244
  do iel=1,ncel
 
245
!
 
246
    if ( indpdf(iel) .eq. 1 ) then
 
247
!
 
248
!  Calcul de Yo2 dans l'oxydant
 
249
!            Yo2 en fs4
 
250
!
 
251
      bb1 = max(0.d0      ,pdfm1(iel))
 
252
      bb2 = min(fs3no(iel),pdfm2(iel))
 
253
      if ( bb2 .gt. bb1 ) then
 
254
        lro = hrec(iel)
 
255
      else
 
256
        lro = 0.d0
 
257
      endif
 
258
      qqq = bb2**2 - bb1**2
 
259
      rrr = bb2    - bb1
 
260
      gt1 = lro*qqq/(2.d0*fs3no(iel))
 
261
      gt2 = lro*rrr
 
262
      gt3 = doxyd(iel)
 
263
      if (  propce(iel, ipproc(iym1(io2))) .gt. 0.d0 ) then
 
264
        yo2ox = propce(iel, ipproc(iym1(io2)))/(-gt1+gt2+gt3)
 
265
!
 
266
        yo2oxmin = min(yo2oxmin,yo2ox)
 
267
        yo2oxmax = max(yo2oxmax,yo2ox)
 
268
!
 
269
        yo2moy = propce(iel, ipproc(iym1(io2)))
 
270
        yo2cb  = 0.d0
 
271
        dirac  =  dfuel(iel)*yo2cb + doxyd(iel)*yo2ox
 
272
!
 
273
        bb1 = max(0.D0      ,pdfm1(iel))
 
274
        bb2 = min(fs4no(iel),pdfm2(iel))
 
275
        bb3 = max(fs4no(iel),pdfm1(iel))
 
276
        bb4 = min(fs3no(iel),pdfm2(iel))
 
277
        if ( bb2 .gt. bb1 ) then
 
278
          lro = hrec(iel)
 
279
        else
 
280
          lro = 0.d0
 
281
        endif
 
282
        if ( bb4 .gt. bb3 ) then
 
283
          lrf = hrec(iel)
 
284
        else
 
285
          lrf = 0.d0
 
286
        endif
 
287
!
 
288
        qqq = bb2**2 - bb1**2
 
289
        rrr = bb2    - bb1
 
290
        sss = bb4**2 - bb3**2
 
291
        ttt = bb4    - bb3
 
292
        uuu = fs4no(iel)-fs3no(iel)
 
293
!
 
294
        gt1 = lro*qqq/(2.d0*fs4no(iel))
 
295
        gt2 = lro*rrr
 
296
!
 
297
        gt10= lrf*sss/(2.d0*uuu)
 
298
        gt20= lrf*ttt*fs3no(iel)/uuu
 
299
!
 
300
        yo24num = yo2moy - dirac + yo2ox*(gt1 -gt2)
 
301
        yo24den = gt1+gt10-gt20
 
302
!
 
303
        yo2s4  = yo24num/yo24den
 
304
!
 
305
      else
 
306
        yo2ox = 0.d0
 
307
        yo2s4 = 0.d0
 
308
      endif
 
309
!
 
310
!     Affichage et clipping
 
311
!
 
312
      yo2min = min(yo2s4,yo2min)
 
313
      yo2max = max(yo2s4,yo2max)
 
314
      if ( yo2s4 .lt. 0.d0 ) then
 
315
         nbclip30 = nbclip30+1
 
316
         yo2s4 = 0.d0
 
317
      endif
 
318
      if ( yo2s4 .gt. yo2ox ) then
 
319
         nbclip31 = nbclip31+1
 
320
         yo2s4 = yo2ox
 
321
      endif
 
322
      yo2min1 = min(yo2s4,yo2min1)
 
323
      yo2max1 = max(yo2s4,yo2max1)
 
324
 
 
325
!
 
326
!     Calcul de Tfioul moyen
 
327
!     ----------------------
 
328
!
 
329
      tfuel = 0.d0
 
330
      xmx2  = 0.d0
 
331
!
 
332
      do icla = 1, nclafu
 
333
        xmx2 = xmx2 + rtp(iel,isca(iyfol(icla)))
 
334
      enddo
 
335
      if ( xmx2 .gt. 0.d0 ) then
 
336
        do icla=1,nclafu
 
337
          ipctem=ipproc(itemp2(icla))
 
338
          tfuel = tfuel +rtp(iel,isca(iyfol(icla)))*propce(iel,ipctem)
 
339
        enddo
 
340
!
 
341
        tfuel = tfuel/xmx2
 
342
!
 
343
      else
 
344
        tfuel = propce(iel,ipproc(itemp1))
 
345
      endif
 
346
!
 
347
!    On recupere la valeur de Toxyd a partir de hoxyd
 
348
!
 
349
      hoxyd = enthox(iel)
 
350
!
 
351
      do ige = 1, ngazem
 
352
        coefe(ige) = zero
 
353
      enddo
 
354
      coefe(io2) =( af3(io2 )*f3m(iel)+af4(io2 )*f4m(iel)+af5(io2 )*f5m(iel) &
 
355
                   +af6(io2 )*f6m(iel)+af7(io2 )*f7m(iel)+af8(io2 )*f8m(iel) &
 
356
                   +af9(io2 )*f9m(iel) ) * wmole(io2)
 
357
 
 
358
      coefe(in2) =( af3(in2 )*f3m(iel)+af4(in2 )*f4m(iel)+af5(in2 )*f5m(iel) &
 
359
                   +af6(in2 )*f6m(iel)+af7(in2 )*f7m(iel)+af8(in2 )*f8m(iel) &
 
360
                   +af9(in2 )*f9m(iel) ) * wmole(in2)
 
361
 
 
362
      coefe(ico2)=( af3(ico2)*f3m(iel)+af4(ico2)*f4m(iel)+af5(ico2)*f5m(iel) &
 
363
                   +af6(ico2)*f6m(iel)+af7(ico2)*f7m(iel)+af8(ico2)*f8m(iel) &
 
364
                   +af9(ico2)*f9m(iel) ) * wmole(ico2)
 
365
 
 
366
      coefe(ih2o)=( af3(ih2o)*f3m(iel)+af4(ih2o)*f4m(iel)+af5(ih2o)*f5m(iel) &
 
367
                   +af6(ih2o)*f6m(iel)+af7(ih2o)*f7m(iel)+af8(ih2o)*f8m(iel) &
 
368
                   +af9(ih2o)*f9m(iel) ) * wmole(ih2o)
 
369
 
 
370
      coefe(ico)=(  af3(ico)*f3m(iel)+af4(ico)*f4m(iel)+af5(ico)*f5m(iel)    &
 
371
                   +af6(ico)*f6m(iel)+af7(ico)*f7m(iel)+af8(ico)*f8m(iel)    &
 
372
                   +af9(ico)*f9m(iel) ) * wmole(ico)
 
373
 
 
374
      coefe(ihy)=(  af3(ihy)*f3m(iel)+af4(ihy)*f4m(iel)+af5(ihy)*f5m(iel)    &
 
375
                   +af6(ihy)*f6m(iel)+af7(ihy)*f7m(iel)+af8(ihy)*f8m(iel)    &
 
376
                   +af9(ihy)*f9m(iel) ) * wmole(ihy)
 
377
!
 
378
!   Nbre de mole qui a reagis avec CO pour faire du CO2
 
379
!
 
380
      deltamol   = (coefe(io2)-yo2ox)/wmole(io2)
 
381
      react      = min(2.d0*deltamol,coefe(ico)/wmole(ico))
 
382
      coefe(io2 )= coefe(io2 )-react/2.d0*wmole(io2)
 
383
      coefe(ico )= coefe(ico )-react     *wmole(ico)
 
384
      coefe(ico2)= coefe(ico2)+react     *wmole(ico2)
 
385
 
 
386
!
 
387
      som = coefe(io2)+coefe(in2)+coefe(ico2)     &
 
388
           +coefe(ih2o)+coefe(ico)+coefe(ihy)
 
389
      coefe(io2 ) = coefe(io2 ) /som
 
390
      coefe(in2 ) = coefe(in2 ) /som
 
391
      coefe(ico2) = coefe(ico2) /som
 
392
      coefe(ih2o) = coefe(ih2o) /som
 
393
      coefe(ico ) = coefe(ico ) /som
 
394
      coefe(ihy ) = coefe(ihy ) /som
 
395
!
 
396
      do icha = 1, ncharm
 
397
        f1mc(icha) = zero
 
398
        f2mc(icha) = zero
 
399
      enddo
 
400
!
 
401
      mode = 1
 
402
      call cs_fuel_htconvers1 ( mode , hoxyd , coefe , toxyd )
 
403
      !======================
 
404
!
 
405
      toxmin = min(toxmin,toxyd)
 
406
      toxmax = max(toxmax,toxyd)
 
407
!
 
408
      if ( toxyd .gt. propce(iel,ipproc(itemp1)) ) then
 
409
        toxyd = propce(iel,ipproc(itemp1))
 
410
      endif
 
411
!
 
412
!    On initialise par les temperatures Toxy et Tfuel aux extremites
 
413
!
 
414
      dirac  =  dfuel(iel)*tfuel + doxyd(iel)*toxyd
 
415
!
 
416
!    On recupere la valeur de la temperature moyenne
 
417
!
 
418
      tmpgaz = propce(iel,ipproc(itemp1))
 
419
!
 
420
      bb1 = max(0.D0      ,pdfm1(iel))
 
421
      bb2 = min(fs4no(iel),pdfm2(iel))
 
422
      bb3 = max(fs4no(iel),pdfm1(iel))
 
423
      bb4 = min(1.d0      ,pdfm2(iel))
 
424
!
 
425
      if ( bb2 .gt. bb1 ) then
 
426
        lro = hrec(iel)
 
427
      else
 
428
        lro = 0.d0
 
429
      endif
 
430
      if ( bb4 .gt. bb3 ) then
 
431
        lrf = hrec(iel)
 
432
      else
 
433
        lrf = 0.d0
 
434
      endif
 
435
!
 
436
      qqq = bb2**2 - bb1**2
 
437
      rrr = bb2    - bb1
 
438
      sss = bb4**2 - bb3**2
 
439
      ttt = bb4    - bb3
 
440
      uuu = 1.d0   - fs4no(iel)
 
441
!
 
442
      gt1 = lro*qqq/(2.d0*fs4no(iel))
 
443
      gt2 = lro*rrr
 
444
!
 
445
      gt10= lrf*sss/(2.d0*uuu)
 
446
      gt20= lrf*ttt
 
447
      gt30= lrf*ttt/uuu
 
448
!
 
449
      ts4num = tmpgaz - dirac + toxyd*(gt1 -gt2      )    &
 
450
                              - tfuel*(gt10+gt20-gt30)
 
451
      ts4den = gt1-gt10+gt30
 
452
!
 
453
      ts4 = ts4num/ts4den
 
454
!
 
455
!   Calcul de l'enthalpie des vapeur a Tfuel
 
456
!
 
457
      hhf = 0.D0
 
458
      do icla=1,nclafu
 
459
        hhf = hhf + rtp(iel,isca(ih2(icla)))
 
460
      enddo
 
461
!
 
462
      if ( xmx2 .gt. epsifl ) then
 
463
!
 
464
        hfuel = hhf / xmx2
 
465
!
 
466
        hfs4ad = fs4no(iel)*hfuel+(1.d0-fs4no(iel))*hoxyd
 
467
!
 
468
        do ige = 1, ngazem
 
469
          coefe(ige) = zero
 
470
        enddo
 
471
        do ige = 1, ngazg
 
472
          coefe(ige) = yfs4no(iel,ige)
 
473
        enddo
 
474
!
 
475
        mode = 1
 
476
        call cs_fuel_htconvers1 ( mode , hfs4ad , coefe , tfs4ad )
 
477
        !======================
 
478
 
 
479
!
 
480
! Calcul pour affichage
 
481
!
 
482
        ts4min = min(ts4min,ts4)
 
483
        ts4max = max(ts4max,ts4)
 
484
!
 
485
        ts4admin= min(ts4admin,tfs4ad)
 
486
        ts4admax= max(ts4admax,tfs4ad)
 
487
!
 
488
        somm = 0.d0
 
489
        do ige = 1, ngazg
 
490
          somm = somm + yfs4no(iel,ige)
 
491
        enddo
 
492
        sommin=min(sommin,somm)
 
493
        sommax=max(sommax,somm)
 
494
!
 
495
        if ( (ts4 .gt. min(toxyd,tmpgaz,tfuel)) .and. &
 
496
             (ts4 .lt. 2400.d0) ) inok = inok + 1
 
497
        if ( ts4 .lt. min(toxyd,tmpgaz,tfuel) ) then
 
498
          if ( ts4 .ge. 300.d0 ) then
 
499
            i300  = i300  + 1
 
500
          else if ( ts4 .gt. 0 ) then
 
501
            i000  = i000  + 1
 
502
          else
 
503
            imini = imini + 1
 
504
          endif
 
505
        endif
 
506
!
 
507
        if ( ts4 .gt. 2400.d0 ) then
 
508
          if ( ts4 .lt. 2500 ) then
 
509
            i2500 = i2500 +1
 
510
          else if ( ts4 .lt. 2600 ) then
 
511
            i2600 = i2600 +1
 
512
          else if ( ts4 .lt. 2700 ) then
 
513
            i2700 = i2700 +1
 
514
          else if ( ts4 .lt. 2800 ) then
 
515
            i2800 = i2800 +1
 
516
          else if ( ts4 .lt. 3000 ) then
 
517
            i3000 = i3000 +1
 
518
          else if ( ts4 .lt. 3500 ) then
 
519
            i3500 = i3500 +1
 
520
          else if ( ts4 .lt. 4000 ) then
 
521
            i4000 = i4000 +1
 
522
          else if ( ts4 .lt. 5000 ) then
 
523
            i5000 = i5000 +1
 
524
          else
 
525
            imaxi = imaxi + 1
 
526
          endif
 
527
        endif
 
528
!
 
529
! Fin calcul pour affichage
 
530
!
 
531
!
 
532
! Clipping de Ts4 : a min(toxyd,tmpgaz,tfuel) en min
 
533
!                   a ts4ad                   en max
 
534
!
 
535
        nbpt = nbpt + 1
 
536
        if ( ts4 .lt. min(toxyd,tmpgaz,tfuel) ) then
 
537
           nbclip1 = nbclip1 + 1
 
538
           ts4 = min(toxyd,tmpgaz,tfuel)
 
539
        endif
 
540
!
 
541
        if ( ts4 .gt. tfs4ad ) then
 
542
           nbclip2 = nbclip2 + 1
 
543
           ts4 = tfs4ad
 
544
        endif
 
545
!
 
546
!   Concentration oxygene
 
547
!
 
548
        xo2 = propce(iel,ipproc(iym1(io2  )))                 &
 
549
             *propce(iel,ipproc(immel))/wmole(io2)
 
550
!
 
551
!  Integration
 
552
!
 
553
        do i = 1, npart+1
 
554
          gs(i) = pdfm1(iel)+dble(i-1)/dble(npart)*(pdfm2(iel)-pdfm1(iel))
 
555
!        calcul de T
 
556
          if( gs(i) .lt. fs4no(iel) ) then
 
557
            tt(i) = (ts4-toxyd)/fs4no(iel)* gs(i) + toxyd
 
558
          else
 
559
            tt(i) = (tfuel-ts4)/(1.d0-fs4no(iel))*gs(i)       &
 
560
                   + tfuel - (tfuel-ts4)/(1.d0-fs4no(iel))
 
561
          endif
 
562
!        calul de yo2
 
563
          if ( gs(i) .lt. fs4no(iel) )  then
 
564
            yyo2(i) = (yo2s4-yo2ox)/fs4no(iel) * gs(i) + yo2ox
 
565
          else if ( gs(i) .lt. fs3no(iel) ) then
 
566
            aa = yo2s4/(fs4no(iel)-fs3no(iel))
 
567
            yyo2(i) = aa * ( gs(i) -fs3no(iel) )
 
568
          else
 
569
            yyo2(i) = 0.d0
 
570
          endif
 
571
        enddo
 
572
!
 
573
!     pas d'integration
 
574
!
 
575
        dgs = ( pdfm2(iel) - pdfm1(iel) ) / dble(npart)
 
576
!
 
577
! Calcul de K1*EXP(-E1/T)
 
578
!
 
579
        if ( ipdf1 .eq. 1 ) then
 
580
!
 
581
          propce(iel,iexp1)= kk1*exp(-ee1/toxyd)*doxyd(iel)        &
 
582
                            +kk1*exp(-ee1/tfuel)*dfuel(iel)
 
583
 
 
584
          do i = 1, npart+1
 
585
            val(i) = kk1*exp(-ee1/tt(i))*hrec(iel)
 
586
          enddo
 
587
 
 
588
          do i = 1, npart
 
589
            propce(iel,iexp1) = propce(iel,iexp1)                 &
 
590
                               +0.5d0*dgs*(val(i)+val(i+1))
 
591
          enddo
 
592
 
 
593
        endif
 
594
!
 
595
!  Calcul de K2*EXP(-E2/T)
 
596
!
 
597
          if ( ipdf2 .eq. 1 ) then
 
598
!
 
599
            if ( xo2 .gt. 0.d0 ) then
 
600
!
 
601
              if(xo2.gt.0.018d0) then
 
602
                bb=0.d0
 
603
              else if(xo2 .lt. 0.0025d0) then
 
604
                bb=1.d0
 
605
              else
 
606
                bb=(0.018d0-xo2)/(0.018d0-0.0025d0)
 
607
              endif
 
608
!
 
609
              propce(iel,iexp2) = kk2*exp(-ee2/toxyd)*doxyd(iel)*(xo2**bb) &
 
610
                                 +kk2*exp(-ee2/tfuel)*dfuel(iel)*(xo2**bb)
 
611
!
 
612
              do i = 1, npart+1
 
613
                val(i) = kk2*exp(-ee2/tt(i))*hrec(iel)
 
614
              enddo
 
615
 
 
616
              do i = 1, npart
 
617
                propce(iel,iexp2) = propce(iel,iexp2)                      &
 
618
                                   +0.5d0*dgs*(val(i)+val(i+1))*(xo2**bb)
 
619
              enddo
 
620
            else
 
621
              propce(iel,iexp2) = 0.d0
 
622
            endif
 
623
 
 
624
          endif
 
625
!
 
626
!  Calcul de K3*EXP(-E3/T)
 
627
!
 
628
          if ( ipdf3 .eq. 1 ) then
 
629
 
 
630
            if ( xo2 .gt. 0.d0 ) then
 
631
!
 
632
              propce(iel,iexp3) = kk3*exp(-ee3/toxyd)                  &
 
633
                                         *doxyd(iel)*(yo2ox**0.5d0)    &
 
634
                                 +kk3*exp(-ee3/tfuel)                  &
 
635
                                         *dfuel(iel)*(yo2cb**0.5d0)
 
636
!
 
637
              do i = 1, npart+1
 
638
                if ( gs(i) .le. fs3no(iel) ) then
 
639
                  val(i) = kk3*exp(-ee3/tt(i))*hrec(iel)*(yyo2(i)**0.5d0)
 
640
                else
 
641
                  val(i) = 0.d0
 
642
                endif
 
643
              enddo
 
644
 
 
645
              do i = 1, npart
 
646
                propce(iel,iexp3) = propce(iel,iexp3)                  &
 
647
                                   +0.5d0*dgs*(val(i)+val(i+1))
 
648
              enddo
 
649
!
 
650
            else
 
651
              propce(iel,iexp3)= 0.d0
 
652
            endif
 
653
          endif
 
654
!
 
655
      endif
 
656
!
 
657
    endif
 
658
  enddo
 
659
!
 
660
  if ( irangp .ge. 0 ) then
 
661
    call parcpt(inok)
 
662
    call parcpt(i300)
 
663
    call parcpt(i000)
 
664
    call parcpt(imini)
 
665
    call parcpt(i2500)
 
666
    call parcpt(i2600)
 
667
    call parcpt(i2700)
 
668
    call parcpt(i2800)
 
669
    call parcpt(i3000)
 
670
    call parcpt(i3500)
 
671
    call parcpt(i4000)
 
672
    call parcpt(i5000)
 
673
    call parcpt(imaxi)
 
674
    call parcpt(nbpt)
 
675
    call parcpt(nbclip1)
 
676
    call parcpt(nbclip2)
 
677
    call parmin(ts4min)
 
678
    call parmax(ts4max)
 
679
    call parmin(ts4admin)
 
680
    call parmax(ts4admax)
 
681
    call parmin(sommin)
 
682
    call parmax(sommax)
 
683
!
 
684
    call parcpt(nbclip30)
 
685
    call parcpt(nbclip31)
 
686
    call parmin(yo2min)
 
687
    call parmax(yo2max)
 
688
    call parmin(yo2min1)
 
689
    call parmax(yo2max1)
 
690
!
 
691
    call parmin(toxmin)
 
692
    call parmax(toxmax)
 
693
    call parmin(yo2oxmin)
 
694
    call parmax(yo2oxmax)
 
695
  endif
 
696
!===============================================================================
 
697
  write(nfecra,*) ' '
 
698
  write(nfecra,*) ' Min max de TSox ',toxmin,toxmax
 
699
  write(nfecra,*) ' Min max de TS4 ',ts4min,ts4max
 
700
  write(nfecra,*) '    nombre de pts a Tmini < ts4 < 2400  ',inok
 
701
  write(nfecra,*) '    nombre de pts a         ts4 < 0     ',imini
 
702
  write(nfecra,*) '    nombre de pts a 0     < ts4 < 300   ',i000
 
703
  write(nfecra,*) '    nombre de pts a 300   < ts4 < Tmini ',i300
 
704
  write(nfecra,*) '    nombre de pts a 2400  < ts4 < 2500  ',i2500
 
705
  write(nfecra,*) '    nombre de pts a 2500  < ts4 < 2600  ',i2600
 
706
  write(nfecra,*) '    nombre de pts a 2600  < ts4 < 2700  ',i2700
 
707
  write(nfecra,*) '    nombre de pts a 2700  < ts4 < 2800  ',i2800
 
708
  write(nfecra,*) '    nombre de pts a 2800  < ts4 < 3000  ',i3000
 
709
  write(nfecra,*) '    nombre de pts a 3000  < ts4 < 3500  ',i3500
 
710
  write(nfecra,*) '    nombre de pts a 3500  < ts4 < 4000  ',i4000
 
711
  write(nfecra,*) '    nombre de pts a 4000  < ts4 < 5000  ',i5000
 
712
  write(nfecra,*) '    nombre de pts a 5000  < ts4         ',imaxi
 
713
  write(nfecra,*) ' Min max de TS4ad ',ts4admin,ts4admax
 
714
  write(nfecra,*) ' Min max concentration en fs4 ',sommin,sommax
 
715
  write(nfecra,*) ' Clipping en min en ',nbclip1,' points sur ',nbpt,' points'
 
716
  write(nfecra,*) ' Clipping en max en ',nbclip2,' points sur ',nbpt,' points'
 
717
!
 
718
  write(nfecra,*) ' '
 
719
  write(nfecra,*) ' Min max de Yo2ox en 0 ',yo2oxmin,yo2oxmax
 
720
  write(nfecra,*) ' Min max de Yo2 en fs4 avant clipping ',yo2min,yo2max
 
721
  write(nfecra,*) ' Clipping en min sur Yo2 en fs4       ',nbclip30
 
722
  write(nfecra,*) ' Clipping en max sur Yo2 en fs4       ',nbclip31
 
723
  write(nfecra,*) ' Min max de Yo2 en fs4 apres clipping ',yo2min1,yo2max1
 
724
!===============================================================================
 
725
!
 
726
endif
 
727
 
 
728
return
 
729
end subroutine