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

« back to all changes in this revision

Viewing changes to src/base/impini.f90

  • Committer: Package Import Robot
  • Author(s): Sylvestre Ledru
  • Date: 2011-11-24 00:00:08 UTC
  • mfrom: (6.1.9 sid)
  • Revision ID: package-import@ubuntu.com-20111124000008-2vo99e38267942q5
Tags: 2.1.0-3
Install a missing file

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
!-------------------------------------------------------------------------------
2
2
 
3
 
!     This file is part of the Code_Saturne Kernel, element of the
4
 
!     Code_Saturne CFD tool.
5
 
 
6
 
!     Copyright (C) 1998-2009 EDF S.A., France
7
 
 
8
 
!     contact: saturne-support@edf.fr
9
 
 
10
 
!     The Code_Saturne Kernel is free software; you can redistribute it
11
 
!     and/or modify it under the terms of the GNU General Public License
12
 
!     as published by the Free Software Foundation; either version 2 of
13
 
!     the License, or (at your option) any later version.
14
 
 
15
 
!     The Code_Saturne Kernel is distributed in the hope that it will be
16
 
!     useful, but WITHOUT ANY WARRANTY; without even the implied warranty
17
 
!     of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18
 
!     GNU General Public License for more details.
19
 
 
20
 
!     You should have received a copy of the GNU General Public License
21
 
!     along with the Code_Saturne Kernel; if not, write to the
22
 
!     Free Software Foundation, Inc.,
23
 
!     51 Franklin St, Fifth Floor,
24
 
!     Boston, MA  02110-1301  USA
 
3
! This file is part of Code_Saturne, a general-purpose CFD tool.
 
4
!
 
5
! Copyright (C) 1998-2011 EDF S.A.
 
6
!
 
7
! This program is free software; you can redistribute it and/or modify it under
 
8
! the terms of the GNU General Public License as published by the Free Software
 
9
! Foundation; either version 2 of the License, or (at your option) any later
 
10
! version.
 
11
!
 
12
! This program is distributed in the hope that it will be useful, but WITHOUT
 
13
! ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
 
14
! FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
 
15
! details.
 
16
!
 
17
! You should have received a copy of the GNU General Public License along with
 
18
! this program; if not, write to the Free Software Foundation, Inc., 51 Franklin
 
19
! Street, Fifth Floor, Boston, MA 02110-1301, USA.
25
20
 
26
21
!-------------------------------------------------------------------------------
27
22
 
48
43
!            --- tableau de travail
49
44
!===============================================================================
50
45
 
 
46
!===============================================================================
 
47
! Module files
 
48
!===============================================================================
 
49
 
 
50
use paramx
 
51
use cstnum
 
52
use dimens
 
53
use numvar
 
54
use optcal
 
55
use cstphy
 
56
use entsor
 
57
use albase
 
58
use parall
 
59
use ppppar
 
60
use ppthch
 
61
use coincl
 
62
use cpincl
 
63
use ppincl
 
64
use radiat
 
65
use lagpar
 
66
use lagdim
 
67
use lagran
 
68
use mltgrd
 
69
use mesh
 
70
 
 
71
!===============================================================================
 
72
 
51
73
implicit none
52
74
 
53
 
!===============================================================================
54
 
! Common blocks
55
 
!===============================================================================
56
 
 
57
 
include "paramx.h"
58
 
include "cstnum.h"
59
 
include "dimens.h"
60
 
include "numvar.h"
61
 
include "optcal.h"
62
 
include "cstphy.h"
63
 
include "entsor.h"
64
 
include "albase.h"
65
 
include "ppppar.h"
66
 
include "ppthch.h"
67
 
include "coincl.h"
68
 
include "cpincl.h"
69
 
include "ppincl.h"
70
 
include "radiat.h"
71
 
include "lagpar.h"
72
 
include "lagdim.h"
73
 
include "lagran.h"
74
 
include "parall.h"
75
 
include "mltgrd.h"
76
 
 
77
 
!===============================================================================
78
 
 
79
75
! Arguments
80
76
 
81
77
 
82
78
! Local variables
83
79
 
84
80
character        name*300, chaine*80
85
 
integer          iok20 , iok21 , iok30 , iok31 , iok50 , iok60
86
 
integer          ii    , jj    , ivar  , iphas , iiesca, iest
 
81
integer          iok20 , iok21 , iok30 , iok31 , iok50 , iok51 , iok60
 
82
integer          iok70
 
83
integer          ii    , jj    , ivar  , iiesca, iest
87
84
integer          ipp   , iwar  , imom
88
85
integer          nbccou
89
86
 
194
191
 
195
192
write(nfecra,1500)
196
193
write(nfecra,1510) nprfml,nfml
197
 
write(nfecra,1520) nphas,nvar,nscal,nscaus,nscapp,                &
 
194
write(nfecra,1520) nvar,nscal,nscaus,nscapp,                &
198
195
                   nproce,nprofa,nprofb
199
196
 
