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

« back to all changes in this revision

Viewing changes to src/turb/visv2f.f90

  • Committer: Package Import Robot
  • Author(s): Sylvestre Ledru
  • Date: 2011-11-01 17:43:32 UTC
  • mto: (6.1.7 sid)
  • mto: This revision was merged to the branch mainline in revision 11.
  • Revision ID: package-import@ubuntu.com-20111101174332-tl4vk45no0x3emc3
Tags: upstream-2.1.0
ImportĀ upstreamĀ versionĀ 2.1.0

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 visv2f &
 
24
!================
 
25
 
 
26
 ( nvar   , nscal  , ncepdp , ncesmp ,                            &
 
27
   icepdc , icetsm , itypsm ,                                     &
 
28
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
 
29
   coefa  , coefb  , ckupdc , smacel )
 
30
 
 
31
!===============================================================================
 
32
! FONCTION :
 
33
! --------
 
34
 
 
35
! CALCUL DE LA VISCOSITE TURBULENTE POUR
 
36
!          LE MODELE K-OMEGA V2F-BL
 
37
 
 
38
 
 
39
! On dispose des types de faces de bord au pas de temps
 
40
!   precedent (sauf au premier pas de temps, ou les tableaux
 
41
!   ITYPFB et ITRIFB n'ont pas ete renseignes)
 
42
 
 
43
! Arguments
 
44
!__________________.____._____.________________________________________________.
 
45
! name             !type!mode ! role                                           !
 
46
!__________________!____!_____!________________________________________________!
 
47
! nvar             ! i  ! <-- ! total number of variables                      !
 
48
! nscal            ! i  ! <-- ! total number of scalars                        !
 
49
! ncepdp           ! i  ! <-- ! number of cells with head loss                 !
 
50
! ncesmp           ! i  ! <-- ! number of cells with mass source term          !
 
51
! icepdc(ncelet    ! te ! <-- ! numero des ncepdp cellules avec pdc            !
 
52
! icetsm(ncesmp    ! te ! <-- ! numero des cellules a source de masse          !
 
53
! itypsm           ! te ! <-- ! type de source de masse pour les               !
 
54
! (ncesmp,nvar)    !    !     !  variables (cf. ustsma)                        !
 
55
! dt(ncelet)       ! ra ! <-- ! time step (per cell)                           !
 
56
! rtp, rtpa        ! ra ! <-- ! calculated variables at cell centers           !
 
57
!  (ncelet, *)     !    !     !  (at current and previous time steps)          !
 
58
! propce(ncelet, *)! ra ! <-- ! physical properties at cell centers            !
 
59
! propfa(nfac, *)  ! ra ! <-- ! physical properties at interior face centers   !
 
60
! propfb(nfabor, *)! ra ! <-- ! physical properties at boundary face centers   !
 
61
! coefa, coefb     ! ra ! <-- ! boundary conditions                            !
 
62
!  (nfabor, *)     !    !     !                                                !
 
63
! ckupdc           ! tr ! <-- ! tableau de travail pour pdc                    !
 
64
!  (ncepdp,6)      !    !     !                                                !
 
65
! smacel           ! tr ! <-- ! valeur des variables associee a la             !
 
66
! (ncesmp,*   )    !    !     !  source de masse                               !
 
67
!                  !    !     !  pour ivar=ipr, smacel=flux de masse           !
 
68
!__________________!____!_____!________________________________________________!
 
69
 
 
70
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
 
71
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
 
72
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
 
73
!            --- tableau de travail
 
74
!===============================================================================
 
75
 
 
76
!===============================================================================
 
77
! Module files
 
78
!===============================================================================
 
79
 
 
80
use paramx
 
81
use dimens, only: ndimfb
 
82
use numvar
 
83
use optcal
 
84
use cstphy
 
85
use entsor
 
86
use pointe, only: coefau, coefbu
 
87
use mesh
 
88
 
 
89
!===============================================================================
 
90
 
 
91
implicit none
 
92
 
 
93
! Arguments
 
94
 
 
95
integer          nvar   , nscal
 
96
integer          ncepdp , ncesmp
 
97
 
 
98
integer          icepdc(ncepdp)
 
99
integer          icetsm(ncesmp), itypsm(ncesmp,nvar)
 
100
 
 
101
double precision dt(ncelet), rtp(ncelet,*), rtpa(ncelet,*)
 
102
double precision propce(ncelet,*)
 
103
double precision propfa(nfac,*), propfb(ndimfb,*)
 
104
double precision coefa(ndimfb,*), coefb(ndimfb,*)
 
105
double precision ckupdc(ncepdp,6), smacel(ncesmp,nvar)
 
106
 
 
107
! Local variables
 
108
 
 
109
integer          iel, iccocg, inc
 
110
integer          ipcliu, ipcliv, ipcliw
 
111
integer          ipcrom, ipcvis, ipcvst
 
112
 
 
113
double precision s11, s22, s33
 
114
double precision dudy, dudz, dvdx, dvdz, dwdx, dwdy
 
115
double precision xk, xe, xrom, xnu
 
116
double precision ttke, ttmin, ttlim, tt
 
117
 
 
118
logical          ilved
 
119
 
 
120
double precision, allocatable, dimension(:) :: s2
 
121
double precision, dimension(:,:,:), allocatable :: gradv
 
122
 
 
123
!===============================================================================
 
124
 
 
125
!===============================================================================
 
126
! 1.  INITIALISATION
 
127
!===============================================================================
 
128
 
 
129
! --- Memoire
 
130
allocate(s2(ncelet))
 
131
 
 
132
! --- Rang des variables dans PROPCE (prop. physiques au centre)
 
133
ipcvis = ipproc(iviscl)
 
134
ipcvst = ipproc(ivisct)
 
135
ipcrom = ipproc(irom  )
 
136
 
 
137
! --- Rang des c.l. des variables dans COEFA COEFB
 
138
!        (c.l. std, i.e. non flux)
 
139
ipcliu = iclrtp(iu,icoef)
 
140
ipcliv = iclrtp(iv,icoef)
 
141
ipcliw = iclrtp(iw,icoef)
 
142
 
 
143
!===============================================================================
 
144
! 2.  CALCUL DES GRADIENTS DE VITESSE ET DE
 
145
!       S2 = 2* (S11**2+S22**2+S33**2+2*(S12**2+S13**2+S23**2)
 
146
!===============================================================================
 
147
 
 
148
! Allocate temporary arrays for gradients calculation
 
149
allocate(gradv(ncelet,3,3))
 
150
 
 
151
iccocg = 1
 
152
inc = 1
 
153
 
 
154
if (ivelco.eq.1) then
 
155
 
 
156
  ilved = .false.
 
157
 
 
158
  call grdvec &
 
159
  !==========
 
160
( iu  , imrgra , inc    , iccocg ,                      &
 
161
  nswrgr(iu) , imligr(iu) , iwarni(iu) ,                &
 
162
  nfecra , epsrgr(iu) , climgr(iu) , extrag(iu) ,       &
 
163
  ilved ,                                               &
 
164
  rtpa(1,iu) ,  coefau , coefbu,                        &
 
165
  gradv  )
 
166
 
 
167
else
 
168
 
 
169
  call grdvni &
 
170
  !==========
 
171
( iu  , imrgra , inc    , iccocg ,                      &
 
172
  nswrgr(iu) , imligr(iu) , iwarni(iu) ,                &
 
173
  nfecra , epsrgr(iu) , climgr(iu) , extrag(iu) ,       &
 
174
  rtpa(1,iu) , coefa(1,ipcliu) , coefb(1,ipcliu) ,      &
 
175
  gradv  )
 
176
 
 
177
endif
 
178
 
 
179
do iel = 1, ncel
 
180
 
 
181
  s11  = gradv(iel,1,1)
 
182
  s22  = gradv(iel,2,2)
 
183
  s33  = gradv(iel,3,3)
 
184
  dudy = gradv(iel,2,1)
 
185
  dudz = gradv(iel,3,1)
 
186
  dvdx = gradv(iel,1,2)
 
187
  dvdz = gradv(iel,3,2)
 
188
  dwdx = gradv(iel,1,3)
 
189
  dwdy = gradv(iel,2,3)
 
190
 
 
191
  s2(iel) = 2.d0*(s11**2 + s22**2 + s33**2)                   &
 
192
       + (dudy+dvdx)**2 + (dudz+dwdx)**2 + (dvdz+dwdy)**2
 
193
 
 
194
enddo
 
195
 
 
196
! Free memory
 
197
deallocate(gradv)
 
198
 
 
199
!===============================================================================
 
200
! 3.  CALCUL DE LA VISCOSITE
 
201
!===============================================================================
 
202
 
 
203
do iel = 1, ncel
 
204
 
 
205
  xk = rtp(iel,ik)
 
206
  xe = rtp(iel,iep)
 
207
  xrom = propce(iel,ipcrom)
 
208
  xnu = propce(iel,ipcvis)/xrom
 
209
 
 
210
  ttke = xk / xe
 
211
  ttmin = cpalct*sqrt(xnu/xe)
 
212
  ttlim = 0.6d0/rtp(iel,iphi)/sqrt(3.d0)/cpalmu/s2(iel)
 
213
  tt = min(ttlim,sqrt(ttke**2 + ttmin**2))
 
214
 
 
215
  propce(iel,ipcvst) = cpalmu*xrom*tt*rtp(iel,iphi)*rtp(iel,ik)
 
216
 
 
217
enddo
 
218
 
 
219
! Free memory
 
220
deallocate(s2)
 
221
 
 
222
!----
 
223
! FORMAT
 
224
!----
 
225
 
 
226
 
 
227
!----
 
228
! FIN
 
229
!----
 
230
 
 
231
return
 
232
end subroutine