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

« back to all changes in this revision

Viewing changes to users/base/usini1.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:
2
2
 
3
3
!VERS
4
4
 
5
 
 
6
 
!     This file is part of the Code_Saturne Kernel, element of the
7
 
!     Code_Saturne CFD tool.
8
 
 
9
 
!     Copyright (C) 1998-2009 EDF S.A., France
10
 
 
11
 
!     contact: saturne-support@edf.fr
12
 
 
13
 
!     The Code_Saturne Kernel is free software; you can redistribute it
14
 
!     and/or modify it under the terms of the GNU General Public License
15
 
!     as published by the Free Software Foundation; either version 2 of
16
 
!     the License, or (at your option) any later version.
17
 
 
18
 
!     The Code_Saturne Kernel is distributed in the hope that it will be
19
 
!     useful, but WITHOUT ANY WARRANTY; without even the implied warranty
20
 
!     of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
21
 
!     GNU General Public License for more details.
22
 
 
23
 
!     You should have received a copy of the GNU General Public License
24
 
!     along with the Code_Saturne Kernel; if not, write to the
25
 
!     Free Software Foundation, Inc.,
26
 
!     51 Franklin St, Fifth Floor,
27
 
!     Boston, MA  02110-1301  USA
 
5
! This file is part of Code_Saturne, a general-purpose CFD tool.
 
6
!
 
7
! Copyright (C) 1998-2011 EDF S.A.
 
8
!
 
9
! This program is free software; you can redistribute it and/or modify it under
 
10
! the terms of the GNU General Public License as published by the Free Software
 
11
! Foundation; either version 2 of the License, or (at your option) any later
 
12
! version.
 
13
!
 
14
! This program is distributed in the hope that it will be useful, but WITHOUT
 
15
! ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
 
16
! FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
 
17
! details.
 
18
!
 
19
! You should have received a copy of the GNU General Public License along with
 
20
! this program; if not, write to the Free Software Foundation, Inc., 51 Franklin
 
21
! Street, Fifth Floor, Boston, MA 02110-1301, USA.
28
22
 
29
23
!-------------------------------------------------------------------------------
 
24
 
30
25
! Purpose:
31
26
! -------
32
27
 
57
52
subroutine usipph &
58
53
!================
59
54
 
60
 
 ( nphmax, nphas , iihmpu, nfecra , iturb , icp , iverif )
 
55
 ( iihmpu, nfecra , iturb , icp , iverif )
61
56
 
62
57
 
63
58
!===============================================================================
71
66
!__________________.____._____.________________________________________________.
72
67
! name             !type!mode ! role                                           !
73
68
!__________________!____!_____!________________________________________________!
74
 
! nphmax           ! i  ! <-- ! maximum number of phases                       !
75
 
! nphas            ! i  ! <-- ! number of active phases                        !
76
69
! iihmpu           ! i  ! <-- ! indicates if the XML file from the GUI is      !
77
70
!                  !    !     ! used (1: yes, 0: no)                           !
78
71
! nfecra           ! i  ! <-- ! Fortran unit number for standard output        !
79
 
! iturb(nphmax)    ! ia ! <-> ! turbulence model                               !
80
 
! icp(nphmax)      ! ia ! <-> ! flag for uniform Cp or not                     !
 
72
! iturb            ! ia ! <-> ! turbulence model                               !
 
73
! icp              ! ia ! <-> ! flag for uniform Cp or not                     !
81
74
! iverif           ! i  ! <-- ! flag for elementary tests                      !
82
75
!__________________!____!_____!________________________________________________!
83
76
 
86
79
!     mode: <-- input, --> output, <-> modifies data, --- work array
87
80
!===============================================================================
88
81
 
 
82
!===============================================================================
 
83
! Module files
 
84
!===============================================================================
 
85
 
 
86
! No module should appear here
 
87
 
 
88
 
 
89
!===============================================================================
 
90
 
89
91
implicit none
90
92
 
91
 
!===============================================================================
92
 
! Common blocks
93
 
!===============================================================================
94
 
 
95
 
 
96
 
! No common should appear here
97
 
 
98
 
 
99
 
!===============================================================================
100
 
 
101
93
! Arguments
102
94
 
103
 
integer nphmax, nphas, iihmpu, nfecra
104
 
integer iturb(nphmax), icp(nphmax)
 
95
integer iihmpu, nfecra
 
96
integer iturb, icp
105
97
integer iverif
106
98
 
107
99
! Local variables
108
100
 
109
 
integer iphas
110
 
 
111
101
!===============================================================================
112
102
 
113
103
! TEST_TO_REMOVE_FOR_USE_OF_SUBROUTINE_START
183
173
!      41...LES (Dynamic)
184
174
!      42...LES (WALE)
185
175
!      50...v2f (phi-model)
 
176
!      51...v2f (BL-v2/k)
186
177
!      60...k-omega SST
 
178
!      70...Spalart Allmaras
187
179
!  For 10, contact the development team before use
188
180
 
189
181
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
190
182
 
191
 
iphas = 1
192
 
iturb(iphas) = 20
 
183
iturb = 20
193
184
 
194
185
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
195
186
 
196
187
 
197
188
! --- Variable specific heat (ICP=1) or not (ICP=0)
198
 
!       for each phase IPHAS
199
189
 
200
190
!     Should be set only if specific physics (coal, combustion, electric arcs)
201
191
!       ARE NOT activated.
207
197
 
208
198
!     Caution:    complete usphyv with the law defining Cp
209
199
!     =========   if and only if variable Cp has been selected here
210
 
!                 (with icp(iphas)=1)
 
200
!                 (with icp=1)
211
201
 
212
202
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
213
203
 
214
 
iphas = 1
215
 
icp(iphas) = 0
 
204
icp = 0
216
205
 
217
206
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
218
207
 
257
246
!     mode: <-- input, --> output, <-> modifies data, --- work array
258
247
!===============================================================================
259
248
 
 
249
!===============================================================================
 
250
! Module files
 
251
!===============================================================================
 
252
 
 
253
 
 
254
! No module should appear here
 
255
 
 
256
 
 
257
!===============================================================================
 
258
 
260
259
implicit none
261
260
 
262
 
!===============================================================================
263
 
! Common blocks
264
 
!===============================================================================
265
 
 
266
 
 
267
 
! No common should appear here
268
 
 
269
 
 
270
 
!===============================================================================
271
 
 
272
261
! Arguments
273
262
 
274
263
integer iihmpu, nfecra
413
402
!     mode: <-- input, --> output, <-> modifies data, --- work array
414
403
!===============================================================================
415
404
 
 
405
!===============================================================================
 