200
197
write(nfecra,9900)
212
209
'       NFML   = ',4X,I10,    ' (Nb de familles              )',/)
213
210
 1520 format(                                                           &
214
211
' --- Physique'                                                ,/,&
215
 
'       NPHAS  = ',4X,I10,    ' (Nb de phases                )',/,&
216
212
'       NVAR   = ',4X,I10,    ' (Nb de variables             )',/,&
217
213
'       NSCAL  = ',4X,I10,    ' (Nb de scalaires             )',/,&
218
214
'       NSCAUS = ',4X,I10,    ' (Nb de scalaires utilisateur )',/,&
233
229
'       NFML   = ',4X,I10,    ' (Nb families                 )',/)
234
230
 1520 format(                                                           &
235
231
' --- Physics'                                                 ,/,&
236
 
'       NPHAS  = ',4X,I10,    ' (Nb phases                   )',/,&
237
232
'       NVAR   = ',4X,I10,    ' (Nb variables                )',/,&
238
233
'       NSCAL  = ',4X,I10,    ' (Nb scalars                  )',/,&
239
234
'       NSCAUS = ',4X,I10,    ' (Nb user scalars             )',/,&
254
249
write(nfecra,2010) gx,gy,gz
255
250
write(nfecra,2011) omegax, omegay, omegaz, icorio
256
251
 
257
 
do iphas = 1, nphas
258
 
    write(nfecra,2020) iphas,                                     &
259
 
                       ro0   (iphas),viscl0(iphas),               &
260
 
                       cp0   (iphas),icp   (iphas),               &
261
 
                       p0    (iphas),pred0 (iphas),               &
262
 
                       t0    (iphas),                             &
263
 
                       irovar(iphas),ivivar(iphas),               &
264
 
                       (xyzp0(ii,iphas),ii=1,3)
265
 
enddo
 
252
write(nfecra,2020) ro0   ,viscl0,               &
 
253
     cp0   ,icp   ,               &
 
254
     p0    ,pred0 ,               &
 
255
     t0    ,                             &
 
256
     irovar,ivivar,               &
 
257
     (xyzp0(ii),ii=1,3)
266
258
 
267
259
if (ippmod(iphpar).ge.1) write(nfecra,2030) diftl0
268
260
 
286
278
'       OMEGAZ = ', E14.5,    ' (Composante z du vecteur rot.)',/,&
287
279
'       ICORIO = ', I10,      ' (Termes source de Coriolis   )',/)
288
280
 2020 format(                                                           &
289
 
'  -- Phase : ',I10                                            ,/,&
 
281
'  -- Phase continue : '                                       ,/,&
290
282
                                                                /,&
291
283
'       RO0    = ', E14.5,    ' (Masse volumique     de ref. )',/,&
292
284
'       VISCL0 = ', E14.5,    ' (Visc. molec. dynam. de ref. )',/,&
320
312
'       OMEGAZ = ', E14.5,    ' (Rotation vector z component )',/,&
321
313
'       ICORIO = ', I10,      ' (Coriolis source terms       )',/)
322
314
 2020 format(                                                           &
323
 
'  -- Phase: ',I10                                             ,/,&
 
315
'  -- Continuous phase: '                                      ,/,&
324
316
                                                                /,&
325
317
'       RO0    = ', E14.5,    ' (Reference density           )',/,&
326
318
'       VISCL0 = ', E14.5,    ' (Ref. molecular dyn. visc.   )',/,&
346
338
 
347
339
!   - Modeles
348
340
 
349
 
do iphas = 1, nphas
350
 
  write(nfecra,2515)iphas,                                        &
351
 
    iturb(iphas),ideuch(iphas),ypluli(iphas),ilogpo(iphas),       &
352
 
    igrhok(iphas),iscalt(iphas)
353
 
  if(iturb(iphas).eq.10) then
354
 
    write(nfecra,2516)                                            &
355
 
      xlomlg(iphas)
356
 
  elseif(iturb(iphas).eq.20) then
357
 
    write(nfecra,2517)                                            &
358
 
      almax(iphas) ,uref(iphas)  ,                                &
359
 
      iclkep(iphas),ikecou(iphas),igrake(iphas)
360
 
    if (ikecou(iphas).eq.0 .and. idtvar.ge.0) then
361
 
      write(nfecra,2527) relaxv(ik(iphas)),relaxv(iep(iphas))
362
 
    else
363
 
      write(nfecra,2529)
364
 
    endif
365
 
  elseif(iturb(iphas).eq.21) then
366
 
    write(nfecra,2518)                                            &
367
 
      almax(iphas) ,uref(iphas)  ,                                &
368
 
      iclkep(iphas),ikecou(iphas),igrake(iphas)
369
 
    if (ikecou(iphas).eq.0.and. idtvar.ge.0) then
370
 
      write(nfecra,2527) relaxv(ik(iphas)),relaxv(iep(iphas))
371
 
    else
372
 
      write(nfecra,2529)
373
 
    endif
374
 
  elseif(iturb(iphas).eq.30) then
375
 
    write(nfecra,2519)                                            &
376
 
      almax(iphas) ,uref(iphas)  ,                                &
377
 
      irijnu(iphas),irijrb(iphas),irijec(iphas),                  &
378
 
      idifre(iphas),igrari(iphas),iclsyr(iphas),iclptr(iphas)
379
 
  elseif(iturb(iphas).eq.31) then
380
 
    write(nfecra,2520)                                            &
381
 
      almax(iphas) ,uref(iphas)  ,                                &
382
 
      irijnu(iphas),irijrb(iphas),                                &
383
 
      igrari(iphas),iclsyr(iphas),iclptr(iphas)
384
 
  elseif(itytur(iphas).eq.4) then
385
 
    write(nfecra,2521)                                            &
386
 
      csmago(iphas),cwale(iphas), xlesfl(iphas),ales(iphas),      &
387
 
      bles(iphas),idries(iphas),cdries(iphas), xlesfd(iphas),     &
388
 
      smagmx(iphas), ivrtex
389
 
  elseif(iturb(iphas).eq.50) then
390
 
    write(nfecra,2522)                                            &
391
 
      almax(iphas) ,uref(iphas)  ,                                &
392
 
      iclkep(iphas),ikecou(iphas),igrake(iphas)
393
 
    if (ikecou(iphas).eq.0 .and. idtvar.ge.0) then
394
 
      write(nfecra,2527) relaxv(ik(iphas)),relaxv(iep(iphas))
395
 
    else
396
 
      write(nfecra,2529)
397
 
    endif
398
 
  elseif(iturb(iphas).eq.60) then
399
 
    write(nfecra,2523)                                            &
400
 
      almax(iphas) ,uref(iphas)  ,                                &
401
 
      ikecou(iphas),igrake(iphas)
402
 
    if (ikecou(iphas).eq.0 .and. idtvar.ge.0) then
403
 
      write(nfecra,2528) relaxv(ik(iphas)),relaxv(iomg(iphas))
404
 
    else
405
 
      write(nfecra,2529)
406
 
    endif
407
 
  endif
408
 
enddo
 
341
write(nfecra,2515)                                              &
 
342
     iturb,ideuch,ypluli,ilogpo,       &
 
343
     igrhok,iscalt
 
344
if(iturb.eq.10) then
 
345
  write(nfecra,2516)                                            &
 
346
       xlomlg
 
347
elseif(iturb.eq.20) then
 
348
  write(nfecra,2517)                                            &
 
349
       almax ,uref  ,                                &
 
350
       iclkep,ikecou,igrake
 
351
  if (ikecou.eq.0 .and. idtvar.ge.0) then
 
352
    write(nfecra,2527) relaxv(ik),relaxv(iep)
 
353
  else
 
354
    write(nfecra,2540)
 
355
  endif
 
356
elseif(iturb.eq.21) then
 
357
  write(nfecra,2518)                                            &
 
358
       almax ,uref  ,                                &
 
359
       iclkep,ikecou,igrake
 
360
  if (ikecou.eq.0.and. idtvar.ge.0) then
 
361
    write(nfecra,2527) relaxv(ik),relaxv(iep)
 
362
  else
 
363
    write(nfecra,2540)
 
364
  endif
 
365
elseif(iturb.eq.30) then
 
366
  write(nfecra,2519)                                            &
 
367
       almax ,uref  ,                                &
 
368
       irijnu,irijrb,irijec,                  &
 
369
       idifre,igrari,iclsyr,iclptr
 
370
elseif(iturb.eq.31) then
 
371
  write(nfecra,2520)                                            &
 
372
       almax ,uref  ,                                &
 
373
       irijnu,irijrb,                                &
 
374
       igrari,iclsyr,iclptr
 
375
elseif(itytur.eq.4) then
 
376
  write(nfecra,2521)                                            &
 
377
       csmago,cwale, xlesfl,ales,      &
 
378
       bles,idries,cdries, xlesfd,     &
 
379
       smagmx, ivrtex
 
380
elseif(iturb.eq.50) then
 
381
  write(nfecra,2522)                                            &
 
382
       almax ,uref  ,                                &
 
383
       iclkep,ikecou,igrake
 
384
  if (ikecou.eq.0 .and. idtvar.ge.0) then
 
385
    write(nfecra,2527) relaxv(ik),relaxv(iep)
 
386
  else
 
387
    write(nfecra,2540)
 
388
  endif
 
389
elseif(iturb.eq.51) then
 
390
  write(nfecra,2524)                                            &
 
391
    almax ,uref  ,                                &
 
392
    iclkep,ikecou,igrake
 
393
  if (ikecou.eq.0 .and. idtvar.ge.0) then
 
394
    write(nfecra,2527) relaxv(ik),relaxv(iep)
 
395
  else
 
396
    write(nfecra,2529)
 
397
  endif
 
398
elseif(iturb.eq.60) then
 
399
  write(nfecra,2523)                                            &
 
400
       almax ,uref  ,                                &
 
401
       ikecou,igrake
 
402
  if (ikecou.eq.0 .and. idtvar.ge.0) then
 
403
    write(nfecra,2528) relaxv(ik),relaxv(iomg)
 
404
  else
 
405
    write(nfecra,2540)
 
406
  endif
 
407
elseif(iturb.eq.70) then
 
408
  write(nfecra,2529) almax , uref , relaxv(inusa)
 
409
endif
409
410
 
410
411
!   - Constantes
411
412
 
416
417
iok30 = 0
417
418
iok31 = 0
418
419
iok50 = 0
 
420
iok51 = 0
419
421
iok60 = 0
420
 
do iphas = 1, nphas
421
 
  if(iturb(iphas).eq.20) then
422
 
    iok20 = 20
423
 
  endif
424
 
  if(iturb(iphas).eq.21) then
425
 
    iok21 = 21
426
 
  endif
427
 
  if(iturb(iphas).eq.30) then
428
 
    iok30 = 30
429
 
  endif
430
 
  if(iturb(iphas).eq.31) then
431
 
    iok31 = 31
432
 
  endif
433
 
  if(iturb(iphas).eq.50) then
434
 
    iok50 = 50
435
 
  endif
436
 
  if(iturb(iphas).eq.60) then
437
 
    iok60 = 60
438
 
  endif
439
 
enddo
 
422
iok70 = 0
 
423
if(iturb.eq.20) then
 
424
  iok20 = 20
 
425
endif
 
426
if(iturb.eq.21) then
 
427
  iok21 = 21
 
428
endif
 
429
if(iturb.eq.30) then
 
430
  iok30 = 30
 
431
endif
 
432
if(iturb.eq.31) then
 
433
  iok31 = 31
 
434
endif
 
435
if(iturb.eq.50) then
 
436
  iok50 = 50
 
437
endif
 
438
if(iturb.eq.51) then
 
439
  iok51 = 51
 
440
endif
 
441
if(iturb.eq.60) then
 
442
  iok60 = 60
 
443
endif
 
444
if(iturb.eq.70) then
 
445
  iok70 = 70
 
446
endif
440
447
if(iok20.gt.0) then
441
448
  write(nfecra,2531)ce1,ce2,sigmak,sigmae,cmu
442
449
endif
455
462
  write(nfecra,2535) cv2fa1,cv2fe2,sigmak,sigmae,cv2fmu,cv2fct,   &
456
463
       cv2fcl,cv2fet,cv2fc1,cv2fc2
457
464
endif
 
465
if(iok51.gt.0) then
 
466
  write(nfecra,2538) cpale1,cpale2,cpale3,cpale4,sigmak,cpalse,cpalmu,cpalct, &
 
467
       cpalcl,cpalet,cpalc1,cpalc2
 
468
endif
458
469
if(iok60.gt.0) then
459
470
  write(nfecra,2536) ckwsk1,ckwsk2,ckwsw1,ckwsw2,ckwbt1,ckwbt2,   &
460
471
       ckwgm1,ckwgm2,ckwa1,ckwc1,cmu
461
472
endif
 
473
if(iok70.gt.0) then
 
474
  write(nfecra,2537) csab1,csab2,csasig,csav1,csaw1,csaw2,csaw3
 
475
endif
462
476
 
463
477
write(nfecra,9900)
464
478
 
470
484
' ** TURBULENCE                                               ',/,&
471
485
'    ----------                                               ',/)
472
486
 2515 format(                                                           &
473
 
' --- Phase : ',I10                                            ,/,&
 
487
' --- Phase continue : '                                       ,/,&
474
488
                                                                /,&
475
489
'   - Communs                                                 ',/,&
476
490
'       ITURB  = ',4X,I10,    ' (Modele de turbulence        )',/,&
547
561
'       ICLKEP = ',4X,I10,    ' (Mode de clipping k-epsilon  )',/,&
548
562
'       IKECOU = ',4X,I10,    ' (Mode de couplage k-epsilon  )',/,&
549
563
'       IGRAKE = ',4X,I10,    ' (Prise en compte de gravite  )')
 
