File: cs_user_boundary_mass_source_terms.f90

package info (click to toggle)
code-saturne 4.3.3%2Brepack-1
  • links: PTS, VCS
  • area: main
  • in suites: stretch
  • size: 77,992 kB
  • sloc: ansic: 281,257; f90: 122,305; python: 56,490; makefile: 3,915; xml: 3,285; cpp: 3,183; sh: 1,139; lex: 176; yacc: 101; sed: 16
file content (253 lines) | stat: -rw-r--r-- 9,363 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
!-------------------------------------------------------------------------------

!VERS

! This file is part of Code_Saturne, a general-purpose CFD tool.
!
! Copyright (C) 1998-2016 EDF S.A.
!
! This program is free software; you can redistribute it and/or modify it under
! the terms of the GNU General Public License as published by the Free Software
! Foundation; either version 2 of the License, or (at your option) any later
! version.
!
! This program is distributed in the hope that it will be useful, but WITHOUT
! ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
! FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
! details.
!
! You should have received a copy of the GNU General Public License along with
! this program; if not, write to the Free Software Foundation, Inc., 51 Franklin
! Street, Fifth Floor, Boston, MA 02110-1301, USA.

!-------------------------------------------------------------------------------

!===============================================================================
! Function:
! ---------

!> \file cs_user_boundary_mass_source_terms.f90
!>
!> \brief Source terms associated at the boundary faces and the neighboring
!> cells with surface condensation.
!>
!> This subroutine fills the condensation source terms for each variable at
!> the cell center associated to the boundary faces identifed in the mesh.
!> The fluid exchange coefficient is computed with a empiric law to be
!> imposed at the boundary face where the condensation phenomenon occurs.
!>
!> This user subroutine is called which allows the setting of
!> \f$ \gamma_{\mbox{cond}} \f$ the condensation source term.
!>
!> This function fills the condensation source term array gamma_cond adding
!> to the following equations:
!>
!> - The equation for mass conservation:
!> \f[ D\frac{rho}{dt} + divs \left( \rho \vect{u}^n\right) = \Gamma _{cond}
!> \f]
!>
!> - The equation for a variable \f$\Phi \f$:
!> \f[ D\frac{\phi}{dt} = ... + \Gamma _{cond}*(\Phi _i - \Phi)
!> \f]
!>
!> discretized as below:
!>
!> \f[ \rho*\dfrac{\Phi^{n+1}-\Phi^{n}}/dt = ...
!>                            + \Gamma _{cond}*(\Phi _i - \Phi^{n+1})
!> \f]
!>
!> \remarks
!>  - \f$ \Phi _i \f$ is the value of \f$ \Phi \f$ associated to the
!>    injected condensation rate.
!>
!>    With 2 options are available:
!>       - the condensation rate is injected with the local value
!>         of variable \f$ \Phi = \Phi ^{n+1}\f$
!>         in this case the \f$ \Phi \f$ variable is not modified.
!>
!>       - the condensation rate is injected with a specific value
!>         for \f$ \Phi = \Phi _i \f$ the specified value given by the
!>         user.
!>
!> \section use Usage
!>
!> The three stages in the code where this User subroutine
!> is called (with \code iappel = 1, 2 and 3\endcode)
!>
!> \code iappel = 1 \endcode
!>  - Calculation of the number of cells where a mass source term is
!>    imposed: ncesmp
!>    Called once at the beginning of the calculation
!>
!> \code iappel = 2 \endcode
!>   - Identification of the cells where a mass source term is imposed:
!>     array icesmp(ncesmp)
!>     Called once at the beginning of the calculation
!>
!> \code iappel = 3 \endcode
!>   - Calculation of the values of the mass source term
!>     Called at each time step
!>
!> \section the specific variables to define with is user subroutine
!>
!>  - nfbpcd: number of faces where a condensation source term is imposed
!>
!>  - ifbpcd(ieltcd): identification of the faces where a condensation
!>                    source term is imposed.
!>
!>  - itypcd(ieltcd,ivar): type of treatment for variable ivar in the
!>                       ieltcd cell with condensation source term.
!>                     - itypcd = 0 --> injection of ivar at local value
!>                     - itypcd = 1 --> injection of ivar at user
!>                                      specified value.
!>
!>  - spcond(ielscd,ipr): value of the injection condensation rate
!>                       gamma_cond (kg/m3/s) in the ieltcd cell
!>                       with condensation source term.
!>
!>  - spcond(ieltcd,ivar): specified value for variable ivar associated
!>                        to the injected condensation in the ieltcd
!>                        cell with a condensation source term except
!>                        for ivar=ipr.
!>
!> \remarks
!>  - For each face where a condensation source terms is imposed ielscd
!>    in [1;nfbpcd]), ifbpcd(ielscd) is the global index number of the
!>    corresponding face (ifbpcd(ieltcd) in [1;ncel]).
!>  - if itypcd(ieltcd,ivar)=0, spcond(ielpcd,ivar) is not used.
!>  - if spcond(ieltcd,ipr)<0, mass is removed from the system,
!>     therefore Code_Saturna automatically considers f_i=f^(n+1),
!>     whatever the values of itypcd or smacel specified by the user
!>
!>   \par Examples of settings for boundary condensation mass source terms
!>        Examples are available
!>        \ref condens_h_boundary "here".
!>
!-------------------------------------------------------------------------------

