simplified print and format strings
This commit is contained in:
parent
e848590c5c
commit
4a913c83e5
|
@ -186,7 +186,7 @@ subroutine homogenization_init
|
||||||
materialpoint_F = materialpoint_F0 ! initialize to identity
|
materialpoint_F = materialpoint_F0 ! initialize to identity
|
||||||
allocate(materialpoint_P(3,3,discretization_nIP,discretization_nElem), source=0.0_pReal)
|
allocate(materialpoint_P(3,3,discretization_nIP,discretization_nElem), source=0.0_pReal)
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- homogenization init -+>>>'; flush(6)
|
print'(/,a)', ' <<<+- homogenization init -+>>>'; flush(6)
|
||||||
|
|
||||||
num%nMPstate = num_homogGeneric%get_asInt ('nMPstate', defaultVal=10)
|
num%nMPstate = num_homogGeneric%get_asInt ('nMPstate', defaultVal=10)
|
||||||
num%subStepMinHomog = num_homogGeneric%get_asFloat('subStepMin', defaultVal=1.0e-3_pReal)
|
num%subStepMinHomog = num_homogGeneric%get_asFloat('subStepMin', defaultVal=1.0e-3_pReal)
|
||||||
|
@ -228,11 +228,11 @@ subroutine materialpoint_stressAndItsTangent(updateJaco,dt)
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
|
|
||||||
if (debugHomog%basic) then
|
if (debugHomog%basic) then
|
||||||
write(6,'(/a,i5,1x,i2)') '<< HOMOG >> Material Point start at el ip ', debugHomog%element, debugHomog%ip
|
print'(/a,i5,1x,i2)', ' << HOMOG >> Material Point start at el ip ', debugHomog%element, debugHomog%ip
|
||||||
|
|
||||||
write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< HOMOG >> F0', &
|
print'(a,/,3(12x,3(f14.9,1x)/))', ' << HOMOG >> F0', &
|
||||||
transpose(materialpoint_F0(1:3,1:3,debugHomog%ip,debugHomog%element))
|
transpose(materialpoint_F0(1:3,1:3,debugHomog%ip,debugHomog%element))
|
||||||
write(6,'(a,/,3(12x,3(f14.9,1x)/))') '<< HOMOG >> F', &
|
print'(a,/,3(12x,3(f14.9,1x)/))', ' << HOMOG >> F', &
|
||||||
transpose(materialpoint_F(1:3,1:3,debugHomog%ip,debugHomog%element))
|
transpose(materialpoint_F(1:3,1:3,debugHomog%ip,debugHomog%element))
|
||||||
endif
|
endif
|
||||||
#endif
|
#endif
|
||||||
|
@ -292,12 +292,11 @@ subroutine materialpoint_stressAndItsTangent(updateJaco,dt)
|
||||||
|
|
||||||
if (converged(i,e)) then
|
if (converged(i,e)) then
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive &
|
if (debugHomog%extensive .and. ((e == debugHomog%element .and. i == debugHomog%ip) &
|
||||||
.and. ((e == debugHomog%element .and. i == debugHomog%ip) &
|
.or. .not. debugHomog%selective)) then
|
||||||
.or. .not. debugHomog%selective)) then
|
print'(a,f12.8,a,f12.8,a,i8,1x,i2/)', ' << HOMOG >> winding forward from ', &
|
||||||
write(6,'(a,1x,f12.8,1x,a,1x,f12.8,1x,a,i8,1x,i2/)') '<< HOMOG >> winding forward from', &
|
subFrac(i,e), ' to current subFrac ', &
|
||||||
subFrac(i,e), 'to current subFrac', &
|
subFrac(i,e)+subStep(i,e),' in materialpoint_stressAndItsTangent at el ip ',e,i
|
||||||
subFrac(i,e)+subStep(i,e),'in materialpoint_stressAndItsTangent at el ip',e,i
|
|
||||||
endif
|
endif
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
|
@ -342,20 +341,17 @@ subroutine materialpoint_stressAndItsTangent(updateJaco,dt)
|
||||||
num%subStepSizeHomog * subStep(i,e) <= num%subStepMinHomog ) then ! would require too small subStep
|
num%subStepSizeHomog * subStep(i,e) <= num%subStepMinHomog ) then ! would require too small subStep
|
||||||
! cutback makes no sense
|
! cutback makes no sense
|
||||||
if (.not. terminallyIll) then ! so first signals terminally ill...
|
if (.not. terminallyIll) then ! so first signals terminally ill...
|
||||||
!$OMP CRITICAL (write2out)
|
print*, ' Integration point ', i,' at element ', e, ' terminally ill'
|
||||||
write(6,*) 'Integration point ', i,' at element ', e, ' terminally ill'
|
|
||||||
!$OMP END CRITICAL (write2out)
|
|
||||||
endif
|
endif
|
||||||
terminallyIll = .true. ! ...and kills all others
|
terminallyIll = .true. ! ...and kills all others
|
||||||
else ! cutback makes sense
|
else ! cutback makes sense
|
||||||
subStep(i,e) = num%subStepSizeHomog * subStep(i,e) ! crystallite had severe trouble, so do a significant cutback
|
subStep(i,e) = num%subStepSizeHomog * subStep(i,e) ! crystallite had severe trouble, so do a significant cutback
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive &
|
if (debugHomog%extensive .and. ((e == debugHomog%element .and. i == debugHomog%ip) &
|
||||||
.and. ((e == debugHomog%element .and. i == debugHomog%ip) &
|
.or. .not. debugHomog%selective)) then
|
||||||
.or. .not. debugHomog%selective)) then
|
print'(a,f12.8,a,i8,1x,i2/)', &
|
||||||
write(6,'(a,1x,f12.8,a,i8,1x,i2/)') &
|
'<< HOMOG >> cutback step in materialpoint_stressAndItsTangent with new subStep: ',&
|
||||||
'<< HOMOG >> cutback step in materialpoint_stressAndItsTangent with new subStep:',&
|
|
||||||
subStep(i,e),' at el ip',e,i
|
subStep(i,e),' at el ip',e,i
|
||||||
endif
|
endif
|
||||||
#endif
|
#endif
|
||||||
|
@ -469,7 +465,7 @@ subroutine materialpoint_stressAndItsTangent(updateJaco,dt)
|
||||||
enddo elementLooping4
|
enddo elementLooping4
|
||||||
!$OMP END PARALLEL DO
|
!$OMP END PARALLEL DO
|
||||||
else
|
else
|
||||||
write(6,'(/,a,/)') '<< HOMOG >> Material Point terminally ill'
|
print'(/,a,/)', ' << HOMOG >> Material Point terminally ill'
|
||||||
endif
|
endif
|
||||||
|
|
||||||
end subroutine materialpoint_stressAndItsTangent
|
end subroutine materialpoint_stressAndItsTangent
|
||||||
|
|
|
@ -92,16 +92,18 @@ module subroutine mech_RGC_init(num_homogMech)
|
||||||
homog, &
|
homog, &
|
||||||
homogMech
|
homogMech
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- homogenization_mech_rgc init -+>>>'
|
print'(/,a)', ' <<<+- homogenization_mech_rgc init -+>>>'
|
||||||
|
|
||||||
write(6,'(/,a)') ' Tjahjanto et al., International Journal of Material Forming 2(1):939–942, 2009'
|
|
||||||
write(6,'(a)') ' https://doi.org/10.1007/s12289-009-0619-1'
|
|
||||||
|
|
||||||
write(6,'(/,a)') ' Tjahjanto et al., Modelling and Simulation in Materials Science and Engineering 18:015006, 2010'
|
|
||||||
write(6,'(a)') ' https://doi.org/10.1088/0965-0393/18/1/015006'
|
|
||||||
|
|
||||||
Ninstance = count(homogenization_type == HOMOGENIZATION_RGC_ID)
|
Ninstance = count(homogenization_type == HOMOGENIZATION_RGC_ID)
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
|
print'(a,i2)', ' # instances: ',Ninstance; flush(6)
|
||||||
|
|
||||||
|
print*, 'Tjahjanto et al., International Journal of Material Forming 2(1):939–942, 2009'
|
||||||
|
print*, 'https://doi.org/10.1007/s12289-009-0619-1'//IO_EOL
|
||||||
|
|
||||||
|
print*, 'Tjahjanto et al., Modelling and Simulation in Materials Science and Engineering 18:015006, 2010'
|
||||||
|
print*, 'https://doi.org/10.1088/0965-0393/18/1/015006'//IO_EOL
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
allocate(param(Ninstance))
|
allocate(param(Ninstance))
|
||||||
allocate(state(Ninstance))
|
allocate(state(Ninstance))
|
||||||
|
@ -240,9 +242,9 @@ module subroutine mech_RGC_partitionDeformation(F,avgF,instance,of)
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive) then
|
if (debugHomog%extensive) then
|
||||||
write(6,'(1x,a32,1x,i3)')'Deformation gradient of grain: ',iGrain
|
print'(a,i3)',' Deformation gradient of grain: ',iGrain
|
||||||
do i = 1,3
|
do i = 1,3
|
||||||
write(6,'(1x,3(e15.8,1x))')(F(i,j,iGrain), j = 1,3)
|
print'(1x,3(e15.8,1x))',(F(i,j,iGrain), j = 1,3)
|
||||||
enddo
|
enddo
|
||||||
print*,' '
|
print*,' '
|
||||||
flush(6)
|
flush(6)
|
||||||
|
@ -303,9 +305,9 @@ module procedure mech_RGC_updateState
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive) then
|
if (debugHomog%extensive) then
|
||||||
write(6,'(1x,a30)')'Obtained state: '
|
print*, 'Obtained state: '
|
||||||
do i = 1,size(stt%relaxationVector(:,of))
|
do i = 1,size(stt%relaxationVector(:,of))
|
||||||
write(6,'(1x,2(e15.8,1x))') stt%relaxationVector(i,of)
|
print'(1x,2(e15.8,1x))', stt%relaxationVector(i,of)
|
||||||
enddo
|
enddo
|
||||||
print*,' '
|
print*,' '
|
||||||
endif
|
endif
|
||||||
|
@ -319,22 +321,6 @@ module procedure mech_RGC_updateState
|
||||||
! calculating volume discrepancy and stress penalty related to overall volume discrepancy
|
! calculating volume discrepancy and stress penalty related to overall volume discrepancy
|
||||||
call volumePenalty(D,dst%volumeDiscrepancy(of),avgF,F,nGrain,instance,of)
|
call volumePenalty(D,dst%volumeDiscrepancy(of),avgF,F,nGrain,instance,of)
|
||||||
|
|
||||||
#ifdef DEBUG
|
|
||||||
if (debugHomog%extensive) then
|
|
||||||
do iGrain = 1,nGrain
|
|
||||||
write(6,'(1x,a30,1x,i3,1x,a4,3(1x,e15.8))')'Mismatch magnitude of grain(',iGrain,') :',&
|
|
||||||
NN(1,iGrain),NN(2,iGrain),NN(3,iGrain)
|
|
||||||
write(6,'(/,1x,a30,1x,i3)')'Stress and penalties of grain: ',iGrain
|
|
||||||
do i = 1,3
|
|
||||||
write(6,'(1x,3(e15.8,1x),1x,3(e15.8,1x),1x,3(e15.8,1x))')(P(i,j,iGrain), j = 1,3), &
|
|
||||||
(R(i,j,iGrain), j = 1,3), &
|
|
||||||
(D(i,j,iGrain), j = 1,3)
|
|
||||||
enddo
|
|
||||||
print*,' '
|
|
||||||
enddo
|
|
||||||
endif
|
|
||||||
#endif
|
|
||||||
|
|
||||||
!------------------------------------------------------------------------------------------------
|
!------------------------------------------------------------------------------------------------
|
||||||
! computing the residual stress from the balance of traction at all (interior) interfaces
|
! computing the residual stress from the balance of traction at all (interior) interfaces
|
||||||
do iNum = 1,nIntFaceTot
|
do iNum = 1,nIntFaceTot
|
||||||
|
@ -369,8 +355,8 @@ module procedure mech_RGC_updateState
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive) then
|
if (debugHomog%extensive) then
|
||||||
write(6,'(1x,a30,1x,i3)')'Traction at interface: ',iNum
|
print'(a,i3)',' Traction at interface: ',iNum
|
||||||
write(6,'(1x,3(e15.8,1x))')(tract(iNum,j), j = 1,3)
|
print'(1x,3(e15.8,1x))',(tract(iNum,j), j = 1,3)
|
||||||
print*,' '
|
print*,' '
|
||||||
endif
|
endif
|
||||||
#endif
|
#endif
|
||||||
|
@ -385,12 +371,11 @@ module procedure mech_RGC_updateState
|
||||||
if (debugHomog%extensive .and. prm%of_debug == of) then
|
if (debugHomog%extensive .and. prm%of_debug == of) then
|
||||||
stresLoc = maxloc(abs(P))
|
stresLoc = maxloc(abs(P))
|
||||||
residLoc = maxloc(abs(tract))
|
residLoc = maxloc(abs(tract))
|
||||||
write(6,'(1x,a)')' '
|
print'(a,i2,1x,i4)',' RGC residual check ... ',ip,el
|
||||||
write(6,'(1x,a,1x,i2,1x,i4)')'RGC residual check ...',ip,el
|
print'(a,e15.8,a,i3,a,i2,i2)', ' Max stress: ',stresMax, &
|
||||||
write(6,'(1x,a15,1x,e15.8,1x,a7,i3,1x,a12,i2,i2)')'Max stress: ',stresMax, &
|
'@ grain ',stresLoc(3),' in component ',stresLoc(1),stresLoc(2)
|
||||||
'@ grain',stresLoc(3),'in component',stresLoc(1),stresLoc(2)
|
print'(a,e15.8,a,i3,a,i2)',' Max residual: ',residMax, &
|
||||||
write(6,'(1x,a15,1x,e15.8,1x,a7,i3,1x,a12,i2)')'Max residual: ',residMax, &
|
' @ iface ',residLoc(1),' in direction ',residLoc(2)
|
||||||
'@ iface',residLoc(1),'in direction',residLoc(2)
|
|
||||||
flush(6)
|
flush(6)
|
||||||
endif
|
endif
|
||||||
#endif
|
#endif
|
||||||
|
@ -403,7 +388,7 @@ module procedure mech_RGC_updateState
|
||||||
mech_RGC_updateState = .true.
|
mech_RGC_updateState = .true.
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive .and. prm%of_debug == of) &
|
if (debugHomog%extensive .and. prm%of_debug == of) &
|
||||||
write(6,'(1x,a55,/)')'... done and happy'; flush(6)
|
print*, '... done and happy'; flush(6)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -423,14 +408,14 @@ module procedure mech_RGC_updateState
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive .and. prm%of_debug == of) then
|
if (debugHomog%extensive .and. prm%of_debug == of) then
|
||||||
write(6,'(1x,a30,1x,e15.8)') 'Constitutive work: ',stt%work(of)
|
print'(a,e15.8)', ' Constitutive work: ',stt%work(of)
|
||||||
write(6,'(1x,a30,3(1x,e15.8))')'Magnitude mismatch: ',dst%mismatch(1,of), &
|
print'(a,3(1x,e15.8))', ' Magnitude mismatch: ',dst%mismatch(1,of), &
|
||||||
dst%mismatch(2,of), &
|
dst%mismatch(2,of), &
|
||||||
dst%mismatch(3,of)
|
dst%mismatch(3,of)
|
||||||
write(6,'(1x,a30,1x,e15.8)') 'Penalty energy: ', stt%penaltyEnergy(of)
|
print'(a,e15.8)', ' Penalty energy: ', stt%penaltyEnergy(of)
|
||||||
write(6,'(1x,a30,1x,e15.8,/)') 'Volume discrepancy: ', dst%volumeDiscrepancy(of)
|
print'(a,e15.8,/)', ' Volume discrepancy: ', dst%volumeDiscrepancy(of)
|
||||||
write(6,'(1x,a30,1x,e15.8)') 'Maximum relaxation rate: ', dst%relaxationRate_max(of)
|
print'(a,e15.8)', ' Maximum relaxation rate: ', dst%relaxationRate_max(of)
|
||||||
write(6,'(1x,a30,1x,e15.8,/)') 'Average relaxation rate: ', dst%relaxationRate_avg(of)
|
print'(a,e15.8,/)', ' Average relaxation rate: ', dst%relaxationRate_avg(of)
|
||||||
flush(6)
|
flush(6)
|
||||||
endif
|
endif
|
||||||
#endif
|
#endif
|
||||||
|
@ -444,7 +429,7 @@ module procedure mech_RGC_updateState
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive .and. prm%of_debug == of) &
|
if (debugHomog%extensive .and. prm%of_debug == of) &
|
||||||
write(6,'(1x,a,/)') '... broken'; flush(6)
|
print'(a,/)', ' ... broken'; flush(6)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
return
|
return
|
||||||
|
@ -452,7 +437,7 @@ module procedure mech_RGC_updateState
|
||||||
else ! proceed with computing the Jacobian and state update
|
else ! proceed with computing the Jacobian and state update
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive .and. prm%of_debug == of) &
|
if (debugHomog%extensive .and. prm%of_debug == of) &
|
||||||
write(6,'(1x,a,/)') '... not yet done'; flush(6)
|
print'(a,/)', ' ... not yet done'; flush(6)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
endif
|
endif
|
||||||
|
@ -509,9 +494,9 @@ module procedure mech_RGC_updateState
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive) then
|
if (debugHomog%extensive) then
|
||||||
write(6,'(1x,a30)')'Jacobian matrix of stress'
|
print*, 'Jacobian matrix of stress'
|
||||||
do i = 1,3*nIntFaceTot
|
do i = 1,3*nIntFaceTot
|
||||||
write(6,'(1x,100(e11.4,1x))')(smatrix(i,j), j = 1,3*nIntFaceTot)
|
print'(1x,100(e11.4,1x))',(smatrix(i,j), j = 1,3*nIntFaceTot)
|
||||||
enddo
|
enddo
|
||||||
print*,' '
|
print*,' '
|
||||||
flush(6)
|
flush(6)
|
||||||
|
@ -569,9 +554,9 @@ module procedure mech_RGC_updateState
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive) then
|
if (debugHomog%extensive) then
|
||||||
write(6,'(1x,a30)')'Jacobian matrix of penalty'
|
print*, 'Jacobian matrix of penalty'
|
||||||
do i = 1,3*nIntFaceTot
|
do i = 1,3*nIntFaceTot
|
||||||
write(6,'(1x,100(e11.4,1x))')(pmatrix(i,j), j = 1,3*nIntFaceTot)
|
print'(1x,100(e11.4,1x))',(pmatrix(i,j), j = 1,3*nIntFaceTot)
|
||||||
enddo
|
enddo
|
||||||
print*,' '
|
print*,' '
|
||||||
flush(6)
|
flush(6)
|
||||||
|
@ -588,9 +573,9 @@ module procedure mech_RGC_updateState
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive) then
|
if (debugHomog%extensive) then
|
||||||
write(6,'(1x,a30)')'Jacobian matrix of penalty'
|
print*, 'Jacobian matrix of penalty'
|
||||||
do i = 1,3*nIntFaceTot
|
do i = 1,3*nIntFaceTot
|
||||||
write(6,'(1x,100(e11.4,1x))')(rmatrix(i,j), j = 1,3*nIntFaceTot)
|
print'(1x,100(e11.4,1x))',(rmatrix(i,j), j = 1,3*nIntFaceTot)
|
||||||
enddo
|
enddo
|
||||||
print*,' '
|
print*,' '
|
||||||
flush(6)
|
flush(6)
|
||||||
|
@ -603,9 +588,9 @@ module procedure mech_RGC_updateState
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive) then
|
if (debugHomog%extensive) then
|
||||||
write(6,'(1x,a30)')'Jacobian matrix (total)'
|
print*, 'Jacobian matrix (total)'
|
||||||
do i = 1,3*nIntFaceTot
|
do i = 1,3*nIntFaceTot
|
||||||
write(6,'(1x,100(e11.4,1x))')(jmatrix(i,j), j = 1,3*nIntFaceTot)
|
print'(1x,100(e11.4,1x))',(jmatrix(i,j), j = 1,3*nIntFaceTot)
|
||||||
enddo
|
enddo
|
||||||
print*,' '
|
print*,' '
|
||||||
flush(6)
|
flush(6)
|
||||||
|
@ -619,9 +604,9 @@ module procedure mech_RGC_updateState
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive) then
|
if (debugHomog%extensive) then
|
||||||
write(6,'(1x,a30)')'Jacobian inverse'
|
print*, 'Jacobian inverse'
|
||||||
do i = 1,3*nIntFaceTot
|
do i = 1,3*nIntFaceTot
|
||||||
write(6,'(1x,100(e11.4,1x))')(jnverse(i,j), j = 1,3*nIntFaceTot)
|
print'(1x,100(e11.4,1x))',(jnverse(i,j), j = 1,3*nIntFaceTot)
|
||||||
enddo
|
enddo
|
||||||
print*,' '
|
print*,' '
|
||||||
flush(6)
|
flush(6)
|
||||||
|
@ -638,17 +623,17 @@ module procedure mech_RGC_updateState
|
||||||
if (any(abs(drelax) > num%maxdRelax)) then ! Forcing cutback when the incremental change of relaxation vector becomes too large
|
if (any(abs(drelax) > num%maxdRelax)) then ! Forcing cutback when the incremental change of relaxation vector becomes too large
|
||||||
mech_RGC_updateState = [.true.,.false.]
|
mech_RGC_updateState = [.true.,.false.]
|
||||||
!$OMP CRITICAL (write2out)
|
!$OMP CRITICAL (write2out)
|
||||||
write(6,'(1x,a,1x,i3,1x,a,1x,i3,1x,a)')'RGC_updateState: ip',ip,'| el',el,'enforces cutback'
|
print'(a,i3,a,i3,a)',' RGC_updateState: ip ',ip,' | el ',el,' enforces cutback'
|
||||||
write(6,'(1x,a,1x,e15.8)')'due to large relaxation change =',maxval(abs(drelax))
|
print'(a,e15.8)',' due to large relaxation change = ',maxval(abs(drelax))
|
||||||
flush(6)
|
flush(6)
|
||||||
!$OMP END CRITICAL (write2out)
|
!$OMP END CRITICAL (write2out)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive) then
|
if (debugHomog%extensive) then
|
||||||
write(6,'(1x,a30)')'Returned state: '
|
print*, 'Returned state: '
|
||||||
do i = 1,size(stt%relaxationVector(:,of))
|
do i = 1,size(stt%relaxationVector(:,of))
|
||||||
write(6,'(1x,2(e15.8,1x))') stt%relaxationVector(i,of)
|
print'(1x,2(e15.8,1x))', stt%relaxationVector(i,of)
|
||||||
enddo
|
enddo
|
||||||
print*,' '
|
print*,' '
|
||||||
flush(6)
|
flush(6)
|
||||||
|
@ -678,9 +663,6 @@ module procedure mech_RGC_updateState
|
||||||
integer :: iGrain,iGNghb,iFace,i,j,k,l
|
integer :: iGrain,iGNghb,iFace,i,j,k,l
|
||||||
real(pReal) :: muGrain,muGNghb,nDefNorm,bgGrain,bgGNghb
|
real(pReal) :: muGrain,muGNghb,nDefNorm,bgGrain,bgGNghb
|
||||||
real(pReal), parameter :: nDefToler = 1.0e-10_pReal
|
real(pReal), parameter :: nDefToler = 1.0e-10_pReal
|
||||||
#ifdef DEBUG
|
|
||||||
logical :: debugActive
|
|
||||||
#endif
|
|
||||||
|
|
||||||
nGDim = param(instance)%Nconstituents
|
nGDim = param(instance)%Nconstituents
|
||||||
rPen = 0.0_pReal
|
rPen = 0.0_pReal
|
||||||
|
@ -695,10 +677,8 @@ module procedure mech_RGC_updateState
|
||||||
associate(prm => param(instance))
|
associate(prm => param(instance))
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
debugActive = debugHomog%extensive .and. prm%of_debug == of
|
if (debugHomog%extensive .and. prm%of_debug == of) then
|
||||||
|
print'(a,2(1x,i3))', ' Correction factor: ',ip,el
|
||||||
if (debugActive) then
|
|
||||||
write(6,'(1x,a20,2(1x,i3))')'Correction factor: ',ip,el
|
|
||||||
print*, surfCorr
|
print*, surfCorr
|
||||||
endif
|
endif
|
||||||
#endif
|
#endif
|
||||||
|
@ -738,10 +718,10 @@ module procedure mech_RGC_updateState
|
||||||
nDefNorm = max(nDefToler,sqrt(nDefNorm)) ! approximation to zero mismatch if mismatch is zero (singularity)
|
nDefNorm = max(nDefToler,sqrt(nDefNorm)) ! approximation to zero mismatch if mismatch is zero (singularity)
|
||||||
nMis(abs(intFace(1)),iGrain) = nMis(abs(intFace(1)),iGrain) + nDefNorm ! total amount of mismatch experienced by the grain (at all six interfaces)
|
nMis(abs(intFace(1)),iGrain) = nMis(abs(intFace(1)),iGrain) + nDefNorm ! total amount of mismatch experienced by the grain (at all six interfaces)
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugActive) then
|
if (debugHomog%extensive .and. prm%of_debug == of) then
|
||||||
write(6,'(1x,a20,i2,1x,a20,1x,i3)')'Mismatch to face: ',intFace(1),'neighbor grain: ',iGNghb
|
print'(a,i2,a,i3)',' Mismatch to face: ',intFace(1),' neighbor grain: ',iGNghb
|
||||||
print*, transpose(nDef)
|
print*, transpose(nDef)
|
||||||
write(6,'(1x,a20,e11.4)')'with magnitude: ',nDefNorm
|
print'(a,e11.4)', ' with magnitude: ',nDefNorm
|
||||||
endif
|
endif
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
|
@ -756,8 +736,8 @@ module procedure mech_RGC_updateState
|
||||||
enddo; enddo;enddo; enddo
|
enddo; enddo;enddo; enddo
|
||||||
enddo interfaceLoop
|
enddo interfaceLoop
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugActive) then
|
if (debugHomog%extensive .and. prm%of_debug == of) then
|
||||||
write(6,'(1x,a20,i2)')'Penalty of grain: ',iGrain
|
print'(a,i2)', ' Penalty of grain: ',iGrain
|
||||||
print*, transpose(rPen(1:3,1:3,iGrain))
|
print*, transpose(rPen(1:3,1:3,iGrain))
|
||||||
endif
|
endif
|
||||||
#endif
|
#endif
|
||||||
|
@ -805,9 +785,8 @@ module procedure mech_RGC_updateState
|
||||||
gVol(i)*transpose(math_inv33(fDef(:,:,i)))
|
gVol(i)*transpose(math_inv33(fDef(:,:,i)))
|
||||||
|
|
||||||
#ifdef DEBUG
|
#ifdef DEBUG
|
||||||
if (debugHomog%extensive &
|
if (debugHomog%extensive .and. param(instance)%of_debug == of) then
|
||||||
.and. param(instance)%of_debug == of) then
|
print'(a,i2)',' Volume penalty of grain: ',i
|
||||||
write(6,'(1x,a30,i2)')'Volume penalty of grain: ',i
|
|
||||||
print*, transpose(vPen(:,:,i))
|
print*, transpose(vPen(:,:,i))
|
||||||
endif
|
endif
|
||||||
#endif
|
#endif
|
||||||
|
|
|
@ -37,10 +37,10 @@ module subroutine mech_isostrain_init
|
||||||
homog, &
|
homog, &
|
||||||
homogMech
|
homogMech
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- homogenization_mech_isostrain init -+>>>'
|
print'(/,a)', ' <<<+- homogenization_mech_isostrain init -+>>>'
|
||||||
|
|
||||||
Ninstance = count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)
|
Ninstance = count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
|
print'(a,i2)', ' # instances: ',Ninstance; flush(6)
|
||||||
|
|
||||||
allocate(param(Ninstance)) ! one container of parameters per instance
|
allocate(param(Ninstance)) ! one container of parameters per instance
|
||||||
|
|
||||||
|
|
|
@ -18,10 +18,10 @@ module subroutine mech_none_init
|
||||||
h, &
|
h, &
|
||||||
NofMyHomog
|
NofMyHomog
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- homogenization_mech_none init -+>>>'
|
print'(/,a)', ' <<<+- homogenization_mech_none init -+>>>'
|
||||||
|
|
||||||
Ninstance = count(homogenization_type == HOMOGENIZATION_NONE_ID)
|
Ninstance = count(homogenization_type == HOMOGENIZATION_NONE_ID)
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
|
print'(a,i2)', ' # instances: ',Ninstance; flush(6)
|
||||||
|
|
||||||
do h = 1, size(homogenization_type)
|
do h = 1, size(homogenization_type)
|
||||||
if (homogenization_type(h) /= HOMOGENIZATION_NONE_ID) cycle
|
if (homogenization_type(h) /= HOMOGENIZATION_NONE_ID) cycle
|
||||||
|
|
|
@ -45,12 +45,11 @@ module function kinematics_cleavage_opening_init(kinematics_length) result(myKin
|
||||||
kinematics, &
|
kinematics, &
|
||||||
kinematic_type
|
kinematic_type
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- kinematics_cleavage_opening init -+>>>'
|
print'(/,a)', ' <<<+- kinematics_cleavage_opening init -+>>>'
|
||||||
|
|
||||||
myKinematics = kinematics_active('cleavage_opening',kinematics_length)
|
myKinematics = kinematics_active('cleavage_opening',kinematics_length)
|
||||||
|
|
||||||
Ninstance = count(myKinematics)
|
Ninstance = count(myKinematics)
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
|
print'(a,i2)', ' # instances: ',Ninstance; flush(6)
|
||||||
if(Ninstance == 0) return
|
if(Ninstance == 0) return
|
||||||
|
|
||||||
phases => config_material%get('phase')
|
phases => config_material%get('phase')
|
||||||
|
|
|
@ -48,12 +48,11 @@ module function kinematics_slipplane_opening_init(kinematics_length) result(myKi
|
||||||
kinematics, &
|
kinematics, &
|
||||||
kinematic_type
|
kinematic_type
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- kinematics_slipplane init -+>>>'
|
print'(/,a)', ' <<<+- kinematics_slipplane init -+>>>'
|
||||||
|
|
||||||
myKinematics = kinematics_active('slipplane_opening',kinematics_length)
|
myKinematics = kinematics_active('slipplane_opening',kinematics_length)
|
||||||
|
|
||||||
Ninstance = count(myKinematics)
|
Ninstance = count(myKinematics)
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
|
print'(a,i2)', ' # instances: ',Ninstance; flush(6)
|
||||||
if(Ninstance == 0) return
|
if(Ninstance == 0) return
|
||||||
|
|
||||||
phases => config_material%get('phase')
|
phases => config_material%get('phase')
|
||||||
|
|
|
@ -38,12 +38,11 @@ module function kinematics_thermal_expansion_init(kinematics_length) result(myKi
|
||||||
kinematics, &
|
kinematics, &
|
||||||
kinematic_type
|
kinematic_type
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- kinematics_thermal_expansion init -+>>>'
|
print'(/,a)', ' <<<+- kinematics_thermal_expansion init -+>>>'
|
||||||
|
|
||||||
myKinematics = kinematics_active('thermal_expansion',kinematics_length)
|
myKinematics = kinematics_active('thermal_expansion',kinematics_length)
|
||||||
|
|
||||||
Ninstance = count(myKinematics)
|
Ninstance = count(myKinematics)
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
|
print'(a,i2)', ' # instances: ',Ninstance; flush(6)
|
||||||
if(Ninstance == 0) return
|
if(Ninstance == 0) return
|
||||||
|
|
||||||
phases => config_material%get('phase')
|
phases => config_material%get('phase')
|
||||||
|
|
|
@ -65,10 +65,10 @@ subroutine results_init(restart)
|
||||||
|
|
||||||
character(len=pStringLen) :: commandLine
|
character(len=pStringLen) :: commandLine
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- results init -+>>>'; flush(6)
|
print'(/,a)', ' <<<+- results init -+>>>'; flush(6)
|
||||||
|
|
||||||
write(6,'(/,a)') ' Diehl et al., Integrating Materials and Manufacturing Innovation 6(1):83–91, 2017'
|
print*, 'Diehl et al., Integrating Materials and Manufacturing Innovation 6(1):83–91, 2017'
|
||||||
write(6,'(a)') ' https://doi.org/10.1007/s40192-017-0084-5'
|
print*, 'https://doi.org/10.1007/s40192-017-0084-5'//IO_EOL
|
||||||
|
|
||||||
if(.not. restart) then
|
if(.not. restart) then
|
||||||
resultsFile = HDF5_openFile(trim(getSolverJobName())//'.hdf5','w',.true.)
|
resultsFile = HDF5_openFile(trim(getSolverJobName())//'.hdf5','w',.true.)
|
||||||
|
|
|
@ -49,12 +49,11 @@ module function source_damage_anisoBrittle_init(source_length) result(mySources)
|
||||||
integer, dimension(:), allocatable :: N_cl
|
integer, dimension(:), allocatable :: N_cl
|
||||||
character(len=pStringLen) :: extmsg = ''
|
character(len=pStringLen) :: extmsg = ''
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_damage_anisoBrittle init -+>>>'
|
print'(/,a)', ' <<<+- source_damage_anisoBrittle init -+>>>'
|
||||||
|
|
||||||
mySources = source_active('damage_anisoBrittle',source_length)
|
mySources = source_active('damage_anisoBrittle',source_length)
|
||||||
|
|
||||||
Ninstance = count(mySources)
|
Ninstance = count(mySources)
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
|
print'(a,i2)', ' # instances: ',Ninstance; flush(6)
|
||||||
if(Ninstance == 0) return
|
if(Ninstance == 0) return
|
||||||
|
|
||||||
phases => config_material%get('phase')
|
phases => config_material%get('phase')
|
||||||
|
|
|
@ -43,13 +43,11 @@ module function source_damage_anisoDuctile_init(source_length) result(mySources)
|
||||||
integer, dimension(:), allocatable :: N_sl
|
integer, dimension(:), allocatable :: N_sl
|
||||||
character(len=pStringLen) :: extmsg = ''
|
character(len=pStringLen) :: extmsg = ''
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_damage_anisoDuctile init -+>>>'
|
print'(/,a)', ' <<<+- source_damage_anisoDuctile init -+>>>'
|
||||||
|
|
||||||
mySources = source_active('damage_anisoDuctile',source_length)
|
mySources = source_active('damage_anisoDuctile',source_length)
|
||||||
|
|
||||||
Ninstance = count(mySources)
|
Ninstance = count(mySources)
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
|
print'(a,i2)', ' # instances: ',Ninstance; flush(6)
|
||||||
|
|
||||||
if(Ninstance == 0) return
|
if(Ninstance == 0) return
|
||||||
|
|
||||||
phases => config_material%get('phase')
|
phases => config_material%get('phase')
|
||||||
|
|
|
@ -39,12 +39,11 @@ module function source_damage_isoBrittle_init(source_length) result(mySources)
|
||||||
integer :: Ninstance,sourceOffset,NipcMyPhase,p
|
integer :: Ninstance,sourceOffset,NipcMyPhase,p
|
||||||
character(len=pStringLen) :: extmsg = ''
|
character(len=pStringLen) :: extmsg = ''
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_damage_isoBrittle init -+>>>'
|
print'(/,a)', ' <<<+- source_damage_isoBrittle init -+>>>'
|
||||||
|
|
||||||
mySources = source_active('damage_isoBrittle',source_length)
|
mySources = source_active('damage_isoBrittle',source_length)
|
||||||
|
|
||||||
Ninstance = count(mySources)
|
Ninstance = count(mySources)
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
|
print'(a,i2)', ' # instances: ',Ninstance; flush(6)
|
||||||
if(Ninstance == 0) return
|
if(Ninstance == 0) return
|
||||||
|
|
||||||
phases => config_material%get('phase')
|
phases => config_material%get('phase')
|
||||||
|
|
|
@ -41,12 +41,11 @@ module function source_damage_isoDuctile_init(source_length) result(mySources)
|
||||||
integer :: Ninstance,sourceOffset,NipcMyPhase,p
|
integer :: Ninstance,sourceOffset,NipcMyPhase,p
|
||||||
character(len=pStringLen) :: extmsg = ''
|
character(len=pStringLen) :: extmsg = ''
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_damage_isoDuctile init -+>>>'
|
print'(/,a)', ' <<<+- source_damage_isoDuctile init -+>>>'
|
||||||
|
|
||||||
mySources = source_active('damage_isoDuctile',source_length)
|
mySources = source_active('damage_isoDuctile',source_length)
|
||||||
|
|
||||||
Ninstance = count(mySources)
|
Ninstance = count(mySources)
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
|
print'(a,i2)', ' # instances: ',Ninstance; flush(6)
|
||||||
if(Ninstance == 0) return
|
if(Ninstance == 0) return
|
||||||
|
|
||||||
phases => config_material%get('phase')
|
phases => config_material%get('phase')
|
||||||
|
|
|
@ -37,12 +37,11 @@ module function source_thermal_dissipation_init(source_length) result(mySources)
|
||||||
src
|
src
|
||||||
integer :: Ninstance,sourceOffset,NipcMyPhase,p
|
integer :: Ninstance,sourceOffset,NipcMyPhase,p
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_thermal_dissipation init -+>>>'
|
print'(/,a)', ' <<<+- source_thermal_dissipation init -+>>>'
|
||||||
|
|
||||||
mySources = source_active('thermal_dissipation',source_length)
|
mySources = source_active('thermal_dissipation',source_length)
|
||||||
|
|
||||||
Ninstance = count(mySources)
|
Ninstance = count(mySources)
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
|
print'(a,i2)', ' # instances: ',Ninstance; flush(6)
|
||||||
if(Ninstance == 0) return
|
if(Ninstance == 0) return
|
||||||
|
|
||||||
phases => config_material%get('phase')
|
phases => config_material%get('phase')
|
||||||
|
|
|
@ -41,12 +41,11 @@ module function source_thermal_externalheat_init(source_length) result(mySources
|
||||||
src
|
src
|
||||||
integer :: Ninstance,sourceOffset,NipcMyPhase,p
|
integer :: Ninstance,sourceOffset,NipcMyPhase,p
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- source_thermal_externalHeat init -+>>>'
|
print'(/,a)', ' <<<+- source_thermal_externalHeat init -+>>>'
|
||||||
|
|
||||||
mySources = source_active('thermal_externalheat',source_length)
|
mySources = source_active('thermal_externalheat',source_length)
|
||||||
|
|
||||||
Ninstance = count(mySources)
|
Ninstance = count(mySources)
|
||||||
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
|
print'(a,i2)', ' # instances: ',Ninstance; flush(6)
|
||||||
if(Ninstance == 0) return
|
if(Ninstance == 0) return
|
||||||
|
|
||||||
phases => config_material%get('phase')
|
phases => config_material%get('phase')
|
||||||
|
|
Loading…
Reference in New Issue