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

« back to all changes in this revision

Viewing changes to users/cogz/usebuc.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-beta2
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
 
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.
28
22
 
29
23
!-------------------------------------------------------------------------------
30
24
 
31
25
subroutine usebuc &
32
26
!================
33
27
 
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 ,                            &
 
28
 ( nvar   , nscal  ,                                              &
41
29
   icodcl , itrifb , itypfb , izfppp ,                            &
42
 
   idevel , ituser , ia     ,                                     &
43
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
44
30
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
45
 
   coefa  , coefb  , rcodcl ,                                     &
46
 
   w1     , w2     , w3     , w4     , w5     , w6     , coefu  , &
47
 
   rdevel , rtuser , ra     )
 
31
   coefa  , coefb  , rcodcl )
48
32
 
49
33
!===============================================================================
50
34
! Purpose:
285
269
!                                 rcodcl(ifac, ivar, 2) = rinfin
286
270
!                                 rcodcl(ifac, ivar, 3) = 0.d0)
287
271
!        Especially, we may have for example:
288
 
!        -> set itypfb(ifac, iphas) = iparoi
 
272
!        -> set itypfb(ifac) = iparoi
289
273
!        which prescribes default wall conditions for all variables at
290
274
!        face ifac,
291
275
!        -> and define IN ADDITION for variable ivar on this face
344
328
! Cell values
345
329
!               Let         iel = ifabor(ifac)
346
330
 
347
 
! * Density                         phase iphas, cell iel:
348
 
!                  propce(iel, ipproc(irom(iphas)))
349
 
! * Dynamic molecular viscosity     phase iphas, cell iel:
350
 
!                  propce(iel, ipproc(iviscl(iphas)))
351
 
! * Turbulent viscosity   dynamique phase iphas, cell iel:
352
 
!                  propce(iel, ipproc(ivisct(iphas)))
353
 
! * Specific heat                   phase iphas, cell iel:
354
 