406
! Module files
 
407
!===============================================================================
 
408
 
 
409
 
 
410
! No module should appear here
 
411
 
 
412
 
 
413
!===============================================================================
 
414
 
416
415
implicit none
417
416
 
418
 
!===============================================================================
419
 
! Common blocks
420
 
!===============================================================================
421
 
 
422
 
 
423
 
! No common should appear here
424
 
 
425
 
 
426
 
!===============================================================================
427
 
 
428
417
! Arguments
429
418
 
430
419
integer nscmax, nscaus, iihmpu, nfecra
508
497
!       So, if we set iscavr(j) = k, we must have
509
498
!       0 < j < nscaus+1, 0< k < nscaus+1 and j different from k.
510
499
 
511
 
!     For example for user scalar 3 to be the variance of user scalar 3,
 
500
!     For example for user scalar 3 to be the variance of user scalar 2,
512
501
!       we set:
513
502
!       iscavr(3) = 2
514
503
!       with nscaus at least equal to 3.
588
577
subroutine usipgl &
589
578
!================
590
579
 
591
 
 ( nphmax, nesmax,                                                &
 
580
 ( nesmax,                                                        &
592
581
   iespre, iesder, iescor, iestot,                                &
593
 
   nphas , iihmpu, nfecra,                                        &
594
 
   idtvar, ipucou, iphydr, ialgce , iescal , iverif )
 
582
   iihmpu, nfecra,                                                &
 
583
   idtvar, ipucou, iphydr, ialgce , iescal , iverif ,             &
 
584
   icwfps, cwfthr )
595
585
 
596
586
 
597
587
!===============================================================================
605
595
!__________________.____._____.________________________________________________.
606
596
! name             !type!mode ! role                                           !
607
597
!__________________!____!_____!________________________________________________!
608
 
! nphmax           ! i  ! <-- ! maximum number of phases                       !
609
598
! nesmax           ! i  ! <-- ! maximum number of error estimators per phase   !
610
599
! iespre           ! i  ! <-- ! number of the prediction error estimator       !
611
600
! iesder           ! i  ! <-- ! number of the derivative error estimator       !
612
601
! iescor           ! i  ! <-- ! number of the correction error estimator       !
613
602
! iestot           ! i  ! <-- ! number of the total error estimator            !
614
 
! nphas            ! i  ! <-- ! number of active phases                        !
615
603
! iihmpu           ! i  ! <-- ! indicates if the XML file from the GUI is      !
616
604
!                  !    !     ! used (1: yes, 0: no)                           !
617
605
! nfecra           ! i  ! <-- ! Fortran unit number for standard output        !
622
610
!                  !    !     ! head-loss terms                                !
623
611
! ialgce           ! i  ! <-- ! option for the method of calculation of        !
624
612
!                  !    !     !  cell centers                                  !
625
 
! iescal           ! ia ! <-- ! flag for activation of error estimators for    !
626
 
!  (nesmax,nphmax) !    !     ! Navier-Stokes                                  !
 
613
! iescal(nesmax)   ! ia ! <-- ! flag for activation of error estimators for    !
 
614
!                  !    !     ! Navier-Stokes                                  !
627
615
! iverif           ! i  ! <-- ! flag for elementary tests                      !
 
616
! cwfthr           ! i  ! <-- ! Treshold angle to cut warped faces (do not     !
 
617
!                  !    !     !  cut warped faces if value is negative)        !
628
618
!__________________!____!_____!________________________________________________!
629
619
 
630
620
!     Type: i (integer), r (real), s (string), a (array), l (logical),
632
622
!     mode: <-- input, --> output, <-> modifies data, --- work array
633
623
!===============================================================================
634
624
 
 
625
!===============================================================================
 
626
! Module files
 
627
!===============================================================================
 
628
 
 
629
 
 
630
! No module should appear here
 
631
 
 
632
 
 
633
!===============================================================================
 
634
 
635
635
implicit none
636
636
 
637
 
!===============================================================================
638
 
! Common blocks
639
 
!===============================================================================
640
 
 
641
 
 
642
 
! No common should appear here
643
 
 
644
 
 
645
 
!===============================================================================
646
 
 
647
637
! Arguments
648
638
 
649
 
integer nphmax, nesmax
 
639
integer nesmax
650
640
integer iespre, iesder, iescor, iestot
651
 
integer nphas , iihmpu, nfecra
652
 
integer idtvar, ipucou, iphydr
653
 
integer iescal(nesmax,nphmax)
654
 
integer iverif
 
641
integer iihmpu, nfecra
 
642
integer idtvar, ipucou, iphydr, ialgce
 
643
integer iescal(nesmax)
 
644
integer iverif, icwfps
 
645
 
 
646
double precision cwfthr
655
647
 
656
648
! Local variables
657
649
 
658
 
integer iphas, ialgce
659
 
 
660
650
!===============================================================================
661
651
 
662
652
! TEST_TO_REMOVE_FOR_USE_OF_SUBROUTINE_START
763
753
 
764
754
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
765
755
 
766
 
iphas = 1
767
756
!       div(rho u) -Gamma
768
 
iescal(iescor,iphas) = 0
 
757
iescal(iescor) = 0
769
758
!       resolution precision for the momentum
770
 
iescal(iestot,iphas) = 0
 
759
iescal(iestot) = 0
 
760
 
 
761
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
 
762
 
 
763
 
 
764
! --- Triangulate warped faces:
 
765
!       If cwfthr is positive, faces whose warping angle are greater than
 
766
!         the given value (in degrees) are subdivided into triangles;
 
767
!       if cwfthr negative, faces are not subdivided.
 
768
!       If icwfps = 1, additional postprocessing will be activated to
 
769
!         show faces before and after cutting.
 
770
 
 
771
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
 
772
 
 
773
icwfps = 0
 
774
cwfthr= -1.d0
771
775
 
772
776
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
773
777
 
810
814
!     mode: <-- input, --> output, <-> modifies data, --- work array
811
815
!===============================================================================
812
816
 
 
817
!===============================================================================
 
818
! Module files
 
819
!===============================================================================
 
820
 
 
821
use paramx
 
822
use cstnum
 
823
use dimens
 
824
use numvar
 
825
use optcal
 
826
use cstphy
 
827
use entsor
 
828
use mltgrd
 
829
use parall
 
830
use period
 
831
use ihmpre
 
832
use ppppar
 
833
use ppthch
 
834
use ppincl
 
835
use coincl
 
836
use cpincl
 
837
use elincl
 
