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

« back to all changes in this revision

Viewing changes to src/cplv/cpiniv.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 cpiniv &
29
24
!================
30
25
 
31
 
 ( idbia0 , idbra0 ,                                              &
32
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
33
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
34
 
   nvar   , nscal  , nphas  ,                                     &
35
 
   nideve , nrdeve , nituse , nrtuse ,                            &
36
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml , maxelt , lstelt , &
37
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
38
 
   idevel , ituser , ia     ,                                     &
39
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
40
 
   dt     , rtp    , propce , propfa , propfb , coefa  , coefb  , &
41
 
   rdevel , rtuser , ra     )
 
26
 ( nvar   , nscal  ,                                              &
 
27
   dt     , rtp    , propce , propfa , propfb , coefa  , coefb  )
42
28
 
43
29
!===============================================================================
44
30
! FONCTION :
66
52
!     PROPCE (prop au centre), PROPFA (aux faces internes),
67
53
!     PROPFB (prop aux faces de bord)
68
54
!     Ainsi,
69
 
!      PROPCE(IEL,IPPROC(IROM  (IPHAS))) designe ROM   (IEL ,IPHAS)
70
 
!      PROPCE(IEL,IPPROC(IVISCL(IPHAS))) designe VISCL (IEL ,IPHAS)
71
 
!      PROPCE(IEL,IPPROC(ICP   (IPHAS))) designe CP    (IEL ,IPHAS)
 
55
!      PROPCE(IEL,IPPROC(IROM  )) designe ROM   (IEL)
 
56
!      PROPCE(IEL,IPPROC(IVISCL)) designe VISCL (IEL)
 
57
!      PROPCE(IEL,IPPROC(ICP   )) designe CP    (IEL)
72
58
!      PROPCE(IEL,IPPROC(IVISLS(ISCAL))) designe VISLS (IEL ,ISCAL)
73
59
 
74
60
!      PROPFA(IFAC,IPPROF(IFLUMA(IVAR ))) designe FLUMAS(IFAC,IVAR)
75
61
 
76
 
!      PROPFB(IFAC,IPPROB(IROM  (IPHAS))) designe ROMB  (IFAC,IPHAS)
 
62
!      PROPFB(IFAC,IPPROB(IROM  )) designe ROMB  (IFAC)
77
63
!      PROPFB(IFAC,IPPROB(IFLUMA(IVAR ))) designe FLUMAB(IFAC,IVAR)
78
64
 
79
65
! LA MODIFICATION DES PROPRIETES PHYSIQUES (ROM, VISCL, VISCLS, CP)
84
70
!__________________.____._____.________________________________________________.
85
71
! name             !type!mode ! role                                           !
86
72
!__________________!____!_____!________________________________________________!
87
 
! idbia0           ! i  ! <-- ! number of first free position in ia            !
88
 
! idbra0           ! i  ! <-- ! number of first free position in ra            !
89
 
! ndim             ! i  ! <-- ! spatial dimension                              !
90
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
91
 
! ncel             ! i  ! <-- ! number of cells                                !
92
 
! nfac             ! i  ! <-- ! number of interior faces                       !
93
 
! nfabor           ! i  ! <-- ! number of boundary faces                       !
94
 
! nfml             ! i  ! <-- ! number of families (group classes)             !
95
 
! nprfml           ! i  ! <-- ! number of properties per family (group class)  !
96
 
! nnod             ! i  ! <-- ! number of vertices                             !
97
 
! lndfac           ! i  ! <-- ! size of nodfac indexed array                   !
98
 
! lndfbr           ! i  ! <-- ! size of nodfbr indexed array                   !
99
 
! ncelbr           ! i  ! <-- ! number of cells with faces on boundary         !
100
73
! nvar             ! i  ! <-- ! total number of variables                      !
101
74
! nscal            ! i  ! <-- ! total number of scalars                        !
102
 
