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

« back to all changes in this revision

Viewing changes to src/base/turrij.f90

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

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
!-------------------------------------------------------------------------------
2
 
 
3
 
!     This file is part of the Code_Saturne Kernel, element of the
4
 
!     Code_Saturne CFD tool.
5
 
 
6
 
!     Copyright (C) 1998-2011 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
25
 
 
26
 
!-------------------------------------------------------------------------------
27
 
 
28
 
subroutine turrij &
29
 
!================
30
 
 
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 , iphas  ,                   &
36
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
37
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
38
 
   icepdc , icetsm , itypsm ,                                     &
39
 
   idevel , ituser , ia     ,                                     &
40
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
41
 
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
42
 
   tslagr ,                                                       &
43
 
   coefa  , coefb  , ckupdc , smacel ,                            &
44
 
   viscf  , viscb  , coefax ,                                     &
45
 
   dam    , xam    , drtp   ,                                     &
46
 
   smbr   , rovsdt , grdvit , produc , grarox , graroy , graroz , &
47
 
   w1     , w2     , w3     , w4     ,                            &
48
 
   w5     , w6     , w7     , w8     , w9     ,                   &
49
 
   rdevel , rtuser , ra     )
50
 
 
51
 
!===============================================================================
52
 
! FONCTION :
53
 
! ----------
54
 
 
55
 
! RESOLUTION DES EQUATIONS Rij-EPS 1 PHASE INCOMPRESSIBLE OU
56
 
! RHO VARIABLE SUR UN PAS DE TEMPS
57
 
 
58
 
!-------------------------------------------------------------------------------
59
 
!ARGU                             ARGUMENTS
60
 
!__________________.____._____.________________________________________________.
61
 
! name             !type!mode ! role                                           !
62
 
!__________________!____!_____!________________________________________________!
63
 
! idbia0           ! i  ! <-- ! number of first free position in ia            !
64
 
! idbra0           ! i  ! <-- ! number of first free position in ra            !
65
 
! ndim             ! i  ! <-- ! spatial dimension                              !
66
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
67
 
! ncel             ! i  ! <-- ! number of cells                                !
68
 
! nfac             ! i  ! <-- ! number of interior faces                       !
69
 
! nfabor           ! i  ! <-- ! number of boundary faces                       !
70
 
! nfml             ! i  ! <-- ! number of families (group classes)             !
71
 
! nprfml           ! i  ! <-- ! number of properties per family (group class)  !
72
 
! nnod             ! i  ! <-- ! number of vertices                             !
73
 
! lndfac           ! i  ! <-- ! size of nodfac indexed array                   !
74
 
! lndfbr           ! i  ! <-- ! size of nodfbr indexed array                   !
75
 
! ncelbr           ! i  ! <-- ! number of cells with faces on boundary         !
76
 
! nvar             ! i  ! <-- ! total number of variables                      !
77
 
! nscal            ! i  ! <-- ! total number of scalars                        !
78
 
! nphas            ! i  ! <-- ! number of phases                               !
79
 
! ncepdp           ! i  ! <-- ! number of cells with head loss                 !
80
 
! ncesmp           ! i  ! <-- ! number of cells with mass source term          !
81
 
! nideve, nrdeve   ! i  ! <-- ! sizes of idevel and rdevel arrays              !
82
 
! nituse, nrtuse   ! i  ! <-- ! sizes of ituser and rtuser arrays              !
83
 
! iphas            ! i  ! <-- ! phase number                                   !
84
 
! ifacel(2, nfac)  ! ia ! <-- ! interior faces -> cells connectivity           !
85
 
! ifabor(nfabor)   ! ia ! <-- ! boundary faces -> cells connectivity           !
86
 
! ifmfbr(nfabor)   ! ia ! <-- ! boundary face family numbers                   !
87
 
! ifmcel(ncelet)   ! ia ! <-- ! cell family numbers                            !
88
 
! iprfml           ! ia ! <-- ! property numbers per family                    !
89
 
!  (nfml, nprfml)  !    !     !                                                !
90
 
! ipnfac(nfac+1)   ! ia ! <-- ! interior faces -> vertices index (optional)    !
91
 
! nodfac(lndfac)   ! ia ! <-- ! interior faces -> vertices list (optional)     !
92
 
! ipnfbr(nfabor+1) ! ia ! <-- ! boundary faces -> vertices index (optional)    !
93
 
! nodfbr(lndfbr)   ! ia ! <-- ! boundary faces -> vertices list (optional)     !
94
 
