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

« back to all changes in this revision

Viewing changes to src/alge/visort.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 visort &
 
24
!================
 
25
 
 
26
 ( imvisf ,                                                       &
 
27
   w1     , w2     , w3     ,                                     &
 
28
   viscf  , viscb  )
 
29
 
 
30
!===============================================================================
 
31
! FONCTION :
 
32
! ----------
 
33
 
 
34
! CALCUL DE LA VITESSE DE DIFFUSION "ORTHOTROPE"
 
35
! VISCF,B = VISCOSITE*SURFACE/DISTANCE, HOMOGENE A UN DEBIT EN KG/S
 
36
 
 
37
!         =
 
38
! (NX**2*VISC11_MOY_FACE
 
39
! +NY**2*VISC22_MOY_FACE+NZ**2*VISC33_MOY_FACE)*SURFACE/DISTANCE
 
40
 
 
41
! LA VISCOSITE EST DONNE PAR W1, W2, W3
 
42
 
 
43
! RQE : A PRIORI, PAS BESOIN DE TECHNIQUE DE RECONSTRUCTION
 
44
!  ( A AMELIORER SI NECESSAIRE )
 
45
 
 
46
!-------------------------------------------------------------------------------
 
47
! Arguments
 
48
!__________________.____._____.________________________________________________.
 
49
! name             !type!mode ! role                                           !
 
50
!__________________!____!_____!________________________________________________!
 
51
! imvisf           ! e  ! <-- ! methode de calcul de la visc face              !
 
52
!                  !    !     !  = 0 arithmetique                              !
 
53
!                  !    !     !  = 1 harmonique                                !
 
54
! w1,2,3(ncelet    ! tr ! <-- ! valeurs de la viscosite                        !
 
55
! viscf(nfac)      ! tr ! --> ! visc*surface/dist aux faces internes           !
 
56
! viscb(nfabor     ! tr ! --> ! visc*surface/dist aux faces de bord            !
 
57
!__________________!____!_____!________________________________________________!
 
58
 
 
59
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
 
60
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
 
61
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
 
62
!            --- tableau de travail
 
63
!===============================================================================
 
64
 
 
65
!===============================================================================
 
66
! Module files
 
67
!===============================================================================
 
68
 
 
69
use paramx
 
70
use pointe
 
71
use parall
 
72
use period
 
73
use mesh
 
74
 
 
75
!===============================================================================
 
76
 
 
77
implicit none
 
78
 
 
79
! Arguments
 
80
 
 
81
integer          imvisf
 
82
 
 
83
 
 
84
double precision w1(ncelet), w2(ncelet), w3(ncelet)
 
85
double precision viscf(nfac), viscb(nfabor)
 
86
 
 
87
! Local variables
 
88
 
 
89
integer          ifac, ii, jj
 
90
double precision viscxi, viscxj, viscyi, viscyj, visczi, visczj
 
91
double precision sx2, sy2, sz2, distbf, pnd, surfn
 
92
 
 
93
!===============================================================================
 
94
 
 
95
! ---> TRAITEMENT DU PARALLELISME ET DE LA PERIODICITE
 
96
 
 
97
if (irangp.ge.0.or.iperio.eq.1) then
 
98
  call syndia(w1, w2, w3)
 
99
  !==========
 
100
endif
 
101
 
 
102
 
 
103
if( imvisf.eq.0 ) then
 
104
 
 
105
  do ifac = 1, nfac
 
106
 
 
107
    ii = ifacel(1,ifac)
 
108
    jj = ifacel(2,ifac)
 
109
 
 
110
    surfn = surfan(ifac)
 
111
 
 
112
    viscxi = w1(ii)
 
113
    viscxj = w1(jj)
 
114
    viscyi = w2(ii)
 
115
    viscyj = w2(jj)
 
116
    visczi = w3(ii)
 
117
    visczj = w3(jj)
 
118
 
 
119
    sx2    = surfac(1,ifac)**2
 
120
    sy2    = surfac(2,ifac)**2
 
121
    sz2    = surfac(3,ifac)**2
 
122
 
 
123
    viscf(ifac) = 0.5d0*(                                         &
 
124
       (viscxi+viscxj)*sx2                                        &
 
125
     + (viscyi+viscyj)*sy2                                        &
 
126
     + (visczi+visczj)*sz2 ) / (surfn*dist(ifac))
 
127
 
 
128
  enddo
 
129
 
 
130
else
 
131
 
 
132
  do ifac = 1,nfac
 
133
 
 
134
    ii = ifacel(1,ifac)
 
135
    jj = ifacel(2,ifac)
 
136
 
 
137
    surfn = surfan(ifac)
 
138
    pnd  = pond(ifac)
 
139
 
 
140
    viscxi = w1(ii)
 
141
    viscxj = w1(jj)
 
142
    viscyi = w2(ii)
 
143
    viscyj = w2(jj)
 
144
    visczi = w3(ii)
 
145
    visczj = w3(jj)
 
146
 
 
147
    sx2    = surfac(1,ifac)**2
 
148
    sy2    = surfac(2,ifac)**2
 
149
    sz2    = surfac(3,ifac)**2
 
150
 
 
151
    viscf(ifac) =                                                 &
 
152
      ( viscxi*viscxj*sx2                                         &
 
153
              /(pnd*viscxi+(1.d0-pnd)*viscxj)                     &
 
154
      + viscyi*viscyj*sy2                                         &
 
155
              /(pnd*viscyi+(1.d0-pnd)*viscyj)                     &
 
156
      + visczi*visczj*sz2                                         &
 
157
              /(pnd*visczi+(1.d0-pnd)*visczj)                     &
 
158
       ) /(surfn*dist(ifac))
 
159
  enddo
 
160
 
 
161
endif
 
162
 
 
163
do ifac=1,nfabor
 
164
 
 
165
  ii = ifabor(ifac)
 
166
 
 
167
  surfn = surfbn(ifac)
 
168
  distbf = distb(ifac)
 
169
 
 
170
  viscxi = w1(ii)
 
171
  viscyi = w2(ii)
 
172
  visczi = w3(ii)
 
173
 
 
174
  sx2    = surfbo(1,ifac)**2
 
175
  sy2    = surfbo(2,ifac)**2
 
176
  sz2    = surfbo(3,ifac)**2
 
177
 
 
178
  viscb(ifac) =                                                   &
 
179
    (viscxi*sx2+viscyi*sy2+visczi*sz2)/(surfn*distbf)
 
180
 
 
181
enddo
 
182
 
 
183
!----
 
184
! FIN
 
185
!----
 
186
 
 
187
return
 
188
 
 
189
end subroutine