838
 
 
839
!===============================================================================
 
840
 
813
841
implicit none
814
842
 
815
 
!===============================================================================
816
 
! Common blocks
817
 
!===============================================================================
818
 
 
819
 
include "paramx.h"
820
 
include "cstnum.h"
821
 
include "dimens.h"
822
 
include "numvar.h"
823
 
include "optcal.h"
824
 
include "cstphy.h"
825
 
include "entsor.h"
826
 
include "vector.h"
827
 
include "parall.h"
828
 
include "period.h"
829
 
include "ihmpre.h"
830
 
include "ppppar.h"
831
 
include "ppthch.h"
832
 
include "ppincl.h"
833
 
include "coincl.h"
834
 
include "cpincl.h"
835
 
include "elincl.h"
836
 
 
837
 
!===============================================================================
838
 
 
839
843
! Arguments
840
844
 
841
845
integer nmodpp
843
847
 
844
848
! Local variables
845
849
 
846
 
integer iphas, iutile, ii, jj, imom
 
850
integer iutile, ii, jj, imom
847
851
 
848
852
!===============================================================================
849
853
 
912
916
! Calculation options (optcal.h)
913
917
! ==============================
914
918
 
915
 
! --- Calculation restart: isuite (= 1) or not (0)
916
919
!     In case of restart, read auxiliary restart file ileaux (= 1) or not (0).
917
920
 
918
921
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
919
922
 
920
 
isuite = 0
921
923
ileaux = 1
922
924
 
923
925
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
967
969
 
968
970
!   On the other hand, if specific physics are NOT activated:
969
971
 
970
 
!     If a USER scalar represents the temperature or enthalpy (of phase iphas):
971
 
!       we define the number of this scalar in iscalt(iphas) and
972
 
!       we set iscsth(iscalt(iphas)) = 1 if it is the temperature
973
 
!          or  iscsth(iscalt(iphas)) = 2 if it is the enthalpy.
 
972
!     If a USER scalar represents the temperature or enthalpy:
 
973
!       we define the number of this scalar in iscalt and
 
974
!       we set iscsth(iscalt) = 1 if it is the temperature
 
975
!          or  iscsth(iscalt) = 2 if it is the enthalpy.
974
976
 
975
 
!     If no scalar represents the temperature or enthalpy (of phase iphas)
976
 
!       we set iscalt(iphas) = -1
977
 
!       and we do not define iscsth(iscalt(iphas)).
 
977
!     If no scalar represents the temperature or enthalpy
 
978
!       we set iscalt = -1
 
979
!       and we do not define iscsth(iscalt).
978
980
 
979
981
 
980
982
!     For the radiative module when used without specific physics, if we
981
983
!      have chosen to solve in temperature (that is if
982
 
!      iscsth(iscalt(iphas)) = 1), the fluid temperature is considered to
 
984
!      iscsth(iscalt) = 1), the fluid temperature is considered to
983
985
!      be in degrees KELVIN (be careful for boundary conditions an expression
984
986
!      of physical properties depending on temperature).
985
987
!      Nonetheless, even though it is not recommended, if we wish for the
986
988
!      fluid solver to work with a temperature in degrees Celsius, we must set
987
 
!      iscsth(iscalt(iphas)) = -1.
 
989
!      iscsth(iscalt) = -1.
988
990
!      This choice is a source of user errors. Indeed, the boundary conditions
989
991
!      for the fluid temperature will then be in degrees Celsius, while the
990
992
!      boundary conditions for radiation in usray2 must still be in Kelvin.
997
999
 
998
1000
if (nmodpp.eq.0) then
999
1001
 
1000
 
  iphas = 1
1001
 
 
1002
1002
  ! Number of the scalar representing temperature or enthalpy,
1003
1003
  !   or -1 if there is none.
1004
1004
  ! When the choice is done by the Code_Saturne GUI, the scalar representing
1005
1005
  !   the temperature or enthalpy is always the first.
1006
 
  iscalt(iphas) = -1
 
1006
  iscalt = -1
1007
1007
 
1008
1008
! If there is a temperature or enthalpy variable:
1009
 
  if (iscalt(iphas).gt.0) then
 
1009
  if (iscalt.gt.0) then
1010
1010
    ! we indicate if it is the temperature (=1) or the enthalpy (=2).
1011
 
    iscsth(iscalt(iphas)) = 1
 
1011
    iscsth(iscalt) = 1
1012
1012
  endif
1013
1013
 
1014
1014
endif
1031
1031
 
1032
1032
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
1033
1033
 
1034
 
iphas = 1
1035
 
if (itytur(iphas).eq.4) then
 
1034
if (itytur.eq.4) then
1036
1035
  ivrtex = 0
1037
1036
endif
1038
1037
 
1056
1055
!         blencv(ivar) = 1.0d0 to use a second-order scheme in space for
1057
1056
!         convection. For temperature or enthalpy in particular, we
1058
1057
!         may thus choose in this case:
1059
 
!          blencv(isca(iscalt(iphas))) = 1.0d0
 
1058
!          blencv(isca(iscalt)) = 1.0d0
1060
1059
 
1061
1060
!       For non-user scalars relative to specific physics (coal, combustion,
1062
1061
!         electric arcs: see usppmo) implicitly defined by the model,
1066
1065
 
1067
1066
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
1068
1067
 
1069
 
iphas = 1
1070
 
 
1071
 
blencv(iu(iphas)) = 1.0d0
1072
 
blencv(iv(iphas)) = 1.0d0
1073
 
blencv(iw(iphas)) = 1.0d0
 
1068
blencv(iu) = 1.0d0
 
1069
blencv(iv) = 1.0d0
 
1070
blencv(iw) = 1.0d0
1074
1071
if (nscaus.ge.1) then
1075
1072
  do ii = 1, nscaus
1076
1073
    blencv(isca(ii)) = 1.0d0
1088
1085
!                            j = 0: conjugate gradient,
1089
1086
!                            j = 1: Jacobi
1090
1087
!                            j = 2: bi-CgStab
 
1088
!                            j = 3: GMRES
1091
1089
 
1092
1090
!     nitmax: maximum number of iterations for each unknown ivar
1093
1091
!     epsilo: relative precision for the solution of the linear system.
1097
1095
iutile = 0
1098
1096
if (iutile.eq.1) then
1099
1097
 
1100
 
  iphas = 1
1101
 
  iresol(iu(iphas)) = 2
1102
 
  iresol(iv(iphas)) = 2
1103
 
  iresol(iw(iphas)) = 2
 
1098
  iresol(iu) = 2
 
