Skip to content

Commit

Permalink
Merge branch 'update.nbr.of.particle.output' into 'master.dev'
Browse files Browse the repository at this point in the history
[update.nbr.of.particle.output] Added output info of average number of particles per processor as well as...

See merge request piclas/piclas!652
  • Loading branch information
scopplestone committed Jun 8, 2022
2 parents b7572a1 + 8c0ae97 commit eb9ed43
Show file tree
Hide file tree
Showing 10 changed files with 173 additions and 84 deletions.
2 changes: 1 addition & 1 deletion regressioncheck/NIG_PIC_poisson_RK3/builds.ini
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
binary=./bin/piclas

! compiler flags
CMAKE_BUILD_TYPE = Release
CMAKE_BUILD_TYPE = Debug,Release
LIBS_BUILD_HDF5 = OFF
PICLAS_POLYNOMIAL_DEGREE = N
PICLAS_EQNSYSNAME = poisson
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ useCurveds = F
! OUTPUT / VISUALIZATION
! =============================================================================== !
ProjectName = N1_06-nbc_BR
IterDisplayStep = 10 ! (default: '1')
IterDisplayStep = 1 ! (default: '1')
! =============================================================================== !
! CALCULATION
! =============================================================================== !
Expand Down
51 changes: 49 additions & 2 deletions src/globals/globals.f90
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,10 @@ MODULE MOD_Globals
INTEGER, PARAMETER :: IK = SELECTED_INT_KIND(8)
#endif

INTEGER(KIND=IK) :: nGlobalNbrOfParticles
#if defined(PARTICLES)
INTEGER(KIND=IK) :: nGlobalNbrOfParticles(6) !< 1-3: min,max,total number of simulation particles over all processors
! !< 4-6: peak values over the complete simulation
#endif /*defined(PARTICLES)*/

INTERFACE ReOpenLogFile
MODULE PROCEDURE ReOpenLogFile
Expand Down Expand Up @@ -163,6 +166,10 @@ END SUBROUTINE processmemusage
INTERFACE SPECIESISELECTRON
MODULE PROCEDURE SPECIESISELECTRON
END INTERFACE

INTERFACE DisplayNumberOfParticles
MODULE PROCEDURE DisplayNumberOfParticles
END INTERFACE
#endif /*defined(PARTICLES)*/

INTERFACE LOG_RAN
Expand Down Expand Up @@ -1111,6 +1118,12 @@ SUBROUTINE DisplaySimulationTime(Time, StartTime, Message)
! Return with all procs except root if not called during abort
IF(.NOT.MPIRoot.AND.(Message.NE.'ABORTED')) RETURN

! Output particle info
#if defined(PARTICLES)
IF(Message.NE.'RUNNING') CALL DisplayNumberOfParticles(2)
#endif /*defined(PARTICLES)*/

! Calculate simulation time
SimulationTime = Time-StartTime

! Get secs, mins, hours and days
Expand All @@ -1123,7 +1136,8 @@ SUBROUTINE DisplaySimulationTime(Time, StartTime, Message)
!days = MOD(SimulationTime,365.) ! Use this if years are also to be displayed
days = SimulationTime

! Output
! Output message with all procs, as root might not be the calling process during abort
IF(MPIRoot.AND.(Message.NE.'ABORTED')) WRITE(UNIT_stdOut,'(132("="))')
WRITE(UNIT_stdOut,'(A,F16.2,A)',ADVANCE='NO') ' PICLAS '//TRIM(Message)//'! [',Time-StartTime,' sec ]'
WRITE(UNIT_stdOut,'(A2,I6,A1,I0.2,A1,I0.2,A1,I0.2,A1)') ' [',INT(days),':',INT(hours),':',INT(mins),':',INT(secs),']'
END SUBROUTINE DisplaySimulationTime
Expand Down Expand Up @@ -1356,4 +1370,37 @@ PPURE LOGICAL FUNCTION ElementOnNode(GlobalElemID) RESULT(L)
END FUNCTION ElementOnNode


#if defined(PARTICLES)
!===================================================================================================================================
!> Write min, max, average and total number of simulations particles to stdout stream
!===================================================================================================================================
SUBROUTINE DisplayNumberOfParticles(Mode)
! MODULES
IMPLICIT NONE
!----------------------------------------------------------------------------------------------------------------------------------!
! INPUT / OUTPUT VARIABLES
INTEGER,INTENT(IN) :: Mode ! 1: during the simulation
! ! 2: at the end of the simulation
!-----------------------------------------------------------------------------------------------------------------------------------
! LOCAL VARIABLES

!===================================================================================================================================
SELECT CASE(Mode)
CASE(1)
SWRITE(UNIT_StdOut,'(4(A,ES16.7))') "#Particles : ", REAL(nGlobalNbrOfParticles(3)),&
" Average particles per proc : ",REAL(nGlobalNbrOfParticles(3))/REAL(nProcessors),&
" Min : ",REAL(nGlobalNbrOfParticles(1)),&
" Max : ",REAL(nGlobalNbrOfParticles(2))
CASE(2)
SWRITE(UNIT_StdOut,'(4(A,ES16.7))') "#Particles : ", REAL(nGlobalNbrOfParticles(6)),&
" (peak) Average (peak) : ",REAL(nGlobalNbrOfParticles(6))/REAL(nProcessors),&
" Min : ",REAL(nGlobalNbrOfParticles(4)),&
" Max : ",REAL(nGlobalNbrOfParticles(5))
CASE DEFAULT
CALL abort(__STAMP__,'DisplayNumberOfParticles() called with unknown Mode=',IntInfoOpt=Mode)
END SELECT
END SUBROUTINE DisplayNumberOfParticles
#endif /*defined(PARTICLES)*/


END MODULE MOD_Globals
7 changes: 7 additions & 0 deletions src/globals/globals_init.f90
Original file line number Diff line number Diff line change
Expand Up @@ -76,6 +76,9 @@ SUBROUTINE InitGlobals()
#if USE_MPI
USE MOD_Globals ,ONLY: MPIRoot
#endif /*USE_MPI*/
#if defined(PARTICLES)
USE MOD_Globals ,ONLY: nGlobalNbrOfParticles
#endif /*defined(PARTICLES)*/
! IMPLICIT VARIABLE HANDLING
IMPLICIT NONE
!-----------------------------------------------------------------------------------------------------------------------------------
Expand Down Expand Up @@ -120,6 +123,10 @@ SUBROUTINE InitGlobals()
CALL abort(__STAMP__,' Speed of light coefficients does not match!')
END IF

#if defined(PARTICLES)
nGlobalNbrOfParticles=0
nGlobalNbrOfParticles(4)=HUGE(nGlobalNbrOfParticles(4))
#endif /*defined(PARTICLES)*/

! Open file for logging
IF(Logging)THEN
Expand Down
1 change: 0 additions & 1 deletion src/init/piclas_init.f90
Original file line number Diff line number Diff line change
Expand Up @@ -387,7 +387,6 @@ SUBROUTINE FinalizePiclas(IsLoadBalance)
! Before program termination: Finalize load balance
! Measure simulation duration
Time=PICLASTIME()
SWRITE(UNIT_stdOut,'(132("="))')
CALL FinalizeLoadBalance(IsLoadBalance)
IF(.NOT.IsLoadBalance)THEN
CALL DisplaySimulationTime(Time, StartTime, 'FINISHED')
Expand Down
Loading

0 comments on commit eb9ed43

Please sign in to comment.