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

« back to all changes in this revision

Viewing changes to examples/2-full_domain/case4/usclim.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
1
!-------------------------------------------------------------------------------
2
2
 
3
 
!                      Code_Saturne version 2.0.0-rc1
 
3
!                      Code_Saturne version 2.1.0-alpha1
4
4
!                      --------------------------
5
5
 
6
6
!     This file is part of the Code_Saturne Kernel, element of the
31
31
subroutine usclim &
32
32
!================
33
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 ,                            &
 
34
 ( nvar   , nscal  ,                                              &
41
35
   icodcl , itrifb , itypfb ,                                     &
42
 
   idevel , ituser , ia     ,                                     &
43
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
44
36
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
45
 
   coefa  , coefb  , rcodcl ,                                     &
46
 
   w1     , w2     , w3     , w4     , w5     , w6     , coefu  , &
47
 
   rdevel , rtuser , ra     )
 
37
   coefa  , coefb  , rcodcl )
48
38
 
49
39
!===============================================================================
50
40
! Purpose:
281
271
!                                 rcodcl(ifac, ivar, 2) = rinfin
282
272
!                                 rcodcl(ifac, ivar, 3) = 0.d0)
283
273
!        Especially, one may have for example:
284
 
!        -> set itypfb(ifac, iphas) = iparoi which prescribes default wall
 
274
!        -> set itypfb(ifac) = iparoi which prescribes default wall
285
275
!        conditions for all variables at face ifac,
286
276
!        -> and define IN ADDITION for variable ivar on this face specific
287
277
!        conditions by specifying icodcl(ifac, ivar) and the 3 rcodcl values.
330
320
!         entering the subroutine.
331
321
 
332
322
 
333
 
