Skip to content

Commit

Permalink
Merge branch 'master.dev' into 'master'
Browse files Browse the repository at this point in the history
Master.dev

See merge request piclas/boltzplatz!265
  • Loading branch information
gitlab-runner-iagpc231 committed Nov 1, 2018
2 parents 3c604e7 + 4945c66 commit 1456e7d
Show file tree
Hide file tree
Showing 31 changed files with 938 additions and 762 deletions.
610 changes: 305 additions & 305 deletions .gitlab-ci.yml

Large diffs are not rendered by default.

102 changes: 63 additions & 39 deletions src/analyze/analyze.f90
Original file line number Diff line number Diff line change
Expand Up @@ -111,6 +111,7 @@ SUBROUTINE InitAnalyze()
USE MOD_Interpolation_Vars ,ONLY: xGP,wBary,InterpolationInitIsDone
USE MOD_Analyze_Vars ,ONLY: Nanalyze,AnalyzeInitIsDone,Analyze_dt,DoCalcErrorNorms,CalcPoyntingInt
USE MOD_Analyze_Vars ,ONLY: CalcPointsPerWavelength,PPWCell,OutputTimeFixed
USE MOD_Analyze_Vars ,ONLY: AnalyzeCount,AnalyzeTime
USE MOD_ReadInTools ,ONLY: GETINT,GETREAL
USE MOD_AnalyzeField ,ONLY: GetPoyntingIntPlane
USE MOD_ReadInTools ,ONLY: GETLOGICAL
Expand Down Expand Up @@ -175,6 +176,10 @@ SUBROUTINE InitAnalyze()
END IF
#endif /*PARTICLES*/

! initialize time and counter for analyze measurement
AnalyzeCount = 0
AnalyzeTime = 0.0

AnalyzeInitIsDone = .TRUE.
SWRITE(UNIT_stdOut,'(A)')' INIT ANALYZE DONE!'
SWRITE(UNIT_StdOut,'(132("-"))')
Expand Down Expand Up @@ -247,7 +252,7 @@ SUBROUTINE InitAnalyzeBasis(N_in,Nanalyze_in,xGP,wBary)
END SUBROUTINE InitAnalyzeBasis


SUBROUTINE CalcError(time,L_2_Error)
SUBROUTINE CalcError(time,L_2_Error,L_Inf_Error)
!===================================================================================================================================
! Calculates L_infinfity and L_2 norms of state variables using the Analyze Framework (GL points+weights)
!===================================================================================================================================
Expand All @@ -269,16 +274,16 @@ SUBROUTINE CalcError(time,L_2_Error)
!----------------------------------------------------------------------------------------------------------------------------------
! OUTPUT VARIABLES
REAL,INTENT(OUT) :: L_2_Error(PP_nVar) !< L2 error of the solution
REAL,INTENT(OUT) :: L_Inf_Error(PP_nVar) !< LInf error of the solution
!----------------------------------------------------------------------------------------------------------------------------------
! LOCAL VARIABLES
INTEGER :: iElem,k,l,m
REAL :: L_Inf_Error(PP_nVar),U_exact(PP_nVar)
REAL :: U_exact(PP_nVar)
REAL :: U_NAnalyze(1:PP_nVar,0:NAnalyze,0:NAnalyze,0:NAnalyze)
REAL :: Coords_NAnalyze(3,0:NAnalyze,0:NAnalyze,0:NAnalyze)
REAL :: J_NAnalyze(1,0:NAnalyze,0:NAnalyze,0:NAnalyze)
REAL :: J_N(1,0:PP_N,0:PP_N,0:PP_N)
REAL :: IntegrationWeight
CHARACTER(LEN=40) :: formatStr
!===================================================================================================================================
L_Inf_Error(:)=-1.E10
L_2_Error(:)=0.
Expand Down Expand Up @@ -321,12 +326,6 @@ SUBROUTINE CalcError(time,L_2_Error)
! We normalize the L_2 Error with the Volume of the domain and take into account that we have to use the square root
L_2_Error = SQRT(L_2_Error/GEO%MeshVolume)

! Graphical output
IF(MPIroot) THEN
WRITE(formatStr,'(A5,I1,A7)')'(A13,',PP_nVar,'ES16.7)'
WRITE(UNIT_StdOut,formatStr)' L_2 : ',L_2_Error
WRITE(UNIT_StdOut,formatStr)' L_inf : ',L_Inf_Error
END IF
END SUBROUTINE CalcError

