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

« back to all changes in this revision

Viewing changes to src/base/varpos.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
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
 
51
46
!            --- tableau de travail
52
47
!===============================================================================
53
48
 
 
49
!===============================================================================
 
50
! Module files
 
51
!===============================================================================
 
52
 
 
53
use paramx
 
54
use dimens
 
55
use numvar
 
56
use optcal
 
57
use cstphy
 
58
use cstnum
 
59
use entsor
 
60
use albase
 
61
use lagpar
 
62
use lagdim
 
63
use lagran
 
64
use parall
 
65
use ppppar
 
66
use ppthch
 
67
use coincl
 
68
use cpincl
 
69
use ppincl
 
70
use radiat
 
71
use ihmpre
 
72
use mesh
 
73
 
 
74
!===============================================================================
 
75
 
54
76
implicit none
55
77
 
56
 
!===============================================================================
57
 
! Common blocks
58
 
!===============================================================================
59
 
 
60
 
include "paramx.h"
61
 
include "dimens.h"
62
 
include "numvar.h"
63
 
include "optcal.h"
64
 
include "cstphy.h"
65
 
include "cstnum.h"
66
 
include "entsor.h"
67
 
include "albase.h"
68
 
include "parall.h"
69
 
include "lagpar.h"
70
 
include "lagdim.h"
71
 
include "lagran.h"
72
 
include "ppppar.h"
73
 
include "ppthch.h"
74
 
include "coincl.h"
75
 
include "cpincl.h"
76
 
include "ppincl.h"
77
 
include "radiat.h"
78
 
include "ihmpre.h"
79
 
 
80
 
!===============================================================================
81
 
 
82
78
! Arguments
83
79
 
84
80
integer       nmodpp
87
83
 
88
84
 
89
85
character     rubriq*64, cmoy4*4, cindfm*4
90
 
integer       ivar  , ipp   , iscal , iphas , iprop , iprofl
 
86
character     ficsui*32
 
87
integer       ivar  , ipp   , iscal , irphas , iprop , iprofl
91
88
integer       ii    , jj    , kk    , ll
92
89
integer       iok   , ippok , ipppst
93
90
integer       iflum , icondl
120
117
! 0. INITIALISATIONS
121
118
!===============================================================================
122
119
 
 
120
! Initialize variables to avoid compiler warnings
 
121
ippok = 0
 
122
 
123
123
ipass = ipass + 1
124
124
 
125
125
!     Nombre max pour les formats choisis
126
126
nfmtmo = 9999
127
127
!     Indefini a 4 caracteres
128
 
CINDFM = 'YYYY'
 
128
cindfm = 'YYYY'
129
129
 
130
130
!===============================================================================
131
 
! 1. PREMIER APPEL : VERIFICATION DU NOMBRE DE PHASES
 
131
! 1. PREMIER APPEL : CALCUL DE NSCAPP
 
132
!                    VERIFICATION DU NOMBRE DE SCALAIRES
 
133
!                    CONSTRUCTION DE ISCAPP
 
134
!                    CALCUL DE NSCAL
132
135
!                    RETURN
133
 
!===============================================================================
134
 
 
135
 
if(ipass.eq.1) then
136
 
 
137
 
  iok = 0
138
 
 
139
 
  if(nphas.le.0) then
140
 
    write(nfecra,5000) nphas
141
 
    iok = iok + 1
142
 
  endif
143
 
  if(nphas.gt.nphsmx) then
144
 
    write(nfecra,5001) nphas, nphsmx, nphas
145
 
    iok = iok + 1
146
 
  endif
147
 
 
148
 
  if(iok.ne.0) then
149
 
    call csexit (1)
150
 
    !==========
151
 
  endif
152
 
 
153
 
  return
154
 
 
155
 
endif
156
 
 
157
 
!===============================================================================
158
 
! 2. SECOND APPEL : CALCUL DE NSCAPP
159
 
!                   VERIFICATION DU NOMBRE DE SCALAIRES
160
 
!                   CONSTRUCTION DE ISCAPP
161
 
!                   CALCUL DE NSCAL
162
 
!                   RETURN
163
136
 
164
137
!  C'est juste avant ce second appel que les modeles de combustion
165
138
!    auront ete renseignes. C'est dans la section ci-dessous qu'on en
166
139
!    en deduira NSCAPP (avant meme les verifications).
167
140
!  A la sortie de cette section, NSCAL, NSCAUS et NSCAPP sont connus.
168
 
!  On renseignera egalement ici les valeurs de IPHSCA, ISCAVR, IVISLS
 
141
!  On renseignera egalement ici les valeurs de ISCAVR, IVISLS
169
142
!    pour les scalaires physiques particulieres en question.
170
143
!  On en profite aussi pour remplir ITYTUR puisque ITURB vient d'etre
171
144
!    defini.
172
145
!===============================================================================
173
146
 
174
 
if(ipass.eq.2) then
 
147
if(ipass.eq.1) then
175
148
 
176
149
! ---> Remplissage de ITYTUR
177
 
  do iphas = 1, nphas
178
 
    itytur(iphas) = iturb(iphas)/10
179
 
  enddo
 
150
  itytur = iturb/10
180
151
 
181
152
! ---> Coherence modele
182
153
!     Rq : ATTENTION il faudrait renforcer le blindage
282
253
 
283
254
 
284
255
!===============================================================================
285
 
! 3. TROISIEME APPEL : VERIFICATIONS ET
 
256
! 2. SECOND APPEL : VERIFICATIONS ET
286
257
!        POSITIONNEMENT DES VARIABLES  : IPR, IU ... ISCA, NVAR
287
258
!                       ET DES PROPRIETES PPALES
288
259
!===============================================================================
289
260
 
290
 
if(ipass.eq.3) then
291
 
 
292
 
 
293
 
! ---> 3.1 VERIFICATIONS
 
261
if(ipass.eq.2) then
 
262
 
 
263
 
 
264
! ---> 2.1 VERIFICATIONS
294
265
!      -----------------
295
266
 
296
267
  iok = 0
297
268
 
298
 
! ---  NPHAS et NSCAL ont deja ete verifies, mais on ne sait jamais.
299
 
 
300
 
  if(nphas.le.0) then
301
 
    write(nfecra,5000) nphas
302
 
    iok = iok + 1
303
 
  endif
304
 
  if(nphas.gt.nphsmx) then
305
 
    write(nfecra,5001) nphas, nphsmx, nphas
306
 
    iok = iok + 1
307
 
  endif
 
269
! ---  NSCAL a deja ete verifie, mais on ne sait jamais.
308
270
 
309
271
  if(nscal.lt.0) then
310
272
    write(nfecra,7010) nscal, nscaus, nscapp
315
277
    iok = iok + 1
316
278
  endif
317
279
 
318
 
! --- IPHSCA(ISCAL) doit etre compris entre 0 et NPHAS.
319
 
 
320
 
  if(nscaus.gt.0) then
321
 
    do ii = 1, nscaus
322
 
      iscal = ii
323
 
      if(iphsca(iscal).gt.nphas.or.iphsca(iscal).lt.0) then
324
 
        write(nfecra,7020) iscal, iscal, ii,ii,                   &
325
 
             iphsca(iscal), nphas
326
 
        iok = iok + 1
327
 
      endif
328
 
    enddo
329
 
  endif
330
 
  if(nscapp.gt.0) then
331
 
    do ii = 1, nscapp
332
 
      iscal = iscapp(ii)
333
 
      if(iphsca(iscal).gt.nphas.or.iphsca(iscal).lt.0) then
334
 
        write(nfecra,7021) iscal, iscal, ii,ii,                   &
335
 
             iphsca(iscal), nphas
336
 
        iok = iok + 1
337
 
      endif
338
 
    enddo
339
 
  endif
340
 
 
341
280
! --- ISCAVR(ISCAL) doit etre compris entre 0 et NSCAL.
342
281
 
343
282
  if(nscaus.gt.0) then
437
376
    enddo
438
377
  endif
439
378
 
440
 
! ---> IPHSCA
441
 
!      Pour les variances de fluctuations, les valeurs de IPHSCA
442
 
!        ne doivent pas avoir ete modifiees par l'utilisateur
443
 
!        Elles sont prises egales aux valeurs correspondantes
444
 
!        pour le scalaire associe.
445
 
 
446
 
  if(nscaus.gt.0) then
447
 
    do jj = 1, nscaus
448
 
      ii    = jj
449
 
      iscal = iscavr(ii)
450
 
      if(iscal.gt.0.and.iscal.le.nscal)then
451
 
        if(iphsca(ii).eq.0) then
452
 
          iphsca(ii) = iphsca(iscal)
453
 
        else
454
 
          ll = 0
455
 
          do kk = 1, nscaus
456
 
            if(       kk .eq.iscal) ll = kk
457
 
          enddo
458
 
          do kk = 1, nscapp
459
 
            if(iscapp(kk).eq.iscal) ll = -kk
460
 
          enddo
461
 
          if(ll.gt.0) then
462
 
            write(nfecra,7060)ii,                                 &
463
 
                 ii,jj,iscal,ll,jj,iscal,                         &
464
 
                 jj,iphsca(iscal)
465
 
          else
466
 
            write(nfecra,7061)ii,                                 &
467
 
                 ii,jj,iscal,-ll,jj,iscal,                        &
468
 
                 jj,iphsca(iscal)
469
 
          endif
470
 
          iok = iok + 1
471
 
        endif
472
 
      endif
473
 
    enddo
474
 
  endif
475
 
 
476
 
  if(nscapp.gt.0) then
477
 
    do jj = 1, nscapp
478
 
      ii    = iscapp(jj)
479
 
      iscal = iscavr(ii)
480
 
      if(iscal.gt.0.and.iscal.le.nscal)then
481
 
        if(iphsca(ii).eq.0) then
482
 
          iphsca(ii) = iphsca(iscal)
483
 
        else
484
 
          ll = 0
485
 
          do kk = 1, nscaus
486
 
            if(       kk .eq.iscal) ll = kk
487
 
          enddo
488
 
          do kk = 1, nscapp
489
 
            if(iscapp(kk).eq.iscal) ll = -kk
490
 
          enddo
491
 
          if(ll.gt.0) then
492
 
            write(nfecra,7062)ii,                                 &
493
 
                 ii,jj,iscal,ll,jj,iscal,                         &
494
 
                 jj,iphsca(iscal)
495
 
          else
496
 
            write(nfecra,7063)ii,                                 &
497
 
                 ii,jj,iscal,-ll,jj,iscal,                        &
498
 
                 jj,iphsca(iscal)
499
 
          endif
500
 
          iok = iok + 1
501
 
        endif
502
 
      endif
503
 
    enddo
504
 
  endif
505
379
 
506
380
! ---> VISCOSITE ALE
507
381
  if (iale.eq.1) then
517
391
  endif
518
392
 
519
393
 
520
 
! ---> 3.2 POSITIONNEMENT DES VARIABLES  : IPR, IU ... ISCA, NVAR
 
394
! ---> 2.2 POSITIONNEMENT DES VARIABLES  : IPR, IU ... ISCA, NVAR
521
395
!      --------------------------------
522
396
 
523
397
  ivar = 0
524
398
 
525
 
  do iphas = 1, nphas
526
 
 
527
 
! --- Pression : supposons ici qu'il n'y a qu'une pression
528
 
!       quelque soit le nombre de phases.
529
 
!     Le reste du code devrait se preter a l'extension, du fait
530
 
!       qu'il n'y a qu'ici qu'on fait cette hypothese (evidemment, il
531
 
!       faudrait ecrire un schema a deux pressions et remplacer navsto,
532
 
!       mais c'est un "detail"...relativement a ce qui nous occupe dans
533
 
!       le present sous-programme)
534
 
 
535
 
    if(iphas.eq.1) then
536
 
      ivar          = ivar + 1
537
 
      ipr   (iphas) = ivar
538
 
    else
539
 
      ipr   (iphas) = ipr(1)
540
 
    endif
541
 
 
542
 
! --- Vitesse
543
 
    ivar          = ivar + 1
544
 
    iu    (iphas) = ivar
545
 
    ivar          = ivar + 1
546
 
    iv    (iphas) = ivar
547
 
    ivar          = ivar + 1
548
 
    iw    (iphas) = ivar
549
 
 
550
 
! --- Turbulence
551
 
    if (itytur(iphas).eq.2) then
552
 
      ivar          = ivar + 1
553
 
      ik    (iphas) = ivar
554
 
      ivar          = ivar + 1
555
 
      iep   (iphas) = ivar
556
 
    elseif(itytur(iphas).eq.3) then
557
 
      ivar          = ivar + 1
558
 
      ir11  (iphas) = ivar
559
 
      ivar          = ivar + 1
560
 
      ir22  (iphas) = ivar
561
 
      ivar          = ivar + 1
562
 
      ir33  (iphas) = ivar
563
 
      ivar          = ivar + 1
564
 
      ir12  (iphas) = ivar
565
 
      ivar          = ivar + 1
566
 
      ir13  (iphas) = ivar
567
 
      ivar          = ivar + 1
568
 
      ir23  (iphas) = ivar
569
 
      ivar          = ivar + 1
570
 
      iep   (iphas) = ivar
571
 
    elseif(iturb(iphas).eq.50) then
572
 
      ivar          = ivar + 1
573
 
      ik    (iphas) = ivar
574
 
      ivar          = ivar + 1
575
 
      iep   (iphas) = ivar
576
 
      ivar          = ivar + 1
577
 
      iphi  (iphas) = ivar
578
 
      ivar          = ivar + 1
579
 
      ifb   (iphas) = ivar
580
 
    elseif(iturb(iphas).eq.60) then
581
 
      ivar          = ivar + 1
582
 
      ik    (iphas) = ivar
