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

« back to all changes in this revision

Viewing changes to src/base/modini.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
 
49
44
!            --- tableau de travail
50
45
!===============================================================================
51
46
 
 
47
!===============================================================================
 
48
! Module files
 
49
!===============================================================================
 
50
 
 
51
use paramx
 
52
use cstnum
 
53
use dimens
 
54
use numvar
 
55
use optcal
 
56
use cstphy
 
57
use entsor
 
58
use albase
 
59
use alstru
 
60
use cplsat
 
61
 
 
62
!===============================================================================
 
63
 
52
64
implicit none
53
65
 
54
 
!===============================================================================
55
 
! Common blocks
56
 
!===============================================================================
57
 
 
58
 
include "paramx.h"
59
 
include "cstnum.h"
60
 
include "dimens.h"
61
 
include "numvar.h"
62
 
include "optcal.h"
63
 
include "cstphy.h"
64
 
include "entsor.h"
65
 
include "albase.h"
66
 
include "alstru.h"
67
 
include "cplsat.h"
68
 
 
69
 
!===============================================================================
70
 
 
71
66
! Arguments
72
67
 
73
68
 
74
69
! Local variables
75
70
 
76
 
integer          ii, jj, ivar, iphas, iok, iest, imom, ikw
 
71
integer          ii, jj, ivar, iok, iest, imom, ikw
77
72
integer          icompt, ipp, nbccou, nn
78
73
integer          nscacp, iscal
79
74
double precision relxsp
114
109
    ichrvr(ii) = 1
115
110
  endif
116
111
enddo
117
 
do iphas = 1, nphas
118
 
  ipp = ipppro(ipproc(irom(iphas)))
119
 
  if(                       ichrvr(ipp).eq.-999) ichrvr(ipp) = 1
120
 
  ipp = ipppro(ipproc(ivisct(iphas)))
121
 
  if( (iturb(iphas).eq.10 .or. itytur(iphas).eq.2                 &
122
 
       .or. iturb(iphas).eq.50 .or. iturb(iphas).eq.60)           &
123
 
       .and.ichrvr(ipp).eq.-999) ichrvr(ipp) = 1
124
 
  if (idtvar.lt.0) then
125
 
    ichrvr(ipppro(ipproc(icour(iphas)))) = 0
126
 
    ichrvr(ipppro(ipproc(ifour(iphas)))) = 0
 
112
ipp = ipppro(ipproc(irom))
 
113
if(                       ichrvr(ipp).eq.-999) ichrvr(ipp) = 1
 
114
ipp = ipppro(ipproc(ivisct))
 
115
if( (iturb.eq.10 .or. itytur.eq.2                 &
 
116
     .or. itytur.eq.5 .or. iturb.eq.60            &
 
117
     .or. iturb.eq.70 )                                  &
 
118
     .and.ichrvr(ipp).eq.-999) ichrvr(ipp) = 1
 
119
if (idtvar.lt.0) then
 
120
  ichrvr(ipppro(ipproc(icour))) = 0
 
121
  ichrvr(ipppro(ipproc(ifour))) = 0
 
122
endif
 
123
do iest = 1, nestmx
 
124
  if(iescal(iest).gt.0) then
 
125
    ipp = ipppro(ipproc(iestim(iest)))
 
126
    if(                     ichrvr(ipp).eq.-999) ichrvr(ipp) = 1
127
127
  endif
128
 
  do iest = 1, nestmx
129
 
    if(iescal(iest,iphas).gt.0) then
130
 
      ipp = ipppro(ipproc(iestim(iest,iphas)))
131
 
      if(                     ichrvr(ipp).eq.-999) ichrvr(ipp) = 1
132
 
    endif
133
 
  enddo
134
128
enddo
135
129
if(idtvar.eq.2.and.ichrvr(ippdt).eq.-999) ichrvr(ippdt) = 1
136
130
if(ipucou.ne.1) then
164
158
do ii = 2, nvppmx
165
159
  if(ichrvr(ii).eq.1) icompt = icompt+1
166
160
enddo
167
 
if(icompt.eq.0) ntchr = -1
168
 
 
169
161
 
170
162
!---> sorties historiques ?
171
163
!      Si une valeur non modifiee par l'utilisateur (=-999)
190
182
  ihisvr(ippty,1) = 0
191
183
  ihisvr(ipptz,1) = 0
192
184
endif
193
 
do iphas = 1, nphas
194
 
  ipp = ipppro(ipproc(ivisct(iphas)))
195
 
  if( (iturb(iphas).eq.10 .or. itytur(iphas).eq.2                 &
196
 
       .or. iturb(iphas).eq.50 .or. iturb(iphas).eq.60)           &
197
 
       .and.ihisvr(ipp,1).eq.-999) ihisvr(ipp,1) = -1
198
 
  if (idtvar.lt.0) then
199
 
    ihisvr(ipppro(ipproc(icour(iphas))),1) = 0
200
 
    ihisvr(ipppro(ipproc(ifour(iphas))),1) = 0
201
 
  endif
202
 
enddo
 
185
ipp = ipppro(ipproc(ivisct))
 
186
if( (iturb.eq.10 .or. itytur.eq.2                 &
 
187
     .or. itytur.eq.5 .or. iturb.eq.60            &
 
188
     .or. iturb.eq.70 )                                  &
 
189
     .and.ihisvr(ipp,1).eq.-999) ihisvr(ipp,1) = -1
 
190
if (idtvar.lt.0) then
 
191
  ihisvr(ipppro(ipproc(icour)),1) = 0
 
192
  ihisvr(ipppro(ipproc(ifour)),1) = 0
 
193
endif
203
194
if(nbmomt.gt.0) then
204
195
  do imom = 1, nbmomt
205
196
    ipp = ipppro(ipproc(icmome(imom)))
222
213
 
223
214
  if(icompt.eq.0.or.ncapt.eq.0) then
224
215
    nthist = -1
 
216
    frhist = -1.d0
 
217
  endif
 
218
endif
 
219
 
 
220
! Adapt the output frequency parameters according to the time scheme.
 
221
if (idtvar.lt.0.or.idtvar.eq.2) then
 
222
  frhist = -1.d0
 
223
else
 
224
  if (frhist > 0.d0) then
 
225
    nthist = -1
225
226
  endif
226
227
endif
227
228
 
228
229
! ---> Nom des variables
229
230
 
230
 
do iphas = 1, nphas
231
 
 
232
 
  IF(NOMVAR(IPPRTP(IPR   (IPHAS))) .EQ.' ') THEN
233
 
    WRITE(NOMVAR(IPPRTP(IPR   (IPHAS))),'(A6,I2.2)')'PresPh',IPHAS
234
 
  endif
235
 
  IF(NOMVAR(IPPRTP(IU    (IPHAS))) .EQ.' ') THEN
236
 
    WRITE(NOMVAR(IPPRTP(IU    (IPHAS))),'(A6,I2.2)')'VitesX',IPHAS
237
 
  endif
238
 
  IF(NOMVAR(IPPRTP(IV    (IPHAS))) .EQ.' ') THEN
239
 
    WRITE(NOMVAR(IPPRTP(IV    (IPHAS))),'(A6,I2.2)')'VitesY',IPHAS
240
 
  endif
241
 
  IF(NOMVAR(IPPRTP(IW    (IPHAS))) .EQ.' ') THEN
242
 
    WRITE(NOMVAR(IPPRTP(IW    (IPHAS))),'(A6,I2.2)')'VitesZ',IPHAS
243
 
  endif
244
 
  if(itytur(iphas).eq.2) then
245
 
    IF(NOMVAR(IPPRTP(IK    (IPHAS))) .EQ.' ') THEN
246
 
      WRITE(NOMVAR(IPPRTP(IK    (IPHAS))),'(A6,I2.2)')            &
247
 
                                                    'EnTurb',IPHAS
248
 
    endif
249
 
    IF(NOMVAR(IPPRTP(IEP   (IPHAS))) .EQ.' ') THEN
250
 
      WRITE(NOMVAR(IPPRTP(IEP   (IPHAS))),'(A6,I2.2)')            &
251
 
                                                    'Dissip',IPHAS
252
 
    endif
253
 
  elseif(itytur(iphas).eq.3) then
254
 
    IF(NOMVAR(IPPRTP(IR11  (IPHAS))) .EQ.' ') THEN
255
 
      WRITE(NOMVAR(IPPRTP(IR11  (IPHAS))),'(A6,I2.2)')            &
256
 
                                                    'R11pha',IPHAS
257
 
    endif
258
 
    IF(NOMVAR(IPPRTP(IR22  (IPHAS))) .EQ.' ') THEN
259
 
      WRITE(NOMVAR(IPPRTP(IR22  (IPHAS))),'(A6,I2.2)')            &
260
 
                                                    'R22pha',IPHAS
261
 
    endif
262
 
    IF(NOMVAR(IPPRTP(IR33  (IPHAS))) .EQ.' ') THEN
263
 
      WRITE(NOMVAR(IPPRTP(IR33  (IPHAS))),'(A6,I2.2)')            &
264
 
                                                    'R33pha',IPHAS
265
 
    endif
266
 
    IF(NOMVAR(IPPRTP(IR12  (IPHAS))) .EQ.' ') THEN
267
 
      WRITE(NOMVAR(IPPRTP(IR12  (IPHAS))),'(A6,I2.2)')            &
268
 
                                                    'R12pha',IPHAS
269
 
    endif
270
 
    IF(NOMVAR(IPPRTP(IR13  (IPHAS))) .EQ.' ') THEN
271
 
      WRITE(NOMVAR(IPPRTP(IR13  (IPHAS))),'(A6,I2.2)')            &
272
 
                                                    'R13pha',IPHAS
273
 
    endif
274
 
    IF(NOMVAR(IPPRTP(IR23  (IPHAS))) .EQ.' ') THEN
275
 
      WRITE(NOMVAR(IPPRTP(IR23  (IPHAS))),'(A6,I2.2)')            &
276
 
                                                    'R23pha',IPHAS
277
 
    endif
