Skip to content

Commit

Permalink
Merge branch 'feature.gcc.warning' into 'master.dev'
Browse files Browse the repository at this point in the history
[feature.gcc.warning] Check GCC parse_associate, split parameter files at comma

See merge request piclas/piclas!907
  • Loading branch information
scopplestone committed Feb 15, 2024
2 parents 581e3e4 + 83e9d48 commit d09a67e
Show file tree
Hide file tree
Showing 5 changed files with 88 additions and 9 deletions.
2 changes: 1 addition & 1 deletion .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ _build/
doxygen/

# regression test
regressioncheck/reggie/*
regressioncheck/*
output_dir_gitlab_tool/
output_dir/
reggie_run/
Expand Down
30 changes: 29 additions & 1 deletion CMakeListsMachine.txt
Original file line number Diff line number Diff line change
Expand Up @@ -198,6 +198,34 @@ IF(NOT Fortran2003Check)
MESSAGE(FATAL_ERROR "Failed to compile basic Fortran2003 programm! Please ensure your compiler is up-to-date!")
ENDIF()

# =========================================================================
# CHECK IF GCC CONTAINS THE PARSE_ASSOCIATE BUG (GC C13.1-13.2)
# =========================================================================
INCLUDE(CheckFortranSourceCompiles)
CHECK_FORTRAN_SOURCE_COMPILES(
"MODULE GCC13MOD
IMPLICIT NONE
PRIVATE
CONTAINS
! Check for MOVE_ALLOC feature
SUBROUTINE GCC_PARSE_ASSOCAIATE()
REAL::x1(3),x2(3)
ASSOCIATE(v1 => x1, v2 => x2)
v1 = 0
v2 = 1
v1 = 0 + v1
END SUBROUTINE GCC_PARSE_ASSOCIATE
END MODULE GCC13MOD

PROGRAM GCC13PROG
END"
GCC13Check
SRC_EXT F90)

IF(NOT GCC13Check)
MESSAGE(WARNING "The requested compiler ${CMAKE_Fortran_COMPILER_ID} (v${CMAKE_Fortran_COMPILER_VERSION}) contains a bug in parse_associate. Ensure ASSOCIATE is only use with explicit array bounds or use a different compiler version. Please see the upstream issue, https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948")
ENDIF()

# =========================================================================
# COMPILER FLAGS
# =========================================================================
Expand Down Expand Up @@ -304,4 +332,4 @@ SET(CMAKE_Fortran_FLAGS "${CMAKE_Fortran_FLAGS}" CACHE STRIN
SET(CMAKE_Fortran_FLAGS_RELEASE "${CMAKE_Fortran_FLAGS_RELEASE}" CACHE STRING "Release compiler flags" FORCE)
SET(CMAKE_Fortran_FLAGS_PROFILE "${CMAKE_Fortran_FLAGS_PROFILE}" CACHE STRING "Profile compiler flags" FORCE)
SET(CMAKE_Fortran_FLAGS_DEBUG "${CMAKE_Fortran_FLAGS_DEBUG}" CACHE STRING "Debug compiler flags" FORCE)
SET(CMAKE_Fortran_FLAGS_SANITIZE "${CMAKE_Fortran_FLAGS_SANITIZE}" CACHE STRING "Sanitize compiler flags" FORCE)
SET(CMAKE_Fortran_FLAGS_SANITIZE "${CMAKE_Fortran_FLAGS_SANITIZE}" CACHE STRING "Sanitize compiler flags" FORCE)
7 changes: 6 additions & 1 deletion src/loadbalance/loadbalance.f90
Original file line number Diff line number Diff line change
Expand Up @@ -123,6 +123,7 @@ SUBROUTINE InitLoadBalance()
END IF
LoadBalanceSample = GETINT('LoadBalanceSample')
LoadBalanceMaxSteps = GETINT('LoadBalanceMaxSteps')
IF (LoadBalanceMaxSteps.LE.0) LoadBalanceMaxSteps = HUGE(1)
PerformPartWeightLB = GETLOGICAL('PartWeightLoadBalance','F')
IF (PerformPartWeightLB) THEN
LoadBalanceSample = 0 ! deactivate loadbalance sampling of elemtimes if balancing with partweight is enabled
Expand Down Expand Up @@ -404,7 +405,11 @@ SUBROUTINE LoadBalance()
SWRITE(UNIT_StdOut,'(132("="))')
nLoadBalanceSteps=nLoadBalanceSteps+1
CALL set_formatting("green")
SWRITE(UNIT_stdOut,'(A,I0,A,I0,A)',ADVANCE='NO') ' PERFORMING LOAD BALANCE ',nLoadBalanceSteps,' of ',LoadBalanceMaxSteps,' ...'
IF (LoadBalanceMaxSteps.LT.HUGE(1)) THEN
SWRITE(UNIT_stdOut,'(A,I0,A,I0,A)',ADVANCE='NO') ' PERFORMING LOAD BALANCE ',nLoadBalanceSteps,' of ',LoadBalanceMaxSteps,' ...'
ELSE
SWRITE(UNIT_stdOut,'(A,I0,A )',ADVANCE='NO') ' PERFORMING LOAD BALANCE ',nLoadBalanceSteps,' ...'
END IF
CALL clear_formatting()
SWRITE(UNIT_StdOut,'(1X)')
! Measure init duration
Expand Down
3 changes: 1 addition & 2 deletions src/mesh/prepare_mesh.f90
Original file line number Diff line number Diff line change
Expand Up @@ -630,9 +630,8 @@ SUBROUTINE setLocalSideIDs()
END DO
#endif /*USE_HDG*/