!       Note how to access some variables (for phase    'iphas'
334
 
!                                              variable 'ivar'
 
323
!       Note how to access some variables (for variable 'ivar'
335
324
!                                              scalar   'iscal'):
336
325
 
337
326
! Cell values  (let iel = ifabor(ifac))
338
327
 
339
 
! * Density:                                 propce(iel, ipproc(irom(iphas)))
340
 
! * Dynamic molecular viscosity:             propce(iel, ipproc(iviscl(iphas)))
341
 
! * Turbulent viscosity:                     propce(iel, ipproc(ivisct(iphas)))
342
 
! * Specific heat:                           propce(iel, ipproc(icp(iphas))
 
328
! * Density:                                 propce(iel, ipproc(irom))
 
329
! * Dynamic molecular viscosity:             propce(iel, ipproc(iviscl))
 
330
! * Turbulent viscosity:                     propce(iel, ipproc(ivisct))
 
331
! * Specific heat:                           propce(iel, ipproc(icp)
343
332
! * Diffusivity(lambda):                     propce(iel, ipproc(ivisls(iscal)))
344
333
 
345
334
! Boundary face values
346
335
 
347
 
! * Density:                                 propfb(ifac, ipprob(irom(iphas)))
 
336
! * Density:                                 propfb(ifac, ipprob(irom))
348
337
! * Mass flux (for convecting 'ivar'):       propfb(ifac, ipprob(ifluma(ivar)))
349
338
 
350
339
! * For other values: take as an approximation the value in the adjacent cell
356
345
!__________________.____._____.________________________________________________.
357
346
! name             !type!mode ! role                                           !
358
347
!__________________!____!_____!________________________________________________!
359
 
! idbia0           ! i  ! <-- ! number of first free position in ia            !
360
 
! idbra0           ! i  ! <-- ! number of first free position in ra            !
361
 
! ndim             ! i  ! <-- ! spatial dimension                              !
362
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
363
 
! ncel             ! i  ! <-- ! number of cells                                !
364
 
! nfac             ! i  ! <-- ! number of interior faces                       !
365
 
! nfabor           ! i  ! <-- ! number of boundary faces                       !
366
 
! nfml             ! i  ! <-- ! number of families (group classes)             !
367
 
! nprfml           ! i  ! <-- ! number of properties per family (group class)  !
368
 
! nnod             ! i  ! <-- ! number of vertices                             !
369
 
! lndfac           ! i  ! <-- ! size of nodfac indexed array                   !
370
 
! lndfbr           ! i  ! <-- ! size of nodfbr indexed array                   !
371
 
! ncelbr           ! i  ! <-- ! number of cells with faces on boundary         !
372
348
! nvar             ! i  ! <-- ! total number of variables                      !
373
349
! nscal            ! i  ! <-- ! total number of scalars                        !
374
 
! nphas            ! i  ! <-- ! number of phases                               !
375
 
! nideve, nrdeve   ! i  ! <-- ! sizes of idevel and rdevel arrays              !
376
 
! nituse, nrtuse   ! i  ! <-- ! sizes of ituser and rtuser arrays              !
377
 
! ifacel(2, nfac)  ! ia ! <-- ! interior faces -> cells connectivity           !
378
 
! ifabor(nfabor)   ! ia ! <-- ! boundary faces -> cells connectivity           !
379
 
! ifmfbr(nfabor)   ! ia ! <-- ! boundary face family numbers                   !
380
 
! ifmcel(ncelet)   ! ia ! <-- ! cell family numbers                            !
381
 
! iprfml           ! ia ! <-- ! property numbers per family                    !
382
 
!  (nfml, nprfml)  !    !     !                                                !
383
 
! maxelt           ! i  ! <-- ! max number of cells and faces (int/boundary)   !
384
 
! lstelt(maxelt)   ! ia ! --- ! work array                                     !
385
 
! ipnfac(nfac+1)   ! ia ! <-- ! interior faces -> vertices index (optional)    !
386
 
! nodfac(lndfac)   ! ia ! <-- ! interior faces -> vertices list (optional)     !
387
 
! ipnfbr(nfabor+1) ! ia ! <-- ! boundary faces -> vertices index (optional)    !
388
 
! nodfbr(lndfbr)   ! ia ! <-- ! boundary faces -> vertices list (optional)     !
389
350
! icodcl           ! ia ! --> ! boundary condition code                        !
390
351
!  (nfabor, nvar)  !    !     ! = 1  -> Dirichlet                              !
391
352
!                  !    !     ! = 2  -> flux density                           !
395
356
!                  !    !     ! = 9  -> free inlet/outlet (velocity)           !
396
357
!                  !    !     !         inflowing possibly blocked             !
397
358
! itrifb           ! ia ! <-- ! indirection for boundary faces ordering        !
398
 
!  (nfabor, nphas) !    !     !                                                !
399
359
! itypfb           ! ia ! --> ! boundary face types                            !
400
 
!  (nfabor, nphas) !    !     !                                                !
401
 
! idevel(nideve)   ! ia ! <-> ! integer work array for temporary development   !
402
 
! ituser(nituse)   ! ia ! <-> ! user-reserved integer work array               !
403
 
! ia(*)            ! ia ! --- ! main integer work array                        !
404
 
! xyzcen           ! ra ! <-- ! cell centers                                   !
405
 
!  (ndim, ncelet)  !    !     !                                                !
406
 
! surfac           ! ra ! <-- ! interior faces surface vectors                 !
407
 
!  (ndim, nfac)    !    !     !                                                !
408
 
! surfbo           ! ra ! <-- ! boundary faces surface vectors                 !
409
 
!  (ndim, nfabor)  !    !     !                                                !
410
 
! cdgfac           ! ra ! <-- ! interior faces centers of gravity              !
411
 
!  (ndim, nfac)    !    !     !                                                !
412
 
! cdgfbo           ! ra ! <-- ! boundary faces centers of gravity              !
413
 
!  (ndim, nfabor)  !    !     !                                                !
414
 
! xyznod           ! ra ! <-- ! vertex coordinates (optional)                  !
415
 
!  (ndim, nnod)    !    !     !                                                !
416
 
! volume(ncelet)   ! ra ! <-- ! cell volumes                                   !
417
360
! dt(ncelet)       ! ra ! <-- ! time step (per cell)                           !
418
361
! rtp, rtpa        ! ra ! <-- ! calculated variables at cell centers           !
419
362
!  (ncelet, *)     !    !     !  (at current and previous time steps)          !
432
375
!                  !    !     ! for velocities           ( vistl+visct)*gradu  !
433
376
!                  !    !     ! for pressure                         dt*gradp  !
434
377
!                  !    !     ! for scalars    cp*(viscls+visct/sigmas)*gradt  !
435
 
! w1,2,3,4,5,6     ! ra ! --- ! work arrays                                    !
436
 
!  (ncelet)        !    !     !  (computation of pressure gradient)            !
437
 
! coefu            ! ra ! --- ! work array                                     !
438
 
!  (nfabor, 3)     !    !     !  (computation of pressure gradient)            !
439
 
! rdevel(nrdeve)   ! ra ! <-> ! real work array for temporary development      !
440
 
! rtuser(nrtuse)   ! ra ! <-> ! user-reserved real work array                  !
441
 
! ra(*)            ! ra ! --- ! main real work array                           !
442
378
!__________________!____!_____!________________________________________________!
443
379
 
444
380
!     Type: i (integer), r (real), s (string), a (array), l (logical),
446
382
!     mode: <-- input, --> output, <-> modifies data, --- work array
447
383
!===============================================================================
448
384
 
 
385
!===============================================================================
 
386
! Module files
 
387
!===============================================================================
 
388
 
 
389
use paramx
 
390
use numvar
 
391
use optcal
 
392
use cstphy
 
393
use cstnum
 
394
use entsor
 
395
use parall
 
396
use period
 
397
use ihmpre
 
398
use mesh
 
399
 
 
400
!===============================================================================
 
401
 
449
402
implicit none
450
403
 
451
 
!===============================================================================
452
 
! Common blocks
453
 
!===============================================================================
454
 
 
455
 
include "paramx.h"
456
 
include "pointe.h"
457
 
include "numvar.h"
458
 
include "optcal.h"
459
 
include "cstphy.h"
460
 
include "cstnum.h"
461
 
include "entsor.h"
462
 
include "parall.h"
463
 
include "period.h"
464
 
include "ihmpre.h"
465
 
 
466
 
!===============================================================================
467
 
 
468
404
! Arguments
469
405
 
470
 
integer          idbia0 , idbra0
471
 
integer          ndim   , ncelet , ncel   , nfac   , nfabor
472
 
integer          nfml   , nprfml
473
 
integer          nnod   , lndfac , lndfbr , ncelbr
474
 
integer          nvar   , nscal  , nphas
475
 
integer          nideve , nrdeve , nituse , nrtuse
 
406
integer          nvar   , nscal
476
407
 
477
 
integer          ifacel(2,nfac) , ifabor(nfabor)
478
 
integer          ifmfbr(nfabor) , ifmcel(ncelet)
479
 
integer          iprfml(nfml,nprfml), maxelt, lstelt(maxelt)
480
 
integer          ipnfac(nfac+1), nodfac(lndfac)
481
 
integer          ipnfbr(nfabor+1), nodfbr(lndfbr)
482
408
integer          icodcl(nfabor,nvar)
483
 
integer          itrifb(nfabor,nphas), itypfb(nfabor,nphas)
484
 
integer          idevel(nideve), ituser(nituse), ia(*)
 
409
integer          itrifb(nfabor), itypfb(nfabor)
485
410
 
486
 
double precision xyzcen(ndim,ncelet)
487
 
double precision surfac(ndim,nfac), surfbo(ndim,nfabor)
488
 
double precision cdgfac(ndim,nfac), cdgfbo(ndim,nfabor)
489
 
double precision xyznod(ndim,nnod), volume(ncelet)
490
411
double precision dt(ncelet), rtp(ncelet,*), rtpa(ncelet,*)
491
412
double precision propce(ncelet,*)
492
413
double precision propfa(nfac,*), propfb(nfabor,*)
493
414
double precision coefa(nfabor,*), coefb(nfabor,*)
494
415
double precision rcodcl(nfabor,nvar,3)
495
 
double precision w1(ncelet),w2(ncelet),w3(ncelet)
496
 
double precision w4(ncelet),w5(ncelet),w6(ncelet)
497
 
double precision coefu(nfabor,ndim)
498
 
double precision rdevel(nrdeve), rtuser(nrtuse), ra(*)
499
416
 
500
417
! Local variables
501
418
 
502
 
integer          idebia, idebra, ielt
 
419
integer          ielt
503
420
integer          ifac, iel, ii, ivar, iphas
504
421
integer          ilelt, nlelt
505
422
double precision uref2, d2s3
507
424
double precision xintur
508
425
double precision xkent, xeent
509
426
 
 
427
integer, allocatable, dimension(:) :: lstelt
 
428
 
510
429
!===============================================================================
511
430
 
512
431
 
514
433
! 1.  Initialization
515
434
!===============================================================================
516
435
 
517
 
idebia = idbia0
518
 
idebra = idbra0
 
436
! Allocate a temporary array for boundary faces selection
 
437
allocate(lstelt(nfabor))
 
438
 
519
439
 
520
440
d2s3 = 2.d0/3.d0
521
441
 
527
447
!         Set the boundary condition for each face
528
448
!===============================================================================
529
449
 
530
 
! --- For boundary faces of color 2 and x <= 0.01,
531
 
!     assign an inlet for all phases
 
450
! --- For boundary faces of color 1,
 
451
!     assign an inlet
532
452
call getfbr('1', nlelt, lstelt)
533
453
!==========
534
454
 
552
472
! End
553
473
!----
554
474
 
 
475
! Deallocate the temporary array
 
476
deallocate(lstelt)
 
477
 
555
478
return
556
479
end subroutine