278
 
    IF(NOMVAR(IPPRTP(IEP   (IPHAS))) .EQ.' ') THEN
279
 
      WRITE(NOMVAR(IPPRTP(IEP   (IPHAS))),'(A6,I2.2)')            &
280
 
                                                    'Dissip',IPHAS
281
 
    endif
282
 
  elseif(iturb(iphas).eq.50) then
283
 
    IF(NOMVAR(IPPRTP(IK    (IPHAS))) .EQ.' ') THEN
284
 
      WRITE(NOMVAR(IPPRTP(IK    (IPHAS))),'(A6,I2.2)')            &
285
 
                                                    'EnTurb',IPHAS
286
 
    endif
287
 
    IF(NOMVAR(IPPRTP(IEP   (IPHAS))) .EQ.' ') THEN
288
 
      WRITE(NOMVAR(IPPRTP(IEP   (IPHAS))),'(A6,I2.2)')            &
289
 
                                                    'Dissip',IPHAS
290
 
    endif
291
 
    IF(NOMVAR(IPPRTP(IPHI  (IPHAS))) .EQ.' ') THEN
292
 
      WRITE(NOMVAR(IPPRTP(IPHI  (IPHAS))),'(A6,I2.2)')            &
293
 
                                                    'phipha',IPHAS
294
 
    endif
295
 
    IF(NOMVAR(IPPRTP(IFB   (IPHAS))) .EQ.' ') THEN
296
 
      WRITE(NOMVAR(IPPRTP(IFB   (IPHAS))),'(A6,I2.2)')            &
297
 
                                                    'fbarre',IPHAS
298
 
    endif
299
 
  elseif(iturb(iphas).eq.60) then
300
 
    IF(NOMVAR(IPPRTP(IK    (IPHAS))) .EQ.' ') THEN
301
 
      WRITE(NOMVAR(IPPRTP(IK    (IPHAS))),'(A6,I2.2)')            &
302
 
                                                    'EnTurb',IPHAS
303
 
    endif
304
 
    IF(NOMVAR(IPPRTP(IOMG  (IPHAS))) .EQ.' ') THEN
305
 
      WRITE(NOMVAR(IPPRTP(IOMG  (IPHAS))),'(A5,I2.2)')            &
306
 
                                                    'Omega',IPHAS
307
 
    endif
308
 
  endif
309
 
 
310
 
  IF(NOMVAR(IPPPRO(IPPROC(IROM  (IPHAS)))) .EQ.' ') THEN
311
 
    WRITE(NOMVAR(IPPPRO(IPPROC(IROM  (IPHAS)))),'(A6,I2.2)')      &
312
 
                                                    'MasVol',IPHAS
313
 
  endif
314
 
  IF(NOMVAR(IPPPRO(IPPROC(IVISCT(IPHAS)))) .EQ.' ') THEN
315
 
    WRITE(NOMVAR(IPPPRO(IPPROC(IVISCT(IPHAS)))),'(A6,I2.2)')      &
316
 
                                                    'VisTur',IPHAS
317
 
  endif
318
 
  IF(NOMVAR(IPPPRO(IPPROC(IVISCL(IPHAS)))) .EQ.' ') THEN
319
 
    WRITE(NOMVAR(IPPPRO(IPPROC(IVISCL(IPHAS)))),'(A6,I2.2)')      &
320
 
                                                    'VisMol',IPHAS
321
 
  endif
322
 
  if (ismago(iphas).gt.0) then
323
 
    IF(NOMVAR(IPPPRO(IPPROC(ISMAGO(IPHAS)))) .EQ.' ') THEN
324
 
      WRITE(NOMVAR(IPPPRO(IPPROC(ISMAGO(IPHAS)))),'(A6,I2.2)')    &
325
 
                                                    'Csdyn2',IPHAS
326
 
    endif
327
 
  endif
328
 
  if(icp   (iphas).gt.0) then
329
 
    IF(NOMVAR(IPPPRO(IPPROC(ICP   (IPHAS)))) .EQ.' ') THEN
330
 
      WRITE(NOMVAR(IPPPRO(IPPROC(ICP   (IPHAS)))),'(A6,I2.2)')    &
331
 
                                                    'ChalSp',IPHAS
332
 
    endif
333
 
  endif
334
 
  if(iescal(iespre,iphas).gt.0) then
335
 
    ipp = ipppro(ipproc(iestim(iespre,iphas)))
336
 
    IF(NOMVAR(IPP) .EQ.' ') THEN
337
 
      WRITE(NOMVAR(IPP),'(A5,I1,I2.2)')                           &
338
 
                             'EsPre',IESCAL(IESPRE,IPHAS),IPHAS
339
 
    endif
340
 
  endif
341
 
  if(iescal(iesder,iphas).gt.0) then
342
 
    ipp = ipppro(ipproc(iestim(iesder,iphas)))
343
 
    IF(NOMVAR(IPP) .EQ.' ') THEN
344
 
      WRITE(NOMVAR(IPP),'(A5,I1,I2.2)')                           &
345
 
                             'EsDer',IESCAL(IESDER,IPHAS),IPHAS
346
 
    endif
347
 
  endif
348
 
  if(iescal(iescor,iphas).gt.0) then
349
 
    ipp = ipppro(ipproc(iestim(iescor,iphas)))
350
 
    IF(NOMVAR(IPP) .EQ.' ') THEN
351
 
      WRITE(NOMVAR(IPP),'(A5,I1,I2.2)')                           &
352
 
                             'EsCor',IESCAL(IESCOR,IPHAS),IPHAS
353
 
    endif
354
 
  endif
355
 
  if(iescal(iestot,iphas).gt.0) then
356
 
    ipp = ipppro(ipproc(iestim(iestot,iphas)))
357
 
    IF(NOMVAR(IPP) .EQ.' ') THEN
358
 
      WRITE(NOMVAR(IPP),'(A5,I1,I2.2)')                           &
359
 
                             'EsTot',IESCAL(IESTOT,IPHAS),IPHAS
360
 
    endif
361
 
  endif
362
 
 
363
 
enddo
 
231
IF(NOMVAR(IPPRTP(IPR   )) .EQ.' ') THEN
 
232
  NOMVAR(IPPRTP(IPR   )) = 'Pres'
 
233
endif
 
234
IF(NOMVAR(IPPRTP(IU    )) .EQ.' ') THEN
 
235
  NOMVAR(IPPRTP(IU    )) = 'VitesX'
 
236
endif
 
237
IF(NOMVAR(IPPRTP(IV    )) .EQ.' ') THEN
 
238
  NOMVAR(IPPRTP(IV    )) = 'VitesY'
 
239
endif
 
240
IF(NOMVAR(IPPRTP(IW    )) .EQ.' ') THEN
 
241
  NOMVAR(IPPRTP(IW    )) = 'VitesZ'
 
242
endif
 
243
if(itytur.eq.2) then
 
244
  IF(NOMVAR(IPPRTP(IK    )) .EQ.' ') THEN
 
245
    NOMVAR(IPPRTP(IK    )) = 'EnTurb'
 
246
  endif
 
247
  IF(NOMVAR(IPPRTP(IEP   )) .EQ.' ') THEN
 
248
    NOMVAR(IPPRTP(IEP   )) = 'Dissip'
 
249
  endif
 
250
elseif(itytur.eq.3) then
 
251
  IF(NOMVAR(IPPRTP(IR11  )) .EQ.' ') THEN
 
252
    NOMVAR(IPPRTP(IR11  )) =  'R11'
 
253
  endif
 
254
  IF(NOMVAR(IPPRTP(IR22  )) .EQ.' ') THEN
 
255
    NOMVAR(IPPRTP(IR22  )) = 'R22'
 
256
  endif
 
257
  IF(NOMVAR(IPPRTP(IR33  )) .EQ.' ') THEN
 
258
    NOMVAR(IPPRTP(IR33  )) = 'R33'
 
259
  endif
 
260
  IF(NOMVAR(IPPRTP(IR12  )) .EQ.' ') THEN
 
261
    NOMVAR(IPPRTP(IR12  )) = 'R12'
 
262
  endif
 
263
  IF(NOMVAR(IPPRTP(IR13  )) .EQ.' ') THEN
 
264
    NOMVAR(IPPRTP(IR13  )) = 'R13'
 
265
  endif
 
266
  IF(NOMVAR(IPPRTP(IR23  )) .EQ.' ') THEN
 
267
    NOMVAR(IPPRTP(IR23  )) = 'R23'
 
268
  endif
 
269
  IF(NOMVAR(IPPRTP(IEP   )) .EQ.' ') THEN
 
270
    NOMVAR(IPPRTP(IEP   )) = 'Dissip'
 
271
  endif
 
272
elseif(itytur.eq.5) then
 
273
  IF(NOMVAR(IPPRTP(IK    )) .EQ.' ') THEN
 
274
    NOMVAR(IPPRTP(IK    )) = 'EnTurb'
 
275
  endif
 
276
  IF(NOMVAR(IPPRTP(IEP   )) .EQ.' ') THEN
 
277
    NOMVAR(IPPRTP(IEP   )) = 'Dissip'
 
278
  endif
 
279
  IF(NOMVAR(IPPRTP(IPHI  )) .EQ.' ') THEN
 
280
    NOMVAR(IPPRTP(IPHI  )) = 'phi'
 
281
  endif
 
282
  if(iturb.eq.50) then
 
283
    IF(NOMVAR(IPPRTP(IFB   )) .EQ.' ') THEN
 
284
      NOMVAR(IPPRTP(IFB   )) = 'fbarre'
 
285
    endif
 
286
  elseif(iturb.eq.51) then
 
287
    IF(NOMVAR(IPPRTP(IAL   )) .EQ.' ') THEN
 
288
      NOMVAR(IPPRTP(IAL   )) = 'Alpha'
 
289
    endif
 
290
  endif
 
291
elseif(iturb.eq.60) then
 
292
  IF(NOMVAR(IPPRTP(IK    )) .EQ.' ') THEN
 
293
    NOMVAR(IPPRTP(IK    )) = 'EnTurb'
 
294
  endif
 
