Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLU_ModNewtonKrylov.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: Collection of routines related to Newton-Krylov schemes.
26 !
27 ! Description: None.
28 !
29 ! Notes: None.
30 !
31 ! ******************************************************************************
32 !
33 ! $Id: RFLU_ModNewtonKrylov.F90,v 1.16 2008/12/06 08:44:22 mtcampbe Exp $
34 !
35 ! Copyright: (c) 2005-2006 by the University of Illinois
36 !
37 ! ******************************************************************************
38 
40 
41  USE moddatatypes
42  USE modglobal, ONLY: t_global
43  USE modparameters
44  USE moderror
45  USE moddatastruct, ONLY: t_region
46  USE modgrid, ONLY: t_grid
47  USE modbndpatch, ONLY: t_patch
48  USE modmixture, ONLY: t_mixt,t_mixt_input
49  USE modmpi
50 
54  USE rflu_modmpi
57  USE rflu_modprobes
61  USE rflu_modweights
62 
84  rungekuttamp, &
85  writeprobe, &
90 
91  IMPLICIT NONE
92 
93  include 'mpif.h'
94 
95 ! DEBUG
96 !#ifdef GENX
97 ! INCLUDE 'rocmanf90.h'
98 !#endif
99 ! END DEBUG
100 
101  PRIVATE
102  PUBLIC :: rflu_nk_timestepping
103 
104 ! ******************************************************************************
105 ! Declarations and definitions
106 ! ******************************************************************************
107 
108  CHARACTER(CHRLEN) :: &
109  RCSIdentString = '$RCSfile: RFLU_ModNewtonKrylov.F90,v $ $Revision: 1.16 $'
110 
111 ! ******************************************************************************
112 ! Routines
113 ! ******************************************************************************
114 
115  CONTAINS
116 
117 
118 
119 
120 
121 
122 ! ******************************************************************************
123 !
124 ! Purpose: Integrate the governing equations in time.
125 !
126 ! Description: None.
127 !
128 ! Input:
129 ! dTimeSystem Total solution time (unsteady flow)
130 ! dIterSystem Total number of iterations (steady flow)
131 ! regions Data for all grid regions
132 !
133 ! Output:
134 ! regions Data for all grid regions
135 !
136 ! Notes: None.
137 !
138 ! ******************************************************************************
139 
140 SUBROUTINE rflu_nk_timestepping(dTimeSystem,dIterSystem,regions)
141 
142  USE moddatatypes
143  USE modparameters
144  USE moderror
145  USE modglobal, ONLY: t_global
146  USE modbndpatch, ONLY: t_patch
147  USE moddatastruct, ONLY: t_region
148  USE modgrid, ONLY: t_grid
149  USE modmixture, ONLY: t_mixt_input
150  USE modmpi
151 
153 
154  IMPLICIT NONE
155 
156 ! ******************************************************************************
157 ! Include PETSc headers
158 ! ******************************************************************************
159 
160 #include "finclude/petsc.h"
161 #include "finclude/petscvec.h"
162 #include "finclude/petscmat.h"
163 #include "finclude/petscksp.h"
164 #include "finclude/petscpc.h"
165 #include "finclude/petscsnes.h"
166 
167 ! ******************************************************************************
168 ! INTERFACE blocks for PETSc SNES callback definition functions
169 ! ******************************************************************************
170 
171  INTERFACE
172  SUBROUTINE snessetfunction(snes,r,fun,ctx,ierr)
173  USE moddatastruct, ONLY: t_region
174  snes :: snes
175  vec :: r
176  EXTERNAL :: fun
177  TYPE(t_region),POINTER :: ctx
178  INTEGER :: ierr
179  END SUBROUTINE
180  SUBROUTINE snessetjacobian(snes,A,pA,fun,ctx,ierr)
181  USE moddatastruct, ONLY: t_region
182  snes :: snes
183  mat :: a, pa
184  EXTERNAL :: fun
185  TYPE(t_region),POINTER :: ctx
186  INTEGER :: ierr
187  END SUBROUTINE
188  SUBROUTINE matfdcoloringsetfunctionsnes(matfd,fun,ctx,ierr)
189  USE moddatastruct, ONLY: t_region
190  matfdcoloring :: matfd
191  EXTERNAL :: fun
192  TYPE(t_region),POINTER :: ctx
193  INTEGER :: ierr
194  END SUBROUTINE
195  END INTERFACE
196 
197 ! ******************************************************************************
198 ! Declarations and definitions
199 ! ******************************************************************************
200 
201 ! ==============================================================================
202 ! Arguments
203 ! ==============================================================================
204 
205  LOGICAL :: doprint,doprobe,dowrite
206  LOGICAL :: finished = .false., movegrid
207  INTEGER :: ditersystem
208  REAL(RFREAL) :: dtimesystem
209  TYPE(t_region), POINTER :: pregion,regions(:)
210 
211 ! ==============================================================================
212 ! Locals
213 ! ==============================================================================
214 
215  INTEGER :: gtemp,ic,ierr,ipatch,ireg,iter,iv,ltemp
216  TYPE(t_global), POINTER :: global
217  TYPE(t_mixt_input), POINTER :: pmixtinput
218  TYPE(t_patch), POINTER :: ppatch
219  snesconvergedreason reason
220  petsclogdouble time
221 
222 ! DEBUG
223 !#ifdef GENX
224 ! DOUBLE PRECISION, DIMENSION(MAN_INTEG_SIZE) :: integ
225 !#endif
226 ! END DEBUG
227 
228 ! TEMPORARY
229  INTEGER :: isub,ivl,ipatch,nsub
230  REAL(RFREAL) :: insub, isubterm
231  TYPE(t_patch), POINTER :: ppatch
232  TYPE(t_grid), POINTER :: pgrid, pgridold, pgridold2
233 ! END TEMPORARY
234 
235 ! ******************************************************************************
236 ! Start, set pointers and variables
237 ! ******************************************************************************
238 
239  global => regions(1)%global
240  pregion => regions(1)
241 
242  nsub = 100
243  insub = 1.0_rfreal/nsub
244 
245  CALL registerfunction(global,'RFLU_NK_TimeStepping',&
246  'RFLU_ModNewtonKrylov.F90')
247 
248 ! ==============================================================================
249 ! Determine whether have moving grids
250 ! ==============================================================================
251 
252  movegrid = .false.
253 
254  DO ireg = 1,global%nRegionsLocal
255  IF ( regions(ireg)%mixtInput%moveGrid .EQV. .true. ) THEN
256  movegrid = .true.
257  END IF ! regions
258  END DO ! iReg
259 
260 ! ==============================================================================
261 ! Set SNES callback functions
262 ! ==============================================================================
263 
264  CALL snessetfunction(pregion%snes,pregion%r, &
265  rflu_petsc_formresidual,pregion,ierr)
266  CALL snessetjacobian(pregion%snes,pregion%A,pregion%preA, &
267  rflu_petsc_formjacobian,pregion,ierr)
268  CALL matfdcoloringsetfunctionsnes(pregion%fdcolor, &
269  rflu_petsc_formresidualfirstorder,pregion,ierr)
270 
271 ! ==============================================================================
272 ! Initialize old variables as current variables
273 ! ==============================================================================
274 
275  pregion%mixt%cvOld(:,:) = pregion%mixt%cv(:,:)
276  pregion%mixt%cvOld1(:,:) = pregion%mixt%cv(:,:)
277  pregion%mixt%cvOld2(:,:) = pregion%mixt%cv(:,:)
278  pregion%gridOld%vol(:) = pregion%grid%vol(:)
279  pregion%gridOld2%vol(:) = pregion%grid%vol(:)
280  pregion%gridOld%xyz(:,:) = pregion%grid%xyz(:,:)
281  pregion%gridOld2%xyz(:,:) = pregion%grid%xyz(:,:)
282 
283 ! ******************************************************************************
284 ! Loop over iterations/time steps
285 ! ******************************************************************************
286 
287 ! DEBUG
288  IF ( global%myProcid == 0 ) THEN
289  CALL petscgettime(time,ierr)
290  print*,'PETSC TIME 1 : ',time
291  END IF ! global%myProcid
292 ! END DEBUG
293 
294  finished = .false.
295 
296  DO
297 
298 ! ==============================================================================
299 ! Update iteration counter for steady flow.
300 ! ==============================================================================
301 
302  IF ( global%flowType == flow_steady ) THEN
303  global%currentIter = global%currentIter + 1
304  global%iterSinceRestart = global%iterSinceRestart + 1
305  END IF ! global%flowType
306 
307 ! ==============================================================================
308 ! Compute time step.
309 ! ==============================================================================
310 
311  DO ireg = 1,global%nRegionsLocal
312  pregion => regions(ireg)
313 
314  IF ( pregion%mixtInput%flowModel == flow_euler ) THEN
315  CALL rflu_timestepinviscid(pregion)
316  ELSE
317  CALL rflu_timestepviscous(pregion)
318  END IF ! pRegion
319  END DO ! iReg
320 
321  global%dtmin = global%dtImposed
322 
323 ! ==============================================================================
324 ! Move or generate new grid
325 ! ==============================================================================
326 
327  IF ( ( global%flowType == flow_unsteady ) .AND. &
328  ( global%iterSinceRestart > 0 ) ) THEN
329  IF ( movegrid .EQV. .true. ) THEN
330 
331 ! ------------------------------------------------------------------------------
332 ! Get the displacements from GENX (or other source).
333 ! ------------------------------------------------------------------------------
334 
335  CALL rflu_getdeformationwrapper(regions)
336 
337 ! ------------------------------------------------------------------------------
338 ! Store the old grid.
339 ! ------------------------------------------------------------------------------
340 
341  DO ireg = 1,global%nRegionsLocal
342  pgrid => regions(ireg)%grid
343  pgridold => regions(ireg)%gridOld
344  pgridold2 => regions(ireg)%gridOld2
345 
346  DO ic = 1,pgrid%nCellsTot ! Explicit copy to avoid ASCI White problem
347  pgridold2%vol(ic) = pgridold%vol(ic)
348  END DO ! ic
349 
350  DO iv = 1,pgrid%nVertTot ! Explicit copy to avoid ASCI White problem
351  pgridold2%xyz(xcoord,iv) = pgridold%xyz(xcoord,iv)
352  pgridold2%xyz(ycoord,iv) = pgridold%xyz(ycoord,iv)
353  pgridold2%xyz(zcoord,iv) = pgridold%xyz(zcoord,iv)
354  END DO ! iv
355  END DO ! iReg
356 
357  DO ireg = 1,global%nRegionsLocal
358  pgrid => regions(ireg)%grid
359  pgridold => regions(ireg)%gridOld
360 
361  DO ic = 1,pgrid%nCellsTot ! Explicit copy to avoid ASCI White problem
362  pgridold%vol(ic) = pgrid%vol(ic)
363  END DO ! ic
364 
365  DO iv = 1,pgrid%nVertTot ! Explicit copy to avoid ASCI White problem
366  pgridold%xyz(xcoord,iv) = pgrid%xyz(xcoord,iv)
367  pgridold%xyz(ycoord,iv) = pgrid%xyz(ycoord,iv)
368  pgridold%xyz(zcoord,iv) = pgrid%xyz(zcoord,iv)
369  END DO ! iv
370  END DO ! iReg
371 
372 ! ------------------------------------------------------------------------------
373 ! We will be substepping Mesquite, so start with a smaller displacement.
374 ! ------------------------------------------------------------------------------
375 
376  DO ireg = 1,global%nRegionsLocal
377  pgrid => regions(ireg)%grid
378 
379  DO ipatch = 1,pgrid%nPatches
380  ppatch => regions(ireg)%patches(ipatch)
381 
382  DO ivl = 1,ppatch%nBVert
383  ppatch%dXyz(xcoord,ivl) = insub*ppatch%dXyz(xcoord,ivl)
384  ppatch%dXyz(ycoord,ivl) = insub*ppatch%dXyz(ycoord,ivl)
385  ppatch%dXyz(zcoord,ivl) = insub*ppatch%dXyz(zcoord,ivl)
386  END DO ! ivl
387  END DO ! iPatch
388  END DO ! iReg
389 
390 ! ------------------------------------------------------------------------------
391 ! Substep displacements and smoothing to avoid inverting elements.
392 ! ------------------------------------------------------------------------------
393 
394  DO isub = 1,nsub
395  isubterm = (1.0_rfreal*isub)/(1.0_rfreal*isub-1.0_rfreal)
396 
397 ! ------- Displace the mesh by steadily increasing displacements until the
398 ! original displacement is reached.
399 
400  DO ireg = 1,global%nRegionsLocal
401  pgrid => regions(ireg)%grid
402 
403  DO ipatch = 1,pgrid%nPatches
404  ppatch => regions(ireg)%patches(ipatch)
405 
406  DO ivl = 1,ppatch%nBVert
407  IF ( isub > 1 ) THEN
408  ppatch%dXyz(xcoord,ivl) = isubterm*ppatch%dXyz(xcoord,ivl)
409  ppatch%dXyz(ycoord,ivl) = isubterm*ppatch%dXyz(ycoord,ivl)
410  ppatch%dXyz(zcoord,ivl) = isubterm*ppatch%dXyz(zcoord,ivl)
411  END IF ! iSub
412  END DO ! ivl
413  END DO ! iPatch
414  END DO ! iReg
415 
416 ! ------- Have Mesquite smooth the grid at each substep. NOTE:
417 ! This function will not store the old grid. That must be done before
418 ! Mesquite substepping begins.
419 
420  CALL rflu_movegridwrapper(regions)
421  END DO ! iSub
422 
423 ! ------------------------------------------------------------------------------
424 ! Finish by generating geometry and grid speeds for the new grid.
425 ! ------------------------------------------------------------------------------
426 
427  DO ireg = 1,global%nRegionsLocal
428  pregion => regions(ireg)
429 
430  CALL rflu_buildgeometry(pregion)
431  CALL rflu_computegridspeeds(pregion)
432 
433  IF ( global%checkLevel == check_high ) THEN
434  CALL rflu_checkgridspeeds(pregion)
435  END IF ! global%checkLevel
436  END DO ! iReg
437  END IF ! moveGrid
438  END IF ! global%flowType
439 
440 ! ==============================================================================
441 ! Recompute weights
442 ! ==============================================================================
443 
444  IF ( global%flowType == flow_unsteady ) THEN
445  IF ( movegrid .EQV. .true. ) THEN
446  DO ireg=1,global%nRegionsLocal
447  pregion => regions(ireg)
448  pmixtinput => pregion%mixtInput
449 
450  IF ( pmixtinput%spaceOrder > 1 ) THEN
451  CALL rflu_computewtsc2cwrapper(pregion,pmixtinput%spaceOrder-1)
452  END IF ! pMixtInput%spaceOrder
453 
454  IF ( pmixtinput%flowModel == flow_navst ) THEN
455  CALL rflu_computewtsf2cwrapper(pregion,pmixtinput%spaceOrder-1)
456  END IF ! pMixtInput%flowModel
457 
458  DO ipatch = 1,pregion%grid%nPatches
459  ppatch => pregion%patches(ipatch)
460 
461  IF ( rflu_decideneedbgradface(pregion,ppatch) .EQV. .true. ) THEN
462  CALL rflu_computewtsbf2cwrapper(pregion,ppatch, &
463  ppatch%spaceOrder)
464  END IF ! RFLU_DecideNeedBGradFace
465  END DO ! iPatch
466 
467  END DO ! iReg
468  END IF ! moveGrid
469  END IF ! global%flowType
470 
471 ! ==============================================================================
472 ! Relocate probes
473 ! ==============================================================================
474 
475  IF ( global%flowType == flow_unsteady ) THEN
476  IF ( movegrid .EQV. .true. ) THEN
477  IF ( global%nProbes > 0 ) THEN
478  DO ireg = 1,global%nRegionsLocal
479  pregion => regions(ireg)
480  CALL rflu_findprobecells(pregion)
481  END DO ! iReg
482 
483  CALL rflu_printprobeinfo(global)
484  END IF ! global
485  END IF ! moveGrid
486  END IF ! global%flowType
487 
488 ! ==============================================================================
489 ! Compute new solution.
490 ! ==============================================================================
491 
492  IF ( global%flowType == flow_steady ) THEN
493 
494 ! ------------------------------------------------------------------------------
495 ! For steady-state problems, simply compute the new solution
496 ! ------------------------------------------------------------------------------
497 
498  global%forceX = 0.0_rfreal
499  global%forceY = 0.0_rfreal
500  global%forceZ = 0.0_rfreal
501  global%massIn = 0.0_rfreal
502  global%massOut = 0.0_rfreal
503  pregion => regions(1)
504  pregion%mixt%cvOld(:,:) = pregion%mixt%cv(:,:)
505  pregion%irkStep = 1
506  CALL snessolve(pregion%snes,petsc_null_object,pregion%x,ierr)
507  CALL snesgetiterationnumber(pregion%snes,iter,ierr)
508 ! CALL RFLU_SetDependentVars(pRegion,1,pRegion%grid%nCells)
509 
510  CALL rflu_mpi_isendwrapper(pregion)
511 ! CALL RFLU_MPI_CopyWrapper(regions)
512  CALL rflu_setdependentvars(pregion,1,pregion%grid%nCells)
513  CALL rflu_mpi_recvwrapper(pregion)
514  CALL rflu_mpi_clearrequestwrapper(pregion)
515  CALL rflu_setdependentvars(pregion,pregion%grid%nCells+1,pregion%grid%nCellsTot)
516 
517  ELSE
518 
519 ! ------------------------------------------------------------------------------
520 ! For transient problems, first update the iteration variables for the
521 ! pseudo steady-state problem.
522 ! ------------------------------------------------------------------------------
523 
524  pregion => regions(1)
525 
526  iter = global%iterSinceRestart
527  global%currentIter = 0
528  global%iterSinceRestart = 0
529 
530  pregion%mixt%cvOld2(:,:) = pregion%mixt%cvOld1(:,:)
531  pregion%mixt%cvOld1(:,:) = pregion%mixt%cv(:,:)
532 
533  DO
534 
535 ! ------------------------------------------------------------------------------
536 ! Repeatedly solve the pseudo steady-state problem until the residual drops
537 ! below the residual tolerance.
538 ! ------------------------------------------------------------------------------
539 
540  global%currentIter = global%currentIter + 1
541  global%iterSinceRestart = global%iterSinceRestart + 1
542 
543  DO ireg = 1,global%nRegionsLocal
544  pregion => regions(ireg)
545  IF ( pregion%mixtInput%flowModel == flow_euler ) THEN
546  CALL rflu_timestepinviscid(pregion)
547  ELSE
548  CALL rflu_timestepviscous(pregion)
549  END IF ! pRegion
550  END DO ! iReg
551  global%dtmin = global%dtImposed
552 
553  pregion%mixt%cvOld(:,:) = pregion%mixt%cv(:,:)
554 
555  global%forceX = 0.0_rfreal
556  global%forceY = 0.0_rfreal
557  global%forceZ = 0.0_rfreal
558  global%massIn = 0.0_rfreal
559  global%massOut = 0.0_rfreal
560 
561  pregion%irkStep = 1
562 
563  CALL snessolve(pregion%snes,petsc_null_object,pregion%x,ierr)
564 ! CALL RFLU_SetDependentVars(pRegion,1,pRegion%grid%nCells)
565 
566  CALL rflu_mpi_isendwrapper(pregion)
567 ! CALL RFLU_MPI_CopyWrapper(regions)
568  CALL rflu_setdependentvars(pregion,1,pregion%grid%nCells)
569  CALL rflu_mpi_recvwrapper(pregion)
570  CALL rflu_mpi_clearrequestwrapper(pregion)
571  CALL rflu_setdependentvars(pregion,pregion%grid%nCells+1,pregion%grid%nCellsTot)
572 
573  CALL rflu_checkvalidity(pregion)
574  CALL rflu_checkpositivity(pregion)
575 
576  CALL rflu_residualnorm(regions)
577 
578 ! DEBUG
579  IF ( global%myProcid == 0 ) THEN
580  print*,'pseudo-steady info:',global%currentIter, &
581  global%residual/global%resInit,global%resTol
582  END IF ! global%myProcid
583 ! END DEBUG
584 
585  IF ( global%residual/global%resInit <= global%resTol ) THEN
586  EXIT
587  END IF ! global%residual
588  END DO
589  END IF ! global%flowType
590 
591 ! ==============================================================================
592 ! Check for convergence problems
593 ! ==============================================================================
594 
595  CALL snesgetconvergedreason(pregion%snes,reason,ierr)
596  !print*,'SNES REASON = ',reason
597  IF(reason == snes_diverged_function_count) THEN
598  global%warnCounter = global%warnCounter + 1
599  print*,'*** WARNING *** SNES FUNCTION COUNT EXCEEDED. ', &
600  'COPYING cvOld INTO cv TO PRESERVE PARTIALLY-CONVERGED SOLUTION.'
601  pregion%mixt%cv(:,:) = pregion%mixt%cvOld(:,:)
602  ENDIF ! reason
603  IF((reason /= snes_diverged_max_it).AND.(reason /= snes_converged_pnorm_relative).AND. &
604  (reason /= snes_diverged_function_count)) THEN
605  global%warnCounter = global%warnCounter + 1
606  print*,'*** WARNING *** SNES REASON DOES NOT INDICATE CONTINUATION OF SNES STEPPING: ',reason
607  ENDIF
608 
609 ! DEBUG
610 ! CALL RFLU_PrintFlowInfo(pRegion)
611 ! END DEBUG
612 
613 ! ==============================================================================
614 ! Check validity and positivity
615 ! ==============================================================================
616 
617  CALL rflu_checkvalidity(pregion)
618  CALL rflu_checkpositivity(pregion)
619 
620 ! ==============================================================================
621 ! Get statistics
622 ! ==============================================================================
623 
624 #ifdef STATS
625  CALL getstatistics(regions)
626 #endif
627 
628 ! ==============================================================================
629 ! Reset global%timeSince* variables. NOTE this must be done right before
630 ! the update of the various time variables, otherwise calling the routines
631 ! RFLU_Decide* from within rungeKuttaMP or explicitMultiStage will not work
632 ! correctly.
633 ! ==============================================================================
634 
635  IF ( rflu_decideprint(global) .EQV. .true. ) THEN
636  IF ( global%flowType == flow_unsteady ) THEN
637  IF ( global%iterSinceRestart > 1 ) THEN
638  global%timeSincePrint = 0.0_rfreal
639  END IF ! global%iterSinceRestart
640  END IF ! global%flowType
641  END IF ! RFLU_DecidePrint
642 
643  IF ( rflu_decidewrite(global) .EQV. .true. ) THEN
644  IF ( global%flowType == flow_unsteady ) THEN
645  global%timeSinceWrite = 0.0_rfreal
646  END IF ! global%flowType
647  END IF ! RFLU_DecideWrite
648 
649  IF ( rflu_decidewriteprobes(global) .EQV. .true. ) THEN
650  IF ( global%flowType == flow_unsteady ) THEN
651  IF ( global%iterSinceRestart > 1 ) THEN
652  global%timeSinceProbe = 0.0_rfreal
653  END IF ! global%iterSinceRestart
654  END IF ! global%flowType
655  END IF ! RFLU_DecideWriteProbes
656 
657 ! ==============================================================================
658 ! Update times for unsteady flow
659 ! ==============================================================================
660 
661  IF ( global%flowType == flow_unsteady ) THEN
662  global%currentTime = global%currentTime + global%dtImposed
663  global%timeSinceRestart = global%timeSinceRestart + global%dtImposed
664 
665  global%timeSincePrint = global%timeSincePrint + global%dtImposed
666  global%timeSinceWrite = global%timeSinceWrite + global%dtImposed
667  global%timeSinceProbe = global%timeSinceProbe + global%dtImposed
668 
669  global%iterSinceRestart = iter + 1
670  END IF ! global%flowType
671 
672 ! ==============================================================================
673 ! Decide whether to print/write convergence, data, and probes
674 ! ==============================================================================
675 
676  doprint = rflu_decideprint(global)
677  dowrite = rflu_decidewrite(global)
678  doprobe = rflu_decidewriteprobes(global)
679 
680 ! ==============================================================================
681 ! Check for end of timestepping
682 ! ==============================================================================
683 
684  IF ( global%flowType == flow_unsteady ) THEN
685  IF ( global%timeSinceRestart >= dtimesystem ) THEN
686  finished = .true.
687  END IF ! global%timeSinceRestart
688  ELSE
689  IF ( (doprint .EQV. .true.) .OR. (global%iterSinceRestart >= ditersystem) ) THEN
690  CALL rflu_residualnorm(regions)
691  IF ( (global%iterSinceRestart >= ditersystem) .OR. &
692  (global%residual/global%resInit <= global%resTol) ) THEN
693  finished = .true.
694  END IF ! global%iterSinceRestart
695  END IF ! doPrint
696  END IF ! global%flowType
697 
698 ! ==============================================================================
699 ! Write convergence (file & screen) and total mass (file) history
700 ! ==============================================================================
701 
702  IF ( (doprint .EQV. .true.) .OR. (finished .EQV. .true.) ) THEN
703  CALL rflu_printwriteconvergence(global)
704 
705 #ifndef GENX
706  IF ( movegrid .EQV. .true. ) THEN
707  CALL rflu_computeintegralvalues(regions)
708  CALL writetotalmass(regions)
709  END IF ! moveGrid
710 #endif
711 
712  DO ireg = 1,global%nRegionsLocal
713  IF ( regions(ireg)%mixtInput%spaceDiscr == discr_opt_les ) THEN
714  CALL rflu_writestatsfileoles(global)
715  END IF ! mixtInput
716  END DO ! iReg
717  END IF ! doPrint
718 
719 ! ==============================================================================
720 ! Compute forces and mass flow
721 ! ==============================================================================
722 
723  IF ( global%forceFlag .EQV. .true. ) THEN
724  IF ( (dowrite .EQV. .true.) .OR. (finished .EQV. .true.) ) THEN
725  DO ireg = 1,global%nRegionsLocal
726  pregion => regions(ireg)
727 
728  CALL rflu_computelocalforcesmoments(pregion)
729  END DO ! iReg
730 
731  CALL rflu_computeglobalforcesmoments(regions)
732 
733  pregion => regions(1)
734 
735  IF ( pregion%global%myProcid == masterproc ) THEN
736  CALL rflu_printglobalforcesmoments(pregion)
737  CALL rflu_writeglobalforcesmoments(pregion)
738  END IF ! pRegion
739  END IF ! doWrite
740  END IF ! global%forceFlag
741 
742 ! ==============================================================================
743 ! Store probe data
744 ! ==============================================================================
745 
746  IF ( global%nProbes > 0 ) THEN
747  IF ( doprobe .EQV. .true. ) THEN
748  DO ireg = 1,global%nRegionsLocal
749  CALL writeprobe(regions,ireg)
750  END DO ! iReg
751  END IF ! doProbe
752  END IF ! global
753 
754 ! DEBUG
755 #ifdef GENX
756 ! CALL RFLU_WriteGridWrapper(pRegion)
757 ! CALL RFLU_WriteFlowWrapper(pRegion)
758 ! CALL RFLU_ComputeIntegralValues(regions,integ)
759 ! print*,global%myProcid,global%currentTime,'777 777',integ(MAN_INTEG_MASS),integ(MAN_INTEG_VOL)
760 #endif
761 ! END DEBUG
762 
763 #ifndef GENX
764 ! ==============================================================================
765 ! Store flow field (and grid if moving). Write restart info file after
766 ! flow (and grid) files so that should those not be written due to reaching
767 ! the time limit, the restart file will not contain the time level of the
768 ! incomplete flow (and grid) files.
769 ! ==============================================================================
770 
771  IF ( (dowrite .EQV. .true.) .AND. (finished .EQV. .false.) ) THEN
772  DO ireg=1,global%nRegionsLocal
773  pregion => regions(ireg)
774 
775  CALL rflu_writedimensionswrapper(pregion,write_dimens_mode_maybe)
776 
777  IF ( movegrid .EQV. .true. ) THEN
778  CALL rflu_writegridwrapper(pregion)
779  CALL rflu_writegridspeedswrapper(pregion)
780 
781  IF ( global%myProcid == masterproc .AND. &
782  global%verbLevel > verbose_none ) THEN
783  CALL rflu_printgridinfo(pregion)
784  END IF ! global%myProcid
785  END IF ! moveGrid
786 
787  CALL rflu_writeflowwrapper(pregion)
788  CALL rflu_writepatchcoeffswrapper(pregion)
789 
790 #ifdef PLAG
791  CALL plag_writesurfstatswrapper(pregion)
792 #endif
793 
794  IF ( global%myProcid == masterproc .AND. &
795  global%verbLevel > verbose_none ) THEN
796 ! TEMPORARY
797 ! CALL RFLU_PrintFlowInfoWrapper(pRegion)
798 ! END TEMPORARY
799 
800  IF ( global%verbLevel > verbose_low ) THEN
801  CALL rflu_printchangeinfo(pregion)
802  END IF ! global%verbLevel
803  END IF ! global%myProcid
804  END DO ! iReg
805 
806  CALL rflu_writerestartinfo(global)
807  END IF ! doWrite
808 
809 #ifdef STATS
810 ! ==============================================================================
811 ! Output statistics
812 ! ==============================================================================
813 
814  IF ( (dowrite .EQV. .true.) .AND. (finished .EQV. .false.) .AND. &
815  (global%doStat == active) ) THEN
816  IF (global%myProcid==masterproc .AND. &
817  global%verbLevel/=verbose_none) THEN
818  WRITE(stdout,'(A)') solver_name,'Saving statistics ...'
819  ENDIF
820 
821  DO ireg = 1,global%nRegionsLocal
822  pregion => regions(ireg)
823  CALL rflu_writestat(pregion)
824  END DO ! iReg
825  END IF ! iReg
826 #endif
827 #endif
828 
829 ! ==============================================================================
830 ! If run finished, update GENX buffers and exit
831 ! ==============================================================================
832 
833  IF ( finished .EQV. .true. ) THEN
834 #ifdef GENX
835  DO ireg = 1,global%nRegionsLocal
836  CALL rflu_putboundaryvalues(regions(ireg))
837  END DO ! iReg
838 
839  global%timeStamp = global%currentTime
840 #endif
841 ! DEBUG
842  IF ( global%myProcid == 0 ) THEN
843  CALL petscgettime(time,ierr)
844  print*,'PETSC TIME 2 : ',time
845  END IF ! global%myProcid
846 ! END DEBUG
847  EXIT
848  END IF ! finished
849 
850 ! ==============================================================================
851 ! End of timestepping loop
852 ! ==============================================================================
853 
854  END DO ! loop over time/iterations
855 
856 ! ******************************************************************************
857 ! End
858 ! ******************************************************************************
859 
860  CALL deregisterfunction(global)
861 
862 END SUBROUTINE rflu_nk_timestepping
863 
864 
865 
866 
867 
868 
869 
870 
871 
872 
873 ! ******************************************************************************
874 ! End
875 ! ******************************************************************************
876 
877 END MODULE rflu_modnewtonkrylov
878 
879 
880 ! ******************************************************************************
881 !
882 ! RCS Revision history:
883 !
884 ! $Log: RFLU_ModNewtonKrylov.F90,v $
885 ! Revision 1.16 2008/12/06 08:44:22 mtcampbe
886 ! Updated license.
887 !
888 ! Revision 1.15 2008/11/19 22:17:33 mtcampbe
889 ! Added Illinois Open Source License/Copyright
890 !
891 ! Revision 1.14 2006/08/19 15:39:10 mparmar
892 ! Added use of RFLU_DecideNeedBGradFace and pPatch%spaceOrder
893 !
894 ! Revision 1.13 2006/04/07 16:04:02 haselbac
895 ! Adapted to changes in bf2c wts computation
896 !
897 ! Revision 1.12 2006/04/07 15:19:20 haselbac
898 ! Removed tabs
899 !
900 ! Revision 1.11 2006/04/07 14:49:41 haselbac
901 ! Adapted to changes in f and bf diff modules and new WENO module
902 !
903 ! Revision 1.10 2006/03/25 21:54:01 haselbac
904 ! Cosmetics only
905 !
906 ! Revision 1.9 2006/03/22 14:58:28 hdewey2
907 ! Fixed bug by adding additional virtual cell communication after SNESSolve calls.
908 !
909 ! Revision 1.8 2006/03/09 14:07:42 haselbac
910 ! Now call wrapper routine for F2C weights
911 !
912 ! Revision 1.7 2006/02/08 21:23:39 hdewey2
913 ! Added disp ramping and changed grid storage
914 !
915 ! Revision 1.6 2006/01/06 22:12:44 haselbac
916 ! Added call to cell grad wrapper routine
917 !
918 ! Revision 1.5 2005/10/25 19:38:47 haselbac
919 ! Reordered modules, added IF on forceFlag
920 !
921 ! Revision 1.4 2005/09/22 17:15:26 hdewey2
922 ! Added dual timestepping functionality to solve implicit time-dependent problems.
923 !
924 ! Revision 1.3 2005/08/02 18:19:43 hdewey2
925 ! Added actual procedures
926 !
927 ! Revision 1.2 2005/05/19 18:19:00 haselbac
928 ! Cosmetics only
929 !
930 ! Revision 1.1 2005/05/16 21:12:45 haselbac
931 ! Initial revision
932 !
933 ! ******************************************************************************
934 
935 
936 
937 
938 
939 
940 
941 
subroutine rflu_timestepviscous(pRegion)
subroutine rflu_movegridwrapper(regions)
unsigned char r() const
Definition: Color.h:68
subroutine rflu_printwriteconvergence(global)
subroutine integratesourcetermsmp(regions)
subroutine rflu_timestepinviscid(pRegion)
subroutine, public rflu_petsc_formresidual(snes, x, f, pRegion, ierr)
subroutine rflu_setdependentvars(pRegion, icgBeg, icgEnd)
subroutine, public rflu_writedimensionswrapper(pRegion, writeMode)
subroutine, public rflu_writeflowwrapper(pRegion)
LOGICAL function rflu_decideneedbgradface(pRegion, pPatch)
subroutine, public rflu_writegridspeedswrapper(pRegion)
subroutine, public rflu_mpi_isendwrapper(pRegion)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
**********************************************************************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 ic
LOGICAL function rflu_decidewrite(global)
subroutine, public rflu_buildgeometry(pRegion, sypeFaceFlag)
subroutine, public rflu_mpi_clearrequestwrapper(pRegion)
subroutine rflu_putboundaryvalues(region)
subroutine rflu_residualnorm(regions)
subroutine, public rflu_findprobecells(pRegion)
subroutine, public rflu_nk_timestepping(dTimeSystem, dIterSystem, regions)
LOGICAL function, public rflu_decidewriteprobes(global)
subroutine, public rflu_computewtsbf2cwrapper(pRegion, pPatch, order)
subroutine rflu_minimumtimestep(regions)
subroutine rflu_writestat(region)
subroutine rflu_checkvalidity(pRegion)
subroutine rflu_explicitmultistage(regions)
subroutine rflu_writestatsfileoles(global)
subroutine writeprobe(regions, iReg)
Definition: WriteProbe.F90:45
subroutine, public rflu_printprobeinfo(global)
subroutine rflu_computegridspeeds(pRegion)
subroutine, public getstatistics(regions)
subroutine, public rflu_writepatchcoeffswrapper(pRegion)
subroutine rflu_computeintegralvalues(regions)
subroutine rungekuttamp(regions)
subroutine, public rflu_writeglobalforcesmoments(pRegion)
subroutine, public rflu_mpi_recvwrapper(pRegion)
subroutine rflu_printflowinfo(pRegion)
subroutine, public rflu_writegridwrapper(pRegion)
subroutine, public plag_writesurfstatswrapper(pRegion)
subroutine, public rflu_computewtsc2cwrapper(pRegion, order)
subroutine, public rflu_petsc_formresidualfirstorder(snes, x, f, pRegion, ierr)
subroutine, public rflu_computeglobalforcesmoments(regions)
virtual std::ostream & print(std::ostream &os) const
subroutine, public rflu_petsc_formjacobian(snes, v, J, pJ, flag, pRegion, ierr)
subroutine, public rflu_computelocalforcesmoments(pRegion)
subroutine rflu_printgridinfo(pRegion)
LOGICAL function rflu_decideprint(global)
subroutine rflu_printchangeinfo(pRegion)
subroutine, public rflu_computewtsf2cwrapper(pRegion, order)
subroutine rflu_checkpositivity(pRegion)
subroutine rflu_checkgridspeeds(pRegion)
subroutine writetotalmass(regions)
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine rflu_writerestartinfo(global)
subroutine rflu_getdeformationwrapper(regions)
RT a() const
Definition: Line_2.h:140
subroutine, public rflu_printglobalforcesmoments(pRegion)
subroutine rflu_printflowinfowrapper(pRegion)