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

« back to all changes in this revision

Viewing changes to src/fuel/fulecd.f90

  • Committer: Package Import Robot
  • Author(s): Sylvestre Ledru
  • Date: 2011-11-01 17:43:32 UTC
  • mto: (6.1.7 sid)
  • mto: This revision was merged to the branch mainline in revision 11.
  • Revision ID: package-import@ubuntu.com-20111101174332-tl4vk45no0x3emc3
Tags: upstream-2.1.0
Import upstream version 2.1.0

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
!-------------------------------------------------------------------------------
2
 
 
3
 
!     This file is part of the Code_Saturne Kernel, element of the
4
 
!     Code_Saturne CFD tool.
5
 
 
6
 
!     Copyright (C) 1998-2009 EDF S.A., France
7
 
 
8
 
!     contact: saturne-support@edf.fr
9
 
 
10
 
!     The Code_Saturne Kernel is free software; you can redistribute it
11
 
!     and/or modify it under the terms of the GNU General Public License
12
 
!     as published by the Free Software Foundation; either version 2 of
13
 
!     the License, or (at your option) any later version.
14
 
 
15
 
!     The Code_Saturne Kernel is distributed in the hope that it will be
16
 
!     useful, but WITHOUT ANY WARRANTY; without even the implied warranty
17
 
!     of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18
 
!     GNU General Public License for more details.
19
 
 
20
 
!     You should have received a copy of the GNU General Public License
21
 
!     along with the Code_Saturne Kernel; if not, write to the
22
 
!     Free Software Foundation, Inc.,
23
 
!     51 Franklin St, Fifth Floor,
24
 
!     Boston, MA  02110-1301  USA
25
 
 
26
 
!-------------------------------------------------------------------------------
27
 
 
28
 
subroutine fulecd
29
 
!================
30
 
!===============================================================================
31
 
!  FONCTION  :
32
 
!  ---------
33
 
 
34
 
! LECTURE DU FICHIER DE DONNEES PHYSIQUE PARTICULIERE
35
 
!      RELATIF A LA COMBUSTION FUEL
36
 
 
37
 
!-------------------------------------------------------------------------------
38
 
! Arguments
39
 
!__________________.____._____.________________________________________________.
40
 
! name             !type!mode ! role                                           !
41
 
!__________________!____!_____!________________________________________________!
42
 
!__________________!____!_____!________________________________________________!
43
 
 
44
 
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
45
 
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
46
 
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
47
 
!            --- tableau de travail
48
 
!===============================================================================
49
 
 
50
 
implicit none
51
 
 
52
 
!===============================================================================
53
 
! Common blocks
54
 
!===============================================================================
55
 
 
56
 
include "paramx.h"
57
 
include "pointe.h"
58
 
include "entsor.h"
59
 
include "cstnum.h"
60
 
include "cstphy.h"
61
 
include "ppppar.h"
62
 
include "ppthch.h"
63
 
include "coincl.h"
64
 
include "cpincl.h"
65
 
include "fuincl.h"
66
 
include "ppincl.h"
67
 
include "ppcpfu.h"
68
 
 
69
 
!===============================================================================
70
 
 
71
 
! Arguments
72
 
 
73
 
! Local variables
74
 
 
75
 
character *150 chain1,chain2
76
 
character *12   nomcoe(ngazem)
77
 
 
78
 
integer          it     , ice    , iat    , ios
79
 
integer          ncoel  , inicoe
80
 
integer          icla
81
 
integer          idebch , ifinch , lonch  , ichai  , ichcoe
82
 
integer          atcoel(ngazem,natom), inicha
83
 
 
84
 
double precision tmin   , tmax
85
 
double precision wmolce(ngazem), ehcoel(ngazem,npot)
86
 
double precision cpcoel(ngazem,npot)
87
 
double precision ncfov,nhfov,nofov,nsfov
88
 
double precision mhsfov,mcofov,mchfov,mtofov
89
 
double precision nhsfov,ncofov,ncmv,nhmv
90
 
double precision ch2fv,ch4fv,h02fov,yo2ox
91
 
 
92
 
!===============================================================================
93
 
!==================================================
94
 
! 1. LECTURE DU FICHIER DONNEES SPECIFIQUES
95
 
!==================================================
96
 
 
97
 
! --> Ouverture du fichier
98
 
 
99
 
open ( unit=impfpp, file=ficfpp,                                  &
100
 
        STATUS='OLD', FORM='FORMATTED', ACCESS='SEQUENTIAL',      &
101
 
                                        iostat=ios, err=99 )
102
 
rewind (unit=impfpp,err=99 )
103
 
 
104
 