583
 
      ivar          = ivar + 1
584
 
      iomg  (iphas) = ivar
585
 
    endif
586
 
 
587
 
  enddo
 
399
  ! --- Pression : supposons ici qu'il n'y a qu'une pression
 
400
  !       quelque soit le nombre de phases.
 
401
  !     Le reste du code devrait se preter a l'extension, du fait
 
402
  !       qu'il n'y a qu'ici qu'on fait cette hypothese (evidemment, il
 
403
  !       faudrait ecrire un schema a deux pressions et remplacer navsto,
 
404
  !       mais c'est un "detail"...relativement a ce qui nous occupe dans
 
405
  !       le present sous-programme)
 
406
 
 
407
  ivar          = ivar + 1
 
408
  ipr    = ivar
 
409
 
 
410
  ! --- Vitesse
 
411
  ivar          = ivar + 1
 
412
  iu     = ivar
 
413
  ivar          = ivar + 1
 
414
  iv     = ivar
 
415
  ivar          = ivar + 1
 
416
  iw     = ivar
 
417
 
 
418
  ! --- Turbulence
 
419
  if (itytur.eq.2) then
 
420
    ivar          = ivar + 1
 
421
    ik     = ivar
 
422
    ivar          = ivar + 1
 
423
    iep    = ivar
 
424
  elseif(itytur.eq.3) then
 
425
    ivar          = ivar + 1
 
426
    ir11   = ivar
 
427
    ivar          = ivar + 1
 
428
    ir22   = ivar
 
429
    ivar          = ivar + 1
 
430
    ir33   = ivar
 
431
    ivar          = ivar + 1
 
432
    ir12   = ivar
 
433
    ivar          = ivar + 1
 
434
    ir13   = ivar
 
435
    ivar          = ivar + 1
 
436
    ir23   = ivar
 
437
    ivar          = ivar + 1
 
438
    iep    = ivar
 
439
  elseif(itytur.eq.5) then
 
440
    ivar          = ivar + 1
 
441
    ik     = ivar
 
442
    ivar          = ivar + 1
 
443
    iep    = ivar
 
444
    ivar          = ivar + 1
 
445
    iphi   = ivar
 
446
    if(iturb.eq.50) then
 
447
      ivar          = ivar + 1
 
448
      ifb    = ivar
 
449
    elseif(iturb.eq.51) then
 
450
      ivar          = ivar + 1
 
451
      ial    = ivar
 
452
    endif
 
453
  elseif(iturb.eq.60) then
 
454
    ivar          = ivar + 1
 
455
    ik     = ivar
 
456
    ivar          = ivar + 1
 
457
    iomg   = ivar
 
458
  elseif (iturb.eq.70) then
 
459
    ivar          = ivar + 1
 
460
    inusa  = ivar
 
461
  endif
588
462
 
589
463
! --- Scalaires
590
464
  if(nscapp.ge.1) then
625
499
 
626
500
! --- Maintenant on peut faire ceci :
627
501
 
628
 
  do iphas = 1, nphas
629
 
    istat (ipr(iphas)) = 0
630
 
    iconv (ipr(iphas)) = 0
631
 
    if (iturb(iphas).eq.50) then
632
 
      istat(ifb(iphas))  = 0
633
 
      iconv(ifb(iphas))  = 0
634
 
!     Pour fb, on sait qu'on a un terme diagonal, meme si ISTAT=0,
635
 
!       donc on ne decalera pas la diagonale
636
 
      idircl(ifb(iphas)) = 0
637
 
    endif
638
 
  enddo
 
502
  istat (ipr) = 0
 
503
  iconv (ipr) = 0
 
504
  if (iturb.eq.50) then
 
505
    istat(ifb)  = 0
 
506
    iconv(ifb)  = 0
 
507
    !     Pour fb, on sait qu'on a un terme diagonal, meme si ISTAT=0,
 
508
    !       donc on ne decalera pas la diagonale
 
509
    idircl(ifb) = 0
 
510
  elseif (iturb.eq.51) then
 
511
    istat(ial)  = 0
 
512
    iconv(ial)  = 0
 
513
    !     Pour alpha, on sait qu'on a un terme diagonal, meme si ISTAT=0,
 
514
    !       donc on ne decalera pas la diagonale
 
515
    idircl(ial) = 0
 
516
  endif
639
517
  if (iale.eq.1) then
640
518
    istat(iuma) = 0
641
519
    iconv(iuma) = 0
649
527
  endif
650
528
 
651
529
 
652
 
! ---> 3.3 POSITIONNEMENT DES PROPRIETES PRINCIPALES
 
530
! ---> 2.3 POSITIONNEMENT DES PROPRIETES PRINCIPALES
653
531
!      --------------------------------
654
532
 
655
533
! --- Numerotation des proprietes presentes ici
684
562
  iprop = 0
685
563
 
686
564
!   Proprietes des phases : proprietes toujours presentes
687
 
  do iphas = 1, nphas
688
 
    iprop         = iprop + 1
689
 
    irom  (iphas) = iprop
690
 
    iprop         = iprop + 1
691
 
    iviscl(iphas) = iprop
692
 
    iprop         = iprop + 1
693
 
    ivisct(iphas) = iprop
694
 
    iprop         = iprop + 1
695
 
    icour (iphas) = iprop
696
 
    iprop         = iprop + 1
697
 
    ifour (iphas) = iprop
698
 
  enddo
 
565
  iprop         = iprop + 1
 
566
  irom   = iprop
 
567
  iprop         = iprop + 1
 
568
  iviscl = iprop
 
569
  iprop         = iprop + 1
 
570
  ivisct = iprop
 
571
  iprop         = iprop + 1
 
572
  icour  = iprop
 
573
  iprop         = iprop + 1
 
574
  ifour  = iprop
699
575
 
700
576
!  Pression totale stockee dans IPRTOT, si on n'est pas en compressible
701
577
!  (sinon Ptot=P* !)
702
578
  if (ippmod(icompf).lt.0) then
703
 
    do iphas = 1, nphas
704
 
      if (iphas.eq.1) then
705
 
        iprop         = iprop + 1
706
 
        iprtot(1)     = iprop
707
 
      else
708
 
        iprtot(iphas) = iprtot(1)
709
 
      endif
710
 
    enddo
 
579
    iprop         = iprop + 1
 
580
    iprtot        = iprop
711
581
  endif
712
582
 
713
583
!  Proprietes des phases : CP s'il est variable
714
 
  do iphas = 1, nphas
715
 
    if(icp(iphas).ne.0) then
716
 
      iprop         = iprop + 1
717
 
      icp   (iphas) = iprop
718
 
    endif
719
 
  enddo
 
584
  if(icp.ne.0) then
 
585
    iprop         = iprop + 1
 
586
    icp    = iprop
 
587
  endif
720
588
 
721
589
!  Proprietes des phases : Cs^2 si on est en LES dynamique
722
 
  do iphas = 1, nphas
723
 
    if(iturb(iphas).eq.41) then
724
 
      iprop         = iprop + 1
725
 
      ismago(iphas) = iprop
726
 
    else
727
 
      ismago(iphas) = -1
728
 
    endif
729
 
  enddo
 
590
  if(iturb.eq.41) then
 
591
    iprop         = iprop + 1
 
592
    ismago = iprop
 
593
  else
 
594
    ismago = -1
 
595
  endif
730
596
 
731
597
!  Viscosite de maillage en ALE
732
598
  if (iale.eq.1) then
746
612
  endif
747
613
 
748
614
!   Proprietes des phases : estimateurs d'erreur
749
 
  do iphas = 1, nphas
750
 
    do iest = 1, nestmx
751
 
      iprop              = iprop + 1
752
 
      iestim(iest,iphas) = iprop
753
 
    enddo
 
615
  do iest = 1, nestmx
 
616
    iprop              = iprop + 1
 
617
    iestim(iest) = iprop
754
618
  enddo
755
619
 
756
 
 
757
620
!   Proprietes des scalaires : VISCLS si elle est variable
758
621
!     On utilisera IVISLS comme suit :
759
622
!       Pour le scalaire II
774
637
!   Proprietes des variables : flux de masse porteur
775
638
 
776
639
  iprofl = iprop
777
 
  do iphas = 1, nphas
778
 
    iprop               = iprop + 1
779
 
    if(iphas.eq.1) then
780
 
      ifluma(ipr (iphas)) = iprop
781
 
    endif
782
 
    ifluma(iu  (iphas)) = iprop
783
 
    ifluma(iv  (iphas)) = iprop
784
 
    ifluma(iw  (iphas)) = iprop
785
 
    if(itytur(iphas).eq.2) then
786
 
      ifluma(ik  (iphas)) = iprop
787
 
      ifluma(iep (iphas)) = iprop
788
 
    elseif(itytur(iphas).eq.3) then
789
 
      ifluma(ir11(iphas)) = iprop
790
 
      ifluma(ir22(iphas)) = iprop
791
 
      ifluma(ir33(iphas)) = iprop
792
 
      ifluma(ir12(iphas)) = iprop
793
 
      ifluma(ir13(iphas)) = iprop
794
 
      ifluma(ir23(iphas)) = iprop
795
 
      ifluma(iep (iphas)) = iprop
796
 
    elseif(iturb(iphas).eq.50) then
797
 
      ifluma(ik  (iphas)) = iprop
798
 
      ifluma(iep (iphas)) = iprop
799
 
      ifluma(iphi(iphas)) = iprop
800
 
      ifluma(ifb (iphas)) = iprop
801
 
    elseif(iturb(iphas).eq.60) then
802
 
      ifluma(ik  (iphas)) = iprop
803
 
      ifluma(iomg(iphas)) = iprop
804
 
    endif
805
 
  enddo
 
640
  iprop               = iprop + 1
 
641
  ifluma(ipr ) = iprop
 
642
  ifluma(iu  ) = iprop
 
643
  ifluma(iv  ) = iprop
 
644
  ifluma(iw  ) = iprop
 
645
  if(itytur.eq.2) then
 
646
    ifluma(ik  ) = iprop
 
647
    ifluma(iep ) = iprop
 
648
  elseif(itytur.eq.3) then
 
649
    ifluma(ir11) = iprop
 
650
    ifluma(ir22) = iprop
 
651
    ifluma(ir33) = iprop
 
652
    ifluma(ir12) = iprop
 
653
    ifluma(ir13) = iprop
 
654
    ifluma(ir23) = iprop
 
655
    ifluma(iep ) = iprop
 
656
  elseif(itytur.eq.5) then
 
657
    ifluma(ik  ) = iprop
 
658
    ifluma(iep ) = iprop
 
659
    ifluma(iphi) = iprop
 
660
    if(iturb.eq.50) then
 
661
      ifluma(ifb ) = iprop
 
662
    elseif(iturb.eq.51) then
 
663
      ifluma(ial ) = iprop
 
664
    endif
 
665
  elseif(iturb.eq.60) then
 
666
    ifluma(ik  ) = iprop
 
667
    ifluma(iomg) = iprop
 
668
  elseif(iturb.eq.70) then
 
669
    ifluma(inusa)= iprop
 
670
  endif
806
671
  do iscal = 1, nscal
807
 
    ifluma(isca(iscal)) = ifluma(iu(iphsca(iscal)))
 
672
    ifluma(isca(iscal)) = ifluma(iu)
808
673
  enddo
809
674
  if (iale.eq.1) then
810
 
    ifluma(iuma) = ifluma(ipr(1))
811
 
    ifluma(ivma) = ifluma(ipr(1))
812
 
    ifluma(iwma) = ifluma(ipr(1))
 
675
    ifluma(iuma) = ifluma(ipr)
 
676
    ifluma(ivma) = ifluma(ipr)
 
677
    ifluma(iwma) = ifluma(ipr)
813
678
  endif
814
679
!     Nombre total de flux de masse
815
680
!       IPROFL ressert plus bas.
856
721
!       imaginaire
857
722
 
858
723
  iprop = 0
859
 
  do iphas = 1, nphas
860
 
 
861
 
    iprop                 = iprop  + 1
862
 
    ipproc(irom  (iphas)) = iprop
863
 
    ipppst                = ipppst + 1
864
 
    ipppro(iprop)         = ipppst
865
 
    iprop                 = iprop  + 1
866
 
    ipproc(iviscl(iphas)) = iprop
867
 
    ipppst                = ipppst + 1
868
 
    ipppro(iprop)         = ipppst
869
 
    iprop                 = iprop  + 1
870
 
    ipproc(ivisct(iphas)) = iprop
871
 
    if (iturb(iphas).eq.0) then
872
 
      ipppro(iprop)         = 1
873
 
    else
874
 
      ipppst                = ipppst + 1
875
 
      ipppro(iprop)         = ipppst
876
 
    endif
877
 
    iprop                 = iprop  + 1
878
 
    ipproc(icour (iphas)) = iprop
879
 
    ipppst                = ipppst + 1
880
 
    ipppro(iprop)         = ipppst
881
 
    iprop                 = iprop  + 1
882
 
    ipproc(ifour (iphas)) = iprop
883
 
    ipppst                = ipppst + 1
884
 
    ipppro(iprop)         = ipppst
885
 
 
886
 
    if (ippmod(icompf).lt.0) then
887
 
      iprop                 = iprop  + 1
888
 
      ipproc(iprtot(iphas)) = iprop
889
 
      ipppst                = ipppst + 1
890
 
      ipppro(iprop)         = ipppst
891
 
    endif
892
 
 
893
 
    if(icp(iphas).gt.0) then
894
 
      iprop                 = iprop + 1
895
 
      ipproc(icp   (iphas)) = iprop
896
 
      ipppst                = ipppst + 1
897
 
      ipppro(iprop)         = ipppst
898
 
    endif
899
 
 
900
 
    if(ismago(iphas).ne.-1) then
