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

« back to all changes in this revision

Viewing changes to users/fuel/usfuiv.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
 
 
6
 
!     This file is part of the Code_Saturne Kernel, element of the
7
 
!     Code_Saturne CFD tool.
8
 
 
9
 
!     Copyright (C) 1998-2009 EDF S.A., France
10
 
 
11
 
!     contact: saturne-support@edf.fr
12
 
 
13
 
!     The Code_Saturne Kernel is free software; you can redistribute it
14
 
!     and/or modify it under the terms of the GNU General Public License
15
 
!     as published by the Free Software Foundation; either version 2 of
16
 
!     the License, or (at your option) any later version.
17
 
 
18
 
!     The Code_Saturne Kernel is distributed in the hope that it will be
19
 
!     useful, but WITHOUT ANY WARRANTY; without even the implied warranty
20
 
!     of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
21
 
!     GNU General Public License for more details.
22
 
 
23
 
!     You should have received a copy of the GNU General Public License
24
 
!     along with the Code_Saturne Kernel; if not, write to the
25
 
!     Free Software Foundation, Inc.,
26
 
!     51 Franklin St, Fifth Floor,
27
 
!     Boston, MA  02110-1301  USA
28
 
 
29
 
!-------------------------------------------------------------------------------
30
 
 
31
 
subroutine usfuiv &
32
 
!================
33
 
 
34
 
 ( idbia0 , idbra0 ,                                              &
35
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
36
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
37
 
   nvar   , nscal  , nphas  ,                                     &
38
 
   nideve , nrdeve , nituse , nrtuse ,                            &
39
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml , maxelt , lstelt , &
40
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
41
 
   idevel , ituser , ia     ,                                     &
42
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
43
 
   dt     , rtp    , propce , propfa , propfb , coefa  , coefb  , &
44
 
   rdevel , rtuser , ra     )
45
 
 
46
 
!===============================================================================
47
 
! PURPOSE  :
48
 
! --------
49
 
 
50
 
! INITIALISATION OF TRANSPORTED VARIABLES
51
 
!    EXTENDED PHYSICS : Heavy Fuel Oil Combustion
52
 
!    similar to  USINIV.F
53
 
!
54
 
! This routine is called at the beginning of every computation
55
 
!  (new or continuation) before the time loop
56
 
!
57
 
! This routine initialize or modify (if continuation)
58
 
!  values of transported variables and of the time step
59
 
!
60
 
! The exemple is ... default value
61
 
 
62
 
!
63
 
! Physical properties are stored in PROPCE(cell center)
64
 
!  PROPFA(inner face) and PROPFB(boundary face)
65
 
!  e.g.
66
 
!  PROPCE(IEL, IPPROC(IROM  (IPHAS))) is ROM(IEL,IPHAS) mean density kg/m3
67
 
!  PROPFA(IFAC,IPPROF(IFLUMA(IVAR ))) is FLUMAS(IFAC,IVAR) convective flux
68
 
!                                                        of variable IVAR
69
 