SUBROUTINE AnalyzeToFile(time,CalcTime,L_2_Error)
Expand Down Expand Up @@ -451,7 +450,7 @@ SUBROUTINE PerformAnalyze(OutputTime,tenddiff,forceAnalyze,OutPut,LastIter_In)
USE MOD_Globals
USE MOD_Preproc
USE MOD_Analyze_Vars ,ONLY: CalcPoyntingInt,DoAnalyze,DoCalcErrorNorms,OutputErrorNorms
USE MOD_Analyze_Vars ,ONLY: DoSurfModelAnalyze
USE MOD_Analyze_Vars ,ONLY: DoSurfModelAnalyze,AnalyzeCount,AnalyzeTime
USE MOD_Restart_Vars ,ONLY: DoRestart
USE MOD_TimeDisc_Vars ,ONLY: iter,tEnd
USE MOD_RecordPoints ,ONLY: RecordPoints
Expand Down Expand Up @@ -528,20 +527,24 @@ SUBROUTINE PerformAnalyze(OutputTime,tenddiff,forceAnalyze,OutPut,LastIter_In)
#endif /*CODE_ANALYZE*/
LOGICAL :: LastIter
REAL :: L_2_Error(PP_nVar)
REAL :: CalcTime
REAL :: L_Inf_Error(PP_nVar)
#if USE_LOADBALANCE
REAL :: tLBStart ! load balance
#endif /*USE_LOADBALANCE*/
REAL :: StartAnalyzeTime,EndAnalyzeTime
CHARACTER(LEN=40) :: formatStr
!===================================================================================================================================

! Create .csv file for performance analysis and load balance: write header line
CALL WriteElemTimeStatistics(WriteHeader=.TRUE.,iter=iter)

! not for first iteration (when analysis is called within RK steps)
! Not for first iteration (when analysis is called within RK steps)
#if (PP_TimeDiscMethod==1)||(PP_TimeDiscMethod==2)||(PP_TimeDiscMethod==6)||(PP_TimeDiscMethod>=501 && PP_TimeDiscMethod<=506)
IF((iter.EQ.0).AND.(.NOT.forceAnalyze)) RETURN
!IF(iter.EQ.0) RETURN
#endif
StartAnalyzeTime=BOLTZPLATZTIME()
!SWRITE(UNIT_stdOut,'(A)',ADVANCE='NO') ' PERFORM ANALYZE ...'
AnalyzeCount = AnalyzeCount + 1

LastIter=.FALSE.
IF(PRESENT(LastIter_in))THEN
Expand All @@ -554,22 +557,10 @@ SUBROUTINE PerformAnalyze(OutputTime,tenddiff,forceAnalyze,OutPut,LastIter_In)

! Calculate error norms
IF(forceAnalyze.OR.Output)THEN
CalcTime=BOLTZPLATZTIME()
IF(DoCalcErrorNorms) THEN
OutputErrorNorms=.TRUE.
CALL CalcError(OutputTime,L_2_Error)
IF (OutputTime.GE.tEnd) CALL AnalyzeToFile(OutputTime,CalcTime,L_2_Error)
END IF
IF(MPIroot) THEN
! write out has to be "Sim time" due to analyzes in reggie. Reggie searches for exactly this tag
WRITE(UNIT_StdOut,'(A13,ES16.7)')' Sim time : ',OutputTime
IF (OutputTime.GT.0.) THEN
WRITE(UNIT_StdOut,'(132("."))')
WRITE(UNIT_stdOut,'(A,A,A,F8.2,A)') ' BOLTZPLATZ RUNNING ',TRIM(ProjectName),'... [',CalcTime-StartTime,' sec ]'
WRITE(UNIT_StdOut,'(132("-"))')
ELSE
WRITE(UNIT_StdOut,'(132("="))')
END IF
CALL CalcError(OutputTime,L_2_Error,L_Inf_Error)
IF (OutputTime.GE.tEnd) CALL AnalyzeToFile(OutputTime,StartAnalyzeTime,L_2_Error)
END IF
END IF