564
 2524 format(                                                           &
 
565
'   - v2f BL-v2/k         (ITURB = 51)                        ',/,&
 
566
'       ALMAX  = ', E14.5,    ' (Longueur caracteristique    )',/,&
 
567
'       UREF   = ', E14.5,    ' (Vitesse  caracteristique    )',/,&
 
568
'       ICLKEP = ',4X,I10,    ' (Mode de clipping k-epsilon  )',/,&
 
569
'       IKECOU = ',4X,I10,    ' (Mode de couplage k-epsilon  )',/,&
 
570
'       IGRAKE = ',4X,I10,    ' (Prise en compte de gravite  )')
550
571
 2523 format(                                                           &
551
572
'   - k-omega SST         (ITURB = 60)                        ',/,&
552
573
'       ALMAX  = ', E14.5,    ' (Longueur caracteristique    )',/,&
559
580
 2528 format(                                                           &
560
581
'       RELAXV = ', E14.5,    ' pour k     (Relaxation)       ',/,&
561
582
'       RELAXV = ', E14.5,    ' pour omega (Relaxation)       ',/)
562
 
 2529 format(/)
 
583
 2529 format(                                                           &
 
584
'   - Spalart-Allmares    (ITURB = 70)                        ',/,&
 
585
'       ALMAX  = ', E14.5,    ' (Longueur caracteristique    )',/,&
 
586
'       UREF   = ', E14.5,    ' (Vitesse  caracteristique    )',/,&
 
587
'       RELAXV = ', E14.5,    ' pour nu (Relaxation)          ',/)
563
588
 
564
589
 2530 format(                                                           &
565
590
' --- Constantes                                              ',/,&
622
647
'       CV2FET = ', E14.5,    ' (Constante C_eta             )',/,&
623
648
'       CV2FC1 = ', E14.5,    ' (Constante C1                )',/,&
624
649
'       CV2FC2 = ', E14.5,    ' (Constante C2                )',/)
 
650
 2538 format(                                                           &
 
651
'   - v2f BL-v2/k         (ITURB = 51)'                        ,/,&
 
652
'       CPALE1 = ', E14.5,    ' (Cepsilon 1 : coef de Prod.  )',/,&
 
653
'       CPALE2 = ', E14.5,    ' (Cepsilon 2 : coef de Diss.  )',/,&
 
654
'       CPALE3 = ', E14.5,    ' (Cepsilon 3 : coef terme E   )',/,&
 
655
'       CPALE4 = ', E14.5,    ' (Cepsilon 4 : coef Diss. mod.)',/,&
 
656
'       SIGMAK = ', E14.5,    ' (Prandtl relatif a k         )',/,&
 
657
'       CPALSE = ', E14.5,    ' (Prandtl relatif a epsilon   )',/,&
 
658
'       CPALMU = ', E14.5,    ' (Constante Cmu               )',/,&
 
659
'       CPALCT = ', E14.5,    ' (Constante CT                )',/,&
 
660
'       CPALCL = ', E14.5,    ' (Constante CL                )',/,&
 
661
'       CPALET = ', E14.5,    ' (Constante C_eta             )',/,&
 
662
'       CPALC1 = ', E14.5,    ' (Constante C1                )',/,&
 
663
'       CPALC2 = ', E14.5,    ' (Constante C2                )',/)
625
664
 2536 format(                                                           &
626
665
'   - k-omega SST         (ITURB = 60)'                        ,/,&
627
666
'       CKWSK1 = ', E14.5,    ' (Constante sigma_k1          )',/,&
636
675
'       CKWC1  = ', E14.5,    ' (Cste c1 pour limiteur prod  )',/,&
637
676
'       CMU    = ', E14.5,    ' (Cste Cmu (ou Beta*) pour    )',/,&
638
677
'                                    conversion omega/epsilon)',/)
 
678
 2537 format(                                                           &
 
679
'   - Spalart-Allmaras    (ITURB = 70)'                        ,/,&
 
680
'       CSAB1  = ', E14.5,    ' (Constante b1                )',/,&
 
681
'       CSAB2  = ', E14.5,    ' (Constante b2                )',/,&
 
682
'       CSASIG = ', E14.5,    ' (Constante sigma             )',/,&
 
683
'       CSAV1  = ', E14.5,    ' (Constante v1                )',/,&
 
684
'       CSAW1  = ', E14.5,    ' (Constante w1                )',/,&
 
685
'       CSAW2  = ', E14.5,    ' (Constante w2                )',/,&
 
686
'       CSAW3  = ', E14.5,    ' (Constante w3                )',/)
 
687
 2540 format(/)
639
688
 
640
689
#else
641
690
 
644
693
' ** TURBULENCE'                                               ,/,&
645
694
'    ----------'                                               ,/)
646
695
 2515 format(                                                           &
647
 
' --- Phase: ',I10                                             ,/,&
 
696
' --- Continuous phase: '                                      ,/,&
648
697
                                                                /,&
649
698
'   - Commons                                                 ',/,&
650
699
'       ITURB  = ',4X,I10,    ' (Turbulence model            )',/,&
720
769
'       ICLKEP = ',4X,I10,    ' (k-epsilon clipping model    )',/,&
721
770
'       IKECOU = ',4X,I10,    ' (k-epsilon coupling mode     )',/,&
722
771
'       IGRAKE = ',4X,I10,    ' (Account for gravity         )')
 
