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

« back to all changes in this revision

Viewing changes to src/fuel/fuphy1.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 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 fuphy1 &
29
 
!================
30
 
 
31
 
 ( idbia0 , idbra0 ,                                              &
32
 
   ncelet , ncel   ,                                              &
33
 
   nitbfu , nrtbfu , nitbwo , nrtbwo ,                            &
34
 
   fvap   , fhtf   , f4p2m  ,                                     &
35
 
   enth   ,                                                       &
36
 
   rtp    , propce , rom1   ,                                     &
37
 
   itbfu  , rtbfu  ,                                              &
38
 
   itbwo  , rtbwo   )
39
 
 
40
 
!===============================================================================
41
 
! FONCTION :
42
 
! --------
43
 
 
44
 
! CALCUL DES PROPRIETES PHYSIQUES DE LA PHASE GAZEUSE
45
 
!  VALEURS CELLULES
46
 
!  ----------------
47
 
!  TEMPERATURE, MASSE VOLUMIQUE ET CONCENTRATIONS MOYENNES
48
 
!  (UTILISATION D'UNE PDF RECTANGLE-DIRAC)
49
 
 
50
 
! ==> CHIMIE RAPIDE MODELE EN 3 POINTS
51
 
!     EXTENSION A TROIS COMBUSTIBLES POUR LE CHARBON PULVERISE
52
 
!                                         --------------------
53
 
 
54
 
! REACTIONS HETEROGENES
55
 
!   - Evaporation
56
 
!     Composition de la vapeur (FOV pour Fuel Oil Vapor)
57
 
 
58
 
!        Le FOV est suppos� �tre un m�lange de H2S, CO, CHn
59
 
!          Les fractions massiques sont HSFOV pour H2S
60
 
!                                       COFOV      CO
61
 
!                                       CHFOV      CHn
62
 
!          l'hydrocarbure moyen est d�termine par nHCFOV
63
 
 
64
 
!   - Combustion heterogene
65
 
!     La composition massque �l�mentairee du coke est donn�e par
66
 
!          CKF, HKF, OKF, SKF
67
 
!           (et InKF inertes qui resteront dans l'inclusion)
68
 
!      lors de la r�action h�terogn�ne, on d�gaze H2S, H2O, CO
69
 
 
70
 
!           Attention, ceci signifie qu'en presence de FHET il y a
71
 
!           eut pr�levement d'O2 dans l'air environnant
72
 
!           (avant les r�action homog�nes).
73
 
 
74
 
!   - Reactions en phase gaz
75
 
 
76
 
!     Avec l'O2 restant dans l'air (apr�s dilution et oxydation h�t�rog�ne)
77
 
!     on consid�re des r�action s successives dans leur ordre
78
 
!          de priorit� pour l'acc�s � l'O2
79
 
!           CHn + (1/2+n/4)O2 -(1)-> CO  + n/2 H2O
80
 
!                H2S + 3/2 O2      -(2)-> SO2 + H2O
81
 
!           CO + 1/2 O2       -(3)-> CO2
82
 
 
83
 
! CHOIX DES VARIABLES
84
 
 
85
 
 
86
 
!  Soit Y les fractions massiques et Z les concentrations (moles/kg)
87
 
!    indice f avant reaction, b final
88
 
 
89
 
 
90
 
! Arguments
91
 
!__________________.____._____.________________________________________________.
92
 
! name             !type!mode ! role                                           !
93
 
!__________________!____!_____!________________________________________________!
94
 
! idbia0           ! i  ! <-- ! number of first free position in ia            !
95
 
! idbra0           ! i  ! <-- ! number of first free position in ra            !
96
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
97
 
! ncel             ! i  ! <-- ! number of cells                                !
98
 
! nitbfu           ! e  ! <-- ! taille du macro tableau fuel entiers           !
99
 
! nrtbfu           ! e  ! <-- ! taille du macro tableau fuel reels             !
100
 
! nitbwo           ! e  ! <-- ! taille du macro tableau work entiers           !
101
 
! nrtbwo           ! e  ! <-- ! taille du macro tableau work reels             !
102
 
! pa               ! tr ! <-- ! pression absolue en pascals                    !
103
 
! fvap             ! tr ! <-- ! moyenne du traceur 1 fov [chn+co]              !
104
 
! fhtf             ! tr ! <-- ! moyenne du traceur 3 (co c.het)                !
105
 
! f4p2m            ! tr ! <-- ! variance du traceur 4 (air)                    !
106
 
! enth             ! tr ! <-- ! enthalpie en j/kg  soit du gaz                 !
107
 
!                  !    !     !                    soit du melange             !
108
 
! rtp              ! tr ! <-- ! variables de calcul au centre des              !
109
 
! (ncelet,*)       !    !     !    cellules (instant courant)                  !
110
 
! propce(ncelet, *)! ra ! <-- ! physical properties at cell centers            !
111
 
! itbfu            ! tr ! <-- ! macro tableau entier fuel travail              !
112
 
! rtbfu            ! tr ! <-- ! macro tableau reel   fuel travail              !
113
 
! itbwo            ! tr ! <-- ! macro tableau entier travail                   !
114
 
! rtbwo            ! tr ! <-- ! macro tableau reel   travail                   !
115
 
!__________________!____!_____!________________________________________________!
116
 
 
117
 
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
118
 
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
119
 
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
120
 
!            --- tableau de travail
121
 
!===============================================================================
122
 
 
123
 
implicit none
124
 
 
125
 
!===============================================================================
126
 
! Common blocks
127
 
!===============================================================================
128
 
 
129
 
include "paramx.h"
130
 
include "numvar.h"
131
 
include "optcal.h"
132
 
include "cstphy.h"
133
 
include "cstnum.h"
134
 
include "entsor.h"
135
 
include "ppppar.h"
136
 
include "ppthch.h"
137
 
include "coincl.h"
138
 
include "cpincl.h"
139
 
include "fuincl.h"
140
 
include "ppincl.h"
141
 
include "ppcpfu.h"
142
 
 
143
 
!===============================================================================
144
 
 
145
 
! Arguments
146
 
 
147
 
integer          idbia0 , idbra0
148
 
integer          ncelet , ncel
149
 
integer          nitbfu , nrtbfu
150
 
integer          nitbwo , nrtbwo
151
 
integer          itbfu(ncelet,nitbfu)
152
 
integer          itbwo(ncelet,nitbwo)
153
 
 
154
 
double precision fvap(ncelet), fhtf(ncelet)
155
 
double precision f4p2m(ncelet), enth(ncelet)
156
 
double precision rtp(ncelet,*), propce(ncelet,*)
157
 
double precision rom1(ncelet)
158
 
double precision rtbfu(ncelet,nrtbfu)
159
 
double precision rtbwo(ncelet,nrtbwo)
160
 
 
161
 
! Local variables
162
 
 
163
 
integer          idebia , idebra
164
 
integer          iel    , iphas  , ice
165
 
integer          ipcte1
166
 
integer          ipcyf1 , ipcyf3 , ipcyox
167
 
integer          ipcyp1 , ipcyp2 , ipcyin , ipcyce
168
 
integer          ipcy2s , ipcyso
169
 
double precision wmolme
170
 
double precision f1m,f3m,f4m,f1cl,f3cl,f4cl
171
 
 
172
 
!===============================================================================
173
 
 
174
 
!===============================================================================
175
 
! 1. INITIALISATIONS
176
 
!===============================================================================
177
 
 
178
 
! --- Initialisation memoire
179
 
 
180
 
idebia = idbia0
181
 
idebra = idbra0
182
 
 
183
 
!===============================================================================
184
 
! 2. DETERMINATION DU TYPE DE PDF
185
 
!===============================================================================
186
 
 
187
 
do iel = 1, ncel
188
 
 
189
 
!       Traceur virtuel au point moyen
190
 
 
191
 
  f1m =  fvap(iel)
192
 
  f3m =  fhtf(iel)/ff3max
193
 
  f4m = 1.d0 - f1m - f3m
194
 
 
195
 
!       Calcul des caract�ristiques du point correspondant au
196
 
!       combustible moyen
197
 
!       F3cl : fraction de masse provenant de F3max et non de F3
198
 
 
199
 
  if ( (f3m+f1m*ff3max) .gt. 0.d0 ) then
200
 
    f1cl = f1m*ff3max/(f3m+f1m*ff3max)
201
 
  else
202
 
    f1cl = 0.d0
203
 
  endif
204
 
 
205
 
  f3cl = 1.d0-f1cl
206
 
  f4cl = (1.d0-ff3max)*f3cl
207
 
 
208
 
  rtbfu(iel,1) = f3m
209
 
  rtbfu(iel,2) = f4m
210
 
  rtbfu(iel,3) = f1cl
211
 
  rtbfu(iel,4) = f3cl
212
 
  rtbfu(iel,5) = f4cl
213
 
 
214
 
!       bornes min et max de la pdf : F4CL a 1
215
 
 
216
 
  rtbfu(iel,6) = 1.d0
217
 
 
218
 
enddo
219
 
 
220
 
call pppdfr                                                       &
221
 
!==========
222
 
 ( ncelet,ncel,                                                   &
223
 
   itbfu(1,1) ,                                                   &
224
 
   rtbfu(1,2), rtp(1,isca(if4p2m)),                               &
225
 
!           F4M
226
 
   rtbfu(1,5), rtbfu(1,6),                                        &
227
 
!           FMINI        FMAXI
228
 
   rtbfu(1,7) , rtbfu(1,8) , rtbfu(1,9) , rtbfu(1,10),            &
229
 
!           D4CL         D4F4          F4M1        F4M2
230
 
    rtbfu(1,11) )
231
 
!           HREC
232
 
 
233
 
!===============================================================================
234
 
! 2.CALCUL DES CONCENTRATIONS MOYENNES
235
 
!===============================================================================
236
 
 
237
 
 
238
 
ipcyf1 = ipproc(iym1(ifov))
239
 
ipcyf3 = ipproc(iym1(ico  ))
240
 
ipcyox = ipproc(iym1(io2  ))
241
 
ipcyp1 = ipproc(iym1(ico2 ))
242
 
ipcyp2 = ipproc(iym1(ih2o ))
243
 
ipcyin = ipproc(iym1(in2  ))
244
 
ipcy2s = ipproc(iym1(ih2s ))
245
 
ipcyso = ipproc(iym1(iso2 ))
246
 
 
247
 
 call fucym1                                                      &
248
 
!!==========
249
 
 ( ncelet , ncel   ,                                              &
250
 
   itbfu(1,1) ,                                                   &
251
 
!         INTPDF
252
 
   rtp    ,                                                       &
253
 
   fvap   ,   rtbfu(1,1) , rtbfu(1,2) ,                           &
254
 
!         F1M           F3M         F4M
255
 
  rtbfu(1,3) , rtbfu(1,4) ,rtbfu(1,5) ,                           &
256
 
!         F1CL         F3CL         F4CL
257
 
 
258
 
   rtbfu(1,9) , rtbfu(1,10) , rtbfu(1,7) ,                        &
259
 
!           F4M1         F4M2        D4CL
260
 
   rtbfu(1,8) ,rtbfu(1,11) ,                                      &
261
 
!           D4F4         HREC
262
 
   propce(1,ipcyf1) , propce(1,ipcyf3) ,                          &
263
 
   propce(1,ipcyox) , propce(1,ipcyp1) , propce(1,ipcyp2) ,       &
264
 
   propce(1,ipcyin) ,                                             &
265
 
   propce(1,ipcy2s) , propce(1,ipcyso) ,                          &
266
 
   rtbfu(1,12) )
267
 
!         F4S3 pour NOx
268
 
 
269
 
! --> Clipping eventuel des fractions massiques
270
 
 
271
 
do iel = 1, ncel
272
 
  do ice = 1, ngaze
273
 
    ipcyce = ipproc(iym1(ice))
274
 
    if ( abs(propce(iel,ipcyce)) .lt. epsifl )                    &
275
 
         propce(iel,ipcyce) = zero
276
 
  enddo
277
 
enddo
278
 
 
279
 
! MODEL NOx : on y passe pas a la 1ere iter
280
 
 
281
 
if ( ieqnox .eq. 1 .and. ntcabs .gt.1) then
282
 
  call fucyno                                                     &
283
 
  !==========
284
 
 ( ncelet , ncel   ,                                              &
285
 
   itbfu(1,1) ,                                                   &
286
 
!         INTPDF
287
 
   rtp    , propce ,                                              &
288
 
   fvap   ,   rtbfu(1,1) , rtbfu(1,2) ,                           &
289
 
!         F1M           F3M         F4M
290
 
  rtbfu(1,3) , rtbfu(1,4) ,rtbfu(1,5) ,                           &
291
 
!         F1CL         F3CL         F4CL
292
 
 
293
 
   rtbfu(1,9) , rtbfu(1,10) , rtbfu(1,7) ,                        &
294
 
!           F4M1         F4M2        D4CL
295
 
   rtbfu(1,8) ,rtbfu(1,11) , rtbfu(1,12) ,                        &
296
 
!           D4F4         HREC
297
 
   propce(1,ipcyf1) , propce(1,ipcyf3) ,                          &
298
 
   propce(1,ipcyox) , propce(1,ipcyp1) , propce(1,ipcyp2) ,       &
299
 
   propce(1,ipcyin) ,                                             &
300
 
   propce(1,ipcy2s) , propce(1,ipcyso) )
301
 
 
302
 
else if ( ieqnox .eq. 1 ) then
303
 
 
304
 
  write(*,*) ' passage init ',IGHCN1,IGHCN2,IGNOTH
305
 
  do iel = 1, ncel
306
 
    propce(iel,ipproc(ighcn1)) = 0.d0
307
 
    propce(iel,ipproc(ighcn2)) = 0.d0
308
 
    propce(iel,ipproc(ignoth)) = 0.d0
309
 
  enddo
310
 
 
311
 
endif
312
 
 
313
 
!===============================================================================
314
 
! 3. CALCUL DE LA TEMPERATURE ET DE LA MASSE VOLUMIQUE
315
 
!===============================================================================
316
 
 
317
 
ipcte1 = ipproc(itemp1)
318
 
 
319
 
call futeh1                                                       &
320
 
!==========
321
 
 ( ncelet , ncel   ,                                              &
322
 
   enth,                                                          &
323
 
   propce(1,ipcyf1), propce(1,ipcyf3),                            &
324
 
   propce(1,ipcyox), propce(1,ipcyp1), propce(1,ipcyp2),          &
325
 
   propce(1,ipcyin), propce(1,ipcy2s), propce(1,ipcyso),          &
326
 
   propce(1,ipcte1),                                              &
327
 
   rtbwo(1,1) , rtbwo(1,2) )
328
 
 
329
 
!          TABLEAUX DE TRAVAIL
330
 
 
331
 
iphas  = 1
332
 
ipcte1 = ipproc(itemp1)
333
 
do iel = 1, ncel
334
 
  wmolme = propce(iel,ipcyf1) / wmole(ifov)                       &
335
 
         + propce(iel,ipcyf3) / wmole(ico )                       &
336
 
         + propce(iel,ipcyox) / wmole(io2 )                       &
337
 
         + propce(iel,ipcyp1) / wmole(ico2)                       &
338
 
         + propce(iel,ipcyp2) / wmole(ih2o)                       &
339
 
         + propce(iel,ipcyin) / wmole(in2 )                       &
340
 
         + propce(iel,ipcy2s) / wmole(ih2s)                       &
341
 
         + propce(iel,ipcyso) / wmole(iso2)
342
 
 
343
 
! stockage de la masse molaire du melange
344
 
 
345
 
  propce(iel,ipproc(immel)) = 1.d0 / wmolme
346
 
 
347
 
! ---- On ne met pas la pression mecanique RTP(IEL,IPR(IPHAS))
348
 
!      mais P0(IPHAS)
349
 
 
350
 
  rom1(iel) = p0(iphas) / (wmolme * rr * propce(iel,ipcte1) )
351
 
enddo
352
 
 
353
 
!===============================================================================
354
 
! FORMATS
355
 
!----
356
 
 
357
 
 
358
 
 
359
 
!----
360
 
! FIN
361
 
!----
362
 
 
363
 
return
364
 
end subroutine