! --> Lecture thermochimie
105
 
 
106
 
read (impfpp,*,err=999,end=999 )
107
 
 
108
 
! ---- Nb de constituants elementaires (gazeux,liquide et solide)
109
 
 
110
 
read ( impfpp,*,err=999,end=999 ) ncoel
111
 
if ( ncoel.gt.ngazgm ) then
112
 
  write(nfecra,9991) ngazgm,ncoel
113
 
  call csexit (1)
114
 
endif
115
 
 
116
 
! ---- Nb de points de tabulation ENTH-TEMP
117
 
 
118
 
read ( impfpp,*,err=999,end=999 ) npo
119
 
if ( npo.gt.npot ) then
120
 
  write(nfecra,9992) npot,npo
121
 
  call csexit (1)
122
 
endif
123
 
 
124
 
! --- Lecture des noms des constituants elementaires
125
 
 
126
 
do ice=1,ncoel
127
 
  do inicoe=1,len(nomcoe(ice))
128
 
    NOMCOE(ICE)(INICOE:INICOE)=' '
129
 
  enddo
130
 
enddo
131
 
 
132
 
do inicha=1,len(chain1)
133
 
  CHAIN1(INICHA:INICHA)=' '
134
 
enddo
135
 
 
136
 
do inicha=1,len(chain2)
137
 
  CHAIN2(INICHA:INICHA)=' '
138
 
enddo
139
 
 
140
 
read (impfpp,*,err=999,end=999)
141
 
!     READ (IMPFPP,*,ERR=999,END=999) CHAIN2
142
 
read (impfpp,1010,err=999,end=999 ) chain1
143
 
call verlon (chain1, idebch, ifinch, lonch)
144
 
chain2(1:lonch)=chain1(idebch:ifinch)
145
 
 
146
 
ice=1
147
 
ichcoe=0
148
 
do ichai = 1, lonch
149
 
  IF (CHAIN2(ICHAI:ICHAI).NE.' ') THEN
150
 
    ichcoe=ichcoe+1
151
 
    nomcoe(ice)(ichcoe:ichcoe) =chain2(ichai:ichai)
152
 
  else
153
 
    if (ichcoe.ne.0) then
154
 
      ice=ice+1
155
 
      ichcoe=0
156
 
    endif
157
 
  endif
158
 
enddo
159
 
 
160
 
 1010 format(a150)
161
 
 
162
 
! --- Temperature Min et Max
163
 
 
164
 
read (impfpp,*,err=999,end=999) tmin
165
 
read (impfpp,*,err=999,end=999) tmax
166
 
 
167
 
 
168
 
! ---- Nb especes atomiques (C, H, O, N, ...)
169
 
 
170
 
read (impfpp,*,err=999,end=999 ) nato
171
 
if ( nato.gt.natom ) then
172
 
  write(nfecra,9993) natom,nato
173
 
  call csexit (1)
174
 
  !==========
175
 
endif
176
 
 
177
 
! ---- Masse molaire especes atomiques
178
 
!      Composition des constituants elementaires en fonction
179
 
!        des especes elementaires
180
 
 
181
 
do iat = 1, nato
182
 
  read (impfpp,*,err=999,end=999 ) wmolat(iat),                   &
183
 
                      ( atcoel(ice,iat),ice=1,ncoel )
184
 
enddo
185
 
 
186
 
! ---- Calcul des masses molaires des constituants elementaires
187
 
 
188
 
do ice = 1, ncoel
189
 
  wmolce(ice) = 0.d0
190
 
  do iat = 1, nato
191
 
    wmolce(ice)= wmolce(ice) + atcoel(ice,iat)*wmolat(iat)
192
 
  enddo
193
 
enddo
194
 
 
195
 
 
196
 
! --> Lecture rayonnement
197
 
 
198
 
read (impfpp,*,err=999,end=999 )
199
 
 
200
 
! ---- Coefficient d'absorption du melange gazeux
201
 
 
202
 
read (impfpp,*,err=999,end=999 ) ckabs1
203
 
 
204
 
 
205
 
! --> Lecture caracteristiques fuel
206
 
 
207
 
read (impfpp,*,err=999,end=999 )
208
 
 
209
 
! ---- Nb de classes de fuel
210
 
 
211
 
read (impfpp,*,err=999,end=999 ) nclafu
212
 
 
213
 
! --> Diametre initial  (mm)
214
 
 
215
 
read (impfpp,*,err=999,end=999 ) ( dinifl(icla),icla=1,nclafu )
216
 
 
217
 