772
 2524 format(                                                           &
 
773
'   - v2f BL-v2/k         (ITURB = 51)                        ',/,&
 
774
'       ALMAX  = ', E14.5,    ' (Characteristic length       )',/,&
 
775
'       UREF   = ', E14.5,    ' (Characteristic velocity     )',/,&
 
776
'       ICLKEP = ',4X,I10,    ' (k-epsilon clipping model    )',/,&
 
777
'       IKECOU = ',4X,I10,    ' (k-epsilon coupling mode     )',/,&
 
778
'       IGRAKE = ',4X,I10,    ' (Account for gravity         )')
723
779
 2523 format(                                                           &
724
780
'   - k-omega SST         (ITURB = 60)                        ',/,&
725
781
'       ALMAX  = ', E14.5,    ' (Characteristic length       )',/,&
732
788
 2528 format(                                                           &
733
789
'       RELAXV = ', E14.5,    ' for k      (Relaxation)       ',/,&
734
790
'       RELAXV = ', E14.5,    ' for omega  (Relaxation)       ',/)
735
 
 2529 format(/)
 
791
 2529 format(                                                           &
 
792
'   - Spalart-Allmares    (ITURB = 70)                        ',/,&
 
793
'       ALMAX  = ', E14.5,    ' (Characteristic length       )',/,&
 
794
'       UREF   = ', E14.5,    ' (Characteristic velocity     )',/,&
 
795
'       RELAXV = ', E14.5,    ' for nu (Relaxation)           ',/)
736
796
 
737
797
 2530 format(                                                           &
738
798
' --- Constants'                                               ,/,&
795
855
'       CV2FET = ', E14.5,    ' (C_eta constant              )',/,&
796
856
'       CV2FC1 = ', E14.5,    ' (C1 constant                 )',/,&
797
857
'       CV2FC2 = ', E14.5,    ' (C2 constant                 )',/)
 
858
 2538 format(                                                           &
 
859
'   - v2f BL-v2/k         (ITURB = 51)'                        ,/,&
 
860
'       CPALE1 = ', E14.5,    ' (Cepsilon 1 : Prod. coeff.   )',/,&
 
861
'       CPALE2 = ', E14.5,    ' (Cepsilon 2 : Diss. coeff.   )',/,&
 
862
'       CPALE3 = ', E14.5,    ' (Cepsilon 3 : E term coeff.  )',/,&
 
863
'       CPALE4 = ', E14.5,    ' (Cepsilon 4 : Mod Diss. coef.)',/,&
 
864
'       SIGMAK = ', E14.5,    ' (Prandtl relative to k       )',/,&
 
865
'       CPALSE = ', E14.5,    ' (Prandtl relative to epsilon )',/,&
 
866
'       CPALMU = ', E14.5,    ' (Cmu constant               )',/,&
 
867
'       CPALCT = ', E14.5,    ' (CT constant                )',/,&
 
868
'       CPALCL = ', E14.5,    ' (CL constant                )',/,&
 
869
'       CPALET = ', E14.5,    ' (C_eta constant             )',/,&
 
870
'       CPALC1 = ', E14.5,    ' (C1 constant                )',/,&
 
871
'       CPALC2 = ', E14.5,    ' (C2 constant                )',/)
798
872
 2536 format(                                                           &
799
873
'   - k-omega SST         (ITURB = 60)                        ',/,&
800
874
'       CKWSK1 = ', E14.5,    ' (sigma_k1 constant           )',/,&
809
883
'       CKWC1  = ', E14.5,    ' (c1 const. for prod. limiter )',/,&
810
884
'       CMU    = ', E14.5,    ' (Cmu (or Beta*) constant for )',/,&
811
885
'                                    omega/epsilon conversion)',/)
 
886
 2537 format(                                                           &
 
887
'   - Spalart-Allmaras    (ITURB = 70)'                        ,/,&
 
888
'       CSAB1  = ', E14.5,    ' (b1 constant                 )',/,&
 
889
'       CSAB2  = ', E14.5,    ' (b2 constant                 )',/,&
 
890
'       CSASIG = ', E14.5,    ' (sigma constant              )',/,&
 
891
'       CSAV1  = ', E14.5,    ' (v1 constant                 )',/,&
 
892
'       CSAW1  = ', E14.5,    ' (w1 constant                 )',/,&
 
893
'       CSAW2  = ', E14.5,    ' (w2 constant                 )',/,&
 
894
'       CSAW3  = ', E14.5,    ' (w3 constant                 )',/)
 
895
 
 
896
 2540 format(/)
812
897
 
813
898
#endif
814
899
 
815
900
! --- Viscosite secondaire
816
901
 
817
902
write(nfecra,2610)
818
 
do iphas = 1, nphas
819
 
  write(nfecra,2620) iphas, ivisse(iphas)
820
 
enddo
 
903
write(nfecra,2620) ivisse
821
904
 
822
905
write(nfecra,9900)
823
906
 
829
912
' ** VISCOSITE SECONDAIRE                                     ',/,&
830
913
'    --------------------                                     ',/)
831
914
 2620 format(                                                           &
832
 
' --- Phase : ',I10                                            ,/,&
 
915
' --- Phase continue : ',I10                                   ,/,&
833
916
'       IVISSE = ',4X,I10,    ' (1 : pris en compte          )',/)
834
917
 
835
918
#else
839
922
' ** SECONDARY VISCOSITY'                                      ,/,&
840
923
'    -------------------'                                      ,/)
841
924
 2620 format(                                                           &
842
 
' --- Phase: ',I10                                             ,/,&
 
925
' --- Continuous phase: ',I10                                  ,/,&
843
926
'       IVISSE = ',4X,I10,    ' (1: accounted for            )',/)
844
927
 
845
928
#endif
847
930
! --- Rayonnement thermique
848
931
 
849
932
if (iirayo.gt.0) then
 
933
 
850
934
  write(nfecra,2630)
851
935
 
852
 
  write(nfecra,2640) irapha, iirayo, iscalt(irapha),       &
853
 
                     iscsth(iscalt(irapha))
 
936
  write(nfecra,2640) iirayo, iscalt,       &
 
937
                     iscsth(iscalt)
854
938
 
855
939
  write(nfecra,2650) isuird, nfreqr, ndirec,                      &
856
940
                     idiver, imodak, iimpar, iimlum
871
955
' ** TRANSFERTS THERMIQUES RADIATIFS                          ',/,&
872
956
'    -------------------------------                          ',/)
873
957
 2640 format(                                                           &
874
 
' --- Phase : ',I10                                            ,/,&
 
958
' --- Phase continue :'                                        ,/,&
875
959
'       IIRAYO = ',4X,I10,    ' (0 : non ; 1 : DOM ; 2 : P-1 )',/,&
876
960
'       ICSALT = ',4X,I10,    ' (Num du sca thermique associe)',/,&
877
961
'       ISCSTH = ',4X,I10,    ' (-1 : T(C) ; 1 : T(K) ; 2 : H)',/)
896
980
' ** RADIATIVE THERMAL TRANSFER'                               ,/,&
897
981
'    --------------------------'                               ,/)
898
982
 2640 format(                                                           &
899
 
' --- Phase: ',I10                                             ,/,&
 
983
' --- Continuous phase:'                                       ,/,&
900
984
'       IIRAYO = ',4X,I10,    ' (0: no; 1: DOM; 2: P-1       )',/,&
901
985
'       ICSALT = ',4X,I10,    ' (Assoc. thermal scalar num.  )',/,&
902
986
'       ISCSTH = ',4X,I10,    ' (-1: T(C); 1: T(K); 2: H     )',/)
920
1004
 
921
1005
if (ippmod(icompf).ge.0) then
922
1006
  write(nfecra,2700)
923
 
  do iphas = 1, nphas
924
 
    write(nfecra,2710) iphas,                                     &
925
 
         icv(iphas),                                              &
926
 
         iviscv(iphas),viscv0(iphas),                             &
927
 
         icfgrp(iphas)
928
 
  enddo
 
1007
  write(nfecra,2710)                                            &
 
1008
       icv,                                              &
 
1009
       iviscv,viscv0,                             &
 
1010
       icfgrp
929
1011
 
930
1012
  write(nfecra,9900)
931
1013
 
