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

« back to all changes in this revision

Viewing changes to src/alge/vectds.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 Code_Saturne, a general-purpose CFD tool.
 
4
!
 
5
! Copyright (C) 1998-2011 EDF S.A.
 
6
!
 
7
! This program is free software; you can redistribute it and/or modify it under
 
8
! the terms of the GNU General Public License as published by the Free Software
 
9
! Foundation; either version 2 of the License, or (at your option) any later
 
10
! version.
 
11
!
 
12
! This program is distributed in the hope that it will be useful, but WITHOUT
 
13
! ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
 
14
! FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
 
15
! details.
 
16
!
 
17
! You should have received a copy of the GNU General Public License along with
 
18
! this program; if not, write to the Free Software Foundation, Inc., 51 Franklin
 
19
! Street, Fifth Floor, Boston, MA 02110-1301, USA.
 
20
 
 
21
!-------------------------------------------------------------------------------
 
22
 
 
23
subroutine vectds &
 
24
!================
 
25
 
 
26
 ( vectx  , vecty  , vectz  ,                                     &
 
27
   valf   , valb   )
 
28
 
 
29
!===============================================================================
 
30
! FONCTION :
 
31
! ----------
 
32
 
 
33
! CALCUL A LA FACE DE (VECT)ij . S
 
34
!  A PARTIR DU VECTEUR VECTX, VECTY, VECTZ
 
35
! UTILISE POUR LE CALCUL DU TERME DE DIFFUSION DE Rij ET Epsilon
 
36
!  EN Rij-Epsilon LRR
 
37
 
 
38
!-------------------------------------------------------------------------------
 
39
! Arguments
 
40
!__________________.____._____.________________________________________________.
 
41
! name             !type!mode ! role                                           !
 
42
!__________________!____!_____!________________________________________________!
 
43
! vectx (ncelet    ! tr ! <-- ! composante x du vecteur   entre                !
 
44
! vecty (ncelet    ! tr ! <-- ! composante y du vecteur   entre                !
 
45
! vectz (ncelet    ! tr ! <-- ! composante z du vecteur   entre                !
 
46
! valf (nfac)      ! tr ! --> ! vect*surface      aux faces internes           !
 
47
! valb (nfabor     ! tr ! --> ! vect*surface      aux faces de bord            !
 
48
!__________________!____!_____!________________________________________________!
 
49
 
 
50
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
 
51
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
 
52
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
 
53
!            --- tableau de travail
 
54
!===============================================================================
 
55
 
 
56
!===============================================================================
 
57
! Module files
 
58
!===============================================================================
 
59
 
 
60
use paramx
 
61
use pointe
 
62
use parall
 
63
use period
 
64
use mesh
 
65
 
 
66
!===============================================================================
 
67
 
 
68
implicit none
 
69
 
 
70
! Arguments
 
71
 
 
72
double precision vectx(ncelet), vecty(ncelet), vectz(ncelet)
 
73
double precision valf(nfac), valb(nfabor)
 
74
 
 
75
! Local variables
 
76
 
 
77
integer          ifac, iel1, iel2
 
78
double precision valfx, valfy, valfz
 
79
 
 
80
!===============================================================================
 
81
 
 
82
! ---> TRAITEMENT DU PARALLELISME ET DE LA PERIODICITE
 
83
 
 
84
if (irangp.ge.0.or.iperio.eq.1) then
 
85
  call synvec(vectx, vecty, vectz)
 
86
  !==========
 
87
endif
 
88
 
 
89
 
 
90
do ifac = 1 , nfac
 
91
 
 
92
  iel1 = ifacel(1,ifac)
 
93
  iel2 = ifacel(2,ifac)
 
94
 
 
95
  valfx =       pond(ifac)  * vectx(iel1) +                       &
 
96
          (1.d0-pond(ifac)) * vectx(iel2)
 
97
  valfy =       pond(ifac)  * vecty(iel1) +                       &
 
98
          (1.d0-pond(ifac)) * vecty(iel2)
 
99
  valfz =       pond(ifac)  * vectz(iel1) +                       &
 
100
          (1.d0-pond(ifac)) * vectz(iel2)
 
101
 
 
102
  valf(ifac) = valfx*surfac(1,ifac) +                             &
 
103
               valfy*surfac(2,ifac) +                             &
 
104
               valfz*surfac(3,ifac)
 
105
 enddo
 
106
 
 
107
 do ifac = 1 , nfabor
 
108
 
 
109
!     On met VALB a zero, ce qui revient a negliger la partie
 
110
!       extradiagonale du tenseur de diffusion au bord.
 
111
!MO          IEL1 = IFABOR(IFAC)
 
112
!MOC
 
113
!MO          VALB(IFAC) = VECTX(IEL1)*SURFBO(1,IFAC) +
 
114
!MO     &                 VECTY(IEL1)*SURFBO(2,IFAC) +
 
115
!MO     &                 VECTZ(IEL1)*SURFBO(3,IFAC)
 
116
    valb(ifac) = 0.d0
 
117
 
 
118
 enddo
 
119
 
 
120
 return
 
121
 end