! icepdc(ncelet    ! te ! <-- ! numero des ncepdp cellules avec pdc            !
95
 
! icetsm(ncesmp    ! te ! <-- ! numero des cellules a source de masse          !
96
 
! itypsm           ! te ! <-- ! type de source de masse pour les               !
97
 
! (ncesmp,nvar)    !    !     !  variables (cf. ustsma)                        !
98
 
! idevel(nideve)   ! ia ! <-> ! integer work array for temporary development   !
99
 
! ituser(nituse)   ! ia ! <-> ! user-reserved integer work array               !
100
 
! ia(*)            ! ia ! --- ! main integer work array                        !
101
 
! xyzcen           ! ra ! <-- ! cell centers                                   !
102
 
!  (ndim, ncelet)  !    !     !                                                !
103
 
! surfac           ! ra ! <-- ! interior faces surface vectors                 !
104
 
!  (ndim, nfac)    !    !     !                                                !
105
 
! surfbo           ! ra ! <-- ! boundary faces surface vectors                 !
106
 
!  (ndim, nfabor)  !    !     !                                                !
107
 
! cdgfac           ! ra ! <-- ! interior faces centers of gravity              !
108
 
!  (ndim, nfac)    !    !     !                                                !
109
 
! cdgfbo           ! ra ! <-- ! boundary faces centers of gravity              !
110
 
!  (ndim, nfabor)  !    !     !                                                !
111
 
! xyznod           ! ra ! <-- ! vertex coordinates (optional)                  !
112
 
!  (ndim, nnod)    !    !     !                                                !
113
 
! volume(ncelet)   ! ra ! <-- ! cell volumes                                   !
114
 
! dt(ncelet)       ! ra ! <-- ! time step (per cell)                           !
115
 
! rtp, rtpa        ! ra ! <-- ! calculated variables at cell centers           !
116
 
!  (ncelet, *)     !    !     !  (at current and previous time steps)          !
117
 
! propce(ncelet, *)! ra ! <-- ! physical properties at cell centers            !
118
 
! propfa(nfac, *)  ! ra ! <-- ! physical properties at interior face centers   !
119
 
! propfb(nfabor, *)! ra ! <-- ! physical properties at boundary face centers   !
120
 
! tslagr           ! tr ! <-- ! terme de couplage retour du                    !
121
 
!(ncelet,*)        !    !     !     lagrangien                                 !
122
 
! coefa, coefb     ! ra ! <-- ! boundary conditions                            !
123
 
!  (nfabor, *)     !    !     !                                                !
124
 
! ckupdc           ! tr ! <-- ! tableau de travail pour pdc                    !
125
 
!  (ncepdp,6)      !    !     !                                                !
126
 
! smacel           ! tr ! <-- ! valeur des variables associee a la             !
127
 
! (ncesmp,*   )    !    !     !  source de masse                               !
128
 
!                  !    !     !  pour ivar=ipr, smacel=flux de masse           !
129
 
! viscf(nfac)      ! tr ! --- ! visc*surface/dist aux faces internes           !
130
 
! viscb(nfabor     ! tr ! --- ! visc*surface/dist aux faces de bord            !
131
 
! coefax(nfabor    ! tr ! --- ! tab de trav pour cond.lim. paroi               !
132
 
!                  ! tr ! --- !   attention : uniquement avec echo             !
133
 
!                  ! tr ! --- !   de paroi et abs(icdpar) = 1                  !
134
 
! dam(ncelet       ! tr ! --- ! tableau de travail pour matrice                !
135
 
! xam(nfac,*)      ! tr ! --- ! tableau de travail pour matrice                !
136
 
! drtp(ncelet      ! tr ! --- ! tableau de travail pour increment              !
137
 
! drtp(ncelet      ! tr ! --- ! tableau de travail pour increment              !
138
 
! smbr (ncelet     ! tr ! --- ! tableau de travail pour sec mem                !
139
 
! drtp(ncelet)     ! tr ! --- ! tableau de travail pour increment              !
140
 
! smbr?(ncelet)    ! tr ! --- ! tableau de travail pour sec mem                !
141
 
! rovsdt(ncelet    ! tr ! --- ! tableau de travail pour terme instat           !
142
 
! grdvit           ! tr ! --- ! tableau de travail pour terme grad             !
143
 
!  (ncelet,3,3)    !    !     !    de vitesse     uniqt pour iturb=31          !
144
 
! produc           ! tr ! <-- ! tableau de travail pour production             !
145
 
!  (6,ncelet)      !    !     ! (sans rho volume) uniqt pour iturb=30          !
146
 
! grarox,y,z       ! tr ! --- ! tableau de travail pour grad rom               !
147
 
!  (ncelet)        !    !     !                                                !
148
 
! w?(ncelet)       ! tr ! --- ! tableau de travail                             !
149
 
! rdevel(nrdeve)   ! ra ! <-> ! real work array for temporary development      !
150
 
! rtuser(nrtuse)   ! ra ! <-> ! user-reserved real work array                  !
151
 
! ra(*)            ! ra ! --- ! main real work array                           !
152
 
!__________________!____!_____!________________________________________________!
153
 
 
154
 
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
155
 
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
156
 
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
157
 
!            --- tableau de travail
158
 
!-------------------------------------------------------------------------------
159
 
!===============================================================================
160
 
 
161
 
implicit none
162
 
 
163
 
!===============================================================================
164
 
! Common blocks
165
 
!===============================================================================
166
 
 
167
 
include "dimfbr.h"
168
 
include "paramx.h"
169
 
include "numvar.h"
170
 
include "entsor.h"
171
 
include "cstphy.h"
172
 
include "optcal.h"
173
 
include "lagpar.h"
174
 
include "lagran.h"
175
 
 
176
 
! Disable use of Fortran 90 pointers if using gfortran < 4.2, as
177
 
! a gfortran 4.1 bug produces an error here. Array bounds checking
178
 
! with such an old version will thus lead to errors.
179
 
#if defined(__GNUC__) && defined(__GNUC_MINOR__)
180
 
#if (__GNUC__ == 4) && (__GNUC_MINOR__ < 2)
181
 
#define CS_DISABLE_F90_POINTERS 1
182
 
#endif
183
 
#endif
184
 
 
185
 
!===============================================================================
186
 
 
187
 
! Arguments
188
 
 
189
 
integer          idbia0 , idbra0
190
 
integer          ndim   , ncelet , ncel   , nfac   , nfabor
191
 
integer          nfml   , nprfml
192
 
integer          nnod   , lndfac , lndfbr , ncelbr
193
 
integer          nvar   , nscal  , nphas
194
 
integer          ncepdp , ncesmp
195
 
integer          nideve , nrdeve , nituse , nrtuse , iphas
196
 
 
197
 
integer          ifacel(2,nfac) , ifabor(nfabor)
198
 
integer          ifmfbr(nfabor) , ifmcel(ncelet)
199
 
integer          iprfml(nfml,nprfml)
200
 
integer          ipnfac(nfac+1), nodfac(lndfac)
201
 
integer          ipnfbr(nfabor+1), nodfbr(lndfbr)
202
 
integer          icepdc(ncepdp)
203
 
integer          icetsm(ncesmp)
204
 
integer          idevel(nideve), ituser(nituse)
205
 
integer          ia(*)
206
 
 
207
 
#if !defined(CS_DISABLE_F90_POINTERS)
208
 
integer, dimension(ncesmp,nvar), target :: itypsm
209
 
#else
210
 
integer          itypsm(ncesmp,nvar)
211
 
#endif
212
 
 
213
 
double precision xyzcen(ndim,ncelet)
214
 
double precision surfac(ndim,nfac), surfbo(ndim,nfabor)
215
 
double precision cdgfac(ndim,nfac), cdgfbo(ndim,nfabor)
216
 
double precision xyznod(ndim,nnod), volume(ncelet)
217
 
double precision dt(ncelet), rtp(ncelet,*), rtpa(ncelet,*)
218
 
double precision propce(ncelet,*)
219
 
double precision propfa(nfac,*), propfb(ndimfb,*)
220
 
double precision coefa(ndimfb,*), coefb(ndimfb,*)
221
 
double precision ckupdc(ncepdp,6)
222
 
double precision viscf(nfac), viscb(nfabor), coefax(nfabor)
223
 
double precision dam(ncelet), xam(nfac,2)
224
 
double precision drtp(ncelet), smbr(ncelet), rovsdt(ncelet)
225
 
double precision grdvit(ncelet,3,3), produc(6,ncelet)
226
 
double precision grarox(ncelet), graroy(ncelet), graroz(ncelet)
227
 
double precision w1(ncelet), w2(ncelet), w3(ncelet)
228
 
double precision w4(ncelet), w5(ncelet), w6(ncelet)
229
 
double precision w7(ncelet), w8(ncelet), w9(ncelet)
230
 
double precision rdevel(nrdeve), rtuser(nrtuse), ra(*)
231
 
 
232
 
#if !defined(CS_DISABLE_F90_POINTERS)
233
 
double precision, dimension(ncesmp,nvar), target ::  smacel
234
 
double precision, dimension(ncelet,*), target :: tslagr
235
 
#else
236
 
double precision smacel(ncesmp,nvar)
237
 
double precision tslagr(ncelet,*)
238
 
#endif
239
 
 
240
 
! Local variables
241
 
 
242
 
integer          idebia, idebra
243
 
integer          ifac  , iel   , ivar  , isou  , ii
244
 
integer          inc   , iccocg
245
 
integer          ipp   , iwarnp, iclip
246
 
integer          ipriph, iuiph , iviph , iwiph
247
 
integer          ir11ip, ir22ip, ir33ip, ir12ip, ir13ip, ir23ip
248
 
integer          ieiph
249
 
integer          icliup, iclivp, icliwp
250
 
integer          nswrgp, imligp, iphydp
251
 
integer          ipcrom, ipbrom, ipcroo, ipbroo, iivar
252
 
integer          iitsla
253
 
double precision epsrgp, climgp, extrap
254
 
 
255
 
#if !defined(CS_DISABLE_F90_POINTERS)
256
 
integer,          pointer, dimension(:) :: itpsmp => null()
257
 
double precision, pointer, dimension(:) :: smcelp => null(), gammap => null()
258
 
double precision, pointer, dimension(:) :: tslage => null(), tslagi => null()
259
 
#endif
260
 
 
261
 
!===============================================================================
262
 
 
263
 
!===============================================================================
264
 
! 1. INITIALISATION
265
 
!===============================================================================
266
 
 
267
 
idebia = idbia0
268
 
idebra = idbra0
269
 
 
270
 
ipriph = ipr (iphas)
271
 
iuiph  = iu  (iphas)
272
 
iviph  = iv  (iphas)
273
 
iwiph  = iw  (iphas)
274
 
ir11ip = ir11(iphas)
275
 
ir22ip = ir22(iphas)
276
 
ir33ip = ir33(iphas)
277
 
ir12ip = ir12(iphas)
278
 
ir13ip = ir13(iphas)
279
 
ir23ip = ir23(iphas)
280
 
ieiph  = iep (iphas)
281
 
 
282
 
icliup = iclrtp(iuiph,icoef)
283
 
iclivp = iclrtp(iviph,icoef)
284
 
icliwp = iclrtp(iwiph,icoef)
285
 
 
286
 
ipcrom = ipproc(irom  (iphas))
287
 
ipbrom = ipprob(irom  (iphas))
288
 
 
289
 
if(iwarni(ieiph).ge.1) then
290
 
  if (iturb(iphas).eq.30) then
291
 
    write(nfecra,1000) iphas
292
 
  else
293
 
    write(nfecra,1001) iphas
294
 
  endif
295
 
endif
296
 
 
297
 
 
298
 
!     SI ITURB=30 (RIJ STD) ON STOCKE DIRECTEMENT LA PRODUCTION DANS
299
 
!     LE TABLEAU PRODUC
300
 
!     SI ITURB=31 (SSG) ON STOCKE LE GRADIENT DE VITESSE DANS GRDVIT
301
 
 
302
 
!===============================================================================
303
 
! 2.a CALCUL DU TENSEUR DE PRODUCTION POUR LE RIJ STANDARD
304
 
!     W7 = P11 , W8 = P22 , W9 = P33
305
 
!     W10 = P12 , W11 = P13 , W9 = P23
306
 
!===============================================================================
307
 
 
308
 
if (iturb(iphas).eq.30) then
309
 
! INITIALISATIONS DE W7 ... W12
310
 
 
311
 
  do ii = 1 , 6
312
 
    do iel = 1, ncel
313
 
      produc(ii,iel) = 0.0d0
314
 
    enddo
315
 
  enddo
316
 
 
317
 
! CALCUL DU GRADIENT DES 3 COMPOSANTES DE LA VITESSE
318
 
 
319
 
  iccocg = 1
320
 
  inc    = 1
321
 
 
322
 
! GRADIENT SUIVANT X
323
 
 
324
 
  nswrgp = nswrgr(iuiph)
325
 
  imligp = imligr(iuiph)
326
 
  iwarnp = iwarni(iuiph)
327
 
  epsrgp = epsrgr(iuiph)
328
 
  climgp = climgr(iuiph)
329
 
  extrap = extrag(iuiph)
330
 
  iphydp = 0
331
 
 
332
 
  call grdcel                                                     &
333
 
  !==========
334
 
 ( idebia , idebra ,                                              &
335
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
336
 
   nnod   , lndfac , lndfbr , ncelbr , nphas  ,                   &
337
 
   nideve , nrdeve , nituse , nrtuse ,                            &
338
 
   iuiph  , imrgra , inc    , iccocg , nswrgp , imligp , iphydp , &
339
 
   iwarnp , nfecra , epsrgp , climgp , extrap ,                   &
340
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
341
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
342
 
   idevel , ituser , ia     ,                                     &
343
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
344
 
   w1     , w1     , w1     ,                                     &
345
 
   rtpa(1,iuiph)   , coefa(1,icliup) , coefb(1,icliup) ,          &
346
 
   w1     , w2     , w3     ,                                     &
347
 
!        ------   ------   ------
348
 
   w4     , w5     , w6     ,                                     &
349
 
   rdevel , rtuser , ra     )
350
 
 
351
 
 
352
 
  do iel = 1 , ncel
353
 
 
354
 
    produc(1,iel) = produc(1,iel)                                 &
355
 
         - 2.0d0*(rtpa(iel,ir11ip)*w1(iel) +                      &
356
 
         rtpa(iel,ir12ip)*w2(iel) +                               &
357
 
         rtpa(iel,ir13ip)*w3(iel) )
358
 
 
359
 
    produc(4,iel) = produc(4,iel)                                 &
360
 
         - (rtpa(iel,ir12ip)*w1(iel) +                            &
361
 
         rtpa(iel,ir22ip)*w2(iel) +                               &
362
 
         rtpa(iel,ir23ip)*w3(iel) )
363
 
 
364
 
    produc(5,iel) = produc(5,iel)                                 &
365
 
         - (rtpa(iel,ir13ip)*w1(iel) +                            &
366
 
         rtpa(iel,ir23ip)*w2(iel) +                               &
367
 
         rtpa(iel,ir33ip)*w3(iel) )
368
 
 
369
 
  enddo
370
 
 
371
 
! Gradient suivant Y
372
 
 
373
 
  nswrgp = nswrgr(iviph)
374
 
  imligp = imligr(iviph)
375
 
  iwarnp = iwarni(iviph)
376
 
  epsrgp = epsrgr(iviph)
377
 
  climgp = climgr(iviph)
378
 
  extrap = extrag(iviph)
379
 
  iphydp = 0
380
 
 
381
 
  call grdcel                                                     &
382
 
  !==========
383
 
 ( idebia , idebra ,                                              &
384
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
385
 
   nnod   , lndfac , lndfbr , ncelbr , nphas  ,                   &
386
 
   nideve , nrdeve , nituse , nrtuse ,                            &
387
 
   iviph  , imrgra , inc    , iccocg , nswrgp , imligp , iphydp , &
388
 
   iwarnp , nfecra , epsrgp , climgp , extrap ,                   &
389
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
390
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
391
 
   idevel , ituser , ia     ,                                     &
392
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
393
 
   w1     , w1     , w1     ,                                     &
394
 
   rtpa(1,iviph)   , coefa(1,iclivp) , coefb(1,iclivp) ,          &
395
 
   w1     , w2     , w3     ,                                     &
396
 
!        ------   ------   ------
397
 
   w4     , w5     , w6     ,                                     &
398
 
   rdevel , rtuser , ra     )
399
 
 
400
 
  do iel = 1 , ncel
401
 
 
402
 
    produc(2,iel) = produc(2,iel)                                 &
403
 
         - 2.0d0*(rtpa(iel,ir12ip)*w1(iel) +                      &
404
 
         rtpa(iel,ir22ip)*w2(iel) +                               &
405
 
         rtpa(iel,ir23ip)*w3(iel) )
406
 
 
407
 
    produc(4,iel) = produc(4,iel)                                 &
408
 
         - (rtpa(iel,ir11ip)*w1(iel) +                            &
409
 
         rtpa(iel,ir12ip)*w2(iel) +                               &
410
 
         rtpa(iel,ir13ip)*w3(iel) )
411
 
 
412
 
    produc(6,iel) = produc(6,iel)                                 &
413
 
         - (rtpa(iel,ir13ip)*w1(iel) +                            &
414
 
         rtpa(iel,ir23ip)*w2(iel) +                               &
415
 
         rtpa(iel,ir33ip)*w3(iel) )
416
 
 
417
 
  enddo
418
 
 
419
 
! Gradient suivant Z
420
 
 
421
 
  nswrgp = nswrgr(iwiph)
422
 
  imligp = imligr(iwiph)
423
 
  iwarnp = iwarni(iwiph)
424
 
  epsrgp = epsrgr(iwiph)
425
 
  climgp = climgr(iwiph)
426
 
  extrap = extrag(iwiph)
427
 
  iphydp = 0
428
 
 
429
 
  call grdcel                                                     &
430
 
  !==========
431
 
 ( idebia , idebra ,                                              &
432
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
433
 
   nnod   , lndfac , lndfbr , ncelbr , nphas  ,                   &
434
 
   nideve , nrdeve , nituse , nrtuse ,                            &
435
 
   iwiph  , imrgra , inc    , iccocg , nswrgp , imligp , iphydp , &
436
 
   iwarnp , nfecra , epsrgp , climgp , extrap ,                   &
437
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
438
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
439
 
   idevel , ituser , ia     ,                                     &
440
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
441
 
   w1     , w1     , w1     ,                                     &
442
 
   rtpa(1,iwiph)   , coefa(1,icliwp) , coefb(1,icliwp) ,          &
443
 
   w1     , w2     , w3     ,                                     &
444
 
!        ------   ------   ------
445
 
   w4     , w5     , w6     ,                                     &
446
 
   rdevel , rtuser , ra     )
447
 
 
448
 
  do iel = 1 , ncel
449
 
 
450
 
    produc(3,iel) = produc(3,iel)                                 &
451
 
         - 2.0d0*(rtpa(iel,ir13ip)*w1(iel) +                      &
452
 
         rtpa(iel,ir23ip)*w2(iel) +                               &
453
 
         rtpa(iel,ir33ip)*w3(iel) )
454
 
 
455
 
    produc(5,iel) = produc(5,iel)                                 &
456
 
         - (rtpa(iel,ir11ip)*w1(iel) +                            &
457
 
         rtpa(iel,ir12ip)*w2(iel) +                               &
458
 
         rtpa(iel,ir13ip)*w3(iel) )
459
 
 
460
 
    produc(6,iel) = produc(6,iel)                                 &
461
 
         - (rtpa(iel,ir12ip)*w1(iel) +                            &
462
 
         rtpa(iel,ir22ip)*w2(iel) +                               &
463
 
         rtpa(iel,ir23ip)*w3(iel) )
464
 
 
465
 
  enddo
466
 
 
467
 
else
468
 
 
469
 
!===============================================================================
470
 
! 2.b CALCUL DU GRADIENT DE VITESSE POUR LE RIJ SSG
471
 
!     GRDVIT(IEL,I,J) = dUi/dxj(IEL)
472
 
!===============================================================================
473
 
 
474
 
! CALCUL DU GRADIENT DES 3 COMPOSANTES DE LA VITESSE
475
 
 
476
 
  iccocg = 1
477
 
  inc    = 1
478
 
 
479
 
! GRADIENT SUIVANT X
480
 
 
481
 
  nswrgp = nswrgr(iuiph)
482
 
  imligp = imligr(iuiph)
483
 
  iwarnp = iwarni(iuiph)
484
 
  epsrgp = epsrgr(iuiph)
485
 
  climgp = climgr(iuiph)
486
 
  extrap = extrag(iuiph)
487
 
  iphydp = 0
488
 
 
489
 
  call grdcel                                                     &
490
 
  !==========
491
 
 ( idebia , idebra ,                                              &
492
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
493
 
   nnod   , lndfac , lndfbr , ncelbr , nphas  ,                   &
494
 
   nideve , nrdeve , nituse , nrtuse ,                            &
495
 
   iuiph  , imrgra , inc    , iccocg , nswrgp , imligp , iphydp , &
496
 
   iwarnp , nfecra , epsrgp , climgp , extrap ,                   &
497
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
498
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
499
 
   idevel , ituser , ia     ,                                     &
500
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
501
 
   w1     , w1     , w1     ,                                     &
502
 
   rtpa(1,iuiph)   , coefa(1,icliup) , coefb(1,icliup) ,          &
503
 
   grdvit(1,1,1)   , grdvit(1,1,2)   , grdvit(1,1,3)   ,          &
504
 
!        -------------     -------------     -------------
505
 
   w4     , w5     , w6     ,                                     &
506
 
   rdevel , rtuser , ra     )
507
 
 
508
 
 
509
 
! Gradient suivant Y
510
 
 
511
 
  nswrgp = nswrgr(iviph)
512
 
  imligp = imligr(iviph)
513
 
  iwarnp = iwarni(iviph)
514
 
  epsrgp = epsrgr(iviph)
515
 
  climgp = climgr(iviph)
516
 
  extrap = extrag(iviph)
517
 
  iphydp = 0
518
 
 
519
 
  call grdcel                                                     &
520
 
  !==========
521
 
 ( idebia , idebra ,                                              &
522
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
523
 
   nnod   , lndfac , lndfbr , ncelbr , nphas  ,                   &
524
 
   nideve , nrdeve , nituse , nrtuse ,                            &
525
 
   iviph  , imrgra , inc    , iccocg , nswrgp , imligp , iphydp , &
526
 
   iwarnp , nfecra , epsrgp , climgp , extrap ,                   &
527
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
528
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
529
 
   idevel , ituser , ia     ,                                     &
530
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
531
 
   w1     , w1     , w1     ,                                     &
532
 
   rtpa(1,iviph)   , coefa(1,iclivp) , coefb(1,iclivp) ,          &
533
 
   grdvit(1,2,1)   , grdvit(1,2,2)   , grdvit(1,2,3)   ,          &
534
 
!        -------------     -------------     -------------
535
 
   w4     , w5     , w6     ,                                     &
536
 
   rdevel , rtuser , ra     )
537
 
 
538
 
 
539
 
! Gradient suivant Z
540
 
 
541
 
  nswrgp = nswrgr(iwiph)
542
 
  imligp = imligr(iwiph)
543
 
  iwarnp = iwarni(iwiph)
544
 
  epsrgp = epsrgr(iwiph)
545
 
  climgp = climgr(iwiph)
546
 
  extrap = extrag(iwiph)
547
 
  iphydp = 0
548
 
 
549
 
  call grdcel                                                     &
550
 
  !==========
551
 
 ( idebia , idebra ,                                              &
552
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
553
 
   nnod   , lndfac , lndfbr , ncelbr , nphas  ,                   &
554
 
   nideve , nrdeve , nituse , nrtuse ,                            &
555
 
   iwiph  , imrgra , inc    , iccocg , nswrgp , imligp , iphydp , &
556
 
   iwarnp , nfecra , epsrgp , climgp , extrap ,                   &
557
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
558
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
559
 
   idevel , ituser , ia     ,                                     &
560
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
561
 
   w1     , w1     , w1     ,                                     &
562
 
   rtpa(1,iwiph)   , coefa(1,icliwp) , coefb(1,icliwp) ,          &
563
 
   grdvit(1,3,1)   , grdvit(1,3,2)   , grdvit(1,3,3)   ,          &
564
 
!        -------------     -------------     -------------
565
 
   w4     , w5     , w6     ,                                     &
566
 
   rdevel , rtuser , ra     )
567
 
 
568
 
endif
569
 
 
570
 
 
571
 
!===============================================================================
572
 
! 3.  CALCUL DU GRADIENT DE ROM POUR LES TERMES DE GRAVITE
573
 
!===============================================================================
574
 
 
575
 
if(igrari(iphas).eq.1) then
576
 
 
577
 
! Conditions aux limites : Dirichlet ROMB
578
 
!   On utilise VISCB pour stocker le coefb relatif a ROM
579
 
!   On impose en Dirichlet (COEFA) la valeur ROMB
580
 
 
581
 
  do ifac = 1, nfabor
582
 
    viscb(ifac) = 0.d0
583
 
  enddo
584
 
 
585
 
! Le choix ci dessous a l'avantage d'etre simple
586
 
 
587
 
  nswrgp = nswrgr(ir11ip)
588
 
  imligp = imligr(ir11ip)
589
 
  iwarnp = iwarni(ir11ip)
590
 
  epsrgp = epsrgr(ir11ip)
591
 
  climgp = climgr(ir11ip)
592
 
  extrap = extrag(ir11ip)
593
 
  iphydp = 0
594
 
 
595
 
  iivar = 0
596
 
 
597
 
!     Si on extrapole les termes sources et rho, on utilise cpdt rho^n
598
 
  ipcroo = ipcrom
599
 
  ipbroo = ipbrom
600
 
  if(isto2t(iphas).gt.0.and.iroext(iphas).gt.0) then
601
 
    ipcroo = ipproc(iroma(iphas))
602
 
    ipbroo = ipprob(iroma(iphas))
603
 
  endif
604
 
 
605
 
  call grdcel                                                     &
606
 
  !==========
607
 
 ( idebia , idebra ,                                              &
608
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
609
 
   nnod   , lndfac , lndfbr , ncelbr , nphas  ,                   &
610
 
   nideve , nrdeve , nituse , nrtuse ,                            &
611
 
   iivar  , imrgra , inc    , iccocg , nswrgp , imligp ,  iphydp ,&
612
 
   iwarnp , nfecra , epsrgp , climgp , extrap ,                   &
613
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
614
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
615
 
   idevel , ituser , ia     ,                                     &
616
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
617
 
   w1     , w1     , w1     ,                                     &
618
 
   propce(1,ipcroo), propfb(1,ipbroo), viscb           ,          &
619
 
   grarox , graroy , graroz ,                                     &
620
 
!        ------   ------   ------
621
 
   w4     , w5     , w6     ,                                     &
622
 
   rdevel , rtuser , ra     )
623
 
 
624
 
endif
625
 
 
626
 
 
627
 
!===============================================================================
628
 
! 4.  Boucle sur les variables Rij (6 variables)
629
 
!     L'ordre est R11 R22 R33 R12 R13 R23 (La place de ces variables
630
 
!     est IR11.    ..
631
 
!     On resout les equation dans une routine semblable a covofi.F
632
 
!===============================================================================
633
 
 
634
 
 
635
 
 
636
 
do isou = 1, 6
637
 
  if    (isou.eq.1) then
638
 
    ivar   = ir11ip
639
 
  elseif(isou.eq.2) then
640
 
    ivar   = ir22ip
641
 
  elseif(isou.eq.3) then
642
 
    ivar   = ir33ip
643
 
  elseif(isou.eq.4) then
644
 
    ivar   = ir12ip
645
 
  elseif(isou.eq.5) then
646
 
    ivar   = ir13ip
647
 
  elseif(isou.eq.6) then
648
 
    ivar   = ir23ip
649
 
  endif
650
 
  ipp    = ipprtp(ivar)
651
 
 
652
 
#if !defined(CS_DISABLE_F90_POINTERS)
653
 
 
654
 
  if (iilagr.eq.2 .and. iphas.eq.1) then
655
 
    iitsla = itsr11 + (isou-1)
656
 
    tslage => tslagr(1:ncelet, iitsla)
657
 
    tslagi => tslagr(1:ncelet, itsli)
658
 
  endif
659
 
 
660
 
  if (ncesmp.gt.0) then
661
 
    itpsmp => itypsm(1:ncesmp,ivar)
662
 
    smcelp => smacel(1:ncesmp,ivar)
663
 
    gammap => smacel(1:ncesmp,ipriph)
664
 
  endif
665
 
 
666
 
  !     Rij-epsilon standard (LRR)
667
 
  if (iturb(iphas).eq.30) then
668
 
    call resrij                                                   &
669
 
    !==========
670
 
 ( idebia , idebra ,                                              &
671
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
672
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
673
 
   nvar   , nscal  , nphas  , ncepdp , ncesmp ,                   &
674
 
   nideve , nrdeve , nituse , nrtuse ,                            &
675
 
   iphas  , ivar   , isou   , ipp    ,                            &
676
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
677
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
678
 
   icepdc , icetsm , itpsmp ,                                     &
679
 
   idevel , ituser , ia     ,                                     &
680
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
681
 
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
682
 
   coefa  , coefb  , produc , grarox , graroy , graroz ,          &
683
 
   ckupdc , smcelp , gammap ,                                     &
684
 
   viscf  , viscb  , coefax ,                                     &
685
 
   tslage , tslagi ,                                              &
686
 
   dam    , xam    , drtp   , smbr   , rovsdt ,                   &
687
 
   w1     , w2     , w3     , w4     ,                            &
688
 
   w5     , w6     , w7     , w8     , w9     ,                   &
689
 
   rdevel , rtuser , ra     )
690
 
 
691
 
  else
692
 
    !     Rij-epsilon SSG
693
 
    call resssg                                                   &
694
 
    !==========
695
 
 ( idebia , idebra ,                                              &
696
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
697
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
698
 
   nvar   , nscal  , nphas  , ncepdp , ncesmp ,                   &
699
 
   nideve , nrdeve , nituse , nrtuse ,                            &
700
 
   iphas  , ivar   , isou   , ipp    ,                            &
701
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
702
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
703
 
   icepdc , icetsm , itpsmp ,                                     &
704
 
   idevel , ituser , ia     ,                                     &
705
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
706
 
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
707
 
   coefa  , coefb  , grdvit , grarox , graroy , graroz ,          &
708
 
   ckupdc , smcelp , gammap ,                                     &
709
 
   viscf  , viscb  , coefax ,                                     &
710
 
   tslage , tslagi ,                                              &
711
 
   dam    , xam    , drtp   , smbr   , rovsdt ,                   &
712
 
   w1     , w2     , w3     , w4     ,                            &
713
 
   w5     , w6     , w7     , w8     , w9     ,                   &
714
 
   rdevel , rtuser , ra     )
715
 
  endif
716
 
 
717
 
#else
718
 
 
719
 
  if (iilagr.eq.2 .and. iphas.eq.1) then
720
 
    iitsla = itsr11 + (isou-1)
721
 
  endif
722
 
 
723
 
!     Rij-epsilon standard (LRR)
724
 
  if (iturb(iphas).eq.30) then
725
 
    call resrij                                                   &
726
 
    !==========
727
 
 ( idebia , idebra ,                                              &
728
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
729
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
730
 
   nvar   , nscal  , nphas  , ncepdp , ncesmp ,                   &
731
 
   nideve , nrdeve , nituse , nrtuse ,                            &
732
 
   iphas  , ivar   , isou   , ipp    ,                            &
733
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
734
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
735
 
   icepdc , icetsm , itypsm(1,ivar)  ,                            &
736
 
   idevel , ituser , ia     ,                                     &
737
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
738
 
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
739
 
   coefa  , coefb  , produc , grarox , graroy , graroz ,          &
740
 
   ckupdc , smacel(1,ivar)  , smacel(1,ipriph),                   &
741
 
   viscf  , viscb  , coefax ,                                     &
742
 
   tslagr(1,iitsla) , tslagr(1,itsli) ,                           &
743
 
   dam    , xam    , drtp   , smbr   , rovsdt ,                   &
744
 
   w1     , w2     , w3     , w4     ,                            &
745
 
   w5     , w6     , w7     , w8     , w9     ,                   &
746
 
   rdevel , rtuser , ra     )
747
 
 
748
 
  else
749
 
!     Rij-epsilon SSG
750
 
    call resssg                                                   &
751
 
    !==========
752
 
 ( idebia , idebra ,                                              &
753
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
754
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
755
 
   nvar   , nscal  , nphas  , ncepdp , ncesmp ,                   &
756
 
   nideve , nrdeve , nituse , nrtuse ,                            &
757
 
   iphas  , ivar   , isou   , ipp    ,                            &
758
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
759
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
760
 
   icepdc , icetsm , itypsm(1,ivar)  ,                            &
761
 
   idevel , ituser , ia     ,                                     &
762
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
763
 
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
764
 
   coefa  , coefb  , grdvit , grarox , graroy , graroz ,          &
765
 
   ckupdc , smacel(1,ivar)  , smacel(1,ipriph),                   &
766
 
   viscf  , viscb  , coefax ,                                     &
767
 
   tslagr(1,iitsla) , tslagr(1,itsli) ,                           &
768
 
   dam    , xam    , drtp   , smbr   , rovsdt ,                   &
769
 
   w1     , w2     , w3     , w4     ,                            &
770
 
   w5     , w6     , w7     , w8     , w9     ,                   &
771
 
   rdevel , rtuser , ra     )
772
 
  endif
773
 
 
774
 
#endif
775
 
 
776
 
enddo
777
 
 
778
 
!===============================================================================
779
 
! 5.  RESOLUTION DE EPSILON
780
 
!===============================================================================
781
 
 
782
 
ivar   = ieiph
783
 
ipp    = ipprtp(ivar)
784
 
isou   = 7
785
 
 
786
 
#if !defined(CS_DISABLE_F90_POINTERS)
787
 
 
788
 
if (ncesmp.gt.0) then
789
 
  itpsmp => itypsm(1:ncesmp,ivar)
790
 
  smcelp => smacel(1:ncesmp,ivar)
791
 
  gammap => smacel(1:ncesmp,ipriph)
792
 
endif
793
 
 
794
 
call reseps                                                       &
795
 
!==========
796
 
 ( idebia , idebra ,                                              &
797
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
798
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
799
 
   nvar   , nscal  , nphas  , ncepdp , ncesmp ,                   &
800
 
   nideve , nrdeve , nituse , nrtuse ,                            &
801
 
   iphas  , ivar   , isou   , ipp    ,                            &
802
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
803
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
804
 
   icepdc , icetsm , itpsmp ,                                     &
805
 
   idevel , ituser , ia     ,                                     &
806
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
807
 
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
808
 
   coefa  , coefb  , grdvit , produc ,grarox , graroy , graroz ,  &
809
 
   ckupdc , smcelp , gammap ,                                     &
810
 
   viscf  , viscb  ,                                              &
811
 
   tslagr ,                                                       &
812
 
   dam    , xam    , drtp   , smbr   , rovsdt ,                   &
813
 
   w1     , w2     , w3     , w4     ,                            &
814
 
   w5     , w6     , w7     , w8     , w9     ,                   &
815
 
   rdevel , rtuser , ra     )
816
 
 
817
 
#else
818
 
 
819
 
   call reseps                                                    &
820
 
   !==========
821
 
 ( idebia , idebra ,                                              &
822
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
823
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
824
 
   nvar   , nscal  , nphas  , ncepdp , ncesmp ,                   &
825
 
   nideve , nrdeve , nituse , nrtuse ,                            &
826
 
   iphas  , ivar   , isou   , ipp    ,                            &
827
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
828
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
829
 
   icepdc , icetsm , itypsm(1,ivar)  ,                            &
830
 
   idevel , ituser , ia     ,                                     &
831
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
832
 
   dt     , rtp    , rtpa   , propce , propfa , propfb ,          &
833
 
   coefa  , coefb  , grdvit , produc ,grarox , graroy , graroz ,  &
834
 
   ckupdc , smacel(1,ivar)  , smacel(1,ipriph),                   &
835
 
   viscf  , viscb  ,                                              &
836
 
   tslagr ,                                                       &
837
 
   dam    , xam    , drtp   , smbr   , rovsdt ,                   &
838
 
   w1     , w2     , w3     , w4     ,                            &
839
 
   w5     , w6     , w7     , w8     , w9     ,                   &
840
 
   rdevel , rtuser , ra     )
841
 
 
842
 
#endif
843
 
 
844
 
!===============================================================================
845
 
! 6. CLIPPING
846
 
!===============================================================================
847
 
 
848
 
iclip  = 2
849
 
call clprij                                                       &
850
 
!==========
851
 
 ( ncelet , ncel   , nvar   , nphas  ,                            &
852
 
   iphas  , iclip  ,                                              &
853
 
   propce , rtpa   , rtp    )
854
 
 
855
 
 
856
 
!--------
857
 
! FORMATS
858
 
!--------
859
 
 
860
 
#if defined(_CS_LANG_FR)
861
 
 
862
 
 1000 format(/,                                                   &
863
 
'   ** PHASE ',I4,' RESOLUTION DU Rij-EPSILON LRR             ',/,&
864
 
'      ------------------------------------------             ',/)
865
 
 1001 format(/,                                                   &
866
 
'   ** PHASE ',I4,' RESOLUTION DU Rij-EPSILON SSG             ',/,&
867
 
'      ------------------------------------------             ',/)
868
 
 
869
 
#else
870
 
 
871
 
 1000 format(/,                                                   &
872
 
'   ** PHASE ',I4,' SOLVING Rij-EPSILON LRR'                   ,/,&
873
 
'      ------------------------------------'                   ,/)
874
 
 1001 format(/,                                                   &
875
 
'   ** PHASE ',I4,' SOLVING Rij-EPSILON SSG'                   ,/,&
876
 
'      ------------------------------------'                   ,/)
877
 
 
878
 
#endif
879
 
 
880
 
!----
881
 
! FIN
882
 
!----
883
 
 
884
 
return
885
 
 
886
 
end subroutine