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

« back to all changes in this revision

Viewing changes to src/cfbl/cfxtcl.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 cfxtcl &
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 ,                   &
37
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
 
26
 ( nvar   , nscal  ,                                              &
38
27
   icodcl , itrifb , itypfb , izfppp ,                            &
39
 
   idevel , ituser , ia     ,                                     &
40
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
41
28
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
42
 
   coefa  , coefb  , rcodcl ,                                     &
43
 
   w1     , w2     , w3     , w4     , w5     , w6     , coefu  , &
44
 
   rdevel , rtuser , ra     )
 
29
   coefa  , coefb  , rcodcl )
45
30
 
46
31
!===============================================================================
47
32
! FONCTION :
57
42
!__________________.____._____.________________________________________________.
58
43
! name             !type!mode ! role                                           !
59
44
!__________________!____!_____!________________________________________________!
60
 
! idbia0           ! i  ! <-- ! number of first free position in ia            !
61
 
! idbra0           ! i  ! <-- ! number of first free position in ra            !
62
 
! ndim             ! i  ! <-- ! spatial dimension                              !
63
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
64
 
! ncel             ! i  ! <-- ! number of cells                                !
65
 
! nfac             ! i  ! <-- ! number of interior faces                       !
66
 
! nfabor           ! i  ! <-- ! number of boundary faces                       !
67
 
! nfml             ! i  ! <-- ! number of families (group classes)             !
68
 
! nprfml           ! i  ! <-- ! number of properties per family (group class)  !
69
 
! nnod             ! i  ! <-- ! number of vertices                             !
70
 
! lndfac           ! i  ! <-- ! size of nodfac indexed array                   !
71
 
! lndfbr           ! i  ! <-- ! size of nodfbr indexed array                   !
72
 
! ncelbr           ! i  ! <-- ! number of cells with faces on boundary         !
73
45
! nvar             ! i  ! <-- ! total number of variables                      !
74
46
! nscal            ! i  ! <-- ! total number of scalars                        !
75
 
! nphas            ! i  ! <-- ! number of phases                               !
76
 
! nideve, nrdeve   ! i  ! <-- ! sizes of idevel and rdevel arrays              !
77
 
! nituse, nrtuse   ! i  ! <-- ! sizes of ituser and rtuser arrays              !
78
 
! ifacel(2, nfac)  ! ia ! <-- ! interior faces -> cells connectivity           !
79
 
! ifabor(nfabor)   ! ia ! <-- ! boundary faces -> cells connectivity           !
80
 
! ifmfbr(nfabor)   ! ia ! <-- ! boundary face family numbers                   !
81
 
! ifmcel(ncelet)   ! ia ! <-- ! cell family numbers                            !
82
 
! iprfml           ! ia ! <-- ! property numbers per family                    !
83
 
!  (nfml, nprfml)  !    !     !                                                !
84
 
! ipnfac(nfac+1)   ! ia ! <-- ! interior faces -> vertices index (optional)    !
85
 
! nodfac(lndfac)   ! ia ! <-- ! interior faces -> vertices list (optional)     !
86
 
! ipnfbr(nfabor+1) ! ia ! <-- ! boundary faces -> vertices index (optional)    !
87
 