295
  IF(NOMVAR(IPPRTP(IOMG  )) .EQ.' ') THEN
 
296
    NOMVAR(IPPRTP(IOMG  )) = 'Omega'
 
297
  endif
 
298
elseif(iturb.eq.70) then
 
299
  IF(NOMVAR(IPPRTP(INUSA )) .EQ.' ') THEN
 
300
    NOMVAR(IPPRTP(INUSA )) = 'NuTild'
 
301
  endif
 
302
endif
 
303
 
 
304
IF(NOMVAR(IPPPRO(IPPROC(IROM  ))) .EQ.' ') THEN
 
305
  NOMVAR(IPPPRO(IPPROC(IROM  ))) = 'MasVol'
 
306
endif
 
307
IF(NOMVAR(IPPPRO(IPPROC(IVISCT))) .EQ.' ') THEN
 
308
  NOMVAR(IPPPRO(IPPROC(IVISCT))) = 'VisTur'
 
309
endif
 
310
IF(NOMVAR(IPPPRO(IPPROC(IVISCL))) .EQ.' ') THEN
 
311
  NOMVAR(IPPPRO(IPPROC(IVISCL))) = 'VisMol'
 
312
endif
 
313
if (ismago.gt.0) then
 
314
  IF(NOMVAR(IPPPRO(IPPROC(ISMAGO))) .EQ.' ') THEN
 
315
    NOMVAR(IPPPRO(IPPROC(ISMAGO))) = 'Csdyn2'
 
316
  endif
 
317
endif
 
318
if(icp   .gt.0) then
 
319
  IF(NOMVAR(IPPPRO(IPPROC(ICP   ))) .EQ.' ') THEN
 
320
    NOMVAR(IPPPRO(IPPROC(ICP   ))) = 'ChalSp'
 
321
  endif
 
322
endif
 
323
if(iescal(iespre).gt.0) then
 
324
  ipp = ipppro(ipproc(iestim(iespre)))
 
325
  IF(NOMVAR(IPP) .EQ.' ') THEN
 
326
    WRITE(NOMVAR(IPP),'(A5,I1)') 'EsPre',IESCAL(IESPRE)
 
327
  endif
 
328
endif
 
329
if(iescal(iesder).gt.0) then
 
330
  ipp = ipppro(ipproc(iestim(iesder)))
 
331
  IF(NOMVAR(IPP) .EQ.' ') THEN
 
332
    WRITE(NOMVAR(IPP),'(A5,I1)') 'EsDer',IESCAL(IESDER)
 
333
  endif
 
334
endif
 
335
if(iescal(iescor).gt.0) then
 
336
  ipp = ipppro(ipproc(iestim(iescor)))
 
337
  IF(NOMVAR(IPP) .EQ.' ') THEN
 
338
    WRITE(NOMVAR(IPP),'(A5,I1)') 'EsCor',IESCAL(IESCOR)
 
339
  endif
 
340
endif
 
341
if(iescal(iestot).gt.0) then
 
342
  ipp = ipppro(ipproc(iestim(iestot)))
 
343
  IF(NOMVAR(IPP) .EQ.' ') THEN
 
344
    WRITE(NOMVAR(IPP),'(A5,I1)') 'EsTot',IESCAL(IESTOT)
 
345
  endif
 
346
endif
364
347
 
365
348
do jj = 1, nscaus
366
349
  ii = jj
427
410
 
428
411
! ---> Sorties listing
429
412
 
430
 
do iphas = 1, nphas
431
 
  ipp = ipppro(ipproc(irom  (iphas)))
432
 
  if(irovar(iphas).eq.1.and.ilisvr(ipp).eq.-999) ilisvr(ipp) = 1
433
 
  ipp = ipppro(ipproc(ivisct(iphas)))
434
 
  if( (iturb(iphas).eq.10 .or. itytur(iphas).eq.2                 &
435
 
       .or. iturb(iphas).eq.50 .or. iturb(iphas).eq.60)           &
436
 
       .and.ilisvr(ipp).eq.-999) ilisvr(ipp) = 1
437
 
  ipp = ipppro(ipproc(icour(iphas)))
438
 
  if (ilisvr(ipp).eq.-999 .or. idtvar.lt.0) ilisvr(ipp) = 0
439
 
  ipp = ipppro(ipproc(ifour(iphas)))
440
 
  if (ilisvr(ipp).eq.-999 .or. idtvar.lt.0) ilisvr(ipp) = 0
441
 
  if(iescal(iespre,iphas).gt.0) then
442
 
    ipp = ipppro(ipproc(iestim(iespre,iphas)))
443
 
    if(                     ilisvr(ipp).eq.-999) ilisvr(ipp) = 1
444
 
  endif
445
 
  if(iescal(iesder,iphas).gt.0) then
446
 
    ipp = ipppro(ipproc(iestim(iesder,iphas)))
447
 
    if(                     ilisvr(ipp).eq.-999) ilisvr(ipp) = 1
448
 
  endif
449
 
  if(iescal(iescor,iphas).gt.0) then
450
 
    ipp = ipppro(ipproc(iestim(iescor,iphas)))
451
 
    if(                     ilisvr(ipp).eq.-999) ilisvr(ipp) = 1
452
 
  endif
453
 
  if(iescal(iestot,iphas).gt.0) then
454
 
    ipp = ipppro(ipproc(iestim(iestot,iphas)))
455
 
    if(                     ilisvr(ipp).eq.-999) ilisvr(ipp) = 1
456
 
  endif
457
 
enddo
 
413
ipp = ipppro(ipproc(irom  ))
 
414
if(irovar.eq.1.and.ilisvr(ipp).eq.-999) ilisvr(ipp) = 1
 
415
ipp = ipppro(ipproc(ivisct))
 
416
if( (iturb.eq.10 .or. itytur.eq.2                 &
 
417
     .or. itytur.eq.5 .or. iturb.eq.60            &
 
418
     .or. iturb.eq.70 )                                  &
 
419
     .and.ilisvr(ipp).eq.-999) ilisvr(ipp) = 1
 
420
if (inusa .gt. 0) then
 
421
  ipp = ipppro(ipproc(inusa))
 
422
  if(iturb.eq.70.and.ilisvr(ipp).eq.-999) ilisvr(ipp) = 1
 
423
endif
 
424
ipp = ipppro(ipproc(icour))
 
425
if (ilisvr(ipp).eq.-999 .or. idtvar.lt.0) ilisvr(ipp) = 0
 
426
ipp = ipppro(ipproc(ifour))
 
427
if (ilisvr(ipp).eq.-999 .or. idtvar.lt.0) ilisvr(ipp) = 0
 
428
if(iescal(iespre).gt.0) then
 
429
  ipp = ipppro(ipproc(iestim(iespre)))
 
430
  if(                     ilisvr(ipp).eq.-999) ilisvr(ipp) = 1
 
431
endif
 
432
if(iescal(iesder).gt.0) then
 
433
  ipp = ipppro(ipproc(iestim(iesder)))
 
434
  if(                     ilisvr(ipp).eq.-999) ilisvr(ipp) = 1
 
435
endif
 
436
if(iescal(iescor).gt.0) then
 
437
  ipp = ipppro(ipproc(iestim(iescor)))
 
438
  if(                     ilisvr(ipp).eq.-999) ilisvr(ipp) = 1
 
439
endif
 
440
if(iescal(iestot).gt.0) then
 
441
  ipp = ipppro(ipproc(iestim(iestot)))
 
442
  if(                     ilisvr(ipp).eq.-999) ilisvr(ipp) = 1
 
443
endif
458
444
 
459
445
if(nbmomt.gt.0) then
460
446
  do imom = 1, nbmomt
496
482
! 3. OPTIONS DU CALCUL : TABLEAUX DE optcal.h
497
483
!===============================================================================
498
484
 
 
485
! ---> restart
 
486
 
 
487
call indsui(isuite)
 
488
!==========
 
489
 
499
490
! ---> Schema en temps
500
491
 
501
 
 
502
 
do iphas = 1, nphas
503
 
 
504
492
!   -- Flux de masse
505
 
  if(abs(thetfl(iphas)+999.d0).gt.epzero) then
506
 
    write(nfecra,1001) iphas,istmpf(iphas)
507
 
    iok = iok + 1
508
 
  elseif(istmpf(iphas).eq.0) then
509
 
    thetfl(iphas) = 0.d0
510
 
  elseif(istmpf(iphas).eq.2) then
511
 
    thetfl(iphas) = 0.5d0
512
 
  endif
 
493
if(abs(thetfl+999.d0).gt.epzero) then
 
494
  write(nfecra,1001) istmpf
 
495
  iok = iok + 1
 
496
elseif(istmpf.eq.0) then
 
497
  thetfl = 0.d0
 
498
elseif(istmpf.eq.2) then
 
499
  thetfl = 0.5d0
 
500
endif
513
501
 
514
502
!    -- Proprietes physiques
515
 
  if(abs(thetro(iphas)+999.d0).gt.epzero) then
516
 
    WRITE(NFECRA,1011) IPHAS,'IROEXT',IROEXT(IPHAS),'THETRO'
517
 
    iok = iok + 1
518
 
  elseif(iroext(iphas).eq.0) then
519
 
    thetro(iphas) = 0.0d0
520
 
  elseif(iroext(iphas).eq.1) then
521
 
    thetro(iphas) = 0.5d0
522
 
  elseif(iroext(iphas).eq.2) then
523
 
    thetro(iphas) = 1.d0
524
 
  endif
525
 
  if(abs(thetvi(iphas)+999.d0).gt.epzero) then
526
 
    WRITE(NFECRA,1011) IPHAS,'IVIEXT',IVIEXT(IPHAS),'THETVI'
527
 
    iok = iok + 1
528
 
  elseif(iviext(iphas).eq.0) then
529
 
    thetvi(iphas) = 0.0d0
530
 
  elseif(iviext(iphas).eq.1) then
531
 
    thetvi(iphas) = 0.5d0
532
 
  elseif(iviext(iphas).eq.2) then
533
 
    thetvi(iphas) = 1.d0
534
 
  endif