901
 
      iprop                 = iprop  + 1
902
 
      ipproc(ismago(iphas)) = iprop
903
 
      ipppst                = ipppst + 1
904
 
      ipppro(iprop)         = ipppst
905
 
    endif
906
 
 
907
 
    if (iale.eq.1) then
908
 
      iprop             = iprop + 1
909
 
      ipproc(ivisma(1)) = iprop
910
 
      ipppst            = ipppst + 1
911
 
      ipppro(iprop)     = ipppst
912
 
      if (iortvm.eq.1) then
913
 
        iprop             = iprop + 1
914
 
        ipproc(ivisma(2)) = iprop
915
 
        ipppst            = ipppst + 1
916
 
        ipppro(iprop)     = ipppst
917
 
        iprop             = iprop + 1
918
 
        ipproc(ivisma(3)) = iprop
919
 
        ipppst            = ipppst + 1
920
 
        ipppro(iprop)     = ipppst
921
 
      endif
922
 
    endif
923
 
 
924
 
    do iest = 1, nestmx
925
 
      if(iescal(iest,iphas).gt.0) then
926
 
        iprop                      = iprop + 1
927
 
        ipproc(iestim(iest,iphas)) = iprop
928
 
        ipppst                     = ipppst + 1
929
 
        ipppro(iprop)              = ipppst
930
 
      endif
931
 
    enddo
932
 
 
 
724
 
 
725
  iprop                 = iprop  + 1
 
726
  ipproc(irom  ) = iprop
 
727
  ipppst                = ipppst + 1
 
728
  ipppro(iprop)         = ipppst
 
729
  iprop                 = iprop  + 1
 
730
  ipproc(iviscl) = iprop
 
731
  ipppst                = ipppst + 1
 
732
  ipppro(iprop)         = ipppst
 
733
  iprop                 = iprop  + 1
 
734
  ipproc(ivisct) = iprop
 
735
  if (iturb.eq.0) then
 
736
    ipppro(iprop)         = 1
 
737
  else
 
738
    ipppst                = ipppst + 1
 
739
    ipppro(iprop)         = ipppst
 
740
  endif
 
741
  iprop                 = iprop  + 1
 
742
  ipproc(icour ) = iprop
 
743
  ipppst                = ipppst + 1
 
744
  ipppro(iprop)         = ipppst
 
745
  iprop                 = iprop  + 1
 
746
  ipproc(ifour ) = iprop
 
747
  ipppst                = ipppst + 1
 
748
  ipppro(iprop)         = ipppst
 
749
 
 
750
  if (ippmod(icompf).lt.0) then
 
751
    iprop                 = iprop  + 1
 
752
    ipproc(iprtot) = iprop
 
753
    ipppst                = ipppst + 1
 
754
    ipppro(iprop)         = ipppst
 
755
  endif
 
756
 
 
757
  if(icp.gt.0) then
 
758
    iprop                 = iprop + 1
 
759
    ipproc(icp   ) = iprop
 
760
    ipppst                = ipppst + 1
 
761
    ipppro(iprop)         = ipppst
 
762
  endif
 
763
 
 
764
  if(ismago.ne.-1) then
 
765
    iprop                 = iprop  + 1
 
766
    ipproc(ismago) = iprop
 
767
    ipppst                = ipppst + 1
 
768
    ipppro(iprop)         = ipppst
 
769
  endif
 
770
 
 
771
  if (iale.eq.1) then
 
772
    iprop             = iprop + 1
 
773
    ipproc(ivisma(1)) = iprop
 
774
    ipppst            = ipppst + 1
 
775
    ipppro(iprop)     = ipppst
 
776
    if (iortvm.eq.1) then
 
777
      iprop             = iprop + 1
 
778
      ipproc(ivisma(2)) = iprop
 
779
      ipppst            = ipppst + 1
 
780
      ipppro(iprop)     = ipppst
 
781
      iprop             = iprop + 1
 
782
      ipproc(ivisma(3)) = iprop
 
783
      ipppst            = ipppst + 1
 
784
      ipppro(iprop)     = ipppst
 
785
    endif
 
786
  endif
 
787
 
 
788
  do iest = 1, nestmx
 
789
    if(iescal(iest).gt.0) then
 
790
      iprop                      = iprop + 1
 
791
      ipproc(iestim(iest)) = iprop
 
792
      ipppst                     = ipppst + 1
 
793
      ipppro(iprop)              = ipppst
 
794
    endif
933
795
  enddo
934
796
 
935
797
!     Conductivite electrique imaginaire :
987
849
!   Au centre des faces de bord (rho et flux de masse)
988
850
 
989
851
  iprop = 0
990
 
  do iphas = 1, nphas
991
 
    iprop                 = iprop + 1
992
 
    ipprob(irom  (iphas)) = iprop
993
 
  enddo
 
852
  iprop                 = iprop + 1
 
853
  ipprob(irom  ) = iprop
994
854
  do iflum = 1, nfluma
995
855
    iprop                 = iprop + 1
996
856
    ipprob(iprofl+iflum)  = iprop
1040
900
endif
1041
901
 
1042
902
!===============================================================================
1043
 
! 4. QUATRIEME APPEL :
 
903
! 3. TROISIEME APPEL :
1044
904
!        POSITIONNEMENT DES PROPRIETES POUR LE SCHEMA EN TEMPS,
1045
905
!                                           LES MOMENTS ET FIN
1046
906
!===============================================================================
1054
914
!       d'infos situees en tete de fichier suite (si on fait une
1055
915
!       suite avec des moments non reinitialises).
1056
916
 
1057
 
if(ipass.eq.4) then
1058
 
 
1059
 
 
1060
 
! ---> 4.1 PROPRIETES ADDITIONNELLES POUR LES ET SCHEMA EN TEMPS
 
917
if(ipass.eq.3) then
 
918
 
 
919
 
 
920
! ---> 3.1 PROPRIETES ADDITIONNELLES POUR LES ET SCHEMA EN TEMPS
1061
921
!      ---------------------------------------------------------
1062
922
 
1063
923
! --- Initialisations par defaut eventuelles et verifications
1082
942
!     Schemas en temps
1083
943
!         en LES : Ordre 2 ; sinon Ordre 1
1084
944
!         (en particulier, ordre 2 impossible en k-eps couple)
1085
 
  do iphas = 1, nphas
1086
 
    if(ischtp(iphas).eq.-999) then
1087
 
      if(itytur(iphas).eq.4) then
1088
 
        ischtp(iphas) = 2
1089
 
      else
1090
 
        ischtp(iphas) = 1
1091
 
      endif
 
945
  if(ischtp.eq.-999) then
 
946
    if(itytur.eq.4) then
 
947
      ischtp = 2
 
948
    else
 
949
      ischtp = 1
1092
950
    endif
1093
 
  enddo
 
951
  endif
1094
952
 
1095
953
!     Schemas en temps : variables deduites
1096
 
  do iphas = 1, nphas
1097
954
!     Schema pour le Flux de masse
1098
 
    if(istmpf(iphas).eq.-999) then
1099
 
      if(ischtp(iphas).eq.1) then
1100
 
        istmpf(iphas) = 1
1101
 
      elseif(ischtp(iphas).eq.2) then
1102
 
        istmpf(iphas) = 2
1103
 
      endif
1104
 
    endif
1105
 
!     Masse volumique
1106
 
    if(iroext(iphas).eq.-999) then
1107
 
      if(ischtp(iphas).eq.1) then
1108
 
        iroext(iphas) = 0
1109
 
      elseif(ischtp(iphas).eq.2) then
1110
 
!       Pour le moment par defaut on ne prend pas l'ordre 2
1111
 
!              IROEXT(IPHAS) = 1
1112
 
        iroext(iphas) = 0
1113
 
      endif
1114
 
    endif
1115
 
!     Viscosite
1116
 
    if(iviext(iphas).eq.-999) then
1117
 
      if(ischtp(iphas).eq.1) then
1118
 
        iviext(iphas) = 0
1119
 
      elseif(ischtp(iphas).eq.2) then
1120
 
!       Pour le moment par defaut on ne prend pas l'ordre 2
1121
 
!              IVIEXT(IPHAS) = 1
1122
 
        iviext(iphas) = 0
1123
 
      endif
1124
 
    endif
1125
 
!     Chaleur massique
1126
 
    if(icpext(iphas).eq.-999) then
1127
 
      if(ischtp(iphas).eq.1) then
1128
 
        icpext(iphas) = 0
1129
 
      elseif(ischtp(iphas).eq.2) then
1130
 
!       Pour le moment par defaut on ne prend pas l'ordre 2
1131
 
!              ICPEXT(IPHAS) = 1
1132
 
        icpext(iphas) = 0
1133
 
      endif
1134
 
    endif
1135
 
!     Termes sources NS,
1136
 
    if(isno2t(iphas).eq.-999) then
1137
 
      if(ischtp(iphas).eq.1) then
1138
 
        isno2t(iphas) = 0
1139
 
!            ELSEIF(ISCHTP(IPHAS).EQ.2.AND.IVISSE(IPHAS).EQ.1) THEN
1140
 
      elseif(ischtp(iphas).eq.2) then
1141
 
!       Pour le moment par defaut on prend l'ordre 2
1142
 
        isno2t(iphas) = 1
1143
 
!              ISNO2T(IPHAS) = 0
1144
 
      endif
1145
 
    endif
1146
 
!     Termes sources turbulence (k-eps, Rij, v2f ou k-omega)
1147
 
!     On n'autorise de changer ISTO2T qu'en Rij (sinon avec
1148
 
!       le couplage k-eps/omega il y a pb)
1149
 
    if(isto2t(iphas).eq.-999) then
1150
 
      if(ischtp(iphas).eq.1) then
1151
 
        isto2t(iphas) = 0
1152
 
      elseif(ischtp(iphas).eq.2) then
1153
 
!       Pour le moment par defaut on ne prend pas l'ordre 2
1154
 
!              ISTO2T(IPHAS) = 1
1155
 
        isto2t(iphas) = 0
1156
 
      endif
1157
 
    else if( itytur(iphas).eq.2.or.iturb(iphas).eq.50             &
1158
 
         .or.iturb(iphas).ne.60) then
1159
 
      write(nfecra,8132) iphas,iturb(iphas),isto2t(iphas)
1160
 
      iok = iok + 1
1161
 
    endif
1162
 
  enddo
 
955
  if(istmpf.eq.-999) then
 
956
    if(ischtp.eq.1) then
 
957
      istmpf = 1
 
958
    elseif(ischtp.eq.2) then
 
959
      istmpf = 2
 
960
    endif
 
961
  endif
 
962
  !     Masse volumique
 
963
  if(iroext.eq.-999) then
 
964
    if(ischtp.eq.1) then
 
965
      iroext = 0
 
966
    elseif(ischtp.eq.2) then
 
967
      !       Pour le moment par defaut on ne prend pas l'ordre 2
 
968
      !              IROEXT = 1
 
969
      iroext = 0
 
970
    endif
 
971
  endif
 
972
  !     Viscosite
 
973
  if(iviext.eq.-999) then
 
974
    if(ischtp.eq.1) then
 
975
      iviext = 0
 
976
    elseif(ischtp.eq.2) then
 
977
      !       Pour le moment par defaut on ne prend pas l'ordre 2
 
978
      !              IVIEXT = 1
 
979
      iviext = 0
 
980
    endif
 
981
  endif
 
982
  !     Chaleur massique
 
983
  if(icpext.eq.-999) then
 
984
    if(ischtp.eq.1) then
 
985
      icpext = 0
 
986
    elseif(ischtp.eq.2) then
 
987
      !       Pour le moment par defaut on ne prend pas l'ordre 2
 
988
      !              ICPEXT = 1
 
989
      icpext = 0
 
990
    endif
 
991
  endif
 
992
  !     Termes sources NS,
 
993
  if(isno2t.eq.-999) then
 
994
    if(ischtp.eq.1) then
 
995
      isno2t = 0
 
996
      !            ELSEIF(ISCHTP.EQ.2.AND.IVISSE.EQ.1) THEN
 
997
    elseif(ischtp.eq.2) then
 
998
      !       Pour le moment par defaut on prend l'ordre 2
 
999
      isno2t = 1
 
1000
      !              ISNO2T = 0
 
1001
    endif
 
1002
  endif
 
1003
  !     Termes sources turbulence (k-eps, Rij, v2f ou k-omega)
 
1004
  !     On n'autorise de changer ISTO2T qu'en Rij (sinon avec
 
1005
  !       le couplage k-eps/omega il y a pb)
 
1006
  if(isto2t.eq.-999) then
 
1007
    if(ischtp.eq.1) then
 
1008
      isto2t = 0
 
1009
    elseif(ischtp.eq.2) then
 
1010
      !       Pour le moment par defaut on ne prend pas l'ordre 2
 
1011
      !              ISTO2T = 1
 
1012
      isto2t = 0
 
1013
    endif
 
1014
  else if( itytur.eq.2.or.iturb.eq.50             &
 
1015
       .or.iturb.ne.60) then
 
1016
    write(nfecra,8132) iturb,isto2t
 
1017
    iok = iok + 1
 
1018
  endif
1163
1019
 
1164
1020
  do iscal = 1, nscal
1165
1021
!     Termes sources Scalaires,
1166
 
    iphas = iphsca(iscal)
1167
1022
    if(isso2t(iscal).eq.-999) then
1168
 
      if(ischtp(iphas).eq.1) then
 
1023
      if(ischtp.eq.1) then
1169
1024
        isso2t(iscal) = 0
1170
 
      elseif(ischtp(iphas).eq.2) then
 
1025
      elseif(ischtp.eq.2) then
