Need only logical mask
'merge' substitutes multiplication with float mask
This commit is contained in:
parent
6367cb8fcb
commit
0a7d4f61ac
|
@ -210,8 +210,7 @@ program DAMASK_grid
|
||||||
temp_maskVector(j) = IO_stringValue(line,chunkPos,i+j) /= '*' ! true if not a *
|
temp_maskVector(j) = IO_stringValue(line,chunkPos,i+j) /= '*' ! true if not a *
|
||||||
if (temp_maskVector(j)) temp_valueVector(j) = IO_floatValue(line,chunkPos,i+j) ! read value where applicable
|
if (temp_maskVector(j)) temp_valueVector(j) = IO_floatValue(line,chunkPos,i+j) ! read value where applicable
|
||||||
enddo
|
enddo
|
||||||
newLoadCase%deformation%maskLogical = transpose(reshape(temp_maskVector,[ 3,3])) ! logical mask in 3x3 notation
|
newLoadCase%deformation%mask = transpose(reshape(temp_maskVector,[ 3,3])) ! mask in 3x3 notation
|
||||||
newLoadCase%deformation%maskFloat = merge(ones,zeros,newLoadCase%deformation%maskLogical) ! float (1.0/0.0) mask in 3x3 notation
|
|
||||||
newLoadCase%deformation%values = math_9to33(temp_valueVector) ! values in 3x3 notation
|
newLoadCase%deformation%values = math_9to33(temp_valueVector) ! values in 3x3 notation
|
||||||
case('p','stress', 's')
|
case('p','stress', 's')
|
||||||
temp_valueVector = 0.0_pReal
|
temp_valueVector = 0.0_pReal
|
||||||
|
@ -219,8 +218,7 @@ program DAMASK_grid
|
||||||
temp_maskVector(j) = IO_stringValue(line,chunkPos,i+j) /= '*' ! true if not an asterisk
|
temp_maskVector(j) = IO_stringValue(line,chunkPos,i+j) /= '*' ! true if not an asterisk
|
||||||
if (temp_maskVector(j)) temp_valueVector(j) = IO_floatValue(line,chunkPos,i+j) ! read value where applicable
|
if (temp_maskVector(j)) temp_valueVector(j) = IO_floatValue(line,chunkPos,i+j) ! read value where applicable
|
||||||
enddo
|
enddo
|
||||||
newLoadCase%stress%maskLogical = transpose(reshape(temp_maskVector,[ 3,3]))
|
newLoadCase%stress%mask = transpose(reshape(temp_maskVector,[ 3,3]))
|
||||||
newLoadCase%stress%maskFloat = merge(ones,zeros,newLoadCase%stress%maskLogical)
|
|
||||||
newLoadCase%stress%values = math_9to33(temp_valueVector)
|
newLoadCase%stress%values = math_9to33(temp_valueVector)
|
||||||
case('t','time','delta') ! increment time
|
case('t','time','delta') ! increment time
|
||||||
newLoadCase%time = IO_floatValue(line,chunkPos,i+1)
|
newLoadCase%time = IO_floatValue(line,chunkPos,i+1)
|
||||||
|
@ -268,8 +266,8 @@ program DAMASK_grid
|
||||||
print*, ' drop guessing along trajectory'
|
print*, ' drop guessing along trajectory'
|
||||||
if (newLoadCase%deformation%myType == 'l') then
|
if (newLoadCase%deformation%myType == 'l') then
|
||||||
do j = 1, 3
|
do j = 1, 3
|
||||||
if (any(newLoadCase%deformation%maskLogical(j,1:3) .eqv. .true.) .and. &
|
if (any(newLoadCase%deformation%mask(j,1:3) .eqv. .true.) .and. &
|
||||||
any(newLoadCase%deformation%maskLogical(j,1:3) .eqv. .false.)) errorID = 832 ! each row should be either fully or not at all defined
|
any(newLoadCase%deformation%mask(j,1:3) .eqv. .false.)) errorID = 832 ! each row should be either fully or not at all defined
|
||||||
enddo
|
enddo
|
||||||
print*, ' velocity gradient:'
|
print*, ' velocity gradient:'
|
||||||
else if (newLoadCase%deformation%myType == 'f') then
|
else if (newLoadCase%deformation%myType == 'f') then
|
||||||
|
@ -278,20 +276,19 @@ program DAMASK_grid
|
||||||
print*, ' deformation gradient rate:'
|
print*, ' deformation gradient rate:'
|
||||||
endif
|
endif
|
||||||
do i = 1, 3; do j = 1, 3
|
do i = 1, 3; do j = 1, 3
|
||||||
if(newLoadCase%deformation%maskLogical(i,j)) then
|
if(newLoadCase%deformation%mask(i,j)) then
|
||||||
write(6,'(2x,f12.7)',advance='no') newLoadCase%deformation%values(i,j)
|
write(6,'(2x,f12.7)',advance='no') newLoadCase%deformation%values(i,j)
|
||||||
else
|
else
|
||||||
write(6,'(2x,12a)',advance='no') ' * '
|
write(6,'(2x,12a)',advance='no') ' * '
|
||||||
endif
|
endif
|
||||||
enddo; write(6,'(/)',advance='no')
|
enddo; write(6,'(/)',advance='no')
|
||||||
enddo
|
enddo
|
||||||
if (any(newLoadCase%stress%maskLogical .eqv. &
|
if (any(newLoadCase%stress%mask .eqv. newLoadCase%deformation%mask)) errorID = 831 ! exclusive or masking only
|
||||||
newLoadCase%deformation%maskLogical)) errorID = 831 ! exclusive or masking only
|
if (any(newLoadCase%stress%mask .and. transpose(newLoadCase%stress%mask) .and. (math_I3<1))) &
|
||||||
if (any(newLoadCase%stress%maskLogical .and. transpose(newLoadCase%stress%maskLogical) &
|
errorID = 838 ! no rotation is allowed by stress BC
|
||||||
.and. (math_I3<1))) errorID = 838 ! no rotation is allowed by stress BC
|
|
||||||
print*, ' stress / GPa:'
|
print*, ' stress / GPa:'
|
||||||
do i = 1, 3; do j = 1, 3
|
do i = 1, 3; do j = 1, 3
|
||||||
if(newLoadCase%stress%maskLogical(i,j)) then
|
if(newLoadCase%stress%mask(i,j)) then
|
||||||
write(6,'(2x,f12.7)',advance='no') newLoadCase%stress%values(i,j)*1e-9_pReal
|
write(6,'(2x,f12.7)',advance='no') newLoadCase%stress%values(i,j)*1e-9_pReal
|
||||||
else
|
else
|
||||||
write(6,'(2x,12a)',advance='no') ' * '
|
write(6,'(2x,12a)',advance='no') ' * '
|
||||||
|
|
|
@ -25,8 +25,6 @@ module grid_mech_FEM
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! derived types
|
|
||||||
type(tSolutionParams) :: params
|
type(tSolutionParams) :: params
|
||||||
|
|
||||||
type :: tNumerics
|
type :: tNumerics
|
||||||
|
@ -282,7 +280,7 @@ function grid_mech_FEM_solution(incInfoIn) result(solution)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! update stiffness (and gamma operator)
|
! update stiffness (and gamma operator)
|
||||||
S = utilities_maskedCompliance(params%rotation_BC,params%stress_mask>.5_pReal,C_volAvg)
|
S = utilities_maskedCompliance(params%rotation_BC,params%stress_mask,C_volAvg)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! solve BVP
|
! solve BVP
|
||||||
|
@ -326,7 +324,7 @@ subroutine grid_mech_FEM_forward(cutBack,guess,timeinc,timeinc_old,loadCaseTime,
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! set module wide available data
|
! set module wide available data
|
||||||
params%stress_mask = stress_BC%maskFloat
|
params%stress_mask = stress_BC%mask
|
||||||
params%rotation_BC = rotation_BC
|
params%rotation_BC = rotation_BC
|
||||||
params%timeinc = timeinc
|
params%timeinc = timeinc
|
||||||
params%timeincOld = timeinc_old
|
params%timeincOld = timeinc_old
|
||||||
|
@ -340,20 +338,20 @@ subroutine grid_mech_FEM_forward(cutBack,guess,timeinc,timeinc_old,loadCaseTime,
|
||||||
else
|
else
|
||||||
C_volAvgLastInc = C_volAvg
|
C_volAvgLastInc = C_volAvg
|
||||||
|
|
||||||
F_aimDot = merge(stress_BC%maskFloat*(F_aim-F_aim_lastInc)/timeinc_old, 0.0_pReal, guess)
|
F_aimDot = merge(merge((F_aim-F_aim_lastInc)/timeinc_old,0.0_pReal,stress_BC%mask), 0.0_pReal, guess)
|
||||||
F_aim_lastInc = F_aim
|
F_aim_lastInc = F_aim
|
||||||
|
|
||||||
!-----------------------------------------------------------------------------------------------
|
!-----------------------------------------------------------------------------------------------
|
||||||
! calculate rate for aim
|
! calculate rate for aim
|
||||||
if (deformation_BC%myType=='l') then ! calculate F_aimDot from given L and current F
|
if (deformation_BC%myType=='l') then ! calculate F_aimDot from given L and current F
|
||||||
F_aimDot = &
|
F_aimDot = F_aimDot &
|
||||||
F_aimDot + deformation_BC%maskFloat * matmul(deformation_BC%values, F_aim_lastInc)
|
+ merge(matmul(deformation_BC%values, F_aim_lastInc),.0_pReal,deformation_BC%mask)
|
||||||
elseif(deformation_BC%myType=='fdot') then ! F_aimDot is prescribed
|
elseif(deformation_BC%myType=='fdot') then ! F_aimDot is prescribed
|
||||||
F_aimDot = &
|
F_aimDot = F_aimDot &
|
||||||
F_aimDot + deformation_BC%maskFloat * deformation_BC%values
|
+ merge(deformation_BC%values,.0_pReal,deformation_BC%mask)
|
||||||
elseif (deformation_BC%myType=='f') then ! aim at end of load case is prescribed
|
elseif (deformation_BC%myType=='f') then ! aim at end of load case is prescribed
|
||||||
F_aimDot = &
|
F_aimDot = F_aimDot &
|
||||||
F_aimDot + deformation_BC%maskFloat * (deformation_BC%values - F_aim_lastInc)/loadCaseTime
|
+ merge((deformation_BC%values - F_aim_lastInc)/loadCaseTime,.0_pReal,deformation_BC%mask)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
if (guess) then
|
if (guess) then
|
||||||
|
@ -374,9 +372,9 @@ subroutine grid_mech_FEM_forward(cutBack,guess,timeinc,timeinc_old,loadCaseTime,
|
||||||
! update average and local deformation gradients
|
! update average and local deformation gradients
|
||||||
F_aim = F_aim_lastInc + F_aimDot * timeinc
|
F_aim = F_aim_lastInc + F_aimDot * timeinc
|
||||||
if (stress_BC%myType=='p') then
|
if (stress_BC%myType=='p') then
|
||||||
P_aim = P_aim + stress_BC%maskFloat*(stress_BC%values - P_aim)/loadCaseTime*timeinc
|
P_aim = P_aim + merge((stress_BC%values - P_aim)/loadCaseTime*timeinc,.0_pReal,stress_BC%mask)
|
||||||
elseif (stress_BC%myType=='pdot') then !UNTESTED
|
elseif (stress_BC%myType=='pdot') then !UNTESTED
|
||||||
P_aim = P_aim + stress_BC%maskFloat*stress_BC%values*timeinc
|
P_aim = P_aim + merge(stress_BC%values*timeinc,.0_pReal,stress_BC%mask)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
call VecAXPY(solution_current,timeinc,solution_rate,ierr); CHKERRQ(ierr)
|
call VecAXPY(solution_current,timeinc,solution_rate,ierr); CHKERRQ(ierr)
|
||||||
|
@ -543,7 +541,7 @@ subroutine formResidual(da_local,x_local, &
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! stress BC handling
|
! stress BC handling
|
||||||
F_aim = F_aim - math_mul3333xx33(S, P_av - P_aim) ! S = 0.0 for no bc
|
F_aim = F_aim - math_mul3333xx33(S, P_av - P_aim) ! S = 0.0 for no bc
|
||||||
err_BC = maxval(abs(params%stress_mask * (P_av - P_aim))) ! mask = 0.0 when no stress bc
|
err_BC = maxval(abs(merge(P_av - P_aim,.0_pReal,params%stress_mask)))
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! constructing residual
|
! constructing residual
|
||||||
|
|
|
@ -24,8 +24,6 @@ module grid_mech_spectral_basic
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! derived types
|
|
||||||
type(tSolutionParams) :: params
|
type(tSolutionParams) :: params
|
||||||
|
|
||||||
type :: tNumerics
|
type :: tNumerics
|
||||||
|
@ -247,7 +245,7 @@ function grid_mech_spectral_basic_solution(incInfoIn) result(solution)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! update stiffness (and gamma operator)
|
! update stiffness (and gamma operator)
|
||||||
S = utilities_maskedCompliance(params%rotation_BC,params%stress_mask>.5_pReal,C_volAvg)
|
S = utilities_maskedCompliance(params%rotation_BC,params%stress_mask,C_volAvg)
|
||||||
if(num%update_gamma) call utilities_updateGamma(C_minMaxAvg)
|
if(num%update_gamma) call utilities_updateGamma(C_minMaxAvg)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -291,7 +289,7 @@ subroutine grid_mech_spectral_basic_forward(cutBack,guess,timeinc,timeinc_old,lo
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! set module wide available data
|
! set module wide available data
|
||||||
params%stress_mask = stress_BC%maskFloat
|
params%stress_mask = stress_BC%mask
|
||||||
params%rotation_BC = rotation_BC
|
params%rotation_BC = rotation_BC
|
||||||
params%timeinc = timeinc
|
params%timeinc = timeinc
|
||||||
params%timeincOld = timeinc_old
|
params%timeincOld = timeinc_old
|
||||||
|
@ -305,20 +303,20 @@ subroutine grid_mech_spectral_basic_forward(cutBack,guess,timeinc,timeinc_old,lo
|
||||||
C_volAvgLastInc = C_volAvg
|
C_volAvgLastInc = C_volAvg
|
||||||
C_minMaxAvgLastInc = C_minMaxAvg
|
C_minMaxAvgLastInc = C_minMaxAvg
|
||||||
|
|
||||||
F_aimDot = merge(stress_BC%maskFloat*(F_aim-F_aim_lastInc)/timeinc_old, 0.0_pReal, guess)
|
F_aimDot = merge(merge((F_aim-F_aim_lastInc)/timeinc_old,0.0_pReal,stress_BC%mask), 0.0_pReal, guess)
|
||||||
F_aim_lastInc = F_aim
|
F_aim_lastInc = F_aim
|
||||||
|
|
||||||
!-----------------------------------------------------------------------------------------------
|
!-----------------------------------------------------------------------------------------------
|
||||||
! calculate rate for aim
|
! calculate rate for aim
|
||||||
if (deformation_BC%myType=='l') then ! calculate F_aimDot from given L and current F
|
if (deformation_BC%myType=='l') then ! calculate F_aimDot from given L and current F
|
||||||
F_aimDot = &
|
F_aimDot = F_aimDot &
|
||||||
F_aimDot + deformation_BC%maskFloat * matmul(deformation_BC%values, F_aim_lastInc)
|
+ merge(matmul(deformation_BC%values, F_aim_lastInc),.0_pReal,deformation_BC%mask)
|
||||||
elseif(deformation_BC%myType=='fdot') then ! F_aimDot is prescribed
|
elseif(deformation_BC%myType=='fdot') then ! F_aimDot is prescribed
|
||||||
F_aimDot = &
|
F_aimDot = F_aimDot &
|
||||||
F_aimDot + deformation_BC%maskFloat * deformation_BC%values
|
+ merge(deformation_BC%values,.0_pReal,deformation_BC%mask)
|
||||||
elseif (deformation_BC%myType=='f') then ! aim at end of load case is prescribed
|
elseif (deformation_BC%myType=='f') then ! aim at end of load case is prescribed
|
||||||
F_aimDot = &
|
F_aimDot = F_aimDot &
|
||||||
F_aimDot + deformation_BC%maskFloat * (deformation_BC%values - F_aim_lastInc)/loadCaseTime
|
+ merge((deformation_BC%values - F_aim_lastInc)/loadCaseTime,.0_pReal,deformation_BC%mask)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
Fdot = utilities_calculateRate(guess, &
|
Fdot = utilities_calculateRate(guess, &
|
||||||
|
@ -333,9 +331,9 @@ subroutine grid_mech_spectral_basic_forward(cutBack,guess,timeinc,timeinc_old,lo
|
||||||
! update average and local deformation gradients
|
! update average and local deformation gradients
|
||||||
F_aim = F_aim_lastInc + F_aimDot * timeinc
|
F_aim = F_aim_lastInc + F_aimDot * timeinc
|
||||||
if (stress_BC%myType=='p') then
|
if (stress_BC%myType=='p') then
|
||||||
P_aim = P_aim + stress_BC%maskFloat*(stress_BC%values - P_aim)/loadCaseTime*timeinc
|
P_aim = P_aim + merge((stress_BC%values - P_aim)/loadCaseTime*timeinc,.0_pReal,stress_BC%mask)
|
||||||
elseif (stress_BC%myType=='pdot') then !UNTESTED
|
elseif (stress_BC%myType=='pdot') then !UNTESTED
|
||||||
P_aim = P_aim + stress_BC%maskFloat*stress_BC%values*timeinc
|
P_aim = P_aim + merge(stress_BC%values*timeinc,.0_pReal,stress_BC%mask)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
F = reshape(utilities_forwardField(timeinc,F_lastInc,Fdot, & ! estimate of F at end of time+timeinc that matches rotated F_aim on average
|
F = reshape(utilities_forwardField(timeinc,F_lastInc,Fdot, & ! estimate of F at end of time+timeinc that matches rotated F_aim on average
|
||||||
|
@ -491,7 +489,7 @@ subroutine formResidual(in, F, &
|
||||||
! stress BC handling
|
! stress BC handling
|
||||||
deltaF_aim = math_mul3333xx33(S, P_av - P_aim) ! S = 0.0 for no bc
|
deltaF_aim = math_mul3333xx33(S, P_av - P_aim) ! S = 0.0 for no bc
|
||||||
F_aim = F_aim - deltaF_aim
|
F_aim = F_aim - deltaF_aim
|
||||||
err_BC = maxval(abs(params%stress_mask * (P_av - P_aim))) ! mask = 0.0 when no stress bc
|
err_BC = maxval(abs(merge(P_av - P_aim,.0_pReal,params%stress_mask)))
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! updated deformation gradient using fix point algorithm of basic scheme
|
! updated deformation gradient using fix point algorithm of basic scheme
|
||||||
|
|
|
@ -24,8 +24,6 @@ module grid_mech_spectral_polarisation
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
|
||||||
! derived types
|
|
||||||
type(tSolutionParams) :: params
|
type(tSolutionParams) :: params
|
||||||
|
|
||||||
type :: tNumerics
|
type :: tNumerics
|
||||||
|
@ -275,7 +273,7 @@ function grid_mech_spectral_polarisation_solution(incInfoIn) result(solution)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! update stiffness (and gamma operator)
|
! update stiffness (and gamma operator)
|
||||||
S = utilities_maskedCompliance(params%rotation_BC,params%stress_mask>.5_pReal,C_volAvg)
|
S = utilities_maskedCompliance(params%rotation_BC,params%stress_mask,C_volAvg)
|
||||||
if(num%update_gamma) then
|
if(num%update_gamma) then
|
||||||
call utilities_updateGamma(C_minMaxAvg)
|
call utilities_updateGamma(C_minMaxAvg)
|
||||||
C_scale = C_minMaxAvg
|
C_scale = C_minMaxAvg
|
||||||
|
@ -325,7 +323,7 @@ subroutine grid_mech_spectral_polarisation_forward(cutBack,guess,timeinc,timeinc
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! set module wide available data
|
! set module wide available data
|
||||||
params%stress_mask = stress_BC%maskFloat
|
params%stress_mask = stress_BC%mask
|
||||||
params%rotation_BC = rotation_BC
|
params%rotation_BC = rotation_BC
|
||||||
params%timeinc = timeinc
|
params%timeinc = timeinc
|
||||||
params%timeincOld = timeinc_old
|
params%timeincOld = timeinc_old
|
||||||
|
@ -341,20 +339,20 @@ subroutine grid_mech_spectral_polarisation_forward(cutBack,guess,timeinc,timeinc
|
||||||
C_volAvgLastInc = C_volAvg
|
C_volAvgLastInc = C_volAvg
|
||||||
C_minMaxAvgLastInc = C_minMaxAvg
|
C_minMaxAvgLastInc = C_minMaxAvg
|
||||||
|
|
||||||
F_aimDot = merge(stress_BC%maskFloat*(F_aim-F_aim_lastInc)/timeinc_old, 0.0_pReal, guess)
|
F_aimDot = merge(merge((F_aim-F_aim_lastInc)/timeinc_old,0.0_pReal,stress_BC%mask), 0.0_pReal, guess)
|
||||||
F_aim_lastInc = F_aim
|
F_aim_lastInc = F_aim
|
||||||
|
|
||||||
!-----------------------------------------------------------------------------------------------
|
!-----------------------------------------------------------------------------------------------
|
||||||
! calculate rate for aim
|
! calculate rate for aim
|
||||||
if (deformation_BC%myType=='l') then ! calculate F_aimDot from given L and current F
|
if (deformation_BC%myType=='l') then ! calculate F_aimDot from given L and current F
|
||||||
F_aimDot = &
|
F_aimDot = F_aimDot &
|
||||||
F_aimDot + deformation_BC%maskFloat * matmul(deformation_BC%values, F_aim_lastInc)
|
+ merge(matmul(deformation_BC%values, F_aim_lastInc),.0_pReal,deformation_BC%mask)
|
||||||
elseif(deformation_BC%myType=='fdot') then ! F_aimDot is prescribed
|
elseif(deformation_BC%myType=='fdot') then ! F_aimDot is prescribed
|
||||||
F_aimDot = &
|
F_aimDot = F_aimDot &
|
||||||
F_aimDot + deformation_BC%maskFloat * deformation_BC%values
|
+ merge(deformation_BC%values,.0_pReal,deformation_BC%mask)
|
||||||
elseif (deformation_BC%myType=='f') then ! aim at end of load case is prescribed
|
elseif (deformation_BC%myType=='f') then ! aim at end of load case is prescribed
|
||||||
F_aimDot = &
|
F_aimDot = F_aimDot &
|
||||||
F_aimDot + deformation_BC%maskFloat * (deformation_BC%values - F_aim_lastInc)/loadCaseTime
|
+ merge((deformation_BC%values - F_aim_lastInc)/loadCaseTime,.0_pReal,deformation_BC%mask)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
Fdot = utilities_calculateRate(guess, &
|
Fdot = utilities_calculateRate(guess, &
|
||||||
|
@ -373,9 +371,9 @@ subroutine grid_mech_spectral_polarisation_forward(cutBack,guess,timeinc,timeinc
|
||||||
! update average and local deformation gradients
|
! update average and local deformation gradients
|
||||||
F_aim = F_aim_lastInc + F_aimDot * timeinc
|
F_aim = F_aim_lastInc + F_aimDot * timeinc
|
||||||
if (stress_BC%myType=='p') then
|
if (stress_BC%myType=='p') then
|
||||||
P_aim = P_aim + stress_BC%maskFloat*(stress_BC%values - P_aim)/loadCaseTime*timeinc
|
P_aim = P_aim + merge((stress_BC%values - P_aim)/loadCaseTime*timeinc,.0_pReal,stress_BC%mask)
|
||||||
elseif (stress_BC%myType=='pdot') then !UNTESTED
|
elseif (stress_BC%myType=='pdot') then !UNTESTED
|
||||||
P_aim = P_aim + stress_BC%maskFloat*stress_BC%values*timeinc
|
P_aim = P_aim + merge(stress_BC%values*timeinc,.0_pReal,stress_BC%mask)
|
||||||
endif
|
endif
|
||||||
|
|
||||||
F = reshape(utilities_forwardField(timeinc,F_lastInc,Fdot, & ! estimate of F at end of time+timeinc that matches rotated F_aim on average
|
F = reshape(utilities_forwardField(timeinc,F_lastInc,Fdot, & ! estimate of F at end of time+timeinc that matches rotated F_aim on average
|
||||||
|
@ -593,9 +591,9 @@ subroutine formResidual(in, FandF_tau, &
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! stress BC handling
|
! stress BC handling
|
||||||
F_aim = F_aim - math_mul3333xx33(S, P_av - P_aim) ! S = 0.0 for no bc
|
F_aim = F_aim - math_mul3333xx33(S, P_av - P_aim) ! S = 0.0 for no bc
|
||||||
err_BC = maxval(abs((1.0_pReal-params%stress_mask) * math_mul3333xx33(C_scale,F_aim &
|
err_BC = maxval(abs(merge(P_av-P_aim, &
|
||||||
-params%rotation_BC%rotate(F_av)) + &
|
math_mul3333xx33(C_scale,F_aim-params%rotation_BC%rotate(F_av)),&
|
||||||
params%stress_mask * (P_av-P_aim))) ! mask = 0.0 for no bc
|
params%stress_mask)))
|
||||||
! calculate divergence
|
! calculate divergence
|
||||||
tensorField_real = 0.0_pReal
|
tensorField_real = 0.0_pReal
|
||||||
tensorField_real(1:3,1:3,1:grid(1),1:grid(2),1:grid3) = residual_F !< stress field in disguise
|
tensorField_real(1:3,1:3,1:grid(1),1:grid(2),1:grid3) = residual_F !< stress field in disguise
|
||||||
|
|
|
@ -82,9 +82,8 @@ module spectral_utilities
|
||||||
end type tSolutionState
|
end type tSolutionState
|
||||||
|
|
||||||
type, public :: tBoundaryCondition !< set of parameters defining a boundary condition
|
type, public :: tBoundaryCondition !< set of parameters defining a boundary condition
|
||||||
real(pReal), dimension(3,3) :: values = 0.0_pReal, &
|
real(pReal), dimension(3,3) :: values = 0.0_pReal
|
||||||
maskFloat = 0.0_pReal
|
logical, dimension(3,3) :: mask = .false.
|
||||||
logical, dimension(3,3) :: maskLogical = .false.
|
|
||||||
character(len=pStringLen) :: myType = 'None'
|
character(len=pStringLen) :: myType = 'None'
|
||||||
end type tBoundaryCondition
|
end type tBoundaryCondition
|
||||||
|
|
||||||
|
@ -101,11 +100,11 @@ module spectral_utilities
|
||||||
integer(kind(FIELD_UNDEFINED_ID)), allocatable :: ID(:)
|
integer(kind(FIELD_UNDEFINED_ID)), allocatable :: ID(:)
|
||||||
end type tLoadCase
|
end type tLoadCase
|
||||||
|
|
||||||
type, public :: tSolutionParams !< @todo use here the type definition for a full loadcase
|
type, public :: tSolutionParams
|
||||||
real(pReal), dimension(3,3) :: stress_mask, stress_BC
|
real(pReal), dimension(3,3) :: stress_BC
|
||||||
|
logical, dimension(3,3) :: stress_mask
|
||||||
type(rotation) :: rotation_BC
|
type(rotation) :: rotation_BC
|
||||||
real(pReal) :: timeinc
|
real(pReal) :: timeinc, timeincOld
|
||||||
real(pReal) :: timeincOld
|
|
||||||
end type tSolutionParams
|
end type tSolutionParams
|
||||||
|
|
||||||
type :: tNumerics
|
type :: tNumerics
|
||||||
|
|
Loading…
Reference in New Issue