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

« back to all changes in this revision

Viewing changes to src/base/iniusi.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
 
42
37
!   CONTROLER LES ZONES OU SONT INITIALISES LES VARIABLES (PAR
43
38
!   LE BIAIS DE PARAMETRES PASSES EN ARGUMENT)
44
39
 
45
 
! ON INITIALISE EGALEMENT ICI NPHAS ET ISCAPH QUI VALENT 1 EN
46
 
!   PRATIQUE DANS TOUS LES CALCULS (C'EST UN PARAMETRE UTILISATEUR,
47
 
!   MAIS SA VALEUR EST QUELQUE PEU CONTRAINTE ENCORE...)
48
 
 
49
40
 
50
41
!-------------------------------------------------------------------------------
51
42
! Arguments
61
52
!            --- tableau de travail
62
53
!===============================================================================
63
54
 
 
55
!===============================================================================
 
56
! Module files
 
57
!===============================================================================
 
58
 
 
59
use paramx
 
60
use cstnum
 
61
use dimens
 
62
use numvar
 
63
use optcal
 
64
use cstphy
 
65
use entsor
 
66
use albase
 
67
use mltgrd
 
68
use parall
 
69
use period
 
70
use ihmpre
 
71
use ppppar
 
72
use ppthch
 
73
use coincl
 
74
use cpincl
 
75
use ppincl
 
76
use ppcpfu
 
77
use radiat
 
78
 
 
79
!===============================================================================
 
80
 
64
81
implicit none
65
82
 
66
 
!===============================================================================
67
 
! Common blocks
68
 
!===============================================================================
69
 
 
70
 
include "paramx.h"
71
 
include "cstnum.h"
72
 
include "dimens.h"
73
 
include "numvar.h"
74
 
include "optcal.h"
75
 
include "cstphy.h"
76
 
include "entsor.h"
77
 
include "vector.h"
78
 
include "albase.h"
79
 
include "parall.h"
80
 
include "period.h"
81
 
include "ihmpre.h"
82
 
include "ppppar.h"
83
 
include "ppthch.h"
84
 
include "coincl.h"
85
 
include "cpincl.h"
86
 
include "ppincl.h"
87
 
include "ppcpfu.h"
88
 
include "radiat.h"
89
 
 
90
 
!===============================================================================
91
 
 
92
83
! Arguments
93
84
 
94
85
integer          iverif
95
86
 
96
87
! Local variables
97
88
 
98
 
integer          ii, iphas , iscal , nmodpp
99
 
integer          nphmax, nscmax, nesmax, nphusi, nscusi
 
89
integer          ii, iscal , nmodpp
 
90
integer          nscmax, nesmax, nscusi
100
91
integer          ieepre, ieeder, ieecor, ieetot, iihmpu
101
 
integer          ialgce, imgrpr
 
92
integer          ialgce, imgrpr, icwfps
102
93
integer          iappel
103
 
double precision relaxp, extrap
 
94
double precision relaxp, extrap, cwfthr
104
95
 
105
96
!===============================================================================
106
97
 
127
118
endif
128
119
 
129
120
!===============================================================================
130
 
! 1. INITIALISATION DE PARAMETRES DEPENDANT DU NOMBRE DE PHASES
 
121
! 1. INITIALISATION DE PARAMETRES POUR LA PHASE CONTINUE
131
122
!===============================================================================
132
123
 
133
 
! --- Nombre de phases
134
 
 
135
 
!     Egal a 1 en version 1.2
136
 
!     =======================
137
 
 
138
 
!     Le nombre de phases maximal est donne par NPHSMX dans paramx.h
139
 
!     On teste la valeur donnee par l'utilisateur avant de completer
140
 
!       les tableaux dimensionnes a NPHSMX (ex. ITURB(NPHSMX)).
141
 
 
142
 
nphas = 1
143
 
 
144
 
 
145
 
! --- Varpos
146
 
!     Verification du nombre de phases
147
 
!      1er passage
148
 
call varpos(nmodpp)
149
 
!==========
150
 
 
151
 
! --- Parametres dependant du nombre de phases
152
 
 
153
124
!     Turbulence
154
125
!     Chaleur massique variable ou non
155
126
 
169
140
!   - Sous-programme utilisateur
170
141
!     ==========================
171
142
 
172
 
