white space adjustments

This commit is contained in:
Martin Diehl 2019-06-15 15:41:37 +02:00
parent 3de3ebdd43
commit 85e6885ea7
1 changed files with 166 additions and 166 deletions

View File

@ -6,70 +6,70 @@
!> @brief Reading in and interpretating the debugging settings for the various modules !> @brief Reading in and interpretating the debugging settings for the various modules
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module debug module debug
use prec use prec
use IO use IO
implicit none implicit none
private private
integer, parameter, public :: & integer, parameter, public :: &
debug_LEVELSELECTIVE = 2**0, & debug_LEVELSELECTIVE = 2**0, &
debug_LEVELBASIC = 2**1, & debug_LEVELBASIC = 2**1, &
debug_LEVELEXTENSIVE = 2**2 debug_LEVELEXTENSIVE = 2**2
integer, parameter, private :: & integer, parameter, private :: &
debug_MAXGENERAL = debug_LEVELEXTENSIVE ! must be set to the last bitcode used by (potentially) all debug types debug_MAXGENERAL = debug_LEVELEXTENSIVE ! must be set to the last bitcode used by (potentially) all debug types
integer, parameter, public :: & integer, parameter, public :: &
debug_SPECTRALRESTART = debug_MAXGENERAL*2**1, & debug_SPECTRALRESTART = debug_MAXGENERAL*2**1, &
debug_SPECTRALFFTW = debug_MAXGENERAL*2**2, & debug_SPECTRALFFTW = debug_MAXGENERAL*2**2, &
debug_SPECTRALDIVERGENCE = debug_MAXGENERAL*2**3, & debug_SPECTRALDIVERGENCE = debug_MAXGENERAL*2**3, &
debug_SPECTRALROTATION = debug_MAXGENERAL*2**4, & debug_SPECTRALROTATION = debug_MAXGENERAL*2**4, &
debug_SPECTRALPETSC = debug_MAXGENERAL*2**5 debug_SPECTRALPETSC = debug_MAXGENERAL*2**5
integer, parameter, public :: & integer, parameter, public :: &
debug_DEBUG = 1, & debug_DEBUG = 1, &
debug_MATH = 2, & debug_MATH = 2, &
debug_FESOLVING = 3, & debug_FESOLVING = 3, &
debug_MESH = 4, & !< stores debug level for mesh part of DAMASK bitwise coded debug_MESH = 4, & !< stores debug level for mesh part of DAMASK bitwise coded
debug_MATERIAL = 5, & !< stores debug level for material part of DAMASK bitwise coded debug_MATERIAL = 5, & !< stores debug level for material part of DAMASK bitwise coded
debug_LATTICE = 6, & !< stores debug level for lattice part of DAMASK bitwise coded debug_LATTICE = 6, & !< stores debug level for lattice part of DAMASK bitwise coded
debug_CONSTITUTIVE = 7, & !< stores debug level for constitutive part of DAMASK bitwise coded debug_CONSTITUTIVE = 7, & !< stores debug level for constitutive part of DAMASK bitwise coded
debug_CRYSTALLITE = 8, & debug_CRYSTALLITE = 8, &
debug_HOMOGENIZATION = 9, & debug_HOMOGENIZATION = 9, &
debug_CPFEM = 10, & debug_CPFEM = 10, &
debug_SPECTRAL = 11, & debug_SPECTRAL = 11, &
debug_MARC = 12, & debug_MARC = 12, &
debug_ABAQUS = 13 debug_ABAQUS = 13
integer, parameter, private :: & integer, parameter, private :: &
debug_MAXNTYPE = debug_ABAQUS !< must be set to the maximum defined debug type debug_MAXNTYPE = debug_ABAQUS !< must be set to the maximum defined debug type
integer,protected, dimension(debug_maxNtype+2), public :: & ! specific ones, and 2 for "all" and "other" integer,protected, dimension(debug_maxNtype+2), public :: & ! specific ones, and 2 for "all" and "other"
debug_level = 0 debug_level = 0
integer, protected, public :: & integer, protected, public :: &
debug_e = 1, & debug_e = 1, &
debug_i = 1, & debug_i = 1, &
debug_g = 1 debug_g = 1
integer, dimension(2), public :: & integer, dimension(2), public :: &
debug_stressMaxLocation = 0, & debug_stressMaxLocation = 0, &
debug_stressMinLocation = 0, & debug_stressMinLocation = 0, &
debug_jacobianMaxLocation = 0, & debug_jacobianMaxLocation = 0, &
debug_jacobianMinLocation = 0 debug_jacobianMinLocation = 0
real(pReal), public :: & real(pReal), public :: &
debug_stressMax = -huge(1.0_pReal), & debug_stressMax = -huge(1.0_pReal), &
debug_stressMin = huge(1.0_pReal), & debug_stressMin = huge(1.0_pReal), &
debug_jacobianMax = -huge(1.0_pReal), & debug_jacobianMax = -huge(1.0_pReal), &
debug_jacobianMin = huge(1.0_pReal) debug_jacobianMin = huge(1.0_pReal)
#ifdef PETSc #ifdef PETSc
character(len=1024), parameter, public :: & character(len=1024), parameter, public :: &
PETSCDEBUG = ' -snes_view -snes_monitor ' PETSCDEBUG = ' -snes_view -snes_monitor '
#endif #endif
public :: debug_init, & public :: debug_init, &
debug_reset, & debug_reset, &
debug_info debug_info
contains contains
@ -79,111 +79,111 @@ contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine debug_init subroutine debug_init
character(len=pStringLen), dimension(:), allocatable :: fileContent character(len=pStringLen), dimension(:), allocatable :: fileContent
integer :: i, what, j integer :: i, what, j
integer, allocatable, dimension(:) :: chunkPos integer, allocatable, dimension(:) :: chunkPos
character(len=pStringLen) :: tag, line character(len=pStringLen) :: tag, line
logical :: fexist logical :: fexist
write(6,'(/,a)') ' <<<+- debug init -+>>>' write(6,'(/,a)') ' <<<+- debug init -+>>>'
#ifdef DEBUG #ifdef DEBUG
write(6,'(a)') achar(27)//'[31m <<<+- DEBUG version -+>>>'//achar(27)//'[0m' write(6,'(a)') achar(27)//'[31m <<<+- DEBUG version -+>>>'//achar(27)//'[0m'
#endif #endif
inquire(file='debug.config', exist=fexist) inquire(file='debug.config', exist=fexist)
fileExists: if (fexist) then fileExists: if (fexist) then
fileContent = IO_read_ASCII('debug.config') fileContent = IO_read_ASCII('debug.config')
do j=1, size(fileContent) do j=1, size(fileContent)
line = fileContent(j) line = fileContent(j)
if (IO_isBlank(line)) cycle ! skip empty lines if (IO_isBlank(line)) cycle ! skip empty lines
chunkPos = IO_stringPos(line) chunkPos = IO_stringPos(line)
tag = IO_lc(IO_stringValue(line,chunkPos,1)) ! extract key tag = IO_lc(IO_stringValue(line,chunkPos,1)) ! extract key
select case(tag) select case(tag)
case ('element','e','el') case ('element','e','el')
debug_e = IO_intValue(line,chunkPos,2) debug_e = IO_intValue(line,chunkPos,2)
case ('integrationpoint','i','ip') case ('integrationpoint','i','ip')
debug_i = IO_intValue(line,chunkPos,2) debug_i = IO_intValue(line,chunkPos,2)
case ('grain','g','gr') case ('grain','g','gr')
debug_g = IO_intValue(line,chunkPos,2) debug_g = IO_intValue(line,chunkPos,2)
end select end select
what = 0 what = 0
select case(tag) select case(tag)
case ('debug') case ('debug')
what = debug_DEBUG what = debug_DEBUG
case ('math') case ('math')
what = debug_MATH what = debug_MATH
case ('fesolving', 'fe') case ('fesolving', 'fe')
what = debug_FESOLVING what = debug_FESOLVING
case ('mesh') case ('mesh')
what = debug_MESH what = debug_MESH
case ('material') case ('material')
what = debug_MATERIAL what = debug_MATERIAL
case ('lattice') case ('lattice')
what = debug_LATTICE what = debug_LATTICE
case ('constitutive') case ('constitutive')
what = debug_CONSTITUTIVE what = debug_CONSTITUTIVE
case ('crystallite') case ('crystallite')
what = debug_CRYSTALLITE what = debug_CRYSTALLITE
case ('homogenization') case ('homogenization')
what = debug_HOMOGENIZATION what = debug_HOMOGENIZATION
case ('cpfem') case ('cpfem')
what = debug_CPFEM what = debug_CPFEM
case ('spectral') case ('spectral')
what = debug_SPECTRAL what = debug_SPECTRAL
case ('marc') case ('marc')
what = debug_MARC what = debug_MARC
case ('abaqus') case ('abaqus')
what = debug_ABAQUS what = debug_ABAQUS
case ('all') case ('all')
what = debug_MAXNTYPE + 1 what = debug_MAXNTYPE + 1
case ('other') case ('other')
what = debug_MAXNTYPE + 2 what = debug_MAXNTYPE + 2
end select end select
if (what /= 0) then if (what /= 0) then
do i = 2, chunkPos(1) do i = 2, chunkPos(1)
select case(IO_lc(IO_stringValue(line,chunkPos,i))) select case(IO_lc(IO_stringValue(line,chunkPos,i)))
case('basic') case('basic')
debug_level(what) = ior(debug_level(what), debug_LEVELBASIC) debug_level(what) = ior(debug_level(what), debug_LEVELBASIC)
case('extensive') case('extensive')
debug_level(what) = ior(debug_level(what), debug_LEVELEXTENSIVE) debug_level(what) = ior(debug_level(what), debug_LEVELEXTENSIVE)
case('selective') case('selective')
debug_level(what) = ior(debug_level(what), debug_LEVELSELECTIVE) debug_level(what) = ior(debug_level(what), debug_LEVELSELECTIVE)
case('restart') case('restart')
debug_level(what) = ior(debug_level(what), debug_SPECTRALRESTART) debug_level(what) = ior(debug_level(what), debug_SPECTRALRESTART)
case('fft','fftw') case('fft','fftw')
debug_level(what) = ior(debug_level(what), debug_SPECTRALFFTW) debug_level(what) = ior(debug_level(what), debug_SPECTRALFFTW)
case('divergence') case('divergence')
debug_level(what) = ior(debug_level(what), debug_SPECTRALDIVERGENCE) debug_level(what) = ior(debug_level(what), debug_SPECTRALDIVERGENCE)
case('rotation') case('rotation')
debug_level(what) = ior(debug_level(what), debug_SPECTRALROTATION) debug_level(what) = ior(debug_level(what), debug_SPECTRALROTATION)
case('petsc') case('petsc')
debug_level(what) = ior(debug_level(what), debug_SPECTRALPETSC) debug_level(what) = ior(debug_level(what), debug_SPECTRALPETSC)
end select end select
enddo enddo
endif endif
enddo enddo
do i = 1, debug_maxNtype do i = 1, debug_maxNtype
if (debug_level(i) == 0) & if (debug_level(i) == 0) &
debug_level(i) = ior(debug_level(i), debug_level(debug_MAXNTYPE + 2)) ! fill undefined debug types with levels specified by "other" debug_level(i) = ior(debug_level(i), debug_level(debug_MAXNTYPE + 2)) ! fill undefined debug types with levels specified by "other"
debug_level(i) = ior(debug_level(i), debug_level(debug_MAXNTYPE + 1)) ! fill all debug types with levels specified by "all" debug_level(i) = ior(debug_level(i), debug_level(debug_MAXNTYPE + 1)) ! fill all debug types with levels specified by "all"
enddo enddo
if (iand(debug_level(debug_debug),debug_LEVELBASIC) /= 0) & if (iand(debug_level(debug_debug),debug_LEVELBASIC) /= 0) &
write(6,'(a,/)') ' using values from config file' write(6,'(a,/)') ' using values from config file'
else fileExists else fileExists
if (iand(debug_level(debug_debug),debug_LEVELBASIC) /= 0) & if (iand(debug_level(debug_debug),debug_LEVELBASIC) /= 0) &
write(6,'(a,/)') ' using standard values' write(6,'(a,/)') ' using standard values'
endif fileExists endif fileExists
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! output switched on (debug level for debug must be extensive) ! output switched on (debug level for debug must be extensive)
if (iand(debug_level(debug_debug),debug_LEVELEXTENSIVE) /= 0) then if (iand(debug_level(debug_debug),debug_LEVELEXTENSIVE) /= 0) then
do i = 1, debug_MAXNTYPE do i = 1, debug_MAXNTYPE
select case(i) select case(i)
case (debug_DEBUG) case (debug_DEBUG)
@ -231,7 +231,7 @@ subroutine debug_init
if(iand(debug_level(i),debug_SPECTRALPETSC) /= 0) write(6,'(a)') ' PETSc' if(iand(debug_level(i),debug_SPECTRALPETSC) /= 0) write(6,'(a)') ' PETSc'
endif endif
enddo enddo
endif endif
end subroutine debug_init end subroutine debug_init
@ -241,14 +241,14 @@ end subroutine debug_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine debug_reset subroutine debug_reset
debug_stressMaxLocation = 0 debug_stressMaxLocation = 0
debug_stressMinLocation = 0 debug_stressMinLocation = 0
debug_jacobianMaxLocation = 0 debug_jacobianMaxLocation = 0
debug_jacobianMinLocation = 0 debug_jacobianMinLocation = 0
debug_stressMax = -huge(1.0_pReal) debug_stressMax = -huge(1.0_pReal)
debug_stressMin = huge(1.0_pReal) debug_stressMin = huge(1.0_pReal)
debug_jacobianMax = -huge(1.0_pReal) debug_jacobianMax = -huge(1.0_pReal)
debug_jacobianMin = huge(1.0_pReal) debug_jacobianMin = huge(1.0_pReal)
end subroutine debug_reset end subroutine debug_reset
@ -258,18 +258,18 @@ end subroutine debug_reset
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine debug_info subroutine debug_info
!$OMP CRITICAL (write2out) !$OMP CRITICAL (write2out)
debugOutputCPFEM: if (iand(debug_level(debug_CPFEM),debug_LEVELBASIC) /= 0 & debugOutputCPFEM: if (iand(debug_level(debug_CPFEM),debug_LEVELBASIC) /= 0 &
.and. any(debug_stressMinLocation /= 0) & .and. any(debug_stressMinLocation /= 0) &
.and. any(debug_stressMaxLocation /= 0) ) then .and. any(debug_stressMaxLocation /= 0) ) then
write(6,'(2/,a,/)') ' Extreme values of returned stress and Jacobian' write(6,'(2/,a,/)') ' Extreme values of returned stress and Jacobian'
write(6,'(a39)') ' value el ip' write(6,'(a39)') ' value el ip'
write(6,'(a14,1x,e12.3,1x,i8,1x,i4)') ' stress min :', debug_stressMin, debug_stressMinLocation write(6,'(a14,1x,e12.3,1x,i8,1x,i4)') ' stress min :', debug_stressMin, debug_stressMinLocation
write(6,'(a14,1x,e12.3,1x,i8,1x,i4)') ' max :', debug_stressMax, debug_stressMaxLocation write(6,'(a14,1x,e12.3,1x,i8,1x,i4)') ' max :', debug_stressMax, debug_stressMaxLocation
write(6,'(a14,1x,e12.3,1x,i8,1x,i4)') ' Jacobian min :', debug_jacobianMin, debug_jacobianMinLocation write(6,'(a14,1x,e12.3,1x,i8,1x,i4)') ' Jacobian min :', debug_jacobianMin, debug_jacobianMinLocation
write(6,'(a14,1x,e12.3,1x,i8,1x,i4,/)') ' max :', debug_jacobianMax, debug_jacobianMaxLocation write(6,'(a14,1x,e12.3,1x,i8,1x,i4,/)') ' max :', debug_jacobianMax, debug_jacobianMaxLocation
endif debugOutputCPFEM endif debugOutputCPFEM
!$OMP END CRITICAL (write2out) !$OMP END CRITICAL (write2out)
end subroutine debug_info end subroutine debug_info