535
 
  if(abs(thetcp(iphas)+999.d0).gt.epzero) then
536
 
    WRITE(NFECRA,1011) IPHAS,'ICPEXT',ICPEXT(IPHAS),'THETCP'
537
 
    iok = iok + 1
538
 
  elseif(icpext(iphas).eq.0) then
539
 
    thetcp(iphas) = 0.0d0
540
 
  elseif(icpext(iphas).eq.1) then
541
 
    thetcp(iphas) = 0.5d0
542
 
  elseif(icpext(iphas).eq.2) then
543
 
    thetcp(iphas) = 1.d0
544
 
  endif
 
503
if(abs(thetro+999.d0).gt.epzero) then
 
504
  WRITE(NFECRA,1011) 'IROEXT',IROEXT,'THETRO'
 
505
  iok = iok + 1
 
506
elseif(iroext.eq.0) then
 
507
  thetro = 0.0d0
 
508
elseif(iroext.eq.1) then
 
509
  thetro = 0.5d0
 
510
elseif(iroext.eq.2) then
 
511
  thetro = 1.d0
 
512
endif
 
513
if(abs(thetvi+999.d0).gt.epzero) then
 
514
  WRITE(NFECRA,1011) 'IVIEXT',IVIEXT,'THETVI'
 
515
  iok = iok + 1
 
516
elseif(iviext.eq.0) then
 
517
  thetvi = 0.0d0
 
518
elseif(iviext.eq.1) then
 
519
  thetvi = 0.5d0
 
520
elseif(iviext.eq.2) then
 
521
  thetvi = 1.d0
 
522
endif
 
523
if(abs(thetcp+999.d0).gt.epzero) then
 
524
  WRITE(NFECRA,1011) 'ICPEXT',ICPEXT,'THETCP'
 
525
  iok = iok + 1
 
526
elseif(icpext.eq.0) then
 
527
  thetcp = 0.0d0
 
528
elseif(icpext.eq.1) then
 
529
  thetcp = 0.5d0
 
530
elseif(icpext.eq.2) then
 
531
  thetcp = 1.d0
 
532
endif
545
533
 
546
534
!    -- Termes sources NS
547
 
  if(abs(thetsn(iphas)+999.d0).gt.epzero) then
548
 
    WRITE(NFECRA,1011) IPHAS,'ISNO2T',ISNO2T(IPHAS),'THETSN'
549
 
    iok = iok + 1
550
 
  elseif(isno2t(iphas).eq.1) then
551
 
    thetsn(iphas) = 0.5d0
552
 
  elseif(isno2t(iphas).eq.2) then
553
 
    thetsn(iphas) = 1.d0
554
 
  elseif(isno2t(iphas).eq.0) then
555
 
    thetsn(iphas) = 0.d0
556
 
  endif
 
535
if(abs(thetsn+999.d0).gt.epzero) then
 
536
  WRITE(NFECRA,1011) 'ISNO2T',ISNO2T,'THETSN'
 
537
  iok = iok + 1
 
538
elseif(isno2t.eq.1) then
 
539
  thetsn = 0.5d0
 
540
elseif(isno2t.eq.2) then
 
541
  thetsn = 1.d0
 
542
elseif(isno2t.eq.0) then
 
543
  thetsn = 0.d0
 
544
endif
557
545
 
558
546
!    -- Termes sources grandeurs turbulentes
559
 
  if(abs(thetst(iphas)+999.d0).gt.epzero) then
560
 
    WRITE(NFECRA,1011) IPHAS,'ISTO2T',ISTO2T(IPHAS),'THETST'
561
 
    iok = iok + 1
562
 
  elseif(isto2t(iphas).eq.1) then
563
 
    thetst(iphas) = 0.5d0
564
 
  elseif(isto2t(iphas).eq.2) then
565
 
    thetst(iphas) = 1.d0
566
 
  elseif(isto2t(iphas).eq.0) then
567
 
    thetst(iphas) = 0.d0
568
 
  endif
569
 
 
570
 
enddo
 
547
if(abs(thetst+999.d0).gt.epzero) then
 
548
  WRITE(NFECRA,1011) 'ISTO2T',ISTO2T,'THETST'
 
549
  iok = iok + 1
 
550
elseif(isto2t.eq.1) then
 
551
  thetst = 0.5d0
 
552
elseif(isto2t.eq.2) then
 
553
  thetst = 1.d0
 
554
elseif(isto2t.eq.0) then
 
555
  thetst = 0.d0
 
556
endif
571
557
 
572
558
do iscal = 1, nscal
573
559
!    -- Termes sources des scalaires
597
583
!     Ici on interdit que l'utilisateur fixe lui meme THETAV, par securite
598
584
!       mais on pourrait le laisser faire
599
585
!       (enlever le IOK, modifier le message et les tests dans verini)
600
 
do iphas = 1, nphas
601
586
 
602
587
!     Vitesse pression (la pression est prise sans interp)
603
 
  if(abs(thetav(iu (iphas))+999.d0).gt.epzero.or.                 &
604
 
     abs(thetav(iv (iphas))+999.d0).gt.epzero.or.                 &
605
 
     abs(thetav(iw (iphas))+999.d0).gt.epzero.or.                 &
606
 
     abs(thetav(ipr(iphas))+999.d0).gt.epzero) then
607
 
    WRITE(NFECRA,1031) IPHAS,'VITESSE-PRESSION ','THETAV'
608
 
    iok = iok + 1
609
 
  elseif(ischtp(iphas).eq.1) then
610
 
    thetav(iu (iphas)) = 1.d0
611
 
    thetav(iv (iphas)) = 1.d0
612
 
    thetav(iw (iphas)) = 1.d0
613
 
    thetav(ipr(iphas)) = 1.d0
614
 
  elseif(ischtp(iphas).eq.2) then
615
 
    thetav(iu (iphas)) = 0.5d0
616
 
    thetav(iv (iphas)) = 0.5d0
617
 
    thetav(iw (iphas)) = 0.5d0
618
 
    thetav(ipr(iphas)) = 1.d0
619
 
  endif
 
588
if(abs(thetav(iu )+999.d0).gt.epzero.or.                 &
 
589
     abs(thetav(iv )+999.d0).gt.epzero.or.                 &
 
590
     abs(thetav(iw )+999.d0).gt.epzero.or.                 &
 
591
     abs(thetav(ipr)+999.d0).gt.epzero) then
 
592
  WRITE(NFECRA,1031) 'VITESSE-PRESSION ','THETAV'
 
593
  iok = iok + 1
 
594
elseif(ischtp.eq.1) then
 
595
  thetav(iu ) = 1.d0
 
596
  thetav(iv ) = 1.d0
 
597
  thetav(iw ) = 1.d0
 
598
  thetav(ipr) = 1.d0
 
599
elseif(ischtp.eq.2) then
 
600
  thetav(iu ) = 0.5d0
 
601
  thetav(iv ) = 0.5d0
 
602
  thetav(iw ) = 0.5d0
 
603
  thetav(ipr) = 1.d0
 
604
endif
620
605
 
621
606
!     Turbulence (en k-eps : ordre 1)
622
 
  if(itytur(iphas).eq.2) then
623
 
    if(abs(thetav(ik (iphas))+999.d0).gt.epzero.or.               &
624
 
       abs(thetav(iep(iphas))+999.d0).gt.epzero) then
625
 
      WRITE(NFECRA,1031) IPHAS,'VARIABLES   K-EPS','THETAV'
626
 
      iok = iok + 1
627
 
    elseif(ischtp(iphas).eq.1) then
628
 
      thetav(ik (iphas)) = 1.d0
629
 
      thetav(iep(iphas)) = 1.d0
630
 
    elseif(ischtp(iphas).eq.2) then
631
 
!     pour le moment, on ne peut pas passer par ici (cf varpos)
632
 
      thetav(ik (iphas)) = 0.5d0
633
 
      thetav(iep(iphas)) = 0.5d0
634
 
    endif
635
 
  elseif(itytur(iphas).eq.3) then
636
 
    if(abs(thetav(ir11(iphas))+999.d0).gt.epzero.or.              &
637
 
       abs(thetav(ir22(iphas))+999.d0).gt.epzero.or.              &
638
 
       abs(thetav(ir33(iphas))+999.d0).gt.epzero.or.              &
639
 
       abs(thetav(ir12(iphas))+999.d0).gt.epzero.or.              &
640
 
       abs(thetav(ir13(iphas))+999.d0).gt.epzero.or.              &
641
 
       abs(thetav(ir23(iphas))+999.d0).gt.epzero.or.              &
642
 
       abs(thetav(iep (iphas))+999.d0).gt.epzero) then
643
 
      WRITE(NFECRA,1031) IPHAS,'VARIABLES  RIJ-EP','THETAV'
644
 
      iok = iok + 1
645
 
    elseif(ischtp(iphas).eq.1) then
646
 
      thetav(ir11(iphas)) = 1.d0
647
 
      thetav(ir22(iphas)) = 1.d0
648
 
      thetav(ir33(iphas)) = 1.d0
649
 
      thetav(ir12(iphas)) = 1.d0
650
 
      thetav(ir13(iphas)) = 1.d0
651
 
      thetav(ir23(iphas)) = 1.d0
652
 
      thetav(iep (iphas)) = 1.d0
653
 
    elseif(ischtp(iphas).eq.2) then
654
 
      thetav(ir11(iphas)) = 0.5d0
655
 
      thetav(ir22(iphas)) = 0.5d0
656
 
      thetav(ir33(iphas)) = 0.5d0
657
 
      thetav(ir12(iphas)) = 0.5d0
658
 
      thetav(ir13(iphas)) = 0.5d0
659
 
      thetav(ir23(iphas)) = 0.5d0
660
 
      thetav(iep (iphas)) = 0.5d0
661
 
    endif
662
 
  elseif(iturb(iphas).eq.50) then
663
 
    if(abs(thetav(ik  (iphas))+999.d0).gt.epzero.or.              &
664
 
       abs(thetav(iep (iphas))+999.d0).gt.epzero.or.              &
665
 
       abs(thetav(iphi(iphas))+999.d0).gt.epzero.or.              &
666
 
       abs(thetav(ifb (iphas))+999.d0).gt.epzero) then
