save information on slip systems for reproducibility
This commit is contained in:
parent
a891fe4281
commit
07fb7f8fdf
|
@ -402,7 +402,7 @@ module subroutine plastic_dislotungsten_results(ph,group)
|
||||||
|
|
||||||
associate(prm => param(ph), stt => state(ph), dst => dependentState(ph))
|
associate(prm => param(ph), stt => state(ph), dst => dependentState(ph))
|
||||||
|
|
||||||
outputsLoop: do ou = 1,size(prm%output)
|
do ou = 1,size(prm%output)
|
||||||
|
|
||||||
select case(trim(prm%output(ou)))
|
select case(trim(prm%output(ou)))
|
||||||
|
|
||||||
|
@ -423,7 +423,7 @@ module subroutine plastic_dislotungsten_results(ph,group)
|
||||||
'threshold stress for slip','Pa')
|
'threshold stress for slip','Pa')
|
||||||
end select
|
end select
|
||||||
|
|
||||||
enddo outputsLoop
|
enddo
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
|
|
|
@ -30,6 +30,8 @@ submodule(phase:plastic) kinehardening
|
||||||
nonSchmidActive = .false.
|
nonSchmidActive = .false.
|
||||||
character(len=pStringLen), allocatable, dimension(:) :: &
|
character(len=pStringLen), allocatable, dimension(:) :: &
|
||||||
output
|
output
|
||||||
|
character(len=:), allocatable, dimension(:) :: &
|
||||||
|
systems_sl
|
||||||
end type tParameters
|
end type tParameters
|
||||||
|
|
||||||
type :: tKinehardeningState
|
type :: tKinehardeningState
|
||||||
|
@ -40,7 +42,6 @@ submodule(phase:plastic) kinehardening
|
||||||
gamma, & !< accumulated (absolute) shear
|
gamma, & !< accumulated (absolute) shear
|
||||||
gamma_0, & !< accumulated shear at last switch of stress sense
|
gamma_0, & !< accumulated shear at last switch of stress sense
|
||||||
sgn_gamma !< sense of acting shear stress (-1 or +1)
|
sgn_gamma !< sense of acting shear stress (-1 or +1)
|
||||||
|
|
||||||
end type tKinehardeningState
|
end type tKinehardeningState
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
@ -113,6 +114,7 @@ module function plastic_kinehardening_init() result(myPlasticity)
|
||||||
N_sl = pl%get_as1dInt('N_sl',defaultVal=emptyIntArray)
|
N_sl = pl%get_as1dInt('N_sl',defaultVal=emptyIntArray)
|
||||||
prm%sum_N_sl = sum(abs(N_sl))
|
prm%sum_N_sl = sum(abs(N_sl))
|
||||||
slipActive: if (prm%sum_N_sl > 0) then
|
slipActive: if (prm%sum_N_sl > 0) then
|
||||||
|
prm%systems_sl = lattice_labels_slip(N_sl,phase_lattice(ph))
|
||||||
prm%P = lattice_SchmidMatrix_slip(N_sl,phase_lattice(ph),phase_cOverA(ph))
|
prm%P = lattice_SchmidMatrix_slip(N_sl,phase_lattice(ph),phase_cOverA(ph))
|
||||||
|
|
||||||
if (phase_lattice(ph) == 'cI') then
|
if (phase_lattice(ph) == 'cI') then
|
||||||
|
@ -351,31 +353,37 @@ module subroutine plastic_kinehardening_results(ph,group)
|
||||||
integer, intent(in) :: ph
|
integer, intent(in) :: ph
|
||||||
character(len=*), intent(in) :: group
|
character(len=*), intent(in) :: group
|
||||||
|
|
||||||
integer :: o
|
integer :: ou
|
||||||
|
|
||||||
|
|
||||||
associate(prm => param(ph), stt => state(ph))
|
associate(prm => param(ph), stt => state(ph))
|
||||||
outputsLoop: do o = 1,size(prm%output)
|
|
||||||
select case(trim(prm%output(o)))
|
do ou = 1,size(prm%output)
|
||||||
case ('xi')
|
|
||||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%xi,group,trim(prm%output(o)), &
|
select case(trim(prm%output(ou)))
|
||||||
'resistance against plastic slip','Pa')
|
|
||||||
case ('chi')
|
case ('xi')
|
||||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%chi,group,trim(prm%output(o)), &
|
call results_writePhaseState(stt%xi,group,trim(prm%output(ou)),prm%systems_sl, &
|
||||||
'back stress','Pa')
|
'resistance against plastic slip','Pa')
|
||||||
case ('sgn(gamma)')
|
case ('chi')
|
||||||
if(prm%sum_N_sl>0) call results_writeDataset(int(stt%sgn_gamma),group,trim(prm%output(o)), &
|
call results_writePhaseState(stt%chi,group,trim(prm%output(ou)),prm%systems_sl, &
|
||||||
'sense of shear','1')
|
'back stress','Pa')
|
||||||
case ('chi_0')
|
case ('sgn(gamma)')
|
||||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%chi_0,group,trim(prm%output(o)), &
|
call results_writePhaseState(int(stt%sgn_gamma),group,trim(prm%output(ou)),prm%systems_sl, &
|
||||||
'back stress at last switch of stress sense','Pa')
|
'sense of shear','1')
|
||||||
case ('gamma_0')
|
case ('chi_0')
|
||||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%gamma_0,group,trim(prm%output(o)), &
|
call results_writePhaseState(stt%chi_0,group,trim(prm%output(ou)),prm%systems_sl, &
|
||||||
'plastic shear at last switch of stress sense','1')
|
'back stress at last switch of stress sense','Pa')
|
||||||
case ('gamma')
|
case ('gamma_0')
|
||||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%gamma,group,trim(prm%output(o)), &
|
call results_writePhaseState(stt%gamma_0,group,trim(prm%output(ou)),prm%systems_sl, &
|
||||||
'plastic shear','1')
|
'plastic shear at last switch of stress sense','1')
|
||||||
end select
|
case ('gamma')
|
||||||
enddo outputsLoop
|
call results_writePhaseState(stt%gamma,group,trim(prm%output(ou)),prm%systems_sl, &
|
||||||
|
'plastic shear','1')
|
||||||
|
end select
|
||||||
|
|
||||||
|
enddo
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
end subroutine plastic_kinehardening_results
|
end subroutine plastic_kinehardening_results
|
||||||
|
|
|
@ -1474,62 +1474,62 @@ module subroutine plastic_nonlocal_results(ph,group)
|
||||||
|
|
||||||
do ou = 1,size(prm%output)
|
do ou = 1,size(prm%output)
|
||||||
|
|
||||||
select case(trim(prm%output(ou)))
|
select case(trim(prm%output(ou)))
|
||||||
|
|
||||||
case('rho_u_ed_pos')
|
case('rho_u_ed_pos')
|
||||||
call results_writePhaseState(stt%rho_sgl_mob_edg_pos,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%rho_sgl_mob_edg_pos,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'positive mobile edge density','1/m²')
|
'positive mobile edge density','1/m²')
|
||||||
case('rho_b_ed_pos')
|
case('rho_b_ed_pos')
|
||||||
call results_writePhaseState(stt%rho_sgl_imm_edg_pos,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%rho_sgl_imm_edg_pos,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'positive immobile edge density','1/m²')
|
'positive immobile edge density','1/m²')
|
||||||
case('rho_u_ed_neg')
|
case('rho_u_ed_neg')
|
||||||
call results_writePhaseState(stt%rho_sgl_mob_edg_neg,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%rho_sgl_mob_edg_neg,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'negative mobile edge density','1/m²')
|
'negative mobile edge density','1/m²')
|
||||||
case('rho_b_ed_neg')
|
case('rho_b_ed_neg')
|
||||||
call results_writePhaseState(stt%rho_sgl_imm_edg_neg,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%rho_sgl_imm_edg_neg,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'negative immobile edge density','1/m²')
|
'negative immobile edge density','1/m²')
|
||||||
case('rho_d_ed')
|
case('rho_d_ed')
|
||||||
call results_writePhaseState(stt%rho_dip_edg,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%rho_dip_edg,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'edge dipole density','1/m²')
|
'edge dipole density','1/m²')
|
||||||
case('rho_u_sc_pos')
|
case('rho_u_sc_pos')
|
||||||
call results_writePhaseState(stt%rho_sgl_mob_scr_pos,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%rho_sgl_mob_scr_pos,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'positive mobile screw density','1/m²')
|
'positive mobile screw density','1/m²')
|
||||||
case('rho_b_sc_pos')
|
case('rho_b_sc_pos')
|
||||||
call results_writePhaseState(stt%rho_sgl_imm_scr_pos,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%rho_sgl_imm_scr_pos,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'positive immobile screw density','1/m²')
|
'positive immobile screw density','1/m²')
|
||||||
case('rho_u_sc_neg')
|
case('rho_u_sc_neg')
|
||||||
call results_writePhaseState(stt%rho_sgl_mob_scr_neg,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%rho_sgl_mob_scr_neg,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'negative mobile screw density','1/m²')
|
'negative mobile screw density','1/m²')
|
||||||
case('rho_b_sc_neg')
|
case('rho_b_sc_neg')
|
||||||
call results_writePhaseState(stt%rho_sgl_imm_scr_neg,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%rho_sgl_imm_scr_neg,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'negative immobile screw density','1/m²')
|
'negative immobile screw density','1/m²')
|
||||||
case('rho_d_sc')
|
case('rho_d_sc')
|
||||||
call results_writePhaseState(stt%rho_dip_scr,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%rho_dip_scr,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'screw dipole density','1/m²')
|
'screw dipole density','1/m²')
|
||||||
case('rho_f')
|
case('rho_f')
|
||||||
call results_writePhaseState(stt%rho_forest,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%rho_forest,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'forest density','1/m²')
|
'forest density','1/m²')
|
||||||
case('v_ed_pos')
|
case('v_ed_pos')
|
||||||
call results_writePhaseState(stt%v_edg_pos,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%v_edg_pos,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'positive edge velocity','m/s')
|
'positive edge velocity','m/s')
|
||||||
case('v_ed_neg')
|
case('v_ed_neg')
|
||||||
call results_writePhaseState(stt%v_edg_neg,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%v_edg_neg,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'negative edge velocity','m/s')
|
'negative edge velocity','m/s')
|
||||||
case('v_sc_pos')
|
case('v_sc_pos')
|
||||||
call results_writePhaseState(stt%v_scr_pos,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%v_scr_pos,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'positive srew velocity','m/s')
|
'positive srew velocity','m/s')
|
||||||
case('v_sc_neg')
|
case('v_sc_neg')
|
||||||
call results_writePhaseState(stt%v_scr_neg,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%v_scr_neg,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'negative screw velocity','m/s')
|
'negative screw velocity','m/s')
|
||||||
case('gamma')
|
case('gamma')
|
||||||
call results_writePhaseState(stt%gamma,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(stt%gamma,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'plastic shear','1')
|
'plastic shear','1')
|
||||||
case('tau_pass')
|
case('tau_pass')
|
||||||
call results_writePhaseState(dst%tau_pass,group,trim(prm%output(ou)), prm%systems_sl, &
|
call results_writePhaseState(dst%tau_pass,group,trim(prm%output(ou)), prm%systems_sl, &
|
||||||
'passing stress for slip','Pa')
|
'passing stress for slip','Pa')
|
||||||
end select
|
end select
|
||||||
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end associate
|
end associate
|
||||||
|
|
||||||
|
|
|
@ -33,6 +33,11 @@ module results
|
||||||
module procedure results_writeVectorDataset_int
|
module procedure results_writeVectorDataset_int
|
||||||
end interface results_writeDataset
|
end interface results_writeDataset
|
||||||
|
|
||||||
|
interface results_writePhaseState
|
||||||
|
module procedure results_writePhaseState_real
|
||||||
|
module procedure results_writePhaseState_int
|
||||||
|
end interface results_writePhaseState
|
||||||
|
|
||||||
interface results_addAttribute
|
interface results_addAttribute
|
||||||
module procedure results_addAttribute_str
|
module procedure results_addAttribute_str
|
||||||
module procedure results_addAttribute_int
|
module procedure results_addAttribute_int
|
||||||
|
@ -361,7 +366,7 @@ end subroutine results_writeVectorDataset_real
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief Store real vector dataset with associated metadata for slip
|
!> @brief Store real vector dataset with associated metadata for slip
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine results_writePhaseState(dataset,group,label,systems,description,SIunit)
|
subroutine results_writePhaseState_real(dataset,group,label,systems,description,SIunit)
|
||||||
|
|
||||||
character(len=*), intent(in) :: label,group,description,SIunit
|
character(len=*), intent(in) :: label,group,description,SIunit
|
||||||
real(pReal), intent(in), dimension(:,:) :: dataset
|
real(pReal), intent(in), dimension(:,:) :: dataset
|
||||||
|
@ -370,7 +375,7 @@ subroutine results_writePhaseState(dataset,group,label,systems,description,SIuni
|
||||||
integer(HID_T) :: groupHandle
|
integer(HID_T) :: groupHandle
|
||||||
|
|
||||||
|
|
||||||
if (size(systems)*size(dataset,2) == 0 ) return !ToDo: maybe use for other results_write (not sure about scalar)
|
if (size(systems)*size(dataset,2) == 0 ) return !ToDo: maybe also implement for other results_write (not sure about scalar)
|
||||||
|
|
||||||
groupHandle = results_openGroup(group)
|
groupHandle = results_openGroup(group)
|
||||||
call HDF5_write(dataset,groupHandle,label)
|
call HDF5_write(dataset,groupHandle,label)
|
||||||
|
@ -378,7 +383,30 @@ subroutine results_writePhaseState(dataset,group,label,systems,description,SIuni
|
||||||
call HDF5_addAttribute(resultsFile,'systems',systems,group//'/'//label)
|
call HDF5_addAttribute(resultsFile,'systems',systems,group//'/'//label)
|
||||||
call HDF5_closeGroup(groupHandle)
|
call HDF5_closeGroup(groupHandle)
|
||||||
|
|
||||||
end subroutine results_writePhaseState
|
end subroutine results_writePhaseState_real
|
||||||
|
|
||||||
|
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
!> @brief Store real vector dataset with associated metadata for slip
|
||||||
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
subroutine results_writePhaseState_int(dataset,group,label,systems,description,SIunit)
|
||||||
|
|
||||||
|
character(len=*), intent(in) :: label,group,description,SIunit
|
||||||
|
integer, intent(in), dimension(:,:) :: dataset
|
||||||
|
character(len=*), intent(in), dimension(:) :: systems
|
||||||
|
|
||||||
|
integer(HID_T) :: groupHandle
|
||||||
|
|
||||||
|
|
||||||
|
if (size(systems)*size(dataset,2) == 0 ) return !ToDo: maybe also implement for other results_write (not sure about scalar)
|
||||||
|
|
||||||
|
groupHandle = results_openGroup(group)
|
||||||
|
call HDF5_write(dataset,groupHandle,label)
|
||||||
|
call executionStamp(group//'/'//label,description,SIunit)
|
||||||
|
call HDF5_addAttribute(resultsFile,'systems',systems,group//'/'//label)
|
||||||
|
call HDF5_closeGroup(groupHandle)
|
||||||
|
|
||||||
|
end subroutine results_writePhaseState_int
|
||||||
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
|
|
Loading…
Reference in New Issue