! nodfbr(lndfbr)   ! ia ! <-- ! boundary faces -> vertices list (optional)     !
88
47
! icodcl           ! te ! --> ! code de condition limites aux faces            !
89
48
!  (nfabor,nvar    !    !     !  de bord                                       !
90
49
!                  !    !     ! = 1   -> dirichlet                             !
94
53
!                  !    !     ! = 6   -> rugosite et u.n=0 (vitesse)           !
95
54
!                  !    !     ! = 9   -> entree/sortie libre (vitesse          !
96
55
! itrifb           ! ia ! <-- ! indirection for boundary faces ordering        !
97
 
!  (nfabor, nphas) !    !     !                                                !
98
56
! itypfb           ! ia ! <-- ! boundary face types                            !
99
 
!  (nfabor, nphas) !    !     !                                                !
100
57
! izfppp           ! te ! <-- ! numero de zone de la face de bord              !
101
58
! (nfabor)         !    !     !  pour le module phys. part.                    !
102
 
! idevel(nideve)   ! ia ! <-> ! integer work array for temporary development   !
103
 
! ituser(nituse)   ! ia ! <-> ! user-reserved integer work array               !
104
 
! ia(*)            ! ia ! --- ! main integer work array                        !
105
 
! xyzcen           ! ra ! <-- ! cell centers                                   !
106
 
!  (ndim, ncelet)  !    !     !                                                !
107
 
! surfac           ! ra ! <-- ! interior faces surface vectors                 !
108
 
!  (ndim, nfac)    !    !     !                                                !
109
 
! surfbo           ! ra ! <-- ! boundary faces surface vectors                 !
110
 
!  (ndim, nfabor)  !    !     !                                                !
111
 
! cdgfac           ! ra ! <-- ! interior faces centers of gravity              !
112
 
!  (ndim, nfac)    !    !     !                                                !
113
 
! cdgfbo           ! ra ! <-- ! boundary faces centers of gravity              !
114
 
!  (ndim, nfabor)  !    !     !                                                !
115
 
! xyznod           ! ra ! <-- ! vertex coordinates (optional)                  !
116
 
!  (ndim, nnod)    !    !     !                                                !
117
 
! volume(ncelet)   ! ra ! <-- ! cell volumes                                   !
118
59
! dt(ncelet)       ! ra ! <-- ! time step (per cell)                           !
119
60
! rtp, rtpa        ! ra ! <-- ! calculated variables at cell centers           !
120
61
!  (ncelet, *)     !    !     !  (at current and previous time steps)          !
135
76
!                  !    !     ! pour la pression             dt*gradp          !
136
77
!                  !    !     ! pour les scalaires                             !
137
78
!                  !    !     !        cp*(viscls+visct/sigmas)*gradt          !
138
 
! w1,2,3,4,5,6     ! ra ! --- ! work arrays                                    !
139
 
!  (ncelet)        !    !     !  (computation of pressure gradient)            !
140
 
! coefu            ! ra ! --- ! work array                                     !
141
 
!  (nfabor, 3)     !    !     !  (computation of pressure gradient)            !
142
 
! rdevel(nrdeve)   ! ra ! <-> ! real work array for temporary development      !
143
 
! rtuser(nrtuse)   ! ra ! <-> ! user-reserved real work array                  !
144
 
! ra(*)            ! ra ! --- ! main real work array                           !
145
79
!__________________!____!_____!________________________________________________!
146
80
 
147
81
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
150
84
!            --- tableau de travail
151
85
!===============================================================================
152
86
 
 
87
!===============================================================================
 
88
! Module files
 
89
!===============================================================================
 
90
 
 
91
! Arguments
 
92
 
 
93
use paramx
 
94
use numvar
 
95
use optcal
 
96
use cstphy
 
97
use cstnum
 
98
use entsor
 
99
use parall
 
100
use ppppar
 
101
use ppthch
 
102
use ppincl
 
103
use cfpoin
 
104
use mesh
 
105
 
 
106
!===============================================================================
 
107
 
153
108
implicit none
154
109
 
155
 
!===============================================================================
156
 
! Common blocks
157
 
!===============================================================================
158
 
 
159
 
! Arguments
160
 
 
161
 
include "paramx.h"
162
 
include "numvar.h"
163
 
include "optcal.h"
164
 
include "cstphy.h"
165
 
include "cstnum.h"
166
 
include "pointe.h"
167
 
include "entsor.h"
168
 
include "parall.h"
169
 
include "ppppar.h"
170
 
include "ppthch.h"
171
 
include "ppincl.h"
172
 
include "cfpoin.h"
173
 
 
174
 
!===============================================================================
175
 
 
176
 
! Arguments
177
 
 
178
 
integer          idbia0 , idbra0
179
 
integer          ndim   , ncelet , ncel   , nfac   , nfabor
180
 
integer          nfml   , nprfml
181
 
integer          nnod   , lndfac , lndfbr , ncelbr
182
 
integer          nvar   , nscal  , nphas
183
 
integer          nideve , nrdeve , nituse , nrtuse
184
 
 
185
 
integer          ifacel(2,nfac) , ifabor(nfabor)
186
 
integer          ifmfbr(nfabor) , ifmcel(ncelet)
187
 
integer          iprfml(nfml,nprfml)
188
 
integer          ipnfac(nfac+1), nodfac(lndfac)
189
 
integer          ipnfbr(nfabor+1), nodfbr(lndfbr)
 
110
! Arguments
 
111
 
 
112
integer          nvar   , nscal
 
113
 
190
114
integer          icodcl(nfabor,nvar)
191
 
integer          itrifb(nfabor,nphas), itypfb(nfabor,nphas)
 
115
integer          itrifb(nfabor), itypfb(nfabor)
192
116
integer          izfppp(nfabor)
193
 
integer          idevel(nideve), ituser(nituse), ia(*)
194
117
 
195
 
double precision xyzcen(ndim,ncelet)
196
 
double precision surfac(ndim,nfac), surfbo(ndim,nfabor)
197
 
double precision cdgfac(ndim,nfac), cdgfbo(ndim,nfabor)
198
 
double precision xyznod(ndim,nnod), volume(ncelet)
199
118
double precision dt(ncelet), rtp(ncelet,*), rtpa(ncelet,*)
200
119
double precision propce(ncelet,*)
201
120
double precision propfa(nfac,*), propfb(nfabor,*)
202
121
double precision coefa(nfabor,*), coefb(nfabor,*)
203
122
double precision rcodcl(nfabor,nvar,3)
204
 
double precision w1(ncelet),w2(ncelet),w3(ncelet)
205
 
double precision w4(ncelet),w5(ncelet),w6(ncelet)
206
 
double precision coefu(nfabor,ndim)
207
 
double precision rdevel(nrdeve), rtuser(nrtuse), ra(*)
208
123
 
209
124
! Local variables
210
125
 
211
 
integer          idebia, idebra
212
 
integer          iphas , ivar  , ifac  , iel
 
126
integer          ivar  , ifac  , iel
213
127
integer          ii    , iii   , imodif, iccfth
214
128
integer          icalep, icalgm
215
129
integer          iflmab
216
 
integer          ipriph, iuiph , iviph , iwiph
217
 
integer          irhiph, ieniph, itkiph
 
130
integer          irh   , ien   , itk
218
131
integer          iclp  , iclr
219
132
integer          iclu  , iclv  , iclw
220
133
integer          nvarcf
225
138
 
226
139
double precision hint  , gammag
227
140
 
 
141
double precision, allocatable, dimension(:) :: w1, w2, w3
 
142
double precision, allocatable, dimension(:) :: w4, w5, w6
 
143
double precision, allocatable, dimension(:) :: w7
 
144
 
228
145
!===============================================================================
229
146
!===============================================================================
230
147
! 1.  INITIALISATIONS
231
148
!===============================================================================
232
149
 
233
 
idebia = idbia0
234
 
idebra = idbra0
235
 
 
236
 
 
237
 
do iphas = 1, nphas
238
 
 
239
 
  ipriph = ipr   (iphas)
240
 
  iuiph  = iu    (iphas)
241
 
  iviph  = iv    (iphas)
242
 
  iwiph  = iw    (iphas)
243
 
  irhiph = isca(irho  (iphas))
244
 
  ieniph = isca(ienerg(iphas))
245
 
  itkiph = isca(itempk(iphas))
246
 
  iclp   = iclrtp(ipriph,icoef)
247
 
  iclr   = iclrtp(irhiph,icoef)
248
 
  iclu   = iclrtp(iuiph ,icoef)
249
 
  iclv   = iclrtp(iviph ,icoef)
250
 
  iclw   = iclrtp(iwiph ,icoef)
251
 
 
252
 
  iflmab = ipprob(ifluma(ieniph))
 
150
! Allocate work arrays
 
151
allocate(w1(ncelet), w2(ncelet), w3(ncelet))
 
152
allocate(w4(ncelet), w5(ncelet), w6(ncelet))
 
153
 
 
154
! Allocate a work array on boundary faces (to be verified...)
 
155
allocate(w7(nfabor))
 
156
 
 
157
 
 
158
 
 
159
irh = isca(irho  )
 
160
ien = isca(ienerg)
 
161
itk = isca(itempk)
 
162
iclp   = iclrtp(ipr,icoef)
 
163
iclr   = iclrtp(irh,icoef)
 
164
iclu   = iclrtp(iu ,icoef)
 
165
iclv   = iclrtp(iv ,icoef)
 
166
iclw   = iclrtp(iw ,icoef)
 
167
 
 
168
iflmab = ipprob(ifluma(ien))
253
169
 
254
170
!     Liste des variables compressible :
255
 
  ivarcf(1) = ipriph
256
 
  ivarcf(2) = iuiph
257
 
  ivarcf(3) = iviph
258
 
  ivarcf(4) = iwiph
259
 
  ivarcf(5) = irhiph
260
 
  ivarcf(6) = ieniph
261
 
  ivarcf(7) = itkiph
262
 
  nvarcf    = 7
 
171
ivarcf(1) = ipr
 
172
ivarcf(2) = iu
 
173
ivarcf(3) = iv
 
174
ivarcf(4) = iw
 
175
ivarcf(5) = irh
 
176
ivarcf(6) = ien
 
177
ivarcf(7) = itk
 
178
nvarcf    = 7
263
179
 
264
180
!     Calcul de epsilon_sup = e - CvT
265
181
!       On en a besoin si on a des parois a temperature imposee.
268
184
!         n�cessaire de gagner de la m�moire, on pourra modifier
269
185
!         uscfth.
270
186
 
271
 
  icalep = 0
272
 
  do ifac = 1, nfabor
273
 
    if(icodcl(ifac,itkiph).eq.5) then
274
 
      icalep = 1
275
 
    endif
276
 
  enddo
277
 
  if(icalep.ne.0) then
278
 
    iccfth = 7
279
 
    imodif = 0
280
 
    call uscfth                                                   &
281
 
    !==========
282
 
 ( idebia , idebra ,                                              &
283
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
284
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
285
 
   nvar   , nscal  , nphas  ,                                     &
286
 
   iccfth , imodif , iphas  ,                                     &
287
 
   nideve , nrdeve , nituse , nrtuse ,                            &
288
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
289
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
290
 
   idevel , ituser , ia     ,                                     &
291
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
292
 
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
293
 
   coefa  , coefb  ,                                              &
294
 
   w5     , coefu(1,1) , w3 , w4     ,                            &
295
 
!        ------   ---------
296
 
   rdevel , rtuser , ra     )
 
187
icalep = 0
 
188
do ifac = 1, nfabor
 
189
  if(icodcl(ifac,itk).eq.5) then
 
190
    icalep = 1
297
191
  endif
 
192
enddo
 
193
if(icalep.ne.0) then
 
194
  iccfth = 7
 
195
  imodif = 0
 
196
  call uscfth                                                   &
 
197
  !==========
 
198
( nvar   , nscal  ,                                              &
 
199
  iccfth , imodif ,                                              &
 
200
  dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
 
201
  coefa  , coefb  ,                                              &
 
202
  w5     , w7     , w3     , w4     )
 
203
endif
298
204
 
299
205
 
300
206
!     Calcul de gamma (constant ou variable ; pour le moment : cst)
301
207
!       On en a besoin pour les entrees sorties avec rusanov
302
208
 
303
 
  icalgm = 0
304
 
  do ifac = 1, nfabor
305
 
    if ( ( itypfb(ifac,iphas).eq.iesicf ) .or.                    &
306
 
         ( itypfb(ifac,iphas).eq.isopcf ) .or.                    &
307
 
         ( itypfb(ifac,iphas).eq.ierucf ) .or.                    &
308
 
         ( itypfb(ifac,iphas).eq.ieqhcf ) ) then
309
 
      icalgm = 1
310
 
    endif
311
 
  enddo
312
 
  if(icalgm.ne.0) then
313
 
    iccfth = 1
314
 
    imodif = 0
315
 
    call uscfth                                                   &
316
 
    !==========
317
 
 ( idebia , idebra ,                                              &
318
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
319
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
320
 
   nvar   , nscal  , nphas  ,                                     &
321
 
   iccfth , imodif , iphas  ,                                     &
322
 
   nideve , nrdeve , nituse , nrtuse ,                            &
323
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
324
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
325
 
   idevel , ituser , ia     ,                                     &
326
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
327
 
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
328
 
   coefa  , coefb  ,                                              &
329
 
   w1     , w2     , w6     , w4     ,                            &
330
 
   rdevel , rtuser , ra     )
 
209
icalgm = 0
 
210
do ifac = 1, nfabor
 
211
  if ( ( itypfb(ifac).eq.iesicf ) .or.                    &
 
212
       ( itypfb(ifac).eq.isopcf ) .or.                    &
 
213
       ( itypfb(ifac).eq.ierucf ) .or.                    &
 
214
       ( itypfb(ifac).eq.ieqhcf ) ) then
 
215
    icalgm = 1
 
216
  endif
 
217
enddo
 
218
if(icalgm.ne.0) then
 
219
  iccfth = 1
 
220
  imodif = 0
 
221
  call uscfth                                                   &
 
222
  !==========
 
223
( nvar   , nscal  ,                                              &
 
224
  iccfth , imodif ,                                              &
 
225
  dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
 
226
  coefa  , coefb  ,                                              &
 
227
  w1     , w2     , w6     , w4     )
331
228
 
332
 
    if(ieos(iphas).eq.1) then
333
 
      gammag = w6(1)
334
 
    else
 
229
  if(ieos.eq.1) then
 
230
    gammag = w6(1)
 
231
  else
335
232
!     Gamma doit etre passe a cfrusb ; s'il est variable
336
233
!       il est dans le tableau W6 et il faut ajouter
337
234
!           GAMMAG = W6(IFABOR(IFAC)) selon IEOS
338
235
!       dans la boucle sur les faces.
339
236
!     En attendant que IEOS different de 1 soit code, on stoppe
340
 
      write(nfecra,7000)
341
 
      call csexit (1)
342
 
    endif
343
 
 
 
237
    write(nfecra,7000)
 
238
    call csexit (1)
344
239
  endif
345
240
 
 
241
endif
 
242
 
346
243
 
347
244
 
348
245
!     Boucle sur les faces
349
246
 
350
 
  do ifac = 1, nfabor
351
 
    iel = ifabor(ifac)
 
247
do ifac = 1, nfabor
 
248
  iel = ifabor(ifac)
352
249
 
353
250
!===============================================================================
354
251
! 2.  REMPLISSAGE DU TABLEAU DES CONDITIONS LIMITES
355
252
!       ON BOUCLE SUR TOUTES LES FACES DE PAROI
356
253
!===============================================================================
357
254
 
358
 
    if ( itypfb(ifac,iphas).eq.iparoi) then
 
255
  if ( itypfb(ifac).eq.iparoi) then
359
256
 
360
257
!     Les RCODCL ont ete initialises a -RINFIN pour permettre de
361
258
!       verifier ceux que l'utilisateur a modifies. On les remet a zero
362
259
!       si l'utilisateur ne les a pas modifies.
363
260
!       En paroi, on traite toutes les variables.
364
 
      do ivar = 1, nvar
365
 
        if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
366
 
          rcodcl(ifac,ivar,1) = 0.d0
367
 
        endif
368
 
      enddo
 
261
    do ivar = 1, nvar
 
262
      if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
 
263
        rcodcl(ifac,ivar,1) = 0.d0
 
264
      endif
 
265
    enddo
369
266
 
370
267
!     Le flux de masse est nul
371
268
 
372
 
      propfb(ifac,iflmab) = 0.d0
 
269
    propfb(ifac,iflmab) = 0.d0
373
270
 
374
271
!     Pression :
375
272
 
376
273
!       Si la gravite est predominante : pression hydrostatique
377
274
!         (approximatif et surtout explicite en rho)
378
275
 
379
 
      if(icfgrp(iphas).eq.1) then
 
276
    if(icfgrp.eq.1) then
380
277
 
381
 
        icodcl(ifac,ipriph) = 3
382
 
        hint = dt(iel)/ra(idistb-1+ifac)
383
 
        rcodcl(ifac,ipriph,3) = -hint                             &
384
 
         * ( gx*(cdgfbo(1,ifac)-xyzcen(1,iel))                    &
 
278
      icodcl(ifac,ipr) = 3
 
279
      hint = dt(iel)/distb(ifac)
 
280
      rcodcl(ifac,ipr,3) = -hint                             &
 
281
           * ( gx*(cdgfbo(1,ifac)-xyzcen(1,iel))                    &
385
282
           + gy*(cdgfbo(2,ifac)-xyzcen(2,iel))                    &
386
283
           + gz*(cdgfbo(3,ifac)-xyzcen(3,iel)) )                  &
387
 
         * rtp(iel,irhiph)
 
284
           * rtp(iel,irh)
388
285
 
389
 
      else
 
286
    else
390
287
 
391
288
!       En g�n�ral : proportionnelle a la valeur interne
392
289
!         (Pbord = COEFB*Pi)
393
290
!       Si on d�tend trop : Dirichlet homogene
394
291
 
395
 
        iccfth = 91
 
292
      iccfth = 91
396
293
 
397
 
        call uscfth                                               &
398
 
        !==========
399
 
 ( idebia , idebra ,                                              &
400
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
401
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
402
 
   nvar   , nscal  , nphas  ,                                     &
403
 
   iccfth , ifac   , iphas  ,                                     &
404
 
   nideve , nrdeve , nituse , nrtuse ,                            &
405
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
406
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
407
 
   idevel , ituser , ia     ,                                     &
408
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
294
      call uscfth                                               &
 
295
      !==========
 
296
 ( nvar   , nscal  ,                                              &
 
297
   iccfth , ifac   ,                                              &
409
298
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
410
299
   coefa  , coefb  ,                                              &
411
 
   w1     , w2     , w3     , w4     ,                            &
412
 
   rdevel , rtuser , ra     )
 
300
   w1     , w2     , w3     , w4     )
413
301
 
414
302
!       En outre, il faut appliquer une pre-correction pour compenser
415
303
!        le traitement fait dans condli... Si on pouvait remplir COEFA
416
304
!        et COEFB directement, on gagnerait en simplicite, mais cela
417
305
!        demanderait un test sur IPPMOD dans condli : � voir)
418
306
 
419
 
        icodcl(ifac,ipriph) = 1
420
 
        if(coefb(ifac,iclp).lt.rinfin*0.5d0.and.                  &
 
307
      icodcl(ifac,ipr) = 1
 
308
      if(coefb(ifac,iclp).lt.rinfin*0.5d0.and.                  &
421
309
           coefb(ifac,iclp).gt.0.d0  ) then
422
 
          hint = dt(iel)/ra(idistb-1+ifac)
423
 
          rcodcl(ifac,ipriph,1) = 0.d0
424
 
          rcodcl(ifac,ipriph,2) =                                 &
425
 
               hint*(1.d0/coefb(ifac,iclp)-1.d0)
426
 
        else
427
 
          rcodcl(ifac,ipriph,1) = 0.d0
428
 
        endif
429
 
 
 
310
        hint = dt(iel)/distb(ifac)
 
311
        rcodcl(ifac,ipr,1) = 0.d0
 
312
        rcodcl(ifac,ipr,2) = hint*(1.d0/coefb(ifac,iclp)-1.d0)
 
313
      else
 
314
        rcodcl(ifac,ipr,1) = 0.d0
430
315
      endif
431
316
 
 
317
    endif
 
318
 
432
319
 
433
320
!       La vitesse et la turbulence sont trait�es de mani�re standard,
434
321
!         dans condli.
445
332
!         aberrantes au voisinage de la couche limite)
446
333
 
447
334
!       Par d�faut : adiabatique
448
 
      if(  icodcl(ifac,itkiph).eq.0.and.                          &
449
 
           icodcl(ifac,ieniph).eq.0) then
450
 
        icodcl(ifac,itkiph) = 3
451
 
        rcodcl(ifac,itkiph,3) = 0.d0
452
 
      endif
 
335
    if(  icodcl(ifac,itk).eq.0.and.                          &
 
336
         icodcl(ifac,ien).eq.0) then
 
337
      icodcl(ifac,itk) = 3
 
338
      rcodcl(ifac,itk,3) = 0.d0
 
339
    endif
453
340
 
454
341
!       Temperature imposee
455
 
      if(icodcl(ifac,itkiph).eq.5) then
 
342
    if(icodcl(ifac,itk).eq.5) then
456
343
 
457
344
!           On impose la valeur de l'energie qui conduit au bon flux.
458
345
!             On notera cependant qu'il s'agit de la condition � la
464
351
!               sachant que l'energie contient l'energie cinetique,
465
352
!               ce qui rend le choix du profil d�licat.
466
353
 
467
 
        icodcl(ifac,ieniph) = 5
468
 
        if(icv(iphas).eq.0) then
469
 
          rcodcl(ifac,ieniph,1) =                                 &
470
 
               cv0(iphas)*rcodcl(ifac,itkiph,1)
471
 
        else
472
 
          rcodcl(ifac,ieniph,1) = propce(iel,ipproc(icv(iphas)))  &
473
 
               *rcodcl(ifac,itkiph,1)
474
 
        endif
475
 
        rcodcl(ifac,ieniph,1) = rcodcl(ifac,ieniph,1)             &
476
 
           + 0.5d0*(rtp(iel,iuiph)**2+                            &
477
 
                    rtp(iel,iviph)**2+rtp(iel,iwiph)**2)          &
 
354
      icodcl(ifac,ien) = 5
 
355
      if(icv.eq.0) then
 
356
        rcodcl(ifac,ien,1) = cv0*rcodcl(ifac,itk,1)
 
357
      else
 
358
        rcodcl(ifac,ien,1) = propce(iel,ipproc(icv))  &
 
359
             *rcodcl(ifac,itk,1)
 
360
      endif
 
361
      rcodcl(ifac,ien,1) = rcodcl(ifac,ien,1)             &
 
362
           + 0.5d0*(rtp(iel,iu)**2+rtp(iel,iv)**2+rtp(iel,iw)**2)          &
478
363
           + w5(iel)
479
364
!                   ^epsilon sup (cf USCFTH)
480
365
 
481
366
!           Les flux en grad epsilon sup et �nergie cin�tique doivent
482
367
!             �tre nuls puisque tout est pris par le terme de
483
368
!             diffusion d'energie.
484
 
        ia(iifbet+ifac-1+(iphas-1)*nfabor) = 1
 
369
      ifbet(ifac) = 1
485
370
 
486
371
!           Flux nul pour la reconstruction �ventuelle de temp�rature
487
 
        icodcl(ifac,itkiph) = 3
488
 
        rcodcl(ifac,itkiph,3) = 0.d0
 
372
      icodcl(ifac,itk) = 3
 
373
      rcodcl(ifac,itk,3) = 0.d0
489
374
 
490
375
!       Flux impose
491
 
      elseif(icodcl(ifac,itkiph).eq.3) then
 
376
    elseif(icodcl(ifac,itk).eq.3) then
492
377
 
493
378
!           On impose le flux sur l'energie
494
 
        icodcl(ifac,ieniph) = 3
495
 
        rcodcl(ifac,ieniph,3) = rcodcl(ifac,itkiph,3)
 
379
      icodcl(ifac,ien) = 3
 
380
      rcodcl(ifac,ien,3) = rcodcl(ifac,itk,3)
496
381
 
497
382
!           Les flux en grad epsilon sup et �nergie cin�tique doivent
498
383
!             �tre nuls puisque tout est pris par le terme de
499
384
!             diffusion d'energie.
500
 
        ia(iifbet+ifac-1+(iphas-1)*nfabor) = 1
 
385
      ifbet(ifac) = 1
501
386
 
502
387
!           Flux nul pour la reconstruction �ventuelle de temp�rature
503
 
        icodcl(ifac,itkiph) = 3
504
 
        rcodcl(ifac,itkiph,3) = 0.d0
 
388
      icodcl(ifac,itk) = 3
 
389
      rcodcl(ifac,itk,3) = 0.d0
505
390
 
506
 
      endif
 
391
    endif
507
392
 
508
393
 
509
394
!     Scalaires : flux nul (par defaut dans typecl pour iparoi)
514
399
!       ON BOUCLE SUR TOUTES LES FACES DE SYMETRIE
515
400
!===============================================================================
516
401
 
517
 
    elseif ( itypfb(ifac,iphas).eq.isymet ) then
 
402
  elseif ( itypfb(ifac).eq.isymet ) then
518
403
 
519
404
!     Les RCODCL ont ete initialises a -RINFIN pour permettre de
520
405
!       verifier ceux que l'utilisateur a modifies. On les remet a zero
521
406
!       si l'utilisateur ne les a pas modifies.
522
407
!       En symetrie, on traite toutes les variables.
523
 
      do ivar = 1, nvar
524
 
        if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
525
 
          rcodcl(ifac,ivar,1) = 0.d0
526
 
        endif
527
 
      enddo
 
408
    do ivar = 1, nvar
 
409
      if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
 
410
        rcodcl(ifac,ivar,1) = 0.d0
 
411
      endif
 
412
    enddo
528
413
 
529
414
!     Le flux de masse est nul
530
415
 
531
 
      propfb(ifac,iflmab) = 0.d0
 
416
    propfb(ifac,iflmab) = 0.d0
532
417
 
533
418
!     Condition de Pression
534
419
 
535
 
      iccfth = 90
 
420
    iccfth = 90
536
421
 
537
 
      call uscfth                                                 &
538
 
      !==========
539
 
 ( idebia , idebra ,                                              &
540
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
541
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
542
 
   nvar   , nscal  , nphas  ,                                     &
543
 
   iccfth , ifac   , iphas  ,                                     &
544
 
   nideve , nrdeve , nituse , nrtuse ,                            &
545
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
546
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
547
 
   idevel , ituser , ia     ,                                     &
548
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
422
    call uscfth                                                 &
 
423
    !==========
 
424
 ( nvar   , nscal  ,                                              &
 
425
   iccfth , ifac   ,                                              &
549
426
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
550
427
   coefa  , coefb  ,                                              &
551
 
   w1     , w2     , w3     , w4     ,                            &
552
 
   rdevel , rtuser , ra     )
 
428
   w1     , w2     , w3     , w4     )
553
429
 
554
430
 
555
431
!     Pression :
562
438
!        et COEFB directement, on gagnerait en simplicite, mais cela
563
439
!        demanderait un test sur IPPMOD dans condli : � voir)
564
440
 
565
 
      icodcl(ifac,ipriph) = 3
566
 
      rcodcl(ifac,ipriph,1) = 0.d0
567
 
      rcodcl(ifac,ipriph,2) = rinfin
568
 
      rcodcl(ifac,ipriph,3) = 0.d0
 
441
    icodcl(ifac,ipr) = 3
 
442
    rcodcl(ifac,ipr,1) = 0.d0
 
443
    rcodcl(ifac,ipr,2) = rinfin
 
444
    rcodcl(ifac,ipr,3) = 0.d0
569
445
 
570
446
!       Toutes les autres variables prennent un flux nul (sauf la vitesse
571
447
!         normale, qui est nulle) : par defaut dans typecl pour isymet.
581
457
!     4.1 Entree/sortie impos�e (par exemple : entree supersonique)
582
458
!===============================================================================
583
459
 
584
 
    elseif ( itypfb(ifac,iphas).eq.iesicf ) then
 
460
  elseif ( itypfb(ifac).eq.iesicf ) then
585
461
 
586
462
!     On a
587
463
!       - la vitesse,
592
468
!     On recherche la variable a initialiser
593
469
!       (si on a donne une valeur nulle, c'est pas adapte : on supposera
594
470
!        qu'on n'a pas initialise et on sort en erreur)
595
 
      iccfth = 10000
596
 
      if(rcodcl(ifac,ipriph,1).gt.0.d0) iccfth = 2*iccfth
597
 
      if(rcodcl(ifac,irhiph,1).gt.0.d0) iccfth = 3*iccfth
598
 
      if(rcodcl(ifac,itkiph,1).gt.0.d0) iccfth = 5*iccfth
599
 
      if(rcodcl(ifac,ieniph,1).gt.0.d0) iccfth = 7*iccfth
600
 
      if((iccfth.le.70000.and.iccfth.ne.60000).or.                &
 
471
    iccfth = 10000
 
472
    if(rcodcl(ifac,ipr,1).gt.0.d0) iccfth = 2*iccfth
 
473
    if(rcodcl(ifac,irh,1).gt.0.d0) iccfth = 3*iccfth
 
474
    if(rcodcl(ifac,itk,1).gt.0.d0) iccfth = 5*iccfth
 
475
    if(rcodcl(ifac,ien,1).gt.0.d0) iccfth = 7*iccfth
 
476
    if((iccfth.le.70000.and.iccfth.ne.60000).or.                &
601
477
         (iccfth.eq.350000)) then
602
 
        write(nfecra,1000)iccfth
603
 
        call csexit (1)
604
 
      endif
605
 
      iccfth = iccfth + 900
 
478
      write(nfecra,1000)iccfth
 
479
      call csexit (1)
 
480
    endif
 
481
    iccfth = iccfth + 900
606
482
 
607
483
!     Les RCODCL ont ete initialises a -RINFIN pour permettre de
608
484
!       verifier ceux que l'utilisateur a modifies. On les remet a zero
609
485
!       si l'utilisateur ne les a pas modifies.
610
486
!       On traite d'abord les variables autres que la turbulence et les
611
487
!       scalaires passifs : celles-ci sont traitees plus bas.
612
 
      do iii = 1, nvarcf
613
 
        ivar = ivarcf(iii)
614
 
        if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
615
 
          rcodcl(ifac,ivar,1) = 0.d0
616
 
        endif
617
 
      enddo
 
488
    do iii = 1, nvarcf
 
489
      ivar = ivarcf(iii)
 
490
      if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
 
491
        rcodcl(ifac,ivar,1) = 0.d0
 
492
      endif
 
493
    enddo
618
494
 
619
495
!     On calcule les variables manquantes parmi P,rho,T,E
620
496
!     COEFA sert de tableau de transfert dans USCFTH
621
497
 
622
 
      do ivar = 1, nvar
623
 
        coefa(ifac,iclrtp(ivar,icoef)) = rcodcl(ifac,ivar,1)
624
 
      enddo
 
498
    do ivar = 1, nvar
 
499
      coefa(ifac,iclrtp(ivar,icoef)) = rcodcl(ifac,ivar,1)
 
500
    enddo
625
501
 
626
 
      call uscfth                                                 &
627
 
      !==========
628
 
 ( idebia , idebra ,                                              &
629
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
630
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
631
 
   nvar   , nscal  , nphas  ,                                     &
632
 
   iccfth , ifac   , iphas  ,                                     &
633
 
   nideve , nrdeve , nituse , nrtuse ,                            &
634
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
635
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
636
 
   idevel , ituser , ia     ,                                     &
637
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
502
    call uscfth                                                 &
 
503
    !==========
 
504
 ( nvar   , nscal  ,                                              &
 
505
   iccfth , ifac   ,                                              &
638
506
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
639
507
   coefa  , coefb  ,                                              &
640
 
   w1     , w2     , w3     , w4     ,                            &
641
 
   rdevel , rtuser , ra     )
 
508
   w1     , w2     , w3     , w4     )
642
509
 
643
510
 
644
511
!     Rusanov, flux de masse et type de conditions aux limites :
649
516
!     4.2 Sortie supersonique
650
517
!===============================================================================
651
518
 
652
 
    elseif ( itypfb(ifac,iphas).eq.isspcf ) then
 
519
  elseif ( itypfb(ifac).eq.isspcf ) then
653
520
 
654
521
!     On impose un Dirichlet �gal � la valeur interne pour rho u E
655
522
!       (on impose des Dirichlet d�duit pour les autres variables).
666
533
!       si l'utilisateur ne les a pas modifies.
667
534
!       On traite d'abord les variables autres que la turbulence et les
668
535
!       scalaires passifs : celles-ci sont traitees plus bas.
669
 
      do iii = 1, nvarcf
670
 
        ivar = ivarcf(iii)
671
 
        if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
672
 
          rcodcl(ifac,ivar,1) = 0.d0
673
 
        endif
674
 
      enddo
 
536
    do iii = 1, nvarcf
 
537
      ivar = ivarcf(iii)
 
538
      if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
 
539
        rcodcl(ifac,ivar,1) = 0.d0
 
540
      endif
 
541
    enddo
675
542
 
676
543
!     Valeurs de rho u E
677
 
      rcodcl(ifac,irhiph,1) = rtp(iel,irhiph)
678
 
      rcodcl(ifac,iuiph ,1) = rtp(iel,iuiph)
679
 
      rcodcl(ifac,iviph ,1) = rtp(iel,iviph)
680
 
      rcodcl(ifac,iwiph ,1) = rtp(iel,iwiph)
681
 
      rcodcl(ifac,ieniph,1) = rtp(iel,ieniph)
 
544
    rcodcl(ifac,irh,1) = rtp(iel,irh)
 
545
    rcodcl(ifac,iu ,1) = rtp(iel,iu)
 
546
    rcodcl(ifac,iv ,1) = rtp(iel,iv)
 
547
    rcodcl(ifac,iw ,1) = rtp(iel,iw)
 
548
    rcodcl(ifac,ien,1) = rtp(iel,ien)
682
549
 
683
550
!     Valeurs de P et s d�duites
684
 
      iccfth = 924
685
 
 
686
 
      do ivar = 1, nvar
687
 
        coefa(ifac,iclrtp(ivar,icoef)) = rcodcl(ifac,ivar,1)
688
 
      enddo
689
 
 
690
 
      call uscfth                                                 &
691
 
      !==========
692
 
 ( idebia , idebra ,                                              &
693
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
694
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
695
 
   nvar   , nscal  , nphas  ,                                     &
696
 
   iccfth , ifac   , iphas  ,                                     &
697
 
   nideve , nrdeve , nituse , nrtuse ,                            &
698
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
699
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
700
 
   idevel , ituser , ia     ,                                     &
701
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
551
    iccfth = 924
 
552
 
 
553
    do ivar = 1, nvar
 
554
      coefa(ifac,iclrtp(ivar,icoef)) = rcodcl(ifac,ivar,1)
 
555
    enddo
 
556
 
 
557
    call uscfth                                                 &
 
558
    !==========
 
559
 ( nvar   , nscal  ,                                              &
 
560
   iccfth , ifac   ,                                              &
702
561
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
703
562
   coefa  , coefb  ,                                              &
704
 
   w1     , w2     , w3     , w4     ,                            &
705
 
   rdevel , rtuser , ra     )
 
563
   w1     , w2     , w3     , w4     )
706
564
 
707
565
!               flux de masse et type de conditions aux limites :
708
566
!       voir plus bas
712
570
!     4.3 Sortie a pression imposee
713
571
!===============================================================================
714
572
 
715
 
    elseif ( itypfb(ifac,iphas).eq.isopcf ) then
 
573
  elseif ( itypfb(ifac).eq.isopcf ) then
716
574
 
717
575
!       Sortie subsonique a priori (si c'est supersonique dans le
718
576
!         domaine, ce n'est pas pour autant que c'est supersonique
726
584
!     Si P n'est pas donn�, erreur ; on sort aussi en erreur si P
727
585
!       n�gatif, m�me si c'est possible, dans la plupart des cas ce
728
586
!       sera une erreur
729
 
      if(rcodcl(ifac,ipriph,1).lt.-rinfin*0.5d0) then
730
 
        write(nfecra,1100)
731
 
        call csexit (1)
732
 
      endif
 
587
    if(rcodcl(ifac,ipr,1).lt.-rinfin*0.5d0) then
 
588
      write(nfecra,1100)
 
589
      call csexit (1)
 
590
    endif
733
591
 
734
592
!     Les RCODCL ont ete initialises a -RINFIN pour permettre de
735
593
!       verifier ceux que l'utilisateur a modifies. On les remet a zero
736
594
!       si l'utilisateur ne les a pas modifies.
737
595
!       On traite d'abord les variables autres que la turbulence et les
738
596
!       scalaires passifs : celles-ci sont traitees plus bas.
739
 
      do iii = 1, nvarcf
740
 
        ivar = ivarcf(iii)
741
 
        if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
742
 
          rcodcl(ifac,ivar,1) = 0.d0
743
 
        endif
744
 
      enddo
 
597
    do iii = 1, nvarcf
 
598
      ivar = ivarcf(iii)
 
599
      if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
 
600
        rcodcl(ifac,ivar,1) = 0.d0
 
601
      endif
 
602
    enddo
745
603
 
746
604
!     Valeurs de rho, u, E, s
747
 
      iccfth = 93
748
 
 
749
 
      do ivar = 1, nvar
750
 
        coefa(ifac,iclrtp(ivar,icoef)) = rcodcl(ifac,ivar,1)
751
 
      enddo
752
 
 
753
 
      call uscfth                                                 &
754
 
      !==========
755
 
 ( idebia , idebra ,                                              &
756
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
757
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
758
 
   nvar   , nscal  , nphas  ,                                     &
759
 
   iccfth , ifac   , iphas  ,                                     &
760
 
   nideve , nrdeve , nituse , nrtuse ,                            &
761
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
762
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
763
 
   idevel , ituser , ia     ,                                     &
764
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
605
    iccfth = 93
 
606
 
 
607
    do ivar = 1, nvar
 
608
      coefa(ifac,iclrtp(ivar,icoef)) = rcodcl(ifac,ivar,1)
 
609
    enddo
 
610
 
 
611
    call uscfth                                                 &
 
612
    !==========
 
613
 ( nvar   , nscal  ,                                              &
 
614
   iccfth , ifac   ,                                              &
765
615
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
766
616
   coefa  , coefb  ,                                              &
767
 
   w1     , w2     , w3     , w4     ,                            &
768
 
   rdevel , rtuser , ra     )
 
617
   w1     , w2     , w3     , w4     )
769
618
 
770
619
!     Rusanov, flux de masse et type de conditions aux limites :
771
620
!       voir plus bas
775
624
!     4.4 Entree � rho et U imposes
776
625
!===============================================================================
777
626
 
778
 
    elseif ( itypfb(ifac,iphas).eq.ierucf ) then
 
627
  elseif ( itypfb(ifac).eq.ierucf ) then
779
628
 
780
629
!       Entree subsonique a priori (si c'est supersonique dans le
781
630
!         domaine, ce n'est pas pour autant que c'est supersonique
786
635
!       selon la thermo et on passe dans Rusanov ensuite pour lisser.
787
636
 
788
637
!     Si rho et u ne sont pas donn�s, erreur
789
 
      if(rcodcl(ifac,irhiph,1).lt.-rinfin*0.5d0.or.               &
790
 
         rcodcl(ifac,iuiph ,1).lt.-rinfin*0.5d0.or.               &
791
 
         rcodcl(ifac,iviph ,1).lt.-rinfin*0.5d0.or.               &
792
 
         rcodcl(ifac,iwiph ,1).lt.-rinfin*0.5d0) then
793
 
        write(nfecra,1200)
794
 
        call csexit (1)
795
 
      endif
 
638
    if(rcodcl(ifac,irh,1).lt.-rinfin*0.5d0.or.               &
 
639
         rcodcl(ifac,iu ,1).lt.-rinfin*0.5d0.or.               &
 
640
         rcodcl(ifac,iv ,1).lt.-rinfin*0.5d0.or.               &
 
641
         rcodcl(ifac,iw ,1).lt.-rinfin*0.5d0) then
 
642
      write(nfecra,1200)
 
643
      call csexit (1)
 
644
    endif
796
645
 
797
646
!     Les RCODCL ont ete initialises a -RINFIN pour permettre de
798
647
!       verifier ceux que l'utilisateur a modifies. On les remet a zero
799
648
!       si l'utilisateur ne les a pas modifies.
800
649
!       On traite d'abord les variables autres que la turbulence et les
801
650
!       scalaires passifs : celles-ci sont traitees plus bas.
802
 
      do iii = 1, nvarcf
803
 
        ivar = ivarcf(iii)
804
 
        if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
805
 
          rcodcl(ifac,ivar,1) = 0.d0
806
 
        endif
807
 
      enddo
 
651
    do iii = 1, nvarcf
 
652
      ivar = ivarcf(iii)
 
653
      if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
 
654
        rcodcl(ifac,ivar,1) = 0.d0
 
655
      endif
 
656
    enddo
808
657
 
809
658
!     Valeurs de P, E, s
810
 
      iccfth = 92
811
 
 
812
 
      do ivar = 1, nvar
813
 
        coefa(ifac,iclrtp(ivar,icoef)) = rcodcl(ifac,ivar,1)
814
 
      enddo
815
 
 
816
 
      call uscfth                                                 &
817
 
      !==========
818
 
 ( idebia , idebra ,                                              &
819
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
820
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
821
 
   nvar   , nscal  , nphas  ,                                     &
822
 
   iccfth , ifac   , iphas  ,                                     &
823
 
   nideve , nrdeve , nituse , nrtuse ,                            &
824
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
825
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
826
 
   idevel , ituser , ia     ,                                     &
827
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
 
659
    iccfth = 92
 
660
 
 
661
    do ivar = 1, nvar
 
662
      coefa(ifac,iclrtp(ivar,icoef)) = rcodcl(ifac,ivar,1)
 
663
    enddo
 
664
 
 
665
    call uscfth                                                 &
 
666
    !==========
 
667
 ( nvar   , nscal  ,                                              &
 
668
   iccfth , ifac   ,                                              &
828
669
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
829
670
   coefa  , coefb  ,                                              &
830
 
   w1     , w2     , w3     , w4     ,                            &
831
 
   rdevel , rtuser , ra     )
 
671
   w1     , w2     , w3     , w4     )
832
672
 
833
673
!     Rusanov, flux de masse et type de conditions aux limites :
834
674
!       voir plus bas
838
678
!     4.5 Entree � rho*U et rho*U*H imposes
839
679
!===============================================================================
840
680
 
841
 
    elseif ( itypfb(ifac,iphas).eq.ieqhcf ) then
 
681
  elseif ( itypfb(ifac).eq.ieqhcf ) then
842
682
 
843
683
!       Entree subsonique a priori (si c'est supersonique dans le
844
684
!         domaine, ce n'est pas pour autant que c'est supersonique
850
690
!       ensuite pour lisser.
851
691
 
852
692
!     Si rho et u ne sont pas donn�s, erreur
853
 
      if(rcodcl(ifac,irun (iphas),1).lt.-rinfin*0.5d0.or.         &
854
 
         rcodcl(ifac,irunh(iphas),1).lt.-rinfin*0.5d0) then
855
 
        write(nfecra,1300)
856
 
        call csexit (1)
857
 
      endif
 
693
    if(rcodcl(ifac,irun ,1).lt.-rinfin*0.5d0.or.         &
 
694
         rcodcl(ifac,irunh,1).lt.-rinfin*0.5d0) then
 
695
      write(nfecra,1300)
 
696
      call csexit (1)
 
697
    endif
858
698
 
859
699
!     Les RCODCL ont ete initialises a -RINFIN pour permettre de
860
700
!       verifier ceux que l'utilisateur a modifies. On les remet a zero
861
701
!       si l'utilisateur ne les a pas modifies.
862
702
!       On traite d'abord les variables autres que la turbulence et les
863
703
!       scalaires passifs : celles-ci sont traitees plus bas.
864
 
      do iii = 1, nvarcf
865
 
        ivar = ivarcf(iii)
866
 
        if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
 
704
    do iii = 1, nvarcf
 
705
      ivar = ivarcf(iii)
 
706
      if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
867
707
          rcodcl(ifac,ivar,1) = 0.d0
868
 
        endif
869
 
      enddo
 
708
      endif
 
709
    enddo
870
710
 
871
711
!     A coder
872
712
 
873
 
!     Noter que IRUN(IPHAS)  = ISCA(IRHO (IPHAS))
874
 
!            et IRUNH(IPHAS) = ISCA(IENER(IPHAS))
 
713
!     Noter que IRUN  = ISCA(IRHO )
 
714
!            et IRUNH = ISCA(IENER)
875
715
!     (aliases pour simplifier uscfcl)
876
716
 
877
 
      write(nfecra,1301)
878
 
      call csexit (1)
 
717
    write(nfecra,1301)
 
718
    call csexit (1)
879
719
 
880
720
!===============================================================================
881
721
! 5. CONDITION NON PREVUE
882
722
!===============================================================================
883
723
!     Stop
884
 
    else
 
724
  else
885
725
 
886
 
      write(nfecra,1400)
887
 
      call csexit (1)
 
726
    write(nfecra,1400)
 
727
    call csexit (1)
888
728
 
889
729
! --- Fin de test sur les types de faces
890
 
    endif
 
730
  endif
891
731
 
892
732
 
893
733
!===============================================================================
897
737
!     TYPE DE C    .L. (DIRICHLET NEUMANN)
898
738
!===============================================================================
899
739
 
900
 
    if ( ( itypfb(ifac,iphas).eq.iesicf ) .or.                    &
901
 
         ( itypfb(ifac,iphas).eq.isspcf ) .or.                    &
902
 
         ( itypfb(ifac,iphas).eq.isopcf ) .or.                    &
903
 
         ( itypfb(ifac,iphas).eq.ierucf ) .or.                    &
904
 
         ( itypfb(ifac,iphas).eq.ieqhcf ) ) then
 
740
  if ( ( itypfb(ifac).eq.iesicf ) .or.                    &
 
741
       ( itypfb(ifac).eq.isspcf ) .or.                    &
 
742
       ( itypfb(ifac).eq.isopcf ) .or.                    &
 
743
       ( itypfb(ifac).eq.ierucf ) .or.                    &
 
744
       ( itypfb(ifac).eq.ieqhcf ) ) then
905
745
 
906
746
!===============================================================================
907
747
!     6.1 Flux de bord Rusanov ou simplement flux de masse
909
749
!===============================================================================
910
750
 
911
751
!     Sortie supersonique :
912
 
      if ( itypfb(ifac,iphas).eq.isspcf ) then
 
752
    if ( itypfb(ifac).eq.isspcf ) then
913
753
 
914
754
!     Seul le flux de masse est calcule (on n'appelle pas Rusanov)
915
755
!       (toutes les variables sont connues)
916
756
 
917
 
        propfb(ifac,iflmab) = coefa(ifac,iclr)*                   &
918
 
             ( coefa(ifac,iclu)*surfbo(1,ifac)                    &
919
 
             + coefa(ifac,iclv)*surfbo(2,ifac)                    &
920
 
             + coefa(ifac,iclw)*surfbo(3,ifac) )
 
757
      propfb(ifac,iflmab) = coefa(ifac,iclr)*                   &
 
758
           ( coefa(ifac,iclu)*surfbo(1,ifac)                    &
 
759
           + coefa(ifac,iclv)*surfbo(2,ifac)                    &
 
760
           + coefa(ifac,iclw)*surfbo(3,ifac) )
921
761
 
922
762
!     Entree subsonique
923
763
 
924
 
      else if ( itypfb(ifac,iphas).eq.ierucf ) then
 
764
    else if ( itypfb(ifac).eq.ierucf ) then
925
765
 
926
766
!     Seul le flux de masse est calcule (on n'appelle pas Rusanov)
927
767
 
928
 
        propfb(ifac,iflmab) = coefa(ifac,iclr)*                   &
929
 
             ( coefa(ifac,iclu)*surfbo(1,ifac)                    &
930
 
             + coefa(ifac,iclv)*surfbo(2,ifac)                    &
931
 
             + coefa(ifac,iclw)*surfbo(3,ifac) )
 
768
      propfb(ifac,iflmab) = coefa(ifac,iclr)*                   &
 
769
           ( coefa(ifac,iclu)*surfbo(1,ifac)                    &
 
770
           + coefa(ifac,iclv)*surfbo(2,ifac)                    &
 
771
           + coefa(ifac,iclw)*surfbo(3,ifac) )
932
772
 
933
773
 
934
774
 
935
775
!     Autres entrees/sorties :
936
 
      else
 
776
    else
937
777
 
938
778
!     On calcule des flux par Rusanov (PROPFB)
939
779
!       (en particulier, le flux de masse est complete)
940
780
 
941
 
        call cfrusb                                               &
942
 
        !==========
943
 
 ( idebia , idebra ,                                              &
944
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
945
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
946
 
   nvar   , nscal  , nphas  ,                                     &
947
 
   ifac   , iphas  ,                                              &
948
 
   nideve , nrdeve , nituse , nrtuse ,                            &
949
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
950
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
951
 
   idevel , ituser , ia     ,                                     &
 
781
      call cfrusb                                               &
 
782
      !==========
 
783
 ( nvar   , nscal  ,                                              &
 
784
   ifac   ,                                                       &
952
785
   gammag ,                                                       &
953
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
954
786
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
955
787
   coefa  , coefb  ,                                              &
956
 
   w1     , w2     , w3     , w4     ,                            &
957
 
   rdevel , rtuser , ra     )
 
788
   w1     , w2     , w3     , w4     )
958
789
 
959
 
      endif
 
790
    endif
960
791
 
961
792
!===============================================================================
962
793
!     6.2 Recuperation de COEFA
963
794
!===============================================================================
964
795
 
965
796
!     On r�tablit COEFA dans RCODCL
966
 
      do ivar = 1, nvar
967
 
        rcodcl(ifac,ivar,1) = coefa(ifac,iclrtp(ivar,icoef))
968
 
      enddo
 
797
    do ivar = 1, nvar
 
798
      rcodcl(ifac,ivar,1) = coefa(ifac,iclrtp(ivar,icoef))
 
799
    enddo
969
800
 
970
801
!===============================================================================
971
802
!     6.3 Types de C.L.
992
823
!-------------------------------------------------------------------------------
993
824
 
994
825
!       Entree sortie imposee : Neumann
995
 
      if ( itypfb(ifac,iphas).eq.iesicf ) then
996
 
        icodcl(ifac,ipriph)   = 3
 
826
    if ( itypfb(ifac).eq.iesicf ) then
 
827
      icodcl(ifac,ipr)   = 3
997
828
!       Entree subsonique
998
 
      else if ( itypfb(ifac,iphas).eq.ierucf ) then
999
 
        icodcl(ifac,ipriph)   = 3
1000
 
        rcodcl(ifac,ipriph,3) = 0.d0
 
829
    else if ( itypfb(ifac).eq.ierucf ) then
 
830
      icodcl(ifac,ipr)   = 3
 
831
      rcodcl(ifac,ipr,3) = 0.d0
1001
832
!       Autres entrees/sorties : Dirichlet
1002
 
      else
1003
 
        icodcl(ifac,ipriph)   = 1
1004
 
      endif
 
833
    else
 
834
      icodcl(ifac,ipr)   = 1
 
835
    endif
1005
836
 
1006
837
!-------------------------------------------------------------------------------
1007
838
!     rho U E T : Dirichlet
1008
839
!-------------------------------------------------------------------------------
1009
840
 
1010
841
!     Masse volumique
1011
 
      icodcl(ifac,irhiph)   = 1
 
842
    icodcl(ifac,irh)   = 1
1012
843
!     Vitesse
1013
 
      icodcl(ifac,iuiph)    = 1
1014
 
      icodcl(ifac,iviph)    = 1
1015
 
      icodcl(ifac,iwiph)    = 1
 
844
    icodcl(ifac,iu)    = 1
 
845
    icodcl(ifac,iv)    = 1
 
846
    icodcl(ifac,iw)    = 1
1016
847
!     Energie totale
1017
 
      icodcl(ifac,ieniph)   = 1
 
848
    icodcl(ifac,ien)   = 1
1018
849
!     Temperature
1019
 
      icodcl(ifac,itkiph)   = 1
 
850
    icodcl(ifac,itk)   = 1
1020
851
 
1021
852
!-------------------------------------------------------------------------------
1022
853
!     turbulence et scalaires passifs : Dirichlet/Neumann selon flux
1026
857
!       On choisit un Dirichlet si le flux de masse est entrant et
1027
858
!       que l'utilisateur a donn� une valeur dans RCODCL
1028
859
 
1029
 
      if(propfb(ifac,iflmab).ge.0.d0) then
1030
 
        if(itytur(iphas).eq.2) then
1031
 
          icodcl(ifac,ik (iphas)) = 3
1032
 
          icodcl(ifac,iep(iphas)) = 3
1033
 
        elseif(itytur(iphas).eq.3) then
1034
 
          icodcl(ifac,ir11(iphas)) = 3
1035
 
          icodcl(ifac,ir22(iphas)) = 3
1036
 
          icodcl(ifac,ir33(iphas)) = 3
1037
 
          icodcl(ifac,ir12(iphas)) = 3
1038
 
          icodcl(ifac,ir13(iphas)) = 3
1039
 
          icodcl(ifac,ir23(iphas)) = 3
1040
 
          icodcl(ifac,iep (iphas)) = 3
1041
 
        elseif(iturb(iphas).eq.50) then
1042
 
          icodcl(ifac,ik  (iphas)) = 3
1043
 
          icodcl(ifac,iep (iphas)) = 3
1044
 
          icodcl(ifac,iphi(iphas)) = 3
1045
 
          icodcl(ifac,ifb (iphas)) = 3
1046
 
        elseif(iturb(iphas).eq.60) then
1047
 
          icodcl(ifac,ik  (iphas)) = 3
1048
 
          icodcl(ifac,iomg(iphas)) = 3
1049
 
        endif
1050
 
        if(nscaus.gt.0) then
1051
 
          do ii = 1, nscaus
1052
 
            icodcl(ifac,isca(ii)) = 3
1053
 
          enddo
1054
 
        endif
1055
 
      else
1056
 
        if(itytur(iphas).eq.2) then
1057
 
          if(rcodcl(ifac,ik (iphas),1).gt.0.d0.and.               &
1058
 
             rcodcl(ifac,iep(iphas),1).gt.0.d0) then
1059
 
            icodcl(ifac,ik (iphas)) = 1
1060
 
            icodcl(ifac,iep(iphas)) = 1
1061
 
          else
1062
 
            icodcl(ifac,ik (iphas)) = 3
1063
 
            icodcl(ifac,iep(iphas)) = 3
1064
 
          endif
1065
 
        elseif(itytur(iphas).eq.3) then
1066
 
          if(rcodcl(ifac,ir11(iphas),1).gt.0.d0.and.              &
1067
 
             rcodcl(ifac,ir22(iphas),1).gt.0.d0.and.              &
1068
 
             rcodcl(ifac,ir33(iphas),1).gt.0.d0.and.              &
1069
 
             rcodcl(ifac,ir12(iphas),1).gt.-rinfin*0.5d0.and.     &
1070
 
             rcodcl(ifac,ir13(iphas),1).gt.-rinfin*0.5d0.and.     &
1071
 
             rcodcl(ifac,ir23(iphas),1).gt.-rinfin*0.5d0.and.     &
1072
 
             rcodcl(ifac,iep (iphas),1).gt.0.d0) then
1073
 
            icodcl(ifac,ir11(iphas)) = 1
1074
 
            icodcl(ifac,ir22(iphas)) = 1
1075
 
            icodcl(ifac,ir33(iphas)) = 1
1076
 
            icodcl(ifac,ir12(iphas)) = 1
1077
 
            icodcl(ifac,ir13(iphas)) = 1
1078
 
            icodcl(ifac,ir23(iphas)) = 1
1079
 
            icodcl(ifac,iep (iphas)) = 1
1080
 
          else
1081
 
            icodcl(ifac,ir11(iphas)) = 3
1082
 
            icodcl(ifac,ir22(iphas)) = 3
1083
 
            icodcl(ifac,ir33(iphas)) = 3
1084
 
            icodcl(ifac,ir12(iphas)) = 3
1085
 
            icodcl(ifac,ir13(iphas)) = 3
1086
 
            icodcl(ifac,ir23(iphas)) = 3
1087
 
            icodcl(ifac,iep (iphas)) = 3
1088
 
          endif
1089
 
        elseif(iturb(iphas).eq.50) then
1090
 
          if(rcodcl(ifac,ik  (iphas),1).gt.0.d0.and.              &
1091
 
             rcodcl(ifac,iep (iphas),1).gt.0.d0.and.              &
1092
 
             rcodcl(ifac,iphi(iphas),1).gt.0.d0.and.              &
1093
 
             rcodcl(ifac,ifb (iphas),1).gt.-rinfin*0.5d0 ) then
1094
 
            icodcl(ifac,ik  (iphas)) = 1
1095
 
            icodcl(ifac,iep (iphas)) = 1
1096
 
            icodcl(ifac,iphi(iphas)) = 1
1097
 
            icodcl(ifac,ifb (iphas)) = 1
1098
 
          else
1099
 
            icodcl(ifac,ik  (iphas)) = 3
1100
 
            icodcl(ifac,iep (iphas)) = 3
1101
 
            icodcl(ifac,iphi(iphas)) = 3
1102
 
            icodcl(ifac,ifb (iphas)) = 3
1103
 
          endif
1104
 
        elseif(iturb(iphas).eq.60) then
1105
 
         if(rcodcl(ifac,ik  (iphas),1).gt.0.d0.and.               &
1106
 
            rcodcl(ifac,iomg(iphas),1).gt.0.d0 ) then
1107
 
            icodcl(ifac,ik  (iphas)) = 1
1108
 
            icodcl(ifac,iomg(iphas)) = 1
1109
 
          else
1110
 
            icodcl(ifac,ik  (iphas)) = 3
1111
 
            icodcl(ifac,iomg(iphas)) = 3
1112
 
          endif
1113
 
        endif
1114
 
        if(nscaus.gt.0) then
1115
 
          do ii = 1, nscaus
1116
 
            if(rcodcl(ifac,isca(ii),1).gt.-rinfin*0.5d0) then
1117
 
              icodcl(ifac,isca(ii)) = 1
1118
 
            else
1119
 
              icodcl(ifac,isca(ii)) = 3
1120
 
            endif
1121
 
          enddo
1122
 
        endif
1123
 
      endif
 
860
    if(propfb(ifac,iflmab).ge.0.d0) then
 
861
      if(itytur.eq.2) then
 
862
        icodcl(ifac,ik ) = 3
 
863
        icodcl(ifac,iep) = 3
 
864
      elseif(itytur.eq.3) then
 
865
        icodcl(ifac,ir11) = 3
 
866
        icodcl(ifac,ir22) = 3
 
867
        icodcl(ifac,ir33) = 3
 
868
        icodcl(ifac,ir12) = 3
 
869
        icodcl(ifac,ir13) = 3
 
870
        icodcl(ifac,ir23) = 3
 
871
        icodcl(ifac,iep ) = 3
 
872
      elseif(iturb.eq.50) then
 
873
        icodcl(ifac,ik  ) = 3
 
874
        icodcl(ifac,iep ) = 3
 
875
        icodcl(ifac,iphi) = 3
 
876
        icodcl(ifac,ifb ) = 3
 
877
      elseif(iturb.eq.60) then
 
878
        icodcl(ifac,ik  ) = 3
 
879
        icodcl(ifac,iomg) = 3
 
880
      elseif(iturb.eq.70) then
 
881
        icodcl(ifac,inusa) = 3
 
882
      endif
 
883
      if(nscaus.gt.0) then
 
884
        do ii = 1, nscaus
 
885
          icodcl(ifac,isca(ii)) = 3
 
886
        enddo
 
887
      endif
 
888
    else
 
889
      if(itytur.eq.2) then
 
890
        if(rcodcl(ifac,ik ,1).gt.0.d0.and.               &
 
891
             rcodcl(ifac,iep,1).gt.0.d0) then
 
892
          icodcl(ifac,ik ) = 1
 
893
          icodcl(ifac,iep) = 1
 
894
        else
 
895
          icodcl(ifac,ik ) = 3
 
896
          icodcl(ifac,iep) = 3
 
897
        endif
 
898
      elseif(itytur.eq.3) then
 
899
        if(rcodcl(ifac,ir11,1).gt.0.d0.and.              &
 
900
             rcodcl(ifac,ir22,1).gt.0.d0.and.              &
 
901
             rcodcl(ifac,ir33,1).gt.0.d0.and.              &
 
902
             rcodcl(ifac,ir12,1).gt.-rinfin*0.5d0.and.     &
 
903
             rcodcl(ifac,ir13,1).gt.-rinfin*0.5d0.and.     &
 
904
             rcodcl(ifac,ir23,1).gt.-rinfin*0.5d0.and.     &
 
905
             rcodcl(ifac,iep ,1).gt.0.d0) then
 
906
          icodcl(ifac,ir11) = 1
 
907
          icodcl(ifac,ir22) = 1
 
908
          icodcl(ifac,ir33) = 1
 
909
          icodcl(ifac,ir12) = 1
 
910
          icodcl(ifac,ir13) = 1
 
911
          icodcl(ifac,ir23) = 1
 
912
          icodcl(ifac,iep ) = 1
 
913
        else
 
914
          icodcl(ifac,ir11) = 3
 
915
          icodcl(ifac,ir22) = 3
 
916
          icodcl(ifac,ir33) = 3
 
917
          icodcl(ifac,ir12) = 3
 
918
          icodcl(ifac,ir13) = 3
 
919
          icodcl(ifac,ir23) = 3
 
920
          icodcl(ifac,iep ) = 3
 
921
        endif
 
922
      elseif(iturb.eq.50) then
 
923
        if(rcodcl(ifac,ik  ,1).gt.0.d0.and.              &
 
924
             rcodcl(ifac,iep ,1).gt.0.d0.and.              &
 
925
             rcodcl(ifac,iphi,1).gt.0.d0.and.              &
 
926
             rcodcl(ifac,ifb ,1).gt.-rinfin*0.5d0 ) then
 
927
          icodcl(ifac,ik  ) = 1
 
928
          icodcl(ifac,iep ) = 1
 
929
          icodcl(ifac,iphi) = 1
 
930
          icodcl(ifac,ifb ) = 1
 
931
        else
 
932
          icodcl(ifac,ik  ) = 3
 
933
          icodcl(ifac,iep ) = 3
 
934
          icodcl(ifac,iphi) = 3
 
935
          icodcl(ifac,ifb ) = 3
 
936
        endif
 
937
      elseif(iturb.eq.60) then
 
938
         if(rcodcl(ifac,ik  ,1).gt.0.d0.and.               &
 
939
              rcodcl(ifac,iomg,1).gt.0.d0 ) then
 
940
           icodcl(ifac,ik  ) = 1
 
941
           icodcl(ifac,iomg) = 1
 
942
         else
 
943
           icodcl(ifac,ik  ) = 3
 
944
           icodcl(ifac,iomg) = 3
 
945
         endif
 
946
       elseif(iturb.eq.70) then
 
947
         if(rcodcl(ifac,inusa,1).gt.0.d0) then
 
948
           icodcl(ifac,inusa) = 1
 
949
         else
 
950
           icodcl(ifac,inusa) = 3
 
951
         endif
 
952
       endif
 
953
       if(nscaus.gt.0) then
 
954
         do ii = 1, nscaus
 
955
           if(rcodcl(ifac,isca(ii),1).gt.-rinfin*0.5d0) then
 
956
             icodcl(ifac,isca(ii)) = 1
 
957
           else
 
958
             icodcl(ifac,isca(ii)) = 3
 
959
           endif
 
960
         enddo
 
961
       endif
 
962
     endif
1124
963
 
1125
964
 
1126
965
!     Les RCODCL ont ete initialises a -RINFIN pour permettre de
1130
969
!       simplifier la boucle, on traite toutes les variables : les
1131
970
!       variables du compressible sont donc vues deux fois, mais ce
1132
971
!       n'est pas grave).
1133
 
      do ivar = 1, nvar
1134
 
        if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
1135
 
          rcodcl(ifac,ivar,1) = 0.d0
1136
 
        endif
1137
 
      enddo
 
972
     do ivar = 1, nvar
 
973
       if(rcodcl(ifac,ivar,1).le.-rinfin*0.5d0) then
 
974
         rcodcl(ifac,ivar,1) = 0.d0
 
975
       endif
 
976
     enddo
1138
977
 
1139
978
 
1140
979
! --- Fin de test sur les faces d'entree sortie
1141
 
    endif
 
980
   endif
1142
981
 
1143
982
! --- Fin de boucle sur les faces de bord
1144
 
  enddo
 
983
 enddo
1145
984
 
1146
 
! --- Fin de boucle sur les phases
1147
 
enddo
 
985
! Free memory
 
986
deallocate(w1, w2, w3)
 
987
deallocate(w4, w5, w6)
 
988
deallocate(w7)
1148
989
 
1149
990
!----
1150
991
! FORMATS