nphmax = nphsmx
173
 
nphusi = nphas
174
143
iihmpu = iihmpr
175
144
call usipph                                                       &
176
145
!==========
177
 
 (nphmax , nphusi , iihmpu , nfecra , iturb  , icp , iverif)
 
146
 (iihmpu , nfecra , iturb  , icp , iverif)
178
147
 
179
148
!===============================================================================
180
149
! 2. INITIALISATION DE PARAMETRES DEPENDANT DU NOMBRE DE SCALAIRES
250
219
 
251
220
! --- Varpos
252
221
!     Verification et construction de ISCAPP
253
 
!      2ieme passage
 
222
!      1ier passage
254
223
call varpos(nmodpp)
255
224
!==========
256
225
 
285
254
 ( nscmax , nscusi , iihmpu , nfecra , iscavr , ivisls , iverif )
286
255
 
287
256
 
288
 
! --- Parametres dependant du nombre de scalaires : exception
289
 
!     IPHSCA indique le numero de la phase porteuse pour chaque
290
 
!                                                    scalaire UTILISATEUR
291
 
 
292
 
!       Dans le cas d'une seule phase, IPHSCA(ISCAL) = 1 : ne rien changer.
293
 
!       ==================================================================
294
 
 
295
 
!       Sinon noter bien que :
296
 
 
297
 
!       La phase porteuse des scalaires UTILISATEUR ISCAL qui
298
 
!         representent la moyenne du carre des fluctuations d'un
299
 
!         scalaire utilisateur K sera la meme que celle de ce scalaire
300
 
!         utilisateur K.
301
 
!         Donc, pour de tels scalaires ISCAL (reperes par ISCAVR(ISCAL)>0),
302
 
!                          on ne doit pas renseigner IPHSCA(ISCAL) ici.
303
 
!         C'est l'objet du test inclus dans l'exemple ci-dessous.
304
 
 
305
 
!       Pour les scalaires non utilisateur relatifs a des physiques
306
 
!         particulieres, (charbon, combustion, electrique : voir usppmo)
307
 
!         implicitement definis selon le modele,
308
 
!         les informations sont donnees automatiquement par ailleurs :
309
 
!                                         on ne modifie pas IPHSCA ici.
310
 
 
311
 
do iscal = 1, nscaus
312
 
  if(iscavr(iscal).le.0) then
313
 
    iphsca(iscal) = 1
314
 
  endif
315
 
enddo
316
 
 
317
 
 
318
257
!===============================================================================
319
258
! 3. INITIALISATION DE PARAMETRES "GLOBAUX"
320
259
!===============================================================================
331
270
!   - Interface Code_Saturne
332
271
!     ======================
333
272
 
334
 
if(iihmpr.eq.1) then
 
273
if (iihmpr.eq.1) then
335
274
 
336
275
  call csidtv(idtvar)
337
276
  !==========
339
278
  call csiphy(iphydr)
340
279
  !==========
341
280
 
 
281
  ! Mesh related options
 
282
 
 
283
  call uicwf
 
284
  !=========
 
285
 
342
286
endif
343
287
 
344
288
!   - Sous-programme utilisateur
345
289
!     ==========================
346
290
 
347
 
nphmax = nphsmx
348
291
nesmax = nestmx
349
292
ieepre = iespre
350
293
ieeder = iesder
351
294
ieecor = iescor
352
295
ieetot = iestot
353
 
nphusi = nphas
354
296
iihmpu = iihmpr
355
297
!     IALGCE permet de remplir la variable cs_glob_maillage_grd_cdg_cel dans
356
298
!       cs_maillage_grd.c, a travers la routine ALGCEN.
360
302
!     Le blindage en erreur est dans cs_maillage_grd.c (erreur si IALGCE>1,
361
303
!       cs_glob_maillage_grd_cdg_cel inchange si IALGCE<0)
362
304
ialgce = -999
 
305
icwfps = 0     ! Set to 1 to postprocess cutting of warped faces
 
306
cwfthr = -1.d0 ! Threshold (in degrees) to triangulate warped faces if positive
363
307
 