!-------------------------------------------------------------------------------
! Arguments
!______________________________________________________________________________.
!  mode           name          role                                           !
!______________________________________________________________________________!
!> \param[in]     nvar          total number of variables
!> \param[in]     nscal         total number of scalars
!> \param[in]     iappel        indicates which at which stage the routine is
!> \param[in]     nfbpcd        number of faces with condensation source terms
!> \param[in]     ifbpcd        index of faces with condensation source terms
!> \param[in]     itypcd        type of condensation source term for each ivar
!> \param[in]     izftcd        faces zone with condensation source terms imposed
!>                              (at previous and current time steps)
!> \param[out]    spcond        variable value associated to the condensation
!>                              source term (for ivar=ipr, spcond is the flow rate
!>                              \f$ \Gamma_{cond}^n \f$)
!> \param[out]    tpar          temperature imposed at the cold wall
!>                              as constant or variable in time
!>                              with a 1D thermal model
!_______________________________________________________________________________

subroutine cs_user_boundary_mass_source_terms &
 ( nvar   , nscal  ,                                              &
   nfbpcd , iappel ,                                              &
   ifbpcd , itypcd , izftcd ,                                     &
   spcond , tpar)

!===============================================================================

!===============================================================================
! Module files
!===============================================================================

use paramx
use numvar
use entsor
use optcal
use cstphy
use cstnum
use parall
use period
use ppincl
use mesh
use field
use cs_tagmr
use cs_nz_condensation
use cs_nz_tagmr
use cs_c_bindings
use cs_f_interfaces

!===============================================================================

implicit none

! Arguments

integer          nvar   , nscal
integer          iappel
integer          nfbpcd

integer          ifbpcd(nfbpcd), itypcd(nfbpcd,nvar)
integer          izftcd(ncel)

double precision spcond(nfbpcd,nvar)
double precision tpar

! Local variables

integer, allocatable, dimension(:) :: lstelt

!===============================================================================

! Allocate a temporary array for cells selection
allocate(lstelt(nfabor))

! INSERT_ADDITIONAL_INITIALIZATION_CODE_HERE

if (iappel.eq.1.or.iappel.eq.2) then

!===============================================================================
! 1. One or two calls
! -------------------
!  - iappel = 1: nfbpcd: calculation of the number of faces with
!                             condensation source term
!  - iappel = 2: ifbpcd: index number of faces with condensation source terms
!
! Remarks
! =======
!  - Do not use spcond in this section (it is set on the third call, iappel=3)
!  - Do not use ifbpcd in this section on the first call (iappel=1)
!  - This section (iappel=1 or 2) is only accessed at the beginning of a
!     calculation. Should the localization of the condensation source terms evolve
!     in time, the user must identify at the beginning all cells that can
!     potentially becomea condensation  source term.
!===============================================================================

! INSERT_MAIN_CODE_HERE

elseif (iappel.eq.3) then

!===============================================================================
! 2. For nfbpcd > 0 , third call
!    iappel = 3 : itypcd: type of condensation source term
!                  spcond: condensation source term
! Remark
! ======
! If itypcd(ieltcd,ivar) is set to 1, spcond(ieltcd,ivar) must be set.
!===============================================================================

! INSERT_MAIN_CODE_HERE

endif

!--------
! Formats
!--------

!----
! End
!----

! Deallocate the temporary array
deallocate(lstelt)

return
end subroutine cs_user_boundary_mass_source_terms