1099
  iresol(iv) = 2
 
1100
  iresol(iw) = 2
1104
1101
  if (nscaus.ge.1) then
1105
1102
    do ii = 1, nscaus
1106
1103
      iresol(isca(ii)) = 2
1123
1120
 
1124
1121
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
1125
1122
 
1126
 
iphas = 1
1127
 
imgr(ipr(iphas)) = 1
 
1123
! mltmmn = 300  ! mean number of cells under which merging takes place
 
1124
! mltmgl = 500  ! global number of cells under which merging takes place
 
1125
! mltmmr = 1    ! number of active ranks under which no merging is done
 
1126
! mltmst = 4    ! number of ranks over which merging takes place
 
1127
 
 
1128
imgr(ipr) = 1
1128
1129
 
1129
1130
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
1130
1131
 
1136
1137
!     For difficult cases, a stabilization may be obtained by not
1137
1138
!     reconstructing the convective and diffusive flux for variables
1138
1139
!     of the turbulence model, that is
1139
 
!       in k-epsilon: if (itytur(iphas).eq.2) then
1140
 
!          ircflu(ik(iphas))   = 0 and ircflu(iep(iphas))  = 0
1141
 
!       in Rij-epsilon: if (itytur(iphas).eq.3) then
1142
 
!          ircflu(ir11(iphas)) = 0,    ircflu(ir22(iphas)) = 0,
1143
 
!          ircflu(ir33(iphas)) = 0,
1144
 
!          ircflu(ir12(iphas)) = 0,    ircflu(ir23(iphas)) = 0,
1145
 
!          ircflu(ir23(iphas)) = 0,
1146
 
!                                  and ircflu(iep(iphas))  = 0
 
1140
!       in k-epsilon: if (itytur.eq.2) then
 
1141
!          ircflu(ik)   = 0 and ircflu(iep)  = 0
 
1142
!       in Rij-epsilon: if (itytur.eq.3) then
 
1143
!          ircflu(ir11) = 0,    ircflu(ir22) = 0,
 
1144
!          ircflu(ir33) = 0,
 
1145
!          ircflu(ir12) = 0,    ircflu(ir23) = 0,
 
1146
!          ircflu(ir23) = 0,
 
1147
!                                  and ircflu(iep)  = 0
1147
1148
!     (note that variable itytur is equal to iturb/10)
1148
1149
 
1149
1150
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
1154
1155
iutile = 0
1155
1156
if (iutile.eq.1) then
1156
1157
 
1157
 
  iphas = 1
1158
 
  if (iturb(iphas).eq.20) then
1159
 
    ircflu(ik(iphas))   = 0
1160
 
    ircflu(iep(iphas))  = 0
 
1158
  if (iturb.eq.20) then
 
1159
    ircflu(ik)   = 0
 
1160
    ircflu(iep)  = 0
1161
1161
  endif
1162
1162
 
1163
1163
endif
1206
1206
!                    the calculation is based on a
1207
1207
!                    reduced pressure P*=Ptot-ro0*g.(x-xref)
1208
1208
!                    (except in compressible case)
1209
 
!       xyzp0(3,.) : coordinates of the reference point for
 
1209
!       xyzp0(3)   : coordinates of the reference point for
1210
1210
!                    the total pressure (where it is equal to p0)
1211
1211
 
1212
1212
!     In general, it is not necessary to furnish a reference point xyz0.
1301
1301
 
1302
1302
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
1303
1303
 
1304
 
iphas = 1
1305
 
 
1306
 
ro0(iphas)    = 0.235d0
1307
 
viscl0(iphas) = 0.84d-6
1308
 
cp0(iphas)    = 1219.d0
 
1304
ro0    = 0.235d0
 
1305
viscl0 = 0.84d-6
 
1306
cp0    = 1219.d0
1309
1307
 
1310
1308
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
1311
1309
 
1312
 
iphas = 1
1313
 
 
1314
 
t0(iphas) = 1000.d0 + 273.15d0
1315
 
p0(iphas) = 1.01325d5
 
1310
t0 = 1000.d0 + 273.15d0
 
1311
p0 = 1.01325d5
1316
1312
! We only specify XYZ0 if we explicitely fix Dirichlet conditions
1317
1313
! for the pressure.
1318
 
! xyzp0(1,iphas) = 0.d0
1319
 
! xyzp0(2,iphas) = 0.d0
1320
 
! xyzp0(3,iphas) = 0.d0
 
1314
! xyzp0(1) = 0.d0
 
1315
! xyzp0(2) = 0.d0
 
1316
! xyzp0(3) = 0.d0
1321
1317
 
1322
1318
 
1323
1319
! --- irovar, ivivar: density and viscosity constant or not ?
1330
1326
!       in the uscfx1 user subroutine.
1331
1327
 
1332
1328
!     When no specific physics module is active, it is necessary to
1333
 
!       specify is the density and the molecular viscosity
 
1329
!       specify if the density and the molecular viscosity
1334
1330
!         are constant (irovar=0, ivivar=0)
1335
1331
!          or variable (irovar=1, ivivar=1)
1336
1332
 
1342
1338
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
1343
1339
 
1344
1340
if (nmodpp.eq.0) then
1345
 
  iphas = 1
1346
 
  irovar(iphas) = 0
1347
 
  ivivar(iphas) = 0
 
1341
  irovar = 0
 
1342
  ivivar = 0
1348
1343
endif
1349
1344
 
1350
1345
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
1403
1398
!     When no specific physics has been activated
1404
1399
!       (coal, combustion, electric arcs) and if a user scalar represents
1405
1400
!       the temperature or enthalpy:
1406
 
!       visls0(iscalt(iphas)) = Lambda/Cp
 
1401
!       visls0(iscalt) = Lambda/Cp
1407
1402
 
1408
1403
!     Here, as an example, we assign to viscl0 the viscosity of the
1409
1404
!       carrier phase, which is fitting for passive tracers which
1420
1415
    ! For scalars which are not variances
1421
1416
    if (iscavr(jj).le.0) then
1422
1417
      ! We define the diffusivity
1423
 
      visls0(jj) = viscl0(iphsca(jj))
 
1418
      visls0(jj) = viscl0
1424
1419
    endif
1425
1420
  enddo
1426
1421
 
1434
1429
 
1435
1430
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
1436
1431
 
1437
 
iphas = 1
1438
 
uref(iphas)    = 1.d0
 
1432
uref    = 1.d0
1439
1433
 
1440
1434
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
1441
1435
 
1448
1442
 
1449
1443
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
1450
1444
 
1451
 