1171
1026
!       Pour coherence avec Navier Stokes on prend l'ordre 2
1172
1027
!       mais de toute facon qui dit ordre 2 dit LES et donc
1173
1028
!       generalement pas de TS scalaire a interpoler.
1177
1032
    endif
1178
1033
!     Diffusivite scalaires
1179
1034
    if(ivsext(iscal).eq.-999) then
1180
 
      iphas = iphsca(iscal)
1181
 
      if(ischtp(iphas).eq.1) then
 
1035
      if(ischtp.eq.1) then
1182
1036
        ivsext(iscal) = 0
1183
 
      elseif(ischtp(iphas).eq.2) then
 
1037
      elseif(ischtp.eq.2) then
1184
1038
!       Pour le moment par defaut on ne prend pas l'ordre 2
1185
1039
!              IVSEXT(ISCAL) = 1
1186
1040
        ivsext(iscal) = 0
1196
1050
  endif
1197
1051
 
1198
1052
!     Viscosite secondaire
1199
 
  do iphas = 1, nphas
1200
 
    ivisph = ivisse(iphas)
1201
 
    if (ivisph.ne.0.and.ivisph.ne.1) then
1202
 
      WRITE(NFECRA,8022) IPHAS,'IVISSE ',IVISPH
1203
 
      iok = iok + 1
1204
 
    endif
1205
 
  enddo
 
1053
  ivisph = ivisse
 
1054
  if (ivisph.ne.0.and.ivisph.ne.1) then
 
1055
    WRITE(NFECRA,8022) 'IVISSE ',IVISPH
 
1056
    iok = iok + 1
 
1057
  endif
1206
1058
 
1207
1059
!     Schemas en temps
1208
 
  do iphas = 1, nphas
1209
 
 
1210
 
!     Schema en temps global.
1211
 
    if(ischtp(iphas).ne. 1.and.ischtp(iphas).ne.2) then
1212
 
      WRITE(NFECRA,8101) IPHAS,'ISCHTP',ISCHTP(IPHAS)
1213
 
      iok = iok + 1
1214
 
    endif
1215
 
    if(ischtp(iphas).eq. 2.and.idtvar.ne.0) then
1216
 
      write(nfecra,8111) iphas,ischtp(iphas),idtvar
1217
 
      iok = iok + 1
1218
 
    endif
1219
 
    if(ischtp(iphas).eq. 2.and.itytur(iphas).eq.2) then
1220
 
      write(nfecra,8112) iphas,ischtp(iphas),iturb(iphas)
1221
 
      iok = iok + 1
1222
 
    endif
1223
 
    if(ischtp(iphas).eq.1.and.itytur(iphas).eq.4) then
1224
 
      write(nfecra,8113) iphas,ischtp(iphas),iturb(iphas)
1225
 
    endif
1226
 
    if(ischtp(iphas).eq. 2.and.iturb(iphas).eq.50) then
1227
 
      write(nfecra,8114) iphas,ischtp(iphas),iturb(iphas)
1228
 
      iok = iok + 1
1229
 
    endif
1230
 
    if(ischtp(iphas).eq. 2.and.iturb(iphas).eq.60) then
1231
 
      write(nfecra,8115) iphas,ischtp(iphas),iturb(iphas)
1232
 
      iok = iok + 1
1233
 
    endif
1234
 
 
1235
 
!     Schema en temps pour le flux de masse
1236
 
    if(istmpf(iphas).ne. 2.and.istmpf(iphas).ne.0.and.            &
1237
 
       istmpf(iphas).ne. 1) then
1238
 
      WRITE(NFECRA,8121) IPHAS,'ISTMPF',ISTMPF(IPHAS)
1239
 
      iok = iok + 1
1240
 
    endif
1241
 
 
1242
 
!     Schema en temps pour les termes sources de NS
1243
 
    if(isno2t(iphas).ne.0.and.                                    &
1244
 
       isno2t(iphas).ne. 1.and.isno2t(iphas).ne.2) then
1245
 
      WRITE(NFECRA,8131) IPHAS,'ISNO2T',ISNO2T(IPHAS)
1246
 
      iok = iok + 1
1247
 
    endif
1248
 
!     Schema en temps pour les termes sources des grandeurs
1249
 
!     turbulentes
1250
 
    if(isto2t(iphas).ne.0.and.                                    &
1251
 
       isto2t(iphas).ne. 1.and.isto2t(iphas).ne.2) then
1252
 
      WRITE(NFECRA,8131) IPHAS,'ISTO2T',ISTO2T(IPHAS)
1253
 
      iok = iok + 1
1254
 
    endif
1255
 
 
1256
 
!     Schema en temps pour la masse volumique
1257
 
    if(iroext(iphas).ne.0.and.                                    &
1258
 
       iroext(iphas).ne. 1.and.iroext(iphas).ne.2) then
1259
 
      WRITE(NFECRA,8131) IPHAS,'IROEXT',IROEXT(IPHAS)
1260
 
      iok = iok + 1
1261
 
    endif
1262
 
 
1263
 
!     Schema en temps pour la viscosite
1264
 
    if(iviext(iphas).ne.0.and.                                    &
1265
 
       iviext(iphas).ne. 1.and.iviext(iphas).ne.2) then
1266
 
      WRITE(NFECRA,8131) IPHAS,'IVIEXT',IVIEXT(IPHAS)
1267
 
      iok = iok + 1
1268
 
    endif
1269
 
 
1270
 
!     Schema en temps pour la chaleur specifique
1271
 
    if(icpext(iphas).ne.0.and.                                    &
1272
 
       icpext(iphas).ne. 1.and.icpext(iphas).ne.2) then
1273
 
      WRITE(NFECRA,8131) IPHAS,'ICPEXT',ICPEXT(IPHAS)
1274
 
      iok = iok + 1
1275
 
    endif
1276
 
 
1277
 
  enddo
 
1060
 
 
1061
  !     Schema en temps global.
 
1062
  if(ischtp.ne. 1.and.ischtp.ne.2) then
 
1063
    WRITE(NFECRA,8101) 'ISCHTP',ISCHTP
 
1064
    iok = iok + 1
 
1065
  endif
 
1066
  if(ischtp.eq. 2.and.idtvar.ne.0) then
 
1067
    write(nfecra,8111) ischtp,idtvar
 
1068
    iok = iok + 1
 
1069
  endif
 
1070
  if(ischtp.eq. 2.and.itytur.eq.2) then
 
1071
    write(nfecra,8112) ischtp,iturb
 
1072
    iok = iok + 1
 
1073
  endif
 
1074
  if(ischtp.eq.1.and.itytur.eq.4) then
 
1075
    write(nfecra,8113) ischtp,iturb
 
1076
  endif
 
1077
  if(ischtp.eq. 2.and.iturb.eq.50) then
 
1078
    write(nfecra,8114) ischtp,iturb
 
1079
    iok = iok + 1
 
1080
  endif
 
1081
  if(ischtp.eq. 2.and.iturb.eq.51) then
 
1082
    write(nfecra,8117) ischtp,iturb
 
1083
    iok = iok + 1
 
1084
  endif
 
1085
  if(ischtp.eq. 2.and.iturb.eq.60) then
 
1086
    write(nfecra,8115) ischtp,iturb
 
1087
    iok = iok + 1
 
1088
  endif
 
1089
  if(ischtp.eq. 2.and.iturb.eq.70) then
 
1090
    write(nfecra,8116) ischtp,iturb
 
1091
    iok = iok + 1
 
1092
  endif
 
1093
 
 
1094
  !     Schema en temps pour le flux de masse
 
1095
  if(istmpf.ne. 2.and.istmpf.ne.0.and.            &
 
1096
       istmpf.ne. 1) then
 
1097
    WRITE(NFECRA,8121) 'ISTMPF',ISTMPF
 
1098
    iok = iok + 1
 
1099
  endif
 
1100
 
 
1101
  !     Schema en temps pour les termes sources de NS
 
1102
  if(isno2t.ne.0.and.                                    &
 
1103
       isno2t.ne. 1.and.isno2t.ne.2) then
 
1104
    WRITE(NFECRA,8131) 'ISNO2T',ISNO2T
 
1105
    iok = iok + 1
 
1106
  endif
 
1107
  !     Schema en temps pour les termes sources des grandeurs
 
1108
  !     turbulentes
 
1109
  if(isto2t.ne.0.and.                                    &
 
1110
       isto2t.ne. 1.and.isto2t.ne.2) then
 
1111
    WRITE(NFECRA,8131) 'ISTO2T',ISTO2T
 
1112
    iok = iok + 1
 
1113
  endif
 
1114
 
 
1115
  !     Schema en temps pour la masse volumique
 
1116
  if(iroext.ne.0.and.                                    &
 
1117
       iroext.ne. 1.and.iroext.ne.2) then
 
1118
    WRITE(NFECRA,8131) 'IROEXT',IROEXT
 
1119
    iok = iok + 1
 
1120
  endif
 
1121
 
 
1122
  !     Schema en temps pour la viscosite
 
1123
  if(iviext.ne.0.and.                                    &
 
1124
       iviext.ne. 1.and.iviext.ne.2) then
 
1125
    WRITE(NFECRA,8131) 'IVIEXT',IVIEXT
 
1126
    iok = iok + 1
 
1127
  endif
 
1128
 
 
1129
  !     Schema en temps pour la chaleur specifique
 
1130
  if(icpext.ne.0.and.                                    &
 
1131
       icpext.ne. 1.and.icpext.ne.2) then
 
1132
    WRITE(NFECRA,8131) 'ICPEXT',ICPEXT
 
1133
    iok = iok + 1
 
1134
  endif
1278
1135
 
1279
1136
  do iscal = 1, nscal
1280
1137
!     Schema en temps pour les termes sources des scalaires
1301
1158
  iprop  = nprmax
1302
1159
 
1303
1160
! --- Numeros de propriete
1304
 
  do iphas = 1, nphas
1305
 
!     On a besoin de la masse volumique si on l'extrapole ou si ICALHY
1306
 
    if(iroext(iphas).gt.0.or.icalhy.eq.1) then
1307
 
      iprop         = iprop + 1
1308
 
      iroma (iphas) = iprop
1309
 
    endif
1310
 
!     Dans le cas d'une extrapolation de la viscosite totale
1311
 
    if(iviext(iphas).gt.0) then
1312
 
      iprop         = iprop + 1
1313
 
      ivisla(iphas) = iprop
1314
 
      iprop         = iprop + 1
1315
 
      ivista(iphas) = iprop
1316
 
    endif
1317
 
  enddo
1318
 
!     Proprietes des phases : CP s'il est variable
1319
 
  do iphas = 1, nphas
1320
 
    if(icp(iphas).ne.0) then
1321
 
      if(icpext(iphas).gt.0) then
1322
 
        iprop         = iprop + 1
1323
 
        icpa  (iphas) = iprop
1324
 
      endif
1325
 
    endif
1326
 
  enddo
1327
 
!     On a besoin d'un tableau pour les termes sources de Navier Stokes
1328
 
!       a extrapoler. Ce tableau est NDIM
1329
 
  do iphas = 1, nphas
1330
 
    if(isno2t(iphas).gt.0) then
1331
 
      iprop         = iprop + 1
1332
 
      itsnsa(iphas) = iprop
1333
 
    endif
1334
 
    if(isto2t(iphas).gt.0) then
1335
 
      iprop         = iprop + 1
1336
 
      itstua(iphas) = iprop
1337
 
    endif
1338
 
  enddo
 
1161
 
 
1162
  !     On a besoin de la masse volumique si on l'extrapole ou si ICALHY
 
1163
  if(iroext.gt.0.or.icalhy.eq.1) then
 
1164
    iprop         = iprop + 1
 
1165
    iroma  = iprop
 
1166
  endif
 
1167
  !     Dans le cas d'une extrapolation de la viscosite totale
 
1168
  if(iviext.gt.0) then
 
1169
    iprop         = iprop + 1
 
1170
    ivisla = iprop
 
1171
    iprop         = iprop + 1
 
1172
    ivista = iprop
 
1173
  endif
 
1174
 
 
1175
  !     Proprietes des phases : CP s'il est variable
 
1176
  if(icp.ne.0) then
 
1177
    if(icpext.gt.0) then
 
1178
      iprop         = iprop + 1
 
1179
      icpa   = iprop
 
1180
    endif
 
1181
  endif
 
1182
 
 
1183
  !     On a besoin d'un tableau pour les termes sources de Navier Stokes
 
1184
  !       a extrapoler. Ce tableau est NDIM
 
1185
  if(isno2t.gt.0) then
 
1186
    iprop         = iprop + 1
 
1187
    itsnsa = iprop
 
1188
  endif
 
1189
  if(isto2t.gt.0) then
 
1190
    iprop         = iprop + 1
 
1191
    itstua = iprop
 
1192
  endif
 
1193
 
1339
1194
!     Proprietes des scalaires : termes sources pour theta schema
1340
1195
!       et VISCLS si elle est variable
1341
1196
  if(nscal.ge.1) then
1368
1223
  enddo
1369
1224
!     On regarde s'il y en a besoin
1370
1225
  iiflaa = 0
1371
 
  do iphas = 1, nphas
1372
 
    if(istmpf(iphas).ne.1) iiflaa = 1
1373
 
  enddo
 
1226
  if(istmpf.ne.1) iiflaa = 1
 
1227
 
1374
1228
!     On les affecte
1375
1229
  iprofa = iprop
1376
1230
  if(iiflaa.eq.1) then
1377
 
    do iphas = 1, nphas
1378
 
      if(iphas.eq.1) then
1379
 
        iprop               = iprop + 1
1380
 
        ifluaa(ipr (iphas)) = iprop
1381
 
      endif
1382
 
      ifluaa(iu  (iphas)) = iprop