364
308
call usipgl                                                       &
365
309
!==========
366
 
 ( nphmax , nesmax ,                                              &
 
310
 ( nesmax ,                                                       &
367
311
   ieepre , ieeder , ieecor , ieetot ,                            &
368
 
   nphusi , iihmpu , nfecra ,                                     &
369
 
   idtvar , ipucou , iphydr , ialgce , iescal , iverif )
 
312
   iihmpu , nfecra ,                                              &
 
313
   idtvar , ipucou , iphydr , ialgce , iescal , iverif,           &
 
314
   icwfps,  cwfthr )
370
315
 
371
316
if (ialgce.ne.-999) call algcen(ialgce)
 
317
if (cwfthr.ge.0.d0) call setcwf(icwfps, cwfthr)
372
318
 
373
319
! --- Parametres de la methode ALE
374
320
 
393
339
!     Determination de IPR, IU ... ISCA, NVAR
394
340
!     Determination de IPP...
395
341
 
396
 
!      3ieme passage
 
342
!      2ieme passage
397
343
call varpos(nmodpp)
398
344
!==========
399
345
 
419
365
             iturb, ik, iep,                                      &
420
366
             ir11, ir22, ir33,                                    &
421
367
             ir12, ir13, ir23,                                    &
422
 
             iomg, iphi, ifb,                                     &
 
368
             iomg, iphi, ifb, ial,                                &
 
369
             inusa,                                               &
423
370
             iale, iuma, ivma, iwma,                              &
424
371
             isca, iscapp)
425
372
 
426
373
!     Suite de calcul, relecture fichier auxiliaire, champ de vitesse figé
427
 
  call csisui(isuite, ntsuit, ileaux, iccvfg)
 
374
 
 
375
  call csisui(ntsuit, ileaux, iccvfg)
428
376
  !==========
429
377
 
430
378
!     Pas de temps (seulement NTMABS, DTREF, INPDT0)
453
401
  imgrpr = 0
454
402
  call csnum2 (ivisse, relaxp, ipucou, extrap, imrgra, imgrpr)
455
403
  !==========
456
 
  iphas = 1
457
 
  extrag(ipr(iphas)) = extrap
458
 
  if (idtvar.ge.0) relaxv(ipr(iphas)) = relaxp
459
 
  imgr(ipr(iphas)) = imgrpr
 
404
  extrag(ipr) = extrap
 
405
  if (idtvar.ge.0) relaxv(ipr) = relaxp
 
406
  imgr(ipr) = imgrpr
460
407
 
461
408
!     Gravite, prop. phys
462
409
  call csphys                                                     &
475
422
  !==========
476
423
 
477
424
!     Init turb (uref, almax) si necessaire (modele RANS)
478
 
  iphas = 1
479
 
  if (itytur(iphas).eq.2 .or. itytur(iphas).eq.3 .or.             &
480
 
      itytur(iphas).eq.5 .or. itytur(iphas).eq.6 ) then
 
425
  if (itytur.eq.2 .or. itytur.eq.3 .or.             &
 
426
      itytur.eq.5 .or. itytur.eq.6 ) then
481
427
    call cstini(uref, almax)
482
428
    !==========
483
429
  endif
503
449
call usipsu(nmodpp , iverif)
504
450
!==========
505
451
 
 
452
call clmopt(mltmmn, mltmgl, mltmmr, mltmst)
 
453
!==========
 
454
 
 
455
call indsui(isuite)
 
456
!==========
506
457
 
507
458
! --- Varpos
508
 
!      4ieme passage
 
459
!      3ieme passage
509
460
call varpos(nmodpp)
510
461
!==========
511
462
 
540
491
 
541
492
  call csenso                                                     &
542
493
  !==========
543
 
     ( nvppmx, ncapt,  nthist, ntlist,                            &
544
 
       ichrvl, ichrbo, ichrsy, ichrmd,                            &
545
 
       fmtchr, len(fmtchr), optchr, len(optchr),                  &
546
 
       ntchr,  iecaux,                                            &
 
494
     ( nvppmx, ncapt,  nthist, frhist, ntlist, iecaux,            &
547
495
       ipstdv, ipstyp, ipstcl, ipstft, ipstfo,                    &
548
 
       ichrvr, ilisvr, ihisvr, isca, iscapp,                      &
 
496
       ichrvr, ilisvr, ihisvr, tplfmt, isca, iscapp,              &
549
497
       ipprtp, xyzcap )
550
498
 
551
499
  do ii = 1,nvppmx