iphas = 1
1452
 
almax(iphas) = -grand
 
1445
almax = -grand
1453
1446
 
1454
1447
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
1455
1448
 
1484
1477
 
1485
1478
  ! First moment: <u>
1486
1479
  imom  = 1
1487
 
  iphas = 1
1488
 
  idfmom(1,imom) =  iu(iphas)
 
1480
  idfmom(1,imom) =  iu
1489
1481
  ntdmom(imom)   =  1000
1490
1482
  ! Second moment: <rho u v>
1491
1483
  imom  = 2
1492
 
  iphas = 1
1493
 
  idfmom(1,imom) = -irom(iphas)
1494
 
  idfmom(2,imom) =  iu(iphas)
1495
 
  idfmom(3,imom) =  iv(iphas)
 
1484
  idfmom(1,imom) = -irom
 
1485
  idfmom(2,imom) =  iu
 
1486
  idfmom(3,imom) =  iv
1496
1487
  imoold(imom)   = -1
1497
1488
  ntdmom(imom)   =  10000
1498
1489
 
1537
1528
!     mode: <-- input, --> output, <-> modifies data, --- work array
1538
1529
!===============================================================================
1539
1530
 
 
1531
!===============================================================================
 
1532
! Module files
 
1533
!===============================================================================
 
1534
 
 
1535
use paramx
 
1536
use cstnum
 
1537
use dimens
 
1538
use numvar
 
1539
use optcal
 
1540
use cstphy
 
1541
use entsor
 
1542
use parall
 
1543
use period
 
1544
use ihmpre
 
1545
use ppppar
 
1546
use ppthch
 
1547
use ppincl
 
1548
 
 
1549
!===============================================================================
 
1550
 
1540
1551
implicit none
1541
1552
 
1542
 
!===============================================================================
1543
 
! Common blocks
1544
 
!===============================================================================
1545
 
 
1546
 
include "paramx.h"
1547
 
include "cstnum.h"
1548
 
include "dimens.h"
1549
 
include "numvar.h"
1550
 
include "optcal.h"
1551
 
include "cstphy.h"
1552
 
include "entsor.h"
1553
 
include "vector.h"
1554
 
include "parall.h"
1555
 
include "period.h"
1556
 
include "ihmpre.h"
1557
 
include "ppppar.h"
1558
 
include "ppthch.h"
1559
 
include "ppincl.h"
1560
 
 
1561
 
!===============================================================================
1562
 
 
1563
1553
! Arguments
1564
1554
 
1565
1555
integer nmodpp
1567
1557
 
1568
1558
! Local variables
1569
1559
 
1570
 
integer ii, iphas, ipp, imom, iutile
 
1560
integer ii, ipp, imom, iutile
1571
1561
 
1572
1562
!===============================================================================
1573
1563
 
1664
1654
iutile = 0
1665
1655
if (iutile.eq.1) then
1666
1656
 
1667
 
  iphas = 1
1668
 
 
1669
1657
  do ii = 1, nvar
1670
1658
    iwarni(ii) = 1
1671
1659
  enddo
1672
1660
 
1673
 
  iwarni(ipr(iphas)) = 2
1674
 
  iwarni(iu(iphas)) = 2
1675
 
  iwarni(iv(iphas)) = 2
1676
 
  iwarni(iw(iphas)) = 2
 
1661
  iwarni(ipr) = 2
 
1662
  iwarni(iu) = 2
 
1663
  iwarni(iv) = 2
 
1664
  iwarni(iw) = 2
1677
1665
 
1678
1666
endif
1679
1667
 
1680
1668
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
1681
1669
 
1682
 
! --- post-processing output
1683
 
 
1684
 
!     ichrvl: post-processing of the fluid domain (yes 1/no 0)
1685
 
!     ichrbo: post-processing of the domain boundary (yes 1/no 0)
1686
 
!     ichrsy: post-processing of zones coupled with SYRTHES (yes 1/ no 0)
1687
 
!     ichrmd: indicates if the meshes output are:
1688
 
!               0: fixed,
1689
 
!               1: deformable with constant connectivity,
1690
 
!               2: modifyable (may be completely redefined during the
1691
 
!                  calculation using the usmpst subroutine).
1692
 
!              10: as indmod = 0, with a displacement field
1693
 
!              11: as indmod = 1, with a displacement field
1694
 
!              11: as indmod = 2, with a displacement field
1695
 
 
1696
 
!     fmtchr: output format, amid
1697
 
!               'EnSight Gold', 'MED', or 'CGNS'
1698
 
!     optchr: options associated with the output format, separated by
1699
 
!             commas, from the following list:
1700
 
!               'text'              (text format, for EnSight)
1701
 
!               'binary'            (binary format, default choice)
1702
 
!               'big_endian'        (forces binary EnSight output to
1703
 
!                                   'big-endian' mode)
1704
 
!               'discard_polygons'  (ignore polygon-type faces)
1705
 
!               'discard_polyhedra' (ignore polyhedron-type cells)
1706
 
!               'divide_polygons'   (subdivides polygon-type faces)
1707
 
!               'divide_polyhedra'  (subdivides polyhedron-type cells)
1708
 
!               'split_tensors'     (writes tensors as separate scalars)
1709
 
 
1710
 
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
1711
 
 
1712
 
ichrvl = 1
1713
 
ichrbo = 0
1714
 
ichrsy = 0
1715
 
 
1716
 
ichrmd = 0
1717
 
 
1718
 
fmtchr = 'EnSight Gold'
1719
 
optchr = 'binary'
1720
 
 
1721
 
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
1722
 
 
1723
 
 
1724
 
! --- chronological output step
1725
 
!       (-1: only one valua at calculation end)
1726
 
!       (strictly positive valeu: output periodicity)
1727
 
 
1728
 
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
1729
 
 
1730
 
ntchr = -1
1731
 
 
1732
 
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
1733
 
 
1734
 
 
1735
1670
! --- history output step
1736
1671
 
1737
1672
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
1738
1673
 
1739
1674
nthist = 1
 
1675
frhist = -1.d0
1740
1676
 
1741
1677
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
1742
1678
 
1747
1683
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
1748
1684
 
1749
1685
ncapt  = 4
 
1686
tplfmt = 1 ! time plot format (1: .dat, 2: .csv, 3: both)
 
1687
 
1750
1688
xyzcap(1,1) = 0.30d0
1751
1689
xyzcap(2,1) = 0.15d0
1752
1690
xyzcap(3,1) = 0.01d0
1787
1725
 
1788
1726
! Current dynamic variables
1789
1727
 
1790
 