1383
 
      ifluaa(iv  (iphas)) = iprop
1384
 
      ifluaa(iw  (iphas)) = iprop
1385
 
      if(itytur(iphas).eq.2) then
1386
 
        ifluaa(ik  (iphas)) = iprop
1387
 
        ifluaa(iep (iphas)) = iprop
1388
 
      elseif(itytur(iphas).eq.3) then
1389
 
        ifluaa(ir11(iphas)) = iprop
1390
 
        ifluaa(ir22(iphas)) = iprop
1391
 
        ifluaa(ir33(iphas)) = iprop
1392
 
        ifluaa(ir12(iphas)) = iprop
1393
 
        ifluaa(ir13(iphas)) = iprop
1394
 
        ifluaa(ir23(iphas)) = iprop
1395
 
        ifluaa(iep (iphas)) = iprop
1396
 
      elseif(iturb(iphas).eq.50) then
1397
 
        ifluaa(ik  (iphas)) = iprop
1398
 
        ifluaa(iep (iphas)) = iprop
1399
 
        ifluaa(iphi(iphas)) = iprop
1400
 
        ifluaa(ifb (iphas)) = iprop
1401
 
      elseif(iturb(iphas).eq.60) then
1402
 
        ifluaa(ik  (iphas)) = iprop
1403
 
        ifluaa(iomg(iphas)) = iprop
1404
 
      endif
1405
 
    enddo
 
1231
    iprop               = iprop + 1
 
1232
    ifluaa(ipr ) = iprop
 
1233
    ifluaa(iu  ) = iprop
 
1234
    ifluaa(iv  ) = iprop
 
1235
    ifluaa(iw  ) = iprop
 
1236
    if(itytur.eq.2) then
 
1237
      ifluaa(ik  ) = iprop
 
1238
      ifluaa(iep ) = iprop
 
1239
    elseif(itytur.eq.3) then
 
1240
      ifluaa(ir11) = iprop
 
1241
      ifluaa(ir22) = iprop
 
1242
      ifluaa(ir33) = iprop
 
1243
      ifluaa(ir12) = iprop
 
1244
      ifluaa(ir13) = iprop
 
1245
      ifluaa(ir23) = iprop
 
1246
      ifluaa(iep ) = iprop
 
1247
    elseif(itytur.eq.5) then
 
1248
      ifluaa(ik  ) = iprop
 
1249
      ifluaa(iep ) = iprop
 
1250
      ifluaa(iphi) = iprop
 
1251
      if(iturb.eq.50) then
 
1252
        ifluaa(ifb ) = iprop
 
1253
      elseif(iturb.eq.51) then
 
1254
        ifluaa(ial ) = iprop
 
1255
      endif
 
1256
    elseif(iturb.eq.60) then
 
1257
      ifluaa(ik  ) = iprop
 
1258
      ifluaa(iomg) = iprop
 
1259
    elseif (iturb.eq.70) then
 
1260
      ifluaa(inusa)= iprop
 
1261
    endif
1406
1262
    do iscal = 1, nscal
1407
 
      ifluaa(isca(iscal)) = ifluaa(iu(iphsca(iscal)))
 
1263
      ifluaa(isca(iscal)) = ifluaa(iu)
1408
1264
    enddo
1409
1265
  endif
1410
1266
 
1417
1273
  ipppst                = nppmax
1418
1274
 
1419
1275
! --- Positionnement des PROPCE
1420
 
  do iphas = 1, nphas
1421
1276
 
1422
 
!     Variables schema en temps
1423
 
    if(iroext(iphas).gt.0.or.icalhy.eq.1) then
1424
 
      iprop                 = iprop  + 1
1425
 
      ipproc(iroma (iphas)) = iprop
1426
 
    endif
1427
 
    if(iviext(iphas).gt.0) then
1428
 
      iprop                 = iprop  + 1
1429
 
      ipproc(ivisla(iphas)) = iprop
1430
 
    endif
1431
 
    if(iviext(iphas).gt.0) then
1432
 
      iprop                 = iprop  + 1
1433
 
      ipproc(ivista(iphas)) = iprop
1434
 
    endif
1435
 
    if(icpext(iphas).gt.0) then
1436
 
      iprop                 = iprop + 1
1437
 
      ipproc(icpa  (iphas)) = iprop
1438
 
    endif
1439
 
    if(isno2t(iphas).gt.0) then
1440
 
      iprop                 = iprop + 1
1441
 
      ipproc(itsnsa(iphas)) = iprop
1442
 
!     Ce tableau est NDIM :
1443
 
      iprop                 = iprop + ndim-1
1444
 
    endif
1445
 
    if(isto2t(iphas).gt.0) then
1446
 
      iprop                 = iprop + 1
1447
 
      ipproc(itstua(iphas)) = iprop
1448
 
!     Ce tableau est 2, 7 ou 4 selon le modele de turbulence :
1449
 
      if    (itytur(iphas).eq.2) then
1450
 
        iprop                 = iprop + 2-1
1451
 
      elseif(itytur(iphas).eq.3) then
1452
 
        iprop                 = iprop + 7-1
1453
 
      elseif(iturb(iphas).eq.50) then
1454
 
        iprop                 = iprop + 4-1
1455
 
      endif
1456
 
    endif
1457
 
  enddo
 
1277
  !     Variables schema en temps
 
1278
  if(iroext.gt.0.or.icalhy.eq.1) then
 
1279
    iprop                 = iprop  + 1
 
1280
    ipproc(iroma ) = iprop
 
1281
  endif
 
1282
  if(iviext.gt.0) then
 
1283
    iprop                 = iprop  + 1
 
1284
    ipproc(ivisla) = iprop
 
1285
  endif
 
1286
  if(iviext.gt.0) then
 
1287
    iprop                 = iprop  + 1
 
1288
    ipproc(ivista) = iprop
 
1289
  endif
 
1290
  if(icpext.gt.0) then
 
1291
    iprop                 = iprop + 1
 
1292
    ipproc(icpa  ) = iprop
 
1293
  endif
 
1294
  if(isno2t.gt.0) then
 
1295
    iprop                 = iprop + 1
 
1296
    ipproc(itsnsa) = iprop
 
1297
    !     Ce tableau est NDIM :
 
1298
    iprop                 = iprop + ndim-1
 
1299
  endif
 
1300
  if(isto2t.gt.0) then
 
1301
    iprop                 = iprop + 1
 
1302
    ipproc(itstua) = iprop
 
1303
    !     Ce tableau est 2, 7 ou 4 selon le modele de turbulence :
 
1304
    if    (itytur.eq.2) then
 
1305
      iprop                 = iprop + 2-1
 
1306
    elseif(itytur.eq.3) then
 
1307
      iprop                 = iprop + 7-1
 
1308
    elseif(iturb.eq.50) then
 
1309
      iprop                 = iprop + 4-1
 
1310
    elseif(iturb.eq.70) then
 
1311
      iprop                 = iprop + 1-1
 
1312
    endif
 
1313
  endif
1458
1314
 
1459
1315
  do ii = 1, nscal
1460
1316
! Termes source des scalaires pour theta schema
1491
1347
  iprop                 = nprofb
1492
1348
 
1493
1349
! --- Positionnement des PROPFB
1494
 
  do iphas = 1, nphas
1495
 
!     Variables schema en temps : rhoa (pas pour icalhy)
1496
 
    if(iroext(iphas).gt.0) then
1497
 
      iprop                 = iprop  + 1
1498
 
      ipprob(iroma (iphas)) = iprop
1499
 
    endif
1500
 
  enddo
1501
 
!     Variables schema en temps : flux de masse A
 
1350
 
 
1351
  !     Variables schema en temps : rhoa (pas pour icalhy)
 
1352
  if(iroext.gt.0) then
 
1353
    iprop                 = iprop  + 1
 
1354
    ipprob(iroma ) = iprop
 
1355
  endif
 
1356
  !     Variables schema en temps : flux de masse A
1502
1357
  if(iiflaa.eq.1) then
1503
1358
    do iflum = 1, nfluma
1504
1359
      iprop                 = iprop + 1
1525
1380
  nprofa = iprop
1526
1381
 
1527
1382
 
1528
 
! ---> 4.2 CALCUL DE LA TAILLE DU TABLEAU DES TEMPS CUMULES POUR LES MOMENTS
 
1383
! ---> 3.2 CALCUL DE LA TAILLE DU TABLEAU DES TEMPS CUMULES POUR LES MOMENTS
1529
1384
!      ---------------------------------------------------------------------
1530
1385
 
1531
1386
!     Pour verification des definitions de moments
1625
1480
!     Ouverture
1626
1481
!        (ILECEC=1:lecture)
1627
1482
    ilecec = 1
1628
 
    call opnsui(ficamx,len(ficamx),ilecec,impamx,ierror)
 
1483
    ficsui = 'auxiliary'
 
1484
    call opnsui(ficsui,len(ficsui),ilecec,impamx,ierror)
1629
1485
    !==========
1630
1486
    if (ierror.ne.0) then
1631
 
      write(nfecra,8300) ficamx
 
1487
      write(nfecra,8300) ficsui
1632
1488
      call csexit (1)
1633
1489
    endif
1634
1490
 
1646
1502
                ivers,ierror)
1647
1503
 
1648
1504
    if (ierror.ne.0) then
1649
 
      write(nfecra,8301)ficamx
 
1505
      write(nfecra,8301)ficsui
1650
1506
      call csexit (1)
1651
1507
    endif
1652
1508
 
1801
1657
    call clssui(impamx,ierror)
1802
1658
 
1803
1659
    if (ierror.ne.0) then
1804
 
      write(nfecra,8390) ficamx
 
1660
      write(nfecra,8390) ficsui
1805
1661
    endif
1806
1662
 
1807
1663
  endif
1907
1763
    nbdtcm=max(idtmom(imom),nbdtcm)
1908
1764
  enddo
1909
1765
 
1910
 
! ---> 4.3 POSITIONNEMENT DANS PROPCE DES MOMENTS ET DU TEMPS CUMULE
 
1766
! ---> 3.3 POSITIONNEMENT DANS PROPCE DES MOMENTS ET DU TEMPS CUMULE
1911
1767
!      -------------------------------------------------------------
1912
1768
 
1913
1769
! --- Reprise du dernier numero de propriete
1950
1806
 
1951
1807
 
1952
1808
 
1953
 
! ---> 4.4  POSITIONNEMENT DES CONDITIONS AUX LIMITES
 
1809
! ---> 3.4  POSITIONNEMENT DES CONDITIONS AUX LIMITES
1954
1810
!      ---------------------------------------------------------------------
1955
1811
 
1956
1812
! --- Numerotation des tableaux NFABOR de type COEFA/COEFB presents ici
1968
1824
    iclrtp(ivar,icoef ) = icondl
1969
1825
    iclrtp(ivar,icoeff) = icondl
1970
1826
  enddo
1971
 
  do iphas = 1, nphas
1972
 
    if( itytur(iphas).eq.2 .or. itytur(iphas).eq.4                &
1973
 
         .or. iturb(iphas).eq.60 ) then
1974
 
      ivar = iu(iphas)
1975
 
      icondl = icondl + 1
1976
 
      iclrtp(ivar,icoeff) = icondl
1977
 
      ivar = iv(iphas)
1978
 
      icondl = icondl + 1
1979
 
      iclrtp(ivar,icoeff) = icondl
1980
 
      ivar = iw(iphas)
1981
 
      icondl = icondl + 1
1982
 
      iclrtp(ivar,icoeff) = icondl
1983
 
    endif
1984
 
  enddo
 
1827
  if( itytur.eq.2 .or. itytur.eq.4                &
 
1828
       .or. iturb.eq.60 .or. iturb.eq.70          &
 
1829
       ) then
 
1830
    ivar = iu
 
1831
    icondl = icondl + 1
 
1832
    iclrtp(ivar,icoeff) = icondl
 
1833
    ivar = iv
 
1834
    icondl = icondl + 1
 
1835
    iclrtp(ivar,icoeff) = icondl
 
1836
    ivar = iw
 
1837
    icondl = icondl + 1
 
1838
    iclrtp(ivar,icoeff) = icondl
 
1839
  endif
1985
1840
  if (iphydr.eq.1) then
1986
 
    do iphas = 1, nphas
1987
 
      icondl = icondl + 1
1988
 
      iclrtp(ipr(iphas),icoeff) = icondl
1989
 
    enddo
 
1841
    icondl = icondl + 1
 
1842
    iclrtp(ipr,icoeff) = icondl
1990
1843
  endif
1991
1844
 
1992
1845
! Compressible
1993
1846
  if (ippmod(icompf).ge.0) then
1994
 
    do iphas = 1, nphas
1995
 
      icondl = icondl + 1
1996
 
      iclrtp(isca(ienerg(iphas)),icoeff) = icondl
1997
 
    enddo
 
1847
    icondl = icondl + 1
 
1848
    iclrtp(isca(ienerg),icoeff) = icondl
1998
1849
  endif
1999
1850
 
2000
1851
  ncofab = icondl
2001
1852
 
2002
1853
 
2003
 
! ---> 4.5 POINTEURS POST-PROCESSING / LISTING / HISTORIQUES / CHRONOS
 
1854
! ---> 3.5 POINTEURS POST-PROCESSING / LISTING / HISTORIQUES / CHRONOS
2004
1855
!      ---------------------------------------------------------------------
2005
1856
 
2006
1857
! --- Les pointeurs ont ete initialises a 1 (poubelle).
2046
1897
endif
2047
1898
 
2048
1899
!===============================================================================
2049
 
! 5. CINQUIEME APPEL :
 
1900
! 4. QUATRIEME APPEL :
2050
1901
!        RESERVATION D'UNE PLACE DANS PROPCE SI RAYONNEMENT
2051
1902
!        ET LAGRANGIEN AVEC THERMIQUE DES PARTICULES
2052
1903
!===============================================================================
2053
1904
 