Expand All @@ -580,20 +571,20 @@ SUBROUTINE PerformAnalyze(OutputTime,tenddiff,forceAnalyze,OutPut,LastIter_In)
#endif /*USE_LOADBALANCE*/
#if (PP_nVar>=6)
IF(forceAnalyze .AND. .NOT.DoRestart)THEN
! initial analysis is only performed for NO restart
! Initial analysis is only performed for NO restart
CALL CalcPoyntingIntegral(OutputTime,doProlong=.TRUE.)
ELSE
! analysis s performed for if iter can be divided by PartAnalyzeStep or for the dtAnalysis steps (writing state files)
! Analysis s performed for if iter can be divided by PartAnalyzeStep or for the dtAnalysis steps (writing state files)
#if defined(LSERK)
IF(DoRestart)THEN ! for a restart, the analyze should NOT be performed in the first iteration, because it is the zero state
IF(DoRestart)THEN ! For a restart, the analyze should NOT be performed in the first iteration, because it is the zero state
IF(iter.GT.1)THEN
! for LSERK the analysis is performed in the next RK-stage, thus, if a dtAnalysis step is performed, the analysis
! For LSERK the analysis is performed in the next RK-stage, thus, if a dtAnalysis step is performed, the analysis
! is triggered with prolong-to-face, which would else be missing
IF(MOD(iter,PartAnalyzeStep).EQ.0 .AND. .NOT. OutPut) CALL CalcPoyntingIntegral(OutputTime,doProlong=.FALSE.)
IF(MOD(iter,PartAnalyzeStep).NE.0 .AND. OutPut .AND. .NOT.LastIter) CALL CalcPoyntingIntegral(OutputTime,doProlong=.TRUE.)
END IF
ELSE
! for LSERK the analysis is performed in the next RK-stage, thus, if a dtAnalysis step is performed, the analysis
! For LSERK the analysis is performed in the next RK-stage, thus, if a dtAnalysis step is performed, the analysis
! is triggered with prolong-to-face, which would else be missing
IF(MOD(iter,PartAnalyzeStep).EQ.0 .AND. .NOT. OutPut) CALL CalcPoyntingIntegral(OutputTime,doProlong=.FALSE.)
IF(MOD(iter,PartAnalyzeStep).NE.0 .AND. OutPut .AND. .NOT.LastIter) CALL CalcPoyntingIntegral(OutputTime,doProlong=.TRUE.)
Expand Down Expand Up @@ -639,18 +630,18 @@ SUBROUTINE PerformAnalyze(OutputTime,tenddiff,forceAnalyze,OutPut,LastIter_In)
#endif

!----------------------------------------------------------------------------------------------------------------------------------
! PIC & DG-Sovler
! PIC & DG-Solver
!----------------------------------------------------------------------------------------------------------------------------------
IF (DoAnalyze.OR.DoSurfModelAnalyze) THEN
#ifdef PARTICLES
! particle analyze
! Particle analyze
IF(forceAnalyze .AND. .NOT.DoRestart)THEN
! initial analysis is only performed for NO restart
! Initial analysis is only performed for NO restart
CALL AnalyzeParticles(OutputTime)
CALL AnalyzeSurface(OutputTime)
ELSE
! analysis s performed for if iter can be divided by PartAnalyzeStep or for the dtAnalysis steps (writing state files)
IF(DoRestart)THEN ! for a restart, the analyze should NOT be performed in the first iteration, because it is the zero state
! Analysis s performed for if iter can be divided by PartAnalyzeStep or for the dtAnalysis steps (writing state files)
IF(DoRestart)THEN ! For a restart, the analyze should NOT be performed in the first iteration, because it is the zero state
#if defined(IMPA) || defined(ROS)
IF(iter.GE.1)THEN
#else
Expand Down Expand Up @@ -832,8 +823,8 @@ SUBROUTINE PerformAnalyze(OutputTime,tenddiff,forceAnalyze,OutPut,LastIter_In)
#endif
END IF

! meassure tracking time for particles // no MPI barrier MPI Wall-time but local CPU time
! allows non-synchronous meassurement of particle tracking
! Measure tracking time for particles // no MPI barrier MPI Wall-time but local CPU time
! Allows non-synchronous measurement of particle tracking
IF(OutPut .AND. MeasureTrackTime)THEN
#ifdef MPI
IF(MPIRoot) THEN
Expand Down Expand Up @@ -892,6 +883,39 @@ SUBROUTINE PerformAnalyze(OutputTime,tenddiff,forceAnalyze,OutPut,LastIter_In)
END IF
#endif /*CODE_ANALYZE*/

! Time for analysis
EndAnalyzeTime=BOLTZPLATZTIME()
!SWRITE(UNIT_stdOut,'(A,F14.2,A)',ADVANCE='YES') ' DONE! [',EndAnalyzeTime-StartAnalyzeTime,' sec ]'
AnalyzeTime = AnalyzeTime + EndAnalyzeTime-StartAnalyzeTime