938
1020
' ** COMPRESSIBLE : donnees complementaires                   ',/,&
939
1021
'    ------------                                             ',/)
940
1022
 2710 format(                                                           &
941
 
' --- Phase : ',I10                                            ,/,&
 
1023
' --- Phase continue : '                                       ,/,&
942
1024
'       ICV    = ',4X,I10,    ' (0 : Cv cst ; 1 : variable   )',/,&
943
1025
'       IVISCV = ',4X,I10,    ' (0 : kappa cst ; 1 : variable ',/,&
944
1026
'                                kappa : viscosite en volume  ',/,&
954
1036
' ** COMPRESSIBLE: additional data'                            ,/,&
955
1037
'    ------------                                             ',/)
956
1038
 2710 format(                                                           &
957
 
' --- Phase : ',I10                                            ,/,&
 
1039
' --- Continuous phase : '                                     ,/,&
958
1040
'       ICV    = ',4X,I10,    ' (0: Cv cst; 1: variable      )',/,&
959
1041
'       IVISCV = ',4X,I10,    ' (0: kappa cst; 1: variable'    ,/,&
960
1042
'                                kappa: volume viscosity'      ,/,&
1028
1110
!   - Ordre du schema en temps
1029
1111
 
1030
1112
  write(nfecra,3060)
1031
 
  do iphas = 1, nphas
1032
 
    write(nfecra,3061) iphas, ischtp(iphas)
1033
 
  enddo
 
1113
  write(nfecra,3061) ischtp
1034
1114
  write(nfecra,3062)
1035
1115
 
1036
1116
endif
1108
1188
 3060 format(                                                           &
1109
1189
' --- Ordre du schema en temps de base'                          )
1110
1190
 3061 format(                                                           &
1111
 
'     Phase : ',I10                                            ,/,&
1112
1191
'       ISCHTP = ',4X,I10,    ' (1 : ordre 1 ; 2 : ordre 2   )'  )
1113
1192
 3062 format(                                                           &
1114
1193
'                                                             '  )
1183
1262
 3060 format(                                                           &
1184
1263
' --- Order of base time stepping scheme'                        )
1185
1264
 3061 format(                                                           &
1186
 
'     Phase: ',I10                                             ,/,&
1187
1265
'       ISCHTP = ',4X,I10,    ' (1: order 1; 2: order 2      )'  )
1188
1266
 3062 format(                                                           &
1189
1267
'                                                             '  )
1212
1290
! --- Stokes
1213
1291
 
1214
1292
write(nfecra,4110) iphydr,icalhy,iprco,ipucou,nterup
1215
 
do iphas = 1, nphas
1216
 
  write(nfecra,4111)iphas,                                        &
1217
 
                    irevmc(iphas)
1218
 
  if (idtvar.ge.0) then
1219
 
    write(nfecra,4112) relaxv(ipr(iphas)),arak(iphas)
1220
 
  else
1221
 
    write(nfecra,4113) arak(iphas)*relaxv(iu(iphas))
1222
 
  endif
1223
 
  write(nfecra,4114)istmpf(iphas),thetfl(iphas),                  &
1224
 
                    iroext(iphas),thetro(iphas),                  &
1225
 
                    iviext(iphas),thetvi(iphas),                  &
1226
 
                    icpext(iphas),thetcp(iphas),                  &
1227
 
                    thetsn(iphas),thetst(iphas),epsup(iphas)
1228
 
enddo
 
1293
write(nfecra,4111) irevmc
 
1294
if (idtvar.ge.0) then
 
1295
  write(nfecra,4112) relaxv(ipr),arak
 
1296
else
 
1297
  write(nfecra,4113) arak*relaxv(iu)
 
1298
endif
 
1299
write(nfecra,4114)istmpf,thetfl,                  &
 
1300
     iroext,thetro,                  &
 
1301
     iviext,thetvi,                  &
 
1302
     icpext,thetcp,                  &
 
1303
     thetsn,thetst,epsup
1229
1304
 
1230
1305
write(nfecra,9900)
1231
1306
 
1274
1349
'       NTERUP = ',4X,I10,  ' (n : avec n sweep sur navsto    ',/,&
1275
1350
'                ',14X,     '      pour couplage vites/pressio',/)
1276
1351
 4111 format(                                                           &
1277
 
'  -- Phase : ',I10                                            ,/,&
 
1352
'  -- Phase continue : '                                       ,/,&
1278
1353
                                                                /,&
1279
1354
'       IREVMC = ',4X,I10,    ' (Mode de reconstruction vites)',/)
1280
1355
 4112 format(                                                           &
1357
1432
'       NTERUP = ',4X,I10,  ' (n: n sweeps on navsto for'      ,/,&
1358
1433
'                ',14X,     '     velocity/pressure coupling )',/)
1359
1434
 4111 format(                                                           &
1360
 
'  -- Phase: ',I10                                             ,/,&
 
1435
'  -- Continuous phase: '                                      ,/,&
1361
1436
                                                                /,&
1362
1437
'       IREVMC = ',4X,I10,    ' (Velocity reconstruction mode)',/)
1363
1438
 4112 format(                                                           &
1433
1508
! --- Estimateurs d'erreurs pour Navier-Stokes
1434
1509
 
1435
1510
iiesca = 0
1436
 
do iphas = 1, nphas
1437
 
  do iest = 1, nestmx
1438
 
    if(iescal(iest,iphas).gt.0) then
1439
 
      iiesca = 1
1440
 
    endif
1441
 
  enddo
 
1511
do iest = 1, nestmx
 
1512
  if(iescal(iest).gt.0) then
 
1513
    iiesca = 1
 
1514
  endif
1442
1515
enddo
1443
1516
 
1444
1517
if(iiesca.gt.0) then
1445
1518
  write(nfecra,4820)
1446
 
  do iphas = 1, nphas
1447
 
    write(nfecra,4821)iphas
1448
 
    do iest = 1, nestmx
1449
 
      write(nfecra,4822)iest, iescal(iest,iphas)
1450
 
    enddo
1451
 
    write(nfecra,4823)
 
1519
  write(nfecra,4821)
 
1520
  do iest = 1, nestmx
 
1521
    write(nfecra,4822)iest, iescal(iest)
1452
1522
  enddo
 
1523
  write(nfecra,4823)
1453
1524
  write(nfecra,4824)iespre,iesder,iescor,iestot
1454
1525
  write(nfecra,9900)
1455
1526
endif
1532
1603
' ** ESTIMATEURS D''ERREUR POUR NAVIER-STOKES'                 ,/,&
1533
1604
'    ----------------------------------------'                 ,/)
1534
1605
 4821 format(                                                           &
1535
 
' --- Phase : ',I10                                            ,/,&
1536
 
                                                                /,&
1537
1606
'----------------------------------------'                     ,/,&
1538
1607
' Estimateur      IESCAL (mode de calcul)'                     ,/,&
1539
1608
'----------------------------------------'                       )
1694
1763
' ** ERROR ESTIMATORS FOR NAVIER-STOKES'                       ,/,&
1695
1764
'    ----------------------------------'                       ,/)
1696
1765
 4821 format(                                                           &
1697
 
' --- Phase: ',I10                                             ,/,&
1698
 
                                                                /,&
1699
1766
'------------------------------------------'                   ,/,&
1700
1767
' Estimateur      IESCAL (calculation mode)'                   ,/,&
1701
1768
'------------------------------------------'                     )
1840
1907
enddo
1841
1908
write(nfecra,5530)
1842
1909
 
 
1910
call clmimp
 
1911
!==========
 
1912
 
1843
1913
write(nfecra,9900)
1844
1914
 
1845
1915
 
1918
1988
'    ---------'                                                ,/,&
1919
1989
                                                                /,&
1920
1990
'       NCEGRM = ',4X,I10,    ' (Max nb cells coarsest grid  )',/,&
1921
 
'       NGRMAX = ',4X,I10,    ' (Max numeber of levels       )',/,&
 
1991
'       NGRMAX = ',4X,I10,    ' (Max number of levels        )',/,&
1922
1992
'------------------------------                               ',/,&
1923
1993
' Variable   IMGR NCYMAX NITMGF                               ',/,&
1924
1994
'------------------------------                               '  )
1945
2015
  write(nfecra,6011)