! Examples for phase 1
1791
 
iphas = 1
1792
 
 
1793
1728
! pressure variable
1794
 
ipp = ipprtp(ipr   (iphas))
 
1729
ipp = ipprtp(ipr   )
1795
1730
nomvar(ipp)   = 'Pressure'
1796
1731
ichrvr(ipp)   = 1
1797
1732
ilisvr(ipp)   = 1
1801
1736
endif
1802
1737
 
1803
1738
! variable v1x
1804
 
ipp = ipprtp(iu    (iphas))
 
1739
ipp = ipprtp(iu    )
1805
1740
nomvar(ipp)   = 'VelocityX'
1806
1741
ichrvr(ipp)   = 1
1807
1742
ilisvr(ipp)   = 1
1811
1746
endif
1812
1747
 
1813
1748
! v1y variable
1814
 
ipp = ipprtp(iv    (iphas))
 
1749
ipp = ipprtp(iv    )
1815
1750
nomvar(ipp)   = 'VelocityY'
1816
1751
ichrvr(ipp)   = 1
1817
1752
ilisvr(ipp)   = 1
1821
1756
endif
1822
1757
 
1823
1758
! v1z variable
1824
 
ipp = ipprtp(iw    (iphas))
 
1759
ipp = ipprtp(iw    )
1825
1760
nomvar(ipp)   = 'VelocityZ'
1826
1761
ichrvr(ipp)   = 1
1827
1762
ilisvr(ipp)   = 1
1830
1765
  nomvar(ipp)   = 'Rel VelocityZ'
1831
1766
endif
1832
1767
 
1833
 
if (itytur(iphas).eq.2) then
 
1768
if (itytur.eq.2) then
1834
1769
 
1835
1770
  ! turbulent kinetic energy
1836
 
  ipp = ipprtp(ik    (iphas))
 
1771
  ipp = ipprtp(ik    )
1837
1772
  nomvar(ipp)   = 'Turb Kinetic Energy'
1838
1773
  ichrvr(ipp)   = 1
1839
1774
  ilisvr(ipp)   = 1
1840
1775
  ihisvr(ipp,1) = -1
1841
1776
 
1842
1777
  ! turbulent dissipation
1843
 
  ipp = ipprtp(iep   (iphas))
 
1778
  ipp = ipprtp(iep   )
1844
1779
  nomvar(ipp)   = 'Turb Dissipation'
1845
1780
  ichrvr(ipp)   = 1
1846
1781
  ilisvr(ipp)   = 1
1847
1782
  ihisvr(ipp,1) = -1
1848
1783
 
1849
 
elseif (itytur(iphas).eq.3) then
 
1784
elseif (itytur.eq.3) then
1850
1785
 
1851
1786
  ! Reynolds stresses
1852
 
  ipp = ipprtp(ir11  (iphas))
 
1787
  ipp = ipprtp(ir11  )
1853
1788
  nomvar(ipp)   = 'R11'
1854
1789
  ichrvr(ipp)   = 1
1855
1790
  ilisvr(ipp)   = 1
1856
1791
  ihisvr(ipp,1) = -1
1857
1792
 
1858
1793
  ! Reynolds stresses
1859
 
  ipp = ipprtp(ir22  (iphas))
 
1794
  ipp = ipprtp(ir22  )
1860
1795
  nomvar(ipp)   = 'R22'
1861
1796
  ichrvr(ipp)   = 1
1862
1797
  ilisvr(ipp)   = 1
1863
1798
  ihisvr(ipp,1) = -1
1864
1799
 
1865
1800
  ! Reynolds stresses
1866
 
  ipp = ipprtp(ir33  (iphas))
 
1801
  ipp = ipprtp(ir33  )
1867
1802
  nomvar(ipp)   = 'R33'
1868
1803
  ichrvr(ipp)   = 1
1869
1804
  ilisvr(ipp)   = 1
1870
1805
  ihisvr(ipp,1) = -1
1871
1806
 
1872
1807
  ! Reynolds stresses
1873
 
  ipp = ipprtp(ir12  (iphas))
 
1808
  ipp = ipprtp(ir12  )
1874
1809
  nomvar(ipp)   = 'R12'
1875
1810
  ichrvr(ipp)   = 1
1876
1811
  ilisvr(ipp)   = 1
1877
1812
  ihisvr(ipp,1) = -1
1878
1813
 
1879
1814
  ! Reynolds stresses
1880
 
  ipp = ipprtp(ir13  (iphas))
 
1815
  ipp = ipprtp(ir13  )
1881
1816
  nomvar(ipp)   = 'R13'
1882
1817
  ichrvr(ipp)   = 1
1883
1818
  ilisvr(ipp)   = 1
1884
1819
  ihisvr(ipp,1) = -1
1885
1820
 
1886
1821
  ! Reynolds stresses
1887
 
  ipp = ipprtp(ir23  (iphas))
 
1822
  ipp = ipprtp(ir23  )
1888
1823
  nomvar(ipp)   = 'R23'
1889
1824
  ichrvr(ipp)   = 1
1890
1825
  ilisvr(ipp)   = 1
1891
1826
  ihisvr(ipp,1) = -1
1892
1827
 
1893
1828
  ! turbulent dissipation
1894
 
  ipp = ipprtp(iep   (iphas))
 
1829
  ipp = ipprtp(iep   )
1895
1830
  nomvar(ipp)   = 'Turb Dissipation'
1896
1831
  ichrvr(ipp)   = 1
1897
1832
  ilisvr(ipp)   = 1
1898
1833
  ihisvr(ipp,1) = -1
1899
1834
 
1900
 
elseif (iturb(iphas).eq.50) then
 
1835
elseif (iturb.eq.50) then
1901
1836
 
1902
1837
  ! turbulent kinetic energy
1903
 
  ipp = ipprtp(ik    (iphas))
 
1838
  ipp = ipprtp(ik    )
1904
1839
  nomvar(ipp)   = 'Turb Kinetic Energy'
1905
1840
  ichrvr(ipp)   = 1
1906
1841
  ilisvr(ipp)   = 1
1907
1842
  ihisvr(ipp,1) = -1
1908
1843
 
1909
1844
  ! turbulent dissipation
1910
 
  ipp = ipprtp(iep   (iphas))
 
1845
  ipp = ipprtp(iep   )
1911
1846
  nomvar(ipp)   = 'Turb Dissipation'
1912
1847
  ichrvr(ipp)   = 1
1913
1848
  ilisvr(ipp)   = 1
1914
1849
  ihisvr(ipp,1) = -1
1915
1850
 