! --> Composition elementaire en C, H, O, S, In (% en masse)
218
 
!     In d�signe les inertes (m�taux, etc.) qui resteront
219
 
!        dans le r�sidu solide
220
 
 
221
 
read (impfpp,*,err=999,end=999 ) cfol
222
 
read (impfpp,*,err=999,end=999 ) hfol
223
 
read (impfpp,*,err=999,end=999 ) ofol
224
 
read (impfpp,*,err=999,end=999 ) sfol
225
 
 
226
 
cfol = 1.d-2 * cfol
227
 
hfol = 1.d-2 * hfol
228
 
ofol = 1.d-2 * ofol
229
 
sfol = 1.d-2 * sfol
230
 
xinfol = 1.d0-cfol-hfol-ofol-sfol
231
 
if (xinfol .lt. zero) then
232
 
   WRITE(NFECRA,*)'Erreur dans les fractions massiques du FOL'
233
 
!         STOP
234
 
endif
235
 
WRITE (NFECRA,*) 'Fractions massiques elementaires / FOL  '
236
 
WRITE (NFECRA,*) ' C = ',CFOL
237
 
WRITE (NFECRA,*) ' H = ',HFOL
238
 
WRITE (NFECRA,*) ' O = ',OFOL
239
 
WRITE (NFECRA,*) ' S = ',SFOL
240
 
WRITE (NFECRA,*) ' In= ',XINFOL
241
 
 
242
 
 
243
 
! --> PCI
244
 
 
245
 
read (impfpp,*,err=999,end=999 ) pcifol
246
 
 
247
 
! --> CP moyen du fuel sec (J/kg/K)
248
 
 
249
 
read (impfpp,*,err=999,end=999 ) cp2fol
250
 
 
251
 
! --> Masse volumique initiale (kg/m3)
252
 
 
253
 
read (impfpp,*,err=999,end=999 ) rho0fl
254
 
 
255
 
! --> Caracteristiques du coke
256
 
 
257
 
read (impfpp,*,err=999,end=999)
258
 
 
259
 
! ------- Composition elementaire en C, H, O, S (% / pur)
260
 
 
261
 
read (impfpp,*,err=999,end=999 ) ckf
262
 
read (impfpp,*,err=999,end=999 ) hkf
263
 
read (impfpp,*,err=999,end=999 ) okf
264
 
read (impfpp,*,err=999,end=999 ) skf
265
 
 
266
 
ckf = 1.d-2 * ckf
267
 
hkf = 1.d-2 * hkf
268
 
okf = 1.d-2 * okf
269
 
skf = 1.d-2 * skf
270
 
 
271
 
if ( abs(ckf+hkf+okf+skf-1.d0) .gt. 1.d-15 ) then
272
 
  write(nfecra,9990) ckf+hkf+okf+skf
273
 
  call csexit(1)
274
 
endif
275
 
 
276
 
! ------ PCI
277
 
 
278
 
read (impfpp,*,err=999,end=999 ) pcikf
279
 
 
280
 
! ---- Fraction de coke dans le fuel
281
 
 
282
 
read (impfpp,*,err=999,end=999) fkc
283
 
WRITE (NFECRA,*)' Fraction massique de coke / FOL'
284
 
write (nfecra,*) fkc
285
 
 
286
 
!     Les inertes restent dans le coke
287
 
xinkf = zero
288
 
if ( fkc .gt. zero) xinkf = xinfol/fkc
289
 
if ( (ckf+hkf+okf+skf) .gt. 1.d0) then
290
 
   WRITE(NFECRA,*)'Erreur dans les fractions massiques du KF'
291
 
!         STOP
292
 
endif
293
 
 
294
 
WRITE (NFECRA,*) 'Fractions massiques elementaires / coke '
295
 
WRITE (NFECRA,*) ' C = ',CKF*(1.D0-XINKF)
296
 
WRITE (NFECRA,*) ' H = ',HKF*(1.D0-XINKF)
297
 
WRITE (NFECRA,*) ' O = ',OKF*(1.D0-XINKF)
298
 
WRITE (NFECRA,*) ' S = ',SKF*(1.D0-XINKF)
299
 
WRITE (NFECRA,*) ' In= ',XInKF
300
 
 
301
 
!     Compatibilite des fractions massiques et des formules mol�culaires
302
 
!     masses �l�mentaires dans le fuel, le coke, les vapeurs
303
 
!        F      K        MV
304
 
!   C    CFOL   CKF*FKC  CFOL-CKF*FKC
305
 
!   H    HFOL   HKF*FKC  HFOL-HKF*FKC
306
 