1946
2016
  do ii = 1, nscal
1947
2017
    chaine=nomvar(ipprtp(isca(ii)))
1948
 
    write(nfecra,6021) chaine(1:8),ii,iphsca(ii),iscsth(ii),      &
 
2018
    write(nfecra,6021) chaine(1:8),ii,iscsth(ii),      &
1949
2019
                       ivisls(ii),visls0(ii),sigmas(ii)
1950
2020
  enddo
1951
2021
  write(nfecra,6031)
1952
2022
  write(nfecra,6012)
1953
2023
  do ii = 1, nscal
1954
2024
    chaine=nomvar(ipprtp(isca(ii)))
1955
 
    write(nfecra,6022) chaine(1:8),ii,iphsca(ii),iscavr(ii),      &
 
2025
    write(nfecra,6022) chaine(1:8),ii,iscavr(ii),      &
1956
2026
                       rvarfl(ii)
1957
2027
  enddo
1958
2028
  write(nfecra,6032)
1959
2029
  write(nfecra,6013)
1960
2030
  do ii = 1, nscal
1961
2031
    chaine=nomvar(ipprtp(isca(ii)))
1962
 
    write(nfecra,6023) chaine(1:8),ii,iphsca(ii),iclvfl(ii),      &
 
2032
    write(nfecra,6023) chaine(1:8),ii,iclvfl(ii),      &
1963
2033
                       scamin(ii),scamax(ii)
1964
2034
  enddo
1965
2035
  write(nfecra,6033)
1984
2054
 6010 format(                                                           &
1985
2055
'       ITBRRB = ',4X,I10,    ' (Reconstruction T ou H au brd)',/)
1986
2056
 6011 format(                                                           &
1987
 
'-------------------------------------------------------------',/,&
1988
 
' Variable Numero IPHSCA ISCSTH IVISLS      VISLS0      SIGMAS',/,&
1989
 
'-------------------------------------------------------------'  )
 
2057
'------------------------------------------------------',/,&
 
2058
' Variable Numero ISCSTH IVISLS      VISLS0      SIGMAS',/,&
 
2059
'------------------------------------------------------'  )
1990
2060
 6021 format(                                                           &
1991
 
 1x,    a8,    i7,    i7,    i7,    i7,      e12.4,      e12.4   )
 
2061
 1x,    a8,    i7,    i7,    i7,      e12.4,      e12.4   )
1992
2062
 6031 format(                                                           &
1993
 
'-------------------------------------------------------------',/)
 
2063
'------------------------------------------------------',/)
1994
2064
 6012 format(                                                           &
1995
 
'------------------------------------------'                   ,/,&
1996
 
' Variable Numero IPHSCA ISCAVR      RVARFL'                   ,/,&
1997
 
'------------------------------------------'                     )
 
2065
'-----------------------------------'                   ,/,&
 
2066
' Variable Numero ISCAVR      RVARFL'                   ,/,&
 
2067
'-----------------------------------'                     )
1998
2068
 6022 format(                                                           &
1999
 
 1x,    a8,    i7,    i7,    i7,      e12.4                      )
 
2069
 1x,    a8,    i7,    i7,      e12.4                      )
2000
2070
 6032 format(                                                           &
2001
 
'------------------------------------------'                   ,/)
 
2071
'-----------------------------------'                   ,/)
2002
2072
 6013 format(                                                           &
2003
 
'------------------------------------------------------'       ,/,&
2004
 
' Variable Numero IPHSCA ICLVFL      SCAMIN      SCAMAX'       ,/,&
2005
 
'------------------------------------------------------'         )
 
2073
'-----------------------------------------------'       ,/,&
 
2074
' Variable Numero ICLVFL      SCAMIN      SCAMAX'       ,/,&
 
2075
'-----------------------------------------------'         )
2006
2076
 6023 format(                                                           &
2007
 
 1x,    a8,    i7,    i7,    i7,      e12.4,      e12.4          )
 
2077
 1x,    a8,    i7,    i7,      e12.4,      e12.4          )
2008
2078
 6033 format(                                                           &
2009
 
'------------------------------------------------------'       ,/)
 
2079
'-----------------------------------------------'       ,/)
2010
2080
 6030 format(                                                           &
2011
2081
'-------------------------------------------------------------',/,&
2012
2082
                                                                /,&
2016
2086
'         scalaires physique particuliere sont a la fin, de'   ,/,&
2017
2087
'         NSCAUS+1 a NSCAPP+NSCAUS=NSCAL.'                     ,/,&
2018
2088
                                                                /,&
2019
 
'       IPHSCA =                (Phase porteuse              )',/,&
2020
2089
'       ISCSTH = -1,0, 1 ou 2   (T (C), Passif, T (K) ou H   )',/,&
2021
2090
'       IVISLS = 0 ou >0        (Viscosite constante ou non  )',/,&
2022
2091
'       VISLS0 = >0             (Viscosite de reference      )',/,&
2055
2124
 6010 format(                                                           &
2056
2125
'       ITBRRB = ',4X,I10,    ' (T or H reconstruction at bdy)',/)
2057
2126
 6011 format(                                                           &
2058
 
'-------------------------------------------------------------',/,&
2059
 
' Variable Number IPHSCA ISCSTH IVISLS      VISLS0      SIGMAS',/,&
2060
 
'-------------------------------------------------------------'  )
 
2127
'------------------------------------------------------',/,&
 
2128
' Variable Number ISCSTH IVISLS      VISLS0      SIGMAS',/,&
 
2129
'------------------------------------------------------'  )
2061
2130
 6021 format(                                                           &
2062
 
 1x,    a8,    i7,    i7,    i7,    i7,      e12.4,      e12.4   )
 
2131
 1x,    a8,    i7,    i7,    i7,      e12.4,      e12.4   )
2063
2132
 6031 format(                                                           &
2064
 
'-------------------------------------------------------------',/)
 
2133
'------------------------------------------------------',/)
2065
2134
 6012 format(                                                           &
2066
 
'------------------------------------------'                   ,/,&
2067
 
' Variable Number IPHSCA ISCAVR      RVARFL'                   ,/,&
2068
 
'------------------------------------------'                     )
 
2135
'-----------------------------------'                   ,/,&
 
2136
' Variable Number ISCAVR      RVARFL'                   ,/,&
 
2137
'-----------------------------------'                     )
2069
2138
 6022 format(                                                           &
2070
 
 1x,    a8,    i7,    i7,    i7,      e12.4                      )
 
2139
 1x,    a8,    i7,    i7,      e12.4                      )
2071
2140
 6032 format(                                                           &
2072
 
'------------------------------------------'                   ,/)
 
2141
'-----------------------------------'                   ,/)
2073
2142
 6013 format(                                                           &
2074
 
'------------------------------------------------------'       ,/,&
2075
 
' Variable Number IPHSCA ICLVFL      SCAMIN      SCAMAX'       ,/,&
2076
 
'------------------------------------------------------'         )
 
2143
'-----------------------------------------------'       ,/,&
 
2144
' Variable Number ICLVFL      SCAMIN      SCAMAX'       ,/,&
 
2145
'-----------------------------------------------'         )
2077
2146
 6023 format(                                                           &
2078
 
 1x,    a8,    i7,    i7,    i7,      e12.4,      e12.4          )
 
2147
 1x,    a8,    i7,    i7,      e12.4,      e12.4          )
2079
2148
 6033 format(                                                           &
2080
 
'------------------------------------------------------'       ,/)
 
