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

« back to all changes in this revision

Viewing changes to users/comb/user_fuel_iniv.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
!VERS
 
4
 
 
5
! This file is part of Code_Saturne, a general-purpose CFD tool.
 
6
!
 
7
! Copyright (C) 1998-2011 EDF S.A.
 
8
!
 
9
! This program is free software; you can redistribute it and/or modify it under
 
10
! the terms of the GNU General Public License as published by the Free Software
 
11
! Foundation; either version 2 of the License, or (at your option) any later
 
12
! version.
 
13
!
 
14
! This program is distributed in the hope that it will be useful, but WITHOUT
 
15
! ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
 
16
! FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
 
17
! details.
 
18
!
 
19
! You should have received a copy of the GNU General Public License along with
 
20
! this program; if not, write to the Free Software Foundation, Inc., 51 Franklin
 
21
! Street, Fifth Floor, Boston, MA 02110-1301, USA.
 
22
 
 
23
!-------------------------------------------------------------------------------
 
24
 
 
25
subroutine user_fuel_iniv &
 
26
!========================
 
27
 
 
28
 ( nvar   , nscal  ,                                              &
 
29
   dt     , rtp    , propce , propfa , propfb , coefa  , coefb  )
 
30
 
 
31
!===============================================================================
 
32
! PURPOSE  :
 
33
! --------
 
34
 
 
35
! INITIALISATION OF TRANSPORTED VARIABLES
 
36
!    EXTENDED PHYSICS : Heavy Fuel Oil Combustion
 
37
!    similar to  USINIV.F
 
38
!
 
39
! This routine is called at the beginning of every computation
 
40
!  (new or continuation) before the time loop
 
41
!
 
42
! This routine initialize or modify (if continuation)
 
43
!  values of transported variables and of the time step
 
44
!
 
45
! The exemple is ... default value
 
46
 
 
47
!
 
48
! Physical properties are stored in PROPCE(cell center)
 
49
!  PROPFA(inner face) and PROPFB(boundary face)
 
50
!  e.g.
 
51
!  PROPCE(IEL, IPPROC(IROM  )) is ROM(IEL) mean density kg/m3
 
52
!  PROPFA(IFAC,IPPROF(IFLUMA(IVAR ))) is FLUMAS(IFAC,IVAR) convective flux
 
53
!                                                        of variable IVAR
 