667
 
      WRITE(NFECRA,1031) IPHAS,'VARIABLES     V2F','THETAV'
668
 
      iok = iok + 1
669
 
    elseif(ischtp(iphas).eq.1) then
670
 
      thetav(ik  (iphas)) = 1.d0
671
 
      thetav(iep (iphas)) = 1.d0
672
 
      thetav(iphi(iphas)) = 1.d0
673
 
      thetav(ifb (iphas)) = 1.d0
674
 
    elseif(ischtp(iphas).eq.2) then
675
 
!     pour le moment, on ne peut pas passer par ici (cf varpos)
676
 
      thetav(ik  (iphas)) = 0.5d0
677
 
      thetav(iep (iphas)) = 0.5d0
678
 
      thetav(iphi(iphas)) = 0.5d0
679
 
      thetav(ifb (iphas)) = 0.5d0
680
 
    endif
681
 
  elseif(iturb(iphas).eq.60) then
682
 
    if(abs(thetav(ik  (iphas))+999.d0).gt.epzero.or.              &
683
 
       abs(thetav(iomg(iphas))+999.d0).gt.epzero ) then
684
 
      WRITE(NFECRA,1031) IPHAS,'VARIABLES K-OMEGA','THETAV'
685
 
      iok = iok + 1
686
 
    elseif(ischtp(iphas).eq.1) then
687
 
      thetav(ik  (iphas)) = 1.d0
688
 
      thetav(iomg(iphas)) = 1.d0
689
 
    elseif(ischtp(iphas).eq.2) then
690
 
!     pour le moment, on ne peut pas passer par ici (cf varpos)
691
 
      thetav(ik  (iphas)) = 0.5d0
692
 
      thetav(iomg(iphas)) = 0.5d0
693
 
    endif
694
 
  endif
695
 
 
696
 
enddo
 
607
if(itytur.eq.2) then
 
608
  if(abs(thetav(ik )+999.d0).gt.epzero.or.               &
 
609
       abs(thetav(iep)+999.d0).gt.epzero) then
 
610
    WRITE(NFECRA,1031) 'VARIABLES   K-EPS','THETAV'
 
611
    iok = iok + 1
 
612
  elseif(ischtp.eq.1) then
 
613
    thetav(ik ) = 1.d0
 
614
    thetav(iep) = 1.d0
 
615
  elseif(ischtp.eq.2) then
 
616
    !     pour le moment, on ne peut pas passer par ici (cf varpos)
 
617
    thetav(ik ) = 0.5d0
 
618
    thetav(iep) = 0.5d0
 
619
  endif
 
620
elseif(itytur.eq.3) then
 
621
  if(abs(thetav(ir11)+999.d0).gt.epzero.or.              &
 
622
       abs(thetav(ir22)+999.d0).gt.epzero.or.              &
 
623
       abs(thetav(ir33)+999.d0).gt.epzero.or.              &
 
624
       abs(thetav(ir12)+999.d0).gt.epzero.or.              &
 
625
       abs(thetav(ir13)+999.d0).gt.epzero.or.              &
 
626
       abs(thetav(ir23)+999.d0).gt.epzero.or.              &
 
627
       abs(thetav(iep )+999.d0).gt.epzero) then
 
628
    WRITE(NFECRA,1031) 'VARIABLES  RIJ-EP','THETAV'
 
629
    iok = iok + 1
 
630
  elseif(ischtp.eq.1) then
 
631
    thetav(ir11) = 1.d0
 
632
    thetav(ir22) = 1.d0
 
633
    thetav(ir33) = 1.d0
 
634
    thetav(ir12) = 1.d0
 
635
    thetav(ir13) = 1.d0
 
636
    thetav(ir23) = 1.d0
 
637
    thetav(iep ) = 1.d0
 
638
  elseif(ischtp.eq.2) then
 
639
    thetav(ir11) = 0.5d0
 
640
    thetav(ir22) = 0.5d0
 
641
    thetav(ir33) = 0.5d0
 
642
    thetav(ir12) = 0.5d0
 
643
    thetav(ir13) = 0.5d0
 
644
    thetav(ir23) = 0.5d0
 
645
    thetav(iep ) = 0.5d0
 
646
  endif
 
647
elseif(iturb.eq.50) then
 
648
  if(abs(thetav(ik  )+999.d0).gt.epzero.or.              &
 
649
       abs(thetav(iep )+999.d0).gt.epzero.or.              &
 
650
       abs(thetav(iphi)+999.d0).gt.epzero.or.              &
 
651
       abs(thetav(ifb )+999.d0).gt.epzero) then
 
652
    WRITE(NFECRA,1031) 'VARIABLES     V2F','THETAV'
 
653
    iok = iok + 1
 
654
  elseif(ischtp.eq.1) then
 
655
    thetav(ik  ) = 1.d0
 
656
    thetav(iep ) = 1.d0
 
657
    thetav(iphi) = 1.d0
 
658
    thetav(ifb ) = 1.d0
 
659
  elseif(ischtp.eq.2) then
 
660
    !     pour le moment, on ne peut pas passer par ici (cf varpos)
 
661
    thetav(ik  ) = 0.5d0
 
662
    thetav(iep ) = 0.5d0
 
663
    thetav(iphi) = 0.5d0
 
664
    thetav(ifb ) = 0.5d0
 
665
  endif
 
666
elseif(iturb.eq.51) then
 
667
  if(abs(thetav(ik  )+999.d0).gt.epzero.or.              &
 
668
       abs(thetav(iep )+999.d0).gt.epzero.or.              &
 
669
       abs(thetav(iphi)+999.d0).gt.epzero.or.              &
 
670
       abs(thetav(ial )+999.d0).gt.epzero) then
 
671
    WRITE(NFECRA,1031) 'VARIABLES BL-V2/K','THETAV'
 
672
    iok = iok + 1
 
673
  elseif(ischtp.eq.1) then
 
674
    thetav(ik  ) = 1.d0
 
675
    thetav(iep ) = 1.d0
 
676
    thetav(iphi) = 1.d0
 
677
    thetav(ial ) = 1.d0
 
678
  elseif(ischtp.eq.2) then
 
679
    !     pour le moment, on ne peut pas passer par ici (cf varpos)
 
680
    thetav(ik  ) = 0.5d0
 
681
    thetav(iep ) = 0.5d0
 
682
    thetav(iphi) = 0.5d0
 
683
    thetav(ial ) = 0.5d0
 
684
  endif
 
685
elseif(iturb.eq.60) then
 
686
  if(abs(thetav(ik  )+999.d0).gt.epzero.or.              &
 
687
       abs(thetav(iomg)+999.d0).gt.epzero ) then
 
688
    WRITE(NFECRA,1031) 'VARIABLES K-OMEGA','THETAV'
 
689
    iok = iok + 1
 
690
  elseif(ischtp.eq.1) then
 
691
    thetav(ik  ) = 1.d0
 
692
    thetav(iomg) = 1.d0
 
693
  elseif(ischtp.eq.2) then
 
694
    !     pour le moment, on ne peut pas passer par ici (cf varpos)
 
695
    thetav(ik  ) = 0.5d0
 
696
    thetav(iomg) = 0.5d0
 
697
  endif
 
698
elseif(iturb.eq.70) then
 
699
  if(abs(thetav(inusa)+999.d0).gt.epzero) then
 
700
    WRITE(NFECRA,1031) 'VARIABLE NU_tilde de SA','THETAV'
 
701
    iok = iok + 1
 
702
  elseif(ischtp.eq.1) then
 
703
    thetav(inusa) = 1.d0
 
704
  elseif(ischtp.eq.2) then
 
705
    !     pour le moment, on ne peut pas passer par ici (cf varpos)
 
706
    thetav(inusa) = 0.5d0
 
707
  endif
 
708
endif
697
709
 
698
710
!     Scalaires
699
711
do iscal = 1, nscal
700
 
  iphas = iphsca(iscal)
701
712
  ivar  = isca(iscal)
702
713
  if(abs(thetav(ivar)+999.d0).gt.epzero) then
703
 
    WRITE(NFECRA,1041) IPHAS,'SCALAIRE',ISCAL,'THETAV'
 
714
    WRITE(NFECRA,1041) 'SCALAIRE',ISCAL,'THETAV'
704
715
    iok = iok + 1
705
 
  elseif(ischtp(iphas).eq.1) then
 
716
  elseif(ischtp.eq.1) then
706
717
    thetav(ivar) = 1.d0
707
 
  elseif(ischtp(iphas).eq.2) then
 
718
  elseif(ischtp.eq.2) then
708
719
    thetav(ivar) = 0.5d0
709
720
  endif
710
721
enddo
711
722
 
712
723
!     Vitesse de maillage en ALE
713
724
if (iale.eq.1) then
714
 
  iphas = 1
715
725
  if(abs(thetav(iuma)+999.d0).gt.epzero.or.                       &
716
726
     abs(thetav(ivma)+999.d0).gt.epzero.or.                       &
717
727
     abs(thetav(iwma)+999.d0).gt.epzero) then
718
728
    WRITE(NFECRA,1032) 'THETAV'
719
729
    iok = iok + 1
720
 
  elseif(ischtp(iphas).eq.1) then
 
730
  elseif(ischtp.eq.1) then
721
731
    thetav(iuma) = 1.d0
722
732
    thetav(ivma) = 1.d0
723
733
    thetav(iwma) = 1.d0
724
 
  elseif(ischtp(iphas).eq.2) then
 
734
  elseif(ischtp.eq.2) then
725
735
!     pour le moment, on ne peut pas passer par ici (cf varpos)
726
736
    thetav(iuma) = 0.5d0
727
737
    thetav(ivma) = 0.5d0
734
744
!        On impose 1 (ie sans) pour la vitesse en LES
735
745
!                  0 (ie avec) sinon
736
746
 
737
 
do iphas = 1, nphas
738
 
  if(itytur(iphas).eq.4) then