2149
'-----------------------------------------------'       ,/)
2081
2150
 6030 format(                                                           &
2082
2151
'-------------------------------------------------------------',/,&
2083
2152
                                                                /,&
2087
2156
'         are placed at the end, from'                         ,/,&
2088
2157
'         NSCAUS+1 to NSCAPP+NSCAUS=NSCAL.'                    ,/,&
2089
2158
                                                                /,&
2090
 
'       IPHSCA =                (Carrier phase               )',/,&
2091
2159
'       ISCSTH = -1,0, 1 ou 2   (T (C), Passive, T (K) or H  )',/,&
2092
2160
'       IVISLS = 0 ou >0        (Viscosity: constant or not  )',/,&
2093
2161
'       VISLS0 = >0             (Reference viscosity         )',/,&
2273
2341
 
2274
2342
!   - Fichiers Ensight
2275
2343
 
2276
 
write(nfecra,7520) ntchr
 
2344
write(nfecra,7520)
2277
2345
do ii = 2, nvppmx
2278
2346
  if(ichrvr(ii).eq.1) then
2279
2347
    name = nomvar(ii)
2283
2351
write(nfecra,7522)
2284
2352
 
2285
2353
!   - Fichiers historiques
2286
 
 
2287
 
write(nfecra,7530) nthist,ncapt,nthsav
 
2354
write(nfecra,7530) nthist,frhist,ncapt,nthsav
2288
2355
do ii = 2, nvppmx
2289
2356
  if(ihisvr(ii,1).ne.0) then
2290
2357
    name = nomvar(ii)
2324
2391
 
2325
2392
#if defined(_CS_LANG_FR)
2326
2393
 
2327
 
 7500 format(                                                           &
 
2394
 7500 format(                                                     &
2328
2395
                                                                /,&
2329
2396
' ** ENTREES SORTIES'                                          ,/,&
2330
2397
'    ---------------'                                          ,/)
2331
 
 7510 format(                                                           &
 
2398
 7510 format(                                                     &
2332
2399
' --- Fichier suite'                                           ,/,&
2333
2400
'       NTSUIT = ',4X,I10,    ' (Periode de sauvegarde)'       ,/)
2334
 
 7520 format(                                                           &
2335
 
' --- Fichiers EnSight, MED, ou CGNS'                          ,/,&
2336
 
'       NTCHR  = ',4X,I10,    ' (Periode de sortie    )'       ,/,&
 
2401
 7520 format(                                                     &
 
2402
' --- Variables post-traitees'                                 ,/,&
2337
2403
                                                                /,&
2338
2404
'       Numero Nom'                                              )
2339
 
 7521 format(                                                           &
 
2405
 7521 format(                                                     &
2340
2406
'   ',     I10,1X,          A16                                  )
2341
 
 7522 format(                                                           &
 
2407
 7522 format(                                                     &
2342
2408
'         --           --'                                     ,/)
2343
 
 7530 format(                                                           &
 
2409
 7530 format(                                                     &
2344
2410
' --- Fichiers historiques'                                    ,/,&
2345
2411
'       NTHIST = ',4X,I10,    ' (Periode de sortie    )'       ,/,&
 
2412
'       FRHIST = ',4X,E11.5,  ' (Periode de sortie (s))'       ,/,&
2346
2413
'       NCAPT  = ',4X,I10,    ' (Nombre de capteurs   )'       ,/,&
2347
2414
'       NTHSAV = ',4X,I10,    ' (Periode de sauvegarde)'       ,/,&
2348
2415
                                                                /,&
2369
2436
 
2370
2437
#else
2371
2438
 
2372
 
 7500 format(                                                           &
 
2439
 7500 format(                                                     &
2373
2440
                                                                /,&
2374
2441
' ** INPUT-OUTPUT'                                             ,/,&
2375
2442
'    ------------'                                             ,/)
2376
 
 7510 format(                                                           &
 
2443
 7510 format(                                                     &
2377
2444
' --- Restart file'                                            ,/,&
2378
2445
'       NTSUIT = ',4X,I10,    ' (Checkpoint frequency )'       ,/)
2379
 
 7520 format(                                                           &
2380
 
' --- EnSight, MED, or CGNS output'                            ,/,&
2381
 
'       NTCHR  = ',4X,I10,    ' (Output frequency     )'       ,/,&
 
2446
 7520 format(                                                     &
 
2447
' --- Post-processed variables'                                ,/,&
2382
2448
                                                                /,&
2383
2449
'       Number Name'                                             )
2384
 
 7521 format(                                                           &
 
2450
 7521 format(                                                     &
2385
2451
'   ',     I10,1X,          A16                                  )
2386
 
 7522 format(                                                           &
 
2452
 7522 format(                                                     &
2387
2453
'         --           --'                                     ,/)
2388
 
 7530 format(                                                           &
 
2454
 7530 format(                                                     &
2389
2455
' --- Probe history files'                                     ,/,&
2390
2456
'       NTHIST = ',4X,I10,    ' (Output frequency     )'       ,/,&
 
2457
'       FRHIST = ',4X,E11.5,  ' (Output frequency (s) )'       ,/,&
2391
2458
'       NCAPT  = ',4X,I10,    ' (Number of probes     )'       ,/,&
2392
2459
'       NTHSAV = ',4X,I10,    ' (Checkpoint frequency )'       ,/,&
2393
2460
                                                                /,&
2415
2482
#endif
2416
2483
 
2417
2484
!===============================================================================
2418
 
! 9. FICHIERS
2419
 
!===============================================================================
2420
 
 
2421
 
! --- Fichiers
2422
 
 
2423
 
write(nfecra,7600)
2424
 
write(nfecra,7610)ficgeo,ficamo,ficamx,ficstp,                    &
2425
 
                  impgeo,impstp
2426
 
write(nfecra,7611)ficava,ficavx
2427
 
write(nfecra,7612)ficfpp,ficamr,ficjnf,ficavr,                    &
2428
 
                  impfpp,       impjnf
2429
 
write(nfecra,7613)ficaml, ficmls, ficavl, ficvls, ficlal,         &
2430
 
                  implal, impli1, impli2
2431
 
 
2432
 
! Autres fichiers lagrangien
2433
 
write(nfecra,7615) impla1,impla2,impla3,impla4,impla5(1),         &
2434
 
                   impla5(2),impla5(3),impla5(4),                 &
2435
 
                   impla5(5),impla5(6),impla5(7),                 &
2436
 
                   impla5(8),impla5(9),impla5(10),                &
2437
 
                   impla5(11),impla5(12),impla5(13),              &
2438
 
                   impla5(14),impla5(15)
2439
 
 
2440
 
! Fichiers hist
2441
 
write(nfecra,7620)(imphis(ii),ii=1,2     )
2442
 
 
2443
 
write(nfecra,7630) nushmx
2444
 
write(nfecra,7631)(ficush(ii),ii=1,nushmx)
2445
 
write(nfecra,7632)(impush(ii),ii=1,nushmx)
2446
 
 
2447
 
 
2448
 
! Fichiers utilisateurs
2449
 
write(nfecra,7640) nusrmx
2450
 
write(nfecra,7631)(ficusr(ii),ii=1,nusrmx)
2451
 
write(nfecra,7632)(impusr(ii),ii=1,nusrmx)
2452
 
 
2453
 
write(nfecra,7650) ifoenv
2454
 
 
2455
 
write(nfecra,9900)
2456
 
 
2457
 
 
2458
 
#if defined(_CS_LANG_FR)
2459
 
 
2460
 
 7600 format(                                                           &
2461
 
                                                                /,&
2462
 
' ** FICHIERS'                                                 ,/,&
2463
 
'    --------'                                                 ,/)
2464
 
 7610 format(                                                           &
2465
 
' --- Fichiers standard'                                       ,/,&
2466
 
                                                                /,&
2467
 
'         GEOMETRIE AMONT PPAL  AMONT AUX       STOP'          ,/,&
2468
 
'Nom    ',     4(5X,A6)                                        ,/,&
2469
 
'Unite  ',     I11,        11X,       11X,       I11           ,/)
2470
 
 7611 format(                                                           &
2471
 
'         AVAL PPAL   AVAL AUX'                                ,/,&
2472
 
'Nom    ',     2(5X,A6)                                        ,/)
2473
 
 7612 format(                                                           &
2474
 
' --- Fichiers rayonnement'                                    ,/,&
2475
 
                                                                /,&
2476
 
'         DONNEES    AMONT    JANAF     AVAL'                  ,/,&
2477
 
'Nom    ',     4(3X,A6)                                        ,/,&
2478
 
'Unite  ',     I9,   9X,     I9                                ,/)
2479
 
 7613 format(                                                           &
2480
 
' --- Fichiers Lagrangiens'                                    ,/,&
2481
 
                                                                /,&
2482
 
'         ---- AMONT ----    ---- AVAL -----    ---- POST ----',/,&
2483
 
'         CALCUL    STAT.    CALCUL    STAT.    LISTING  HISTO',/,&
2484
 
'Nom   ',     2(3X,A6),  1X,      2(3X,A6),   4X,       A6     ,/,&
2485
 
'Unite ',         18X ,  1X,           18X,   6X,     3 I4     ,/)
2486
 
 7615 format(                                                           &
2487
 
' --- Autres fichiers pour le module Lagrangien'               ,/,&
2488
 
                                                                /,&
2489
 
'Unite  ',     5I9                                             ,/,&
2490
 
'       ',     5I9                                             ,/,&
2491
 
'       ',     5I9                                             ,/,&
2492
 
'       ',     4I9                                             ,/)
2493
 
 
2494
 
 7620 format(                                                           &
2495
 
' --- Fichiers developpeurs pour historiques'                  ,/,&
2496
 
'                IMPHIS(1)         IMPHIS(2)'                  ,/,&
2497
 
'Unite  ',     2(9X,I9)                                        ,/)
2498
 
 7630 format(                                                           &
2499
 
' --- Fichiers utilisateurs pour historiques'                  ,/,&
2500
 
'                 ',I10   ,' fichiers'                         ,/,&
2501
 
' Nom et unite'                                                  )
2502
 
 7631 format(                                                           &
2503
 
               6(3x,a6)                                          )
2504
 
 7632 format(                                                           &
2505
 
               6i9                                               )
2506
 
 7640 format(                                                           &
2507
 
                                                                /,&
2508
 
' --- Fichiers utilisateurs libres'                            ,/,&
2509
 
'                 ',I10   ,' fichiers'                         ,/,&
2510
 
' Nom et unite'                                                  )
2511
 
 7650 format(                                                           &
2512
 
                                                                /,&
2513
 
' --- Fichiers preprocesseur'                                  ,/,&
2514
 
'   Format : 1=Lecture du fichier preprocessor_output'         ,/,&
2515
 
'            0=Solveur autonome'                               ,/,&
2516
 
                                                                /,&
2517
 
' Format ',I10                                                 ,/)
2518
 
 
2519
 
#else
2520
 
 
2521
 
 7600 format(                                                           &
2522
 
                                                                /,&
2523
 
' ** FILES'                                                    ,/,&
2524
 
'    -----'                                                    ,/)
2525
 
 7610 format(                                                           &
2526
 
' --- Standard files'                                          ,/,&
2527
 
                                                                /,&
2528
 
'         GEOMETRY  MAIN RESTART  AUX RESTART   STOP'          ,/,&
2529
 
'Name   ',     4(5X,A6)                                        ,/,&
2530
 
'Unit   ',     I11,        11X,       11X,       I11           ,/)
2531
 
 7611 format(                                                           &
2532
 
'         MAIN CHECKPOINT  AUX CHECKPOINT'                     ,/,&
2533
 
'Name   ',     2(5X,A6)                                        ,/)
2534
 
 7612 format(                                                           &
2535
 
' --- Radiative files'                                         ,/,&
2536
 
                                                                /,&
2537
 
'         DATA       RESTART  JANAF   CHECKPOINT'              ,/,&
2538
 
'Name   ',     4(3X,A6)                                        ,/,&
2539
 
'Unit   ',     I9,   9X,     I9                                ,/)
2540
 
 7613 format(                                                           &
2541
 
' --- Lagrangian files'                                        ,/,&
2542
 
                                                                /,&
2543
 
'         --- RESTART ---    -- CHECKPOINT -    ---- POST ----',/,&
2544
 
'         CALCUL.   STAT.    CALCUL.   STAT.    LOG      HIST.',/,&
2545
 
'Name  ',     2(3X,A6),  1X,      2(3X,A6),   4X,       A6     ,/,&
2546
 
'Unit  ',         18X ,  1X,           18X,   6X,     3 I4     ,/)
2547
 
 7615 format(                                                           &
2548
 
' --- Other files for Lagrangian module'                       ,/,&
2549
 
                                                                /,&
2550
 
'Unit   ',     5I9                                             ,/,&
2551
 
'       ',     5I9                                             ,/,&
2552
 
'       ',     5I9                                             ,/,&
2553
 
'       ',     4I9                                             ,/)
2554
 
 
2555
 
 7620 format(                                                           &
2556
 
' --- Developper files for probe history'                      ,/,&
2557
 
'                IMPHIS(1)         IMPHIS(2)'                  ,/,&
2558
 
'Unit   ',     2(9X,I9)                                        ,/)
2559
 
 7630 format(                                                           &
2560
 
' --- User files for probe history'                            ,/,&
2561
 
'                 ',I10   ,' files'                            ,/,&
2562
 
' Name and unit'                                                 )
2563
 
 7631 format(                                                           &
2564
 
               6(3x,a6)                                          )
2565
 
 7632 format(                                                           &
2566
 
               6i9                                               )
2567
 
 7640 format(                                                           &
2568
 
                                                                /,&
2569
 
' --- Free user files'                                         ,/,&
2570
 
'                 ',I10   ,' files'                            ,/,&
2571
 
' Name and unit'                                                 )
2572
 
 7650 format(                                                           &
2573
 
                                                                /,&
2574
 
' --- Preprocessor files'                                      ,/,&
2575
 
'   Format: 1=Read preprocessor_output file'                   ,/,&
2576
 
'           0=Standalone solver'                               ,/,&
2577
 
                                                                /,&
2578
 
' Format ',I10                                                 ,/)
2579
 
 
2580
 
#endif
2581
 
 
2582
 
 
2583
 
!===============================================================================
2584
 
! 10. COUPLAGES
 
2485
! 9. COUPLAGES
2585
2486
!===============================================================================
2586
2487
 
2587
2488
 
2654
2555
#endif
2655
2556
 
2656
2557
!===============================================================================
2657
 
! 11. Lagrangien
 
2558
! 10. Lagrangien
2658
2559
!===============================================================================
2659
2560
 
2660
2561
! --- Lagrangien
2661
2562
 
2662
2563
if (iilagr.ne.0) then
2663
 
  write(nfecra,8100) ilphas, iilagr, isuila, isuist, iphyla
 
2564
  write(nfecra,8100) iilagr, isuila, isuist, iphyla
2664
2565
 
2665
2566
  if (iphyla.eq.1) then
2666
2567
    write(nfecra,8105) idpvar, itpvar, impvar
2718
2619
                                                                /,&
2719
2620
' ** ECOULEMENT DIPHASIQUE LAGRANGIEN'                         ,/,&
2720
2621
'    --------------------------------'                         ,/,&
2721
 
' --- Numero de la phase continue : ',I10                      ,/,&
 
2622
' --- Phase continue : '                                       ,/,&
2722
2623
'       IILAGR = ',4X,I10,    ' (0 : Lagrangien desactive     ',/,&
2723
2624
'                ',14X,       '  1 : one way coupling         ',/,&
2724
2625
'                ',14X,       '  2 : two way coupling         ',/,&
2827
2728
                                                                /,&
2828
2729
' ** TWO-PHASE LANGRANGIEN FLOW'                               ,/,&
2829
2730
'    --------------------------'                               ,/,&
2830
 
' --- Number of the continuous phase: ',I10                    ,/,&
 
2731
' --- Continuous phase: '                                      ,/,&
2831
2732
'       IILAGR = ',4X,I10,    ' (0: Lagrangian deactivated    ',/,&
2832
2733
'                ',14X,       '  1: one way coupling          ',/,&
2833
2734
'                ',14X,       '  2: two way coupling          ',/,&
2933
2834
#endif
2934
2835
 
2935
2836
!===============================================================================
2936
 
! 12. METHODE ALE
 
2837
! 11. METHODE ALE
2937
2838
!===============================================================================
2938
2839
! --- Activation de la methode ALE
2939
2840
 
2968
2869
#endif
2969
2870
 
2970
2871
!===============================================================================
2971
 
! 13. FIN
 
2872
! 12. FIN
2972
2873
!===============================================================================
2973
2874
 
2974
2875
return