2011-04-07 12:50:28 +05:30
|
|
|
! Copyright 2011 Max-Planck-Institut für Eisenforschung GmbH
|
2011-04-04 19:39:54 +05:30
|
|
|
!
|
|
|
|
! This file is part of DAMASK,
|
2011-04-07 12:50:28 +05:30
|
|
|
! the Düsseldorf Advanced MAterial Simulation Kit.
|
2011-04-04 19:39:54 +05:30
|
|
|
!
|
|
|
|
! DAMASK is free software: you can redistribute it and/or modify
|
|
|
|
! it under the terms of the GNU General Public License as published by
|
|
|
|
! the Free Software Foundation, either version 3 of the License, or
|
|
|
|
! (at your option) any later version.
|
|
|
|
!
|
|
|
|
! DAMASK is distributed in the hope that it will be useful,
|
|
|
|
! but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
! GNU General Public License for more details.
|
|
|
|
!
|
|
|
|
! You should have received a copy of the GNU General Public License
|
|
|
|
! along with DAMASK. If not, see <http://www.gnu.org/licenses/>.
|
|
|
|
!
|
|
|
|
!##############################################################
|
2009-08-31 20:39:15 +05:30
|
|
|
!* $Id$
|
2008-01-11 00:23:57 +05:30
|
|
|
!##############################################################
|
2011-03-17 18:43:13 +05:30
|
|
|
MODULE debug
|
2008-01-11 00:23:57 +05:30
|
|
|
!##############################################################
|
2011-03-17 18:43:13 +05:30
|
|
|
use prec
|
2008-01-11 00:23:57 +05:30
|
|
|
|
2011-03-17 18:43:13 +05:30
|
|
|
implicit none
|
|
|
|
character(len=64), parameter :: debug_configFile = 'debug.config' ! name of configuration file
|
2012-01-12 15:53:05 +05:30
|
|
|
integer(pInt), parameter :: debug_spectralGeneral = 1_pInt, &
|
|
|
|
debug_spectralDivergence = 2_pInt, &
|
2012-01-13 20:51:24 +05:30
|
|
|
debug_spectralRestart = 4_pInt, &
|
|
|
|
debug_spectralFFTW = 8_pInt
|
2010-09-23 13:31:41 +05:30
|
|
|
|
2011-03-17 18:43:13 +05:30
|
|
|
integer(pInt), dimension(:,:), allocatable :: debug_StressLoopDistribution
|
|
|
|
integer(pInt), dimension(:,:), allocatable :: debug_LeapfrogBreakDistribution
|
|
|
|
integer(pInt), dimension(:,:), allocatable :: debug_StateLoopDistribution
|
|
|
|
integer(pInt), dimension(:), allocatable :: debug_CrystalliteLoopDistribution
|
|
|
|
integer(pInt), dimension(:), allocatable :: debug_MaterialpointStateLoopDistribution
|
|
|
|
integer(pInt), dimension(:), allocatable :: debug_MaterialpointLoopDistribution
|
2012-02-10 16:54:53 +05:30
|
|
|
integer(pLongInt) :: debug_cumLpTicks = 0_pLongInt
|
|
|
|
integer(pLongInt) :: debug_cumDotStateTicks = 0_pLongInt
|
|
|
|
integer(pLongInt) :: debug_cumDotTemperatureTicks = 0_pLongInt
|
2011-03-17 18:43:13 +05:30
|
|
|
integer(pInt) :: debug_cumLpCalls = 0_pInt
|
|
|
|
integer(pInt) :: debug_cumDotStateCalls = 0_pInt
|
|
|
|
integer(pInt) :: debug_cumDotTemperatureCalls = 0_pInt
|
|
|
|
integer(pInt) :: debug_e = 1_pInt
|
|
|
|
integer(pInt) :: debug_i = 1_pInt
|
|
|
|
integer(pInt) :: debug_g = 1_pInt
|
|
|
|
integer(pInt), dimension(2) :: debug_stressMaxLocation = 0_pInt
|
|
|
|
integer(pInt), dimension(2) :: debug_stressMinLocation = 0_pInt
|
|
|
|
integer(pInt), dimension(2) :: debug_jacobianMaxLocation = 0_pInt
|
|
|
|
integer(pInt), dimension(2) :: debug_jacobianMinLocation = 0_pInt
|
|
|
|
real(pReal) :: debug_stressMax
|
|
|
|
real(pReal) :: debug_stressMin
|
|
|
|
real(pReal) :: debug_jacobianMax
|
|
|
|
real(pReal) :: debug_jacobianMin
|
2011-03-21 16:01:17 +05:30
|
|
|
logical :: debug_selectiveDebugger = .true.
|
|
|
|
integer(pInt) :: debug_verbosity = 1_pInt
|
2012-01-12 15:53:05 +05:30
|
|
|
integer(pInt) :: debug_spectral = 0_pInt
|
2008-02-19 18:28:46 +05:30
|
|
|
|
2011-03-17 18:43:13 +05:30
|
|
|
CONTAINS
|
2008-02-19 18:28:46 +05:30
|
|
|
|
2009-10-22 14:44:17 +05:30
|
|
|
|
|
|
|
!********************************************************************
|
|
|
|
! initialize the debugging capabilities
|
|
|
|
!********************************************************************
|
2009-06-15 18:41:21 +05:30
|
|
|
subroutine debug_init()
|
|
|
|
|
2012-02-13 19:38:07 +05:30
|
|
|
use, intrinsic :: iso_fortran_env ! to get compiler_version and compiler_options (at least for gfortran 4.6 at the moment)
|
2009-06-15 18:41:21 +05:30
|
|
|
use prec, only: pInt
|
|
|
|
use numerics, only: nStress, &
|
|
|
|
nState, &
|
2009-07-31 17:32:20 +05:30
|
|
|
nCryst, &
|
2009-08-11 22:01:57 +05:30
|
|
|
nMPstate, &
|
|
|
|
nHomog
|
2010-09-23 14:43:46 +05:30
|
|
|
use IO, only: IO_error, &
|
2012-02-13 23:11:27 +05:30
|
|
|
IO_open_file_stat, &
|
2010-09-23 14:43:46 +05:30
|
|
|
IO_isBlank, &
|
|
|
|
IO_stringPos, &
|
|
|
|
IO_stringValue, &
|
|
|
|
IO_lc, &
|
|
|
|
IO_floatValue, &
|
|
|
|
IO_intValue
|
2009-06-15 18:41:21 +05:30
|
|
|
implicit none
|
2009-06-18 19:58:02 +05:30
|
|
|
|
2010-09-23 14:43:46 +05:30
|
|
|
!*** input variables ***!
|
|
|
|
|
|
|
|
!*** output variables ***!
|
|
|
|
|
|
|
|
!*** local variables ***!
|
|
|
|
integer(pInt), parameter :: fileunit = 300
|
|
|
|
integer(pInt), parameter :: maxNchunks = 2
|
|
|
|
integer(pInt), dimension(1+2*maxNchunks) :: positions
|
|
|
|
character(len=64) tag
|
|
|
|
character(len=1024) line
|
2011-03-21 16:01:17 +05:30
|
|
|
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!$OMP CRITICAL (write2out)
|
|
|
|
write(6,*)
|
|
|
|
write(6,*) '<<<+- debug init -+>>>'
|
|
|
|
write(6,*) '$Id$'
|
2012-02-01 00:48:55 +05:30
|
|
|
#include "compilation_info.f90"
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!$OMP END CRITICAL (write2out)
|
2010-09-23 13:31:41 +05:30
|
|
|
|
2010-09-06 21:36:41 +05:30
|
|
|
allocate(debug_StressLoopDistribution(nStress,2)) ; debug_StressLoopDistribution = 0_pInt
|
2010-09-30 13:01:53 +05:30
|
|
|
allocate(debug_LeapfrogBreakDistribution(nStress,2)) ; debug_LeapfrogBreakDistribution = 0_pInt
|
2010-10-01 17:48:49 +05:30
|
|
|
allocate(debug_StateLoopDistribution(nState,2)) ; debug_StateLoopDistribution = 0_pInt
|
2010-09-02 02:34:02 +05:30
|
|
|
allocate(debug_CrystalliteLoopDistribution(nCryst+1)) ; debug_CrystalliteLoopDistribution = 0_pInt
|
2009-08-11 22:01:57 +05:30
|
|
|
allocate(debug_MaterialpointStateLoopDistribution(nMPstate)) ; debug_MaterialpointStateLoopDistribution = 0_pInt
|
2010-09-02 02:34:02 +05:30
|
|
|
allocate(debug_MaterialpointLoopDistribution(nHomog+1)) ; debug_MaterialpointLoopDistribution = 0_pInt
|
2010-09-23 13:31:41 +05:30
|
|
|
|
|
|
|
! try to open the config file
|
2012-02-13 23:11:27 +05:30
|
|
|
if(IO_open_file_stat(fileunit,debug_configFile)) then
|
2010-09-23 13:31:41 +05:30
|
|
|
|
|
|
|
line = ''
|
|
|
|
! read variables from config file and overwrite parameters
|
|
|
|
do
|
|
|
|
read(fileunit,'(a1024)',END=100) line
|
|
|
|
if (IO_isBlank(line)) cycle ! skip empty lines
|
|
|
|
positions = IO_stringPos(line,maxNchunks)
|
2012-02-10 16:54:53 +05:30
|
|
|
tag = IO_lc(IO_stringValue(line,positions,1_pInt)) ! extract key
|
2010-09-23 13:31:41 +05:30
|
|
|
select case(tag)
|
|
|
|
case ('element','e','el')
|
2012-02-10 16:54:53 +05:30
|
|
|
debug_e = IO_intValue(line,positions,2_pInt)
|
2011-12-06 22:28:17 +05:30
|
|
|
case ('integrationpoint','i','ip')
|
2012-02-10 16:54:53 +05:30
|
|
|
debug_i = IO_intValue(line,positions,2_pInt)
|
2010-09-23 13:31:41 +05:30
|
|
|
case ('grain','g','gr')
|
2012-02-10 16:54:53 +05:30
|
|
|
debug_g = IO_intValue(line,positions,2_pInt)
|
2010-09-23 13:31:41 +05:30
|
|
|
case ('selective')
|
2012-02-10 16:54:53 +05:30
|
|
|
debug_selectiveDebugger = IO_intValue(line,positions,2_pInt) > 0_pInt
|
2011-03-21 16:01:17 +05:30
|
|
|
case ('verbosity')
|
2012-02-10 16:54:53 +05:30
|
|
|
debug_verbosity = IO_intValue(line,positions,2_pInt)
|
2011-12-06 22:28:17 +05:30
|
|
|
case ('(spectral)')
|
2012-02-10 16:54:53 +05:30
|
|
|
select case(IO_lc(IO_stringValue(line,positions,2_pInt)))
|
2011-12-06 22:28:17 +05:30
|
|
|
case('general')
|
2012-01-12 15:53:05 +05:30
|
|
|
debug_spectral = ior(debug_spectral, debug_spectralGeneral)
|
2011-12-06 22:28:17 +05:30
|
|
|
case('divergence')
|
2012-01-12 15:53:05 +05:30
|
|
|
debug_spectral = ior(debug_spectral, debug_spectralDivergence)
|
2011-12-06 22:28:17 +05:30
|
|
|
case('restart')
|
2012-01-12 15:53:05 +05:30
|
|
|
debug_spectral = ior(debug_spectral, debug_spectralRestart)
|
2012-02-10 16:54:53 +05:30
|
|
|
case('fftw', 'fft')
|
2012-01-13 20:51:24 +05:30
|
|
|
debug_spectral = ior(debug_spectral, debug_spectralFFTW)
|
2011-12-06 22:28:17 +05:30
|
|
|
endselect
|
2010-09-23 13:31:41 +05:30
|
|
|
endselect
|
|
|
|
enddo
|
|
|
|
100 close(fileunit)
|
2011-03-21 16:01:17 +05:30
|
|
|
|
|
|
|
if (debug_verbosity > 0) then
|
|
|
|
!$OMP CRITICAL (write2out)
|
|
|
|
write(6,*) ' ... using values from config file'
|
|
|
|
write(6,*)
|
|
|
|
!$OMP END CRITICAL (write2out)
|
|
|
|
endif
|
|
|
|
|
2010-09-23 13:31:41 +05:30
|
|
|
! no config file, so we use standard values
|
|
|
|
else
|
2010-09-23 14:43:46 +05:30
|
|
|
|
2011-03-21 16:01:17 +05:30
|
|
|
if (debug_verbosity > 0) then
|
|
|
|
!$OMP CRITICAL (write2out)
|
|
|
|
write(6,*) ' ... using standard values'
|
|
|
|
write(6,*)
|
|
|
|
!$OMP END CRITICAL (write2out)
|
|
|
|
endif
|
|
|
|
|
2010-09-23 14:43:46 +05:30
|
|
|
endif
|
|
|
|
|
2011-03-21 16:01:17 +05:30
|
|
|
if (debug_verbosity > 0) then
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!$OMP CRITICAL (write2out)
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(a24,1x,i1)') 'verbose: ',debug_verbosity
|
|
|
|
write(6,'(a24,1x,l1)') 'selective: ',debug_selectiveDebugger
|
openmp parallelization working again (at least for j2 and nonlocal constitutive model).
In order to keep it like that, please follow these simple rules:
DON'T use implicit array subscripts:
example: real, dimension(3,3) :: A,B
A(:,2) = B(:,1) <--- DON'T USE
A(1:3,2) = B(1:3,1) <--- BETTER USE
In many cases the use of explicit array subscripts is inevitable for parallelization. Additionally, it is an easy means to prevent memory leaks.
Enclose all write statements with the following:
!$OMP CRITICAL (write2out)
<your write statement>
!$OMP END CRITICAL (write2out)
Whenever you change something in the code and are not sure if it affects parallelization and leads to nonconforming behavior, please ask me and/or Franz to check this.
2011-03-17 16:16:17 +05:30
|
|
|
!$OMP END CRITICAL (write2out)
|
2011-03-21 16:01:17 +05:30
|
|
|
endif
|
|
|
|
if (debug_selectiveDebugger) then
|
|
|
|
if (debug_verbosity > 0) then
|
|
|
|
!$OMP CRITICAL (write2out)
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(a24,1x,i8)') 'element: ',debug_e
|
|
|
|
write(6,'(a24,1x,i8)') 'ip: ',debug_i
|
|
|
|
write(6,'(a24,1x,i8)') 'grain: ',debug_g
|
2011-03-21 16:01:17 +05:30
|
|
|
!$OMP END CRITICAL (write2out)
|
|
|
|
endif
|
2010-09-30 13:01:53 +05:30
|
|
|
else
|
|
|
|
debug_e = 0_pInt ! switch off selective debugging
|
|
|
|
debug_i = 0_pInt
|
|
|
|
debug_g = 0_pInt
|
2010-09-23 13:31:41 +05:30
|
|
|
endif
|
2011-11-15 23:24:18 +05:30
|
|
|
!$OMP CRITICAL (write2out) ! bitwise coded
|
2012-01-12 15:53:05 +05:30
|
|
|
if (iand(debug_spectral,debug_spectralGeneral) > 0_pInt) write(6,'(a)') ' spectral general debugging'
|
|
|
|
if (iand(debug_spectral,debug_spectralDivergence) > 0_pInt) write(6,'(a)') ' spectral divergence debugging'
|
2012-01-12 20:38:44 +05:30
|
|
|
if (iand(debug_spectral,debug_spectralRestart) > 0_pInt) write(6,'(a)') ' spectral restart debugging'
|
2012-01-13 20:51:24 +05:30
|
|
|
if (iand(debug_spectral,debug_spectralFFTW) > 0_pInt) write(6,'(a)') ' spectral FFTW debugging'
|
2011-11-15 23:24:18 +05:30
|
|
|
!$OMP END CRITICAL (write2out)
|
2010-09-23 13:31:41 +05:30
|
|
|
|
2009-06-15 18:41:21 +05:30
|
|
|
endsubroutine
|
|
|
|
|
2009-05-07 21:57:36 +05:30
|
|
|
!********************************************************************
|
|
|
|
! reset debug distributions
|
|
|
|
!********************************************************************
|
2009-06-15 18:41:21 +05:30
|
|
|
subroutine debug_reset()
|
2009-05-07 21:57:36 +05:30
|
|
|
|
2009-06-15 18:41:21 +05:30
|
|
|
use prec
|
|
|
|
implicit none
|
2009-05-07 21:57:36 +05:30
|
|
|
|
2009-08-11 22:01:57 +05:30
|
|
|
debug_StressLoopDistribution = 0_pInt ! initialize debugging data
|
2010-09-30 13:01:53 +05:30
|
|
|
debug_LeapfrogBreakDistribution = 0_pInt
|
2010-10-01 17:48:49 +05:30
|
|
|
debug_StateLoopDistribution = 0_pInt
|
2009-08-11 22:01:57 +05:30
|
|
|
debug_CrystalliteLoopDistribution = 0_pInt
|
|
|
|
debug_MaterialpointStateLoopDistribution = 0_pInt
|
|
|
|
debug_MaterialpointLoopDistribution = 0_pInt
|
2012-02-10 16:54:53 +05:30
|
|
|
debug_cumLpTicks = 0_pLongInt
|
|
|
|
debug_cumDotStateTicks = 0_pLongInt
|
|
|
|
debug_cumDotTemperatureTicks = 0_pLongInt
|
2009-10-22 14:44:17 +05:30
|
|
|
debug_cumLpCalls = 0_pInt
|
|
|
|
debug_cumDotStateCalls = 0_pInt
|
2009-07-01 15:59:35 +05:30
|
|
|
debug_cumDotTemperatureCalls = 0_pInt
|
2011-03-17 18:43:13 +05:30
|
|
|
debug_stressMaxLocation = 0_pInt
|
|
|
|
debug_stressMinLocation = 0_pInt
|
|
|
|
debug_jacobianMaxLocation = 0_pInt
|
|
|
|
debug_jacobianMinLocation = 0_pInt
|
2011-03-24 13:08:56 +05:30
|
|
|
debug_stressMax = -huge(1.0_pReal)
|
|
|
|
debug_stressMin = huge(1.0_pReal)
|
|
|
|
debug_jacobianMax = -huge(1.0_pReal)
|
|
|
|
debug_jacobianMin = huge(1.0_pReal)
|
2011-03-17 18:43:13 +05:30
|
|
|
|
2009-05-07 21:57:36 +05:30
|
|
|
|
2009-06-15 18:41:21 +05:30
|
|
|
endsubroutine
|
2008-02-19 18:28:46 +05:30
|
|
|
|
|
|
|
!********************************************************************
|
|
|
|
! write debug statements to standard out
|
|
|
|
!********************************************************************
|
2011-03-17 18:43:13 +05:30
|
|
|
subroutine debug_info()
|
2008-02-19 18:28:46 +05:30
|
|
|
|
2011-03-17 18:43:13 +05:30
|
|
|
use prec
|
|
|
|
use numerics, only: nStress, &
|
|
|
|
nState, &
|
|
|
|
nCryst, &
|
|
|
|
nMPstate, &
|
|
|
|
nHomog
|
|
|
|
implicit none
|
2009-05-07 21:57:36 +05:30
|
|
|
|
2011-03-17 18:43:13 +05:30
|
|
|
integer(pInt) i,integral
|
|
|
|
integer(pLongInt) tickrate
|
2008-02-19 18:28:46 +05:30
|
|
|
|
2011-03-17 18:43:13 +05:30
|
|
|
call system_clock(count_rate=tickrate)
|
2009-05-07 21:57:36 +05:30
|
|
|
|
2011-06-06 20:57:35 +05:30
|
|
|
if (debug_verbosity > 4) then
|
2011-03-21 16:01:17 +05:30
|
|
|
!$OMP CRITICAL (write2out)
|
2011-03-17 18:43:13 +05:30
|
|
|
|
2011-03-21 16:01:17 +05:30
|
|
|
write(6,*)
|
|
|
|
write(6,*) 'DEBUG Info (from previous cycle)'
|
|
|
|
write(6,*)
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(a33,1x,i12)') 'total calls to LpAndItsTangent :',debug_cumLpCalls
|
2011-03-21 16:01:17 +05:30
|
|
|
if (debug_cumLpCalls > 0_pInt) then
|
2012-02-10 16:54:53 +05:30
|
|
|
write(6,'(a33,1x,f12.3)') 'total CPU time/s :',real(debug_cumLpTicks,pReal)&
|
|
|
|
/real(tickrate,pReal)
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(a33,1x,f12.6)') 'avg CPU time/microsecs per call :',&
|
2012-02-10 16:54:53 +05:30
|
|
|
real(debug_cumLpTicks,pReal)*1.0e6_pReal/real(tickrate,pReal)/real(debug_cumLpCalls,pReal)
|
2011-03-17 18:43:13 +05:30
|
|
|
endif
|
2011-03-21 16:01:17 +05:30
|
|
|
write(6,*)
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(a33,1x,i12)') 'total calls to collectDotState :',debug_cumDotStateCalls
|
2011-03-21 16:01:17 +05:30
|
|
|
if (debug_cumdotStateCalls > 0_pInt) then
|
2012-02-10 16:54:53 +05:30
|
|
|
write(6,'(a33,1x,f12.3)') 'total CPU time/s :',real(debug_cumDotStateTicks,pReal)&
|
|
|
|
/real(tickrate,pReal)
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(a33,1x,f12.6)') 'avg CPU time/microsecs per call :',&
|
2012-02-10 16:54:53 +05:30
|
|
|
real(debug_cumDotStateTicks,pReal)*1.0e6_pReal/real(tickrate,pReal)&
|
|
|
|
/real(debug_cumDotStateCalls,pReal)
|
2011-03-17 18:43:13 +05:30
|
|
|
endif
|
2011-03-21 16:01:17 +05:30
|
|
|
write(6,*)
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(a33,1x,i12)') 'total calls to dotTemperature :',debug_cumDotTemperatureCalls
|
2011-03-21 16:01:17 +05:30
|
|
|
if (debug_cumdotTemperatureCalls > 0_pInt) then
|
2012-02-10 16:54:53 +05:30
|
|
|
write(6,'(a33,1x,f12.3)') 'total CPU time/s :',real(debug_cumDotTemperatureTicks,pReal)&
|
|
|
|
/real(tickrate,pReal)
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(a33,1x,f12.6)') 'avg CPU time/microsecs per call :',&
|
2012-02-10 16:54:53 +05:30
|
|
|
real(debug_cumDotTemperatureTicks,pReal)*1.0e6_pReal/real(tickrate,pReal)&
|
|
|
|
/real(debug_cumDotTemperatureCalls,pReal)
|
2011-03-17 18:43:13 +05:30
|
|
|
endif
|
|
|
|
|
2011-03-21 16:01:17 +05:30
|
|
|
integral = 0_pInt
|
|
|
|
write(6,*)
|
|
|
|
write(6,*)
|
|
|
|
write(6,*) 'distribution_StressLoop : stress frogbreak stiffness frogbreak'
|
|
|
|
do i=1,nStress
|
|
|
|
if (any(debug_StressLoopDistribution(i,:) /= 0_pInt ) .or. &
|
|
|
|
any(debug_LeapfrogBreakDistribution(i,:) /= 0_pInt ) ) then
|
|
|
|
integral = integral + i*debug_StressLoopDistribution(i,1) + i*debug_StressLoopDistribution(i,2)
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(i25,1x,i10,1x,i10,1x,i10,1x,i10)') i,debug_StressLoopDistribution(i,1),debug_LeapfrogBreakDistribution(i,1), &
|
2011-03-21 16:01:17 +05:30
|
|
|
debug_StressLoopDistribution(i,2),debug_LeapfrogBreakDistribution(i,2)
|
2011-03-17 18:43:13 +05:30
|
|
|
endif
|
2011-03-21 16:01:17 +05:30
|
|
|
enddo
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(a15,i10,1x,i10,12x,i10)') ' total',integral,&
|
2011-03-21 16:01:17 +05:30
|
|
|
sum(debug_StressLoopDistribution(:,1)), &
|
|
|
|
sum(debug_StressLoopDistribution(:,2))
|
|
|
|
|
|
|
|
integral = 0_pInt
|
|
|
|
write(6,*)
|
|
|
|
write(6,*) 'distribution_CrystalliteStateLoop :'
|
|
|
|
do i=1,nState
|
|
|
|
if (any(debug_StateLoopDistribution(i,:) /= 0)) then
|
|
|
|
integral = integral + i*debug_StateLoopDistribution(i,1) + i*debug_StateLoopDistribution(i,2)
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(i25,1x,i10,12x,i10)') i,debug_StateLoopDistribution(i,1),debug_StateLoopDistribution(i,2)
|
2011-03-21 16:01:17 +05:30
|
|
|
endif
|
|
|
|
enddo
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(a15,i10,1x,i10,12x,i10)') ' total',integral,&
|
2011-03-21 16:01:17 +05:30
|
|
|
sum(debug_StateLoopDistribution(:,1)), &
|
|
|
|
sum(debug_StateLoopDistribution(:,2))
|
|
|
|
|
|
|
|
integral = 0_pInt
|
|
|
|
write(6,*)
|
|
|
|
write(6,*) 'distribution_CrystalliteCutbackLoop :'
|
|
|
|
do i=1,nCryst+1
|
|
|
|
if (debug_CrystalliteLoopDistribution(i) /= 0) then
|
|
|
|
integral = integral + i*debug_CrystalliteLoopDistribution(i)
|
|
|
|
if (i <= nCryst) then
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(i25,1x,i10)') i,debug_CrystalliteLoopDistribution(i)
|
2011-03-21 16:01:17 +05:30
|
|
|
else
|
|
|
|
write(6,'(i25,a1,i10)') i-1,'+',debug_CrystalliteLoopDistribution(i)
|
|
|
|
endif
|
|
|
|
endif
|
|
|
|
enddo
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(a15,i10,1x,i10)') ' total',integral,sum(debug_CrystalliteLoopDistribution)
|
2011-06-06 20:57:35 +05:30
|
|
|
|
|
|
|
!$OMP END CRITICAL (write2out)
|
|
|
|
endif
|
2011-03-21 16:01:17 +05:30
|
|
|
|
2011-06-06 20:57:35 +05:30
|
|
|
if (debug_verbosity > 2) then
|
|
|
|
!$OMP CRITICAL (write2out)
|
|
|
|
|
2011-03-21 16:01:17 +05:30
|
|
|
integral = 0_pInt
|
|
|
|
write(6,*)
|
|
|
|
write(6,*) 'distribution_MaterialpointStateLoop :'
|
|
|
|
do i=1,nMPstate
|
|
|
|
if (debug_MaterialpointStateLoopDistribution(i) /= 0) then
|
|
|
|
integral = integral + i*debug_MaterialpointStateLoopDistribution(i)
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(i25,1x,i10)') i,debug_MaterialpointStateLoopDistribution(i)
|
2011-03-21 16:01:17 +05:30
|
|
|
endif
|
|
|
|
enddo
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(a15,i10,1x,i10)') ' total',integral,sum(debug_MaterialpointStateLoopDistribution)
|
2011-03-21 16:01:17 +05:30
|
|
|
|
|
|
|
integral = 0_pInt
|
|
|
|
write(6,*)
|
|
|
|
write(6,*) 'distribution_MaterialpointCutbackLoop :'
|
|
|
|
do i=1,nHomog+1
|
|
|
|
if (debug_MaterialpointLoopDistribution(i) /= 0) then
|
|
|
|
integral = integral + i*debug_MaterialpointLoopDistribution(i)
|
|
|
|
if (i <= nHomog) then
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(i25,1x,i10)') i,debug_MaterialpointLoopDistribution(i)
|
2011-03-21 16:01:17 +05:30
|
|
|
else
|
|
|
|
write(6,'(i25,a1,i10)') i-1,'+',debug_MaterialpointLoopDistribution(i)
|
|
|
|
endif
|
|
|
|
endif
|
|
|
|
enddo
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(a15,i10,1x,i10)') ' total',integral,sum(debug_MaterialpointLoopDistribution)
|
2011-03-21 16:01:17 +05:30
|
|
|
|
|
|
|
write(6,*)
|
|
|
|
write(6,*)
|
|
|
|
write(6,*) 'Extreme values of returned stress and jacobian'
|
|
|
|
write(6,*)
|
|
|
|
write(6,'(a39)') ' value el ip'
|
2012-02-01 00:48:55 +05:30
|
|
|
write(6,'(a14,1x,e12.3,1x,i6,1x,i4)') 'stress min :', debug_stressMin, debug_stressMinLocation
|
|
|
|
write(6,'(a14,1x,e12.3,1x,i6,1x,i4)') ' max :', debug_stressMax, debug_stressMaxLocation
|
|
|
|
write(6,'(a14,1x,e12.3,1x,i6,1x,i4)') 'jacobian min :', debug_jacobianMin, debug_jacobianMinLocation
|
|
|
|
write(6,'(a14,1x,e12.3,1x,i6,1x,i4)') ' max :', debug_jacobianMax, debug_jacobianMaxLocation
|
2011-03-21 16:01:17 +05:30
|
|
|
write(6,*)
|
2009-07-31 17:32:20 +05:30
|
|
|
|
2011-03-21 16:01:17 +05:30
|
|
|
!$OMP END CRITICAL (write2out)
|
|
|
|
endif
|
2009-08-11 22:01:57 +05:30
|
|
|
|
2011-03-17 18:43:13 +05:30
|
|
|
endsubroutine
|
2008-01-11 00:23:57 +05:30
|
|
|
|
2011-03-17 18:43:13 +05:30
|
|
|
END MODULE debug
|