2009-08-31 20:39:15 +05:30
|
|
|
!* $Id$
|
2008-01-11 00:23:57 +05:30
|
|
|
!##############################################################
|
|
|
|
MODULE debug
|
|
|
|
!##############################################################
|
2008-02-19 18:28:46 +05:30
|
|
|
use prec
|
2008-01-11 00:23:57 +05:30
|
|
|
|
2008-02-19 18:28:46 +05:30
|
|
|
implicit none
|
2010-09-23 13:31:41 +05:30
|
|
|
character(len=64), parameter :: debug_configFile = 'debug.config' ! name of configuration file
|
|
|
|
|
2010-09-06 21:36:41 +05:30
|
|
|
integer(pInt), dimension(:,:), allocatable :: debug_StressLoopDistribution
|
2010-09-30 13:01:53 +05:30
|
|
|
integer(pInt), dimension(:,:), allocatable :: debug_LeapfrogBreakDistribution
|
2010-10-01 17:48:49 +05:30
|
|
|
integer(pInt), dimension(:,:), allocatable :: debug_StateLoopDistribution
|
2010-09-06 21:36:41 +05:30
|
|
|
integer(pInt), dimension(:), allocatable :: debug_CrystalliteLoopDistribution
|
|
|
|
integer(pInt), dimension(:), allocatable :: debug_MaterialpointStateLoopDistribution
|
|
|
|
integer(pInt), dimension(:), allocatable :: debug_MaterialpointLoopDistribution
|
2010-09-02 02:34:02 +05:30
|
|
|
integer(pLongInt) :: debug_cumLpTicks = 0_pInt
|
|
|
|
integer(pLongInt) :: debug_cumDotStateTicks = 0_pInt
|
2009-07-01 15:59:35 +05:30
|
|
|
integer(pLongInt) :: debug_cumDotTemperatureTicks = 0_pInt
|
2010-09-02 02:34:02 +05:30
|
|
|
integer(pInt) :: debug_cumLpCalls = 0_pInt
|
|
|
|
integer(pInt) :: debug_cumDotStateCalls = 0_pInt
|
2009-07-01 15:59:35 +05:30
|
|
|
integer(pInt) :: debug_cumDotTemperatureCalls = 0_pInt
|
2010-02-17 18:51:36 +05:30
|
|
|
integer(pInt) :: debug_e = 1_pInt
|
|
|
|
integer(pInt) :: debug_i = 1_pInt
|
|
|
|
integer(pInt) :: debug_g = 1_pInt
|
2010-09-30 13:01:53 +05:30
|
|
|
logical :: selectiveDebugger = .true.
|
|
|
|
logical :: verboseDebugger = .false.
|
2010-09-06 21:36:41 +05:30
|
|
|
logical :: debugger = .true.
|
2009-03-04 17:18:54 +05:30
|
|
|
logical :: distribution_init = .false.
|
2008-02-19 18:28:46 +05:30
|
|
|
|
|
|
|
CONTAINS
|
|
|
|
|
2009-10-22 14:44:17 +05:30
|
|
|
|
|
|
|
!********************************************************************
|
|
|
|
! initialize the debugging capabilities
|
|
|
|
!********************************************************************
|
2009-06-15 18:41:21 +05:30
|
|
|
subroutine debug_init()
|
|
|
|
|
|
|
|
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, &
|
|
|
|
IO_open_file, &
|
|
|
|
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
|
|
|
|
|
2009-06-18 19:58:02 +05:30
|
|
|
write(6,*)
|
|
|
|
write(6,*) '<<<+- debug init -+>>>'
|
2009-08-31 20:39:15 +05:30
|
|
|
write(6,*) '$Id$'
|
2009-06-18 19:58:02 +05:30
|
|
|
write(6,*)
|
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
|
|
|
|
if(IO_open_file(fileunit,debug_configFile)) then
|
|
|
|
|
|
|
|
write(6,*) ' ... using values from config file'
|
|
|
|
write(6,*)
|
|
|
|
|
|
|
|
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)
|
|
|
|
tag = IO_lc(IO_stringValue(line,positions,1)) ! extract key
|
|
|
|
select case(tag)
|
|
|
|
case ('element','e','el')
|
|
|
|
debug_e = IO_intValue(line,positions,2)
|
|
|
|
case ('itegrationpoint','i','ip')
|
|
|
|
debug_i = IO_intValue(line,positions,2)
|
|
|
|
case ('grain','g','gr')
|
|
|
|
debug_g = IO_intValue(line,positions,2)
|
|
|
|
case ('selective')
|
|
|
|
selectiveDebugger = IO_intValue(line,positions,2) > 0_pInt
|
|
|
|
case ('verbose')
|
|
|
|
verboseDebugger = IO_intValue(line,positions,2) > 0_pInt
|
|
|
|
case ('debug')
|
|
|
|
debugger = IO_intValue(line,positions,2) > 0_pInt
|
|
|
|
endselect
|
|
|
|
enddo
|
|
|
|
100 close(fileunit)
|
|
|
|
|
|
|
|
! no config file, so we use standard values
|
|
|
|
else
|
2010-09-23 14:43:46 +05:30
|
|
|
|
2010-09-23 13:31:41 +05:30
|
|
|
write(6,*) ' ... using standard values'
|
|
|
|
write(6,*)
|
2010-09-23 14:43:46 +05:30
|
|
|
|
|
|
|
endif
|
|
|
|
|
2010-09-23 13:31:41 +05:30
|
|
|
! writing parameters to output file
|
|
|
|
write(6,'(a24,x,l)') 'debug: ',debugger
|
|
|
|
write(6,'(a24,x,l)') 'verbose: ',verboseDebugger
|
|
|
|
write(6,'(a24,x,l)') 'selective: ',selectiveDebugger
|
|
|
|
if (selectiveDebugger) then
|
|
|
|
write(6,'(a24,x,i8)') ' element: ',debug_e
|
|
|
|
write(6,'(a24,x,i8)') ' ip: ',debug_i
|
|
|
|
write(6,'(a24,x,i8)') ' grain: ',debug_g
|
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
|
|
|
|
|
|
|
|
|
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
|
2009-10-22 14:44:17 +05:30
|
|
|
debug_cumLpTicks = 0_pInt
|
|
|
|
debug_cumDotStateTicks = 0_pInt
|
2009-07-01 15:59:35 +05:30
|
|
|
debug_cumDotTemperatureTicks = 0_pInt
|
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
|
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
|
|
|
|
!********************************************************************
|
2009-06-15 18:41:21 +05:30
|
|
|
subroutine debug_info()
|
2008-02-19 18:28:46 +05:30
|
|
|
|
|
|
|
use prec
|
2009-06-15 18:41:21 +05:30
|
|
|
use numerics, only: nStress, &
|
2009-08-11 22:01:57 +05:30
|
|
|
nState, &
|
|
|
|
nCryst, &
|
|
|
|
nMPstate, &
|
|
|
|
nHomog
|
2008-01-11 00:23:57 +05:30
|
|
|
implicit none
|
2008-02-19 18:28:46 +05:30
|
|
|
|
2009-10-22 14:44:17 +05:30
|
|
|
integer(pInt) i,integral
|
|
|
|
integer(pLongInt) tickrate
|
2009-06-15 18:41:21 +05:30
|
|
|
|
2009-10-22 14:44:17 +05:30
|
|
|
call system_clock(count_rate=tickrate)
|
2008-02-19 18:28:46 +05:30
|
|
|
|
2009-03-16 23:08:33 +05:30
|
|
|
write(6,*)
|
2008-02-19 18:28:46 +05:30
|
|
|
write(6,*) 'DEBUG Info'
|
2009-03-16 23:08:33 +05:30
|
|
|
write(6,*)
|
2010-09-02 02:34:02 +05:30
|
|
|
write(6,'(a33,x,i12)') 'total calls to LpAndItsTangent :',debug_cumLpCalls
|
2009-03-16 23:08:33 +05:30
|
|
|
if (debug_cumLpCalls > 0_pInt) then
|
2009-10-22 14:44:17 +05:30
|
|
|
write(6,'(a33,x,f12.3)') 'total CPU time/s :',dble(debug_cumLpTicks)/tickrate
|
|
|
|
write(6,'(a33,x,f12.6)') 'avg CPU time/microsecs per call :',&
|
|
|
|
dble(debug_cumLpTicks)*1.0e6_pReal/tickrate/debug_cumLpCalls
|
2009-03-16 23:08:33 +05:30
|
|
|
endif
|
|
|
|
write(6,*)
|
2010-09-02 02:34:02 +05:30
|
|
|
write(6,'(a33,x,i12)') 'total calls to collectDotState :',debug_cumDotStateCalls
|
2009-03-20 20:04:24 +05:30
|
|
|
if (debug_cumdotStateCalls > 0_pInt) then
|
2009-10-22 14:44:17 +05:30
|
|
|
write(6,'(a33,x,f12.3)') 'total CPU time/s :',dble(debug_cumDotStateTicks)/tickrate
|
|
|
|
write(6,'(a33,x,f12.6)') 'avg CPU time/microsecs per call :',&
|
|
|
|
dble(debug_cumDotStateTicks)*1.0e6_pReal/tickrate/debug_cumDotStateCalls
|
2009-03-20 20:04:24 +05:30
|
|
|
endif
|
2009-07-01 15:59:35 +05:30
|
|
|
write(6,*)
|
2010-09-02 02:34:02 +05:30
|
|
|
write(6,'(a33,x,i12)') 'total calls to dotTemperature :',debug_cumDotTemperatureCalls
|
2009-07-01 15:59:35 +05:30
|
|
|
if (debug_cumdotTemperatureCalls > 0_pInt) then
|
2009-10-22 14:44:17 +05:30
|
|
|
write(6,'(a33,x,f12.3)') 'total CPU time/s :', dble(debug_cumDotTemperatureTicks)/tickrate
|
|
|
|
write(6,'(a33,x,f12.6)') 'avg CPU time/microsecs per call :',&
|
|
|
|
dble(debug_cumDotTemperatureTicks)*1.0e6_pReal/tickrate/debug_cumDotTemperatureCalls
|
2009-07-01 15:59:35 +05:30
|
|
|
endif
|
2009-05-07 21:57:36 +05:30
|
|
|
|
2009-03-16 23:08:33 +05:30
|
|
|
integral = 0_pInt
|
2009-05-07 21:57:36 +05:30
|
|
|
write(6,*)
|
2010-09-30 13:01:53 +05:30
|
|
|
write(6,*) 'distribution_StressLoop : stress frogbreak stiffness frogbreak'
|
2009-05-07 21:57:36 +05:30
|
|
|
do i=1,nStress
|
2010-09-30 13:01:53 +05:30
|
|
|
if (any(debug_StressLoopDistribution(i,:) /= 0_pInt ) .or. &
|
|
|
|
any(debug_LeapfrogBreakDistribution(i,:) /= 0_pInt ) ) then
|
2010-09-07 14:36:02 +05:30
|
|
|
integral = integral + i*debug_StressLoopDistribution(i,1) + i*debug_StressLoopDistribution(i,2)
|
2010-09-30 13:01:53 +05:30
|
|
|
write(6,'(i25,x,i10,x,i10,x,i10,x,i10)') i,debug_StressLoopDistribution(i,1),debug_LeapfrogBreakDistribution(i,1), &
|
|
|
|
debug_StressLoopDistribution(i,2),debug_LeapfrogBreakDistribution(i,2)
|
2009-03-16 23:08:33 +05:30
|
|
|
endif
|
2008-02-19 18:28:46 +05:30
|
|
|
enddo
|
2010-09-30 13:01:53 +05:30
|
|
|
write(6,'(a15,i10,x,i10,12x,i10)') ' total',integral,&
|
|
|
|
sum(debug_StressLoopDistribution(:,1)), &
|
|
|
|
sum(debug_StressLoopDistribution(:,2))
|
2008-02-19 18:28:46 +05:30
|
|
|
|
2009-03-16 23:08:33 +05:30
|
|
|
integral = 0_pInt
|
2009-05-07 21:57:36 +05:30
|
|
|
write(6,*)
|
2010-09-02 02:34:02 +05:30
|
|
|
write(6,*) 'distribution_CrystalliteStateLoop :'
|
2009-05-28 22:08:40 +05:30
|
|
|
do i=1,nState
|
2010-10-01 17:48:49 +05:30
|
|
|
if (any(debug_StateLoopDistribution(i,:) /= 0)) then
|
|
|
|
integral = integral + i*debug_StateLoopDistribution(i,1) + i*debug_StateLoopDistribution(i,2)
|
|
|
|
write(6,'(i25,x,i10,12x,i10)') i,debug_StateLoopDistribution(i,1),debug_StateLoopDistribution(i,2)
|
2009-05-07 21:57:36 +05:30
|
|
|
endif
|
|
|
|
enddo
|
2010-10-01 17:48:49 +05:30
|
|
|
write(6,'(a15,i10,x,i10,12x,i10)') ' total',integral,&
|
|
|
|
sum(debug_StateLoopDistribution(:,1)), &
|
|
|
|
sum(debug_StateLoopDistribution(:,2))
|
2009-05-07 21:57:36 +05:30
|
|
|
|
|
|
|
integral = 0_pInt
|
|
|
|
write(6,*)
|
2010-09-02 02:34:02 +05:30
|
|
|
write(6,*) 'distribution_CrystalliteCutbackLoop :'
|
2009-08-11 22:01:57 +05:30
|
|
|
do i=1,nCryst+1
|
2009-05-28 22:08:40 +05:30
|
|
|
if (debug_CrystalliteLoopDistribution(i) /= 0) then
|
|
|
|
integral = integral + i*debug_CrystalliteLoopDistribution(i)
|
2009-08-11 22:01:57 +05:30
|
|
|
if (i <= nCryst) then
|
|
|
|
write(6,'(i25,x,i10)') i,debug_CrystalliteLoopDistribution(i)
|
|
|
|
else
|
|
|
|
write(6,'(i25,a1,i10)') i-1,'+',debug_CrystalliteLoopDistribution(i)
|
|
|
|
endif
|
2009-03-16 23:08:33 +05:30
|
|
|
endif
|
2008-02-19 18:28:46 +05:30
|
|
|
enddo
|
2009-08-11 22:01:57 +05:30
|
|
|
write(6,'(a15,i10,x,i10)') ' total',integral,sum(debug_CrystalliteLoopDistribution)
|
2010-09-02 02:34:02 +05:30
|
|
|
|
2009-08-11 22:01:57 +05:30
|
|
|
integral = 0_pInt
|
|
|
|
write(6,*)
|
2010-09-02 02:34:02 +05:30
|
|
|
write(6,*)
|
|
|
|
write(6,*) 'distribution_MaterialpointStateLoop :'
|
2009-08-11 22:01:57 +05:30
|
|
|
do i=1,nMPstate
|
|
|
|
if (debug_MaterialpointStateLoopDistribution(i) /= 0) then
|
|
|
|
integral = integral + i*debug_MaterialpointStateLoopDistribution(i)
|
|
|
|
write(6,'(i25,x,i10)') i,debug_MaterialpointStateLoopDistribution(i)
|
|
|
|
endif
|
|
|
|
enddo
|
|
|
|
write(6,'(a15,i10,x,i10)') ' total',integral,sum(debug_MaterialpointStateLoopDistribution)
|
|
|
|
|
2009-07-31 17:32:20 +05:30
|
|
|
integral = 0_pInt
|
|
|
|
write(6,*)
|
2010-09-02 02:34:02 +05:30
|
|
|
write(6,*) 'distribution_MaterialpointCutbackLoop :'
|
2009-08-11 22:01:57 +05:30
|
|
|
do i=1,nHomog+1
|
2009-07-31 17:32:20 +05:30
|
|
|
if (debug_MaterialpointLoopDistribution(i) /= 0) then
|
|
|
|
integral = integral + i*debug_MaterialpointLoopDistribution(i)
|
2009-08-11 22:01:57 +05:30
|
|
|
if (i <= nHomog) then
|
|
|
|
write(6,'(i25,x,i10)') i,debug_MaterialpointLoopDistribution(i)
|
|
|
|
else
|
|
|
|
write(6,'(i25,a1,i10)') i-1,'+',debug_MaterialpointLoopDistribution(i)
|
|
|
|
endif
|
2009-07-31 17:32:20 +05:30
|
|
|
endif
|
|
|
|
enddo
|
2009-08-11 22:01:57 +05:30
|
|
|
write(6,'(a15,i10,x,i10)') ' total',integral,sum(debug_MaterialpointLoopDistribution)
|
2009-07-31 17:32:20 +05:30
|
|
|
|
2010-09-02 02:34:02 +05:30
|
|
|
write(6,*)
|
2009-08-11 22:01:57 +05:30
|
|
|
|
2009-06-15 18:41:21 +05:30
|
|
|
endsubroutine
|
2008-01-11 00:23:57 +05:30
|
|
|
|
|
|
|
END MODULE debug
|