108 CHARACTER(CHRLEN) :: &
109 RCSIdentString =
'$RCSfile: RFLU_ModNewtonKrylov.F90,v $ $Revision: 1.16 $'
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"
172 SUBROUTINE snessetfunction(snes,r,fun,ctx,ierr)
177 TYPE(t_region
),
POINTER :: ctx
180 SUBROUTINE snessetjacobian(snes,A,pA,fun,ctx,ierr)
185 TYPE(t_region
),
POINTER :: ctx
188 SUBROUTINE matfdcoloringsetfunctionsnes(matfd,fun,ctx,ierr)
190 matfdcoloring :: matfd
192 TYPE(t_region
),
POINTER :: ctx
205 LOGICAL :: doprint,doprobe,dowrite
206 LOGICAL :: finished = .false., movegrid
207 INTEGER :: ditersystem
208 REAL(RFREAL) :: dtimesystem
209 TYPE(t_region
),
POINTER :: pregion,regions(:)
215 INTEGER :: gtemp,
ic,ierr,ipatch,ireg,iter,iv,ltemp
218 TYPE(t_patch),
POINTER :: ppatch
219 snesconvergedreason reason
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
239 global => regions(1)%global
240 pregion => regions(1)
243 insub = 1.0_rfreal/nsub
246 'RFLU_ModNewtonKrylov.F90')
254 DO ireg = 1,global%nRegionsLocal
255 IF ( regions(ireg)%mixtInput%moveGrid .EQV. .true. )
THEN
264 CALL snessetfunction(pregion%snes,pregion%r, &
266 CALL snessetjacobian(pregion%snes,pregion%A,pregion%preA, &
268 CALL matfdcoloringsetfunctionsnes(pregion%fdcolor, &
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(:,:)
288 IF ( global%myProcid == 0 )
THEN
289 CALL petscgettime(time,ierr)
290 print*,
'PETSC TIME 1 : ',time
302 IF ( global%flowType == flow_steady )
THEN
303 global%currentIter = global%currentIter + 1
304 global%iterSinceRestart = global%iterSinceRestart + 1
311 DO ireg = 1,global%nRegionsLocal
312 pregion => regions(ireg)
314 IF ( pregion%mixtInput%flowModel == flow_euler )
THEN
321 global%dtmin = global%dtImposed
327 IF ( ( global%flowType == flow_unsteady ) .AND. &
328 ( global%iterSinceRestart > 0 ) )
THEN
329 IF ( movegrid .EQV. .true. )
THEN
341 DO ireg = 1,global%nRegionsLocal
342 pgrid => regions(ireg)%grid
343 pgridold => regions(ireg)%gridOld
344 pgridold2 => regions(ireg)%gridOld2
346 DO ic = 1,pgrid%nCellsTot
347 pgridold2%vol(
ic) = pgridold%vol(
ic)
350 DO iv = 1,pgrid%nVertTot
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)
357 DO ireg = 1,global%nRegionsLocal
358 pgrid => regions(ireg)%grid
359 pgridold => regions(ireg)%gridOld
361 DO ic = 1,pgrid%nCellsTot
362 pgridold%vol(
ic) = pgrid%vol(
ic)
365 DO iv = 1,pgrid%nVertTot
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)
376 DO ireg = 1,global%nRegionsLocal
377 pgrid => regions(ireg)%grid
379 DO ipatch = 1,pgrid%nPatches
380 ppatch => regions(ireg)%patches(ipatch)
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)
395 isubterm = (1.0_rfreal*isub)/(1.0_rfreal*isub-1.0_rfreal)
400 DO ireg = 1,global%nRegionsLocal
401 pgrid => regions(ireg)%grid
403 DO ipatch = 1,pgrid%nPatches
404 ppatch => regions(ireg)%patches(ipatch)
406 DO ivl = 1,ppatch%nBVert
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)
427 DO ireg = 1,global%nRegionsLocal
428 pregion => regions(ireg)
433 IF ( global%checkLevel == check_high )
THEN
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
450 IF ( pmixtinput%spaceOrder > 1 )
THEN
454 IF ( pmixtinput%flowModel == flow_navst )
THEN
458 DO ipatch = 1,pregion%grid%nPatches
459 ppatch => pregion%patches(ipatch)
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)
492 IF ( global%flowType == flow_steady )
THEN
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(:,:)
506 CALL snessolve(pregion%snes,petsc_null_object,pregion%x,ierr)
507 CALL snesgetiterationnumber(pregion%snes,iter,ierr)
524 pregion => regions(1)
526 iter = global%iterSinceRestart
527 global%currentIter = 0
528 global%iterSinceRestart = 0
530 pregion%mixt%cvOld2(:,:) = pregion%mixt%cvOld1(:,:)
531 pregion%mixt%cvOld1(:,:) = pregion%mixt%cv(:,:)
540 global%currentIter = global%currentIter + 1
541 global%iterSinceRestart = global%iterSinceRestart + 1
543 DO ireg = 1,global%nRegionsLocal
544 pregion => regions(ireg)
545 IF ( pregion%mixtInput%flowModel == flow_euler )
THEN
551 global%dtmin = global%dtImposed
553 pregion%mixt%cvOld(:,:) = pregion%mixt%cv(:,:)
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
563 CALL snessolve(pregion%snes,petsc_null_object,pregion%x,ierr)
579 IF ( global%myProcid == 0 )
THEN
580 print*,
'pseudo-steady info:',global%currentIter, &
581 global%residual/global%resInit,global%resTol
585 IF ( global%residual/global%resInit <= global%resTol )
THEN
595 CALL snesgetconvergedreason(pregion%snes,reason,ierr)
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(:,:)
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
636 IF ( global%flowType == flow_unsteady )
THEN
637 IF ( global%iterSinceRestart > 1 )
THEN
638 global%timeSincePrint = 0.0_rfreal
644 IF ( global%flowType == flow_unsteady )
THEN
645 global%timeSinceWrite = 0.0_rfreal
650 IF ( global%flowType == flow_unsteady )
THEN
651 IF ( global%iterSinceRestart > 1 )
THEN
652 global%timeSinceProbe = 0.0_rfreal
661 IF ( global%flowType == flow_unsteady )
THEN
662 global%currentTime = global%currentTime + global%dtImposed
663 global%timeSinceRestart = global%timeSinceRestart + global%dtImposed
665 global%timeSincePrint = global%timeSincePrint + global%dtImposed
666 global%timeSinceWrite = global%timeSinceWrite + global%dtImposed
667 global%timeSinceProbe = global%timeSinceProbe + global%dtImposed
669 global%iterSinceRestart = iter + 1
684 IF ( global%flowType == flow_unsteady )
THEN
685 IF ( global%timeSinceRestart >= dtimesystem )
THEN
689 IF ( (doprint .EQV. .true.) .OR. (global%iterSinceRestart >= ditersystem) )
THEN
691 IF ( (global%iterSinceRestart >= ditersystem) .OR. &
692 (global%residual/global%resInit <= global%resTol) )
THEN
702 IF ( (doprint .EQV. .true.) .OR. (finished .EQV. .true.) )
THEN
706 IF ( movegrid .EQV. .true. )
THEN
712 DO ireg = 1,global%nRegionsLocal
713 IF ( regions(ireg)%mixtInput%spaceDiscr == discr_opt_les )
THEN
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)
733 pregion => regions(1)
735 IF ( pregion%global%myProcid == masterproc )
THEN
746 IF ( global%nProbes > 0 )
THEN
747 IF ( doprobe .EQV. .true. )
THEN
748 DO ireg = 1,global%nRegionsLocal
771 IF ( (dowrite .EQV. .true.) .AND. (finished .EQV. .false.) )
THEN
772 DO ireg=1,global%nRegionsLocal
773 pregion => regions(ireg)
777 IF ( movegrid .EQV. .true. )
THEN
781 IF ( global%myProcid == masterproc .AND. &
782 global%verbLevel > verbose_none )
THEN
794 IF ( global%myProcid == masterproc .AND. &
795 global%verbLevel > verbose_none )
THEN
800 IF ( global%verbLevel > verbose_low )
THEN
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 ...'
821 DO ireg = 1,global%nRegionsLocal
822 pregion => regions(ireg)
833 IF ( finished .EQV. .true. )
THEN
835 DO ireg = 1,global%nRegionsLocal
839 global%timeStamp = global%currentTime
842 IF ( global%myProcid == 0 )
THEN
843 CALL petscgettime(time,ierr)
844 print*,
'PETSC TIME 2 : ',time
subroutine rflu_timestepviscous(pRegion)
subroutine rflu_movegridwrapper(regions)
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)
**********************************************************************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)
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)
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)
subroutine rflu_writerestartinfo(global)
subroutine, public rflu_printglobalforcesmoments(pRegion)
subroutine rflu_printflowinfowrapper(pRegion)