* removed last remnants of old debugger
* replaced "dble" intrinsic function by "real" with pReal kind in constitutive_nonlocal.f90 * removed useless line breaks in output of state in CPFEM.f90
This commit is contained in:
parent
06fc83ac14
commit
790dbed1e4
|
@ -368,8 +368,9 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt
|
|||
!$OMP CRITICAL (write2out)
|
||||
write(6,'(a)') '<< CPFEM >> Aging states'
|
||||
if (debug_e == cp_en .and. debug_i == IP) then
|
||||
write(6,'(a,x,i5,x,i2,x,i3,/,(12(x),6(e20.8,x),/))') '<< CPFEM >> AGED state of element ip grain',&
|
||||
write(6,'(a,x,i5,x,i2,x,i3,/,(12(x),6(e20.8,x)))') '<< CPFEM >> AGED state of element ip grain',&
|
||||
cp_en, IP, 1, constitutive_state(1,IP,cp_en)%p
|
||||
write(6,*)
|
||||
endif
|
||||
!$OMP END CRITICAL (write2out)
|
||||
endif
|
||||
|
|
|
@ -985,7 +985,7 @@ if (.not. phase_localConstitution(phase)) then
|
|||
cycle ! this is myself
|
||||
endif
|
||||
neighboring_ipCoords = mesh_ipCenterOfGravity(1:3,neighboring_ip,neighboring_el) &
|
||||
+ (/dble(deltaX), dble(deltaY), dble(deltaZ)/) * meshSize
|
||||
+ (/real(deltaX,pReal), real(deltaY,pReal), real(deltaZ,pReal)/) * meshSize
|
||||
connection = neighboring_ipCoords - ipCoords
|
||||
distance = sqrt(sum(connection ** 2.0_pReal))
|
||||
if (.not. phase_localConstitution(neighboring_phase) &
|
||||
|
@ -1036,7 +1036,7 @@ if (.not. phase_localConstitution(phase)) then
|
|||
neighboring_Nexcess = neighboring_rhoExcess(1,s) * mesh_ipVolume(neighboring_ip,neighboring_el) / segmentLength
|
||||
flipSign = sign(1.0_pReal, -y)
|
||||
do side = 1,-1,-2
|
||||
lambda = dble(side) * 0.5_pReal * segmentLength - y
|
||||
lambda = real(side,pReal) * 0.5_pReal * segmentLength - y
|
||||
R = sqrt(xsquare + zsquare + lambda**2.0_pReal)
|
||||
Rsquare = R ** 2.0_pReal
|
||||
Rcube = R**3.0_pReal
|
||||
|
@ -1045,19 +1045,19 @@ if (.not. phase_localConstitution(phase)) then
|
|||
call IO_error(237,el,ip,g)
|
||||
endif
|
||||
|
||||
sigma(1,1) = sigma(1,1) - dble(side) * flipSign * z / denominator &
|
||||
* (1.0_pReal + xsquare / Rsquare + xsquare / denominator) &
|
||||
* neighboring_Nexcess
|
||||
sigma(2,2) = sigma(2,2) - dble(side) * (flipSign * 2.0_pReal * nu * z / denominator + z * lambda / Rcube) &
|
||||
* neighboring_Nexcess
|
||||
sigma(3,3) = sigma(3,3) + dble(side) * flipSign * z / denominator &
|
||||
* (1.0_pReal - zsquare / Rsquare - zsquare / denominator) &
|
||||
* neighboring_Nexcess
|
||||
sigma(1,2) = sigma(1,2) + dble(side) * x * z / Rcube * neighboring_Nexcess
|
||||
sigma(1,3) = sigma(1,3) + dble(side) * flipSign * x / denominator &
|
||||
* (1.0_pReal - zsquare / Rsquare - zsquare / denominator) &
|
||||
* neighboring_Nexcess
|
||||
sigma(2,3) = sigma(2,3) - dble(side) * (nu / R - zsquare / Rcube) * neighboring_Nexcess
|
||||
sigma(1,1) = sigma(1,1) - real(side,pReal) * flipSign * z / denominator &
|
||||
* (1.0_pReal + xsquare / Rsquare + xsquare / denominator) &
|
||||
* neighboring_Nexcess
|
||||
sigma(2,2) = sigma(2,2) - real(side,pReal) * (flipSign * 2.0_pReal * nu * z / denominator + z * lambda / Rcube) &
|
||||
* neighboring_Nexcess
|
||||
sigma(3,3) = sigma(3,3) + real(side,pReal) * flipSign * z / denominator &
|
||||
* (1.0_pReal - zsquare / Rsquare - zsquare / denominator) &
|
||||
* neighboring_Nexcess
|
||||
sigma(1,2) = sigma(1,2) + real(side,pReal) * x * z / Rcube * neighboring_Nexcess
|
||||
sigma(1,3) = sigma(1,3) + real(side,pReal) * flipSign * x / denominator &
|
||||
* (1.0_pReal - zsquare / Rsquare - zsquare / denominator) &
|
||||
* neighboring_Nexcess
|
||||
sigma(2,3) = sigma(2,3) - real(side,pReal) * (nu / R - zsquare / Rcube) * neighboring_Nexcess
|
||||
enddo
|
||||
|
||||
|
||||
|
@ -1066,7 +1066,7 @@ if (.not. phase_localConstitution(phase)) then
|
|||
neighboring_Nexcess = neighboring_rhoExcess(2,s) * mesh_ipVolume(neighboring_ip,neighboring_el) / segmentLength
|
||||
flipSign = sign(1.0_pReal, x)
|
||||
do side = 1,-1,-2
|
||||
lambda = x + dble(side) * 0.5_pReal * segmentLength
|
||||
lambda = x + real(side,pReal) * 0.5_pReal * segmentLength
|
||||
R = sqrt(ysquare + zsquare + lambda**2.0_pReal)
|
||||
Rsquare = R ** 2.0_pReal
|
||||
Rcube = R**3.0_pReal
|
||||
|
@ -1075,8 +1075,8 @@ if (.not. phase_localConstitution(phase)) then
|
|||
call IO_error(237,el,ip,g)
|
||||
endif
|
||||
|
||||
sigma(1,2) = sigma(1,2) - dble(side) * flipSign * z * (1.0_pReal - nu) / denominator * neighboring_Nexcess
|
||||
sigma(1,3) = sigma(1,3) + dble(side) * flipSign * y * (1.0_pReal - nu) / denominator * neighboring_Nexcess
|
||||
sigma(1,2) = sigma(1,2) - real(side,pReal) * flipSign * z * (1.0_pReal - nu) / denominator * neighboring_Nexcess
|
||||
sigma(1,3) = sigma(1,3) + real(side,pReal) * flipSign * y * (1.0_pReal - nu) / denominator * neighboring_Nexcess
|
||||
enddo
|
||||
|
||||
|
||||
|
@ -1888,9 +1888,6 @@ use mesh, only: mesh_element, &
|
|||
use lattice, only: lattice_sn, &
|
||||
lattice_sd, &
|
||||
lattice_st
|
||||
use debug, only: debugger, &
|
||||
debug_e, debug_i, debug_g, &
|
||||
verboseDebugger
|
||||
|
||||
implicit none
|
||||
|
||||
|
@ -2002,7 +1999,7 @@ do n = 1,Nneighbors
|
|||
belowThreshold = .true.
|
||||
do while (compatibilitySum < 1.0_pReal .and. any(belowThreshold(1:ns)))
|
||||
thresholdValue = maxval(compatibility(2,1:ns,s1,n), belowThreshold(1:ns)) ! screws always positive
|
||||
nThresholdValues = dble(count(compatibility(2,1:ns,s1,n) == thresholdValue))
|
||||
nThresholdValues = real(count(compatibility(2,1:ns,s1,n) == thresholdValue),pReal)
|
||||
where (compatibility(2,1:ns,s1,n) >= thresholdValue) &
|
||||
belowThreshold(1:ns) = .false.
|
||||
if (compatibilitySum + thresholdValue * nThresholdValues > 1.0_pReal) &
|
||||
|
|
|
@ -503,7 +503,6 @@ function constitutive_phenopowerlaw_stateInit(myInstance)
|
|||
!* initial microstructural state *
|
||||
!*********************************************************************
|
||||
use prec, only: pReal,pInt
|
||||
use debug, only: debugger
|
||||
use lattice, only: lattice_maxNslipFamily, lattice_maxNtwinFamily
|
||||
implicit none
|
||||
|
||||
|
@ -621,7 +620,6 @@ subroutine constitutive_phenopowerlaw_LpAndItsTangent(Lp,dLp_dTstar,Tstar_v,Temp
|
|||
!* - dLp_dTstar : derivative of Lp (4th-rank tensor) *
|
||||
!*********************************************************************
|
||||
use prec, only: pReal,pInt,p_vec
|
||||
use debug, only: debugger
|
||||
use math, only: math_Plain3333to99
|
||||
use lattice, only: lattice_Sslip,lattice_Sslip_v,lattice_Stwin,lattice_Stwin_v, lattice_maxNslipFamily, lattice_maxNtwinFamily, &
|
||||
lattice_NslipSystem,lattice_NtwinSystem
|
||||
|
@ -728,7 +726,6 @@ function constitutive_phenopowerlaw_dotState(Tstar_v,Temperature,state,ipc,ip,el
|
|||
!* - constitutive_dotState : evolution of state variable *
|
||||
!*********************************************************************
|
||||
use prec, only: pReal,pInt,p_vec
|
||||
use debug, only: debugger
|
||||
use lattice, only: lattice_Sslip,lattice_Sslip_v,lattice_Stwin,lattice_Stwin_v, lattice_maxNslipFamily, lattice_maxNtwinFamily, &
|
||||
lattice_NslipSystem,lattice_NtwinSystem,lattice_shearTwin
|
||||
use mesh, only: mesh_NcpElems,mesh_maxNips
|
||||
|
|
|
@ -1548,10 +1548,11 @@ relTemperatureResiduum = 0.0_pReal
|
|||
|
||||
! --- nonlocal convergence check ---
|
||||
|
||||
#ifndef _OPENMP
|
||||
if (debug_verbosity > 5) then
|
||||
write(6,'(a,L)') '<< CRYST >> crystallite_converged',crystallite_converged
|
||||
endif
|
||||
#ifndef _OPENMP
|
||||
if (debug_verbosity > 5) then
|
||||
write(6,'(a,i8,a,i2)') '<< CRYST >> ', count(crystallite_converged(:,:,:)), ' grains converged'
|
||||
write(6,*)
|
||||
endif
|
||||
#endif
|
||||
if (.not. singleRun) then ! if not requesting Integration of just a single IP
|
||||
if ( any(.not. crystallite_converged .and. .not. crystallite_localConstitution)) then ! any non-local not yet converged (or broken)...
|
||||
|
@ -1835,10 +1836,11 @@ relTemperatureResiduum = 0.0_pReal
|
|||
|
||||
! --- NONLOCAL CONVERGENCE CHECK ---
|
||||
|
||||
#ifndef _OPENMP
|
||||
if (debug_verbosity > 5) then
|
||||
write(6,'(a,L)') '<< CRYST >> crystallite_converged',crystallite_converged
|
||||
endif
|
||||
#ifndef _OPENMP
|
||||
if (debug_verbosity > 5) then
|
||||
write(6,'(a,i8,a,i2)') '<< CRYST >> ', count(crystallite_converged(:,:,:)), ' grains converged'
|
||||
write(6,*)
|
||||
endif
|
||||
#endif
|
||||
if (.not. singleRun) then ! if not requesting Integration of just a single IP
|
||||
if ( any(.not. crystallite_converged .and. .not. crystallite_localConstitution)) then ! any non-local not yet converged (or broken)...
|
||||
|
@ -2883,8 +2885,7 @@ use mesh, only: mesh_element, &
|
|||
FE_NipNeighbors
|
||||
use debug, only: debug_verbosity, &
|
||||
debug_selectiveDebugger, &
|
||||
debug_e, debug_i, debug_g, &
|
||||
verboseDebugger
|
||||
debug_e, debug_i, debug_g
|
||||
use constitutive_nonlocal, only: constitutive_nonlocal_structure, &
|
||||
constitutive_nonlocal_updateCompatibility
|
||||
|
||||
|
|
|
@ -30,9 +30,6 @@ real(pReal) :: debug_stressMax
|
|||
real(pReal) :: debug_stressMin
|
||||
real(pReal) :: debug_jacobianMax
|
||||
real(pReal) :: debug_jacobianMin
|
||||
logical :: selectiveDebugger = .true.
|
||||
logical :: verboseDebugger = .false.
|
||||
logical :: debugger = .true.
|
||||
logical :: debug_selectiveDebugger = .true.
|
||||
integer(pInt) :: debug_verbosity = 1_pInt
|
||||
|
||||
|
@ -131,9 +128,8 @@ subroutine debug_init()
|
|||
|
||||
if (debug_verbosity > 0) then
|
||||
!$OMP CRITICAL (write2out)
|
||||
write(6,'(a24,x,l)') 'debug: ',debugger
|
||||
write(6,'(a24,x,l)') 'verbose: ',verboseDebugger
|
||||
write(6,'(a24,x,l)') 'selective: ',selectiveDebugger
|
||||
write(6,'(a24,x,l)') 'verbose: ',debug_verbosity
|
||||
write(6,'(a24,x,l)') 'selective: ',debug_selectiveDebugger
|
||||
!$OMP END CRITICAL (write2out)
|
||||
endif
|
||||
if (debug_selectiveDebugger) then
|
||||
|
|
Loading…
Reference in New Issue