!  PROPFB(......                      .................................
70
 
!
71
 
! Physical properties (ROM, VISCL, CP ...) are computed in PPPHYV
72
 
!  not to be modified here
73
 
!
74
 
 
75
 
!   All cells can be identified by using the subroutine 'getcel'.
76
 
!    Syntax of getcel:
77
 
!     getcel(string, nelts, eltlst) :
78
 
!     - string is a user-supplied character string containing
79
 
!       selection criteria;
80
 
!     - nelts is set by the subroutine. It is an integer value
81
 
!       corresponding to the number of boundary faces verifying the
82
 
!       selection criteria;
83
 
!     - lstelt is set by the subroutine. It is an integer array of
84
 
!       size nelts containing the list of boundary faces verifying
85
 
!       the selection criteria.
86
 
 
87
 
!       string may contain:
88
 
!       - references to colors (ex.: 1, 8, 26, ...
89
 
!       - references to groups (ex.: inlet, group1, ...)
90
 
!       - geometric criteria (ex. x < 0.1, y >= 0.25, ...)
91
 
!
92
 
!       These criteria may be combined using logical operators
93
 
!       ('and', 'or') and parentheses.
94
 
!       Example: '1 and (group2 or group3) and y < 1' will select boundary
95
 
!       faces of color 1, belonging to groups 'group2' or 'group3' and
96
 
!       with face center coordinate y less than 1.
97
 
!
98
 
!   All boundary faces may be identified using the 'getfbr' subroutine.
99
 
!    Syntax of getfbr:
100
 
!     getfbr(string, nelts, eltlst) :
101
 
!     - string is a user-supplied character string containing
102
 
!       selection criteria;
103
 
!     - nelts is set by the subroutine. It is an integer value
104
 
!       corresponding to the number of boundary faces verifying the
105
 
!       selection criteria;
106
 
!     - lstelt is set by the subroutine. It is an integer array of
107
 
!       size nelts containing the list of boundary faces verifying
108
 
!       the selection criteria.
109
 
!
110
 
!     string may contain:
111
 
!     - references to colors (ex.: 1, 8, 26, ...
112
 
!     - references to groups (ex.: inlet, group1, ...)
113
 
!     - geometric criteria (ex. x < 0.1, y >= 0.25, ...)
114
 
!
115
 
!     These criteria may be combined using logical operators
116
 
!     ('and', 'or') and parentheses.
117
 
!
118
 
!   All internam faces may be identified using the 'getfac' subroutine.
119
 
!    Syntax of getfac:
120
 
!     getfac(string, nelts, eltlst) :
121
 
!     - string is a user-supplied character string containing
122
 
!       selection criteria;
123
 
!     - nelts is set by the subroutine. It is an integer value
124
 
!       corresponding to the number of boundary faces verifying the
125
 
!       selection criteria;
126
 
!     - lstelt is set by the subroutine. It is an integer array of
127
 
!       size nelts containing the list of boundary faces verifying
128
 
!       the selection criteria.
129
 
!
130
 
!     string may contain:
131
 
!     - references to colors (ex.: 1, 8, 26, ...
132
 
!     - references to groups (ex.: inlet, group1, ...)
133
 
!     - geometric criteria (ex. x < 0.1, y >= 0.25, ...)
134
 
!
135
 
!     These criteria may be combined using logical operators
136
 
!     ('and', 'or') and parentheses.
137
 
 
138
 
!-------------------------------------------------------------------------------
139
 
! Arguments
140
 
!__________________.____._____.________________________________________________.
141
 
! name             !type!mode ! role                                           !
142
 
!__________________!____!_____!________________________________________________!
143
 
! idbia0           ! i  ! <-- ! number of first free position in ia            !
144
 
! idbra0           ! i  ! <-- ! number of first free position in ra            !
145
 
! ndim             ! i  ! <-- ! spatial dimension                              !
146
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
147
 
! ncel             ! i  ! <-- ! number of cells                                !
148
 
! nfac             ! i  ! <-- ! number of interior faces                       !
149
 
! nfabor           ! i  ! <-- ! number of boundary faces                       !
150
 
! nfml             ! i  ! <-- ! number of families (group classes)             !
151
 
! nprfml           ! i  ! <-- ! number of properties per family (group class)  !
152
 
! nnod             ! i  ! <-- ! number of vertices                             !
153
 
! lndfac           ! i  ! <-- ! size of nodfac indexed array                   !
154
 
! lndfbr           ! i  ! <-- ! size of nodfbr indexed array                   !
155
 
! ncelbr           ! i  ! <-- ! number of cells with faces on boundary         !
156
 
! nvar             ! i  ! <-- ! total number of variables                      !
157
 
! nscal            ! i  ! <-- ! total number of scalars                        !
158
 
! nphas            ! i  ! <-- ! number of phases                               !
159
 
! nideve, nrdeve   ! i  ! <-- ! sizes of idevel and rdevel arrays              !
160
 
! nituse, nrtuse   ! i  ! <-- ! sizes of ituser and rtuser arrays              !
161
 
! ifacel(2, nfac)  ! ia ! <-- ! interior faces -> cells connectivity           !
162
 
! ifabor(nfabor)   ! ia ! <-- ! boundary faces -> cells connectivity           !
163
 
! ifmfbr(nfabor)   ! ia ! <-- ! boundary face family numbers                   !
164
 
! ifmcel(ncelet)   ! ia ! <-- ! cell family numbers                            !
165
 
! iprfml           ! ia ! <-- ! property numbers per family                    !
166
 
!  (nfml, nprfml)  !    !     !                                                !
167
 
! maxelt           !  e ! <-- ! max number of cells and faces (int/boundary)   !
168
 
! lstelt(maxelt)   ! ia ! --- ! work array                                     !
169
 
! ipnfac(nfac+1)   ! ia ! <-- ! interior faces -> vertices index (optional)    !
170
 
! nodfac(lndfac)   ! ia ! <-- ! interior faces -> vertices list (optional)     !
171
 
! ipnfbr(nfabor+1) ! ia ! <-- ! boundary faces -> vertices index (optional)    !
172
 
! nodfac(lndfbr)   ! ia ! <-- ! boundary faces -> vertices list (optional)     !
173
 
! icodcl           ! ia ! --> ! boundary condition code                        !
174
 
!  (nfabor, nvar)  !    !     ! = 1  -> Dirichlet                              !
175
 
!                  !    !     ! = 2  -> flux density                           !
176
 
!                  !    !     ! = 4  -> sliding wall and u.n=0 (velocity)      !
177
 
!                  !    !     ! = 5  -> friction and u.n=0 (velocity)          !
178
 
!                  !    !     ! = 6  -> roughness and u.n=0 (velocity)         !
179
 
!                  !    !     ! = 9  -> free inlet/outlet (velocity)           !
180
 
!                  !    !     !         inflowing possibly blocked             !
181
 
! itrifb(nfabor    ! ia ! <-- ! indirection for boundary faces ordering)       !
182
 
!  (nfabor, nphas) !    !     !                                                !
183
 
! itypfb           ! ia ! --> ! boundary face types                            !
184
 
!  (nfabor, nphas) !    !     !                                                !
185
 
! idevel(nideve)   ! ia ! <-- ! integer work array for temporary developpement !
186
 
! ituser(nituse    ! ia ! <-- ! user-reserved integer work array               !
187
 
! ia(*)            ! ia ! --- ! main integer work array                        !
188
 
! xyzcen           ! ra ! <-- ! cell centers                                   !
189
 
!  (ndim, ncelet)  !    !     !                                                !
190
 
! surfac           ! ra ! <-- ! interior faces surface vectors                 !
191
 
!  (ndim, nfac)    !    !     !                                                !
192
 
! surfbo           ! ra ! <-- ! boundary faces surface vectors                 !
193
 
!  (ndim, nfavor)  !    !     !                                                !
194
 
! cdgfac           ! ra ! <-- ! interior faces centers of gravity              !
195
 
!  (ndim, nfac)    !    !     !                                                !
196
 
! cdgfbo           ! ra ! <-- ! boundary faces centers of gravity              !
197
 
!  (ndim, nfabor)  !    !     !                                                !
198
 
! xyznod           ! ra ! <-- ! vertex coordinates (optional)                  !
199
 
!  (ndim, nnod)    !    !     !                                                !
200
 
! volume(ncelet)   ! ra ! <-- ! cell volumes                                   !
201
 
! dt(ncelet)       ! ra ! <-- ! time step (per cell)                           !
202
 
! rtp, rtpa        ! ra ! <-- ! calculated variables at cell centers           !
203
 
!  (ncelet, *)     !    !     !  (at current and preceding time steps)         !
204
 
! propce(ncelet, *)! ra ! <-- ! physical properties at cell centers            !
205
 
! propfa(nfac, *)  ! ra ! <-- ! physical properties at interior face centers   !
206
 
! propfb(nfabor, *)! ra ! <-- ! physical properties at boundary face centers   !
207
 
! coefa, coefb     ! ra ! <-- ! boundary conditions                            !
208
 
!  (nfabor, *)     !    !     !                                                !
209
 
! rcodcl           ! ra ! --> ! boundary condition values                      !
210
 
!                  !    !     ! rcodcl(1) = Dirichlet value                    !
211
 
!                  !    !     ! rcodcl(2) = exterior exchange coefficient      !
212
 
!                  !    !     !  (infinite if no exchange)                     !
213
 
!                  !    !     ! rcodcl(3) = flux density value                 !
214
 
!                  !    !     !  (negative for gain) in w/m2 or                !
215
 
!                  !    !     !  roughness height (m) if icodcl=6              !
216
 
!                  !    !     ! for velocities           ( vistl+visct)*gradu  !
217
 
!                  !    !     ! for pressure                         dt*gradp  !
218
 
!                  !    !     ! for scalars    cp*(viscls+visct/sigmas)*gradt  !
219
 
! w1,2,3,4,5,6     ! ra ! --- ! work arrays                                    !
220
 
!  (ncelet)        !    !     !  (computation of pressure gradient)            !
221
 
! coefu            ! ra ! --- ! tab de trav                                    !
222
 
!  (nfabor, 3)     !    !     !  (computation of pressure gradient)            !
223
 
! rdevel(nrdeve)   ! ra ! <-> ! tab reel complementaire developemt             !
224
 
! rdevel(nideve)   ! ra ! <-- ! real work array for temporary developpement    !
225
 
! rtuser(nituse    ! ra ! <-- ! user-reserved real work array                  !
226
 
! ra(*)            ! ra ! --- ! main real work array                           !
227
 
!__________________!____!_____!________________________________________________!
228
 
 
229
 
!     Type: i (integer), r (real), s (string), a (array), l (logical),
230
 
!           and composite types (ex: ra real array)
231
 
!     mode: <-- input, --> output, <-> modifies data, --- work array
232
 
!===============================================================================
233
 
 
234
 
implicit none
235
 
 
236
 
!===============================================================================
237
 
!     DONNEES EN COMMON
238
 
!===============================================================================
239
 
 
240
 
include "paramx.h"
241
 
include "pointe.h"
242
 
include "numvar.h"
243
 
include "optcal.h"
244
 
include "cstphy.h"
245
 
include "cstnum.h"
246
 
include "entsor.h"
247
 
include "parall.h"
248
 
include "period.h"
249
 
include "ppppar.h"
250
 
include "ppthch.h"
251
 
include "coincl.h"
252
 
include "cpincl.h"
253
 
include "fuincl.h"
254
 
include "ppincl.h"
255
 
include "ppcpfu.h"
256
 
 
257
 
!===============================================================================
258
 
 
259
 
integer          idbia0 , idbra0
260
 
integer          ndim   , ncelet , ncel   , nfac   , nfabor
261
 
integer          nfml   , nprfml
262
 
integer          nnod   , lndfac , lndfbr , ncelbr
263
 
integer          nvar   , nscal  , nphas
264
 
integer          nideve , nrdeve , nituse , nrtuse
265
 
 
266
 
integer          ifacel(2,nfac) , ifabor(nfabor)
267
 
integer          ifmfbr(nfabor) , ifmcel(ncelet)
268
 
integer          iprfml(nfml,nprfml), maxelt, lstelt(maxelt)
269
 
integer          ipnfac(nfac+1), nodfac(lndfac)
270
 
integer          ipnfbr(nfabor+1), nodfbr(lndfbr)
271
 
integer          idevel(nideve), ituser(nituse), ia(*)
272
 
 
273
 
double precision xyzcen(ndim,ncelet)
274
 
double precision surfac(ndim,nfac), surfbo(ndim,nfabor)
275
 
double precision cdgfac(ndim,nfac), cdgfbo(ndim,nfabor)
276
 
double precision xyznod(ndim,nnod), volume(ncelet)
277
 
double precision dt(ncelet), rtp(ncelet,*), propce(ncelet,*)
278
 
double precision propfa(nfac,*), propfb(nfabor,*)
279
 
double precision coefa(nfabor,*), coefb(nfabor,*)
280
 
double precision rdevel(nrdeve), rtuser(nrtuse), ra(*)
281
 
 
282
 
 
283
 
! LOCAL VARIABLES
284
 
 
285
 
integer          idebia, idebra
286
 
integer          iel, ige, mode, iphas, icla
287
 
 
288
 
double precision t1init, h1init, coefe(ngazem)
289
 
double precision t2init, h2init
290
 
double precision xkent, xeent, d2s3
291
 
 
292
 
!===============================================================================
293
 
 
294
 
 
295
 
! TEST_TO_REMOVE_FOR_USE_OF_SUBROUTINE_START
296
 
!===============================================================================
297
 
 
298
 
if(1.eq.1) return
299
 
 
300
 
!===============================================================================
301
 
! TEST_TO_REMOVE_FOR_USE_OF_SUBROUTINE_END
302
 
 
303
 
!===============================================================================
304
 
! 0. CONTROL PRINT
305
 
!===============================================================================
306
 
 
307
 
write(nfecra,9001)
308
 
 
309
 
!===============================================================================
310
 
! 1.  LOCAL VARIABLES INITIALISATION
311
 
!===============================================================================
312
 
 
313
 
idebia = idbia0
314
 
idebra = idbra0
315
 
 
316
 
d2s3 = 2.d0/3.d0
317
 
 
318
 
!===============================================================================
319
 
! 2. INITIALISATION OF TRANSPORTED VARIABLES
320
 
!      RONLY IF THE COMPUTATION IS NOT A CONTINUATION
321
 
!===============================================================================
322
 
 
323
 
if ( isuite.eq.0 ) then
324
 
 
325
 
  iphas = 1
326
 
 
327
 
! --> Initialisation of k and epsilon (exemple)
328
 
 
329
 
  xkent = 1.d-10
330
 
  xeent = 1.d-10
331
 
 
332
 
! ---- TURBULENCE
333
 
 
334
 
  if (itytur(iphas).eq.2) then
335
 
 
336
 
    do iel = 1, ncel
337
 
      rtp(iel,ik(iphas))  = xkent
338
 
      rtp(iel,iep(iphas)) = xeent
339
 
    enddo
340
 
 
341
 
  elseif (itytur(iphas).eq.3) then
342
 
 
343
 
    do iel = 1, ncel
344
 
      rtp(iel,ir11(iphas)) = d2s3*xkent
345
 
      rtp(iel,ir22(iphas)) = d2s3*xkent
346
 
      rtp(iel,ir33(iphas)) = d2s3*xkent
347
 
      rtp(iel,ir12(iphas)) = 0.d0
348
 
      rtp(iel,ir13(iphas)) = 0.d0
349
 
      rtp(iel,ir23(iphas)) = 0.d0
350
 
      rtp(iel,iep(iphas))  = xeent
351
 
    enddo
352
 
 
353
 
  elseif (iturb(iphas).eq.50) then
354
 
 
355
 
    do iel = 1, ncel
356
 
      rtp(iel,ik(iphas))   = xkent
357
 
      rtp(iel,iep(iphas))  = xeent
358
 
      rtp(iel,iphi(iphas)) = d2s3
359
 
      rtp(iel,ifb(iphas))  = 0.d0
360
 
    enddo
361
 
 
362
 
  elseif (iturb(iphas).eq.60) then
363
 
 
364
 
    do iel = 1, ncel
365
 
      rtp(iel,ik(iphas))   = xkent
366
 
      rtp(iel,iomg(iphas)) = xeent/cmu/xkent
367
 
    enddo
368
 
 
369
 
  endif
370
 
 
371
 
! --> All the computation domain is initialised with air at TINITK
372
 
!                   ================================================
373
 
 
374
 
! ---- Computation of H1INIT and  H2INIT
375
 
 
376
 
  t1init = t0(iphas)
377
 
  t2init = t0(iphas)
378
 
 
379
 
! ------ Transported variables for droplets
380
 
 
381
 
  h2init = h02fol +  cp2fol*(t2init-trefth)
382
 
 
383
 
  do icla = 1, nclafu
384
 
    do iel = 1, ncel
385
 
      rtp(iel,isca(iyfol(icla))) = zero
386
 
      rtp(iel,isca(ing(icla) ))  = zero
387
 
      rtp(iel,isca(ihlf(icla)))  = h2init
388
 
    enddo
389
 
  enddo
390
 
 
391
 
! ------ Transported variables for the mix (droplets and carrying gases)
392
 
 
393
 
  do ige = 1, ngazem
394
 
    coefe(ige) = zero
395
 
  enddo
396
 
  coefe(io2) = wmole(io2) / (wmole(io2)+xsi*wmole(in2))
397
 
  coefe(in2) = 1.d0 - coefe(io2)
398
 
  mode = -1
399
 
  call futhp1                                                     &
400
 
  !==========
401
 
 ( mode   , h1init , coefe  , t1init )
402
 
 
403
 
  do iel = 1, ncel
404
 
    rtp(iel,isca(ihm)) = h1init
405
 
  enddo
406
 
 
407
 
! ------ Transported variables for gaseous mixture
408
 
!        (passive scalars, variance, reactive species)
409
 
 
410
 
  do iel = 1, ncel
411
 
    rtp(iel,isca(ifvap )) = zero
412
 
    rtp(iel,isca(ifhtf )) = zero
413
 
    rtp(iel,isca(if4p2m)) = zero
414
 
    if ( ieqco2 .ge. 1 ) then
415
 
      rtp(iel,isca(iyco2)) = zero
416
 
    endif
417
 
    if ( ieqnox .eq. 1 ) then
418
 
      rtp(iel,isca(iyhcn)) = zero
419
 
      rtp(iel,isca(iyno )) = zero
420
 
      rtp(iel,isca(itaire)) = 20.d0+tkelvi
421
 
    endif
422
 
  enddo
423
 
 
424
 
endif
425
 
 
426
 
 
427
 
!----
428
 
! FORMATS
429
 
!----
430
 
 
431
 
 9001 format(                                                     &
432
 
'                                                             ',/,&
433
 
'  usfuiv : Variables Initialisation for FUel by the USer     ',/,&
434
 
'                                                             ',/)
435
 
 
436
 
!----
437
 
! END
438
 
!----
439
 
return
440
 
end subroutine