46 SUBROUTINE rflo_flowsolver( globalGenx,timeSystem,dTimeSystem,genxHandleBc, &
74 INTEGER,
INTENT(in) :: genxhandlebc, genxhandlegm
76 DOUBLE PRECISION,
INTENT(in) :: timesystem, dtimesystem
80 REAL(RFREAL) :: dtimesystem
83 INTEGER :: ditersystem
85 TYPE (t_region
),
POINTER :: regions(:)
91 CHARACTER(CHRLEN) ::
msg
93 REAL(RFREAL) :: timerbeg, timerend, timerloc, timerglob
101 global => globalgenx%global
102 regions => globalgenx%regions
104 global%genxHandleBc = genxhandlebc
105 global%genxHandleGm = genxhandlegm
107 IF ((global%currentTime-timesystem) > 1.e-9_rfreal)
THEN
108 global%predCorrIter = .true.
110 global%predCorrIter = .false.
112 global%currentTime = timesystem
113 global%timeStamp = timesystem
115 global => regions(1)%global
118 global%dTimeSystem = dtimesystem
121 'RFLO_FlowSolver.F90' )
126 IF (global%predCorrIter)
THEN
127 IF (global%myProcid == masterproc)
WRITE(stdout,
'(A)') &
128 solver_name//
' Restoring geometry (PC iteration) ...'
129 DO ireg=1,global%nRegions
130 IF (regions(ireg)%procid==global%myProcid .AND. &
131 regions(ireg)%active==active)
THEN
143 CALL com_call_function( genxhandlebc,2,0._rfreal,1 )
144 DO ireg=1,global%nRegions
145 IF (regions(ireg)%procid==global%myProcid .AND. &
146 regions(ireg)%active==active)
THEN
150 CALL com_call_function( genxhandlebc,2,0._rfreal,2 )
152 DO ireg=1,global%nRegions
153 IF (regions(ireg)%procid==global%myProcid .AND. &
154 regions(ireg)%active==active .AND. &
155 regions(ireg)%mixtInput%externalBc)
THEN
163 IF (global%flowType == flow_unsteady)
THEN
164 IF (dtimesystem <= 0._rfreal)
THEN
165 WRITE(
msg,1000) global%currentTime,global%maxTime
166 CALL
errorstop( global,err_dtime_negative,__line__,
msg )
169 IF (ditersystem <= 0)
THEN
170 WRITE(
msg,1005) global%currentIter,global%maxIter
171 CALL
errorstop( global,err_diter_negative,__line__,
msg )
179 CALL mpi_barrier( global%mpiComm,global%mpierr )
180 IF (global%mpierr /=0 ) CALL
errorstop( global,err_mpi_trouble,__line__ )
181 timerbeg = mpi_wtime()
185 IF (global%flowType == flow_unsteady)
THEN
186 IF (global%solverType == solv_explicit)
THEN
189 IF (global%cycleType == mgcycle_no)
THEN
196 IF (global%cycleType == mgcycle_no)
THEN
205 timerend = mpi_wtime()
206 timerloc = timerend - timerbeg
207 CALL mpi_reduce( timerloc,timerglob,1,mpi_rfreal,mpi_sum,masterproc, &
208 global%mpiComm,global%mpierr )
209 IF (global%mpierr /=0 ) CALL
errorstop( global,err_mpi_trouble,__line__ )
211 IF (global%myProcid == masterproc) &
212 WRITE(stdout,1020) solver_name,timerglob/
REAL(global%nProcAlloc), &
223 1000
FORMAT(
'Current time is= ',1pe12.5,
' but max. time is= ',e12.5)
224 1005
FORMAT(
'Current iteration is= ',i6,
' but max. iteration is= ',i6)
225 1020
FORMAT(/,
a,
' Elapsed time for this run: ',1pe12.5,
' sec. (average over ', &
subroutine rflo_copygeometrydummy(region)
subroutine rflo_dualmultigrid(dTimeSystem, regions)
subroutine registerfunction(global, funName, fileName)
subroutine rflo_flowsolver(dTimeSystem, dIterSystem, regions)
subroutine rflo_timestepping(dTimeSystem, dIterSystem, regions)
subroutine rflo_exchangegeometry(regions)
subroutine rflo_generatecoarsegrids(region)
subroutine rflo_sendboundaryvalues(region, initialize)
subroutine rflo_multigrid(dIterSystem, regions)
subroutine rflo_getboundaryvalues(region)
subroutine errorstop(global, errorCode, errorLine, addMessage)
subroutine, public rflo_calcgridmetrics(regions)
subroutine deregisterfunction(global)
subroutine rflo_dualtimestepping(dTimeSystem, regions)