Skip to content

Commit

Permalink
Enable separate keyword for result file only
Browse files Browse the repository at this point in the history
  • Loading branch information
raback committed Jan 30, 2021
1 parent 2a20455 commit e575746
Show file tree
Hide file tree
Showing 2 changed files with 20 additions and 4 deletions.
23 changes: 19 additions & 4 deletions fem/src/ElmerSolver.F90
Expand Up @@ -81,7 +81,7 @@ SUBROUTINE ElmerSolver(initialize)

TYPE(Element_t),POINTER :: CurrentElement

LOGICAL :: GotIt,Transient,Scanning,LastSaved, MeshMode = .FALSE.
LOGICAL :: GotIt,Transient,Scanning, LastSaved, MeshMode = .FALSE.

INTEGER :: TimeIntervals,interval,timestep, &
TotalTimesteps,SavedSteps,CoupledMaxIter,CoupledMinIter
Expand Down Expand Up @@ -2672,7 +2672,13 @@ SUBROUTINE ExecSimulation(TimeIntervals, CoupledMinIter, &
IF( ExecThis ) CALL SolverActivate( CurrentModel,Solver,dt,Transient )
END DO

CALL SaveCurrent(Timestep)
! Output file is used to Save the results for restart.
! Optionally we may save just the final stage which saves disk space and time.
IF( .NOT. ListGetLogical( CurrentModel % Simulation,'Output File Final Only',GotIt) ) THEN
CALL SaveCurrent(Timestep)
END IF

CALL SaveToPost(TimeStep)
LastSaved = .TRUE.

DO i=1,nSolvers
Expand Down Expand Up @@ -2755,7 +2761,11 @@ SUBROUTINE ExecSimulation(TimeIntervals, CoupledMinIter, &
END DO

CALL SaveToPost(0)
CALL SaveCurrent(Timestep)
CALL SaveToPost(TimeStep)

IF( .NOT. ListGetLogical( CurrentModel % Simulation,'Output File Final Only',GotIt) ) THEN
CALL SaveCurrent(Timestep)
END IF

DO i=1,CurrentModel % NumberOfSolvers
Solver => CurrentModel % Solvers(i)
Expand All @@ -2765,7 +2775,11 @@ SUBROUTINE ExecSimulation(TimeIntervals, CoupledMinIter, &
IF ( GotIt ) ExecThis = ( When == 'after saving')
IF( ExecThis ) CALL SolverActivate( CurrentModel,Solver,dt,Transient )
END DO
ELSE IF( ListGetLogical( CurrentModel % Simulation,'Output File Final Only',GotIt) ) THEN
CALL SaveCurrent(Timestep)
END IF



!------------------------------------------------------------------------------
END SUBROUTINE ExecSimulation
Expand Down Expand Up @@ -2887,7 +2901,8 @@ SUBROUTINE SaveCurrent( CurrentStep )
Mesh => Mesh % Next
END DO
END IF
CALL SaveToPost(CurrentStep)
! We want to seprate saving of ElmerPost file and Result file.
! CALL SaveToPost(CurrentStep)
!------------------------------------------------------------------------------
END SUBROUTINE SaveCurrent
!------------------------------------------------------------------------------
Expand Down
1 change: 1 addition & 0 deletions fem/src/SOLVER.KEYWORDS
Expand Up @@ -1809,4 +1809,5 @@ solver:real: 'cyclic system convergence tolerance'
simulation:logical: 'parallel timestepping'
simulation:integer: 'periodic timesteps'
simulation:logical: 'single mesh'
simulation:logical: 'output file final only'

0 comments on commit e575746

Please sign in to comment.