739
 
    ii = iu(iphas)
740
 
    if(isstpc(ii).eq.-999) isstpc(ii) = 1
741
 
    ii = iv(iphas)
742
 
    if(isstpc(ii).eq.-999) isstpc(ii) = 1
743
 
    ii = iw(iphas)
744
 
    if(isstpc(ii).eq.-999) isstpc(ii) = 1
745
 
    do jj = 1, nscal
746
 
      ii = isca(jj)
747
 
      if(isstpc(ii).eq.-999) isstpc(ii) = 0
748
 
    enddo
749
 
  endif
750
 
enddo
 
747
if(itytur.eq.4) then
 
748
  ii = iu
 
749
  if(isstpc(ii).eq.-999) isstpc(ii) = 1
 
750
  ii = iv
 
751
  if(isstpc(ii).eq.-999) isstpc(ii) = 1
 
752
  ii = iw
 
753
  if(isstpc(ii).eq.-999) isstpc(ii) = 1
 
754
  do jj = 1, nscal
 
755
    ii = isca(jj)
 
756
    if(isstpc(ii).eq.-999) isstpc(ii) = 0
 
757
  enddo
 
758
endif
751
759
 
752
760
do ii = 1, nvarmx
753
761
  if (isstpc(ii).eq.-999) then
762
770
!                  0 (ie upwind pur) pour le reste
763
771
!   (en particulier, en L.E.S. toutes les variables sont donc en centre)
764
772
 
765
 
do iphas = 1, nphas
766
 
  ii = iu(iphas)
767
 
  if(abs(blencv(ii)+999.d0).lt.epzero) blencv(ii) = 1.d0
768
 
  ii = iv(iphas)
769
 
  if(abs(blencv(ii)+999.d0).lt.epzero) blencv(ii) = 1.d0
770
 
  ii = iw(iphas)
771
 
  if(abs(blencv(ii)+999.d0).lt.epzero) blencv(ii) = 1.d0
772
 
enddo
 
773
ii = iu
 
774
if(abs(blencv(ii)+999.d0).lt.epzero) blencv(ii) = 1.d0
 
775
ii = iv
 
776
if(abs(blencv(ii)+999.d0).lt.epzero) blencv(ii) = 1.d0
 
777
ii = iw
 
778
if(abs(blencv(ii)+999.d0).lt.epzero) blencv(ii) = 1.d0
773
779
do jj = 1, nscaus
774
780
  ii = isca(jj)
775
781
  if(abs(blencv(ii)+999.d0).lt.epzero) blencv(ii) = 1.d0
797
803
!                  on initialise EPSILO a 1.D-5
798
804
!     Attention aux tests dans verini
799
805
 
800
 
do iphas = 1, nphas
801
 
  if(ischtp(iphas).eq.2) then
802
 
    ii = ipr(iphas)
803
 
    if(nswrsm(ii).eq.-999) nswrsm(ii) = 5
804
 
    if(abs(epsrsm(ii)+999.d0).lt.epzero) epsrsm(ii) = 1.d-5
805
 
    if(abs(epsilo(ii)+999.d0).lt.epzero) epsilo(ii) = 1.d-5
806
 
    ii = iu(iphas)
807
 
    if(nswrsm(ii).eq.-999) nswrsm(ii) = 10
808
 
    if(abs(epsrsm(ii)+999.d0).lt.epzero) epsrsm(ii) = 1.d-5
809
 
    if(abs(epsilo(ii)+999.d0).lt.epzero) epsilo(ii) = 1.d-5
810
 
    ii = iv(iphas)
811
 
    if(nswrsm(ii).eq.-999) nswrsm(ii) = 10
812
 
    if(abs(epsrsm(ii)+999.d0).lt.epzero) epsrsm(ii) = 1.d-5
813
 
    if(abs(epsilo(ii)+999.d0).lt.epzero) epsilo(ii) = 1.d-5
814
 
    ii = iw(iphas)
815
 
    if(nswrsm(ii).eq.-999) nswrsm(ii) = 10
816
 
    if(abs(epsrsm(ii)+999.d0).lt.epzero) epsrsm(ii) = 1.d-5
817
 
    if(abs(epsilo(ii)+999.d0).lt.epzero) epsilo(ii) = 1.d-5
818
 
    do jj = 1, nscal
819
 
      ii = isca(jj)
820
 
      if(nswrsm(ii).eq.-999) nswrsm(ii) = 10
821
 
      if(abs(epsrsm(ii)+999.d0).lt.epzero) epsrsm(ii) = 1.d-5
822
 
      if(abs(epsilo(ii)+999.d0).lt.epzero) epsilo(ii) = 1.d-5
823
 
    enddo
824
 
  endif
825
 
  ii = ipr(iphas)
826
 
  if(nswrsm(ii).eq.-999) nswrsm(ii) = 2
827
 
enddo
 
806
if(ischtp.eq.2) then
 
807
  ii = ipr
 
808
  if(nswrsm(ii).eq.-999) nswrsm(ii) = 5
 
809
  if(abs(epsrsm(ii)+999.d0).lt.epzero) epsrsm(ii) = 1.d-5
 
810
  if(abs(epsilo(ii)+999.d0).lt.epzero) epsilo(ii) = 1.d-5
 
811
  ii = iu
 
812
  if(nswrsm(ii).eq.-999) nswrsm(ii) = 10
 
813
  if(abs(epsrsm(ii)+999.d0).lt.epzero) epsrsm(ii) = 1.d-5
 
814
  if(abs(epsilo(ii)+999.d0).lt.epzero) epsilo(ii) = 1.d-5
 
815
  ii = iv
 
816
  if(nswrsm(ii).eq.-999) nswrsm(ii) = 10
 
817
  if(abs(epsrsm(ii)+999.d0).lt.epzero) epsrsm(ii) = 1.d-5
 
818
  if(abs(epsilo(ii)+999.d0).lt.epzero) epsilo(ii) = 1.d-5
 
819
  ii = iw
 
820
  if(nswrsm(ii).eq.-999) nswrsm(ii) = 10
 
821
  if(abs(epsrsm(ii)+999.d0).lt.epzero) epsrsm(ii) = 1.d-5
 
822
  if(abs(epsilo(ii)+999.d0).lt.epzero) epsilo(ii) = 1.d-5
 
823
  do jj = 1, nscal
 
824
    ii = isca(jj)
 
825
    if(nswrsm(ii).eq.-999) nswrsm(ii) = 10
 
826
    if(abs(epsrsm(ii)+999.d0).lt.epzero) epsrsm(ii) = 1.d-5
 
827
    if(abs(epsilo(ii)+999.d0).lt.epzero) epsilo(ii) = 1.d-5
 
828
  enddo
 
829
endif
 
830
ii = ipr
 
831
if(nswrsm(ii).eq.-999) nswrsm(ii) = 2
828
832
 
829
833
do ii = 1, nvarmx
830
834
  if (nswrsm(ii).eq.-999) nswrsm(ii) = 1
871
875
  dtmax = 1.0d3*dtref
872
876
endif
873
877
 
874
 
do iphas = 1, nphas
875
 
 
876
878
!     Ici, ce n'est pas grave pour le moment,
877
879
!      etant entendu que ces coefs ne servent pas
878
880
!      s'ils servaient, attention dans le cas a plusieurs phases avec
879
881
!      une seule pression : celle ci prend le coef de la derniere phase
880
 
  cdtvar(iv (iphas)) = cdtvar(iu(iphas))
881
 
  cdtvar(iw (iphas)) = cdtvar(iu(iphas))
882
 
  cdtvar(ipr(iphas)) = cdtvar(iu(iphas))
883
 
 
884
 
  if(itytur(iphas).eq.2) then
885
 
    cdtvar(iep (iphas)) = cdtvar(ik  (iphas))
886
 
  elseif(itytur(iphas).eq.3) then
887
 
    cdtvar(ir22(iphas)) = cdtvar(ir11(iphas))
888
 
    cdtvar(ir33(iphas)) = cdtvar(ir11(iphas))
889
 
    cdtvar(ir12(iphas)) = cdtvar(ir11(iphas))
890
 
    cdtvar(ir13(iphas)) = cdtvar(ir11(iphas))
891
 
    cdtvar(ir23(iphas)) = cdtvar(ir11(iphas))
892
 
    cdtvar(iep (iphas)) = cdtvar(ir11(iphas))
893
 
  elseif(iturb(iphas).eq.50) then
894
 
    cdtvar(iep (iphas)) = cdtvar(ik  (iphas))
895
 
 
896
 
    cdtvar(iphi(iphas)) = cdtvar(ik  (iphas))
897
 
!     CDTVAR(IFB) est en fait inutile car pas de temps dans l'eq de f_barre
898
 
    cdtvar(ifb (iphas)) = cdtvar(ik  (iphas))
899
 
  elseif(iturb(iphas).eq.60) then
900
 
    cdtvar(iomg(iphas)) = cdtvar(ik  (iphas))
 
882
cdtvar(iv ) = cdtvar(iu)
 
883
cdtvar(iw ) = cdtvar(iu)
 
884
cdtvar(ipr) = cdtvar(iu)
 
885
 
 
886
if(itytur.eq.2) then
 
887
  cdtvar(iep ) = cdtvar(ik  )
 
888
elseif(itytur.eq.3) then
 
889
  cdtvar(ir22) = cdtvar(ir11)
 
890
  cdtvar(ir33) = cdtvar(ir11)
 
891
  cdtvar(ir12) = cdtvar(ir11)
 
892
  cdtvar(ir13) = cdtvar(ir11)
 
893
  cdtvar(ir23) = cdtvar(ir11)
 
894
  cdtvar(iep ) = cdtvar(ir11)
 
895
elseif(itytur.eq.5) then
 
896
  cdtvar(iep ) = cdtvar(ik  )
 
897
  cdtvar(iphi) = cdtvar(ik  )
 
898
!     CDTVAR(IFB/IAL) est en fait inutile car pas de temps dans
 
899
!     l'eq de f_barre/alpha
 
900
  if(iturb.eq.50) then
 
