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

« back to all changes in this revision

Viewing changes to src/cfbl/cfdttv.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
 
!     This file is part of the Code_Saturne Kernel, element of the
4
 
!     Code_Saturne CFD tool.
5
 
 
6
 
!     Copyright (C) 1998-2009 EDF S.A., France
7
 
 
8
 
!     contact: saturne-support@edf.fr
9
 
 
10
 
!     The Code_Saturne Kernel is free software; you can redistribute it
11
 
!     and/or modify it under the terms of the GNU General Public License
12
 
!     as published by the Free Software Foundation; either version 2 of
13
 
!     the License, or (at your option) any later version.
14
 
 
15
 
!     The Code_Saturne Kernel is distributed in the hope that it will be
16
 
!     useful, but WITHOUT ANY WARRANTY; without even the implied warranty
17
 
!     of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18
 
!     GNU General Public License for more details.
19
 
 
20
 
!     You should have received a copy of the GNU General Public License
21
 
!     along with the Code_Saturne Kernel; if not, write to the
22
 
!     Free Software Foundation, Inc.,
23
 
!     51 Franklin St, Fifth Floor,
24
 
!     Boston, MA  02110-1301  USA
 
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.
25
20
 
26
21
!-------------------------------------------------------------------------------
27
22
 
28
23
subroutine cfdttv &
29
24
!================
30
25
 
31
 
 ( idbia0 , idbra0 ,                                              &
32
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
33
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
34
 
   nvar   , nscal  , nphas  , ncepdp , ncesmp ,                   &
35
 
   nideve , nrdeve , nituse , nrtuse , iwarnp ,                   &
36
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
37
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
 
26
 ( nvar   , nscal  , ncepdp , ncesmp ,                            &
 
27
   iwarnp ,                                                       &
38
28
   icepdc , icetsm , itypsm ,                                     &
39
 
   idevel , ituser , ia     ,                                     &
40
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
41
29
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
42
30
   coefa  , coefb  , ckupdc , smacel ,                            &
43
31
   wcf    ,                                                       &
44
 
   wflmas , wflmab , viscb  , w1     , w2     , w3     ,          &
45
 
   w4     , w5     , w6     ,                                     &
46
 
   rdevel , rtuser , ra     )
 
32
   wflmas , wflmab , viscb  )
47
33
 
48
34
!===============================================================================
49
35
! FONCTION :
56
42
!__________________.____._____.________________________________________________.
57
43
! name             !type!mode ! role                                           !
58
44
!__________________!____!_____!________________________________________________!
59
 
! idbia0           ! i  ! <-- ! number of first free position in ia            !
60
 
! idbra0           ! i  ! <-- ! number of first free position in ra            !
61
 
! ndim             ! i  ! <-- ! spatial dimension                              !
62
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
63
 
! ncel             ! i  ! <-- ! number of cells                                !
64
 
! nfac             ! i  ! <-- ! number of interior faces                       !
65
 
! nfabor           ! i  ! <-- ! number of boundary faces                       !
66
 
! nfml             ! i  ! <-- ! number of families (group classes)             !
67
 
! nprfml           ! i  ! <-- ! number of properties per family (group class)  !
68
 
! nnod             ! i  ! <-- ! number of vertices                             !
69
 
! lndfac           ! i  ! <-- ! size of nodfac indexed array                   !
70
 
! lndfbr           ! i  ! <-- ! size of nodfbr indexed array                   !
71
 
! ncelbr           ! i  ! <-- ! number of cells with faces on boundary         !
72
45
! nvar             ! i  ! <-- ! total number of variables                      !
73
46
! nscal            ! i  ! <-- ! total number of scalars                        !
74
 
! nphas            ! i  ! <-- ! number of phases                               !
75
47
! ncepdp           ! i  ! <-- ! number of cells with head loss                 !
76
48
! ncesmp           ! i  ! <-- ! number of cells with mass source term          !
77
 
! nideve, nrdeve   ! i  ! <-- ! sizes of idevel and rdevel arrays              !
78
 
! nituse, nrtuse   ! i  ! <-- ! sizes of ituser and rtuser arrays              !
79
49
! iwarnp           ! i  ! <-- ! verbosity                                      !
80
 
! ifacel(2, nfac)  ! ia ! <-- ! interior faces -> cells connectivity           !
81
 
! ifabor(nfabor)   ! ia ! <-- ! boundary faces -> cells connectivity           !
82
 
! ifmfbr(nfabor)   ! ia ! <-- ! boundary face family numbers                   !
83
 
! ifmcel(ncelet)   ! ia ! <-- ! cell family numbers                            !
84
 
! iprfml           ! ia ! <-- ! property numbers per family                    !
85
 
!  (nfml, nprfml)  !    !     !                                                !
86
 
! ipnfac(nfac+1)   ! ia ! <-- ! interior faces -> vertices index (optional)    !
87
 
! nodfac(lndfac)   ! ia ! <-- ! interior faces -> vertices list (optional)     !
88
 
! ipnfbr(nfabor+1) ! ia ! <-- ! boundary faces -> vertices index (optional)    !
89
 
