1!-------------------------------------------------------------------------------
2
3! This file is part of Code_Saturne, a general-purpose CFD tool.
4!
5! Copyright (C) 1998-2021 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
23subroutine cs_fuel_readata
24!=========================
25!===============================================================================
26!  FONCTION  :
27!  ---------
28
29! LECTURE DU FICHIER DE DONNEES PHYSIQUE PARTICULIERE
30!      RELATIF A LA COMBUSTION FUEL
31
32!-------------------------------------------------------------------------------
33! Arguments
34!__________________.____._____.________________________________________________.
35! name             !type!mode ! role                                           !
36!__________________!____!_____!________________________________________________!
37!__________________!____!_____!________________________________________________!
38
39!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
40!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
41!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
42!            --- tableau de travail
43!===============================================================================
44
45!===============================================================================
46! Module files
47!===============================================================================
48
49use paramx
50use pointe
51use entsor
52use cstnum
53use cstphy
54use ppppar
55use ppthch
56use coincl
57use cpincl
58use cs_fuel_incl
59use ppincl
60use ppcpfu
61
62!===============================================================================
63
64implicit none
65
66! Arguments
67
68! Local variables
69
70character(len=150) :: chain1,chain2
71
72integer          it     , ice    , iat    , ios , ii , ioxy
73integer          ncoel  , inicoe
74integer          icla
75integer          idebch , ifinch , lonch  , ichai  , ichcoe
76integer          atcoel(ngazem,natom), inicha
77
78double precision tmin   , tmax
79double precision wmolce(ngazem), ehcoel(ngazem,npot)
80double precision cpcoel(ngazem,npot)
81double precision ncfov,nhfov,nofov,nsfov
82double precision mhsfov,mcofov,mchfov,mtofov
83double precision nhsfov,ncofov,ncmv,nhmv
84double precision ch2fv,ch4fv,h02fov
85double precision dmf3 ,dmf4 , dmf5
86double precision wmco,wmco2,wmo2,wmn2,wmh2o, wmc
87
88!===============================================================================
89! 1. LECTURE DU FICHIER DONNEES SPECIFIQUES
90!===============================================================================
91
92! --> Ouverture du fichier
93
94open ( unit=impfpp, file=ficfpp,                                  &
95        STATUS='OLD', FORM='FORMATTED', ACCESS='SEQUENTIAL',      &
96                                        iostat=ios, err=99 )
97rewind (unit=impfpp,err=99 )
98
99! --> Lecture thermochimie
100
101read (impfpp,*,err=999,end=999 )
102
103! ---- Nb de constituants elementaires (gazeux,liquide et solide)
104
105read ( impfpp,*,err=999,end=999 ) ncoel
106if ( ncoel.gt.ngazgm ) then
107  write(nfecra,9991) ngazgm,ncoel
108  call csexit (1)
109endif
110
111! ---- Nb de points de tabulation ENTH-TEMP
112
113read ( impfpp,*,err=999,end=999 ) npo
114if ( npo.gt.npot ) then
115  write(nfecra,9992) npot,npo
116  call csexit (1)
117endif
118
119! --- Lecture des noms des constituants elementaires
120
121do ice=1,ncoel
122  do inicoe=1,len(nomcoe(ice))
123    NOMCOE(ICE)(INICOE:INICOE)=' '
124  enddo
125enddo
126
127do inicha=1,len(chain1)
128  CHAIN1(INICHA:INICHA)=' '
129enddo
130
131do inicha=1,len(chain2)
132  CHAIN2(INICHA:INICHA)=' '
133enddo
134
135read (impfpp,*,err=999,end=999)
136read (impfpp,1010,err=999,end=999 ) chain1
137call verlon (chain1, idebch, ifinch, lonch)
138chain2(1:lonch)=chain1(idebch:ifinch)
139
140ice=1
141ichcoe=0
142do ichai = 1, lonch
143  IF (CHAIN2(ICHAI:ICHAI).NE.' ') THEN
144    ichcoe=ichcoe+1
145    nomcoe(ice)(ichcoe:ichcoe) =chain2(ichai:ichai)
146  else
147    if (ichcoe.ne.0) then
148      ice=ice+1
149      ichcoe=0
150    endif
151  endif
152enddo
153
154 1010 format(a150)
155
156! --- Temperature Min et Max
157
158read (impfpp,*,err=999,end=999) tmin
159read (impfpp,*,err=999,end=999) tmax
160
161! ---- Nb especes atomiques (C, H, O, N, S)
162
163read (impfpp,*,err=999,end=999 ) nato
164if ( nato.gt.natom ) then
165  write(nfecra,9993) natom,nato
166  call csexit (1)
167  !==========
168endif
169
170! ---- Masse molaire especes atomiques
171!      Composition des constituants elementaires en fonction
172!        des especes elementaires
173
174do iat = 1, nato
175  read (impfpp,*,err=999,end=999 ) wmolat(iat),                   &
176                      ( atcoel(ice,iat),ice=1,ncoel )
177enddo
178
179! ---- Calcul des masses molaires des constituants elementaires
180
181do ice = 1, ncoel
182  wmolce(ice) = 0.d0
183  do iat = 1, nato
184    wmolce(ice)= wmolce(ice) + atcoel(ice,iat)*wmolat(iat)
185  enddo
186enddo
187
188
189! --> Lecture rayonnement : Coefficient d'absorption du melange gazeux
190
191read (impfpp,*,err=999,end=999 )
192read (impfpp,*,err=999,end=999 ) ckabs1
193
194
195! --> Lecture caracteristiques fuel
196
197read (impfpp,*,err=999,end=999 )
198
199! ---- Nb de classes de fuel
200
201read (impfpp,*,err=999,end=999 ) nclafu
202if ( nclafu.gt.nclcpm ) then
203  write(nfecra,9996) nclcpm,nclafu
204  call csexit (1)
205endif
206
207! --> Diametre initial  (mm)
208
209read (impfpp,*,err=999,end=999 ) ( dinifl(icla),icla=1,nclafu )
210
211! --> Composition elementaire en C, H, O, S, In (% en masse)
212!     In designe les inertes (m�taux, etc.) qui resteront
213!        dans le residu solide
214
215read (impfpp,*,err=999,end=999 ) cfol
216read (impfpp,*,err=999,end=999 ) hfol
217read (impfpp,*,err=999,end=999 ) ofol
218read (impfpp,*,err=999,end=999 ) sfol
219
220cfol = 1.d-2 * cfol
221hfol = 1.d-2 * hfol
222ofol = 1.d-2 * ofol
223sfol = 1.d-2 * sfol
224xinfol = 1.d0-cfol-hfol-ofol-sfol
225if (xinfol .lt. zero) then
226   WRITE(NFECRA,*)'Erreur dans les fractions massiques du FOL'
227!         STOP
228endif
229WRITE (NFECRA,*) 'Fractions massiques elementaires / FOL  '
230WRITE (NFECRA,*) ' C = ',CFOL
231WRITE (NFECRA,*) ' H = ',HFOL
232WRITE (NFECRA,*) ' O = ',OFOL
233WRITE (NFECRA,*) ' S = ',SFOL
234WRITE (NFECRA,*) ' In= ',XINFOL
235
236
237! --> PCI
238
239read (impfpp,*,err=999,end=999 ) pcifol
240
241! --> CP moyen du fuel sec (J/kg/K)
242
243read (impfpp,*,err=999,end=999 ) cp2fol
244
245! --> Masse volumique initiale (kg/m3)
246
247read (impfpp,*,err=999,end=999 ) rho0fl
248
249! --> Caracteristiques du coke
250
251read (impfpp,*,err=999,end=999)
252
253! ------- Composition elementaire en C, H, O, S (% / pur)
254
255read (impfpp,*,err=999,end=999 ) ckf
256read (impfpp,*,err=999,end=999 ) hkf
257read (impfpp,*,err=999,end=999 ) okf
258read (impfpp,*,err=999,end=999 ) skf
259
260ckf = 1.d-2 * ckf
261hkf = 1.d-2 * hkf
262okf = 1.d-2 * okf
263skf = 1.d-2 * skf
264
265if ( abs(ckf+hkf+okf+skf-1.d0) .gt. 1.d-15 ) then
266  write(nfecra,9990) ckf+hkf+okf+skf
267  call csexit(1)
268endif
269
270! ------ PCI
271
272read (impfpp,*,err=999,end=999 ) pcikf
273
274! ---- Fraction de coke dans le fuel
275
276read (impfpp,*,err=999,end=999) fkc
277WRITE (NFECRA,*)' Fraction massique de coke / FOL',fkc
278
279!     Les inertes restent dans le coke
280xinkf = zero
281if ( fkc .gt. zero) xinkf = xinfol/fkc
282if ( (ckf+hkf+okf+skf) .gt. 1.d0) then
283   WRITE(NFECRA,*)'Erreur dans les fractions massiques du KF'
284!         STOP
285endif
286
287WRITE (NFECRA,*) 'Fractions massiques elementaires / coke '
288WRITE (NFECRA,*) ' C = ',CKF*(1.D0-XINKF)
289WRITE (NFECRA,*) ' H = ',HKF*(1.D0-XINKF)
290WRITE (NFECRA,*) ' O = ',OKF*(1.D0-XINKF)
291WRITE (NFECRA,*) ' S = ',SKF*(1.D0-XINKF)
292WRITE (NFECRA,*) ' In= ',XInKF
293
294!     Compatibilite des fractions massiques et des formules moleculaires
295!     masses elementaires dans le fuel, le coke, les vapeurs
296!        F      K        MV
297!   C    CFOL   CKF*FKC  CFOL-CKF*FKC
298!   H    HFOL   HKF*FKC  HFOL-HKF*FKC
299!   O    OFOL   OKF*FKC  OFOL-OKF*FKC
300!   S    SFOL   SKF*FKC  SFOL-SKF*FKC
301!   In   XInFOL  XInFOL    0
302!      elements dans les vapeurs
303ncfov  = (cfol-ckf*fkc*(1.d0-xinkf))/wmolat(iatc)/(1.d0-fkc)
304nhfov  = (hfol-hkf*fkc*(1.d0-xinkf))/wmolat(iath)/(1.d0-fkc)
305nofov  = (ofol-okf*fkc*(1.d0-xinkf))/wmolat(iato)/(1.d0-fkc)
306nsfov  = (sfol-skf*fkc*(1.d0-xinkf))/wmolat(iats)/(1.d0-fkc)
307!       on considere que S se degage sous forme H2S
308!                    que O                      CO
309nhsfov = nsfov
310ncofov = nofov
311ncmv   = ncfov - ncofov
312nhmv   = nhfov - 2.d0*nhsfov
313
314!   Les vapeurs sont alors constituees de nHSFOV moles de H2S
315!                                         nCOFOV          CO
316!                                         nCMV            CHn
317!   ou CHn est un hydrocarbure modele de formule moyenne avec
318nhcfov  = nhmv/ncmv
319WRITE(NFECRA,*) ' nHCFOV = ',NHCFOV ,NHMV,NCMV
320
321!   Les masses dans les vapeurs sont
322mhsfov = (wmolat(iats)+2.d0*wmolat(iath))*nhsfov
323mcofov = (wmolat(iatc)+wmolat(iato))*ncofov
324mchfov = wmolat(iatc)*ncmv+wmolat(iath)*nhmv
325mtofov = mhsfov+mcofov+mchfov
326
327WRITE(NFECRA,*) ' mtoFOV = ',MTOFOV
328
329!   Les fractions massiques dans les vapeurs sont
330hsfov = mhsfov / mtofov
331cofov = mcofov / mtofov
332chfov = mchfov / mtofov
333WRITE (NFECRA,*) 'Fractions massiques sp�cifiques / FOV '
334WRITE (NFECRA,*) ' H2S = ',HSFOV
335WRITE (NFECRA,*) ' CO  = ',COFOV
336WRITE (NFECRA,*) ' CHn = ',CHFOV
337WRITE (NFECRA,*) ' ..n = ',nHCFOV
338ch4fv = zero
339ch2fv = chfov
340if ( nhcfov.ge.2.d0 .and. nhcfov.le.4.d0 ) then
341  WRITE(NFECRA,*) 'Le FOV est equivalent a un melange '
342  ch2fv = 2.d0-0.5d0*nhcfov
343   ch4fv = (1-ch2fv)*16.d0/(12.d0+nhcfov)
344   ch2fv = ch2fv*14.d0/(12.d0+nhcfov)
345   ch4fv = ch4fv * chfov
346   ch2fv = ch2fv * chfov
347   WRITE (NFECRA,*) ' H2S = ',HSFOV
348   WRITE (NFECRA,*) ' CO  = ',COFOV
349   WRITE (NFECRA,*) ' CH4 = ',CH4FV
350   WRITE (NFECRA,*) 'C2H4 = ',CH2FV
351elseif ( nhcfov.ge.4.d0 ) then
352  WRITE(NFECRA,*) '========================================= '
353  WRITE(NFECRA,*) 'WARNING! Char content in fuel is too high'
354  WRITE(NFECRA,*) 'Please modify it in dp_FUE'
355  WRITE(NFECRA,*) '========================================= '
356  call csexit (1)
357elseif ( nhcfov.le.2.d0 ) then
358  WRITE(NFECRA,*) '======================================== '
359  WRITE(NFECRA,*) 'WARNING! Char content in fuel is too low'
360  WRITE(NFECRA,*) 'Please modify it in dp_FUE'
361  WRITE(NFECRA,*) '======================================== '
362  call csexit (1)
363endif
364WRITE(NFECRA,*) ' nHCFOV 2 = ',NHCFOV
365
366! ---- Parametre d'evaporation
367
368 read (impfpp,*,err=999,end=999) tevap1
369 read (impfpp,*,err=999,end=999) tevap2
370
371! ---- Parametres combustion heterogene (modele a sphere retrecissante)
372
373read (impfpp,*,err=999,end=999 )
374
375read (impfpp,*,err=999,end=999 ) ahetfl
376read (impfpp,*,err=999,end=999 ) ehetfl
377read (impfpp,*,err=999,end=999 ) iofhet
378
379! --> Lecture caracteristiques Oxydants
380
381read (impfpp,*,err=999,end=999 )
382
383! ---- Nb d'oxydants
384read ( impfpp,*,err=999,end=999 ) noxyd
385if ( noxyd.lt.1 .or. noxyd .gt. 3 ) then
386  write(nfecra,9895) noxyd
387  call csexit (1)
388endif
389
390! ---- Composition en O2,N2,H2O,N2
391
392do ioxy=1,3
393  oxyo2 (ioxy) = 0.d0
394  oxyn2 (ioxy) = 0.d0
395  oxyh2o(ioxy) = 0.d0
396  oxyco2(ioxy) = 0.d0
397enddo
398
399read (impfpp,*,err=999,end=999 )                                  &
400     ( oxyo2(ioxy),ioxy=1,noxyd )
401read (impfpp,*,err=999,end=999 )                                  &
402     ( oxyn2(ioxy),ioxy=1,noxyd )
403read (impfpp,*,err=999,end=999 )                                  &
404     ( oxyh2o(ioxy),ioxy=1,noxyd )
405read (impfpp,*,err=999,end=999 )                                  &
406     ( oxyco2(ioxy),ioxy=1,noxyd )
407
408! --> Fermeture du fichier (ne pas oublier, car l'unite sert pour janaf)
409
410close(impfpp)
411
412!===============================================================================
413! 2.
414!===============================================================================
415
416
417! --> Discretisation de la temperature
418
419do it = 1, npo
420  th(it) = dble(it-1)*(tmax-tmin)/dble(npo-1) + tmin
421enddo
422
423! --> Calcul des enthalpies pour les differentes especes courantes
424
425call pptbht                                                       &
426!==========
427 ( ncoel  ,                                                       &
428   nomcoe , ehcoel , cpcoel , wmolce )
429
430! --> Calcul tabulation enthalpie - temperature pour le melange gazeux
431
432! ---- Nb de constituants gazeux
433!     ATTENTION ON COMPTE EGALEMENT H2S et le monomere SO2
434
435ngaze = 12
436ngazg = 12
437
438! ---- Definition des pointeurs pour les tableaux WMOLE et EHGAZE
439!      REMARQUE : Cette position de pointeurs va egalement servir
440!                 pour le tableau de pointeurs IYM1 relatif aux
441!                 (indices de propriétés)
442!                 ON BALAYE JUSTE DE 1 A NGAZE
443
444!     ATTENTION : ordre des especes dans EHCOEL, WMOLCE
445!                 vient du fichier data_FUE
446ifo0 = 1
447ifov = 2
448ico  = 3
449ih2s = 4
450ihy  = 5
451ihcn = 6
452inh3 = 7
453io2  = 8
454ico2 = 9
455ih2o = 10
456iso2 = 11
457in2  = 12
458
459! ---- Remplissage de EHGAZE et WMOLE
460!         a partir de EHCOEL et WMOLCE
461
462do it = 1, npo
463  ehgaze(ifov ,it) = ( ch4fv*ehcoel(1,it) + ch2fv*ehcoel(2,it) )
464  ehgaze(ifo0 ,it) = ehgaze(ifov ,it)
465  do ii=3,ngazg
466    ehgaze(ii,it) = ehcoel(ii,it)
467  enddo
468enddo
469wmole(ifov ) = (ch4fv+ch2fv)/(ch4fv/wmolce(1)+ch2fv/wmolce(2))
470WRITE(NFECRA,*) ' Wmole IFOV 1ere formule= ',WMOLE(IFOV ),CH4FV,CH2FV
471wmole(ifov ) = (1.d0*0.012d0 + nhcfov *0.001d0 )
472wmole(ifo0 ) = wmole(ifov )
473WRITE(NFECRA,*) ' Wmole IFOV 2eme formule= ',WMOLE(IFOV ),CH4FV,CH2FV
474do ii=3,ngazg
475  wmole(ii) = wmolce(ii)
476enddo
477!
478! --> Calcul tabulation enthalpie - temperature pour la phase dispersee
479!     Fuel Oil Liquid et  Coke
480
481! ---- Nb de constituants solide
482
483nsolid = 2
484
485! ---- Definition des pointeurs IFOL et IKF
486
487ifol = 1
488ikf = 2
489
490! ------ Calcul de H02FOL
491
492!       H0, EH & PCI en J/kg
493!       CFOL, HFOL sont des fractions massiques elementaires
494!       rapports des masses molaires des produits aux elements du
495!                combustible (le comburant est dans l'etat de ref.)
496
497! ------ Calcul de HRFVAP
498
499!  L'enthalpie de formation du fuel gazeux est connue (melange CH4, C2H4),
500!  Le PCI du fuel liquide est connu , on peut donc reconstituer son
501!   enthalpie de formation (on neglige l'effet de H2S => SO2)
502!   on introduit les enthalpies de formation massique du CO2 et de H2O
503
504  h02fol = pcifol                                                 &
505         + cfol * 44.d0/12.d0 * ehcoel(ico2,1)                    &
506         + hfol * 18.d0/2.d0  * ehcoel(ih2o,1)
507!       H02FOL en J/kg (de fol)
508!       L'enthalpie de formation de la vapeur de fuel
509!       est supposee etre des celle des seuls hydrocarbures
510!       (i.e. on neglige, pour l'instant, CO et H2S)
511  h02fov = ch4fv * ehcoel(1,1) + ch2fv * ehcoel(2,1)
512!  L'enthalpie de formation du coke peut-etre consideree nulle
513!  (pas loin du graphite)
514
515!  L'enthalpie de changement de phase est donc celle de la reaction
516!  Fuel_Liquide => FKC*Coke + (1-FKC)*Fuel_Vapeur
517  hrfvap =  (1.d0-fkc)*h02fov-h02fol
518
519  WRITE(NFECRA,*) 'Donnees thermo pour le fuel'
520  WRITE(NFECRA,*) 'PCIFOL ',PCIFOL
521  WRITE(NFECRA,*) 'H02FOL ',H02FOL
522  WRITE(NFECRA,*) 'CP2FOL ',CP2FOL
523  WRITE(NFECRA,*) 'HRFVAP ',HRFVAP
524  WRITE(NFECRA,*) 'H02FOV ',H02FOV
525!  L'enthalpie de la reaction heterogene est directement celle de la
526!  formation d'une  mole de CO a partir de carbone a l'etat de reference
527!  il est d'usage d'ajouter cette enthalpie a celle de la phase
528!  dispersee
529
530! ------ Calcul de EHSOLI pour le fuel
531!        Si CP2FOL > 0 : HFOL = H02FOL + CP2FOL(T2-TREFTH)
532
533    do it = 1, npo
534      ehsoli(ifol,it) = h02fol                                    &
535                            + cp2fol * ( th(it) - trefth )
536    enddo
537
538! ---- Calcul relatif au coke
539
540! ------ Coke = CH(GAMMA)O(DELTA)
541
542!        On considere le PCI constant qqs T
543
544!          Soit le PCI est connu et fourni dans le fichier
545!          soit on considere qu'il est entierement fourni
546!          par la combustion de la fraction carbone
547!          supposee à l'etat de reference
548 do it = 1, npo
549    ehsoli(ikf,it) = cp2fol * ( th(it) - trefth )
550 enddo
551!
552WRITE(NFECRA,*) ' Verification des enthalpies de formation'
553WRITE(NFECRA,*) ' CH4  ',EHCOEL(1,1)
554WRITE(NFECRA,*) ' C2H4 ',EHCOEL(2,1)
555WRITE(NFECRA,*) ' FOV  ',EHGAZE(IFOV,1)
556WRITE(NFECRA,*) ' FOL  ',EHSOLI(IFOL,1)
557WRITE(NFECRA,*) ' KF   ',EHSOLI(IKF,1)
558!
559!     Masse Vol + Diametre (en milimetres)
560!        on suppose que les masse vol sont les memes
561!        pour le fuel, coke et residu
562!
563do icla = 1, nclafu
564  dinikf(icla) = dinifl(icla)*(fkc**(1.d0/3.d0))
565  diniin(icla) = dinifl(icla)*(xinfol**(1.d0/3.d0))
566!
567  WRITE(NFECRA,*) ' Classe D = ',ICLA,DINIFL(ICLA),DINIKF(ICLA),  &
568                                      diniin(icla)
569!
570enddo
571!
572!  Calcul des AiFj : nbre de mole de i par kg de j a l'origine
573!
574wmco   = wmole(ico)
575wmo2   = wmole(io2)
576wmco2  = wmole(ico2)
577wmh2o  = wmole(ih2o)
578wmn2   = wmole(in2)
579wmc    = wmolat(iatc)
580
581dmf3  = ( oxyo2 (1)*wmo2 +oxyn2 (1)*wmn2     &
582         +oxyh2o(1)*wmh2o+oxyco2(1)*wmco2 )
583
584if ( dmf3 .le. 0.d0 ) then
585  write(nfecra,9896) oxyo2(1) ,oxyn2(1) ,    &
586                     oxyh2o(1),oxyco2(1)
587
588endif
589
590af3(io2)  = oxyo2(1)  / dmf3
591af3(in2)  = oxyn2(1)  / dmf3
592af3(ih2o) = oxyh2o(1) / dmf3
593af3(ico2) = oxyco2(1) / dmf3
594
595if ( noxyd .ge. 2.d0 ) then
596  dmf4  = ( oxyo2 (2)*wmo2 +oxyn2 (2)*wmn2     &
597           +oxyh2o(2)*wmh2o+oxyco2(2)*wmco2 )
598  if ( dmf4 .le. 0.d0 ) then
599    write(nfecra,9897) oxyo2(2) ,oxyn2(2) ,     &
600                       oxyh2o(2),oxyco2(2)
601    call csexit(1)
602  endif
603
604  af4(io2)  = oxyo2(2)  / dmf4
605  af4(in2)  = oxyn2(2)  / dmf4
606  af4(ih2o) = oxyh2o(2) / dmf4
607  af4(ico2) = oxyco2(2) / dmf4
608
609endif
610
611if ( noxyd .eq. 3.d0 ) then
612  dmf5  = ( oxyo2 (3)*wmo2 +oxyn2 (3)*wmn2    &
613           +oxyh2o(3)*wmh2o+oxyco2(3)*wmco2 )
614  if ( dmf5 .le. 0.d0 ) then
615    write(nfecra,9898) oxyo2(3) ,oxyn2(3) ,   &
616                       oxyh2o(3),oxyco2(3)
617    call csexit(1)
618  endif
619
620  af5(io2)  = oxyo2 (3) / dmf5
621  af5(in2)  = oxyn2 (3) / dmf5
622  af5(ih2o) = oxyh2o(3) / dmf5
623  af5(ico2) = oxyco2(3) / dmf5
624
625endif
626!vapeur
627af6(ih2o)  = 1.d0/wmh2o
628! coke par o2
629af7(ico)   = 1.0d0/wmc
630af7(io2)   =-0.5d0/wmc
631
632return
633
634
635!===============================================================================
636! 3. SORTIE EN ERREUR
637!===============================================================================
638
639  99  continue
640write ( nfecra,9998 )
641call csexit (1)
642!==========
643
644  999 continue
645write ( nfecra,9999 )
646call csexit (1)
647!==========
648!--------
649! Formats
650!--------
651
652
653 9990 format(                                                     &
654'@                                                            ',/,&
655'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
656'@                                                            ',/,&
657'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FULECD)      ',/,&
658'@    =========                                               ',/,&
659'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
660'@                                                            ',/,&
661'@  Erreur sur la composition du Coke :                       ',/,&
662'@   la somme des compositions elementaires doit etre egal    ',/,&
663'@   a 1, elle vaut ici : ',G15.7,'                           ',/,&
664'@                                                            ',/,&
665'@  Le calcul ne sera pas execute.                            ',/,&
666'@                                                            ',/,&
667'@  Verifier le fichier parametrique.                         ',/,&
668'@                                                            ',/,&
669'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
670'@                                                            ',/)
671 9991 format(                                                     &
672'@                                                            ',/,&
673'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
674'@                                                            ',/,&
675'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FULECD)      ',/,&
676'@    =========                                               ',/,&
677'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
678'@                                                            ',/,&
679'@  Le nombre d''especes courantes doit etre inferieur        ',/,&
680'@                                  ou egal a',I10             ,/,&
681'@   Il vaut ',I10   ,' dans le fichier parametrique          ',/,&
682'@                                                            ',/,&
683'@  Le calcul ne sera pas execute.                            ',/,&
684'@                                                            ',/,&
685'@  Verifier le fichier parametrique.                         ',/,&
686'@                                                            ',/,&
687'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
688'@                                                            ',/)
689 9992 format(                                                     &
690'@                                                            ',/,&
691'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
692'@                                                            ',/,&
693'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FULECD)      ',/,&
694'@    =========                                               ',/,&
695'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
696'@                                                            ',/,&
697'@  Le nombre de points de tabulation est limite a ',I10       ,/,&
698'@   Il vaut ',I10   ,' dans le fichier parametrique          ',/,&
699'@                                                            ',/,&
700'@  Le calcul ne sera pas execute.                            ',/,&
701'@                                                            ',/,&
702'@  Verifier le fichier parametrique.                         ',/,&
703'@                                                            ',/,&
704'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
705'@                                                            ',/)
706 9993 format(                                                     &
707'@                                                            ',/,&
708'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
709'@                                                            ',/,&
710'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FULECD)      ',/,&
711'@    =========                                               ',/,&
712'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
713'@                                                            ',/,&
714'@  Le nombre d''especes elementaires est limite a ',I10       ,/,&
715'@   Il vaut ',I10   ,' dans le fichier parametrique          ',/,&
716'@                                                            ',/,&
717'@  Le calcul ne sera pas execute.                            ',/,&
718'@                                                            ',/,&
719'@  Verifier le fichier parametrique.                         ',/,&
720'@                                                            ',/,&
721'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
722'@                                                            ',/)
723 9996 format(                                                     &
724'@                                                            ',/,&
725'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
726'@                                                            ',/,&
727'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FULECD)      ',/,&
728'@    =========                                               ',/,&
729'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
730'@                                                            ',/,&
731'@  Le nombre de classes de fioul est limite a ',I10           ,/,&
732'@   Il vaut ',I10                                             ,/,&
733'@                      dans le fichier parametrique          ',/,&
734'@                                                            ',/,&
735'@  Le calcul ne sera pas execute.                            ',/,&
736'@                                                            ',/,&
737'@  Verifier le fichier parametrique.                         ',/,&
738'@                                                            ',/,&
739'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
740'@                                                            ',/)
741 9998 format(                                                     &
742'@                                                            ',/,&
743'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
744'@                                                            ',/,&
745'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FULECD)      ',/,&
746'@    =========                                               ',/,&
747'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
748'@                                                            ',/,&
749'@  Erreur a l''ouverture du fichier parametrique.            ',/,&
750'@                                                            ',/,&
751'@  Le calcul ne sera pas execute.                            ',/,&
752'@                                                            ',/,&
753'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
754'@                                                            ',/)
755 9999 format(                                                     &
756'@                                                            ',/,&
757'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
758'@                                                            ',/,&
759'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FULECD)      ',/,&
760'@    =========                                               ',/,&
761'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
762'@                                                            ',/,&
763'@  Erreur a la lecture du fichier parametrique.              ',/,&
764'@    Le fichier a ete ouvert mais est peut etre incomplet    ',/,&
765'@    ou son format inadapte.                                 ',/,&
766'@                                                            ',/,&
767'@  Le calcul ne sera pas execute.                            ',/,&
768'@                                                            ',/,&
769'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
770'@                                                            ',/)
771 9895 format(                                                     &
772'@                                                            ',/,&
773'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
774'@                                                            ',/,&
775'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FULECD)      ',/,&
776'@    =========                                               ',/,&
777'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
778'@                                                            ',/,&
779'@  Le nombre d''Oxydants doit etre compris entre 1 et 3      ',/,&
780'@   Il vaut ',I10   ,' dans le fichier parametrique          ',/,&
781'@                                                            ',/,&
782'@  Le calcul ne sera pas execute.                            ',/,&
783'@                                                            ',/,&
784'@  Verifier le fichier parametrique.                         ',/,&
785'@                                                            ',/,&
786'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
787'@                                                            ',/)
788
789 9896 format(                                                     &
790'@                                                            ',/,&
791'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
792'@                                                            ',/,&
793'@                                                            ',/,&
794'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FUEL)        ',/,&
795'@    =========                                               ',/,&
796'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
797'@                                                            ',/,&
798'@  LA COMPOSITION DE L''OXYDANT 1 EST ERRONEE                ',/,&
799'@     O2  :  ',G15.7,'                                       ',/,&
800'@     N2  :  ',G15.7,'                                       ',/,&
801'@     H2O :  ',G15.7,'                                       ',/,&
802'@     CO2 :  ',G15.7,'                                       ',/,&
803'@                                                            ',/,&
804'@  Le calcul ne sera pas execute.                            ',/,&
805'@                                                            ',/,&
806'@  Verifier le fichier parametrique.                         ',/,&
807'@                                                            ',/,&
808'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
809'@                                                            ',/)
810 9897 format(                                                     &
811'@                                                            ',/,&
812'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
813'@                                                            ',/,&
814'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FUEL)        ',/,&
815'@    =========                                               ',/,&
816'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
817'@                                                            ',/,&
818'@  LA COMPOSITION DE L''OXYDANT 2 EST ERRONEE                ',/,&
819'@     O2  :  ',G15.7,'                                       ',/,&
820'@     N2  :  ',G15.7,'                                       ',/,&
821'@     H2O :  ',G15.7,'                                       ',/,&
822'@     CO2 :  ',G15.7,'                                       ',/,&
823'@                                                            ',/,&
824'@  Le calcul ne sera pas execute.                            ',/,&
825'@                                                            ',/,&
826'@  Verifier le fichier parametrique.                         ',/,&
827'@                                                            ',/,&
828'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
829'@                                                            ',/)
830 9898 format(                                                     &
831'@                                                            ',/,&
832'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
833'@                                                            ',/,&
834'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES (FUEL)        ',/,&
835'@    =========                                               ',/,&
836'@      PHYSIQUE PARTICULIERE (FUEL)                          ',/,&
837'@                                                            ',/,&
838'@  LA COMPOSITION DE L''OXYDANT 3 EST ERRONEE                ',/,&
839'@     O2  :  ',G15.7,'                                       ',/,&
840'@     N2  :  ',G15.7,'                                       ',/,&
841'@     H2O :  ',G15.7,'                                       ',/,&
842'@     CO2 :  ',G15.7,'                                       ',/,&
843'@                                                            ',/,&
844'@  Le calcul ne sera pas execute.                            ',/,&
845'@                                                            ',/,&
846'@  Verifier le fichier parametrique.                         ',/,&
847'@                                                            ',/,&
848'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
849'@                                                            ',/)
850
851!----
852! End
853!----
854
855return
856end subroutine
857