Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
PERI_coPgradUpdateFlo.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_coPgradUpdateFlo.F90,v 1.8 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
53  USE moderror
54  USE modmpi
55  USE modparameters
57  IMPLICIT NONE
58 
59 #include "Indexing.h"
60 
61 ! ... parameters
62  TYPE(t_region) :: region
63 
64 ! ... loop variables
65  INTEGER :: i, j, k, n, ir
66 
67 ! ... local variables
68  CHARACTER(CHRLEN) :: rcsidentstring
69  TYPE(t_global), POINTER :: global
70 
71  INTEGER :: ipcbeg, ipcend, jpcbeg, jpcend, kpcbeg, kpcend
72  INTEGER :: ilev, icoff, ijcoff, inoff, ijnoff, ijkc0, ijkc1
73  INTEGER :: ijkn, ijknp1, ipc, kpc, istage
74 
75  REAL(RFREAL) :: rhoc, rhouc, rhovc, rhowc, rhoec, pc
76  REAL(RFREAL) :: refmassflux, rescaler, alpha, massflux
77  REAL(RFREAL) :: cfl, dt, rucm, delta, deltamassflux, aversize
78  REAL(RFREAL) :: sndmassflux, rcvmassflux, sndaversize, rcvaversize
79  REAL(RFREAL) :: snddt, rcvdt, avgdt, dtfactor, refmeanpgrad, reftauwall
80  REAL(RFREAL) :: tauwall, avgtauwall, sndtauwall, rcvtauwall
81  REAL(RFREAL) :: rn, sndrn, rcvrn
82  REAL(RFREAL), POINTER :: xyz(:,:), cv(:,:), dv(:,:), tv(:,:), rdt(:)
83 
84 !******************************************************************************
85 
86  rcsidentstring = '$RCSfile: PERI_coPgradUpdateFlo.F90,v $ $Revision: 1.8 $'
87 
88  global => region%global
89  CALL registerfunction( global,'PERI_CoPgradUpdate',&
90  'PERI_coPgradUpdateFlo.F90' )
91 
92 ! get dimensions, parameters and pointers -------------------------------------
93 
94  ilev = region%currLevel
95  CALL rflo_getdimensphys( region,ilev,ipcbeg,ipcend, &
96  jpcbeg,jpcend,kpcbeg,kpcend )
97  CALL rflo_getcelloffset( region,ilev,icoff,ijcoff )
98  CALL rflo_getnodeoffset( region,ilev,inoff,ijnoff )
99 
100  xyz => region%levels(ilev)%grid%xyz
101  cv => region%levels(ilev)%mixt%cv
102  dv => region%levels(ilev)%mixt%dv
103  tv => region%levels(ilev)%mixt%tv
104  rdt => region%levels(ilev)%dt
105 
106  istage = mod(region%irkStep,global%nrkSteps) + 1
107  alpha = region%mixtInput%ark(istage)
108  refmassflux = region%periInput%bulkmFlux
109 
110  IF (region%periInput%flowKind == peri_flow_cpr) THEN
111  rescaler = region%periInput%cprEpsilon
112  IF (global%flowType == flow_unsteady .AND. &
113  global%solverType == solv_explicit ) alpha = 1._rfreal
114  ELSEIF (region%periInput%flowKind == peri_flow_channel) THEN
115  rescaler = 1._rfreal
116  ENDIF
117 
118  IF (global%flowType==flow_steady) THEN
119  cfl = region%mixtInput%cfl
120  avgdt = 0._rfreal
121  IF (global%solverType == solv_implicit ) THEN ! Dual Tst
122  dtfactor = 10._rfreal
123  ELSE
124 ! dtFactor = 0.9_RFREAL
125  dtfactor = 10._rfreal
126  ENDIF
127  n = 0
128  DO k=kpcbeg,kpcend
129  DO j=jpcbeg,jpcend
130  DO i=ipcbeg,ipcend
131  n = n+1
132  ijkc0 = indijk(i ,j ,k ,icoff,ijcoff)
133  avgdt = avgdt + rdt(ijkc0)
134  ENDDO
135  ENDDO
136  ENDDO
137  rn = REAL(n)
138 #ifdef MPI
139  snddt = avgdt
140  CALL mpi_allreduce( snddt,rcvdt,1,mpi_double_precision, mpi_sum, &
141  global%mpiComm, global%mpierr )
142  avgdt = rcvdt
143  sndrn = rn
144  CALL mpi_allreduce( sndrn,rcvrn,1,mpi_double_precision, mpi_sum, &
145  global%mpiComm, global%mpierr )
146  rn = rcvrn
147 #endif
148  avgdt = dtfactor*avgdt/rn
149  dt = cfl*avgdt
150 ! IF (global%solverType == SOLV_IMPLICIT ) dt = global%dtMin ! Dual Tst
151  ELSE
152  dt = global%dtMin
153  ENDIF
154 
155 ! check if pressure gradient constant in all regions
156 
157  refmeanpgrad = region%periInput%meanPgrad
158 
159 #ifdef MPI
160  IF (refmeanpgrad /= global%moduleVar(1) ) THEN
161  CALL errorstop( global,err_peri_physparam,__line__, &
162  'mean pressure gradient vary between regions' )
163  ENDIF
164 #endif
165 
166 ! compute mass flux prior rho.u update -------------------------------------
167 
168  ipc = ipcend-ipcbeg+1
169  kpc = kpcend-kpcbeg+1
170  aversize = dble(ipc*kpc)
171 
172  massflux = 0._rfreal
173 
174  DO j = jpcbeg,jpcend
175  rucm = 0._rfreal
176  DO k=kpcbeg,kpcend
177  DO i=ipcbeg,ipcend
178  ijkc0 = indijk(i ,j ,k ,icoff,ijcoff)
179  ijkn = indijk(i ,j ,k ,inoff,ijnoff)
180  ijknp1= indijk(i ,j+1,k ,inoff,ijnoff)
181  rucm = rucm + cv(cv_mixt_xmom,ijkc0)
182  END DO
183  END DO
184  massflux = massflux + rucm*(xyz(ycoord,ijknp1)-xyz(ycoord,ijkn))
185  END DO ! j
186 
187 ! this part only for channel flow
188 
189  avgtauwall = 0._rfreal
190 
191  IF (region%periInput%flowKind == peri_flow_channel .AND. &
192  region%periInput%split(jcoord) /= off ) THEN
193 
194  IF (region%procId == masterproc) THEN
195  DO k=kpcbeg,kpcend
196  DO i=ipcbeg,ipcend
197  ijkc0 = indijk(i ,1 ,k ,icoff,ijcoff)
198  ijkc1 = indijk(i ,2 ,k ,icoff,ijcoff)
199  ijkn = indijk(i ,1 ,k ,inoff,ijnoff)
200  ijknp1= indijk(i ,2 ,k ,inoff,ijnoff)
201  tauwall = 0.5_rfreal*tv(tv_mixt_muel,ijkc0)* &
202  (dv(dv_mixt_uvel,ijkc1)+dv(dv_mixt_uvel,ijkc0))/ &
203  (xyz(ycoord,ijknp1)-xyz(ycoord,ijkn))
204  avgtauwall = avgtauwall + tauwall
205  ENDDO
206  ENDDO
207  ENDIF
208 
209  IF (region%procId == global%nProcAlloc-1) THEN
210  DO k=kpcbeg,kpcend
211  DO i=ipcbeg,ipcend
212  ijkc0 = indijk(i ,jpcend ,k ,icoff,ijcoff)
213  ijkc1 = indijk(i ,jpcend-1 ,k ,icoff,ijcoff)
214  ijkn = indijk(i ,jpcend ,k ,inoff,ijnoff)
215  ijknp1= indijk(i ,jpcend+1 ,k ,inoff,ijnoff)
216  tauwall = 0.5_rfreal*tv(tv_mixt_muel,ijkc0)* &
217  (dv(dv_mixt_uvel,ijkc1)+dv(dv_mixt_uvel,ijkc0))/ &
218  abs( xyz(ycoord,ijknp1)-xyz(ycoord,ijkn) )
219  avgtauwall = avgtauwall + tauwall
220  ENDDO
221  ENDDO
222  ENDIF ! procId
223  ENDIF ! flowKind=channel
224 
225 ! get average mass flux over all processors
226 
227 #ifdef MPI
228  sndmassflux = massflux
229  CALL mpi_allreduce( sndmassflux,rcvmassflux,1,mpi_double_precision,mpi_sum, &
230  global%mpiComm, global%mpierr )
231  massflux = rcvmassflux
232 
233  IF (region%periInput%flowKind == peri_flow_channel) THEN
234  sndtauwall = avgtauwall
235  CALL mpi_allreduce( sndtauwall,rcvtauwall,1,mpi_double_precision,mpi_sum, &
236  global%mpiComm, global%mpierr )
237  avgtauwall = rcvtauwall
238  ENDIF
239 
240  IF (region%periInput%split(jcoord) == off) THEN
241  sndaversize = aversize
242  CALL mpi_allreduce( sndaversize,rcvaversize,1,mpi_double_precision,mpi_sum, &
243  global%mpiComm, global%mpierr )
244  aversize = rcvaversize
245  ENDIF
246 #endif
247  IF (global%myProcId==masterproc) write(*,*)massflux,aversize
248 
249 ! channel half width needed to update pressure gradient
250 
251  delta = global%refLength
252  massflux = massflux/aversize
253  avgtauwall = 0.5_rfreal*avgtauwall/aversize
254 
255 ! update pressure gradient
256 
257  deltamassflux = refmassflux - massflux
258  IF (global%myProcId==masterproc) WRITE(*,*) region%localNumber, &
259  'refMassFlux-massFlux prior updating u',refmassflux,massflux,deltamassflux, &
260  avgtauwall/delta
261 
262  refmeanpgrad = refmeanpgrad - 0.5_rfreal*deltamassflux/ &
263  (delta*rescaler*alpha*dt)
264 
265  IF ((region%periInput%flowKind == peri_flow_channel) .AND. &
266  (region%periInput%pgradType == cnl_pgrad_tauwall)) THEN
267 ! refTauWall = global%refDensity*region%periInput%cnlUtau**2
268 ! refMeanPgrad = -refTauWall/global%refLength
269  refmeanpgrad = min( refmeanpgrad, -avgtauwall/global%refLength )
270  ENDIF
271 
272  IF (global%myProcId==masterproc) WRITE(*,*) region%localNumber, &
273  ' meanPgrad ',refmeanpgrad,dt,alpha
274 
275 ! store pressure gradient in data structure
276  region%periInput%meanPgrad = refmeanpgrad
277 
278 ! update x-momentum due to updated pressure gradient/ mass flux ---------------
279 
280  IF (region%periInput%flowKind == peri_flow_cpr) THEN
281 
282  massflux = 0._rfreal
283 
284  DO j = jpcbeg,jpcend
285  rucm = 0._rfreal
286  DO k=kpcbeg,kpcend
287  DO i=ipcbeg,ipcend
288  ijkc0 = indijk(i ,j ,k ,icoff,ijcoff)
289  ijkn = indijk(i ,j ,k ,inoff,ijnoff)
290  ijknp1= indijk(i ,j+1,k ,inoff,ijnoff)
291  cv(cv_mixt_xmom,ijkc0) = cv(cv_mixt_xmom,ijkc0) + 0.5_rfreal* &
292  deltamassflux/delta
293  dv(dv_mixt_uvel,ijkc0) = cv(cv_mixt_xmom,ijkc0)/cv(cv_mixt_dens,ijkc0)
294  rucm = rucm + cv(cv_mixt_xmom,ijkc0)
295  ENDDO
296  ENDDO
297  massflux = massflux + rucm*(xyz(ycoord,ijknp1)-xyz(ycoord,ijkn))
298  ENDDO ! j
299 
300 #ifdef MPI
301  CALL mpi_barrier( global%mpiComm, global%mpierr )
302  sndmassflux = massflux
303  CALL mpi_allreduce( sndmassflux,rcvmassflux,1,mpi_double_precision,mpi_sum, &
304  global%mpiComm, global%mpierr )
305  massflux = rcvmassflux
306 #endif
307 
308  massflux = massflux/aversize
309 
310  deltamassflux = refmassflux - massflux
311  IF (global%myProcId==masterproc) WRITE(*,*) region%localNumber, &
312  'refMassFlux-massFlux AFTER updating u',refmassflux,massflux,deltamassflux
313 
314  ENDIF ! flowKind=CPR
315 
316 ! save pressure gradient in a global variable for restart purpose
317 
318  global%moduleVar(1) = refmeanpgrad
319 
320 ! finalize --------------------------------------------------------------------
321 
322  CALL deregisterfunction( global )
323 
324 END SUBROUTINE peri_copgradupdate
325 
326 !******************************************************************************
327 !
328 ! RCS Revision history:
329 !
330 ! $Log: PERI_coPgradUpdateFlo.F90,v $
331 ! Revision 1.8 2008/12/06 08:44:37 mtcampbe
332 ! Updated license.
333 !
334 ! Revision 1.7 2008/11/19 22:17:49 mtcampbe
335 ! Added Illinois Open Source License/Copyright
336 !
337 ! Revision 1.6 2005/03/08 06:00:33 wasistho
338 ! set dtFactor to 10 for steady computation
339 !
340 ! Revision 1.5 2004/12/11 03:48:18 wasistho
341 ! resereve dt=global%dtMin for dual tst
342 !
343 ! Revision 1.4 2004/12/08 19:42:07 wasistho
344 ! used dtFactor
345 !
346 ! Revision 1.3 2004/12/08 01:47:46 wasistho
347 ! bug fix, MPI_MAX to MPI_SUM
348 !
349 ! Revision 1.2 2004/12/04 06:49:14 wasistho
350 ! take global%dtMin for dt regardless steady or unsteady
351 !
352 ! Revision 1.1 2004/06/08 23:56:56 wasistho
353 ! changed nomenclature
354 !
355 ! Revision 1.15 2004/01/23 22:42:49 wasistho
356 ! set avgDt to 0.9 of the true value for stability of steady state computations
357 !
358 ! Revision 1.14 2004/01/23 03:11:22 wasistho
359 ! modified dt, added computed tauwall, unst.impl.condition, no cnl massflx correction
360 !
361 ! Revision 1.13 2003/10/21 20:26:37 wasistho
362 ! global max for dt of unsteady flow
363 !
364 ! Revision 1.12 2003/10/20 00:32:07 wasistho
365 ! modified istage definition
366 !
367 ! Revision 1.11 2003/10/18 00:47:50 wasistho
368 ! modified dt for unsteady flow
369 !
370 ! Revision 1.10 2003/09/18 01:56:26 wasistho
371 ! added ijksplit and pgradType in PERI_PgradUpdate
372 !
373 ! Revision 1.9 2003/09/12 20:57:45 wasistho
374 ! update pressure gradient only for CPR, fixed for channel
375 !
376 ! Revision 1.8 2003/09/07 23:32:02 wasistho
377 ! shift ISTAGE 1 stage forward to be consistent
378 !
379 ! Revision 1.7 2003/05/15 02:57:05 jblazek
380 ! Inlined index function.
381 !
382 ! Revision 1.6 2003/04/25 23:17:49 wasistho
383 ! update cpr pgrad per time-step for unsteady
384 !
385 ! Revision 1.5 2003/04/05 04:06:39 wasistho
386 ! shift forward time stage
387 !
388 ! Revision 1.4 2003/04/04 22:27:19 wasistho
389 ! correct averSize for multi processors
390 !
391 ! Revision 1.3 2003/04/03 20:57:02 wasistho
392 ! replace regions to region in pgradUpdate
393 !
394 ! Revision 1.2 2003/04/03 00:30:07 wasistho
395 ! uniform pgrad multiblock/proc
396 !
397 ! Revision 1.1.1.1 2003/03/29 03:36:30 wasistho
398 ! install ROCPERI
399 !
400 !
401 !******************************************************************************
402 
403 
404 
405 
406 
407 
408 
j indices k indices k
Definition: Indexing.h:6
**********************************************************************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 kpcbeg
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
subroutine peri_copgradupdate(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 jpcbeg
**********************************************************************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 ipcend
subroutine rflo_getnodeoffset(region, iLev, iNodeOffset, ijNodeOffset)
**********************************************************************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 ipcbeg
blockLoc i
Definition: read.cpp:79
subroutine rflo_getcelloffset(region, iLev, iCellOffset, ijCellOffset)
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
j indices j
Definition: Indexing.h:6
**********************************************************************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 jpcend
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
subroutine rflo_getdimensphys(region, iLev, ipcbeg, ipcend, jpcbeg, jpcend, kpcbeg, kpcend)