!                  propce(iel, ipproc(icp(iphasl))
 
331
! * Density                                      cell iel:
 
332
!                  propce(iel, ipproc(irom))
 
333
! * Dynamic molecular viscosity                  cell iel:
 
334
!                  propce(iel, ipproc(iviscl))
 
335
! * Turbulent viscosity   dynamique              cell iel:
 
336
!                  propce(iel, ipproc(ivisct))
 
337
! * Specific heat                                cell iel:
 
338
!                  propce(iel, ipproc(icp))
355
339
! * Diffusivity: lambda          scalaire iscal, cell iel:
356
340
!                  propce(iel, ipproc(ivisls(iscal)))
357
341
 
358
342
! Boundary face values
359
343
 
360
 
! * Density                        phase iphas, boundary face ifac :
361
 
!                  propfb(ifac, ipprob(irom(iphas)))
 
344
! * Density                                     boundary face ifac :
 
345
!                  propfb(ifac, ipprob(irom))
362
346
! * Mass flow relative to variable ivar, boundary face ifac:
363
347
!      (i.e. the mass flow used for convecting ivar)
364
348
!                  propfb(ifac, pprob(ifluma(ivar )))
371
355
!__________________.____._____.________________________________________________.
372
356
! name             !type!mode ! role                                           !
373
357
!__________________!____!_____!________________________________________________!
374
 
! idbia0           ! i  ! <-- ! number of first free position in ia            !
375
 
! idbra0           ! i  ! <-- ! number of first free position in ra            !
376
 
! ndim             ! i  ! <-- ! spatial dimension                              !
377
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
378
 
! ncel             ! i  ! <-- ! number of cells                                !
379
 
! nfac             ! i  ! <-- ! number of interior faces                       !
380
 
! nfabor           ! i  ! <-- ! number of boundary faces                       !
381
 
! nfml             ! i  ! <-- ! number of families (group classes)             !
382
 
! nprfml           ! i  ! <-- ! number of properties per family (group class)  !
383
 
! nnod             ! i  ! <-- ! number of vertices                             !
384
 
! lndfac           ! i  ! <-- ! size of nodfac indexed array                   !
385
 
! lndfbr           ! i  ! <-- ! size of nodfbr indexed array                   !
386
 
! ncelbr           ! i  ! <-- ! number of cells with faces on boundary         !
387
358
! nvar             ! i  ! <-- ! total number of variables                      !
388
359
! nscal            ! i  ! <-- ! total number of scalars                        !
389
 
! nphas            ! i  ! <-- ! number of phases                               !
390
 
! nideve, nrdeve   ! i  ! <-- ! sizes of idevel and rdevel arrays              !
391
 
! nituse, nrtuse   ! i  ! <-- ! sizes of ituser and rtuser arrays              !
392
 
! ifacel(2, nfac)  ! ia ! <-- ! interior faces -> cells connectivity           !
393
 
! ifabor(nfabor)   ! ia ! <-- ! boundary faces -> cells connectivity           !
394
 
! ifmfbr(nfabor)   ! ia ! <-- ! boundary face family numbers                   !
395
 
! ifmcel(ncelet)   ! ia ! <-- ! cell family numbers                            !
396
 
! iprfml           ! ia ! <-- ! property numbers per family                    !
397
 
!  (nfml, nprfml)  !    !     !                                                !
398
 
! maxelt           !  e ! <-- ! max number of cells and faces (int/boundary)   !
399
 
! lstelt(maxelt)   ! ia ! --- ! work array                                     !
400
 
! ipnfac(nfac+1)   ! ia ! <-- ! interior faces -> vertices index (optional)    !
401
 
! nodfac(lndfac)   ! ia ! <-- ! interior faces -> vertices list (optional)     !
402
 
! ipnfbr(nfabor+1) ! ia ! <-- ! boundary faces -> vertices index (optional)    !
403
 
! nodfac(lndfbr)   ! ia ! <-- ! boundary faces -> vertices list (optional)     !
404
360
! icodcl           ! ia ! --> ! boundary condition code                        !
405
361
!  (nfabor, nvar)  !    !     ! = 1  -> Dirichlet                              !
406
362
!                  !    !     ! = 2  -> flux density                           !
410
366
!                  !    !     ! = 9  -> free inlet/outlet (velocity)           !
411
367
!                  !    !     !         inflowing possibly blocked             !
412
368
! itrifb(nfabor    ! ia ! <-- ! indirection for boundary faces ordering)       !
413
 
!  (nfabor, nphas) !    !     !                                                !
414
369
! itypfb           ! ia ! --> ! boundary face types                            !
415
 
!  (nfabor, nphas) !    !     !                                                !
416
 
! idevel(nideve)   ! ia ! <-- ! integer work array for temporary developpement !
417
 
! ituser(nituse    ! ia ! <-- ! user-reserved integer work array               !
418
 
! ia(*)            ! ia ! --- ! main integer work array                        !
419
 
! xyzcen           ! ra ! <-- ! cell centers                                   !
420
 
!  (ndim, ncelet)  !    !     !                                                !
421
 
! surfac           ! ra ! <-- ! interior faces surface vectors                 !
422
 
!  (ndim, nfac)    !    !     !                                                !
423
 
! surfbo           ! ra ! <-- ! boundary faces surface vectors                 !
424
 
!  (ndim, nfavor)  !    !     !                                                !
425
 
! cdgfac           ! ra ! <-- ! interior faces centers of gravity              !
426
 
!  (ndim, nfac)    !    !     !                                                !
427
 
! cdgfbo           ! ra ! <-- ! boundary faces centers of gravity              !
428
 
!  (ndim, nfabor)  !    !     !                                                !
429
 
! xyznod           ! ra ! <-- ! vertex coordinates (optional)                  !
430
 
!  (ndim, nnod)    !    !     !                                                !
431
 
! volume(ncelet)   ! ra ! <-- ! cell volumes                                   !
432
370
! dt(ncelet)       ! ra ! <-- ! time step (per cell)                           !
433
371
! rtp, rtpa        ! ra ! <-- ! calculated variables at cell centers           !
434
372
!  (ncelet, *)     !    !     !  (at current and preceding time steps)         !
447
385
!                  !    !     ! for velocities           ( vistl+visct)*gradu  !
448
386
!                  !    !     ! for pressure                         dt*gradp  !
449
387
!                  !    !     ! for scalars    cp*(viscls+visct/sigmas)*gradt  !
450
 
! w1,2,3,4,5,6     ! ra ! --- ! work arrays                                    !
451
 
!  (ncelet)        !    !     !  (computation of pressure gradient)            !
452
 
! coefu            ! ra ! --- ! tab de trav                                    !
453
 
!  (nfabor, 3)     !    !     !  (computation of pressure gradient)            !
454
 
! rdevel(nrdeve)   ! ra ! <-> ! tab reel complementaire developemt             !
455
 
! rdevel(nideve)   ! ra ! <-- ! real work array for temporary developpement    !
456
 
! rtuser(nituse    ! ra ! <-- ! user-reserved real work array                  !
457
 
! ra(*)            ! ra ! --- ! main real work array                           !
458
388
!__________________!____!_____!________________________________________________!
459
389
 
460
390
!     Type: i (integer), r (real), s (string), a (array), l (logical),
462
392
!     mode: <-- input, --> output, <-> modifies data, --- work array
463
393
!===============================================================================
464
394
 
 
395
!===============================================================================
 
396
! Module files
 
397
!===============================================================================
 
398
 
 
399
use paramx
 
400
use numvar
 
401
use optcal
 
402
use cstphy
 
403
use cstnum
 
404
use entsor
 
405
use parall
 
406
use period
 
407
use ppppar
 
408
use ppthch
 
409
use coincl
 
410
use cpincl
 
411
use ppincl
 
412
use mesh
 
413
 
 
414
!===============================================================================
 
415
 
465
416
implicit none
466
417
 
467
 
!===============================================================================
468
 
!     Common Blocks
469
 
!===============================================================================
470
 
 
471
 
include "paramx.h"
472
 
include "pointe.h"
473
 
include "numvar.h"
474
 
include "optcal.h"
475
 
include "cstphy.h"
476
 
include "cstnum.h"
477
 
include "entsor.h"
478
 
include "parall.h"
479
 
include "period.h"
480
 
include "ppppar.h"
481
 
include "ppthch.h"
482
 
include "coincl.h"
483
 
include "cpincl.h"
484
 
include "ppincl.h"
485
 
 
486
 
!===============================================================================
487
 
 
488
418
! Arguments
489
419
 
490
 
integer          idbia0 , idbra0
491
 
integer          ndim   , ncelet , ncel   , nfac   , nfabor
492
 
integer          nfml   , nprfml
493
 
integer          nnod   , lndfac , lndfbr , ncelbr
494
 
integer          nvar   , nscal  , nphas
495
 
integer          nideve , nrdeve , nituse , nrtuse
 
420
integer          nvar   , nscal
496
421
 
497
 
integer          ifacel(2,nfac) , ifabor(nfabor)
498
 
integer          ifmfbr(nfabor) , ifmcel(ncelet)
499
 
integer          iprfml(nfml,nprfml)
500
 
integer          maxelt, lstelt(maxelt)
501
 
integer          ipnfac(nfac+1), nodfac(lndfac)
502
 
integer          ipnfbr(nfabor+1), nodfbr(lndfbr)
503
422
integer          icodcl(nfabor,nvar)
504
 
integer          itrifb(nfabor,nphas), itypfb(nfabor,nphas)
 
423
integer          itrifb(nfabor), itypfb(nfabor)
505
424
integer          izfppp(nfabor)
506
 
integer          idevel(nideve), ituser(nituse), ia(*)
507
425
 
508
 
double precision xyzcen(ndim,ncelet)
509
 
double precision surfac(ndim,nfac), surfbo(ndim,nfabor)
510
 
double precision cdgfac(ndim,nfac), cdgfbo(ndim,nfabor)
511
 
double precision xyznod(ndim,nnod), volume(ncelet)
512
426
double precision dt(ncelet), rtp(ncelet,*), rtpa(ncelet,*)
513
427
double precision propce(ncelet,*)
514
428
double precision propfa(nfac,*), propfb(nfabor,*)
515
429
double precision coefa(nfabor,*), coefb(nfabor,*)
516
430
double precision rcodcl(nfabor,nvar,3)
517
 
double precision w1(ncelet),w2(ncelet),w3(ncelet)
518
 
double precision w4(ncelet),w5(ncelet),w6(ncelet)
519
 
double precision coefu(nfabor,ndim)
520
 
double precision rdevel(nrdeve), rtuser(nrtuse), ra(*)
521
431
 
522
432
! Local Variables
523
433
 
524
 
integer          idebia, idebra
525
 
integer          ifac, iphas, izone, ii
 
434
integer          ifac, izone, ii
526
435
integer          ilelt, nlelt
527
436
 
528
437
double precision uref2, xkent, xeent, d2s3
529
438
 
 
439
integer, allocatable, dimension(:) :: lstelt
 
440
 
530
441
!===============================================================================
531
442
 
532
443
!===============================================================================
533
444
! 1.  INITIALISATION
534
 
 
535
445
!===============================================================================
536
446
 
537
 
idebia = idbia0
538
 
idebra = idbra0
 
447
! Allocate a temporary array for boundary faces selection
 
448
allocate(lstelt(nfabor))
 
449
 
539
450
 
540
451
d2s3 = 2.d0/3.d0
541
452
 
547
458
!         Set the boundary condition for each face
548
459
!===============================================================================
549
460
 
550
 
iphas = 1
551
 
 
552
 
 
553
461
! Definition of a burned gas inlet (pilot flame) for each face of colour 11
554
462
 
555
463
 
561
469
  ifac = lstelt(ilelt)
562
470
 
563
471
!   Type of pre-defined boundary condidition (see above)
564
 
  itypfb(ifac,iphas) = ientre
 
472
  itypfb(ifac) = ientre
565
473
 
566
474
!   Zone number (arbitrary number between 1 and n)
567
475
  izone = 1
577
485
  qimp (izone) = zero
578
486
!
579
487
!   b) an inlet velocity -> iqimp()  = 0
580
 
  rcodcl(ifac,iu(iphas),1) = 0.d0
581
 
  rcodcl(ifac,iv(iphas),1) = 0.d0
582
 
  rcodcl(ifac,iw(iphas),1) = 21.47d0
 
488
  rcodcl(ifac,iu,1) = 0.d0
 
489
  rcodcl(ifac,iv,1) = 0.d0
 
490
  rcodcl(ifac,iw,1) = 21.47d0
583
491
! ATTENTION: If iqimp()  = 1 the direction vector of the massfow has
584
492
!            to be given here.
585
493
!
596
504
 
597
505
  if(icalke(izone).eq.0) then
598
506
 
599
 
    uref2 = rcodcl(ifac,iu(iphas),1)**2                           &
600
 
           +rcodcl(ifac,iv(iphas),1)**2                           &
601
 
           +rcodcl(ifac,iw(iphas),1)**2
 
507
    uref2 = rcodcl(ifac,iu,1)**2                           &
 
508
           +rcodcl(ifac,iv,1)**2                           &
 
509
           +rcodcl(ifac,iw,1)**2
602
510
    uref2 = max(uref2,1.d-12)
603
511
    xkent  = epzero
604
512
    xeent  = epzero
608
516
      ( uref2, xintur(izone), dh(izone), cmu, xkappa,             &
609
517
        xkent, xeent )
610
518
 
611
 
    if    (itytur(iphas).eq.2) then
612
 
 
613
 
      rcodcl(ifac,ik(iphas),1)  = xkent
614
 
      rcodcl(ifac,iep(iphas),1) = xeent
615
 
 
616
 
    elseif(itytur(iphas).eq.3) then
617
 
 
618
 
      rcodcl(ifac,ir11(iphas),1) = d2s3*xkent
619
 
      rcodcl(ifac,ir22(iphas),1) = d2s3*xkent
620
 
      rcodcl(ifac,ir33(iphas),1) = d2s3*xkent
621
 
      rcodcl(ifac,ir12(iphas),1) = 0.d0
622
 
      rcodcl(ifac,ir13(iphas),1) = 0.d0
623
 
      rcodcl(ifac,ir23(iphas),1) = 0.d0
624
 
      rcodcl(ifac,iep(iphas),1)  = xeent
625
 
 
626
 
    elseif (iturb(iphas).eq.50) then
627
 
 
628
 
      rcodcl(ifac,ik(iphas),1)   = xkent
629
 
      rcodcl(ifac,iep(iphas),1)  = xeent
630
 
      rcodcl(ifac,iphi(iphas),1) = d2s3
631
 
      rcodcl(ifac,ifb(iphas),1)  = 0.d0
632
 
 
633
 
    elseif (iturb(iphas).eq.60) then
634
 
 
635
 
      rcodcl(ifac,ik(iphas),1)   = xkent
636
 
      rcodcl(ifac,iomg(iphas),1) = xeent/cmu/xkent
 
519
    if    (itytur.eq.2) then
 
520
 
 
521
      rcodcl(ifac,ik,1)  = xkent
 
522
      rcodcl(ifac,iep,1) = xeent
 
523
 
 
524
    elseif(itytur.eq.3) then
 
525
 
 
526
      rcodcl(ifac,ir11,1) = d2s3*xkent
 
527
      rcodcl(ifac,ir22,1) = d2s3*xkent
 
528
      rcodcl(ifac,ir33,1) = d2s3*xkent
 
529
      rcodcl(ifac,ir12,1) = 0.d0
 
530
      rcodcl(ifac,ir13,1) = 0.d0
 
531
      rcodcl(ifac,ir23,1) = 0.d0
 
532
      rcodcl(ifac,iep,1)  = xeent
 
533
 
 
534
    elseif (iturb.eq.50) then
 
535
 
 
536
      rcodcl(ifac,ik,1)   = xkent
 
537
      rcodcl(ifac,iep,1)  = xeent
 
538
      rcodcl(ifac,iphi,1) = d2s3
 
539
      rcodcl(ifac,ifb,1)  = 0.d0
 
540
 
 
541
    elseif (iturb.eq.60) then
 
542
 
 
543
      rcodcl(ifac,ik,1)   = xkent
 
544
      rcodcl(ifac,iomg,1) = xeent/cmu/xkent
 
545
 
 
546
    elseif (iturb.eq.70) then
 
547
 
 
548
      rcodcl(ifac,inusa,1) = cmu*xkent**2/xeent
637
549
 
638
550
    endif
639
551
 
664
576
  ifac = lstelt(ilelt)
665
577
 
666
578
!   Type of pre-defined boundary condidition (see above)
667
 
  itypfb(ifac,iphas) = ientre
 
579
  itypfb(ifac) = ientre
668
580
 
669
581
!   Zone number (arbitrary number between 1 and n)
670
582
  izone = 2
680
592
  qimp(izone)  = zero
681
593
!
682
594
!   b) an inlet velocity -> iqimp()  = 0
683
 
  rcodcl(ifac,iu(iphas),1) = 60.d0
684
 
  rcodcl(ifac,iv(iphas),1) = 0.d0
685
 
  rcodcl(ifac,iw(iphas),1) = 0.d0
 
595
  rcodcl(ifac,iu,1) = 60.d0
 
596
  rcodcl(ifac,iv,1) = 0.d0
 
597
  rcodcl(ifac,iw,1) = 0.d0
686
598
! ATTENTION: If iqimp()  = 1 the direction vector of the massfow has
687
599
!            to be given here.
688
600
 
718
630
  ifac = lstelt(ilelt)
719
631
 
720
632
!   Type de condition aux limites pour les variables standard
721
 
  itypfb(ifac,iphas)   = iparoi
 
633
  itypfb(ifac)   = iparoi
722
634
 
723
635
!   Zone number (arbitrary number between 1 and n)
724
636
  izone = 4
738
650
  ifac = lstelt(ilelt)
739
651
 
740
652
!   Type de condition aux limites pour les variables standard
741
 
  itypfb(ifac,iphas)   = isolib
 
653
  itypfb(ifac)   = isolib
742
654
 
743
655
!   Zone number (arbitrary number between 1 and n)
744
656
  izone = 5
759
671
  ifac = lstelt(ilelt)
760
672
 
761
673
!   Type de condition aux limites pour les variables standard
762
 
  itypfb(ifac,iphas)   = isymet
 
674
  itypfb(ifac)   = isymet
763
675
 
764
676
!   Zone number (arbitrary number between 1 and n)
765
677
  izone = 6
774
686
! END
775
687
!----
776
688
 
 
689
! Deallocate the temporary array
 
690
deallocate(lstelt)
 
691
 
777
692
return
778
693
end subroutine