writePartitionInfo = GETLOGICAL('writePartitionInfo','.FALSE.')
writePartitionInfo = GETLOGICAL('writePartitionInfo')
IF(DoLoadBalance)THEN
writePartitionInfo=.TRUE.
WRITE( hilf,'(I4.4)') nLoadBalanceSteps
filename='partitionInfo-'//TRIM(hilf)//'.out'
ELSE
Expand Down
55 changes: 51 additions & 4 deletions src/readintools/readintools.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1215,12 +1215,13 @@ SUBROUTINE GetGeneralOption(value, name, proposal)
CLASS(link),POINTER :: current
CLASS(Option),POINTER :: opt
CHARACTER(LEN=255) :: proposal_loc
CHARACTER(LEN=20) :: fmtName
INTEGER :: ind,mode
CLASS(link),POINTER :: check
CLASS(Option),POINTER :: multi
CLASS(OPTION),ALLOCATABLE :: newopt
CHARACTER(LEN=:),ALLOCATABLE :: testname
INTEGER :: i,k
CHARACTER(LEN=20) :: fmtName
! Temporary arrays to create new options
CHARACTER(LEN=255) :: tmpValue
CLASS(LogicalOption),ALLOCATABLE,TARGET :: logicalopt
Expand Down Expand Up @@ -1269,11 +1270,31 @@ SUBROUTINE GetGeneralOption(value, name, proposal)
CLASS IS (StringOption)
SELECT TYPE(value)
TYPE IS (STR255)
! If the string contains a comma, strip it and provide the first part of this string. This might occur when directly running a regressioncheck file
ind = INDEX(opt%value,",")
IF (ind.GT.0) THEN
opt%value = opt%value(1:ind-1)
! Print option and value to stdout. Custom print, so do it here
WRITE(fmtName,*) prms%maxNameLen
SWRITE(UNIT_stdOut,'(A3)', ADVANCE='NO') " | "
CALL set_formatting("blue")
SWRITE(UNIT_stdOut,"(A"//fmtName//")", ADVANCE='NO') TRIM(name)
CALL clear_formatting()
SWRITE(UNIT_stdOut,'(A3)', ADVANCE='NO') " | "
CALL opt%printValue(prms%maxValueLen)
SWRITE(UNIT_stdOut,"(A3)", ADVANCE='NO') ' | '
CALL set_formatting("cyan")
SWRITE(UNIT_stdOut,'(A7)', ADVANCE='NO') "*SPLIT"
CALL clear_formatting()
SWRITE(UNIT_stdOut,"(A3)") ' | '
! Set mode to indicate print already occured
mode = 1
END IF
value%chars = opt%value
END SELECT
END SELECT
! print option and value to stdout
CALL opt%print(prms%maxNameLen, prms%maxValueLen, mode=0)
IF (mode.EQ.0) CALL opt%print(prms%maxNameLen, prms%maxValueLen, mode=0)
! remove the option from the linked list of all parameters
IF(prms%removeAfterRead) current%opt%isRemoved = .TRUE.
RETURN
Expand Down Expand Up @@ -1818,6 +1839,7 @@ FUNCTION GETINTFROMSTR(name) result(value)
CHARACTER(LEN=:),ALLOCATABLE :: testname
INTEGER :: iChar,kChar
CHARACTER(LEN=20) :: fmtName
INTEGER :: ind
!==================================================================================================================================
! iterate over all options and compare names
current => prms%firstLink
Expand Down Expand Up @@ -1864,8 +1886,33 @@ FUNCTION GETINTFROMSTR(name) result(value)
RETURN
END IF
END DO
CALL Abort(__STAMP__,&
"Unknown value for option: "//TRIM(name))
! If a string contains a comma, check if the first part of this string exists in the list and set its integer representation
! according to the mapping. This might occur when directly running a regressioncheck file
DO i=1,listSize
ind = INDEX(opt%value,",")
IF (STRICMP(opt%strList(i), opt%value(1:ind-1))) THEN
value = opt%intList(i)
opt%listIndex = i ! Store index of the mapping
! print option and value to stdout. Custom print, so do it here
WRITE(fmtName,*) prms%maxNameLen
SWRITE(UNIT_stdOut,'(A3)', ADVANCE='NO') " | "
CALL set_formatting("blue")
SWRITE(UNIT_stdOut,"(A"//fmtName//")", ADVANCE='NO') TRIM(name)
CALL clear_formatting()
SWRITE(UNIT_stdOut,'(A3)', ADVANCE='NO') " | "
CALL opt%printValue(prms%maxValueLen)
SWRITE(UNIT_stdOut,"(A3)", ADVANCE='NO') ' | '
CALL set_formatting("cyan")
SWRITE(UNIT_stdOut,'(A7)', ADVANCE='NO') "*SPLIT"
CALL clear_formatting()
SWRITE(UNIT_stdOut,"(A3)") ' | '
! CALL opt%print(prms%maxNameLen, prms%maxValueLen, mode=0)
! remove the option from the linked list of all parameters
IF(prms%removeAfterRead) current%opt%isRemoved = .TRUE.
RETURN
END IF
END DO
CALL Abort(__STAMP__,"Unknown value for option: "//TRIM(name))
END SELECT
END IF
current => current%next
Expand Down

0 comments on commit d09a67e

Please sign in to comment.