54
!  PROPFB(......                      .................................
 
55
!
 
56
! Physical properties (ROM, VISCL, CP ...) are computed in PPPHYV
 
57
!  not to be modified here
 
58
!
 
59
 
 
60
!   All cells can be identified by using the subroutine 'getcel'.
 
61
!    Syntax of getcel:
 
62
!     getcel(string, nelts, eltlst) :
 
63
!     - string is a user-supplied character string containing
 
64
!       selection criteria;
 
65
!     - nelts is set by the subroutine. It is an integer value
 
66
!       corresponding to the number of boundary faces verifying the
 
67
!       selection criteria;
 
68
!     - lstelt is set by the subroutine. It is an integer array of
 
69
!       size nelts containing the list of boundary faces verifying
 
70
!       the selection criteria.
 
71
 
 
72
!       string may contain:
 
73
!       - references to colors (ex.: 1, 8, 26, ...
 
74
!       - references to groups (ex.: inlet, group1, ...)
 
75
!       - geometric criteria (ex. x < 0.1, y >= 0.25, ...)
 
76
!
 
77
!       These criteria may be combined using logical operators
 
78
!       ('and', 'or') and parentheses.
 
79
!       Example: '1 and (group2 or group3) and y < 1' will select boundary
 
80
!       faces of color 1, belonging to groups 'group2' or 'group3' and
 
81
!       with face center coordinate y less than 1.
 
82
!
 
83
!   All boundary faces may be identified using the 'getfbr' subroutine.
 
84
!    Syntax of getfbr:
 
85
!     getfbr(string, nelts, eltlst) :
 
86
!     - string is a user-supplied character string containing
 
87
!       selection criteria;
 
88
!     - nelts is set by the subroutine. It is an integer value
 
89
!       corresponding to the number of boundary faces verifying the
 
90
!       selection criteria;
 
91
!     - lstelt is set by the subroutine. It is an integer array of
 
92
!       size nelts containing the list of boundary faces verifying
 
93
!       the selection criteria.
 
94
!
 
95
!     string may contain:
 
96
!     - references to colors (ex.: 1, 8, 26, ...
 
97
!     - references to groups (ex.: inlet, group1, ...)
 
98
!     - geometric criteria (ex. x < 0.1, y >= 0.25, ...)
 
99
!
 
100
!     These criteria may be combined using logical operators
 
101
!     ('and', 'or') and parentheses.
 
102
!
 
103
!   All internam faces may be identified using the 'getfac' subroutine.
 
104
!    Syntax of getfac:
 
105
!     getfac(string, nelts, eltlst) :
 
106
!     - string is a user-supplied character string containing
 
107
!       selection criteria;
 
108
!     - nelts is set by the subroutine. It is an integer value
 
109
!       corresponding to the number of boundary faces verifying the
 
110
!       selection criteria;
 
111
!     - lstelt is set by the subroutine. It is an integer array of
 
112
!       size nelts containing the list of boundary faces verifying
 
113
!       the selection criteria.
 
114
!
 
115
!     string may contain:
 
116
!     - references to colors (ex.: 1, 8, 26, ...
 
117
!     - references to groups (ex.: inlet, group1, ...)
 
118
!     - geometric criteria (ex. x < 0.1, y >= 0.25, ...)
 
119
!
 
120
!     These criteria may be combined using logical operators
 
121
!     ('and', 'or') and parentheses.
 
122
 
 
123
!-------------------------------------------------------------------------------
 
124
! Arguments
 
125
!__________________.____._____.________________________________________________.
 
126
! name             !type!mode ! role                                           !
 
127
!__________________!____!_____!________________________________________________!
 
128
! nvar             ! i  ! <-- ! total number of variables                      !
 
129
! nscal            ! i  ! <-- ! total number of scalars                        !
 
130
! rtp, rtpa        ! ra ! <-- ! calculated variables at cell centers           !
 
131
!  (ncelet, *)     !    !     !  (at current and preceding time steps)         !
 
132
! propce(ncelet, *)! ra ! <-- ! physical properties at cell centers            !
 
133
! propfa(nfac, *)  ! ra ! <-- ! physical properties at interior face centers   !
 
134
! propfb(nfabor, *)! ra ! <-- ! physical properties at boundary face centers   !
 
135
! coefa, coefb     ! ra ! <-- ! boundary conditions                            !
 
136
!  (nfabor, *)     !    !     !                                                !
 
137
!__________________!____!_____!________________________________________________!
 
138
 
 
139
!     Type: i (integer), r (real), s (string), a (array), l (logical),
 
140
!           and composite types (ex: ra real array)
 
141
!     mode: <-- input, --> output, <-> modifies data, --- work array
 
142
!===============================================================================
 
143
 
 
144
!===============================================================================
 
145
! Module files
 
146
!===============================================================================
 
147
 
 
148
use paramx
 
149
use pointe
 
150
use numvar
 
151
use optcal
 
152
use cstphy
 
153
use cstnum
 
154
use entsor
 
155
use parall
 
156
use period
 
157
use ppppar
 
158
use ppthch
 
159
use coincl
 
160
use cpincl
 
161
use cs_fuel_incl
 
162
use ppincl
 
163
use ppcpfu
 
164
use mesh
 
165
 
 
166
!===============================================================================
 
167
 
 
168
implicit none
 
169
 
 
170
integer          nvar   , nscal
 
171
 
 
172
double precision dt(ncelet), rtp(ncelet,*), propce(ncelet,*)
 
173
double precision propfa(nfac,*), propfb(nfabor,*)
 
174
double precision coefa(nfabor,*), coefb(nfabor,*)
 
175
 
 
176
! LOCAL VARIABLES
 
177
 
 
178
integer          iel, ige, mode, icla
 
179
integer          ioxy
 
180
 
 
181
double precision t1init, h1init, coefe(ngazem)
 
182
double precision t2init, h2init
 
183
double precision xkent, xeent, d2s3
 
184
double precision dmas , wmco2 , wmh2o , wmn2 , wmo2
 
185
 
 
186
!===============================================================================
 
187
 
 
188
 
 
189
! TEST_TO_REMOVE_FOR_USE_OF_SUBROUTINE_START
 
190
!===============================================================================
 
191
 
 
192
if(1.eq.1) return
 
193
 
 
194
!===============================================================================
 
195
! TEST_TO_REMOVE_FOR_USE_OF_SUBROUTINE_END
 
196
 
 
197
!===============================================================================
 
198
! 0. CONTROL PRINT
 
199
!===============================================================================
 
200
 
 
201
write(nfecra,9001)
 
202
 
 
203
!===============================================================================
 
204
! 1.  LOCAL VARIABLES INITIALISATION
 
205
!===============================================================================
 
206
 
 
207
d2s3 = 2.d0/3.d0
 
208
 
 
209
!===============================================================================
 
210
! 2. INITIALISATION OF TRANSPORTED VARIABLES
 
211
!      RONLY IF THE COMPUTATION IS NOT A CONTINUATION
 
212
!===============================================================================
 
213
 
 
214
if ( isuite.eq.0 ) then
 
215
 
 
216
! --> Initialisation of k and epsilon (exemple)
 
217
 
 
218
  xkent = 1.d-10
 
219
  xeent = 1.d-10
 
220
 
 
221
! ---- TURBULENCE
 
222
 
 
223
  if (itytur.eq.2) then
 
224
 
 
225
    do iel = 1, ncel
 
226
      rtp(iel,ik)  = xkent
 
227
      rtp(iel,iep) = xeent
 
228
    enddo
 
229
 
 
230
  elseif (itytur.eq.3) then
 
231
 
 
232
    do iel = 1, ncel
 
233
      rtp(iel,ir11) = d2s3*xkent
 
234
      rtp(iel,ir22) = d2s3*xkent
 
235
      rtp(iel,ir33) = d2s3*xkent
 
236
      rtp(iel,ir12) = 0.d0
 
237
      rtp(iel,ir13) = 0.d0
 
238
      rtp(iel,ir23) = 0.d0
 
239
      rtp(iel,iep)  = xeent
 
240
    enddo
 
241
 
 
242
  elseif (iturb.eq.50) then
 
243
 
 
244
    do iel = 1, ncel
 
245
      rtp(iel,ik)   = xkent
 
246
      rtp(iel,iep)  = xeent
 
247
      rtp(iel,iphi) = d2s3
 
248
      rtp(iel,ifb)  = 0.d0
 
249
    enddo
 
250
 
 
251
  elseif (iturb.eq.60) then
 
252
 
 
253
    do iel = 1, ncel
 
254
      rtp(iel,ik)   = xkent
 
255
      rtp(iel,iomg) = xeent/cmu/xkent
 
256
    enddo
 
257
 
 
258
  endif
 
259
 
 
260
! --> All the computation domain is initialised with air at TINITK
 
261
!                   ================================================
 
262
 
 
263
! ---- Computation of H1INIT and  H2INIT
 
264
 
 
265
  t1init = 1000.d0
 
266
  t2init = 1000.d0
 
267
 
 
268
! ------ Transported variables for droplets
 
269
 
 
270
  h2init = h02fol +  cp2fol*(t2init-trefth)
 
271
 
 
272
  do icla = 1, nclafu
 
273
    do iel = 1, ncel
 
274
      rtp(iel,isca(iyfol(icla))) = zero
 
275
      rtp(iel,isca(ing(icla  )))  = zero
 
276
      rtp(iel,isca(ih2(icla  )))  = zero
 
277
    enddo
 
278
  enddo
 
279
 
 
280
! ------ Transported variables for the mix (droplets and carrying gases)
 
281
 
 
282
  do ige = 1, ngazem
 
283
    coefe(ige) = zero
 
284
  enddo
 
285
!  On considere l'oxydant 1
 
286
  coefe(io2) = wmole(io2)*oxyo2(1)                                &
 
287
              /( wmole(io2) *oxyo2(1) +wmole(in2) *oxyn2(1)       &
 
288
                +wmole(ih2o)*oxyh2o(1)+wmole(ico2)*oxyco2(1))
 
289
  coefe(ih2o) = wmole(ih2o)*oxyh2o(1)                             &
 
290
              /( wmole(io2) *oxyo2(1) +wmole(in2) *oxyn2(1)       &
 
291
                +wmole(ih2o)*oxyh2o(1)+wmole(ico2)*oxyco2(1))
 
292
  coefe(ico2) = wmole(ico2)*oxyco2(1)                             &
 
293
              /( wmole(io2) *oxyo2(1) +wmole(in2) *oxyn2(1)       &
 
294
                +wmole(ih2o)*oxyh2o(1)+wmole(ico2)*oxyco2(1))
 
295
  coefe(in2) = 1.d0-coefe(io2)-coefe(ih2o)-coefe(ico2)
 
296
 
 
297
  mode = -1
 
298
  call cs_fuel_htconvers1(mode,h1init,coefe,t1init)
 
299
 !============================
 
300
 
 
301
  do iel = 1, ncel
 
302
    rtp(iel,isca(ihm)) = h1init
 
303
  enddo
 
304
 
 
305
! ------ Transported variables for gaseous mixture
 
306
!        (passive scalars, variance, reactive species)
 
307
 
 
308
  do iel = 1, ncel
 
309
    rtp(iel,isca(ifvap )) = 0.d0
 
310
    rtp(iel,isca(if7m  )) = zero
 
311
    rtp(iel,isca(ifvp2m)) = zero
 
312
    if ( ieqco2 .ge. 1 ) then
 
313
      ioxy   =  1
 
314
      wmo2   = wmole(io2)
 
315
      wmco2  = wmole(ico2)
 
316
      wmh2o  = wmole(ih2o)
 
317
      wmn2   = wmole(in2)
 
318
      dmas = ( oxyo2 (ioxy)*wmo2 +oxyn2 (ioxy)*wmn2               &
 
319
              +oxyh2o(ioxy)*wmh2o+oxyco2(ioxy)*wmco2 )
 
320
      rtp(iel,isca(iyco2)) = oxyco2(ioxy)*wmco2/dmas
 
321
    endif
 
322
    if ( ieqnox .eq. 1 ) then
 
323
      rtp(iel,isca(iyhcn)) = zero
 
324
      rtp(iel,isca(iyno )) = zero
 
325
      rtp(iel,isca(ihox)) = h1init
 
326
    endif
 
327
  enddo
 
328
 
 
329
endif
 
330
 
 
331
 
 
332
!----
 
333
! FORMATS
 
334
!----
 
335
 
 
336
 9001 format(                                                     &
 
337
'                                                             ',/,&
 
338
'  usfuiv : Variables Initialisation for FUel by the USer     ',/,&
 
339
'                                                             ',/)
 
340
 
 
341
!----
 
342
! END
 
343
!----
 
344
return
 
345
end subroutine