!   O    OFOL   OKF*FKC  OFOL-OKF*FKC
307
 
!   S    SFOL   SKF*FKC  SFOL-SKF*FKC
308
 
!   In   XInFOL  XInFOL    0
309
 
!      elements dans les vapeurs
310
 
ncfov  = (cfol-ckf*fkc*(1.d0-xinkf))/wmolat(iatc)/(1.d0-fkc)
311
 
nhfov  = (hfol-hkf*fkc*(1.d0-xinkf))/wmolat(iath)/(1.d0-fkc)
312
 
nofov  = (ofol-okf*fkc*(1.d0-xinkf))/wmolat(iato)/(1.d0-fkc)
313
 
nsfov  = (sfol-skf*fkc*(1.d0-xinkf))/wmolat(iats)/(1.d0-fkc)
314
 
!       on consid�re que S se d�gage sous forme H2S
315
 
!                    que O                      CO
316
 
nhsfov = nsfov
317
 
ncofov = nofov
318
 
ncmv   = ncfov - ncofov
319
 
nhmv   = nhfov - 2.d0*nhsfov
320
 
 
321
 
!   Les vapeurs sont alors constitu�es de nHSFOV moles de H2S
322
 
!                                         nCOFOV          CO
323
 
!                                         nCMV            CHn
324
 
!   o� CHn est un hydrocarbure mod�le de formule moyenne avec
325
 
nhcfov  = nhmv/ncmv
326
 
WRITE(NFECRA,*) ' nHCFOV = ',NHCFOV ,NHMV,NCMV
327
 
 
328
 
!   Les masses dans les vapeurs sont
329
 
mhsfov = (wmolat(iats)+2.d0*wmolat(iath))*nhsfov
330
 
mcofov = (wmolat(iatc)+wmolat(iato))*ncofov
331
 
mchfov = wmolat(iatc)*ncmv+wmolat(iath)*nhmv
332
 
mtofov = mhsfov+mcofov+mchfov
333
 
 
334
 
WRITE(NFECRA,*) ' mtoFOV = ',MTOFOV
335
 
 
336
 
!   Les fractions massiques dans les vapeurs sont
337
 
hsfov = mhsfov / mtofov
338
 
cofov = mcofov / mtofov
339
 
chfov = mchfov / mtofov
340
 
WRITE (NFECRA,*) 'Fractions massiques sp�cifiques / FOV '
341
 
WRITE (NFECRA,*) ' H2S = ',HSFOV
342
 
WRITE (NFECRA,*) ' CO  = ',COFOV
343
 
WRITE (NFECRA,*) ' CHn = ',CHFOV
344
 
WRITE (NFECRA,*) ' ..n = ',nHCFOV
345
 
ch4fv = zero
346
 
ch2fv = chfov
347
 
if ( nhcfov.ge.2.d0 .and. nhcfov.le.4.d0 ) then
348
 
  WRITE(NFECRA,*) 'Le FOV est equivalent a un melange '
349
 
  ch2fv = 2.d0-0.5d0*nhcfov
350
 
   ch4fv = (1-ch2fv)*16.d0/(12.d0+nhcfov)
351
 
   ch2fv = ch2fv*14.d0/(12.d0+nhcfov)
352
 
   ch4fv = ch4fv * chfov
353
 
   ch2fv = ch2fv * chfov
354
 
   WRITE (NFECRA,*) ' H2S = ',HSFOV
355
 
   WRITE (NFECRA,*) ' CO  = ',COFOV
356
 
   WRITE (NFECRA,*) ' CH4 = ',CH4FV
357
 
   WRITE (NFECRA,*) 'C2H4 = ',CH2FV
358
 
endif
359
 
WRITE(NFECRA,*) ' nHCFOV 2 = ',NHCFOV
360
 
 
361
 
! ---- Parametre d'evaporation
362
 
 
363
 
 read (impfpp,*,err=999,end=999) tevap1
364
 
 read (impfpp,*,err=999,end=999) tevap2
365
 
 
366
 
! ---- Parametres combustion heterogene (modele a sphere retrecissante)
367
 
 
368
 
read (impfpp,*,err=999,end=999 )
369
 
 
370
 
read (impfpp,*,err=999,end=999 ) ahetfl
371
 
read (impfpp,*,err=999,end=999 ) ehetfl
372
 
read (impfpp,*,err=999,end=999 ) iofhet
373
 
 
374
 
