Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
TURB_coViscousFluxesFlu.F90
Go to the documentation of this file.
1 ! *********************************************************************
2 ! * Rocstar Simulation Suite *
3 ! * Copyright@2015, Illinois Rocstar LLC. All rights reserved. *
4 ! * *
5 ! * Illinois Rocstar LLC *
6 ! * Champaign, IL *
7 ! * www.illinoisrocstar.com *
8 ! * sales@illinoisrocstar.com *
9 ! * *
10 ! * License: See LICENSE file in top level of distribution package or *
11 ! * http://opensource.org/licenses/NCSA *
12 ! *********************************************************************
13 ! *********************************************************************
14 ! * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, *
15 ! * EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES *
16 ! * OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND *
17 ! * NONINFRINGEMENT. IN NO EVENT SHALL THE CONTRIBUTORS OR *
18 ! * COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER *
19 ! * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, *
20 ! * Arising FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE *
21 ! * USE OR OTHER DEALINGS WITH THE SOFTWARE. *
22 ! *********************************************************************
23 !******************************************************************************
24 !
25 ! Purpose: Compute total viscous fluxes and add them to dissipation.
26 !
27 ! Description: total viscous flux is superposition of laminar and turbulent:
28 ! fv_total = sigma_ij + tau_ij
29 ! = mu_l.S_ij + tau_ij
30 ! for eddy viscosity type turbulence model:
31 ! fv_total = (mu_l+mu_t).S_ij, otherwise
32 ! fv_total = mu_l.S_ij + m_ij, where m_ij is a model for tau_ij
33 !
34 ! Input: region = data of current region.
35 !
36 ! Output: mixt%diss = total viscous fluxes + num. dissipation
37 !
38 ! Notes:
39 ! 1. This routine is similar to routine ViscousFluxes for laminar flow.
40 ! 2. THIS ROUTINE IS BROKEN FOR ROCFLU - CANNOT ADAPT EASILY TO CHANGES
41 ! IN ROCFLU, WILL NOT BE USED IN ROCFLU.
42 !
43 !******************************************************************************
44 !
45 ! $Id: TURB_coViscousFluxesFlu.F90,v 1.9 2008/12/06 08:44:43 mtcampbe Exp $
46 !
47 ! Copyright: (c) 2001 by the University of Illinois
48 !
49 !******************************************************************************
50 
51 SUBROUTINE turb_coviscousfluxes( region ) ! PUBLIC
52 
53  USE moddatatypes
54  USE modbndpatch, ONLY : t_patch
55  USE moddatastruct, ONLY : t_region
56  USE modturbulence, ONLY : t_turb
57  USE modglobal, ONLY : t_global
61  USE turb_modinterfaces, ONLY : turb_calcstrainrate, turb_getmodelstresscell, &
66  USE moderror
67  USE modparameters
69  IMPLICIT NONE
70 
71 ! ... parameters
72  TYPE(t_region), POINTER :: region
73 
74 ! ... loop variables
75  INTEGER :: ipatch
76 
77 ! ... local variables
78  CHARACTER(CHRLEN) :: rcsidentstring
79  TYPE(t_global), POINTER :: global
80  TYPE(t_turb), POINTER :: turb
81  TYPE(t_patch), POINTER :: patch
82 
83  INTEGER :: turbmodel, modelclass, errorflag, prevcvstate
84  INTEGER :: npatches, ncellstot, nfaces, nfacestot, nbfaces, nbfacestot
85  INTEGER :: ibc, iec, ibn, ien, gradindx(3)
86 
87  REAL(RFREAL), POINTER :: gradi(:,:,:), bgradi(:,:,:)
88 
89 !******************************************************************************
90 
91  rcsidentstring = '$RCSfile: TURB_coViscousFluxesFlu.F90,v $ $Revision: 1.9 $'
92 
93  global => region%global
94  CALL registerfunction( global,'TURB_CoViscousFluxes',&
95  'TURB_coViscousFluxesFlu.F90' )
96 
97 ! Specific Rocflu ------------------------------------------------------------
98 ! check the state of cv first and convert to conservative if not yet
99 
100  IF (region%mixt%cvState /= cv_mixt_state_cons) THEN
101  prevcvstate = region%mixt%cvState
102  CALL rflu_convertcvprim2cons(region,cv_mixt_state_cons)
103  ENDIF
104 
105 ! get cell and node dimensions -----------------------------------------------
106  ncellstot = region%grid%nCellsTot
107  nfaces = region%grid%nFaces
108  nfacestot = region%grid%nFacesTot
109  ibc = 1
110  iec = ncellstot
111  ibn = 1
112  ien = nfaces
113  npatches = region%grid%nPatches
114 
115  nbfaces = 0
116  nbfacestot = 0
117 
118  DO ipatch = 1,npatches
119  patch => region%patches(ipatch)
120 
121  nbfaces = nbfaces + patch%nBTris + patch%nBQuads
122  nbfacestot = nbfacestot + patch%nBTrisTot + patch%nBQuadsTot
123  END DO ! iPatch
124 
125 ! get pointers and parameters
126 
127  turbmodel = region%mixtInput%turbModel
128  modelclass= region%turbInput%modelClass
129  turb => region%turb
130 
131 ! get mixture strain rate tensor and store in mISij
132 
133  gradi => region%mixt%gradFace
134 ! TEMPORARY
135 ! bGradi => region%mixt%bGradFace
136 
137  gradindx(1) = grf_mixt_xvel
138  gradindx(2) = grf_mixt_yvel
139  gradindx(3) = grf_mixt_zvel
140 
141  ALLOCATE( turb%mISij(tensor_symm_nelm, nfaces ),stat=errorflag )
142  global%error = errorflag
143  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
144 
145  ALLOCATE( turb%bmISij(tensor_symm_nelm,nbfaces),stat=errorflag )
146  global%error = errorflag
147  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
148 
149  CALL turb_calcstrainrate( region,1, nfaces,gradindx, gradi, turb%mISij )
150  IF (npatches > 0) &
151  CALL turb_calcstrainrate( region,1,nbfaces,gradindx,bgradi,turb%bmISij )
152 
153 ! get new non-uniform filter and averaging coefficients if the grid moves
154 
155 ! IF (region%mixtInput%moveGrid) THEN ! better performed in TURB_CalcMetric
156 ! IF (region%irkStep == 1) THEN
157 ! CALL TURB_FluLesMoveGrid
158 ! ENDIF
159 ! ENDIF
160 
161 ! allocate and initiate LES arrays required within this scope
162 
163  IF (modelclass == model_les) THEN
164  ALLOCATE( turb%mueT( diri, nfaces),stat=errorflag )
165  global%error = errorflag
166  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
167 
168  ALLOCATE( turb%bMueT(diri,nbfaces),stat=errorflag )
169  global%error = errorflag
170  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
171 
172  ALLOCATE( turb%trace(ibc:iec),stat=errorflag )
173  global%error = errorflag
174  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
175 
176  turb%dv = 0._rfreal ! cell dynamic coefficient is stored in dv
177  turb%mueT = 0._rfreal
178  turb%bMueT = 0._rfreal
179  turb%trace = 0._rfreal
180  ENDIF
181 
182 ! get total viscous flux based on selected turbulence model
183 
184  IF (turbmodel==turb_model_fixsmag) THEN
185  CALL turb_lesfluxfixsmag( region,ibn,ien )
186 
187  ELSEIF ((turbmodel==turb_model_dynsmag) .OR. &
188  (turbmodel==turb_model_dynmixd)) THEN
189 
190 ! - allocate arrays for strain rate of filtered velocities in LesGetEddyVis,
191 ! and for space of tauij (in Dynamic Mixed model)
192 
193  ALLOCATE( turb%fISij( tensor_symm_nelm, nfaces),stat=errorflag )
194  global%error = errorflag
195  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
196 
197  ALLOCATE( turb%bfISij(tensor_symm_nelm,nbfaces),stat=errorflag )
198  global%error = errorflag
199  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
200 
201 ! - get eddy viscosity of dynamic Smagorinsky and dynamic Mixed models
202  CALL turb_lesgeteddyvis( region,ibc,iec,ibn,ien )
203 
204 ! - get viscous fluxes
205  IF (turbmodel==turb_model_dynsmag) THEN
206  CALL turb_visfluxeddy( region )
207  ELSEIF (turbmodel==turb_model_dynmixd) THEN
208  CALL turb_vfluxhybrid( region )
209  ENDIF
210 
211 ! - deallocate retired arrays
212  DEALLOCATE( turb%fISij, turb%bfISij )
213 
214  ELSEIF (turbmodel==turb_model_scalsim) THEN
215  CALL turb_lesfluxscalsim( region,ibn,ien )
216 
217 
218  ELSEIF ((turbmodel==turb_model_sa).OR. &
219  (turbmodel==turb_model_dessa).OR. &
220  (turbmodel==turb_model_hdessa)) THEN
221 
222 ! - viscous fluxes of SA equation
223  CALL turb_ranssavisflux( region )
224 
225 ! - allocate total tv for NS viscous fluxes
226  ALLOCATE( turb%tv(tvt_rans_nelm,ibc:iec),stat=errorflag )
227  global%error = errorflag
228  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
229 
230 ! - compute total RaNS tv and use it to obtain NS viscous fluxes
231  CALL turb_ranstotaltv( region,tvt_rans_mue,tvt_rans_tco,turb%tv )
232  CALL rflu_viscousfluxes( region,turb%tv,tvt_rans_mue,tvt_rans_tco )
233  CALL rflu_viscousfluxespatches( region,turb%tv,tvt_rans_mue,tvt_rans_tco )
234 
235 ! - deallocate retired arrays
236  DEALLOCATE( turb%tv )
237 
238  ENDIF
239 
240 ! finalize viscous flux treatment
241 ! if desired, interpolate model stresses to cell centers for statistics
242 
243  IF (region%turbInput%nSv > 0) CALL turb_getmodelstresscell( region )
244  DEALLOCATE( turb%mISij, turb%bmISij )
245 
246  IF (modelclass == model_les) THEN
247 ! - interpolate transport variables at cell centers
248  CALL turb_gettvcell( region )
249 
250 ! - deallocate LES arrays
251  DEALLOCATE( turb%mueT, turb%bMueT, turb%trace )
252  ENDIF
253 
254 ! convert cv back to the previous state before entering this routine
255 
256  IF (region%mixt%cvState /= prevcvstate) &
257  CALL rflu_convertcvcons2prim( region,prevcvstate )
258 
259 ! finalize --------------------------------------------------------------------
260 
261  CALL deregisterfunction( global )
262 
263 END SUBROUTINE turb_coviscousfluxes
264 
265 !******************************************************************************
266 !
267 ! RCS Revision history:
268 !
269 ! $Log: TURB_coViscousFluxesFlu.F90,v $
270 ! Revision 1.9 2008/12/06 08:44:43 mtcampbe
271 ! Updated license.
272 !
273 ! Revision 1.8 2008/11/19 22:17:55 mtcampbe
274 ! Added Illinois Open Source License/Copyright
275 !
276 ! Revision 1.7 2006/08/19 15:40:43 mparmar
277 ! Commented use of region%mixt%bGradFace
278 !
279 ! Revision 1.6 2005/12/29 19:52:06 wasistho
280 ! modified allocation for bMISij
281 !
282 ! Revision 1.5 2005/12/20 20:44:19 wasistho
283 ! adapted to changing in Rocflu on viscous fluxes routines
284 !
285 ! Revision 1.4 2005/03/07 05:03:58 wasistho
286 ! install hybrid DESSA turbulence model
287 !
288 ! Revision 1.3 2004/05/28 01:58:35 wasistho
289 ! update unstructured grid LES
290 !
291 ! Revision 1.2 2004/03/27 02:16:42 wasistho
292 ! compiled with Rocflu
293 !
294 ! Revision 1.1 2004/03/25 04:42:58 wasistho
295 ! prepared for RFLU
296 !
297 !
298 !
299 !******************************************************************************
300 
301 
302 
303 
304 
305 
306 
subroutine turb_visfluxeddy(region)
subroutine, public rflu_viscousfluxespatches(pRegion, tv, tvIndxVisc, tvIndxCond)
subroutine turb_coviscousfluxes(region)
subroutine turb_vfluxhybrid(region)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
subroutine turb_lesfluxscalsim(region, ibn, ien)
subroutine turb_getmodelstresscell(region)
subroutine, public rflu_convertcvcons2prim(pRegion, cvStateFuture)
Definition: patch.h:74
subroutine turb_ranssageteddyvis(region)
subroutine turb_ranstotaltv(region, indxMu, indxTCo, tvt)
IndexType nfaces() const
Definition: Mesh.H:641
subroutine, public rflu_convertcvprim2cons(pRegion, cvStateFuture)
subroutine turb_lesgeteddyvis(region, ibc, iec, ibn, ien)
subroutine turb_lesfluxfixsmag(region, ibn, ien)
subroutine turb_ranssavisflux(region)
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE iEndG gradi(:,:)
subroutine turb_gettvcell(region)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine, public rflu_viscousfluxes(pRegion, tv, tvIndxVisc, tvIndxCond)