Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
PERI_coPgradUpdateFlu.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: update pressure gradient based on mass flux balance
26 !
27 ! Description: when computed mass flux is lower than reference mass flux
28 ! pressure gradient is adjusted in such away that the bulk flow
29 ! accelerate, in other words mass flux is conserved
30 !
31 ! Input: region = data of current region.
32 !
33 ! Output: region%levels%mixt%rhs = updated pressure gradient added to residual.
34 !
35 ! Notes: If MPI, nProcAlloc should be equal to nRegions, otherwise the wall
36 ! normal extent should be covered in one region.
37 !
38 !******************************************************************************
39 !
40 ! $Id: PERI_coPgradUpdateFlu.F90,v 1.9 2008/12/06 08:44:37 mtcampbe Exp $
41 !
42 ! Copyright: (c) 2001 by the University of Illinois
43 !
44 !******************************************************************************
45 
46 SUBROUTINE peri_copgradupdate( region )
47 
48  USE moddatatypes
49  USE modglobal, ONLY : t_global
50  USE moddatastruct, ONLY : t_region
51  USE modbndpatch, ONLY : t_patch
52  USE moderror
53  USE modmpi
54  USE modparameters
56  IMPLICIT NONE
57 
58 ! ... parameters
59  TYPE(t_region) :: region
60 
61 ! ... loop variables
62  INTEGER :: ijkc, ifc, ipatch
63 
64 ! ... local variables
65  CHARACTER(CHRLEN) :: rcsidentstring
66  TYPE(t_global), POINTER :: global
67  TYPE(t_patch), POINTER :: patch
68 
69  INTEGER :: n, ijkc0, ijkcb, istage
70 
71  REAL(RFREAL) :: rhoc, rhouc, rhovc, rhowc, rhoec, pc
72  REAL(RFREAL) :: refmassflux, rescaler, alpha, massflux
73  REAL(RFREAL) :: cfl, dt, rucm, delta, deltamassflux, aversurf
74  REAL(RFREAL) :: sndmassflux, rcvmassflux, sndaversurf, rcvaversurf
75  REAL(RFREAL) :: snddt, rcvdt, avgdt, dtfactor, refmeanpgrad, reftauwall
76  REAL(RFREAL) :: tauwall, avgtauwall, sndtauwall, rcvtauwall
77  REAL(RFREAL) :: rn, sndrn, rcvrn, dy, fnmag, voltot
78  REAL(RFREAL), POINTER :: xyz(:,:), vol(:), cofg(:,:)
79  REAL(RFREAL), POINTER :: cv(:,:), tv(:,:), rdt(:)
80 
81 !******************************************************************************
82 
83  rcsidentstring = '$RCSfile: PERI_coPgradUpdateFlu.F90,v $ $Revision: 1.9 $'
84 
85  global => region%global
86  CALL registerfunction( global,'PERI_CoPgradUpdate',&
87  'PERI_coPgradUpdateFlu.F90' )
88 
89 ! get dimensions, parameters and pointers -------------------------------------
90 
91  xyz => region%grid%xyz
92  vol => region%grid%vol
93  cofg => region%grid%cofg
94  cv => region%mixt%cv
95  tv => region%mixt%tv
96  rdt => region%dt
97 
98  istage = mod(region%irkStep,global%nrkSteps) + 1
99  alpha = region%mixtInput%ark(istage)
100  refmassflux = region%periInput%bulkmFlux
101  delta = global%refLength
102 
103  IF (region%periInput%flowKind == peri_flow_cpr) THEN
104  rescaler = region%periInput%cprEpsilon
105  IF (global%flowType == flow_unsteady .AND. &
106  global%solverType == solv_explicit ) alpha = 1._rfreal
107  ELSEIF (region%periInput%flowKind == peri_flow_channel) THEN
108  rescaler = 1._rfreal
109  ENDIF
110 
111  IF (global%flowType==flow_steady) THEN
112  cfl = region%mixtInput%cfl
113  avgdt = 0._rfreal
114  IF (global%solverType == solv_implicit ) THEN ! Dual Tst
115  dtfactor = 10._rfreal
116  ELSE
117  dtfactor = 0.9_rfreal
118  ENDIF
119  n = 0
120  DO ijkc0=1,region%grid%nCellsTot
121  n = n+1
122  avgdt = avgdt + rdt(ijkc0)
123  ENDDO
124  rn = REAL(n)
125 #ifdef MPI
126  snddt = avgdt
127  CALL mpi_allreduce( snddt,rcvdt,1,mpi_double_precision, mpi_sum, &
128  global%mpiComm, global%mpierr )
129  avgdt = rcvdt
130  sndrn = rn
131  CALL mpi_allreduce( sndrn,rcvrn,1,mpi_double_precision, mpi_sum, &
132  global%mpiComm, global%mpierr )
133  rn = rcvrn
134 #endif
135  avgdt = dtfactor*avgdt/rn
136  dt = cfl*avgdt
137 ! IF (global%solverType == SOLV_IMPLICIT ) dt = global%dtMin ! Dual Tst
138  ELSE
139  dt = global%dtMin
140  ENDIF
141 
142 ! check if pressure gradient constant in all regions
143 
144  refmeanpgrad = region%periInput%meanPgrad
145 
146 #ifdef MPI
147  IF (refmeanpgrad /= global%moduleVar(1) ) THEN
148  CALL errorstop( global,err_peri_physparam,__line__, &
149  'mean pressure gradient vary between regions' )
150  ENDIF
151 #endif
152 
153 ! compute mass flux prior rho.u update -------------------------------------
154 
155  rucm = 0._rfreal
156  voltot = 0._rfreal
157  DO ijkc = 1, region%grid%nCellsTot
158  rucm = rucm + cv(cv_mixt_xmom,ijkc0)*vol(ijkc)
159  voltot = voltot + vol(ijkc)
160  END DO
161  massflux = rucm
162  aversurf = 0.5_rfreal*voltot/delta
163 
164 ! this part only for channel flow
165 
166  avgtauwall = 0._rfreal
167 
168  IF (region%periInput%flowKind == peri_flow_channel .AND. &
169  region%periInput%split(jcoord) /= off ) THEN
170 
171  DO ipatch=1,region%grid%nPatches
172  patch => region%patches(ipatch)
173  IF (patch%bcType>=bc_noslipwall .AND. &
174  patch%bcType<=bc_noslipwall+bc_range) THEN ! my boundary type
175 
176  DO ifc=1,patch%nBFaces
177  ijkcb = patch%bf2c(ifc)
178 
179  dy = abs( cofg(ycoord,ijkcb)-patch%fc(ycoord,ifc) )
180  fnmag = patch%fn(xyzmag,ifc)
181 
182  tauwall = 0.5_rfreal*tv(tv_mixt_muel,ijkcb)* &
183  cv(cv_mixt_xmom,ijkcb)/cv(cv_mixt_dens,ijkcb)/dy
184  avgtauwall = avgtauwall + tauwall*fnmag
185  ENDDO ! ifc
186  ENDIF ! NOSLIPWALL
187  ENDDO ! iPatch
188  ENDIF ! flowKind=channel
189 
190 ! get average mass flux over all processors
191 
192 #ifdef MPI
193  sndmassflux = massflux
194  CALL mpi_allreduce( sndmassflux,rcvmassflux,1,mpi_double_precision,mpi_sum, &
195  global%mpiComm, global%mpierr )
196  massflux = rcvmassflux
197 
198  IF (region%periInput%flowKind == peri_flow_channel) THEN
199  sndtauwall = avgtauwall
200  CALL mpi_allreduce( sndtauwall,rcvtauwall,1,mpi_double_precision,mpi_sum, &
201  global%mpiComm, global%mpierr )
202  avgtauwall = rcvtauwall
203  ENDIF
204 
205  IF (region%periInput%split(jcoord) == off) THEN
206  sndaversurf = aversurf
207  CALL mpi_allreduce( sndaversurf,rcvaversurf,1,mpi_double_precision,mpi_sum, &
208  global%mpiComm, global%mpierr )
209  aversurf = rcvaversurf
210  ENDIF
211 #endif
212  IF (global%myProcId==masterproc) write(*,*)massflux,aversurf
213 
214 ! channel half width needed to update pressure gradient
215 
216  massflux = massflux/aversurf
217  avgtauwall = 0.5_rfreal*avgtauwall/aversurf
218 
219 ! update pressure gradient
220 
221  deltamassflux = refmassflux - massflux
222  IF (global%myProcId==masterproc) WRITE(*,*) region%iRegionGlobal, &
223  'refMassFlux-massFlux prior updating u',refmassflux,massflux,deltamassflux, &
224  avgtauwall/delta
225 
226  refmeanpgrad = refmeanpgrad - 0.5_rfreal*deltamassflux/ &
227  (delta*rescaler*alpha*dt)
228 
229  IF ((region%periInput%flowKind == peri_flow_channel) .AND. &
230  (region%periInput%pgradType == cnl_pgrad_tauwall)) THEN
231 ! refTauWall = global%refDensity*region%periInput%cnlUtau**2
232 ! refMeanPgrad = -refTauWall/global%refLength
233  refmeanpgrad = min( refmeanpgrad, -avgtauwall/global%refLength )
234  ENDIF
235 
236  IF (global%myProcId==masterproc) WRITE(*,*) region%iRegionGlobal, &
237  ' meanPgrad ',refmeanpgrad,dt,alpha
238 
239 ! store pressure gradient in data structure
240  region%periInput%meanPgrad = refmeanpgrad
241 
242 ! update x-momentum due to updated pressure gradient/ mass flux ---------------
243 
244  IF (region%periInput%flowKind == peri_flow_cpr) THEN
245 
246  rucm = 0._rfreal
247  DO ijkc = 1,region%grid%nCellsTot
248  rucm = rucm + cv(cv_mixt_xmom,ijkc0)*vol(ijkc)
249  END DO
250  massflux = rucm
251 
252 #ifdef MPI
253  CALL mpi_barrier( global%mpiComm, global%mpierr )
254  sndmassflux = massflux
255  CALL mpi_allreduce( sndmassflux,rcvmassflux,1,mpi_double_precision,mpi_sum, &
256  global%mpiComm, global%mpierr )
257  massflux = rcvmassflux
258 #endif
259 
260  massflux = massflux/aversurf
261 
262  deltamassflux = refmassflux - massflux
263  IF (global%myProcId==masterproc) WRITE(*,*) region%iRegionGlobal, &
264  'refMassFlux-massFlux AFTER updating u',refmassflux,massflux,deltamassflux
265 
266  ENDIF ! flowKind=CPR
267 
268 ! save pressure gradient in a global variable for restart purpose
269 
270  global%moduleVar(1) = refmeanpgrad
271 
272 ! finalize --------------------------------------------------------------------
273 
274  CALL deregisterfunction( global )
275 
276 END SUBROUTINE peri_copgradupdate
277 
278 !******************************************************************************
279 !
280 ! RCS Revision history:
281 !
282 ! $Log: PERI_coPgradUpdateFlu.F90,v $
283 ! Revision 1.9 2008/12/06 08:44:37 mtcampbe
284 ! Updated license.
285 !
286 ! Revision 1.8 2008/11/19 22:17:49 mtcampbe
287 ! Added Illinois Open Source License/Copyright
288 !
289 ! Revision 1.7 2004/12/11 03:49:52 wasistho
290 ! resereve dt=global%dtMin for dual tst
291 !
292 ! Revision 1.6 2004/12/08 19:42:03 wasistho
293 ! used dtFactor
294 !
295 ! Revision 1.5 2004/12/08 01:47:50 wasistho
296 ! bug fix, MPI_MAX to MPI_SUM
297 !
298 ! Revision 1.4 2004/12/04 06:51:32 wasistho
299 ! take global%dtMin for dt regardless steady or unsteady
300 !
301 ! Revision 1.3 2004/06/17 20:04:02 wasistho
302 ! compiled with RFLU
303 !
304 ! Revision 1.2 2004/06/17 00:50:53 wasistho
305 ! prepared for RFLU
306 !
307 ! Revision 1.1 2004/06/09 01:10:26 wasistho
308 ! changed nomenclature
309 !
310 ! Revision 1.15 2004/01/23 22:42:49 wasistho
311 ! set avgDt to 0.9 of the true value for stability of steady state computations
312 !
313 ! Revision 1.14 2004/01/23 03:11:22 wasistho
314 ! modified dt, added computed tauwall, unst.impl.condition, no cnl massflx correction
315 !
316 ! Revision 1.13 2003/10/21 20:26:37 wasistho
317 ! global max for dt of unsteady flow
318 !
319 ! Revision 1.12 2003/10/20 00:32:07 wasistho
320 ! modified istage definition
321 !
322 ! Revision 1.11 2003/10/18 00:47:50 wasistho
323 ! modified dt for unsteady flow
324 !
325 ! Revision 1.10 2003/09/18 01:56:26 wasistho
326 ! added ijksplit and pgradType in PERI_PgradUpdate
327 !
328 ! Revision 1.9 2003/09/12 20:57:45 wasistho
329 ! update pressure gradient only for CPR, fixed for channel
330 !
331 ! Revision 1.8 2003/09/07 23:32:02 wasistho
332 ! shift ISTAGE 1 stage forward to be consistent
333 !
334 ! Revision 1.7 2003/05/15 02:57:05 jblazek
335 ! Inlined index function.
336 !
337 ! Revision 1.6 2003/04/25 23:17:49 wasistho
338 ! update cpr pgrad per time-step for unsteady
339 !
340 ! Revision 1.5 2003/04/05 04:06:39 wasistho
341 ! shift forward time stage
342 !
343 ! Revision 1.4 2003/04/04 22:27:19 wasistho
344 ! correct averSize for multi processors
345 !
346 ! Revision 1.3 2003/04/03 20:57:02 wasistho
347 ! replace regions to region in pgradUpdate
348 !
349 ! Revision 1.2 2003/04/03 00:30:07 wasistho
350 ! uniform pgrad multiblock/proc
351 !
352 ! Revision 1.1.1.1 2003/03/29 03:36:30 wasistho
353 ! install ROCPERI
354 !
355 !
356 !******************************************************************************
357 
358 
359 
360 
361 
362 
363 
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
subroutine peri_copgradupdate(region)
Definition: patch.h:74
const NT & n
RT delta(int i) const
Definition: Direction_2.h:159
Vector_n min(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:346
NT dy
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
unsigned char alpha() const
Definition: Color.h:75
subroutine deregisterfunction(global)
Definition: ModError.F90:469