901
    cdtvar(ifb ) = cdtvar(ik  )
 
902
  elseif(iturb.eq.51) then
 
903
    cdtvar(ial ) = cdtvar(ik  )
901
904
  endif
902
 
 
903
 
enddo
 
905
elseif(iturb.eq.60) then
 
906
  cdtvar(iomg) = cdtvar(ik  )
 
907
elseif(iturb.eq.70) then
 
908
  ! cdtvar est � 1.0 par defaut dans iniini.f90
 
909
  cdtvar(inusa)= cdtvar(inusa)
 
910
endif
904
911
 
905
912
! ---> IDEUCH, YPLULI
906
 
!      En laminaire, longueur de melange et LES, une echelle de vitesse
 
913
!      En laminaire, longueur de melange, Spalar-Allmaras et LES,
 
914
!      une echelle de vitesse.
907
915
!      Sinon, 2 echelles, sauf si l'utilisateur choisit 1 echelle.
908
916
!      On a initialise IDEUCH a -999 pour voir si l'utilisateur essaye
909
917
!        de choisir deux echelles quand ce n'est pas possible et le
910
918
!        prevenir dans la section verification.
911
919
 
912
 
do iphas = 1, nphas
913
 
  if(ideuch(iphas).eq.-999) then
914
 
    if(iturb(iphas).eq. 0.or.                                     &
915
 
       iturb(iphas).eq.10.or.                                     &
916
 
       itytur(iphas).eq.4 ) then
917
 
      ideuch(iphas) = 0
918
 
    else
919
 
      ideuch(iphas) = 1
920
 
    endif
921
 
  endif
922
 
!     Pour YPLULI, 1/XKAPPA est la valeur qui assure la continuite de la derivee entre
923
 
!     la zone lineaire et la zone logarithmique. Dans le cas des lois de paroi invariantes,
924
 
!     on utilise la valeur de continuite du profil de vitesse, 10,88.
925
 
!     Pour la L    .E.S., on remet 10,88, afin d'eviter des clic/clac quand on est a la limite
926
 
!     (en modele a une echelle en effet, YPLULI=1/XKAPPA ne permet pas forcement de calculer
927
 
!      u* de maniere totalement satisfaisante)
928
 
  if (ypluli(iphas).lt.-grand) then
929
 
    if (ideuch(iphas).eq.2 .or. itytur(iphas).eq.4 ) then
930
 
      ypluli(iphas) = 10.88d0
931
 
    else
932
 
      ypluli(iphas) = 1.d0/xkappa
933
 
    endif
934
 
  endif
935
 
enddo
 
920
if(ideuch.eq.-999) then
 
921
  if(iturb.eq. 0.or.                                     &
 
922
       iturb.eq.10.or.                                     &
 
923
       itytur.eq.4.or.                                     &
 
924
       iturb.eq.70) then
 
925
    ideuch = 0
 
926
  else
 
927
    ideuch = 1
 
928
  endif
 
929
endif
 
930
 
 
931
! Pour YPLULI, 1/XKAPPA est la valeur qui assure la continuite de la derivee
 
932
! entre la zone lineaire et la zone logarithmique.
 
933
 
 
934
! Dans le cas des lois de paroi invariantes, on utilise la valeur de
 
935
! continuite du profil de vitesse, 10.88.
 
936
 
 
937
! Pour la LES, on remet 10.88, afin d'eviter des clic/clac quand on est a
 
938
! la limite (en modele a une echelle en effet, YPLULI=1/XKAPPA ne permet pas
 
939
! forcement de calculer u* de maniere totalement satisfaisante).
 
940
! Idem en Spalart-Allmaras.
 
941
 
 
942
if (ypluli.lt.-grand) then
 
943
  if (ideuch.eq.2 .or. itytur.eq.4 .or.           &
 
944
       iturb.eq.70    ) then
 
945
    ypluli = 10.88d0
 
946
  else
 
947
    ypluli = 1.d0/xkappa
 
948
  endif
 
949
endif
936
950
 
937
951
 
938
952
! ---> Van Driest
939
 
do iphas = 1, nphas
940
 
  if(idries(iphas).eq.-1) then
941
 
!   On met 1 en supposant qu'en periodicite ou parallele on utilise le
942
 
!     mode de calcul de la distance a la paroi qui les prend en charge
943
 
!     (ICDPAR=+/-1, valeur par defaut)
944
 
    if(iturb(iphas).eq.40) then
945
 
      idries(iphas) = 1
946
 
    elseif(iturb(iphas).eq.41) then
947
 
      idries(iphas) = 0
948
 
    elseif(iturb(iphas).eq.42) then
949
 
      idries(iphas) = 0
950
 
    endif
 
953
if(idries.eq.-1) then
 
954
  !   On met 1 en supposant qu'en periodicite ou parallele on utilise le
 
955
  !     mode de calcul de la distance a la paroi qui les prend en charge
 
956
  !     (ICDPAR=+/-1, valeur par defaut)
 
957
  if(iturb.eq.40) then
 
958
    idries = 1
 
959
  elseif(iturb.eq.41) then
 
960
    idries = 0
 
961
  elseif(iturb.eq.42) then
 
962
    idries = 0
951
963
  endif
952
 
enddo
 
964
endif
953
965
 
954
966
 
955
967
! ---> ICPSYR
984
996
!       Si l'utilisateur n'a pas couple de scalaire,
985
997
    if(nscacp.eq.0) then
986
998
 
987
 
!         On couple le scalaire temperature de la premiere phase
988
 
      do iphas = 1, nphas
989
 
        if(iscalt(iphas).gt.0.and.iscalt(iphas).le.nscal) then
990
 
          icpsyr(iscalt(iphas)) = 1
991
 
          goto 100
992
 
        endif
993
 
      enddo
 
999
!         On couple le scalaire temperature de la phase
 
1000
      if(iscalt.gt.0.and.iscalt.le.nscal) then
 
1001
        icpsyr(iscalt) = 1
 
1002
        goto 100
 
1003
      endif
994
1004
 100        continue
995
1005
 
996
1006
    endif
1027
1037
if(nscal.gt.0) then
1028
1038
  do ii = 1, nscal
1029
1039
    if(iscsth(ii).eq.-10)then
1030
 
      iphas = iphsca(ii)
1031
 
      if(ii.ne.iscalt(iphas)) then
 
1040
      if(ii.ne.iscalt) then
1032
1041
        iscsth(ii) = 0
1033
1042
      endif
1034
1043
    endif
1066
1075
!      il faut la distance a la paroi pour une suite propre, donc on initialise a 1 et
1067
1076
!      on avertit (dans verini).
1068
1077
ikw = 0
1069
 
do iphas = 1, nphas
1070
 
  if (iturb(iphas).eq.60) ikw = 1
1071
 
enddo
 
1078
if (iturb.eq.60) ikw = 1
1072
1079
if (icdpar.eq.-999) then
1073
1080
  icdpar = -1
1074
1081
  if (ikw.eq.1) icdpar = 1
1082
1089
!       (une seule phase ...)
1083
1090
 
1084
1091
ineedy = 0
1085
 
do iphas = 1, nphas
1086
 
  if((iturb(iphas).eq.30.and.irijec(iphas).eq.1).or.              &
1087
 
     (itytur(iphas).eq.4.and.idries(iphas).eq.1).or.              &
1088
 
      iturb(iphas).eq.60 ) then
1089
 
    ineedy = 1
1090
 
  endif
1091
 
enddo
 
1092
if((iturb.eq.30.and.irijec.eq.1).or.              &
 
1093
     (itytur.eq.4.and.idries.eq.1).or.              &
 
1094
     iturb.eq.60.or.iturb.eq.70      ) then
 
1095
  ineedy = 1
 
1096
endif
1092
1097
 
1093
1098
if (imrgra.eq.0 .or. imrgra.eq.4) then
1094
1099
  if (imligy.eq.-999) then
1102
1107
 
1103
1108
!     Warning : non initialise => comme la vitesse
1104
1109
if(iwarny.eq.-999) then
1105
 
  iwarny = iwarni(iu(1))
 
1110
  iwarny = iwarni(iu)
1106
1111
endif
1107
1112
 
1108
1113
 
1111
1116
!     sinon on le laisse a 1
1112
1117
!     Dans verini on bloquera le v2f et le k-eps prod lin si IKECOU.NE.0
1113
1118
!     On bloquera aussi le stationnaire si IKECOU.NE.0
1114
 
do iphas = 1, nphas
1115
 
  if (ikecou(iphas).eq.-999) then
1116
 
    if (idtvar.lt.0) then
1117
 
      ikecou(iphas) = 0
1118
 
    else if (iturb(iphas).eq.21 .or. iturb(iphas).eq.50           &
1119
 
        .or. iturb(iphas).eq.60 ) then
1120
 
      ikecou(iphas) = 0
1121
 
    else
1122
 
      ikecou(iphas) = 1
1123
 
    endif
 
1119
if (ikecou.eq.-999) then
 
1120
  if (idtvar.lt.0) then
 
1121
    ikecou = 0
 
1122
  else if (iturb.eq.21 .or. itytur.eq.5           &
 
1123
       .or. iturb.eq.60 ) then
 
1124
    ikecou = 0
 
1125
  else
 
1126
    ikecou = 1
1124
1127
  endif
1125
 
enddo
 
1128
endif
1126
1129
 
1127
1130
! ---> RELAXV
1128
1131
if (idtvar.lt.0) then
1129
1132
  relxsp = 1.d0-relxst
1130
1133
  if (relxsp.le.epzero) relxsp = relxst
1131
 
  do iphas = 1, nphas
1132
 
    if (abs(relaxv(ipr(iphas))+999.d0).le.epzero)                 &
1133
 
         relaxv(ipr(iphas)) = relxsp
1134
 
  enddo
 
1134
  if (abs(relaxv(ipr)+999.d0).le.epzero)                 &
 
1135
       relaxv(ipr) = relxsp
1135
1136
  do ii = 1, nvarmx
1136
1137
    if (abs(relaxv(ii)+999.d0).le.epzero) relaxv(ii) = relxst
