1!-------------------------------------------------------------------------------
2
3!VERS
4
5! This file is part of Code_Saturne, a general-purpose CFD tool.
6!
7! Copyright (C) 1998-2021 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.
22
23!-------------------------------------------------------------------------------
24
25!===============================================================================
26!> \file cs_user_physical_properties.f90
27!>
28!> \brief Definition of physical variable laws.
29!>
30!> See \ref physical_properties for examples.
31!>
32
33!===============================================================================
34!> \brief Definition of physical variable laws.
35!>
36!> \section Warning
37!>
38!> It is \b forbidden to modify turbulent viscosity \c visct here
39!> (a specific subroutine is dedicated to that: \ref usvist)
40!>
41!> - icp = 0 must <b> have been specified </b>
42!>    in \ref usipsu if we wish to define a variable specific heat
43!>    cpro_cp (otherwise: memory overwrite).
44!>
45!> - the kivisl field integer key (diffusivity_id)
46!>    must <b> have been specified </b>
47!>    in \ref usipsu if we wish to define a variable viscosity
48!>    \c viscls.
49!>
50!>
51!> \remarks
52!>  - This routine is called at the beginning of each time step
53!>    Thus, <b> AT THE FIRST TIME STEP </b> (non-restart case), the only
54!>    values initialized before this call are those defined
55!>      - in the GUI or  \ref usipsu (cs_user_parameters.f90)
56!>             - density    (initialized at \c ro0)
57!>             - viscosity  (initialized at \c viscl0)
58!>      - in the GUI or \ref cs_user_initialization
59!>             - calculation variables (initialized at 0 by defaut
60!>             or to the value given in the GUI or in \ref cs_user_initialization)
61!>
62!>  - We may define here variation laws for cell properties, for:
63!>     - density:                                    rom    kg/m3
64!>     - density at boundary faces:                  romb   kg/m3)
65!>     - molecular viscosity:                        cpro_viscl  kg/(m s)
66!>     - specific heat:                              cpro_cp     J/(kg degrees)
67!>     - diffusivities associated with scalars:      cpro_vscalt kg/(m s)
68!>
69!> \b Warning: if the scalar is the temperature, cpro_vscalt corresponds
70!> to its conductivity (Lambda) in W/(m K)
71!>
72!>
73!> The types of boundary faces at the previous time step are available
74!>   (except at the first time step, where arrays \c itypfb and \c itrifb have
75!>   not been initialized yet)
76!>
77!> It is recommended to keep only the minimum necessary in this file
78!>   (i.e. remove all unused example code)
79!>
80!>
81!> \section usphyv_cell_id Cells identification
82!>
83!> Cells may be identified using the \ref getcel subroutine.
84!> The syntax of this subroutine is described in the
85!> \ref cs_user_boundary_conditions subroutine,
86!> but a more thorough description can be found in the user guide.
87!
88!-------------------------------------------------------------------------------
89
90!-------------------------------------------------------------------------------
91! Arguments
92!______________________________________________________________________________.
93!  mode           name          role                                           !
94!______________________________________________________________________________!
95!> \param[in]     nvar          total number of variables
96!> \param[in]     nscal         total number of scalars
97!> \param[in]     mbrom         indicator of filling of romb array
98!> \param[in]     dt            time step (per cell)
99!_______________________________________________________________________________
100
101subroutine usphyv &
102 ( nvar   , nscal  ,                                              &
103   mbrom  ,                                                       &
104   dt     )
105
106!===============================================================================
107
108!===============================================================================
109! Module files
110!===============================================================================
111
112use paramx
113use pointe
114use numvar
115use optcal
116use cstphy
117use cstnum
118use entsor
119use parall
120use period
121use ppppar
122use ppthch
123use ppincl
124use field
125use mesh
126use lagran
127use cs_c_bindings
128
129!===============================================================================
130
131implicit none
132
133! Arguments
134
135integer          nvar   , nscal
136
137integer          mbrom
138
139double precision dt(ncelet)
140
141!===============================================================================
142
143!--------
144! Formats
145!--------
146
147!----
148! End
149!----
150
151return
152end subroutine usphyv
153
154!===============================================================================
155!> \brief Modify turbulent viscosity
156!>
157!> This subroutine is called at beginning of each time step
158!> after the computation of the turbulent viscosity
159!> (physical quantities have already been computed in \ref usphyv).
160!>
161!> Turbulent viscosity \f$ \mu_T \f$ (kg/(m s)) can be modified.
162!>
163!> A modification of the turbulent viscosity can lead to very
164!> significant differences between solutions and even give wrong
165!> results.
166!>
167!> This subroutine is therefore reserved to expert users.
168!
169!-------------------------------------------------------------------------------
170
171!-------------------------------------------------------------------------------
172! Arguments
173!______________________________________________________________________________.
174!  mode           name          role                                           !
175!______________________________________________________________________________!
176!> \param[in]     nvar          total number of variables
177!> \param[in]     nscal         total number of scalars
178!> \param[in]     ncepdp        number of cells with head loss
179!> \param[in]     ncesmp        number of cells with mass source term
180!> \param[in]     icepdc        head loss cell numbering
181!> \param[in]     icetsm        numbering of cells with mass source term
182!> \param[in]     itypsm        kind of mass source for each variable
183!> \param[in]     dt            time step (per cell)
184!> \param[in]     ckupdc        work array for head loss terms
185!> \param[in]     smacel        values of variables related to mass source
186!>                              term. If ivar=ipr, smacel=mass flux
187!_______________________________________________________________________________
188
189subroutine usvist &
190 ( nvar   , nscal  , ncepdp , ncesmp ,                            &
191   icepdc , icetsm , itypsm ,                                     &
192   dt     ,                                                       &
193   ckupdc , smacel )
194
195!===============================================================================
196
197!===============================================================================
198! Module files
199!===============================================================================
200
201use paramx
202use numvar
203use optcal
204use cstphy
205use entsor
206use parall
207use period
208use mesh
209use field
210use field_operator
211
212!===============================================================================
213
214implicit none
215
216! Arguments
217
218integer          nvar   , nscal
219integer          ncepdp , ncesmp
220
221integer          icepdc(ncepdp)
222integer          icetsm(ncesmp), itypsm(ncesmp,nvar)
223
224double precision dt(ncelet)
225double precision ckupdc(6,ncepdp), smacel(ncesmp,nvar)
226
227!===============================================================================
228
229!--------
230! Formats
231!--------
232
233!----
234! End
235!----
236
237return
238end subroutine usvist
239
240
241!===============================================================================
242
243!===============================================================================
244!> \brief user modification of the Smagorinsky constant in the case of a
245!>   dynamic model
246!>
247!>              SMAGOR = Mij.Lij / Mij.Mij
248!>
249!> The local averages of the numerator and denominator are done before calling
250!> this subroutine, so
251!>
252!>              SMAGOR = < Mij.Lij > / < Mij.Mij >
253!>
254!> In this subroutine, Mij.Lij and Mij.Mij are passed as arguments before
255!> the local average.
256
257!-------------------------------------------------------------------------------
258! Arguments
259!______________________________________________________________________________.
260!  mode           name          role                                           !
261!______________________________________________________________________________!
262!> \param[in]     nvar          total number of variables
263!> \param[in]     nscal         total number of scalars
264!> \param[in]     ncepdp        number of cells with head loss
265!> \param[in]     ncesmp        number of cells with mass source term
266!> \param[in]     icepdc        head loss cell numbering
267!> \param[in]     icetsm        numbering of cells with mass source term
268!> \param[in]     itypsm        kind of mass source for each variable
269!> \param[in]     dt            time step (per cell)
270!> \param[in]     ckupdc        work array for head loss terms
271!> \param[in]     smacel        values of variables related to mass source
272!>                              term. If ivar=ipr, smacel=mass flux
273!> \param[in]     mijlij        mij.lij before the local averaging
274!> \param[in]     mijmij        mij.mij before the local averaging
275!_______________________________________________________________________________
276
277subroutine ussmag &
278 ( nvar   , nscal  , ncepdp , ncesmp ,                            &
279   icepdc , icetsm , itypsm ,                                     &
280   dt     ,                                                       &
281   ckupdc , smacel ,                                              &
282   mijlij , mijmij )
283
284!===============================================================================
285
286!===============================================================================
287! Module files
288!===============================================================================
289
290use paramx
291use numvar
292use cstnum
293use optcal
294use cstphy
295use entsor
296use parall
297use field
298use mesh
299
300!===============================================================================
301
302implicit none
303
304! Arguments
305
306integer          nvar   , nscal
307integer          ncepdp , ncesmp
308
309integer          icepdc(ncepdp)
310integer          icetsm(ncesmp), itypsm(ncesmp,nvar)
311
312double precision dt(ncelet)
313double precision ckupdc(6,ncepdp), smacel(ncesmp,nvar)
314double precision mijlij(ncelet), mijmij(ncelet)
315
316! Local
317
318double precision, dimension(:), pointer :: cpro_smago
319
320call field_get_val_s(ismago, cpro_smago)
321
322!===============================================================================
323
324!----
325! End
326!----
327
328return
329end subroutine ussmag
330
331!===============================================================================
332
333