! nodfbr(lndfbr)   ! ia ! <-- ! boundary faces -> vertices list (optional)     !
90
50
! icepdc(ncelet    ! te ! <-- ! numero des ncepdp cellules avec pdc            !
91
51
! icetsm(ncesmp    ! te ! <-- ! numero des cellules a source de masse          !
92
52
! itypsm           ! te ! <-- ! type de source de masse pour les               !
93
53
! (ncesmp,nvar)    !    !     !  variables (cf. ustsma)                        !
94
 
! idevel(nideve)   ! ia ! <-> ! integer work array for temporary development   !
95
 
! ituser(nituse)   ! ia ! <-> ! user-reserved integer work array               !
96
 
! ia(*)            ! ia ! --- ! main integer work array                        !
97
 
! xyzcen           ! ra ! <-- ! cell centers                                   !
98
 
!  (ndim, ncelet)  !    !     !                                                !
99
 
! surfac           ! ra ! <-- ! interior faces surface vectors                 !
100
 
!  (ndim, nfac)    !    !     !                                                !
101
 
! surfbo           ! ra ! <-- ! boundary faces surface vectors                 !
102
 
!  (ndim, nfabor)  !    !     !                                                !
103
 
! cdgfac           ! ra ! <-- ! interior faces centers of gravity              !
104
 
!  (ndim, nfac)    !    !     !                                                !
105
 
! cdgfbo           ! ra ! <-- ! boundary faces centers of gravity              !
106
 
!  (ndim, nfabor)  !    !     !                                                !
107
 
! xyznod           ! ra ! <-- ! vertex coordinates (optional)                  !
108
 
!  (ndim, nnod)    !    !     !                                                !
109
 
! volume(ncelet)   ! ra ! <-- ! cell volumes                                   !
110
54
! dt(ncelet)       ! ra ! <-- ! time step (per cell)                           !
111
55
! rtp, rtpa        ! ra ! <-- ! calculated variables at cell centers           !
112
56
!  (ncelet, *)     !    !     !  (at current and previous time steps)          !
124
68
! wflmas(nfac)     ! tr ! --- ! tab de trav aux faces internes                 !
125
69
! wflmab(nfabor    ! tr ! --- ! tab de trav aux faces de bord                  !
126
70
! viscb(nfabor     ! tr ! --- ! tab de trav aux faces de bord                  !
127
 
! w1..6 (ncelet    ! tr ! --- ! tableaux de travail                            !
128
 
! rdevel(nrdeve)   ! ra ! <-> ! real work array for temporary development      !
129
 
! rtuser(nrtuse)   ! ra ! <-> ! user-reserved real work array                  !
130
 
! ra(*)            ! ra ! --- ! main real work array                           !
131
71
!__________________!____!_____!________________________________________________!
132
72
 
133
73
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
136
76
!            --- tableau de travail
137
77
!===============================================================================
138
78
 
 
79
!===============================================================================
 
80
! Module files
 
81
!===============================================================================
 
82
 
 
83
use paramx
 
84
use numvar
 
85
use cstnum
 
86
use cstphy
 
87
use optcal
 
88
use entsor
 
89
use parall
 
90
use ppppar
 
91
use ppthch
 
92
use ppincl
 
93
use mesh
 
94
 
 
95
!===============================================================================
 
96
 
139
97
implicit none
140
98
 
141
 
!===============================================================================
142
 
! Common blocks
143
 
!===============================================================================
144
 
 
145
 
include "paramx.h"
146
 
include "numvar.h"
147
 
include "cstnum.h"
148
 
include "cstphy.h"
149
 
include "optcal.h"
150
 
include "entsor.h"
151
 
include "parall.h"
152
 
include "ppppar.h"
153
 
include "ppthch.h"
154
 
include "ppincl.h"
155
 
 
156
 
!===============================================================================
157
 
 
158
99
! Arguments
159
100
 
160
 
integer          idbia0 , idbra0
161
 
integer          ndim   , ncelet , ncel   , nfac   , nfabor
162
 
integer          nfml   , nprfml
163
 
integer          nnod   , lndfac , lndfbr , ncelbr
164
 
integer          nvar   , nscal  , nphas
 
101
integer          nvar   , nscal
165
102
integer          ncepdp , ncesmp
166
 
integer          nideve , nrdeve , nituse , nrtuse , iwarnp
 
103
integer          iwarnp
167
104
 
168
 
integer          ifacel(2,nfac) , ifabor(nfabor)
169
 
integer          ifmfbr(nfabor) , ifmcel(ncelet)
170
 
integer          iprfml(nfml,nprfml)
171
 
integer          ipnfac(nfac+1), nodfac(lndfac)
172
 
integer          ipnfbr(nfabor+1), nodfbr(lndfbr)
173
105
integer          icepdc(ncepdp)
174
106
integer          icetsm(ncesmp), itypsm(ncesmp,nvar)
175
 
integer          idevel(nideve), ituser(nituse)
176
 
integer          ia(*)
177
107
 
178
 
double precision xyzcen(ndim,ncelet)
179
 
double precision surfac(ndim,nfac), surfbo(ndim,nfabor)
180
 
double precision cdgfac(ndim,nfac), cdgfbo(ndim,nfabor)
181
 
double precision xyznod(ndim,nnod), volume(ncelet)
182
108
double precision dt(ncelet), rtp(ncelet,*), rtpa(ncelet,*)
183
109
double precision propce(ncelet,*)
184
110
double precision propfa(nfac,*), propfb(nfabor,*)
186
112
double precision ckupdc(ncepdp,6), smacel(ncesmp,nvar)
187
113
double precision wcf(ncelet)
188
114
double precision wflmas(nfac), wflmab(nfabor), viscb(nfabor)
189
 
double precision w1(ncelet), w2(ncelet), w3(ncelet)
190
 
double precision w4(ncelet), w5(ncelet), w6(ncelet)
191
 
double precision rdevel(nrdeve), rtuser(nrtuse), ra(*)
192
115
 
193
116
! Local variables
194
117
 
195
 
integer          idebia, idebra, ifinia, ifinra
196
 
integer          ifac  , iel   , iphas , ivar  , iscal
 
118
integer          ifac  , iel   , ivar  , iscal
197
119
integer          init
198
 
integer          iw7   , iw8   , iw9   , iw10  , iw11  , iw12
199
 
integer          iviscf, icoefu, ixam
 
120
 
 
121
double precision, allocatable, dimension(:) :: viscf
 
122
double precision, allocatable, dimension(:,:) :: coefu
 
123
double precision, allocatable, dimension(:) :: w1, w2
200
124
 
201
125
!===============================================================================
202
126
!===============================================================================
203
127
! 0.  INITIALISATION
204
128
!===============================================================================
205
129
 
206
 
idebia = idbia0
207
 
idebra = idbra0
208
 
 
209
 
iphas   = 1
210
 
 
211
 
iscal  = irho(iphas)
 
130
! Allocate temporary arrays
 
131
allocate(viscf(nfac))
 
132
allocate(coefu(nfabor,3))
 
133
 
 
134
! Allocate work arrays
 
135
allocate(w1(ncelet), w2(ncelet))
 
136
 
 
137
 
 
138
iscal  = irho
212
139
ivar   = isca(iscal)
213
140
 
214
141
!===============================================================================
215
 
! 1. MEMOIRE
216
 
!===============================================================================
217
 
 
218
 
call memcft                                                       &
219
 
!==========
220
 
 ( idebia , idebra ,                                              &
221
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
222
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
223
 
   nvar   , nscal  , nphas  ,                                     &
224
 
   iw7    , iw8    , iw9    , iw10   , iw11   , iw12   ,          &
225
 
   iviscf , icoefu , ixam   ,                                     &
226
 
   ifinia , ifinra )
227
 
 
228
 
idebia = ifinia
229
 
idebra = ifinra
230
 
 
231
 
!===============================================================================
232
 
! 2. CALCUL DE LA CONDITION CFL ASSOCIEE A LA MASSE VOLUMIQUE
 
142
! 1. CALCUL DE LA CONDITION CFL ASSOCIEE A LA MASSE VOLUMIQUE
233
143
!===============================================================================
234
144
 
235
145
! ---> Calcul du "flux de masse" associe a la masse volumique
243
153
 
244
154
call cfmsfl                                                       &
245
155
!==========
246
 
 ( idebia , idebra ,                                              &
247
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
248
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
249
 
   nvar   , nscal  , nphas  , ncepdp , ncesmp ,                   &
250
 
   nideve , nrdeve , nituse , nrtuse , iscal  ,                   &
251
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
252
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
 
156
 ( nvar   , nscal  , ncepdp , ncesmp ,                            &
 
157
   iscal  ,                                                       &
253
158
   icepdc , icetsm , itypsm ,                                     &
254
 
   idevel , ituser , ia     ,                                     &
255
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
256
159
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
257
160
   coefa  , coefb  , ckupdc , smacel ,                            &
258
161
   wflmas , wflmab ,                                              &
259
 
   w1     , w2     , w3     , w4     , w5     , w6     ,          &
260
 
   ra(iw7), ra(iw8), ra(iw9), ra(iw10) , ra(iw11) , ra(iw12) ,    &
261
 
   ra(iviscf) , viscb , ra(icoefu) , ra(ixam) ,                   &
262
 
   rdevel , rtuser ,                                              &
263
 
   ra     )
 
162
   viscf  , viscb  , coefu  )
264
163
 
265
164
! ---> Sommation sur les faces (depend de si l'on explicite ou non
266
165
!                               le terme de convection)
286
185
       max( dble(1-iconv(ivar))*w2(iel)/volume(iel), 0.d0 ) )
287
186
enddo
288
187
 
 
188
! Free memory
 
189
deallocate(viscf)
 
190
deallocate(coefu)
 
191
deallocate(w1, w2)
 
192
 
289
193
!--------
290
194
! FORMATS
291
195
!--------