! nphas            ! i  ! <-- ! number of phases                               !
103
 
! nideve, nrdeve   ! i  ! <-- ! sizes of idevel and rdevel arrays              !
104
 
! nituse, nrtuse   ! i  ! <-- ! sizes of ituser and rtuser arrays              !
105
 
! ifacel(2, nfac)  ! ia ! <-- ! interior faces -> cells connectivity           !
106
 
! ifabor(nfabor)   ! ia ! <-- ! boundary faces -> cells connectivity           !
107
 
! ifmfbr(nfabor)   ! ia ! <-- ! boundary face family numbers                   !
108
 
! ifmcel(ncelet)   ! ia ! <-- ! cell family numbers                            !
109
 
! iprfml           ! ia ! <-- ! property numbers per family                    !
110
 
!  (nfml, nprfml)  !    !     !                                                !
111
 
! maxelt           ! i  ! <-- ! max number of cells and faces (int/boundary)   !
112
 
! lstelt(maxelt)   ! ia ! --- ! work array                                     !
113
 
! ipnfac(nfac+1)   ! ia ! <-- ! interior faces -> vertices index (optional)    !
114
 
! nodfac(lndfac)   ! ia ! <-- ! interior faces -> vertices list (optional)     !
115
 
! ipnfbr(nfabor+1) ! ia ! <-- ! boundary faces -> vertices index (optional)    !
116
 
! nodfbr(lndfbr)   ! ia ! <-- ! boundary faces -> vertices list (optional)     !
117
 
! idevel(nideve)   ! ia ! <-> ! integer work array for temporary development   !
118
 
! ituser(nituse)   ! ia ! <-> ! user-reserved integer work array               !
119
 
! ia(*)            ! ia ! --- ! main integer work array                        !
120
 
! xyzcen           ! ra ! <-- ! cell centers                                   !
121
 
!  (ndim, ncelet)  !    !     !                                                !
122
 
! surfac           ! ra ! <-- ! interior faces surface vectors                 !
123
 
!  (ndim, nfac)    !    !     !                                                !
124
 
! surfbo           ! ra ! <-- ! boundary faces surface vectors                 !
125
 
!  (ndim, nfabor)  !    !     !                                                !
126
 
! cdgfac           ! ra ! <-- ! interior faces centers of gravity              !
127
 
!  (ndim, nfac)    !    !     !                                                !
128
 
! cdgfbo           ! ra ! <-- ! boundary faces centers of gravity              !
129
 
!  (ndim, nfabor)  !    !     !                                                !
130
 
! xyznod           ! ra ! <-- ! vertex coordinates (optional)                  !
131
 
!  (ndim, nnod)    !    !     !                                                !
132
 
! volume(ncelet)   ! ra ! <-- ! cell volumes                                   !
133
75
! dt(ncelet)       ! tr ! <-- ! valeur du pas de temps                         !
134
76
! rtp              ! tr ! <-- ! variables de calcul au centre des              !
135
77
! (ncelet,*)       !    !     !    cellules                                    !
138
80
! propfb(nfabor, *)! ra ! <-- ! physical properties at boundary face centers   !
139
81
! coefa coefb      ! tr ! <-- ! conditions aux limites aux                     !
140
82
!  (nfabor,*)      !    !     !    faces de bord                               !
141
 
! rdevel(nrdeve)   ! ra ! <-> ! real work array for temporary development      !
142
 
! rtuser(nrtuse)   ! ra ! <-> ! user-reserved real work array                  !
143
 
! ra(*)            ! ra ! --- ! main real work array                           !
144
83
!__________________!____!_____!________________________________________________!
145
84
 
146
85
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
149
88
!            --- tableau de travail
150
89
!===============================================================================
151
90
 
 
91
!===============================================================================
 
92
! Module files
 
93
!===============================================================================
 
94
 
 
95
use paramx
 
96
use numvar
 
97
use optcal
 
98
use cstphy
 