! --> Fermeture du fichier (ne pas oublier, car l'unite sert pour janaf)
375
 
 
376
 
close(impfpp)
377
 
 
378
 
!==============================================
379
 
! 2.
380
 
!==============================================
381
 
 
382
 
 
383
 
! --> Discretisation de la temperature
384
 
 
385
 
do it = 1, npo
386
 
  th(it) = dble(it-1)*(tmax-tmin)/dble(npo-1) + tmin
387
 
enddo
388
 
 
389
 
! --> Calcul des enthalpies pour les differentes especes courantes
390
 
 
391
 
call pptbht                                                       &
392
 
!==========
393
 
 ( ncoel  ,                                                       &
394
 
   nomcoe , ehcoel , cpcoel , wmolce )
395
 
 
396
 
! --> Calcul tabulation enthalpie - temperature pour le melange gazeux
397
 
 
398
 
! ---- Nb de constituants gazeux
399
 
!     ATTENTION ON COMPTE EGALEMENT H2S et le monomere SO2
400
 
 
401
 
ngaze = 8
402
 
 
403
 
! ---- Definition des pointeurs pour les tableaux WMOLE et EHGAZE
404
 
!      REMARQUE : Cette position de pointeurs va egalement servir
405
 
!                 pour le tableau de pointeurs IYM1 relatif aux
406
 
!                 tableaux PROPCE et PROPFB
407
 
!                 ON BALAYE JUSTE DE 1 A NGAZE
408
 
 
409
 
!     ATTENTION : ordre des esp�ces dans EHCOEL, WMOLCE
410
 
!                 vient du fichier data_FUE
411
 
!     Actuellement 1   CH4
412
 
!                  2   C2H4
413
 
!                  3   CO
414
 
!                  4   O2
415
 
!                  5   CO2
416
 
!                  6   H2O
417
 
!                  7   N2
418
 
!                  8   C (solide)
419
 
!                  9   H2S
420
 
!                 10   SO2
421
 
ifov = 1
422
 
ico  = 2
423
 
ih2s = 3
424
 
ih2o = 4
425
 
ico2 = 5
426
 
iso2 = 6
427
 
io2  = 7
428
 
in2  = 8
429
 
 
430
 
! ---- Remplissage de EHGAZE et WMOLE
431
 
!         a partir de EHCOEL et WMOLCE
432
 
 
433
 
do it = 1, npo
434
 
  ehgaze(ifov ,it) = ( ch4fv*ehcoel(1,it) + ch2fv*ehcoel(2,it) )
435
 
  ehgaze(ico  ,it) = ehcoel( 3,it)
436
 
  ehgaze(io2  ,it) = ehcoel( 4,it)
437
 
  ehgaze(ico2 ,it) = ehcoel( 5,it)
438
 
  ehgaze(ih2o ,it) = ehcoel( 6,it)
439
 
  ehgaze(in2  ,it) = ehcoel( 7,it)
440
 
  ehgaze(ih2s ,it) = ehcoel( 9,it)
441
 
  ehgaze(iso2 ,it) = ehcoel(10,it)
442
 
enddo
443
 
wmole(ifov ) = (ch4fv+ch2fv)/(ch4fv/wmolce(1)+ch2fv/wmolce(2))
444
 
 
445
 
wmole(ifov ) = (1.d0*0.012d0 + nhcfov *0.001d0 )
446
 
WRITE(NFECRA,*) ' Wmole IFOV = ',WMOLE(IFOV ),CH4FV,CH2FV
447
 
wmole(ico  ) = wmolce( 3)
448
 
wmole(io2  ) = wmolce( 4)
449
 
wmole(ico2 ) = wmolce( 5)
450
 
wmole(ih2o ) = wmolce( 6)
451
 
wmole(in2  ) = wmolce( 7)
452
 
wmole(ih2s ) = wmolce( 9)
453
 
wmole(iso2 ) = wmolce(10)
454
 
 
455
 
!     Concentrations dans les vapeurs
456
 
afovf1 = chfov / wmole(ifov)
457
 
acof1  = cofov / wmole(ico)
458
 
ah2sf1  = hsfov / wmole(ih2s)
459
 
!      Caract�risation de l'oxydant
460
 
yo2ox = wmole(io2) / (wmole(io2)+xsi*wmole(in2))
461
 
!     Caract�ristion des gaz issus de la combustion h�t�rog�ne
462
 
!      Max est le point o� F3 est maximal ; il correspond � un
463
 
!      m�lange stoechiometrique de coke et d'oxydant
464
 
!      On suppose, pour l'instant, que l'oxydant est un melange O2, N2
465
 
!      � modifier si recyclage de fum�es
466
 
!      FF3MAX(CKF*C+OKF*O+SKF*S+HKF*H) + (1-F3max)*(YO2Ox*O2+(1-YO2Ox)*N2) =>
467
 
!            CO + H2O + H2S + N2
468
 
!      On suppose que S est prioritaire pour H
469
 
!      Masse de C dans les r�actants FF3MAX*CKF
470
 
!      Masse de O                    FF3MAX*OKF + (1-F3max)*YO2Ox
471
 
!      Masse de S                    FF3MAX*SKF
472
 
!      Masse de H                    FF3MAX*HKF
473
 
!      Masse de N                    (1-FF3MAX)*(1-YO2Ox)
474
 
!      Nombre de C                   FF3MAX*CKF / WMOLAT(IATC)
475
 
!      Nombre de O                   (FF3MAX*OKF+(1-F3max*YO2Ox)/WMOLAT(IATO)
476
 
!      Nombre de S                   FF3MAX*SKF / WMOLAT(IATS)
477
 
!      Nombre de H                   FF3MAX*HKF / WMOLAT(IATH)
478
 
!      Nombre de moles de H2S dans les produits = nombre de moles de S
479
 
!      Nombre de moles de H2O dans les produits = 1/2 nombre H-nb moles H2S
480
 
!      Nombre de moles de CO = nombre de moles de C
481
 
!      Nombre de moles de O dans les produits = nb moles CO + H2O
482
 
!      Et il vient :
483
 
!      FF3MAX * ( CKF/WMOLAT(IATC) + 0.5*HKF/WOLAT(IATH) - SKF/WMOLAT(IATS)
484
 
!                -OKF/WMOALT(IATO) - YO2Ox/WOLAT(IATO) )
485
 
!      =     YO2Ox/WMOLAT(IATO)
486
 
 
487
 
!      FF3MAX = YO2Ox /(0.016*(CKF/.012 + 0.5*HKF/.001 -SKF/.032)-OKF+YO2Ox)
488
 
 
489
 
 ff3max = yo2ox/(wmolat(iato)*(ckf/wmolat(iatc)                   &
490
 
                       +0.5d0*hkf/wmolat(iath)                    &
491
 
                             -skf/wmolat(iats))                   &
492
 
                -okf + yo2ox)
493
 
 
494
 
!      AXXF3 nb de moles de l'esp�ce XX en kilog de F3 calcules en FF3MAX
495
 
 ah2sf3 = ff3max*skf/wmolat(iats)
496
 
 ah2of3 = 0.5d0*ff3max*hkf/wmolat(iath)-ah2sf3
497
 
 acof3  = ff3max*ckf/wmolat(iatc)
498
 
 
499
 
!       AO2F3  = 0.5d0*FF3MAX*(     OKF/WMOLAT(IATO)-CKF/WMOLAT(IATC)
500
 
!     &                       -0.5*HKF/WMOLAT(IATH)+SKF/WMOLAT(IATS))
501
 
 ao2f3  = 0.d0
502
 
 
503
 
 an2f3  = (1.d0-yo2ox)/wmole(in2) * (1.d0-ff3max)
504
 
 
505
 
 ao2f4 = yo2ox/wmole(io2)
506
 
 an2f4 = (1.d0-yo2ox)/wmole(in2)
507
 
 
508
 
!      Avec cette convention la concentration en O2 est n�gative en FF3MAX
509
 
!      ceci correspond � l'oxyg�ne absorb� par la r�action h�t�rog�ne.
510
 
 
511
 
! --> Calcul tabulation enthalpie - temperature pour la phase dispersee
512
 
!     Fuel Oil Liquid et  Coke
513
 
 
514
 
! ---- Nb de constituants solide
515
 
 
516
 
nsolid = 2
517
 
 
518
 
! ---- Definition des pointeurs IFOL et IKF
519
 
 
520
 
ifol = 1
521
 
ikf = 2
522
 
 
523
 
! ------ Calcul de H02FOL
524
 
 
525
 
!       H0, EH & PCI en J/kg
526
 
!       CFOL, HFOL sont des fractions massiques �l�mentaires
527
 
!       rapports des masses molaires des produits aux �l�ments du
528
 
!                combustible (le comburant est dans l'�tat de r�f.)
529
 
 
530
 
! ------ Calcul de HRFVAP
531
 
 
532
 
!  L'enthalpie de formation du fuel gazeux est connue (m�lange CH4, C2H4),
533
 
!  Le PCI du fuel liquide est connu , on peut donc reconstituer son
534
 
!   enthalpie de formation (on n�glige l'effet de H2S => SO2)
535
 
!   on introduit les enthalpies de formation massique du CO2 et de H2O
536
 
 
537
 
  h02fol = pcifol                                                 &
538
 
         + cfol * 44.d0/12.d0 * ehcoel(5,1)                       &
539
 
         + hfol * 18.d0/2.d0  * ehcoel(6,1)
540
 
!       H02FOL en J/kg (de fol)
541
 
!       L'enthalpie de formation de la vapeur de fuel
542
 
!       est suppos�e etre des celle des seuls hydrocarbures
543
 
!       (i.e. on n�glige, pour l'instant, CO et H2S)
544
 
  h02fov = ch4fv * ehcoel(1,1) + ch2fv * ehcoel(2,1)
545
 
!  L'enthalpie de formation du coke peut-�tre consid�r�e nulle
546
 
!  (pas loin du graphite)
547
 
 
548
 
!  L'enthalpie de changement de phase est donc celle de la r�action
549
 
!  Fuel_Liquide => FKC*Coke + (1-FKC)*Fuel_Vapeur
550
 
  hrfvap =  (1.d0-fkc)*h02fov-h02fol
551
 
 
552
 
  WRITE(NFECRA,*) 'Donnees thermo pour le fuel'
553
 
  WRITE(NFECRA,*) 'PCIFOL ',PCIFOL
554
 
  WRITE(NFECRA,*) 'H02FOL ',H02FOL
555
 
  WRITE(NFECRA,*) 'CP2FOL ',CP2FOL
556
 
  WRITE(NFECRA,*) 'HRFVAP ',HRFVAP
557
 
  WRITE(NFECRA,*) 'H02FOV ',H02FOV
558
 
 
559
 
!  L'enthalpie de la r�action h�t�rog�ne est directement celle de la
560
 
!  formation d'une  mole de CO � partir de carbone � l'�tat de r�f�rence
561
 
!  il est d'usage d'ajouter cette enthalpie � celle de la phase
562
 
!  dispers�e
563
 
 
564
 
! ------ Calcul de EHSOLI pour le fuel
565
 
!        Si CP2FOL > 0 : HFOL = H02FOL + CP2FOL(T2-TREFTH)
566
 
 
567
 
    do it = 1, npo
568
 
      ehsoli(ifol,it) = h02fol                                    &
569
 
                            + cp2fol * ( th(it) - trefth )
570
 
    enddo
571
 
 
572
 
! ---- Calcul relatif au coke
573
 
 
574
 
! ------ Coke = CH(GAMMA)O(DELTA)
575
 
 
576
 
!        On considere le PCI constant qqs T
577
 
 
578
 
!          Soit le PCI est connu et fourni dans le fichier
579
 
!          soit on consid�re qu'il est entierement fourni
580
 
!          par la combustion de la fraction carbone
581
 
!          suppos�e � l'�tat de r�f�rence
582
 
 do it = 1, npo
583
 
    ehsoli(ikf,it) = cp2fol * ( th(it) - trefth )
584
 
 enddo
585
 
 
586
 
WRITE(NFECRA,*) ' Verification des enthalpies de formation'
587
 
WRITE(NFECRA,*) ' CH4  ',EHCOEL(1,1)
588
 
WRITE(NFECRA,*) ' C2H4 ',EHCOEL(2,1)
589
 
WRITE(NFECRA,*) ' FOV  ',EHGAZE(IFOV,1)
590
 
WRITE(NFECRA,*) ' FOL  ',EHSOLI(IFOL,1)
591
 
WRITE(NFECRA,*) ' KF   ',EHSOLI(IKF,1)
592
 
 
593
 
!     Masse Vol + Diametre (en milimetres)
594
 
!        on suppose que les masse vol sont les memes
595
 
!        pour le fuel, coke et residu
596
 
 
597
 
rhokf  = rho0fl
598
 
do icla = 1, nclafu
599
 
  dinikf(icla) = dinifl(icla)*(fkc*rho0fl/rhokf)**(1.d0/3.d0)
600
 
  diniin(icla) = dinifl(icla)*(xinfol*rho0fl/rho0fl)**(1.d0/3.d0)
601
 
  WRITE(NFECRA,*) ' Classe D = ',ICLA,DINIFL(ICLA),DINIKF(ICLA),  &
602
 
                                      diniin(icla)
603
 
enddo
604
 
 
605
 
return
606
 
 
607
 
 
608
 
!============================
609
 
! 3. SORTIE EN ERREUR
610
 
!============================
611
 
 
612
 
  99  continue
613
 
write ( nfecra,9998 )
614
 
call csexit (1)
615
 
!==========
616
 
 
617
 
  999 continue
618
 
write ( nfecra,9999 )
619
 
call csexit (1)
620
 
!==========
621
 
!--------
622
 
! FORMATS
623
 
!--------
624
 
 
625
 
 
626
 
 9990 format(                                                           &
627
 
'@                                                            ',/,&
628
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
629
 
'@                                                            ',/,&
630
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FULECD)      ',/,&
631
 
'@    =========                                               ',/,&
632
 
'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
633
 
'@                                                            ',/,&
634
 
'@  Erreur sur la composition du Coke :                       ',/,&
635
 
'@   la somme des compositions elementaires doit etre egal    ',/,&
636
 
'@   a 1, elle vaut ici : ',G15.7,'                           ',/,&
637
 
'@                                                            ',/,&
638
 
'@  Le calcul ne sera pas execute.                            ',/,&
639
 
'@                                                            ',/,&
640
 
'@  Verifier le fichier parametrique.                         ',/,&
641
 
'@                                                            ',/,&
642
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
643
 
'@                                                            ',/)
644
 
 9991 format(                                                           &
645
 
'@                                                            ',/,&
646
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
647
 
'@                                                            ',/,&
648
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FULECD)      ',/,&
649
 
'@    =========                                               ',/,&
650
 
'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
651
 
'@                                                            ',/,&
652
 
'@  Le nombre d''especes courantes doit etre inferieur        ',/,&
653
 
'@                                  ou egal a',I10             ,/,&
654
 
'@   Il vaut ',I10   ,' dans le fichier parametrique          ',/,&
655
 
'@                                                            ',/,&
656
 
'@  Le calcul ne sera pas execute.                            ',/,&
657
 
'@                                                            ',/,&
658
 
'@  Verifier le fichier parametrique.                         ',/,&
659
 
'@                                                            ',/,&
660
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
661
 
'@                                                            ',/)
662
 
 9992 format(                                                           &
663
 
'@                                                            ',/,&
664
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
665
 
'@                                                            ',/,&
666
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FULECD)      ',/,&
667
 
'@    =========                                               ',/,&
668
 
'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
669
 
'@                                                            ',/,&
670
 
'@  Le nombre de points de tabulation est limite a ',I10       ,/,&
671
 
'@   Il vaut ',I10   ,' dans le fichier parametrique          ',/,&
672
 
'@                                                            ',/,&
673
 
'@  Le calcul ne sera pas execute.                            ',/,&
674
 
'@                                                            ',/,&
675
 
'@  Verifier le fichier parametrique.                         ',/,&
676
 
'@                                                            ',/,&
677
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
678
 
'@                                                            ',/)
679
 
 9993 format(                                                           &
680
 
'@                                                            ',/,&
681
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
682
 
'@                                                            ',/,&
683
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FULECD)      ',/,&
684
 
'@    =========                                               ',/,&
685
 
'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
686
 
'@                                                            ',/,&
687
 
'@  Le nombre d''especes elementaires est limite a ',I10       ,/,&
688
 
'@   Il vaut ',I10   ,' dans le fichier parametrique          ',/,&
689
 
'@                                                            ',/,&
690
 
'@  Le calcul ne sera pas execute.                            ',/,&
691
 
'@                                                            ',/,&
692
 
'@  Verifier le fichier parametrique.                         ',/,&
693
 
'@                                                            ',/,&
694
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
695
 
'@                                                            ',/)
696
 
 9998 format(                                                           &
697
 
'@                                                            ',/,&
698
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
699
 
'@                                                            ',/,&
700
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FULECD)      ',/,&
701
 
'@    =========                                               ',/,&
702
 
'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
703
 
'@                                                            ',/,&
704
 
'@  Erreur a l''ouverture du fichier parametrique.            ',/,&
705
 
'@                                                            ',/,&
706
 
'@  Le calcul ne sera pas execute.                            ',/,&
707
 
'@                                                            ',/,&
708
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
709
 
'@                                                            ',/)
710
 
 9999 format(                                                           &
711
 
'@                                                            ',/,&
712
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
713
 
'@                                                            ',/,&
714
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FULECD)      ',/,&
715
 
'@    =========                                               ',/,&
716
 
'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
717
 
'@                                                            ',/,&
718
 
'@  Erreur a la lecture du fichier parametrique.              ',/,&
719
 
'@    Le fichier a ete ouvert mais est peut etre incomplet    ',/,&
720
 
'@    ou son format inadapte.                                 ',/,&
721
 
'@                                                            ',/,&
722
 
'@  Le calcul ne sera pas execute.                            ',/,&
723
 
'@                                                            ',/,&
724
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
725
 
'@                                                            ',/)
726
 
 
727
 
end subroutine
728
 
 
729