!----------------------------------------------------------------------------------------------------------------------------------
! Output info
!----------------------------------------------------------------------------------------------------------------------------------
IF(forceAnalyze.OR.Output)THEN
IF(DoCalcErrorNorms) THEN
! Graphical output
IF(MPIroot) THEN
WRITE(formatStr,'(A5,I1,A7)')'(A13,',PP_nVar,'ES16.7)'
WRITE(UNIT_StdOut,formatStr)' L_2 : ',L_2_Error
WRITE(UNIT_StdOut,formatStr)' L_inf : ',L_Inf_Error
END IF
END IF
IF(MPIroot) THEN
! write out has to be "Sim time" due to analyzes in reggie. Reggie searches for exactly this tag
WRITE(UNIT_StdOut,'(A13,ES16.7)') ' Sim time : ',OutputTime
WRITE(UNIT_StdOut,'(A17,ES16.7,A9,I5,A)')' Analyze time : ',AnalyzeTime, ' (called ',AnalyzeCount,' times)'
AnalyzeCount = 0
AnalyzeTime = 0.0
IF (OutputTime.GT.0.) THEN
WRITE(UNIT_StdOut,'(132("."))')
WRITE(UNIT_stdOut,'(A,A,A,F14.2,A)') ' BOLTZPLATZ RUNNING ',TRIM(ProjectName),'... [',StartAnalyzeTime-StartTime,' sec ]'
WRITE(UNIT_StdOut,'(132("-"))')
ELSE
WRITE(UNIT_StdOut,'(132("="))')
END IF
END IF
END IF

END SUBROUTINE PerformAnalyze

#ifdef CODE_ANALYZE
Expand Down
2 changes: 2 additions & 0 deletions src/analyze/analyze_vars.f90
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,8 @@ MODULE MOD_Analyze_Vars
LOGICAL :: CalcPoyntingInt !< calulate pointing vector integral | only perp to z axis
REAL :: PoyntingIntCoordErr !< tolerance in plane searching
INTEGER :: nPoyntingIntPlanes !< number of planes
INTEGER :: AnalyzeCount !< number of analyzes (for info)
REAL :: AnalyzeTime !< accumulated time of analyzes (for info)
REAL,ALLOCATABLE :: PosPoyntingInt(:) !< z-coordinate of plane
REAL,ALLOCATABLE :: PoyntingIntPlaneFactor(:) !< plane factor
REAL,ALLOCATABLE :: S(:,:,:,:), STEM(:,:,:) !< vector, abs for TEM waves
Expand Down
10 changes: 5 additions & 5 deletions src/boltzplatz.f90
Original file line number Diff line number Diff line change
Expand Up @@ -114,7 +114,7 @@ PROGRAM Boltzplatz
! Measure init duration
Time=BOLTZPLATZTIME()
SWRITE(UNIT_stdOut,'(132("="))')
SWRITE(UNIT_stdOut,'(A,F8.2,A,I0,A)') ' READING INI DONE! [',Time-StartTime,' sec ] NOW '&
SWRITE(UNIT_stdOut,'(A,F14.2,A,I0,A)') ' READING INI DONE! [',Time-StartTime,' sec ] NOW '&
,prms%count_setentries(),' PARAMETERS ARE SET'
SWRITE(UNIT_stdOut,'(132("="))')
! Check if we want to read in DSMC.ini
Expand All @@ -124,7 +124,7 @@ PROGRAM Boltzplatz
! Measure init duration
Time=BOLTZPLATZTIME()
SWRITE(UNIT_stdOut,'(132("="))')
SWRITE(UNIT_stdOut,'(A,F8.2,A,I0,A)') ' READING FURTHER INI DONE! [',Time-StartTime,' sec ] NOW '&
SWRITE(UNIT_stdOut,'(A,F14.2,A,I0,A)') ' READING FURTHER INI DONE! [',Time-StartTime,' sec ] NOW '&
,prms%count_setentries(),' PARAMETERS ARE SET'
SWRITE(UNIT_stdOut,'(132("="))')
END IF
Expand Down Expand Up @@ -154,7 +154,7 @@ PROGRAM Boltzplatz
IF(MPIroot)THEN
Call SwapMesh()
SWRITE(UNIT_stdOut,'(132("="))')
SWRITE(UNIT_stdOut,'(A,F8.2,A)') ' SWAPMESH DONE! BOLTZPLATZ DONE! [',Time-StartTime,' sec ]'
SWRITE(UNIT_stdOut,'(A,F14.2,A)') ' SWAPMESH DONE! BOLTZPLATZ DONE! [',Time-StartTime,' sec ]'
SWRITE(UNIT_stdOut,'(132("="))')
STOP
ELSE
Expand All @@ -171,7 +171,7 @@ PROGRAM Boltzplatz
Time=BOLTZPLATZTIME()
InitializationWallTime=Time-StartTime
SWRITE(UNIT_stdOut,'(132("="))')
SWRITE(UNIT_stdOut,'(A,F8.2,A)') ' INITIALIZATION DONE! [',InitializationWallTime,' sec ]'
SWRITE(UNIT_stdOut,'(A,F14.2,A)') ' INITIALIZATION DONE! [',InitializationWallTime,' sec ]'
SWRITE(UNIT_stdOut,'(132("="))')