1137
1138
  enddo
1138
1139
else
1139
 
  do iphas = 1, nphas
1140
 
    if ( ikecou(iphas).eq.0) then
1141
 
      if (itytur(iphas).eq.2 .or. itytur(iphas).eq.5) then
1142
 
        if (abs(relaxv(ik(iphas))+999.d0).lt.epzero)              &
1143
 
             relaxv(ik(iphas)) = 0.7d0
1144
 
        if (abs(relaxv(iep(iphas))+999.d0).lt.epzero)             &
1145
 
             relaxv(iep(iphas)) = 0.7d0
1146
 
      else if (itytur(iphas).eq.6) then
1147
 
        if (abs(relaxv(ik(iphas))+999.d0).lt.epzero)              &
1148
 
             relaxv(ik(iphas)) = 0.7d0
1149
 
        if (abs(relaxv(iomg(iphas))+999.d0).lt.epzero)            &
1150
 
             relaxv(iomg(iphas)) = 0.7d0
1151
 
      endif
1152
 
    endif
1153
 
    if (abs(relaxv(ipr(iphas))+999.d0).lt.epzero)                 &
1154
 
             relaxv(ipr(iphas)) = 1.d0
1155
 
  enddo
 
1140
  if ( ikecou.eq.0) then
 
1141
    if (itytur.eq.2 .or. itytur.eq.5) then
 
1142
      if (abs(relaxv(ik)+999.d0).lt.epzero)              &
 
1143
           relaxv(ik) = 0.7d0
 
1144
      if (abs(relaxv(iep)+999.d0).lt.epzero)             &
 
1145
           relaxv(iep) = 0.7d0
 
1146
    else if (itytur.eq.6) then
 
1147
      if (abs(relaxv(ik)+999.d0).lt.epzero)              &
 
1148
           relaxv(ik) = 0.7d0
 
1149
      if (abs(relaxv(iomg)+999.d0).lt.epzero)            &
 
1150
           relaxv(iomg) = 0.7d0
 
1151
    endif
 
1152
  endif
 
1153
  if(iturb.eq.70) then
 
1154
    if(abs(relaxv(inusa)+999.d0).lt.epzero) then
 
1155
      relaxv(inusa) = 1.D0
 
1156
    endif
 
1157
  endif
 
1158
  if (abs(relaxv(ipr)+999.d0).lt.epzero)                 &
 
1159
       relaxv(ipr) = 1.d0
1156
1160
endif
1157
1161
 
1158
1162
! ---> SPECIFIQUE STATIONNAIRE
1163
1167
  do ii = 1, nvarmx
1164
1168
    istat(ii) = 0
1165
1169
  enddo
1166
 
  do iphas = 1, nphas
1167
 
    arak(iphas) = arak(iphas)/max(relaxv(iu(iphas)),epzero)
1168
 
  enddo
 
1170
  arak = arak/max(relaxv(iu),epzero)
1169
1171
endif
1170
1172
 
1171
1173
! ---> INEEDF
1206
1208
enddo
1207
1209
 
1208
1210
 
1209
 
! ---> VISLS0 (IPHSCA, IVISLS ont ete verifies dans varpos)
 
1211
! ---> VISLS0 (IVISLS ont ete verifies dans varpos)
1210
1212
!      Pour les variances de fluctuations, les valeurs du tableau
1211
1213
!        precedent ne doivent pas avoir ete modifiees par l'utilisateur
1212
1214
!        Elles sont prises egales aux valeurs correspondantes pour le
1233
1235
!      a partir du moment ou il a specifie une coordonnee.
1234
1236
!      Pour les coordonnees non specifiees, on met 0.
1235
1237
 
1236
 
do iphas = 1, nphas
1237
 
  do ii = 1, 3
1238
 
    if (xyzp0(ii,iphas).gt.-0.5d0*rinfin) then
1239
 
      ixyzp0(iphas) = 1
1240
 
    else
1241
 
      xyzp0(ii,iphas) = 0.d0
1242
 
    endif
1243
 
  enddo
 
1238
do ii = 1, 3
 
1239
  if (xyzp0(ii).gt.-0.5d0*rinfin) then
 
1240
    ixyzp0 = 1
 
1241
  else
 
1242
    xyzp0(ii) = 0.d0
 
1243
  endif
1244
1244
enddo
1245
1245
 
1246
1246
! Vecteur rotation et matrice(s) associees
1249
1249
 
1250
1250
if (omgnrm.ge.epzero) then
1251
1251
 
1252
 
  ! Vecteur rotation norm�
 
1252
  ! Normalized rotation vector
1253
1253
 
1254
1254
  ux = omegax / omgnrm
1255
1255
  uy = omegay / omgnrm
1270
1270
  prot(2,3) = uy*uz
1271
1271
  prot(3,2) = prot(2,3)
1272
1272
 
1273
 
  ! Repr�sentation antisym�trique de Omega
 
1273
  ! Antisymetrc representation of Omega
1274
1274
 
1275
1275
  qrot(1,1) = 0.d0
1276
1276
  qrot(2,2) = 0.d0
1346
1346
! 7. PARAMETRES DE cplsat.h
1347
1347
!===============================================================================
1348
1348
 
1349
 
! R�cup�ration du nombre de couplage
 
1349
! Get coupling number
1350
1350
 
1351
1351
call nbccpl(nbrcpl)
1352
1352
!==========
1360
1360
    ! Maillage mobile
1361
1361
    if (icorio.eq.0) then
1362
1362
      imobil = 1
1363
 
      ichrmd = 1
 
1363
      call pstdfm
 
1364
      !==========
1364
1365
    endif
1365
1366
  endif
1366
1367
endif
1381
1382
'@                                                            ',/,&
1382
1383
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
1383
1384
'@    =========                                               ',/,&
1384
 
'@    PHASE ',   I10,' ISTMPF = ',   I10                       ,/,&
 
1385
'@    ISTMPF = ',   I10                                        ,/,&
1385
1386
'@    THETFL SERA INITIALISE AUTOMATIQUEMENT.                 ',/,&
1386
1387
'@    NE PAS LE MODIFIER DANS usini1.                         ',/,&
1387
1388
'@                                                            ',/,&
1397
1398
'@                                                            ',/,&
1398
1399
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
1399
1400
'@    =========                                               ',/,&
1400
 
'@    PHASE ',   I10,' ',A6,' = ',   I10                       ,/,&
 
1401
'@    ',A6,' = ',   I10                                        ,/,&
1401
1402
'@    ',A6,' SERA INITIALISE AUTOMATIQUEMENT.                 ',/,&
1402
1403
'@    NE PAS LE MODIFIER DANS usini1.                         ',/,&
1403
1404
'@                                                            ',/,&
1429
1430
'@                                                            ',/,&
1430
1431
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
1431
1432
'@    =========                                               ',/,&
1432
 
'@    PHASE ',   I10,' ',A17                                   ,/,&
 
1433
'@    ',A17                                                    ,/,&
1433
1434
'@    ',A6,' SERA INITIALISE AUTOMATIQUEMENT.                 ',/,&
1434
1435
'@    NE PAS LE MODIFIER DANS usini1.                         ',/,&
1435
1436
'@                                                            ',/,&
1461
1462
'@                                                            ',/,&
1462
1463
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
1463
1464
'@    =========                                               ',/,&
1464
 
'@    PHASE ',   I10,' ',A8,' ',I10                            ,/,&
 
1465
'@    ',A8,' ',I10                                             ,/,&
1465
1466
'@    ',A6,' SERA INITIALISE AUTOMATIQUEMENT.                 ',/,&
1466
1467
'@    NE PAS LE MODIFIER DANS usini1.                         ',/,&
1467
1468
'@                                                            ',/,&
1555
1556
'@                                                            ',/,&
1556
1557
'@ @@ WARNING: ABORT IN THE DATA SPECIFICATION                ',/,&
1557
1558
'@    ========                                                ',/,&
1558
 
'@    PHASE ',   I10,' ISTMPF = ',   I10                       ,/,&
 
1559
'@    ISTMPF = ',   I10                                        ,/,&
1559
1560
'@    THETFL WILL BE AUTOMATICALLY INITIALIZED.               ',/,&
1560
1561
'@    DO NOT MODIFY IT IN usini1.                             ',/,&
1561
1562
'@                                                            ',/,&
1571
1572
'@                                                            ',/,&
1572
1573
'@ @@ WARNING: ABORT IN THE DATA SPECIFICATION                ',/,&
1573
1574
'@    ========                                                ',/,&
1574
 
'@    PHASE ',   I10,' ',A6,' = ',   I10                       ,/,&
 
1575
'@    ',A6,' = ',   I10                                        ,/,&
1575
1576
'@    ',A6,' WILL BE INITIALIZED AUTOMATICALLY                ',/,&
1576
1577
'@    DO NOT MODIFY IT IN usini1.                             ',/,&
1577
1578
'@                                                            ',/,&
1603
1604
'@                                                            ',/,&
1604
1605
'@ @@ WARNING: ABORT IN THE DATA SPECIFICATION                ',/,&
1605
1606
'@    ========                                                ',/,&
1606
 
'@    PHASE ',   I10,' ',A17                                   ,/,&
 
1607
'@    ',A17                                                    ,/,&
1607
1608
'@    ',A6,' WILL BE INITIALIZED AUTOMATICALLY                ',/,&
1608
1609
'@    DO NOT MODIFY IT IN usini1.                             ',/,&
1609
1610
'@                                                            ',/,&
1635
1636
'@                                                            ',/,&
1636
1637
'@ @@ WARNING: ABORT IN THE DATA SPECIFICATION                ',/,&
1637
1638
'@    ========                                                ',/,&
1638
 
'@    PHASE ',   I10,' ',A8,' ',I10                            ,/,&
 
1639
'@    ',A8,' ',I10                                             ,/,&
1639
1640
'@    ',A6,' WILL BE INITIALIZED AUTOMATICALLY                ',/,&
1640
1641
'@    DO NOT MODIFY IT IN usini1.                             ',/,&
1641
1642
'@                                                            ',/,&