1916
1851
  ! phi
1917
 
  ipp = ipprtp(iphi  (iphas))
 
1852
  ipp = ipprtp(iphi  )
1918
1853
  nomvar(ipp)   = 'Phi'
1919
1854
  ichrvr(ipp)   = 1
1920
1855
  ilisvr(ipp)   = 1
1921
1856
  ihisvr(ipp,1) = -1
1922
1857
 
1923
1858
  ! f_bar
1924
 
  ipp = ipprtp(ifb   (iphas))
 
1859
  ipp = ipprtp(ifb   )
1925
1860
  nomvar(ipp)   = 'f_bar'
1926
1861
  ichrvr(ipp)   = 1
1927
1862
  ilisvr(ipp)   = 1
1928
1863
  ihisvr(ipp,1) = -1
1929
1864
 
1930
 
elseif (iturb(iphas).eq.60) then
1931
 
 
1932
 
  ! turbulent kinetic energy
1933
 
  ipp = ipprtp(ik    (iphas))
 
1865
elseif (iturb.eq.51) then
 
1866
 
 
1867
  ! turbulent kinetic energy
 
1868
  ipp = ipprtp(ik    )
 
1869
  nomvar(ipp)   = 'Turb Kinetic Energy'
 
1870
  ichrvr(ipp)   = 1
 
1871
  ilisvr(ipp)   = 1
 
1872
  ihisvr(ipp,1) = -1
 
1873
 
 
1874
  ! turbulent dissipation
 
1875
  ipp = ipprtp(iep   )
 
1876
  nomvar(ipp)   = 'Turb Dissipation'
 
1877
  ichrvr(ipp)   = 1
 
1878
  ilisvr(ipp)   = 1
 
1879
  ihisvr(ipp,1) = -1
 
1880
 
 
1881
  ! phi
 
1882
  ipp = ipprtp(iphi  )
 
1883
  nomvar(ipp)   = 'Phi'
 
1884
  ichrvr(ipp)   = 1
 
1885
  ilisvr(ipp)   = 1
 
1886
  ihisvr(ipp,1) = -1
 
1887
 
 
1888
  ! alpha
 
1889
  ipp = ipprtp(ial   )
 
1890
  nomvar(ipp)   = 'Alpha'
 
1891
  ichrvr(ipp)   = 1
 
1892
  ilisvr(ipp)   = 1
 
1893
  ihisvr(ipp,1) = -1
 
1894
 
 
1895
elseif (iturb.eq.60) then
 
1896
 
 
1897
  ! turbulent kinetic energy
 
1898
  ipp = ipprtp(ik    )
1934
1899
  nomvar(ipp)   = 'Turb Kinetic Energy'
1935
1900
  ichrvr(ipp)   = 1
1936
1901
  ilisvr(ipp)   = 1
1937
1902
  ihisvr(ipp,1) = -1
1938
1903
 
1939
1904
  ! omega
1940
 
  ipp = ipprtp(iomg  (iphas))
 
1905
  ipp = ipprtp(iomg  )
1941
1906
  nomvar(ipp)   = 'Omega'
1942
1907
  ichrvr(ipp)   = 1
1943
1908
  ilisvr(ipp)   = 1
1944
1909
  ihisvr(ipp,1) = -1
1945
1910
 
 
1911
elseif (iturb.eq.70) then
 
1912
 
 
1913
  ! Spalart-Allmaras variable (viscosity-like)
 
1914
  ipp = ipprtp(inusa )
 
1915
  nomvar(ipp)   = 'NuTilda'
 
1916
  ichrvr(ipp)   = 1
 
1917
  ilisvr(ipp)   = 1
 
1918
  ihisvr(ipp,1) = -1
 
1919
 
1946
1920
endif
1947
1921
 
1948
1922
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
1979
1953
 
1980
1954
! Other variables
1981
1955
 
1982
 
iphas = 1
1983
 
 
1984
1956
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
1985
1957
 
1986
1958
! Density variable (output for post-processing only if variable or
1987
1959
!                   in the case of specific physics)
1988
 
ipp = ipppro(ipproc(irom  (iphas)))
 
1960
ipp = ipppro(ipproc(irom  ))
1989
1961
nomvar(ipp)   = 'Density'
1990
 
ichrvr(ipp)   = max(irovar(iphas),nmodpp)
 
1962
ichrvr(ipp)   = max(irovar,nmodpp)
1991
1963
ilisvr(ipp)   = 1
1992
1964
ihisvr(ipp,1) = -1
1993
1965
 
1994
1966
! specific heat
1995
 
if (icp   (iphas).gt.0) then
1996
 
  ipp = ipppro(ipproc(icp   (iphas)))
 
1967
if (icp   .gt.0) then
 
1968
  ipp = ipppro(ipproc(icp   ))
1997
1969
  nomvar(ipp)   = 'Specific Heat'
1998
1970
  ichrvr(ipp)   = 0
1999
1971
  ilisvr(ipp)   = 0
2001
1973
endif
2002
1974
 
2003
1975
! laminar viscosity
2004
 
ipp = ipppro(ipproc(iviscl(iphas)))
 
1976
ipp = ipppro(ipproc(iviscl))
2005
1977
nomvar(ipp)   = 'Laminar Viscosity'
2006
1978
ichrvr(ipp)   = 0
2007
1979
ilisvr(ipp)   = 0
2008
1980
ihisvr(ipp,1) = 0
2009
1981
 
2010
1982
! turbulent viscosity
2011
 
ipp = ipppro(ipproc(ivisct(iphas)))
 
1983
ipp = ipppro(ipproc(ivisct))
2012
1984
nomvar(ipp)   = 'Turb Viscosity'
2013
1985
ichrvr(ipp)   = 1
2014
1986
ilisvr(ipp)   = 1
2015
1987
ihisvr(ipp,1) = -1
2016
1988
 
2017
1989
! Courant number
2018
 
ipp = ipppro(ipproc(icour(iphas)))
 
1990
ipp = ipppro(ipproc(icour))
2019
1991
nomvar(ipp)   = 'CFL'
2020
1992
ichrvr(ipp)   = 1
2021
1993
ilisvr(ipp)   = 0
2022
1994
ihisvr(ipp,1) = -1
2023
1995
 
2024
1996
! Fourier number
2025
 
ipp = ipppro(ipproc(ifour(iphas)))
 
1997
ipp = ipppro(ipproc(ifour))
2026
1998
nomvar(ipp)   = 'Fourier Number'
2027
1999
ichrvr(ipp)   = 1
2028
2000
ilisvr(ipp)   = 0
2030
2002
 
