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

« back to all changes in this revision

Viewing changes to users/base/ustssa.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
!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.
 
22
 
 
23
!-------------------------------------------------------------------------------
 
24
 
 
25
subroutine ustssa &
 
26
!================
 
27
 
 
28
 ( nvar   , nscal  , ncepdp , ncesmp ,                            &
 
29
   icepdc , icetsm , itypsm ,                                     &
 
30
   dt     , rtpa   , propce , propfa , propfb ,                   &
 
31
   coefa  , coefb  , ckupdc , smacel , tinssa , divu   ,          &
 
32
   crvexp , crvimp )
 
33
 
 
34
!===============================================================================
 
35
! Purpose:
 
36
! -------
 
37
 
 
38
!    User subroutine.
 
39
 
 
40
!    Additional right-hand side source terms for the viscosity-like variable
 
41
!    when using the Spalart-Allmaras model (ITURB=70)
 
42
!
 
43
! Usage
 
44
! -----
 
45
!
 
46
! The additional source term is decomposed into an explicit part (crvexp) and
 
47
! an implicit part (crvimp) that must be provided here.
 
48
! The resulting equations solved by the code are:
 
49
!
 
50
!  rho*volume*d(nusa)/dt   + .... = crvimp*nusa   + crvexp
 
51
!
 
52
! Note that crvexp, crvimp are defined after the Finite Volume
 
53
! integration over the cells, so they include the "volume" term. More precisely:
 
54
!   - crvexp is expressed in kg.m2/s2
 
55
!   - crvimp is expressed in kg/s
 
56
!
 
57
! The crvexp, crvimp arrays are already initialized to 0 before
 
58
! entering the routine. It is not needed to do it in the routine (waste of CPU time).
 
59
!
 
60
! For stability reasons, Code_Saturne will not add -crvimp directly to the
 
61
! diagonal of the matrix, but Max(-crvimp,0). This way, the crvimp term is
 
62
! treated implicitely only if it strengthens the diagonal of the matrix.
 
63
! However, when using the second-order in time scheme, this limitation cannot
 
64
! be done anymore and -crvimp is added directly. The user should therefore test
 
65
! the negativity of crvimp by himself.
 
66
!
 
67
! When using the second-order in time scheme, one should supply:
 
68
!   - crvexp at time n
 
69
!   - crvimp at time n+1/2
 
70
!
 
71
! When entering the routine, two additional work arrays are already set for
 
72
! potential user need:
 
73
!   tinssa =  2 (S11)**2 + 2 (S22)**2 + 2 (S33)**2
 
74
!          +  (2 S12)**2 + (2 S13)**2 + (2 S23)**2
 
75
!
 
76
!          where Sij = (dUi/dxj+dUj/dxi)/2
 
77
!
 
78
!   divu = du/dx + dv/dy + dw/dz
 
79
 
 
80
 
 
81
 
 
82
!
 
83
! The selection of cells where to apply the source terms is based on a getcel
 
84
! command. For more info on the syntax of the getcel command, refer to the
 
85
! user manual or to the comments on the similar command getfbr in the routine
 
86
! usclim.
 
87
 
 
88
!-------------------------------------------------------------------------------
 
89
! Arguments
 
90
!__________________.____._____.________________________________________________.
 
91
! name             !type!mode ! role                                           !
 
92
!__________________!____!_____!________________________________________________!
 
93
! nvar             ! i  ! <-- ! total number of variables                      !
 
94
! nscal            ! i  ! <-- ! total number of scalars                        !
 
95
! ncepdp           ! i  ! <-- ! number of cells with head loss terms           !
 
96
! ncesmp           ! i  ! <-- ! number of cells with mass source term          !
 
97
! icepdc(ncepdp)   ! ia ! <-- ! index number of cells with head loss terms     !
 
98
! icetsm(ncesmp)   ! ia ! <-- ! index number of cells with mass source terms   !
 
99
! itypsm           ! ia ! <-- ! type of mass source term for each variable     !
 
100
!  (ncesmp,nvar)   !    !     !  (see ustsma)                                  !
 
101
! dt(ncelet)       ! ra ! <-- ! time step (per cell)                           !
 
102
! rtpa             ! ra ! <-- ! calculated variables at cell centers           !
 
103
!  (ncelet, *)     !    !     !  (preceding time steps)                        !
 
104
! propce(ncelet, *)! ra ! <-- ! physical properties at cell centers            !
 
105
! propfa(nfac, *)  ! ra ! <-- ! physical properties at interior face centers   !
 
106
! propfb(nfabor, *)! ra ! <-- ! physical properties at boundary face centers   !
 
107
! coefa, coefb     ! ra ! <-- ! boundary conditions                            !
 