99
use cstnum
 
100
use entsor
 
101
use ppppar
 
102
use ppthch
 
103
use coincl
 
104
use cpincl
 
105
use ppincl
 
106
use ppcpfu
 
107
use mesh
 
108
 
 
109
!===============================================================================
 
110
 
152
111
implicit none
153
112
 
154
 
!===============================================================================
155
 
! Common blocks
156
 
!===============================================================================
157
 
 
158
 
include "paramx.h"
159
 
include "numvar.h"
160
 
include "optcal.h"
161
 
include "cstphy.h"
162
 
include "cstnum.h"
163
 
include "entsor.h"
164
 
include "ppppar.h"
165
 
include "ppthch.h"
166
 
include "coincl.h"
167
 
include "cpincl.h"
168
 
include "ppincl.h"
169
 
include "ppcpfu.h"
170
 
 
171
 
!===============================================================================
172
 
 
173
 
integer          idbia0 , idbra0
174
 
integer          ndim   , ncelet , ncel   , nfac   , nfabor
175
 
integer          nfml   , nprfml
176
 
integer          nnod   , lndfac , lndfbr , ncelbr
177
 
integer          nvar   , nscal  , nphas
178
 
integer          nideve , nrdeve , nituse , nrtuse
179
 
 
180
 
integer          ifacel(2,nfac) , ifabor(nfabor)
181
 
integer          ifmfbr(nfabor) , ifmcel(ncelet)
182
 
integer          iprfml(nfml,nprfml), maxelt, lstelt(maxelt)
183
 
integer          ipnfac(nfac+1), nodfac(lndfac)
184
 
integer          ipnfbr(nfabor+1), nodfbr(lndfbr)
185
 
integer          idevel(nideve), ituser(nituse), ia(*)
186
 
 
187
 
double precision xyzcen(ndim,ncelet)
188
 
double precision surfac(ndim,nfac), surfbo(ndim,nfabor)
189
 
double precision cdgfac(ndim,nfac), cdgfbo(ndim,nfabor)
190
 
double precision xyznod(ndim,nnod), volume(ncelet)
 
113
integer          nvar   , nscal
 
114
 
 
115
 
191
116
double precision dt(ncelet), rtp(ncelet,*), propce(ncelet,*)
192
117
double precision propfa(nfac,*), propfb(nfabor,*)
193
118
double precision coefa(nfabor,*), coefb(nfabor,*)
194
 
double precision rdevel(nrdeve), rtuser(nrtuse), ra(*)
195
119
 
196
120
! Local variables
197
121
 
198
 
integer          idebia, idebra
199
 
integer          iel, ige, mode, icla, icha, iphas
 
122
integer          iel, ige, mode, icla, icha
200
123
 
201
124
double precision t1init, h1init, coefe(ngazem)
202
125
double precision t2init, h2init
220
143
 
221
144
ipass = ipass + 1
222
145
 
223
 
idebia = idbia0
224
 
idebra = idbra0
225
146
 
226
147
d2s3 = 2.d0/3.d0
227
148
 
234
155
 
235
156
if ( isuite.eq.0 .and. ipass.eq.1 ) then
236
157
 
237
 
  iphas = 1
238
 
 
239
158
! --> Initialisation de k et epsilon
240
159
 
241
160
  xkent = 1.d-10
243
162
 
244
163
! ---- TURBULENCE
245
164
 
246
 
  if (itytur(iphas).eq.2) then
247
 
 
248
 
    do iel = 1, ncel
249
 
      rtp(iel,ik(iphas))  = xkent
250
 
      rtp(iel,iep(iphas)) = xeent
251
 
    enddo
252
 
 
253
 
  elseif (itytur(iphas).eq.3) then
254
 
 
255
 
    do iel = 1, ncel
256
 
      rtp(iel,ir11(iphas)) = d2s3*xkent
257
 
      rtp(iel,ir22(iphas)) = d2s3*xkent