2031
2003
! 'csmago' variable for dynamic L.E.S. models
2032
2004
!    (square of the Samgorinsky "constant")
2033
 
if (ismago(iphas).gt.0) then
2034
 
  ipp = ipppro(ipproc(ismago(iphas)))
 
2005
if (ismago.gt.0) then
 
2006
  ipp = ipppro(ipproc(ismago))
2035
2007
  nomvar(ipp)   = 'Csdyn2'
2036
2008
  ichrvr(ipp)   = 1
2037
2009
  ilisvr(ipp)   = 1
2050
2022
 
2051
2023
! total pressure (not defined in compressible case)
2052
2024
if (ippmod(icompf).lt.0) then
2053
 
  ipp = ipppro(ipproc(iprtot(iphas)))
 
2025
  ipp = ipppro(ipproc(iprtot))
2054
2026
  nomvar(ipp)   = 'Total Pressure'
2055
2027
  ichrvr(ipp)   = 1
2056
2028
  ilisvr(ipp)   = 1
2094
2066
 
2095
2067
return
2096
2068
end subroutine
2097
 
 
2098
 
 
2099
 
!===============================================================================
2100
 
 
2101
 
 
2102
 
subroutine ustbtr &
2103
 
!================
2104
 
 
2105
 
 ( ncel   , ncelet , nfac   , nfabor , nnod   ,                   &
2106
 
   longia , longra ,                                              &
2107
 
   nideve , nituse , nrdeve , nrtuse )
2108
 
 
2109
 
!===============================================================================
2110
 
! Purpose:
2111
 
! -------
2112
 
 
2113
 
! User subroutine to define the sizes of macro-arrays ia and ra,
2114
 
!   of user arrays ituser and rtuser,
2115
 
!   of developper arrays idevel and rdevel.
2116
 
 
2117
 
!-------------------------------------------------------------------------------
2118
 
! Arguments
2119
 
!__________________.____._____.________________________________________________.
2120
 
! name             !type!mode ! role                                           !
2121
 
!__________________!____!_____!________________________________________________!
2122
 
! ncel             ! i  ! <-- ! number of cells                                !
2123
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
2124
 
! nfac             ! i  ! <-- ! number of interior faces                       !
2125
 
! nfabor           ! i  ! <-- ! number of boundary faces                       !
2126
 
! nnod             ! i  ! <-- ! number of vertices                             !
2127
 
! longia           ! i  ! --> ! size of array ia                               !
2128
 
! longra           ! i  ! --> ! size of array ra                               !
2129
 
! nideve           ! i  ! --> ! size of array idevel                           !
2130
 
! nituse           ! i  ! --> ! size of array ituser                           !
2131
 
! nrdeve           ! i  ! --> ! size of array rdevel                           !
2132
 
! nrtuse           ! i  ! --> ! size of array rtuser                           !
2133
 
!__________________!____!_____!________________________________________________!
2134
 
 
2135
 
!     Type: i (integer), r (real), s (string), a (array), l (logical),
2136
 
!           and composite types (ex: ra real array)
2137
 
!     mode: <-- input, --> output, <-> modifies data, --- work array
2138
 
!===============================================================================
2139
 
 
2140
 
implicit none
2141
 
 
2142
 
!===============================================================================
2143
 
! Common blocks
2144
 
!===============================================================================
2145
 
 
2146
 
!===============================================================================
2147
 
 
2148
 
! Arguments
2149
 
 
2150
 
integer          ncel  , ncelet, nfac  , nfabor, nnod
2151
 
integer          longia, longra
2152
 
integer          nideve, nituse, nrdeve, nrtuse
2153
 
 
2154
 
!===============================================================================
2155
 
 
2156
 
! TEST_TO_REMOVE_FOR_USE_OF_SUBROUTINE_START
2157
 
!===============================================================================
2158
 
! 0.  This test allows the user to ensure that the version of this subroutine
2159
 
!       used is that from his case definition, and not that from the library.
2160
 
!     If a file from the GUI is used, this subroutine may not be mandatory,
2161
 
!       thus the default (library reference) version returns immediately.
2162
 
 
2163
 
if (1.eq.1) return
2164
 
 
2165
 
!===============================================================================
2166
 
! TEST_TO_REMOVE_FOR_USE_OF_SUBROUTINE_END
2167
 
 
2168
 
!===============================================================================
2169
 
! 1. Size of macro arrays ia and ra:
2170
 
 
2171
 
!  The user may need to modify the size of integer and real work
2172
 
!    arrays here: longia and longra respectively.
2173
 
 
2174
 
!  The number of integers 'longia' and the number of reals 'longra' depend
2175
 
!    on calculation options, on the element type and mesh characteristics
2176
 
!    (2d, 3d, hybrid, non-conforming, ...) and on the number of variables.
2177
 
!  In k-epsilon, if we note 'ncel' the local number of cells in the mesh,
2178
 
!    we ay usually use the following coarse overestimation:
2179
 
!    longia = 45*ncel and longra = 220*ncel. In Rij-epsilon, an additional
2180
 
!    20% may be applied.
2181
 
!  These values are relatively high so as to account for 2D meshes which
2182
 
!    have many boundary faces. A more precise but complex formula would be
2183
 
!    necessary. For large 3D cases, a more precise estimation is given by:
2184
 
!    longia = 25*ncel  and longra = 120*ncel.
2185
 
 
2186
 
!  If longia and longra are left at 0, then these values are estimated
2187
 
!    and set automatically.
2188
 
 
2189
 
!===============================================================================
2190
 
 
2191
 
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
2192
 
 
2193
 
! Size of main integer work array 'ia'
2194
 
 
2195
 
longia = 0
2196
 
 
2197
 
! Size of main real work array 'ra'
2198
 
 
2199
 
longra = 0
2200
 
 
2201
 
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
2202
 
 
2203
 
!===============================================================================
2204
 
! 2. Size of macro arrays ituser and rtuser:
2205
 
!===============================================================================
2206
 
 
2207
 
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_START
2208
 
 
2209
 
! Size user-reserved integer array 'ituser'
2210
 
 
2211
 
nituse = 0
2212
 
 
2213
 
! Size user-reserved real array 'rtuser'
2214
 
 
2215
 
nrtuse = 0
2216
 
 
2217
 
! EXAMPLE_CODE_TO_BE_ADAPTED_BY_THE_USER_END
2218
 
 
2219
 
 
2220
 
!----
2221
 
! Formats
2222
 
!----
2223
 
 
2224
 
 
2225
 
return
2226
 
end subroutine