108
!  (nfabor, *)     !    !     !                                                !
 
109
! ckupdc(ncepdp,6) ! ra ! <-- ! head loss coefficient                          !
 
110
! smacel           ! ra ! <-- ! value associated to each variable in the mass  !
 
111
!  (ncesmp,nvar)   !    !     !  source terms or mass rate (see ustsma)        !
 
112
! tinssa           ! ra ! <-- ! tubulent production term (see comment above)   !
 
113
! divu             ! ra ! <-- ! velocity divergence (see comment above)        !
 
114
! crvexp           ! ra ! --> ! explicit part of the source term for k         !
 
115
! crvimp           ! ra ! --> ! implicit part of the source term for k         !
 
116
!__________________!____!_____!________________________________________________!
 
117
 
 
118
!     Type: i (integer), r (real), s (string), a (array), l (logical),
 
119
!           and composite types (ex: ra real array)
 
120
!     mode: <-- input, --> output, <-> modifies data, --- work array
 
121
!===============================================================================
 
122
 
 
123
!===============================================================================
 
124
! Module files
 
125
!===============================================================================
 
126
 
 
127
use paramx
 
128
use numvar
 
129
use entsor
 
130
use optcal
 
131
use cstphy
 
132
use parall
 
133
use period
 
134
use mesh
 
135
 
 
136
!===============================================================================
 
137
 
 
138
implicit none
 
139
 
 
140
! Arguments
 
141
 
 
142
integer          nvar   , nscal
 
143
integer          ncepdp , ncesmp
 
144
 
 
145
integer          icepdc(ncepdp)
 
146
integer          icetsm(ncesmp), itypsm(ncesmp,nvar)
 
147
 
 
148
double precision dt(ncelet), rtpa(ncelet,*)
 
149
double precision propce(ncelet,*)
 
150
double precision propfa(nfac,*), propfb(nfabor,*)
 
151
double precision coefa(nfabor,*), coefb(nfabor,*)
 
152
double precision ckupdc(ncepdp,6), smacel(ncesmp,nvar)
 
153
double precision tinssa(ncelet), divu(ncelet)
 
154
double precision crvexp(ncelet), crvimp(ncelet)
 
155
 
 
156
! Local variables
 
157
 
 
158
integer          iel, ipcrom
 
159
double precision ff, tau, xx
 
160
 
 
161
integer, allocatable, dimension(:) :: lstelt
 
162
 
 
163
!===============================================================================
 
164
 
 
165
! TEST_TO_REMOVE_FOR_USE_OF_SUBROUTINE_START
 
166
!===============================================================================
 
167
 
 
168
if(1.eq.1) return
 
169
 
 
170
!===============================================================================
 
171
! TEST_TO_REMOVE_FOR_USE_OF_SUBROUTINE_END
 
172
 
 
173
 
 
174
!===============================================================================
 
175
! 1. Initialization
 
176
!===============================================================================
 
177
 
 
178
! Allocate a temporary array for cells selection
 
179
allocate(lstelt(ncel))
 
180
 
 
181
 
 
182
! --- Index number of the density in the propce array
 
183
ipcrom = ipproc(irom)
 
184
 
 
185
if(iwarni(inusa).ge.1) then
 
186
  write(nfecra,1000)
 
187
endif
 
188
 
 
189
!===============================================================================
 
190
! 2. Example of arbitrary additional source term for nusa
 
191
 
 
192
!      Source term for k :
 
193
!         rho volume d(k)/dt       = ...
 
194
!                        ... - rho*volume*ff - rho*volume*nusa/tau
 
195
 
 
196
!      With xx = 2.d0, ff=3.d0 and tau = 4.d0
 
197
 
 
198
!===============================================================================
 
199
 
 
200
! --- Explicit source terms
 
201
 
 
202
ff  = 3.d0
 
203
tau = 4.d0
 
204
xx  = 2.d0
 
205
 
 
206
do iel = 1, ncel
 
207
  crvexp(iel) = -propce(iel,ipcrom)*volume(iel)*ff
 
208
enddo
 
209
 
 
210
! --- Implicit source terms
 
211
!        crvimp is already initialized to 0, no need to set it here
 
212
 
 
213
do iel = 1, ncel
 
214
  crvimp(iel) = -propce(iel,ipcrom)*volume(iel)/tau
 
215
enddo
 
216
 
 
217
!--------
 
218
! Formats
 
219
!--------
 
220
 
 
221
 1000 format(' User source terms for Spalart-Allmaras',/)
 
222
 
 
223
!----
 
224
! End
 
225
!----
 
226
 
 
227
! Deallocate the temporary array
 
228
deallocate(lstelt)
 
229
 
 
230
return
 
231
end subroutine