258
 
      rtp(iel,ir33(iphas)) = d2s3*xkent
259
 
      rtp(iel,ir12(iphas)) = 0.d0
260
 
      rtp(iel,ir13(iphas)) = 0.d0
261
 
      rtp(iel,ir23(iphas)) = 0.d0
262
 
      rtp(iel,iep(iphas))  = xeent
263
 
    enddo
264
 
 
265
 
  elseif (iturb(iphas).eq.50) then
266
 
 
267
 
    do iel = 1, ncel
268
 
      rtp(iel,ik(iphas))   = xkent
269
 
      rtp(iel,iep(iphas))  = xeent
270
 
      rtp(iel,iphi(iphas)) = d2s3
271
 
      rtp(iel,ifb(iphas))  = 0.d0
272
 
    enddo
273
 
 
274
 
  elseif (iturb(iphas).eq.60) then
275
 
 
276
 
    do iel = 1, ncel
277
 
      rtp(iel,ik(iphas))   = xkent
278
 
      rtp(iel,iomg(iphas)) = xeent/cmu/xkent
 
165
  if (itytur.eq.2) then
 
166
 
 
167
    do iel = 1, ncel
 
168
      rtp(iel,ik)  = xkent
 
169
      rtp(iel,iep) = xeent
 
170
    enddo
 
171
 
 
172
  elseif (itytur.eq.3) then
 
173
 
 
174
    do iel = 1, ncel
 
175
      rtp(iel,ir11) = d2s3*xkent
 
176
      rtp(iel,ir22) = d2s3*xkent
 
177
      rtp(iel,ir33) = d2s3*xkent
 
178
      rtp(iel,ir12) = 0.d0
 
179
      rtp(iel,ir13) = 0.d0
 
180
      rtp(iel,ir23) = 0.d0
 
181
      rtp(iel,iep)  = xeent
 
182
    enddo
 
183
 
 
184
  elseif (iturb.eq.50) then
 
185
 
 
186
    do iel = 1, ncel
 
187
      rtp(iel,ik)   = xkent
 
188
      rtp(iel,iep)  = xeent
 
189
      rtp(iel,iphi) = d2s3
 
190
      rtp(iel,ifb)  = 0.d0
 
191
    enddo
 
192
 
 
193
  elseif (iturb.eq.60) then
 
194
 
 
195
    do iel = 1, ncel
 
196
      rtp(iel,ik)   = xkent
 
197
      rtp(iel,iomg) = xeent/cmu/xkent
 
198
    enddo
 
199
 
 
200
  elseif (iturb.eq.70) then
 
201
 
 
202
    do iel = 1, ncel
 
203
      rtp(iel,inusa) = cmu*xkent**2/xeent
279
204
    enddo
280
205
 
281
206
  endif
285
210
 
286
211
! ---- Calculs de H1INIT et H2INIT
287
212
 
288
 
  t1init = t0(iphas)
289
 
  t2init = t0(iphas)
 
213
  t1init = t0
 
214
  t2init = t0
290
215
 
291
216
! ------ Variables de transport relatives a la phase solide :
292
217
!        calcul de H
393
318
if (ipass.eq.1) then
394
319
  call uscpiv                                                     &
395
320
  !==========
396
 
 ( idebia , idebra ,                                              &
397
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
398
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
399
 
   nvar   , nscal  , nphas  ,                                     &
400
 
   nideve , nrdeve , nituse , nrtuse ,                            &
401
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml , maxelt , lstelt , &
402
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
403
 
   idevel , ituser , ia     ,                                     &
404
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
405
 
   dt     , rtp    , propce , propfa , propfb , coefa  , coefb  , &
406
 
   rdevel , rtuser , ra     )
 
321
 ( nvar   , nscal  ,                                              &
 
322
   dt     , rtp    , propce , propfa , propfb , coefa  , coefb  )
407
323
endif
408
324
 
409
325
!----