2054
 
if (ipass.eq.5) then
 
1905
if (ipass.eq.4) then
2055
1906
 
2056
1907
  if ( iirayo.gt.0 ) then
2057
1908
 
2069
1920
    iqz          = iprop
2070
1921
 
2071
1922
 
2072
 
    do iphas = 1, nphasc
 
1923
    do irphas = 1, nrphas
2073
1924
 
2074
 
      iprop                = iprop + 1
2075
 
      itsre(iphas)         = iprop
2076
 
      iprop                = iprop + 1
2077
 
      itsri(iphas)         = iprop
2078
 
      iprop                = iprop + 1
2079
 
      iabs(iphas)          = iprop
2080
 
      iprop                = iprop + 1
2081
 
      iemi(iphas)          = iprop
2082
 
      iprop                = iprop + 1
2083
 
      icak(iphas)          = iprop
 
1925
      iprop                 = iprop + 1
 
1926
      itsre(irphas)         = iprop
 
1927
      iprop                 = iprop + 1
 
1928
      itsri(irphas)         = iprop
 
1929
      iprop                 = iprop + 1
 
1930
      iabs(irphas)          = iprop
 
1931
      iprop                 = iprop + 1
 
1932
      iemi(irphas)          = iprop
 
1933
      iprop                 = iprop + 1
 
1934
      icak(irphas)          = iprop
2084
1935
 
2085
1936
    enddo
2086
1937
 
2119
1970
! Leur dimensionnement n'est pas le meme si on est en charbon ou non
2120
1971
 
2121
1972
 
2122
 
    do iphas = 1, nphasc
2123
 
!
2124
 
      iprop                = iprop + 1
2125
 
      ipproc(itsre(iphas)) = iprop
2126
 
      ipppst               = ipppst + 1
2127
 
      ipppro(iprop)        = ipppst
2128
 
 
2129
 
      iprop                = iprop + 1
2130
 
      ipproc(itsri(iphas)) = iprop
2131
 
      ipppst               = ipppst + 1
2132
 
      ipppro(iprop)        = ipppst
2133
 
!
2134
 
      iprop                = iprop + 1
2135
 
      ipproc(iabs(iphas))  = iprop
2136
 
      ipppst               = ipppst + 1
2137
 
      ipppro(iprop)        = ipppst
2138
 
 
2139
 
      iprop                = iprop + 1
2140
 
      ipproc(iemi(iphas))  = iprop
2141
 
      ipppst               = ipppst + 1
2142
 
      ipppro(iprop)        = ipppst
2143
 
 
2144
 
      iprop                = iprop + 1
2145
 
      ipproc(icak(iphas))  = iprop
 
1973
    do irphas = 1, nrphas
 
1974
!
 
1975
      iprop                = iprop + 1
 
1976
      ipproc(itsre(irphas)) = iprop
 
1977
      ipppst               = ipppst + 1
 
1978
      ipppro(iprop)        = ipppst
 
1979
 
 
1980
      iprop                = iprop + 1
 
1981
      ipproc(itsri(irphas)) = iprop
 
1982
      ipppst               = ipppst + 1
 
1983
      ipppro(iprop)        = ipppst
 
1984
!
 
1985
      iprop                = iprop + 1
 
1986
      ipproc(iabs(irphas))  = iprop
 
1987
      ipppst               = ipppst + 1
 
1988
      ipppro(iprop)        = ipppst
 
1989
 
 
1990
      iprop                = iprop + 1
 
1991
      ipproc(iemi(irphas))  = iprop
 
1992
      ipppst               = ipppst + 1
 
1993
      ipppro(iprop)        = ipppst
 
1994
 
 
1995
      iprop                = iprop + 1
 
1996
      ipproc(icak(irphas))  = iprop
2146
1997
      ipppst               = ipppst + 1
2147
1998
      ipppro(iprop)        = ipppst
2148
1999
 
2213
2064
 
2214
2065
      call uirapr &
2215
2066
      !==========
