1!-------------------------------------------------------------------------------
2
3! This file is part of Code_Saturne, a general-purpose CFD tool.
4!
5! Copyright (C) 1998-2021 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.
20
21!-------------------------------------------------------------------------------
22
23!> \file paramx.f90
24!> \brief Module for definition of general parameters
25
26module paramx
27
28  !=============================================================================
29
30  implicit none
31
32  !> \defgroup paramx Module for definition of general parameters
33
34  !> \addtogroup paramx
35  !> \{
36
37  !=============================================================================
38
39  !> maximum number of scalars solutions of an
40  !> advection equation, apart from the variables of the turbulence model
41  !> \f$ (k, \varepsilon, R_{ij}, \omega, \varphi, \overline{f}, \alpha, \nu_t\f$)
42  !> , that is to say
43  !> the temperature and other scalars (passive or not, user-defined or not)
44  integer   nscamx
45
46  !> maximal number of variables = nscamx + 12 (u,v,w,P,Rij,e,alp)
47  integer   nvarmx
48
49  parameter(nscamx=500)
50  parameter(nvarmx=nscamx+12)
51
52  !> Maximal possible boundary condition types
53  integer    ntypmx
54  parameter(ntypmx=200)
55
56  !> \anchor iindef
57  !> pointer for undefined type face (non-standard case)
58  integer   iindef
59
60  !> \anchor ientre
61  !> if \ref itypfb=ientre: inlet face.
62  !> -  Zero-flux condition for pressure and Dirichlet condition for all
63  !> other variables. The value of the Dirichlet must be given in
64  !> \ref rcodcl "rcodcl"(ifac,ivar,1) for every value of \c ivar, except for
65  !> \c ivar = \ref ipr. The other values of \ref rcodcl and
66  !> \ref icodcl are filled automatically.
67  integer   ientre
68
69  !> \anchor isolib
70  !> if \ref itypfb=isolib: free outlet face (or more precisely free inlet/outlet
71  !> with forced pressure)
72  !>  - The pressure is always treated with a Dirichlet condition, calculated with the constraint
73  !> \f$\displaystyle \frac{\partial }{\partial n}\left(\frac{ \partial P}{\partial \tau}\right)=0\f$.
74  !> The pressure is set to \f$P_0\f$ at the first \ref isolib face met.
75  !> The pressure calibration is always done on a single face, even if there are
76  !> several outlets.
77  !>  - if the mass flow is coming in, the velocity is set to zero
78  !> and a Dirichlet condition for the scalars and the turbulent quantities is used
79  !> (or zero-flux condition if no Dirichlet value has been specified).
80  !>  - if the mass flow is going out, zero-flux condition are set for the velocity,
81  !> the scalars and the turbulent quantities.
82  !>  - Nothing is written in \ref icodcl or \ref rcodcl for the pressure or
83  !> the velocity. An optional Dirichlet condition can be specified for the scalars
84  !> and turbulent quantities.
85  !> \remark A standard \ref isolib outlet face amounts to a Dirichlet
86  !> condition (\ref icodcl=1) for the pressure, a free outlet condition
87  !> (\ref icodcl=9) for the velocity and a Dirichlet condition
88  !> (\ref icodcl=1) if the user has specified a Dirichlet value or a zero-flux
89  !> condition (\ref icodcl=3) for the other variables.
90  integer   isolib
91
92  !> \anchor isymet
93  !> if \ref itypfb=isymet: symmetry face (or wall without friction).
94  !> - Nothing to be writen in \ref icodcl and  \ref rcodcl.
95  integer   isymet
96
97  !> \anchor iparoi
98  !> if \ref itypfb=iparoi: smooth solid wall face, impermeable and with friction.
99  integer   iparoi
100
101  !> \anchor iparug
102  !> if \ref itypfb=iparug: rough solid wall face, impermeable and with friction.
103  integer   iparug
104
105  !> if \ref itypfb=iesicf: imposed inlet/outlet for compressible flow (for example, supersonic inlet).
106  !>  - A boundary value has to be given for the following quantities:
107  !>         - velocity
108  !>         - two of the four thermodynamical properties: density, pressure, total energy, temperature
109  !>         - all other variables.
110  !>  - Homogeneous Neumann boundary condition for the pressure (seen by the reconstruction
111  !> gradients and the diffusion operator).
112  !>  - Dirichlet condition for the velocity and the total energy.
113  !>  - The boundary convective fluxes of momentum and total energy are computed from a Rusanov scheme
114  !> for stability reasons. Note that the pressure boundary value is needed to compute those
115  !> two fluxes (seen by the pressure gradient of the momentum equation).
116  !>  - If the mass flow is coming in, Dirichlet condition for the scalars and the turbulent quantities
117  !> is used (or zero-flux condition if no Dirichlet value has been specified).
118  !>  - If the mass flow is going out, zero-flux condition are set for the scalars and the turbulent
119  !> quantities.
120  integer   iesicf
121
122  !> if \ref itypfb=isspcf: supersonic outlet for compressible flow.
123  !>  - Nothing needs to be given. The imposed state at the boundary is the upstream state
124  !> (values in boundary cells).
125  !>  - Homogeneous Neumann boundary condition for the pressure (seen by the reconstruction
126  !> gradients and the diffusion operator).
127  !>  - Dirichlet (\ref icodcl=1) for the velocity and the total energy.
128  !> (pressure boundary value seen by the pressure gradient of the momentum equation).
129  !>  - If the mass flow is coming in, Dirichlet condition for the scalars and the turbulent quantities
130  !> is used (or zero-flux condition if no Dirichlet value has been specified).
131  !>  - If the mass flow is going out, zero-flux condition are set for the scalars and the turbulent
132  !> quantities.
133  integer   isspcf
134
135  !> if \ref itypfb=isopcf: mixed outlet for compressible flow with a given pressure.
136  !>  - Boundary values are obtained by solving a Riemann problem between an inner (values
137  !> at boundary cells center) and an outer state. The given pressure is considered as an
138  !> outer value.
139  !>  - Homogeneous Neumann boundary condition for the pressure (seen by the reconstruction
140  !> gradients and the diffusion operator).
141  !>  - Dirichlet (\ref icodcl=1) for the velocity and the total energy.
142  !>  - Analytical boundary convective fluxes of momentum and total energy are computed.
143  !> Note that the pressure boundary value is needed to compute those two fluxes.
144  !> (seen by the pressure gradient of the momentum equation).
145  !>  - If the mass flow is coming in, Dirichlet condition for the scalars and the turbulent quantities
146  !> is used (or zero-flux condition if no Dirichlet value has been specified).
147  !>  - If the mass flow is going out, zero-flux condition are set for the scalars and the turbulent
148  !> quantities.
149  integer   isopcf
150
151  !> if \ref itypfb=iephcf: mixed inlet for compressible flow with given total pressure
152  !>                        and total enthalpy (reservoir boundary conditions).
153  !>  - Boundary values are obtained by solving a Riemann problem between an inner (values
154  !> at boundary cells center) and an outer state.
155  !>  - Homogeneous Neumann boundary condition for the pressure (seen by the reconstruction
156  !> gradients and the diffusion operator).
157  !>  - Dirichlet (\ref icodcl=1) for velocity and total energy.
158  !>  - Analytical boundary convective fluxes of momentum and total energy are computed.
159  !> Note that the pressure boundary value is needed to compute those two fluxes
160  !> (seen by the pressure gradient of the momentum equation).
161  !>   - If the mass flow is coming in, Dirichlet condition for the scalars and the turbulent quantities
162  !> is used (or zero-flux condition if no Dirichlet value has been specified).
163  !>  - If the mass flow is going out, zero-flux condition are set for the scalars and the turbulent
164  !> quantities.
165  integer   iephcf
166
167  ! TODO : not available yet.
168  integer   ieqhcf
169
170  !> \anchor icscpl
171  !> code/code coupling condition
172  integer   icscpl
173
174  !> \anchor icscpd
175  !> code/code coupling condition with decentered flux
176  integer   icscpd
177
178  !> \anchor ifrent
179  !> if \ref itypfb=ifrent: free entrance based on Bernoulli equation when
180  !> the flow is incoming, standard outlet when outgoing
181  integer   ifrent
182
183  !> \anchor ifresf
184  !> if \ref itypfb=ifresf: free surface for mobile mesh boundary condition
185  !>  - Homogeneous Neumann boundary condition for velocity and total energy (seen by the reconstruction
186  !> gradients and the diffusion operator).
187  !>  - Dirichlet (\ref icodcl=1) for the pressure.
188  !> Alse a boundary condition type for mesh velocity in ALE for modelling
189  !> free surface (\f$ \vect{u} \cdot \vect{S} = \vect{w} \cdot \vect{S} \f$).
190  integer   ifresf
191
192  !> \anchor i_convective_inlet
193  !> if \ref itypfb=i_convective_inlet: inlet face where the total mass flux is
194  !>                                    prescribed.
195  !> -  Zero-flux condition for pressure and Dirichlet condition for all
196  !> other variables. The value of the Dirichlet must be given in
197  !> \ref rcodcl "rcodcl"(ifac,ivar,1) for every value of \c ivar, except for
198  !> \c ivar = \ref numvar::ipr "ipr". The other values of \ref rcodcl and
199  !> \ref icodcl are filled automatically.
200  !> The diffusive flux is CANCELLED (therefore the total mass flux is due to
201  !> convection only).
202  integer   i_convective_inlet
203
204
205  parameter(iindef=1, ientre=2, isolib=3, isymet=4, iparoi=5,       &
206            iparug=6, iesicf=7, isspcf=8, isopcf=9, iephcf=10,      &
207            ieqhcf=11, icscpl=12, icscpd=13, ifrent=14, ifresf=15,  &
208            i_convective_inlet=16)
209
210  !> maximal number of valuators for Navier-Stokes
211  integer    nestmx
212  parameter (nestmx=4)
213
214  !> Error estimator for Navier-Stokes.
215  !> iest = iespre: prediction, (default name: EsPre).
216  !> After the velocity prediction step (yielding \f$\vect{u}^*\f$), the
217  !> estimator \f$\eta^{\,pred}_{\,i,k}(\vect{u}^*)\f$, local variable calculated
218  !> at every cell \f$ \Omega_i \f$, is created from
219  !> \f$\vect{\mathcal R}^{\,pred}(\vect{u}^*)\f$,
220  !> which represents the residual of the equation solved during this step:
221  !> \f$\vect{u}\f$ and \f$ P \f$:
222  !> \f{eqnarray*}{
223  !>   \vect{\mathcal R}^{\,pred}(\vect{u}^*)
224  !>       & = & \rho^n \dfrac{\vect{u}^*-\vect{u}^n}{\Delta t}
225  !>           + \rho^n \vect{u}^n \cdot \gradt (\vect{u}^*)
226  !>           - \divv \left((\mu+\mu_t)^n \gradt (\vect{u}^*) \right)
227  !>           + \grad(P^n)
228  !>   \\  & - & \text{rest of the right-hand member }
229  !>            (\vect{u}^n, P^n, \text{other variables}^n)
230  !> \f}
231  !>  - By definition:
232  !> \f$ \eta^{\,pred}_{\,i,k}(\vect{u}^*)= {|\Omega_i|}^{\,(k-2)/2}\ ||\vect{\mathcal R}^{\,pred}(\vect{u}^*)||
233  !> _{{IL}^{2}(\Omega_i)} \f$
234  !>  - The first family, k=1, suppresses the
235  !> volume \f$ |\Omega_i| \f$ which intrinsicly appears  with the norm
236  !> \f$ {IL}^{2}(\Omega_i) \f$.
237  !>  - The second family, k=2, exactly represents the norm
238  !> \f$ {IL}^{2}(\Omega_i) \f$. The size of the cell therefore
239  !> appears in its calculation and induces a weighting effect.
240  !>  - \f$ \eta^{\,pred}_{\,i,k}(\vect{u}^*)\f$  is ideally equal to zero when the
241  !> reconstruction methods are perfect and the associated system is solved exactly.
242  integer   iespre
243
244  !> Error estimator for Navier-Stokes.
245  !> iest = iesder: drift  (default name: EsDer).
246  !> The estimator \f$\eta^{\,der}_{\,i,k}(\vect{u}^{\,n+1})\f$ is based on the
247  !> following quantity (intrinsic to the code):
248  !> \f{eqnarray*}{
249  !> \eta^{\,der}_{\,i,k}(\vect{u}^{\,n+1})
250  !>    &=& {|\Omega_i|}^{(k-2)/2}
251  !>       || \divs (\text{corrected mass flow after the pressure step})
252  !>       - \Gamma||_{{L}^{2}(\Omega_i)}
253  !> \\ &=& {|\Omega_i|}^{(1-k)/2}
254  !>      | \divs (\text{corrected mass flow after the pressure step})- \Gamma|
255  !> \f}
256  !>  - Ideally, it is equal to zero when the Poisson equation related to the pressure is
257  !> solved exactly.
258  integer   iesder
259
260  !> Error estimator for Navier-Stokes.
261  !> iest = iescor: correction, (default name: EsCor).
262  !> The estimator \f$ \eta^{\,corr}_{\,i,k}(\vect{u}^{\,n+1})\f$ comes directly
263  !> from the mass flow calculated with the updated velocity field:
264  !> \f{eqnarray*}{
265  !> \eta^{\,corr}_{\,i,k}(\vect{u}^{\,n+1})=
266  !> |\Omega_i|^{\,\delta_{\,2,k}}\ |div (\rho^n \vect{u}^{n+1}) - \Gamma|
267  !> \f}
268  !> - The velocities \f$\vect{u}^{n+1}\f$ are taken at the cell centers,
269  !> the divergence is calculated after projection on the faces.
270  !> \f$ \,\delta_{\,2,k}\f$ represents the Kronecker symbol.
271  !> - The first family, k=1, is the absolute raw value of the divergence of the mass flow
272  !< minus the mass source term.
273  !> The second family, $k=2$, represents a physical property and allows to evaluate
274  !> the difference in \f$kg.s^{\,-1}\f$.
275  !> - Ideally, it is equal to zero when the Poisson equation is solved exactly and
276  !> the projection from the mass flux at the faces to the velocity at the cell
277  !> centers is made in a set of  functions with null divergence.
278  integer   iescor
279
280  !> Error estimator for Navier-Stokes. iest = iestot: total, (default name: EsTot).
281  !> The estimator \f$ \eta^{\,tot}_{\,i,k}(\vect{u}^{\,n+1})\f$, local variable
282  !> calculated at every cell \f$\Omega_i\f$, is based on the quantity
283  !> \f$\vect{\mathcal R}^{\,tot}(\vect{u}^{\,n+1})\f$, which represents the
284  !> residual of the equation using the updated values of
285  !> \f$\vect{u}\f$ and \f$P\f$:
286  !> \f{eqnarray*}{
287  !>   \vect{\mathcal R}^{\,pred}(\vect{u}^*)
288  !>       & = & \rho^n \dfrac{\vect{u}^*-\vect{u}^n}{\Delta t}
289  !>           + \rho^n \vect{u}^n \cdot \gradt (\vect{u}^*)
290  !>           - \divv \left((\mu+\mu_t)^n \gradt (\vect{u}^*) \right)
291  !>           + \grad(P^n)
292  !>   \\  & - & \text{rest of the right-hand member }
293  !>            (\vect{u}^n, P^n, \text{other variables}^n)
294  !> \f}
295  !> - By definition:
296  !> \f$ \eta^{\,tot}_{\,i,k}(\vect{u}^{\,n+1})= {|\Omega_i|}^{\,(k-2)/2}\ ||\vect{\mathcal R}^{\,tot}(\vect{u}^{\,n+1})||
297  !> _{{I\hspace{-.25em}L}^{2}(\Omega_i)} \f$
298  !> - The mass flux in the convective term is recalculated from \f$\vect{u}^{n+1}\f$
299  !> expressed at the cell centers (and not taken from the updated mass flow at the
300  !> faces).
301  !> - As for the prediction estimator:
302  !>   - The first family, k=1, suppresses the
303  !> volume \f$ |\Omega_i| \f$ which intrinsicly appears  with the norm
304  !> \f$ {IL}^{2}(\Omega_i) \f$.
305  !>   - The second family, k=2, exactly represents the norm
306  !> \f$ {IL}^{2}(\Omega_i) \f$. The size of the cell therefore
307  !> appears in its calculation and induces a weighting effect.
308  integer   iestot
309  parameter (iespre=1, iesder=2, iescor=3, iestot=4)
310
311  ! conditions aux limites possibles pour la vitesse de maillage en ale
312
313  !> \anchor ibfixe
314  !> boundary condition type for mesh velocity in ALE: fixed wall
315  integer   ibfixe
316
317  !> \anchor igliss
318  !> boundary condition type for mesh velocity in ALE: sliding wall
319  integer   igliss
320
321  !> \anchor ivimpo
322  !> boundary condition type for mesh velocity in ALE: imposed velocity.
323  !> - In the case where all the nodes of a face have a imposed displacement,
324  !> it is not necessary to fill the tables with boundary conditions
325  !> mesh velocity for this face, they will be erased. In the other case,
326  !> the value of the Dirichlet must be given in \ref rcodcl "rcodcl"(ifac,ivar,1)
327  !> for every value of \c ivar (\ref iuma, \ref ivma and \ref iwma).
328  !> The other boxes of \ref rcodcl and \ref icodcl are completed automatically.
329  !> The tangential mesh velocity is taken like a tape speed under the
330  !> boundary conditions of wall for the fluid, except if wall fluid velocity
331  !> was specified by the user in the interface or \ref cs_user_boundary_conditions
332  !> (in which case it is this speed which is considered).
333  integer   ivimpo
334
335  parameter(ibfixe=1, igliss=2, ivimpo=3)
336
337  !> maximum number of structures in ALE
338  integer    nstrmx
339  parameter (nstrmx=200)
340
341  !=============================================================================
342
343  !> \}
344
345  ! Temporary former Fortan subroutine names so that the user soubroutines
346  ! do not compile if the deprecated name (now used for the C routine) is used.
347  integer cs_user_boundary_conditions, cs_user_parameters,         &
348          cs_user_initialization, cs_user_physical_properties,     &
349          cs_user_extra_operations, ushist, cs_f_user_head_losses, &
350          cs_user_turbulence_source_terms,                         &
351          usatph, usvosy, usvpst, usati1, usthht
352
353end module paramx
354