! Run Simulation
Expand Down Expand Up @@ -201,7 +201,7 @@ PROGRAM Boltzplatz
,'MPI finalize error',iError,999.)
#endif
SWRITE(UNIT_stdOut,'(132("="))')
SWRITE(UNIT_stdOut,'(A,F8.2,A)') ' BOLTZPLATZ FINISHED! [',Time-StartTime,' sec ]'
SWRITE(UNIT_stdOut,'(A,F14.2,A)') ' BOLTZPLATZ FINISHED! [',Time-StartTime,' sec ]'
SWRITE(UNIT_stdOut,'(132("="))')

END PROGRAM Boltzplatz
Expand Down
2 changes: 1 addition & 1 deletion src/boltzplatz.h
Original file line number Diff line number Diff line change
Expand Up @@ -125,7 +125,7 @@
#define RIEMANN_VAC2DIELECTRIC_NC 6

! format
#define WRITEFORMAT '(E25.14E3)'
#define WRITEFORMAT '(ES25.14E3)'

! Load Balance (LB) position in array for measuring the time that is spent on specific operations
#define LB_DG 1
Expand Down
4 changes: 2 additions & 2 deletions src/h5boltz2vtk.f90
Original file line number Diff line number Diff line change
Expand Up @@ -191,7 +191,7 @@ PROGRAM H5BOLTZ2VTK
! Measure init duration
Time=BOLTZPLATZTIME()
SWRITE(UNIT_stdOut,'(132("="))')
SWRITE(UNIT_stdOut,'(A,F8.2,A)') ' INITIALIZATION DONE! [',Time-StartTime,' sec ]'
SWRITE(UNIT_stdOut,'(A,F14.2,A)') ' INITIALIZATION DONE! [',Time-StartTime,' sec ]'
SWRITE(UNIT_stdOut,'(132("="))')

! Initialize an "old" state to check against - used to determine if we need to reinitialize some variables
Expand Down Expand Up @@ -406,7 +406,7 @@ PROGRAM H5BOLTZ2VTK
END IF
#endif
SWRITE(UNIT_stdOut,'(132("="))')
SWRITE(UNIT_stdOut,'(A,F8.2,A)') ' H5BOLTZ2VTK FINISHED! [',Time-StartTime,' sec ]'
SWRITE(UNIT_stdOut,'(A,F14.2,A)') ' H5BOLTZ2VTK FINISHED! [',Time-StartTime,' sec ]'
SWRITE(UNIT_stdOut,'(132("="))')

END PROGRAM H5BOLTZ2VTK
Expand Down
2 changes: 1 addition & 1 deletion src/hdg/elem_mat.f90
Original file line number Diff line number Diff line change
Expand Up @@ -284,7 +284,7 @@ SUBROUTINE Elem_Mat(td_iter)
IF(DoDisplayIter)THEN
IF(MOD(td_iter,IterDisplayStep).EQ.0) THEN
time=BOLTZPLATZTIME()
SWRITE(UNIT_stdOut,'(A,F8.2,A)') ' HDG ELEME_MAT DONE! [',Time-time0,' sec ]'
SWRITE(UNIT_stdOut,'(A,F14.2,A)') ' HDG ELEME_MAT DONE! [',Time-time0,' sec ]'
SWRITE(UNIT_stdOut,'(132("-"))')
END IF
END IF
Expand Down
Loading

0 comments on commit 1456e7d

Please sign in to comment.