2216
 
    ( nprayc, nprayb, nphasc, ipppro, ipproc,           &
 
2067
    ( nprayc, nprayb, nrphas, ipppro, ipproc,           &
2217
2068
      ilumin, iqx, iqy, iqz,                            &
2218
2069
      itsre, itsri, iabs, iemi, icak)
2219
2070
 
2241
2092
 
2242
2093
 
2243
2094
!===============================================================================
2244
 
! 6. FORMATS
 
2095
! 5. FORMATS
2245
2096
!===============================================================================
2246
2097
 
2247
2098
#if defined(_CS_LANG_FR)
2248
 
 5000 format(                                                           &
2249
 
'@                                                            ',/,&
2250
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2251
 
'@                                                            ',/,&
2252
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
2253
 
'@    =========                                               ',/,&
2254
 
'@     NOMBRE DE PHASES ERRONE                                ',/,&
2255
 
'@                                                            ',/,&
2256
 
'@  Le nombre de phases doit etre un entier strictement       ',/,&
2257
 
'@    positif. Il vaut ici                NPHAS  = ',I10       ,/,&
2258
 
'@                                                            ',/,&
2259
 
'@  Le calcul ne sera pas execute.                            ',/,&
2260
 
'@                                                            ',/,&
2261
 
'@  Verifier usini1.                                          ',/,&
2262
 
'@                                                            ',/,&
2263
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2264
 
'@                                                            ',/)
2265
 
 5001 format(                                                           &
2266
 
'@                                                            ',/,&
2267
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2268
 
'@                                                            ',/,&
2269
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
2270
 
'@    =========                                               ',/,&
2271
 
'@     NOMBRE DE PHASES TROP GRAND                            ',/,&
2272
 
'@                                                            ',/,&
2273
 
'@  Le nombre de phases                                       ',/,&
2274
 
'@    - demande          dans usini1   est NPHAS  = ',I10      ,/,&
2275
 
'@    - maximal autorise dans paramx.h est NPHSMX = ',I10      ,/,&
2276
 
'@                                                            ',/,&
2277
 
'@  Le calcul ne sera pas execute.                            ',/,&
2278
 
'@                                                            ',/,&
2279
 
'@  Verifier usini1.                                          ',/,&
2280
 
'@                                                            ',/,&
2281
 
'@  NPHSMX doit valoir au moins ',I10                          ,/,&
2282
 
'@                                                            ',/,&
2283
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2284
 
'@                                                            ',/)
2285
2099
 6000 format(                                                           &
2286
2100
'@                                                            ',/,&
2287
2101
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2425
2239
'@                                                            ',/,&
2426
2240
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2427
2241
'@                                                            ',/)
2428
 
 7020 format(                                                           &
2429
 
'@                                                            ',/,&
2430
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2431
 
'@                                                            ',/,&
2432
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
2433
 
'@    =========                                               ',/,&
2434
 
'@    PHASE PORTEUSE INCORRECTE POUR LE SCALAIRE ',I10         ,/,&
2435
 
'@                                                            ',/,&
2436
 
'@  La phase porteuse du scalaire ',I10                        ,/,&
2437
 
'@          (scalaire utilisateur ',I10   ,') indiquee dans   ',/,&
2438
 
'@    usini1 est IPHSCA(',I10   ,') = ',I10                    ,/,&
2439
 
'@  Elle devrait etre comprise entre 0 et NPHAS = ',I10        ,/,&
2440
 
'@  Le calcul ne sera pas execute.                            ',/,&
2441
 
'@                                                            ',/,&
2442
 
'@  Verifier IPHSCA dans usini1.                              ',/,&
2443
 
'@                                                            ',/,&
2444
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2445
 
'@                                                            ',/)
2446
 
 7021 format(                                                           &
2447
 
'@                                                            ',/,&
2448
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2449
 
'@                                                            ',/,&
2450
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
2451
 
'@    =========                                               ',/,&
2452
 
'@    PHASE PORTEUSE INCORRECTE POUR LE SCALAIRE ',I10         ,/,&
2453
 
'@                                                            ',/,&
2454
 
'@  La phase porteuse du scalaire ',I10                        ,/,&
2455
 
'@          (scalaire physique particuliere ',I10   ,')       ',/,&
2456
 
'@           est IPHSCA(ISCAPP(',I10   ,')) = ',I10            ,/,&
2457
 
'@  Elle devrait etre comprise entre 0 et NPHAS = ',I10        ,/,&
2458
 
'@  Le calcul ne sera pas execute.                            ',/,&
2459
 
'@                                                            ',/,&
2460
 
'@  Verifier IPHSCA.                                          ',/,&
2461
 
'@                                                            ',/,&
2462
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2463
 
'@                                                            ',/)
2464
2242
 7030 format(                                                           &
2465
2243
'@                                                            ',/,&
2466
2244
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2645
2423
'@                                                            ',/,&
2646
2424
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2647
2425
'@                                                            ',/)
2648
 
 7060 format(                                                           &
2649
 
'@                                                            ',/,&
2650
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2651
 
'@                                                            ',/,&
2652
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
2653
 
'@    =========                                               ',/,&
2654
 
'@    SCALAIRE ',I10   ,' NE PAS MODIFIER LA PHASE PORTEUSE   ',/,&
2655
 
'@                                                            ',/,&
2656
 
'@  Le scalaire ',I10                                          ,/,&
2657
 
'@    (scalaire utilisateur           ',I10   ,') represente  ',/,&
2658
 
'@    la variance des fluctuations du scalaire ',I10           ,/,&
2659
 
'@    (scalaire utilisateur           ',I10   ,') puisque     ',/,&
2660
 
'@    ISCAVR(',I10   ,') vaut ',I10   ,' (non nul)            ',/,&
2661
 
'@                                                            ',/,&
2662
 
'@  La phase porteuse IPHSCA(',I10   ,') du scalaire          ',/,&
2663
 
'@    ne doit pas etre renseignee.                            ',/,&
2664
 
'@  Elle sera automatiquement prise identique a la phase      ',/,&
2665
 
'@    porteuse du scalaire associe, soit ',I10                 ,/,&
2666
 
'@                                                            ',/,&
2667
 
'@  Le calcul ne sera pas execute.                            ',/,&
2668
 
'@                                                            ',/,&
2669
 
'@  Verifier IPHSCA dans usini1.                              ',/,&
2670
 
'@                                                            ',/,&
2671
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2672
 
'@                                                            ',/)
2673
 
 7061 format(                                                           &
2674
 
'@                                                            ',/,&
2675
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2676
 
'@                                                            ',/,&
2677
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
2678
 
'@    =========                                               ',/,&
2679
 
'@    SCALAIRE ',I10   ,' NE PAS MODIFIER LA PHASE PORTEUSE   ',/,&
2680
 
'@                                                            ',/,&
2681
 
'@  Le scalaire ',I10                                          ,/,&
2682
 
'@    (scalaire utilisateur           ',I10   ,') represente  ',/,&
2683
 
'@    la variance des fluctuations du scalaire ',I10           ,/,&
2684
 
'@    (scalaire physique particuliere ',I10   ,') puisque     ',/,&
2685
 
'@    ISCAVR(',I10   ,') vaut ',I10   ,' (non nul)            ',/,&
2686
 
'@                                                            ',/,&
2687
 
'@  La phase porteuse IPHSCA(',I10   ,') du scalaire          ',/,&
2688
 
'@    ne doit pas etre renseignee.                            ',/,&
2689
 
'@  Elle sera automatiquement prise identique a la phase      ',/,&
2690
 
'@    porteuse du scalaire associe, soit ',I10                 ,/,&
2691
 
'@                                                            ',/,&
2692
 
'@  Le calcul ne sera pas execute.                            ',/,&
2693
 
'@                                                            ',/,&
2694
 
'@  Verifier IPHSCA dans usini1.                              ',/,&
2695
 
'@                                                            ',/,&
2696
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2697
 
'@                                                            ',/)
2698
 
 7062 format(                                                           &
2699
 
'@                                                            ',/,&
2700
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2701
 
'@                                                            ',/,&
2702
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
2703
 
'@    =========                                               ',/,&
2704
 
'@    SCALAIRE ',I10   ,' NE PAS MODIFIER LA PHASE PORTEUSE   ',/,&
2705
 
'@                                                            ',/,&
2706
 
'@  Le scalaire ',I10                                          ,/,&
2707
 
'@    (scalaire physique particuliere ',I10   ,') represente  ',/,&
2708
 
'@    la variance des fluctuations du scalaire ',I10           ,/,&
2709
 
'@    (scalaire utilisateur           ',I10   ,') puisque     ',/,&
2710
 
'@    ISCAVR(ISCAPP(',I10   ,')) vaut ',I10   ,' (non nul)    ',/,&
2711
 
'@                                                            ',/,&
2712
 
'@  La phase porteuse IPHSCA(ISCAPP(',I10   ,')) du scalaire  ',/,&
2713
 
'@    ne doit pas etre renseignee.                            ',/,&
2714
 
'@  Elle sera automatiquement prise identique a la phase      ',/,&
2715
 
'@    porteuse du scalaire associe, soit ',I10                 ,/,&
2716
 
'@                                                            ',/,&
2717
 
'@  Le calcul ne sera pas execute.                            ',/,&
2718
 
'@                                                            ',/,&
2719
 
'@  Verifier IPHSCA.                                          ',/,&
2720
 
'@                                                            ',/,&
2721
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2722
 
'@                                                            ',/)
2723
 
 7063 format(                                                           &
2724
 
'@                                                            ',/,&
2725
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2726
 
'@                                                            ',/,&
2727
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
2728
 
'@    =========                                               ',/,&
2729
 
'@    SCALAIRE ',I10   ,' NE PAS MODIFIER LA PHASE PORTEUSE   ',/,&
2730
 
'@                                                            ',/,&
2731
 
'@  Le scalaire ',I10                                          ,/,&
2732
 
'@    (scalaire physique particuliere ',I10   ,') represente  ',/,&
2733
 
'@    la variance des fluctuations du scalaire ',I10           ,/,&
2734
 
'@    (scalaire physique particuliere ',I10   ,') puisque     ',/,&
2735
 
'@    ISCAVR(ISCAPP(',I10   ,')) vaut ',I10   ,' (non nul)    ',/,&
2736
 
'@                                                            ',/,&
2737
 
'@  La phase porteuse IPHSCA(ISCAPP(',I10   ,')) du scalaire  ',/,&
2738
 
'@    ne doit pas etre renseignee.                            ',/,&
2739
 
'@  Elle sera automatiquement prise identique a la phase      ',/,&
2740
 
'@    porteuse du scalaire associe, soit ',I10                 ,/,&
2741
 
'@                                                            ',/,&
2742
 
'@  Le calcul ne sera pas execute.                            ',/,&
2743
 
'@                                                            ',/,&
2744
 
'@  Verifier IPHSCA.                                          ',/,&
2745
 
'@                                                            ',/,&
2746
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2747
 
'@                                                            ',/)
2748
2426
 7070 format(                                                           &
2749
2427
'@                                                            ',/,&
2750
2428
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2827
2505
'@                                                            ',/,&
2828
2506
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
2829
2507
'@    =========                                               ',/,&
2830
 
'@    PHASE ',I10                                              ,/,&
2831
2508
'@    ',A6,' DOIT ETRE UN ENTIER EGAL A 0 OU 1                ',/,&
2832
2509
'@    IL VAUT ICI ',I10                                        ,/,&
2833
2510
'@                                                            ',/,&
2843
2520
'@                                                            ',/,&
2844
2521
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
2845
2522
'@    =========                                               ',/,&
2846
 
'@    PHASE ',I10                                              ,/,&
2847
2523
'@    ',A6,' DOIT ETRE UN ENTIER EGAL A 1 ou 2                ',/,&
2848
2524
'@    IL VAUT ICI ',I10                                        ,/,&
2849
2525
'@                                                            ',/,&
2857
2533
'@                                                            ',/,&
2858
2534
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2859
2535
'@                                                            ',/,&
2860
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES PHASE ',I10    ,/,&
 
2536
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES'               ,/,&
2861
2537
'@    =========                                               ',/,&
2862
2538
'@    AVEC UN SCHEMA EN TEMPS D ORDRE 2 : ISCHTP = ', I10      ,/,&
2863
2539
'@    IL FAUT UTILISER UN PAS DE TEMPS CONSTANT ET UNIFORME   ',/,&
2873
2549
'@                                                            ',/,&
2874
2550
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2875
2551
'@                                                            ',/,&
2876
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES PHASE ',I10    ,/,&
 
2552
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES'               ,/,&
2877
2553
'@    =========                                               ',/,&
2878
2554
'@    ON IMPOSE UN SCHEMA EN TEMPS D ORDRE 2 (ISCHTP = ',I10   ,/,&
2879
2555
'@    EN K-EPSILON (ITURB = ',I10,' )'                         ,/,&
2891
2567
'@                                                            ',/,&
2892
2568
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2893
2569
'@                                                            ',/,&
2894
 
'@ @@ ATTENTION :       A L''ENTREE DES DONNEES PHASE ',I10    ,/,&
 
2570
'@ @@ ATTENTION :       A L''ENTREE DES DONNEES'               ,/,&
2895
2571
'@    =========                                               ',/,&
2896
2572
'@    ON IMPOSE UN SCHEMA EN TEMPS D ORDRE 1 (ISCHTP = ',I10   ,/,&
2897
2573
'@    EN LES (ITURB = ',I10,' )'                               ,/,&
2906
2582
'@                                                            ',/,&
2907
2583
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2908
2584
'@                                                            ',/,&
 
2585
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES'               ,/,&
 
2586
'@    =========                                               ',/,&
 
2587
'@    ON IMPOSE UN SCHEMA EN TEMPS D ORDRE 2 (ISCHTP = ',I10   ,/,&
 
2588
'@    EN PHI_FBAR (ITURB = ',I10,' )'                          ,/,&
 
2589
'@                                                            ',/,&
 
2590
'@   La version courante ne supporte pas l''ordre 2 avec le   ',/,&
 
2591
'@   couplage des termes sources du k-epsilon.                ',/,&
 
2592
'@                                                            ',/,&
 
2593
'@  Le calcul ne sera pas execute.                            ',/,&
 
2594
'@                                                            ',/,&
 
2595
'@  Modifier usini1.                                          ',/,&
 
2596
'@                                                            ',/,&
 
2597
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
 
2598
'@                                                            ',/)
 
2599
 8117 format(                                                           &
 
2600
'@                                                            ',/,&
 
2601
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
 
2602
'@                                                            ',/,&
2909
2603
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES PHASE ',I10    ,/,&
2910
2604
'@    =========                                               ',/,&
2911
2605
'@    ON IMPOSE UN SCHEMA EN TEMPS D ORDRE 2 (ISCHTP = ',I10   ,/,&
2912
 
'@    EN V2F       (ITURB = ',I10,' )'                         ,/,&
 
2606
'@    EN BL-V2/K  (ITURB = ',I10,' )'                         ,/,&
2913
2607
'@                                                            ',/,&
2914
2608
'@   La version courante ne supporte pas l''ordre 2 avec le   ',/,&
2915
2609
'@   couplage des termes sources du k-epsilon.                ',/,&
2924
2618
'@                                                            ',/,&
2925
2619
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2926
2620
'@                                                            ',/,&
2927
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES PHASE ',I10    ,/,&
 
2621
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES'               ,/,&
2928
2622
'@    =========                                               ',/,&
2929
2623
'@    ON IMPOSE UN SCHEMA EN TEMPS D ORDRE 2 (ISCHTP = ',I10   ,/,&
2930
2624
'@    EN K-OMEGA   (ITURB = ',I10,' )'                         ,/,&
2938
2632
'@                                                            ',/,&
2939
2633
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2940
2634
'@                                                            ',/)
 
2635
 8116 format(                                                           &
 
2636
'@                                                            ',/,&
 
2637
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
 
2638
'@                                                            ',/,&
 
2639
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES'               ,/,&
 
2640
'@    =========                                               ',/,&
 
2641
'@    ON IMPOSE UN SCHEMA EN TEMPS D ORDRE 2 (ISCHTP = ',I10   ,/,&
 
2642
'@    EN SPALART   (ITURB = ',I10,' )'                         ,/,&
 
2643
'@                                                            ',/,&
 
2644
'@   La version courante ne supporte pas l''ordre 2 avec le   ',/,&
 
2645
'@   couplage des termes sources de Spalart-Allmaras.         ',/,&
 
2646
'@                                                            ',/,&
 
2647
'@  Le calcul ne sera pas execute.                            ',/,&
 
2648
'@                                                            ',/,&
 
2649
'@  Modifier usini1.                                          ',/,&
 
2650
'@                                                            ',/,&
 
2651
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
 
2652
'@                                                            ',/)
2941
2653
 8121 format(                                                           &
2942
2654
'@                                                            ',/,&
2943
2655
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2944
2656
'@                                                            ',/,&
2945
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES PHASE ',I10    ,/,&
 
2657
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES'               ,/,&
2946
2658
'@    =========                                               ',/,&
2947
2659
'@    ',A6,' DOIT ETRE UN ENTIER EGAL A  0, 1 OU 2            ',/,&
2948
2660
'@    IL VAUT ICI ',I10                                        ,/,&
2957
2669
'@                                                            ',/,&
2958
2670
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2959
2671
'@                                                            ',/,&
2960
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES PHASE ',I10    ,/,&
 
2672
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES'               ,/,&
2961
2673
'@    =========                                               ',/,&
2962
2674
'@    ',A6,' DOIT ETRE UN ENTIER EGAL A 0, 1 OU 2             ',/,&
2963
2675
'@    IL VAUT ICI ',I10                                        ,/,&
2972
2684
'@                                                            ',/,&
2973
2685
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
2974
2686
'@                                                            ',/,&
2975
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES PHASE ',I10    ,/,&
 
2687
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES'               ,/,&
2976
2688
'@    =========                                               ',/,&
2977
2689
'@                                                            ',/,&
2978
2690
'@  Avec le modele de turbulence choisi, ITURB = ',I10         ,/,&
3381
3093
 
3382
3094
#else
3383
3095
 
3384
 
 5000 format(                                                           &
3385
 
'@                                                            ',/,&
3386
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3387
 
'@                                                            ',/,&
3388
 
'@ @@ WARNING   : STOP AT THE INITIAL DATA                    ',/,&
3389
 
'@    =========                                               ',/,&
3390
 
'@     WRTONG    NUMBER OF PHASES                             ',/,&
3391
 
'@                                                            ',/,&
3392
 
'@  The number of phases must be an integer strictly          ',/,&
3393
 
'@    positive. Here it has a value of    NPHAS  = ',I10       ,/,&
3394
 
'@                                                            ',/,&
3395
 
'@  The calculation will not be run.                          ',/,&
3396
 
'@                                                            ',/,&
3397
 
'@  Verify   usini1.                                          ',/,&
3398
 
'@                                                            ',/,&
3399
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3400
 
'@                                                            ',/)
3401
 
 5001 format(                                                           &
3402
 
'@                                                            ',/,&
3403
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3404
 
'@                                                            ',/,&
3405
 
'@ @@ WARNING   : STOP AT THE INITIAL DATA VERIFICATION       ',/,&
3406
 
'@    =========                                               ',/,&
3407
 
'@     NUMBER OF PHASES TOO LARGE                             ',/,&
3408
 
'@                                                            ',/,&
3409
 
'@  The number of phases                                      ',/,&
3410
 
'@    - requested        in   usini1   is  NPHAS  = ',I10      ,/,&
3411
 
'@    - maximmum authorised in paramx.h is NPHSMX = ',I10      ,/,&
3412
 
'@                                                            ',/,&
3413
 
'@  The calculation will not be run.                          ',/,&
3414
 
'@                                                            ',/,&
3415
 
'@  Verify   usini1.                                          ',/,&
3416
 
'@                                                            ',/,&
3417
 
'@  NPHSMX must be at least     ',I10                          ,/,&
3418
 
'@                                                            ',/,&
3419
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3420
 
'@                                                            ',/)
3421
3096
 6000 format(                                                           &
3422
3097
'@                                                            ',/,&
3423
3098
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3561
3236
'@                                                            ',/,&
3562
3237
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3563
3238
'@                                                            ',/)
3564
 
 7020 format(                                                           &
3565
 
'@                                                            ',/,&
3566
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3567
 
'@                                                            ',/,&
3568
 
'@ @@ WARNING   : STOP AT THE INITIAL DATA VERIFICATION       ',/,&
3569
 
'@    =========                                               ',/,&
3570
 
'@    CARRIER PHASE IS INCORRECT FOR THE SCALAR  ',I10         ,/,&
3571
 
'@                                                            ',/,&
3572
 
'@  The carrier phase of the scalar ' ,I10                     ,/,&
3573
 
'@    (user scalar          ',I10   ,') indicated in          ',/,&
3574
 
'@    usini1 is  IPHSCA(',I10   ,') = ',I10                    ,/,&
3575
 
'@    It should be between zero and       NPHAS = ',I10        ,/,&
3576
 
'@  The calculation cannot be executed                        ',/,&
3577
 
'@                                                            ',/,&
3578
 
'@  Verify   IPHSCA in   usini1.                              ',/,&
3579
 
'@                                                            ',/,&
3580
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3581
 
'@                                                            ',/)
3582
 
 7021 format(                                                           &
3583
 
'@                                                            ',/,&
3584
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3585
 
'@                                                            ',/,&
3586
 
'@ @@ WARNING   : STOP AT THE INITIAL DATA VERIFICATION       ',/,&
3587
 
'@    =========                                               ',/,&
3588
 
'@    CARRIER PHASE IS INCORRECT FOR THE SCALAR  ',I10         ,/,&
3589
 
'@                                                            ',/,&
3590
 
'@  The carrier phase of the scalar ' ,I10                     ,/,&
3591
 
'@          (scalar in paricular phisics    ',I10   ,')       ',/,&
3592
 
'@           is  IPHSCA(ISCAPP(',I10   ,')) = ',I10            ,/,&
3593
 
'@  It should be between zero and    NPHAS = ',I10             ,/,&
3594
 
'@  The calculation cannot be executed                        ',/,&
3595
 
'@                                                            ',/,&
3596
 
'@  Verify   IPHSCA.                                          ',/,&
3597
 
'@                                                            ',/,&
3598
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3599
 
'@                                                            ',/)
3600
3239
 7030 format(                                                           &
3601
3240
'@                                                            ',/,&
3602
3241
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3781
3420
'@                                                            ',/,&
3782
3421
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3783
3422
'@                                                            ',/)
3784
 
 7060 format(                                                           &
3785
 
'@                                                            ',/,&
3786
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3787
 
'@                                                            ',/,&
3788
 
'@ @@ WARNING   : STOP AT THE INITIAL DATA VERIFICATION       ',/,&
3789
 
'@    =========                                               ',/,&
3790
 
'@    SCALAR   ',I10   ,' DO NOT MODIFY THE CARRIER PHASE     ',/,&
3791
 
'@                                                            ',/,&
3792
 
'@  The scalar  ',I10                                          ,/,&
3793
 
'@    (user scalar                    ',I10   ,') represents  ',/,&
3794
 
'@    the variance of fluctuations of the scalar',I10          ,/,&
3795
 
'@    (user scalar                    ',I10   ,') since       ',/,&
3796
 
'@    ISCAVR(',I10   ,') has a value ',I10   ,' (non-zero)    ',/,&
3797
 
'@                                                            ',/,&
3798
 
'@  The carrier phase IPHSCA(',I10   ,') of the scalar        ',/,&
3799
 
'@    must not be set.                                        ',/,&
3800
 
'@  It will automatically be set equal to the carrier phase   ',/,&
3801
 
'@    of the associated scalar ',I10                           ,/,&
3802
 
'@                                                            ',/,&
3803
 
'@  The calculation cannot be executed                        ',/,&
3804
 
'@                                                            ',/,&
3805
 
'@  Verify   IPHSCA in   usini1.                              ',/,&
3806
 
'@                                                            ',/,&
3807
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3808
 
'@                                                            ',/)
3809
 
 7061 format(                                                           &
3810
 
'@                                                            ',/,&
3811
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3812
 
'@                                                            ',/,&
3813
 
'@ @@ WARNING   : STOP AT THE INITIAL DATA VERIFICATION       ',/,&
3814
 
'@    =========                                               ',/,&
3815
 
'@    SCALAR   ',I10   ,' DO NOT MODIFY THE CARRIER PHASE     ',/,&
3816
 
'@                                                            ',/,&
3817
 
'@  The scalar  ',I10                                          ,/,&
3818
 
'@    (user scalar                    ',I10   ,') represents  ',/,&
3819
 
'@    the variance of fluctuations of the scalar',I10          ,/,&
3820
 
'@    (scalar of specific physics   ',I10   ,') since         ',/,&
3821
 
'@    ISCAVR(',I10   ,')has a value ',I10   ,' (non-zero)     ',/,&
3822
 
'@                                                            ',/,&
3823
 
'@  The carrier phase IPHSCA(',I10   ,') of the scalar        ',/,&
3824
 
'@    must not be set.                                        ',/,&
3825
 
'@  It will automatically be set equal to the carrier phase   ',/,&
3826
 
'@    of the associated scalar ',I10                           ,/,&
3827
 
'@                                                            ',/,&
3828
 
'@  The calculation cannot be executed                        ',/,&
3829
 
'@                                                            ',/,&
3830
 
'@  Verify   IPHSCA in   usini1.                              ',/,&
3831
 
'@                                                            ',/,&
3832
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3833
 
'@                                                            ',/)
3834
 
 7062 format(                                                           &
3835
 
'@                                                            ',/,&
3836
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3837
 
'@                                                            ',/,&
3838
 
'@ @@ WARNING   : STOP AT THE INITIAL DATA VERIFICATION       ',/,&
3839
 
'@    =========                                               ',/,&
3840
 
'@    SCALAR   ',I10   ,' DO NOT MODIFY THE CARRIER PHASE     ',/,&
3841
 
'@                                                            ',/,&
3842
 
'@  The scalar  ',I10                                          ,/,&
3843
 
'@    (scalar of specific physics   ',I10   ,') represents    ',/,&
3844
 
'@    the variance of fluctuations of the scalar',I10          ,/,&
3845
 
'@    (user scalar                    ',I10   ,') since       ',/,&
3846
 
'@ ISCAVR(ISCAPP(',I10   ,'))has a value ',I10   ,' (non-zero)',/,&
3847
 
'@                                                            ',/,&
3848
 
'@  The carrier phase IPHSCA(ISCAPP(',I10   ,')) of the scalar',/,&
3849
 
'@    must not be set.                                        ',/,&
3850
 
'@  It will automatically be set equal to the carrier phase   ',/,&
3851
 
'@    of the associated scalar ',I10                           ,/,&
3852
 
'@                                                            ',/,&
3853
 
'@  The calculation cannot be executed                        ',/,&
3854
 
'@                                                            ',/,&
3855
 
'@  Verify   IPHSCA.                                          ',/,&
3856
 
'@                                                            ',/,&
3857
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3858
 
'@                                                            ',/)
3859
 
 7063 format(                                                           &
3860
 
'@                                                            ',/,&
3861
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3862
 
'@                                                            ',/,&
3863
 
'@ @@ WARNING   : STOP AT THE INITIAL DATA VERIFICATION       ',/,&
3864
 
'@    =========                                               ',/,&
3865
 
'@    SCALAR   ',I10   ,' DO NOT MODIFY THE CARRIER PHASE     ',/,&
3866
 
'@                                                            ',/,&
3867
 
'@  The scalar  ',I10                                          ,/,&
3868
 
'@    (scalar of specific physics   ',I10   ,') represents    ',/,&
3869
 
'@    the variance of fluctuations of the scalar',I10          ,/,&
3870
 
'@    (scalar of specific physics   ',I10   ,') since         ',/,&
3871
 
'@ ISCAVR(ISCAPP(',I10   ,'))has a value ',I10   ,' (non-zero)',/,&
3872
 
'@                                                            ',/,&
3873
 
'@  The carrier phase IPHSCA(ISCAPP(',I10   ,')) of the scalar',/,&
3874
 
'@    must not be set.                                        ',/,&
3875
 
'@  It will automatically be set equal to the carrier phase   ',/,&
3876
 
'@    of the associated scalar ',I10                           ,/,&
3877
 
'@                                                            ',/,&
3878
 
'@  The calculation cannot be executed                        ',/,&
3879
 
'@                                                            ',/,&
3880
 
'@  Verify   IPHSCA.                                          ',/,&
3881
 
'@                                                            ',/,&
3882
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3883
 
'@                                                            ',/)
3884
3423
 7070 format(                                                           &
3885
3424
'@                                                            ',/,&
3886
3425
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3963
3502
'@                                                            ',/,&
3964
3503
'@ @@ WARNING   : STOP AT THE INITIAL DATA VERIFICATION       ',/,&
3965
3504
'@    =========                                               ',/,&
3966
 
'@    PHASE ',I10                                              ,/,&
3967
3505
'@    ',A6,' MUST BE AN INTEGER EQUAL TO 0 OR 1               ',/,&
3968
3506
'@    HERE IT IS  ',I10                                        ,/,&
3969
3507
'@                                                            ',/,&
3979
3517
'@                                                            ',/,&
3980
3518
'@ @@ WARNING   : STOP AT THE INITIAL DATA VERIFICATION       ',/,&
3981
3519
'@    =========                                               ',/,&
3982
 
'@    PHASE ',I10                                              ,/,&
3983
3520
'@    ',A6,' MUST BE AN INTEGER EQUAL TO 1 OR 2               ',/,&
3984
3521
'@    HERE IT IS  ',I10                                        ,/,&
3985
3522
'@                                                            ',/,&
3993
3530
'@                                                            ',/,&
3994
3531
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
3995
3532
'@                                                            ',/,&
3996
 
'@ @@ WARNING   : STOP AT THE INITIAL DATA FOR PHASE'  ,I10    ,/,&
 
3533
'@ @@ WARNING   : STOP AT THE INITIAL DATA'                    ,/,&
3997
3534
'@    =========                                               ',/,&
3998
3535
'@    WITH A SECOND ORDER SCHEME IN TIME: ISCHTP = ', I10      ,/,&
3999
3536
'@    IT IS NECESSARY TO USE A CONSTANT AND UNIFORM TIME STEP ',/,&
4009
3546
'@                                                            ',/,&
4010
3547
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
4011
3548
'@                                                            ',/,&
4012
 
'@ @@ WARNING   : STOP AT THE INITIAL DATA FOR PHASE'  ,I10    ,/,&
 
3549
'@ @@ WARNING   : STOP AT THE INITIAL DATA'                    ,/,&
4013
3550
'@    =========                                               ',/,&
4014
3551
'@    A 2ND ORDER SCHEME HAS BEEN IMPOSED    (ISCHTP = ',I10   ,/,&
4015
3552
'@    WITH K-EPSILON (ITURB = ',I10,' )'                       ,/,&
4027
3564
'@                                                            ',/,&
4028
3565
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
4029
3566
'@                                                            ',/,&
4030
 
'@ @@ WARNING   :     AT THE INITIAL DATA FOR PHASE   ',I10    ,/,&
 
3567
'@ @@ WARNING   :      AT THE INITIAL DATA'                    ,/,&
4031
3568
'@    =========                                               ',/,&
4032
3569
'@    A 1st ORDER SCHEME HAS BEEN IMPOSSED   (ISCHTP = ',I10   ,/,&
4033
3570
'@    FOR LES (ITURB = ',I10,' )'                              ,/,&
4042
3579
'@                                                            ',/,&
4043
3580
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
4044
3581
'@                                                            ',/,&
 
3582
'@ @@ WARNING   : STOP AT THE INITIAL DATA'                    ,/,&
 
3583
'@    =========                                               ',/,&
 
3584
'@    A 2nd ORDER SCHEME HAS BEEN IMPOSED    (ISCHTP = ',I10   ,/,&
 
3585
'@    FOR PHI_FBAR (ITURB = ',I10,' )'                         ,/,&
 
3586
'@                                                            ',/,&
 
3587
'@   The current version does not support the 2nd order with  ',/,&
 
3588
'@   coupling of the source terms of k-epsilon.               ',/,&
 
3589
'@                                                            ',/,&
 
3590
'@  The calculation cannot be executed                        ',/,&
 
3591
'@                                                            ',/,&
 
3592
'@  Modify   usini1.                                          ',/,&
 
3593
'@                                                            ',/,&
 
3594
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
 
3595
'@                                                            ',/)
 
3596
 8117 format(                                                           &
 
3597
'@                                                            ',/,&
 
3598
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
 
3599
'@                                                            ',/,&
4045
3600
'@ @@ WARNING   : STOP AT THE INITIAL DATA FOR  PHASE ',I10    ,/,&
4046
3601
'@    =========                                               ',/,&
4047
3602
'@    A 2nd ORDER SCHEME HAS BEEN IMPOSED    (ISCHTP = ',I10   ,/,&
4048
 
'@    FOR V2F       (ITURB = ',I10,' )'                        ,/,&
 
3603
'@    FOR BL-V2/K  (ITURB = ',I10,' )'                        ,/,&
4049
3604
'@                                                            ',/,&
4050
3605
'@   The current version does not support the 2nd order with  ',/,&
4051
3606
'@   coupling of the source terms of k-epsilon.               ',/,&
4060
3615
'@                                                            ',/,&
4061
3616
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
4062
3617
'@                                                            ',/,&
4063
 
'@ @@ WARNING   : STOP AT THE INITIAL DATA FOR  PHASE ',I10    ,/,&
 
3618
'@ @@ WARNING   : STOP AT THE INITIAL DATA'                    ,/,&
4064
3619
'@    =========                                               ',/,&
4065
3620
'@    A 2nd ORDER SCHEME HAS BEEN IMPOSED    (ISCHTP = ',I10   ,/,&
4066
3621
'@    FOR K-OMEGA   (ITURB = ',I10,' )'                        ,/,&
4074
3629
'@                                                            ',/,&
4075
3630
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
4076
3631
'@                                                            ',/)
 
3632
 8116 format(                                                           &
 
3633
'@                                                            ',/,&
 
3634
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
 
3635
'@                                                            ',/,&
 
3636
'@ @@ WARNING   : STOP AT THE INITIAL DATA'                    ,/,&
 
3637
'@    =========                                               ',/,&
 
3638
'@    A 2nd ORDER SCHEME HAS BEEN IMPOSED    (ISCHTP = ',I10   ,/,&
 
3639
'@    FOR SPALART   (ITURB = ',I10,' )'                        ,/,&
 
3640
'@                                                            ',/,&
 
3641
'@   The current version does not support the 2nd order with  ',/,&
 
3642
'@   coupling of the source terms of Spalart-Allmaras.        ',/,&
 
3643
'@                                                            ',/,&
 
3644
'@  The calculation cannot be executed                        ',/,&
 
3645
'@                                                            ',/,&
 
3646
'@  Modify   usini1.                                          ',/,&
 
3647
'@                                                            ',/,&
 
3648
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
 
3649
'@                                                            ',/)
4077
3650
 8121 format(                                                           &
4078
3651
'@                                                            ',/,&
4079
3652
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
4080
3653
'@                                                            ',/,&
4081
 
'@ @@ WARNING   : STOP AT THE INITIAL DATA FOR  PHASE ',I10    ,/,&
 
3654
'@ @@ WARNING   : STOP AT THE INITIAL DATA'                    ,/,&
4082
3655
'@    =========                                               ',/,&
4083
3656
'@    ',A6,' MUST BE AN INTEGER EQUAL TO 0, 1 OR 2            ',/,&
4084
3657
'@    HERE IT IS  ',I10                                        ,/,&
4093
3666
'@                                                            ',/,&
4094
3667
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
4095
3668
'@                                                            ',/,&
4096
 
'@ @@ WARNING   : STOP AT THE INITIAL DATA FOR  PHASE ',I10    ,/,&
 
3669
'@ @@ WARNING   : STOP AT THE INITIAL DATA'                    ,/,&
4097
3670
'@    =========                                               ',/,&
4098
3671
'@    ',A6,' MUST BE AN INTEGER EQUAL TO 0, 1 OR 2            ',/,&
4099
3672
'@    HERE IT IS  ',I10                                        ,/,&
4108
3681
'@                                                            ',/,&
4109
3682
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
4110
3683
'@                                                            ',/,&
4111
 
'@ @@ WARNING   : STOP AT THE INITIAL DATA FOR  PHASE ',I10    ,/,&
 
3684
'@ @@ WARNING   : STOP AT THE INITIAL DATA'                    ,/,&
4112
3685
'@    =========                                               ',/,&
4113
3686
'@                                                            ',/,&
4114
3687
'@  With the chosen turbulence model   , ITURB = ',I10         ,/,&