Merge branch 'report-systems' into 'development'
add information about active slip+twin systems to DADF5 See merge request damask/DAMASK!423
This commit is contained in:
commit
4a0a7f3c07
|
@ -1301,7 +1301,8 @@ class Result:
|
|||
loc = f[group+'/'+label]
|
||||
datasets_in[arg]={'data' :loc[()],
|
||||
'label':label,
|
||||
'meta': {k:(v if h5py3 else v.decode()) for k,v in loc.attrs.items()}}
|
||||
'meta': {k:(v.decode() if not h5py3 and type(v) is bytes else v) \
|
||||
for k,v in loc.attrs.items()}}
|
||||
lock.release()
|
||||
r = func(**datasets_in,**args)
|
||||
return [group,r]
|
||||
|
@ -1369,7 +1370,7 @@ class Result:
|
|||
now.strftime('%Y-%m-%d %H:%M:%S%z').encode()
|
||||
|
||||
for l,v in result['meta'].items():
|
||||
dataset.attrs[l.lower()]=v if h5py3 else v.encode()
|
||||
dataset.attrs[l.lower()]=v.encode() if not h5py3 and type(v) is str else v
|
||||
creator = dataset.attrs['creator'] if h5py3 else \
|
||||
dataset.attrs['creator'].decode()
|
||||
dataset.attrs['creator'] = f'damask.Result.{creator} v{damask.version}' if h5py3 else \
|
||||
|
|
|
@ -314,12 +314,12 @@ subroutine HDF5_addAttribute_str(loc_id,attrLabel,attrValue,path)
|
|||
character(len=*), intent(in) :: attrLabel, attrValue
|
||||
character(len=*), intent(in), optional :: path
|
||||
|
||||
integer(HID_T) :: attr_id, space_id, type_id
|
||||
integer(HID_T) :: attr_id, space_id
|
||||
logical :: attrExists
|
||||
integer :: hdferr
|
||||
character(len=:), allocatable :: p
|
||||
character(len=:,kind=C_CHAR), allocatable,target :: attrValue_
|
||||
type(c_ptr), target, dimension(1) :: ptr
|
||||
character(len=len_trim(attrValue)+1,kind=C_CHAR), dimension(1), target :: attrValue_
|
||||
type(C_PTR), target, dimension(1) :: ptr
|
||||
|
||||
|
||||
if (present(path)) then
|
||||
|
@ -328,29 +328,26 @@ subroutine HDF5_addAttribute_str(loc_id,attrLabel,attrValue,path)
|
|||
p = '.'
|
||||
endif
|
||||
|
||||
attrValue_ = trim(attrValue)//C_NULL_CHAR
|
||||
ptr(1) = c_loc(attrValue_)
|
||||
attrValue_(1) = trim(attrValue)//C_NULL_CHAR
|
||||
ptr(1) = c_loc(attrValue_(1))
|
||||
|
||||
call h5screate_f(H5S_SCALAR_F,space_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tcopy_f(H5T_STRING, type_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5aexists_by_name_f(loc_id,trim(p),attrLabel,attrExists,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
if (attrExists) then
|
||||
call h5adelete_by_name_f(loc_id, trim(p), attrLabel, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5adelete_by_name_f(loc_id, trim(p), attrLabel, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
endif
|
||||
call h5acreate_by_name_f(loc_id,trim(p),trim(attrLabel),type_id,space_id,attr_id,hdferr)
|
||||
|
||||
call h5acreate_by_name_f(loc_id,trim(p),trim(attrLabel),H5T_STRING,space_id,attr_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5awrite_f(attr_id, type_id, c_loc(ptr(1)), hdferr)
|
||||
call h5awrite_f(attr_id, H5T_STRING, c_loc(ptr), hdferr) ! ptr instead of c_loc(ptr) works on gfortran, not on ifort
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5aclose_f(attr_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tclose_f(type_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5sclose_f(space_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
|
@ -388,6 +385,7 @@ subroutine HDF5_addAttribute_int(loc_id,attrLabel,attrValue,path)
|
|||
call h5adelete_by_name_f(loc_id, trim(p), attrLabel, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
endif
|
||||
|
||||
call h5acreate_by_name_f(loc_id,trim(p),trim(attrLabel),H5T_NATIVE_INTEGER,space_id,attr_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5awrite_f(attr_id, H5T_NATIVE_INTEGER, attrValue, int([1],HSIZE_T), hdferr)
|
||||
|
@ -432,6 +430,7 @@ subroutine HDF5_addAttribute_real(loc_id,attrLabel,attrValue,path)
|
|||
call h5adelete_by_name_f(loc_id, trim(p), attrLabel, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
endif
|
||||
|
||||
call h5acreate_by_name_f(loc_id,trim(p),trim(attrLabel),H5T_NATIVE_DOUBLE,space_id,attr_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5awrite_f(attr_id, H5T_NATIVE_DOUBLE, attrValue, int([1],HSIZE_T), hdferr)
|
||||
|
@ -455,12 +454,12 @@ subroutine HDF5_addAttribute_str_array(loc_id,attrLabel,attrValue,path)
|
|||
character(len=*), intent(in), dimension(:) :: attrValue
|
||||
character(len=*), intent(in), optional :: path
|
||||
|
||||
integer(HID_T) :: attr_id, space_id, filetype_id, memtype_id
|
||||
integer :: hdferr
|
||||
integer(HID_T) :: attr_id, space_id
|
||||
logical :: attrExists
|
||||
integer :: hdferr,i
|
||||
character(len=:), allocatable :: p
|
||||
type(C_PTR) :: f_ptr
|
||||
character(len=:), allocatable, dimension(:), target :: attrValue_
|
||||
character(len=len(attrValue)+1,kind=C_CHAR), dimension(size(attrValue)), target :: attrValue_
|
||||
type(C_PTR), target, dimension(size(attrValue)) :: ptr
|
||||
|
||||
|
||||
if (present(path)) then
|
||||
|
@ -469,34 +468,26 @@ subroutine HDF5_addAttribute_str_array(loc_id,attrLabel,attrValue,path)
|
|||
p = '.'
|
||||
endif
|
||||
|
||||
attrValue_ = attrValue
|
||||
do i=1,size(attrValue)
|
||||
attrValue_(i) = attrValue(i)//C_NULL_CHAR
|
||||
ptr(i) = c_loc(attrValue_(i))
|
||||
enddo
|
||||
|
||||
call h5tcopy_f(H5T_C_S1,filetype_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tset_size_f(filetype_id, int(len(attrValue_)+1,C_SIZE_T),hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tcopy_f(H5T_FORTRAN_S1, memtype_id, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tset_size_f(memtype_id, int(len(attrValue_),C_SIZE_T), hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5screate_simple_f(1,shape(attrValue_,kind=HSIZE_T),space_id, hdferr)
|
||||
call h5screate_simple_f(1,shape(attrValue_,kind=HSIZE_T),space_id,hdferr,shape(attrValue_,kind=HSIZE_T))
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5aexists_by_name_f(loc_id,trim(p),attrLabel,attrExists,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
if (attrExists) then
|
||||
call h5adelete_by_name_f(loc_id, trim(p), attrLabel, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
endif
|
||||
call h5acreate_by_name_f(loc_id,trim(p),trim(attrLabel),filetype_id,space_id,attr_id,hdferr)
|
||||
|
||||
call h5acreate_by_name_f(loc_id,trim(p),trim(attrLabel),H5T_STRING,space_id,attr_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
f_ptr = c_loc(attrValue_)
|
||||
call h5awrite_f(attr_id, memtype_id, f_ptr, hdferr)
|
||||
call h5awrite_f(attr_id, H5T_STRING, c_loc(ptr), hdferr) ! ptr instead of c_loc(ptr) works on gfortran, not on ifort
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
|
||||
call h5tclose_f(memtype_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5tclose_f(filetype_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5aclose_f(attr_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5sclose_f(space_id,hdferr)
|
||||
|
@ -539,6 +530,7 @@ subroutine HDF5_addAttribute_int_array(loc_id,attrLabel,attrValue,path)
|
|||
call h5adelete_by_name_f(loc_id, trim(p), attrLabel, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
endif
|
||||
|
||||
call h5acreate_by_name_f(loc_id,trim(p),trim(attrLabel),H5T_NATIVE_INTEGER,space_id,attr_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5awrite_f(attr_id, H5T_NATIVE_INTEGER, attrValue, array_size, hdferr)
|
||||
|
@ -586,6 +578,7 @@ subroutine HDF5_addAttribute_real_array(loc_id,attrLabel,attrValue,path)
|
|||
call h5adelete_by_name_f(loc_id, trim(p), attrLabel, hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
endif
|
||||
|
||||
call h5acreate_by_name_f(loc_id,trim(p),trim(attrLabel),H5T_NATIVE_DOUBLE,space_id,attr_id,hdferr)
|
||||
if(hdferr < 0) error stop 'HDF5 error'
|
||||
call h5awrite_f(attr_id, H5T_NATIVE_DOUBLE, attrValue, array_size, hdferr)
|
||||
|
|
|
@ -1930,7 +1930,8 @@ subroutine buildTransformationSystem(Q,S,Ntrans,cOverA,a_fcc,a_bcc)
|
|||
-1,-2,-1, -1, 1,-1, &
|
||||
-1, 1, 2, -1, 1,-1 &
|
||||
],pReal),shape(FCCTOHEX_SYSTEMTRANS))
|
||||
real(pReal), dimension(4,fcc_Ntrans), parameter :: &
|
||||
|
||||
real(pReal), dimension(4,fcc_Ntrans), parameter :: &
|
||||
FCCTOBCC_SYSTEMTRANS = reshape([&
|
||||
0.0, 1.0, 0.0, 10.26, & ! Pitsch OR (Ma & Hartmaier 2014, Table 3)
|
||||
0.0,-1.0, 0.0, 10.26, &
|
||||
|
@ -1978,7 +1979,7 @@ subroutine buildTransformationSystem(Q,S,Ntrans,cOverA,a_fcc,a_bcc)
|
|||
0.0, 0.0, 1.0, 45.0 &
|
||||
],shape(FCCTOBCC_BAINROT))
|
||||
|
||||
if (a_bcc > 0.0_pReal .and. a_fcc > 0.0_pReal .and. dEq0(cOverA)) then ! fcc -> bcc transformation
|
||||
if (a_bcc > 0.0_pReal .and. a_fcc > 0.0_pReal .and. dEq0(cOverA)) then ! fcc -> bcc
|
||||
do i = 1,sum(Ntrans)
|
||||
call R%fromAxisAngle(FCCTOBCC_SYSTEMTRANS(:,i),degrees=.true.,P=1)
|
||||
call B%fromAxisAngle(FCCTOBCC_BAINROT(:,i), degrees=.true.,P=1)
|
||||
|
@ -1992,7 +1993,7 @@ subroutine buildTransformationSystem(Q,S,Ntrans,cOverA,a_fcc,a_bcc)
|
|||
Q(1:3,1:3,i) = matmul(R%asMatrix(),B%asMatrix())
|
||||
S(1:3,1:3,i) = matmul(R%asMatrix(),U) - MATH_I3
|
||||
enddo
|
||||
elseif (cOverA > 0.0_pReal .and. dEq0(a_bcc)) then ! fcc -> hex transformation
|
||||
elseif (cOverA > 0.0_pReal .and. dEq0(a_bcc)) then ! fcc -> hex
|
||||
ss = MATH_I3
|
||||
sd = MATH_I3
|
||||
ss(1,3) = sqrt(2.0_pReal)/4.0_pReal
|
||||
|
@ -2062,7 +2063,7 @@ function getlabels(active,potential,system) result(labels)
|
|||
enddo normal
|
||||
label(i:i) = ')'
|
||||
|
||||
labels(s) = label
|
||||
labels(a) = label
|
||||
|
||||
enddo activeSystems
|
||||
enddo activeFamilies
|
||||
|
|
|
@ -44,20 +44,22 @@ submodule(phase:plastic) dislotungsten
|
|||
output
|
||||
logical :: &
|
||||
dipoleFormation !< flag indicating consideration of dipole formation
|
||||
end type !< container type for internal constitutive parameters
|
||||
character(len=:), allocatable, dimension(:) :: &
|
||||
systems_sl
|
||||
end type tParameters !< container type for internal constitutive parameters
|
||||
|
||||
type :: tDisloTungstenState
|
||||
type :: tDislotungstenState
|
||||
real(pReal), dimension(:,:), pointer :: &
|
||||
rho_mob, &
|
||||
rho_dip, &
|
||||
gamma_sl
|
||||
end type tDisloTungstenState
|
||||
end type tDislotungstenState
|
||||
|
||||
type :: tDisloTungstendependentState
|
||||
type :: tDislotungstenDependentState
|
||||
real(pReal), dimension(:,:), allocatable :: &
|
||||
Lambda_sl, &
|
||||
tau_pass
|
||||
end type tDisloTungstendependentState
|
||||
end type tDislotungstenDependentState
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! containers for parameters and state
|
||||
|
@ -65,7 +67,7 @@ submodule(phase:plastic) dislotungsten
|
|||
type(tDisloTungstenState), allocatable, dimension(:) :: &
|
||||
dotState, &
|
||||
state
|
||||
type(tDisloTungstendependentState), allocatable, dimension(:) :: dependentState
|
||||
type(tDisloTungstenDependentState), allocatable, dimension(:) :: dependentState
|
||||
|
||||
contains
|
||||
|
||||
|
@ -136,6 +138,7 @@ module function plastic_dislotungsten_init() result(myPlasticity)
|
|||
N_sl = pl%get_as1dInt('N_sl',defaultVal=emptyIntArray)
|
||||
prm%sum_N_sl = sum(abs(N_sl))
|
||||
slipActive: if (prm%sum_N_sl > 0) then
|
||||
prm%systems_sl = lattice_labels_slip(N_sl,phase_lattice(ph))
|
||||
prm%P_sl = lattice_SchmidMatrix_slip(N_sl,phase_lattice(ph),phase_cOverA(ph))
|
||||
|
||||
if (phase_lattice(ph) == 'cI') then
|
||||
|
@ -394,28 +397,34 @@ module subroutine plastic_dislotungsten_results(ph,group)
|
|||
integer, intent(in) :: ph
|
||||
character(len=*), intent(in) :: group
|
||||
|
||||
integer :: o
|
||||
integer :: ou
|
||||
|
||||
|
||||
associate(prm => param(ph), stt => state(ph), dst => dependentState(ph))
|
||||
outputsLoop: do o = 1,size(prm%output)
|
||||
select case(trim(prm%output(o)))
|
||||
case('rho_mob')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%rho_mob,group,trim(prm%output(o)), &
|
||||
'mobile dislocation density','1/m²')
|
||||
case('rho_dip')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%rho_dip,group,trim(prm%output(o)), &
|
||||
'dislocation dipole density','1/m²')
|
||||
case('gamma_sl')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%gamma_sl,group,trim(prm%output(o)), &
|
||||
'plastic shear','1')
|
||||
case('Lambda_sl')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(dst%Lambda_sl,group,trim(prm%output(o)), &
|
||||
'mean free path for slip','m')
|
||||
case('tau_pass')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(dst%tau_pass,group,trim(prm%output(o)), &
|
||||
'threshold stress for slip','Pa')
|
||||
end select
|
||||
enddo outputsLoop
|
||||
|
||||
do ou = 1,size(prm%output)
|
||||
|
||||
select case(trim(prm%output(ou)))
|
||||
|
||||
case('rho_mob')
|
||||
call results_writeDataset(stt%rho_mob,group,trim(prm%output(ou)), &
|
||||
'mobile dislocation density','1/m²',prm%systems_sl)
|
||||
case('rho_dip')
|
||||
call results_writeDataset(stt%rho_dip,group,trim(prm%output(ou)), &
|
||||
'dislocation dipole density','1/m²',prm%systems_sl)
|
||||
case('gamma_sl')
|
||||
call results_writeDataset(stt%gamma_sl,group,trim(prm%output(ou)), &
|
||||
'plastic shear','1',prm%systems_sl)
|
||||
case('Lambda_sl')
|
||||
call results_writeDataset(dst%Lambda_sl,group,trim(prm%output(ou)), &
|
||||
'mean free path for slip','m',prm%systems_sl)
|
||||
case('tau_pass')
|
||||
call results_writeDataset(dst%tau_pass,group,trim(prm%output(ou)), &
|
||||
'threshold stress for slip','Pa',prm%systems_sl)
|
||||
end select
|
||||
|
||||
enddo
|
||||
|
||||
end associate
|
||||
|
||||
end subroutine plastic_dislotungsten_results
|
||||
|
|
|
@ -82,6 +82,9 @@ submodule(phase:plastic) dislotwin
|
|||
ExtendedDislocations, & !< consider split into partials for climb calculation
|
||||
fccTwinTransNucleation, & !< twinning and transformation models are for fcc
|
||||
omitDipoles !< flag controlling consideration of dipole formation
|
||||
character(len=:), allocatable, dimension(:) :: &
|
||||
systems_sl, &
|
||||
systems_tw
|
||||
end type !< container type for internal constitutive parameters
|
||||
|
||||
type :: tDislotwinState
|
||||
|
@ -93,7 +96,7 @@ submodule(phase:plastic) dislotwin
|
|||
f_tr
|
||||
end type tDislotwinState
|
||||
|
||||
type :: tDislotwinMicrostructure
|
||||
type :: tDislotwinDependentState
|
||||
real(pReal), dimension(:,:), allocatable :: &
|
||||
Lambda_sl, & !< mean free path between 2 obstacles seen by a moving dislocation
|
||||
Lambda_tw, & !< mean free path between 2 obstacles seen by a growing twin
|
||||
|
@ -105,7 +108,7 @@ submodule(phase:plastic) dislotwin
|
|||
V_tr, & !< volume of a new martensite disc
|
||||
tau_r_tw, & !< stress to bring partials close together (twin)
|
||||
tau_r_tr !< stress to bring partials close together (trans)
|
||||
end type tDislotwinMicrostructure
|
||||
end type tDislotwinDependentState
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! containers for parameters and state
|
||||
|
@ -113,7 +116,7 @@ submodule(phase:plastic) dislotwin
|
|||
type(tDislotwinState), allocatable, dimension(:) :: &
|
||||
dotState, &
|
||||
state
|
||||
type(tDislotwinMicrostructure), allocatable, dimension(:) :: dependentState
|
||||
type(tDislotwinDependentState), allocatable, dimension(:) :: dependentState
|
||||
|
||||
contains
|
||||
|
||||
|
@ -192,6 +195,7 @@ module function plastic_dislotwin_init() result(myPlasticity)
|
|||
N_sl = pl%get_as1dInt('N_sl',defaultVal=emptyIntArray)
|
||||
prm%sum_N_sl = sum(abs(N_sl))
|
||||
slipActive: if (prm%sum_N_sl > 0) then
|
||||
prm%systems_sl = lattice_labels_slip(N_sl,phase_lattice(ph))
|
||||
prm%P_sl = lattice_SchmidMatrix_slip(N_sl,phase_lattice(ph),phase_cOverA(ph))
|
||||
prm%h_sl_sl = lattice_interaction_SlipBySlip(N_sl,pl%get_as1dFloat('h_sl-sl'),phase_lattice(ph))
|
||||
prm%forestProjection = lattice_forestProjection_edge(N_sl,phase_lattice(ph),phase_cOverA(ph))
|
||||
|
@ -259,6 +263,7 @@ module function plastic_dislotwin_init() result(myPlasticity)
|
|||
N_tw = pl%get_as1dInt('N_tw', defaultVal=emptyIntArray)
|
||||
prm%sum_N_tw = sum(abs(N_tw))
|
||||
twinActive: if (prm%sum_N_tw > 0) then
|
||||
prm%systems_tw = lattice_labels_twin(N_tw,phase_lattice(ph))
|
||||
prm%P_tw = lattice_SchmidMatrix_twin(N_tw,phase_lattice(ph),phase_cOverA(ph))
|
||||
prm%h_tw_tw = lattice_interaction_TwinByTwin(N_tw,pl%get_as1dFloat('h_tw-tw'), &
|
||||
phase_lattice(ph))
|
||||
|
@ -787,44 +792,49 @@ module subroutine plastic_dislotwin_results(ph,group)
|
|||
integer, intent(in) :: ph
|
||||
character(len=*), intent(in) :: group
|
||||
|
||||
integer :: o
|
||||
integer :: ou
|
||||
|
||||
associate(prm => param(ph), stt => state(ph), dst => dependentState(ph))
|
||||
outputsLoop: do o = 1,size(prm%output)
|
||||
select case(trim(prm%output(o)))
|
||||
|
||||
case('rho_mob')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%rho_mob,group,trim(prm%output(o)), &
|
||||
'mobile dislocation density','1/m²')
|
||||
case('rho_dip')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%rho_dip,group,trim(prm%output(o)), &
|
||||
'dislocation dipole density','1/m²')
|
||||
case('gamma_sl')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%gamma_sl,group,trim(prm%output(o)), &
|
||||
'plastic shear','1')
|
||||
case('Lambda_sl')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(dst%Lambda_sl,group,trim(prm%output(o)), &
|
||||
'mean free path for slip','m')
|
||||
case('tau_pass')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(dst%tau_pass,group,trim(prm%output(o)), &
|
||||
'passing stress for slip','Pa')
|
||||
associate(prm => param(ph), stt => state(ph), dst => dependentState(ph))
|
||||
|
||||
case('f_tw')
|
||||
if(prm%sum_N_tw>0) call results_writeDataset(stt%f_tw,group,trim(prm%output(o)), &
|
||||
'twinned volume fraction','m³/m³')
|
||||
case('Lambda_tw')
|
||||
if(prm%sum_N_tw>0) call results_writeDataset(dst%Lambda_tw,group,trim(prm%output(o)), &
|
||||
'mean free path for twinning','m')
|
||||
case('tau_hat_tw')
|
||||
if(prm%sum_N_tw>0) call results_writeDataset(dst%tau_hat_tw,group,trim(prm%output(o)), &
|
||||
'threshold stress for twinning','Pa')
|
||||
do ou = 1,size(prm%output)
|
||||
|
||||
case('f_tr')
|
||||
if(prm%sum_N_tr>0) call results_writeDataset(stt%f_tr,group,trim(prm%output(o)), &
|
||||
'martensite volume fraction','m³/m³')
|
||||
select case(trim(prm%output(ou)))
|
||||
|
||||
case('rho_mob')
|
||||
call results_writeDataset(stt%rho_mob,group,trim(prm%output(ou)), &
|
||||
'mobile dislocation density','1/m²',prm%systems_sl)
|
||||
case('rho_dip')
|
||||
call results_writeDataset(stt%rho_dip,group,trim(prm%output(ou)), &
|
||||
'dislocation dipole density','1/m²',prm%systems_sl)
|
||||
case('gamma_sl')
|
||||
call results_writeDataset(stt%gamma_sl,group,trim(prm%output(ou)), &
|
||||
'plastic shear','1',prm%systems_sl)
|
||||
case('Lambda_sl')
|
||||
call results_writeDataset(dst%Lambda_sl,group,trim(prm%output(ou)), &
|
||||
'mean free path for slip','m',prm%systems_sl)
|
||||
case('tau_pass')
|
||||
call results_writeDataset(dst%tau_pass,group,trim(prm%output(ou)), &
|
||||
'passing stress for slip','Pa',prm%systems_sl)
|
||||
|
||||
case('f_tw')
|
||||
call results_writeDataset(stt%f_tw,group,trim(prm%output(ou)), &
|
||||
'twinned volume fraction','m³/m³',prm%systems_tw)
|
||||
case('Lambda_tw')
|
||||
call results_writeDataset(dst%Lambda_tw,group,trim(prm%output(ou)), &
|
||||
'mean free path for twinning','m',prm%systems_tw)
|
||||
case('tau_hat_tw')
|
||||
call results_writeDataset(dst%tau_hat_tw,group,trim(prm%output(ou)), &
|
||||
'threshold stress for twinning','Pa',prm%systems_tw)
|
||||
|
||||
case('f_tr')
|
||||
if(prm%sum_N_tr>0) call results_writeDataset(stt%f_tr,group,trim(prm%output(ou)), &
|
||||
'martensite volume fraction','m³/m³')
|
||||
|
||||
end select
|
||||
|
||||
enddo
|
||||
|
||||
end select
|
||||
enddo outputsLoop
|
||||
end associate
|
||||
|
||||
end subroutine plastic_dislotwin_results
|
||||
|
|
|
@ -30,6 +30,8 @@ submodule(phase:plastic) kinehardening
|
|||
nonSchmidActive = .false.
|
||||
character(len=pStringLen), allocatable, dimension(:) :: &
|
||||
output
|
||||
character(len=:), allocatable, dimension(:) :: &
|
||||
systems_sl
|
||||
end type tParameters
|
||||
|
||||
type :: tKinehardeningState
|
||||
|
@ -40,7 +42,6 @@ submodule(phase:plastic) kinehardening
|
|||
gamma, & !< accumulated (absolute) shear
|
||||
gamma_0, & !< accumulated shear at last switch of stress sense
|
||||
sgn_gamma !< sense of acting shear stress (-1 or +1)
|
||||
|
||||
end type tKinehardeningState
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
@ -113,6 +114,7 @@ module function plastic_kinehardening_init() result(myPlasticity)
|
|||
N_sl = pl%get_as1dInt('N_sl',defaultVal=emptyIntArray)
|
||||
prm%sum_N_sl = sum(abs(N_sl))
|
||||
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))
|
||||
|
||||
if (phase_lattice(ph) == 'cI') then
|
||||
|
@ -351,31 +353,37 @@ module subroutine plastic_kinehardening_results(ph,group)
|
|||
integer, intent(in) :: ph
|
||||
character(len=*), intent(in) :: group
|
||||
|
||||
integer :: o
|
||||
integer :: ou
|
||||
|
||||
|
||||
associate(prm => param(ph), stt => state(ph))
|
||||
outputsLoop: do o = 1,size(prm%output)
|
||||
select case(trim(prm%output(o)))
|
||||
case ('xi')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%xi,group,trim(prm%output(o)), &
|
||||
'resistance against plastic slip','Pa')
|
||||
case ('chi')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%chi,group,trim(prm%output(o)), &
|
||||
'back stress','Pa')
|
||||
case ('sgn(gamma)')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(int(stt%sgn_gamma),group,trim(prm%output(o)), &
|
||||
'sense of shear','1')
|
||||
case ('chi_0')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%chi_0,group,trim(prm%output(o)), &
|
||||
'back stress at last switch of stress sense','Pa')
|
||||
case ('gamma_0')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%gamma_0,group,trim(prm%output(o)), &
|
||||
'plastic shear at last switch of stress sense','1')
|
||||
case ('gamma')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%gamma,group,trim(prm%output(o)), &
|
||||
'plastic shear','1')
|
||||
end select
|
||||
enddo outputsLoop
|
||||
|
||||
do ou = 1,size(prm%output)
|
||||
|
||||
select case(trim(prm%output(ou)))
|
||||
|
||||
case ('xi')
|
||||
call results_writeDataset(stt%xi,group,trim(prm%output(ou)), &
|
||||
'resistance against plastic slip','Pa',prm%systems_sl)
|
||||
case ('chi')
|
||||
call results_writeDataset(stt%chi,group,trim(prm%output(ou)), &
|
||||
'back stress','Pa',prm%systems_sl)
|
||||
case ('sgn(gamma)')
|
||||
call results_writeDataset(int(stt%sgn_gamma),group,trim(prm%output(ou)), &
|
||||
'sense of shear','1',prm%systems_sl)
|
||||
case ('chi_0')
|
||||
call results_writeDataset(stt%chi_0,group,trim(prm%output(ou)), &
|
||||
'back stress at last switch of stress sense','Pa',prm%systems_sl)
|
||||
case ('gamma_0')
|
||||
call results_writeDataset(stt%gamma_0,group,trim(prm%output(ou)), &
|
||||
'plastic shear at last switch of stress sense','1',prm%systems_sl)
|
||||
case ('gamma')
|
||||
call results_writeDataset(stt%gamma,group,trim(prm%output(ou)), &
|
||||
'plastic shear','1',prm%systems_sl)
|
||||
end select
|
||||
|
||||
enddo
|
||||
|
||||
end associate
|
||||
|
||||
end subroutine plastic_kinehardening_results
|
||||
|
|
|
@ -120,13 +120,15 @@ submodule(phase:plastic) nonlocal
|
|||
logical :: &
|
||||
shortRangeStressCorrection, & !< use of short range stress correction by excess density gradient term
|
||||
nonSchmidActive = .false.
|
||||
character(len=:), allocatable, dimension(:) :: &
|
||||
systems_sl
|
||||
end type tParameters
|
||||
|
||||
type :: tNonlocalMicrostructure
|
||||
type :: tNonlocalDependentState
|
||||
real(pReal), allocatable, dimension(:,:) :: &
|
||||
tau_pass, &
|
||||
tau_Back
|
||||
end type tNonlocalMicrostructure
|
||||
end type tNonlocalDependentState
|
||||
|
||||
type :: tNonlocalState
|
||||
real(pReal), pointer, dimension(:,:) :: &
|
||||
|
@ -162,7 +164,7 @@ submodule(phase:plastic) nonlocal
|
|||
|
||||
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters
|
||||
|
||||
type(tNonlocalMicrostructure), dimension(:), allocatable :: microstructure
|
||||
type(tNonlocalDependentState), dimension(:), allocatable :: dependentState
|
||||
|
||||
contains
|
||||
|
||||
|
@ -219,13 +221,13 @@ module function plastic_nonlocal_init() result(myPlasticity)
|
|||
allocate(state0(phases%length))
|
||||
allocate(dotState(phases%length))
|
||||
allocate(deltaState(phases%length))
|
||||
allocate(microstructure(phases%length))
|
||||
allocate(dependentState(phases%length))
|
||||
|
||||
do ph = 1, phases%length
|
||||
if(.not. myPlasticity(ph)) cycle
|
||||
|
||||
associate(prm => param(ph), dot => dotState(ph), stt => state(ph), &
|
||||
st0 => state0(ph), del => deltaState(ph), dst => microstructure(ph))
|
||||
st0 => state0(ph), del => deltaState(ph), dst => dependentState(ph))
|
||||
|
||||
phase => phases%get(ph)
|
||||
mech => phase%get('mechanical')
|
||||
|
@ -246,6 +248,7 @@ module function plastic_nonlocal_init() result(myPlasticity)
|
|||
ini%N_sl = pl%get_as1dInt('N_sl',defaultVal=emptyIntArray)
|
||||
prm%sum_N_sl = sum(abs(ini%N_sl))
|
||||
slipActive: if (prm%sum_N_sl > 0) then
|
||||
prm%systems_sl = lattice_labels_slip(ini%N_sl,phase_lattice(ph))
|
||||
prm%P_sl = lattice_SchmidMatrix_slip(ini%N_sl,phase_lattice(ph), phase_cOverA(ph))
|
||||
|
||||
if (phase_lattice(ph) == 'cI') then
|
||||
|
@ -604,7 +607,7 @@ module subroutine nonlocal_dependentState(ph, en, ip, el)
|
|||
real(pReal), dimension(3,param(ph)%sum_N_sl,2) :: &
|
||||
m ! direction of dislocation motion
|
||||
|
||||
associate(prm => param(ph),dst => microstructure(ph), stt => state(ph))
|
||||
associate(prm => param(ph),dst => dependentState(ph), stt => state(ph))
|
||||
|
||||
rho = getRho(ph,en)
|
||||
|
||||
|
@ -771,7 +774,7 @@ module subroutine nonlocal_LpAndItsTangent(Lp,dLp_dMp, &
|
|||
tau, & !< resolved shear stress including backstress terms
|
||||
dot_gamma !< shear rate
|
||||
|
||||
associate(prm => param(ph),dst=>microstructure(ph),stt=>state(ph))
|
||||
associate(prm => param(ph),dst=>dependentState(ph),stt=>state(ph))
|
||||
|
||||
!*** shortcut to state variables
|
||||
rho = getRho(ph,en)
|
||||
|
@ -867,7 +870,7 @@ module subroutine plastic_nonlocal_deltaState(Mp,ph,en)
|
|||
dUpperOld, & ! old maximum stable dipole distance for edges and screws
|
||||
deltaDUpper ! change in maximum stable dipole distance for edges and screws
|
||||
|
||||
associate(prm => param(ph),dst => microstructure(ph),del => deltaState(ph))
|
||||
associate(prm => param(ph),dst => dependentState(ph),del => deltaState(ph))
|
||||
|
||||
!*** shortcut to state variables
|
||||
forall (s = 1:prm%sum_N_sl, t = 1:4) v(s,t) = plasticState(ph)%state(iV(s,t,ph),en)
|
||||
|
@ -979,7 +982,7 @@ module subroutine nonlocal_dotState(Mp, Temperature,timestep, &
|
|||
return
|
||||
endif
|
||||
|
||||
associate(prm => param(ph), dst => microstructure(ph), dot => dotState(ph), stt => state(ph))
|
||||
associate(prm => param(ph), dst => dependentState(ph), dot => dotState(ph), stt => state(ph))
|
||||
|
||||
tau = 0.0_pReal
|
||||
dot_gamma = 0.0_pReal
|
||||
|
@ -1176,7 +1179,7 @@ function rhoDotFlux(timestep,ph,en,ip,el)
|
|||
|
||||
|
||||
associate(prm => param(ph), &
|
||||
dst => microstructure(ph), &
|
||||
dst => dependentState(ph), &
|
||||
dot => dotState(ph), &
|
||||
stt => state(ph))
|
||||
ns = prm%sum_N_sl
|
||||
|
@ -1458,71 +1461,76 @@ end subroutine plastic_nonlocal_updateCompatibility
|
|||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief writes results to HDF5 output file
|
||||
!> @brief Write results to HDF5 output file.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
module subroutine plastic_nonlocal_results(ph,group)
|
||||
|
||||
integer, intent(in) :: ph
|
||||
character(len=*),intent(in) :: group
|
||||
|
||||
integer :: o
|
||||
integer :: ou
|
||||
|
||||
associate(prm => param(ph),dst => dependentState(ph),stt=>state(ph))
|
||||
|
||||
do ou = 1,size(prm%output)
|
||||
|
||||
select case(trim(prm%output(ou)))
|
||||
|
||||
case('rho_u_ed_pos')
|
||||
call results_writeDataset(stt%rho_sgl_mob_edg_pos,group,trim(prm%output(ou)), &
|
||||
'positive mobile edge density','1/m²', prm%systems_sl)
|
||||
case('rho_b_ed_pos')
|
||||
call results_writeDataset(stt%rho_sgl_imm_edg_pos,group,trim(prm%output(ou)), &
|
||||
'positive immobile edge density','1/m²', prm%systems_sl)
|
||||
case('rho_u_ed_neg')
|
||||
call results_writeDataset(stt%rho_sgl_mob_edg_neg,group,trim(prm%output(ou)), &
|
||||
'negative mobile edge density','1/m²', prm%systems_sl)
|
||||
case('rho_b_ed_neg')
|
||||
call results_writeDataset(stt%rho_sgl_imm_edg_neg,group,trim(prm%output(ou)), &
|
||||
'negative immobile edge density','1/m²', prm%systems_sl)
|
||||
case('rho_d_ed')
|
||||
call results_writeDataset(stt%rho_dip_edg,group,trim(prm%output(ou)), &
|
||||
'edge dipole density','1/m²', prm%systems_sl)
|
||||
case('rho_u_sc_pos')
|
||||
call results_writeDataset(stt%rho_sgl_mob_scr_pos,group,trim(prm%output(ou)), &
|
||||
'positive mobile screw density','1/m²', prm%systems_sl)
|
||||
case('rho_b_sc_pos')
|
||||
call results_writeDataset(stt%rho_sgl_imm_scr_pos,group,trim(prm%output(ou)), &
|
||||
'positive immobile screw density','1/m²', prm%systems_sl)
|
||||
case('rho_u_sc_neg')
|
||||
call results_writeDataset(stt%rho_sgl_mob_scr_neg,group,trim(prm%output(ou)), &
|
||||
'negative mobile screw density','1/m²', prm%systems_sl)
|
||||
case('rho_b_sc_neg')
|
||||
call results_writeDataset(stt%rho_sgl_imm_scr_neg,group,trim(prm%output(ou)), &
|
||||
'negative immobile screw density','1/m²', prm%systems_sl)
|
||||
case('rho_d_sc')
|
||||
call results_writeDataset(stt%rho_dip_scr,group,trim(prm%output(ou)), &
|
||||
'screw dipole density','1/m²', prm%systems_sl)
|
||||
case('rho_f')
|
||||
call results_writeDataset(stt%rho_forest,group,trim(prm%output(ou)), &
|
||||
'forest density','1/m²', prm%systems_sl)
|
||||
case('v_ed_pos')
|
||||
call results_writeDataset(stt%v_edg_pos,group,trim(prm%output(ou)), &
|
||||
'positive edge velocity','m/s', prm%systems_sl)
|
||||
case('v_ed_neg')
|
||||
call results_writeDataset(stt%v_edg_neg,group,trim(prm%output(ou)), &
|
||||
'negative edge velocity','m/s', prm%systems_sl)
|
||||
case('v_sc_pos')
|
||||
call results_writeDataset(stt%v_scr_pos,group,trim(prm%output(ou)), &
|
||||
'positive srew velocity','m/s', prm%systems_sl)
|
||||
case('v_sc_neg')
|
||||
call results_writeDataset(stt%v_scr_neg,group,trim(prm%output(ou)), &
|
||||
'negative screw velocity','m/s', prm%systems_sl)
|
||||
case('gamma')
|
||||
call results_writeDataset(stt%gamma,group,trim(prm%output(ou)), &
|
||||
'plastic shear','1', prm%systems_sl)
|
||||
case('tau_pass')
|
||||
call results_writeDataset(dst%tau_pass,group,trim(prm%output(ou)), &
|
||||
'passing stress for slip','Pa', prm%systems_sl)
|
||||
end select
|
||||
|
||||
enddo
|
||||
|
||||
associate(prm => param(ph),dst => microstructure(ph),stt=>state(ph))
|
||||
outputsLoop: do o = 1,size(prm%output)
|
||||
select case(trim(prm%output(o)))
|
||||
case('rho_u_ed_pos')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%rho_sgl_mob_edg_pos,group,trim(prm%output(o)), &
|
||||
'positive mobile edge density','1/m²')
|
||||
case('rho_b_ed_pos')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%rho_sgl_imm_edg_pos,group,trim(prm%output(o)), &
|
||||
'positive immobile edge density','1/m²')
|
||||
case('rho_u_ed_neg')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%rho_sgl_mob_edg_neg,group,trim(prm%output(o)), &
|
||||
'negative mobile edge density','1/m²')
|
||||
case('rho_b_ed_neg')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%rho_sgl_imm_edg_neg,group,trim(prm%output(o)), &
|
||||
'negative immobile edge density','1/m²')
|
||||
case('rho_d_ed')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%rho_dip_edg,group,trim(prm%output(o)), &
|
||||
'edge dipole density','1/m²')
|
||||
case('rho_u_sc_pos')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%rho_sgl_mob_scr_pos,group,trim(prm%output(o)), &
|
||||
'positive mobile screw density','1/m²')
|
||||
case('rho_b_sc_pos')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%rho_sgl_imm_scr_pos,group,trim(prm%output(o)), &
|
||||
'positive immobile screw density','1/m²')
|
||||
case('rho_u_sc_neg')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%rho_sgl_mob_scr_neg,group,trim(prm%output(o)), &
|
||||
'negative mobile screw density','1/m²')
|
||||
case('rho_b_sc_neg')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%rho_sgl_imm_scr_neg,group,trim(prm%output(o)), &
|
||||
'negative immobile screw density','1/m²')
|
||||
case('rho_d_sc')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%rho_dip_scr,group,trim(prm%output(o)), &
|
||||
'screw dipole density','1/m²')
|
||||
case('rho_f')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%rho_forest,group,trim(prm%output(o)), &
|
||||
'forest density','1/m²')
|
||||
case('v_ed_pos')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%v_edg_pos,group,trim(prm%output(o)), &
|
||||
'positive edge velocity','m/s')
|
||||
case('v_ed_neg')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%v_edg_neg,group,trim(prm%output(o)), &
|
||||
'negative edge velocity','m/s')
|
||||
case('v_sc_pos')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%v_scr_pos,group,trim(prm%output(o)), &
|
||||
'positive srew velocity','m/s')
|
||||
case('v_sc_neg')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%v_scr_neg,group,trim(prm%output(o)), &
|
||||
'negative screw velocity','m/s')
|
||||
case('gamma')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%gamma,group,trim(prm%output(o)), &
|
||||
'plastic shear','1')
|
||||
case('tau_pass')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(dst%tau_pass,group,trim(prm%output(o)), &
|
||||
'passing stress for slip','Pa')
|
||||
end select
|
||||
enddo outputsLoop
|
||||
end associate
|
||||
|
||||
end subroutine plastic_nonlocal_results
|
||||
|
|
|
@ -42,6 +42,9 @@ submodule(phase:plastic) phenopowerlaw
|
|||
nonSchmidActive = .false.
|
||||
character(len=pStringLen), allocatable, dimension(:) :: &
|
||||
output
|
||||
character(len=:), allocatable, dimension(:) :: &
|
||||
systems_sl, &
|
||||
systems_tw
|
||||
end type tParameters
|
||||
|
||||
type :: tPhenopowerlawState
|
||||
|
@ -115,6 +118,7 @@ module function plastic_phenopowerlaw_init() result(myPlasticity)
|
|||
N_sl = pl%get_as1dInt('N_sl',defaultVal=emptyIntArray)
|
||||
prm%sum_N_sl = sum(abs(N_sl))
|
||||
slipActive: if (prm%sum_N_sl > 0) then
|
||||
prm%systems_sl = lattice_labels_slip(N_sl,phase_lattice(ph))
|
||||
prm%P_sl = lattice_SchmidMatrix_slip(N_sl,phase_lattice(ph),phase_cOverA(ph))
|
||||
|
||||
if (phase_lattice(ph) == 'cI') then
|
||||
|
@ -126,8 +130,7 @@ module function plastic_phenopowerlaw_init() result(myPlasticity)
|
|||
prm%P_nS_pos = prm%P_sl
|
||||
prm%P_nS_neg = prm%P_sl
|
||||
endif
|
||||
prm%h_sl_sl = lattice_interaction_SlipBySlip(N_sl,pl%get_as1dFloat('h_sl-sl'), &
|
||||
phase_lattice(ph))
|
||||
prm%h_sl_sl = lattice_interaction_SlipBySlip(N_sl,pl%get_as1dFloat('h_sl-sl'),phase_lattice(ph))
|
||||
|
||||
xi_0_sl = pl%get_as1dFloat('xi_0_sl', requiredSize=size(N_sl))
|
||||
prm%xi_inf_sl = pl%get_as1dFloat('xi_inf_sl', requiredSize=size(N_sl))
|
||||
|
@ -162,11 +165,10 @@ module function plastic_phenopowerlaw_init() result(myPlasticity)
|
|||
N_tw = pl%get_as1dInt('N_tw', defaultVal=emptyIntArray)
|
||||
prm%sum_N_tw = sum(abs(N_tw))
|
||||
twinActive: if (prm%sum_N_tw > 0) then
|
||||
prm%P_tw = lattice_SchmidMatrix_twin(N_tw,phase_lattice(ph),phase_cOverA(ph))
|
||||
prm%h_tw_tw = lattice_interaction_TwinByTwin(N_tw,pl%get_as1dFloat('h_tw-tw'), &
|
||||
phase_lattice(ph))
|
||||
prm%gamma_char = lattice_characteristicShear_twin(N_tw,phase_lattice(ph),&
|
||||
phase_cOverA(ph))
|
||||
prm%systems_tw = lattice_labels_twin(N_tw,phase_lattice(ph))
|
||||
prm%P_tw = lattice_SchmidMatrix_twin(N_tw,phase_lattice(ph),phase_cOverA(ph))
|
||||
prm%h_tw_tw = lattice_interaction_TwinByTwin(N_tw,pl%get_as1dFloat('h_tw-tw'),phase_lattice(ph))
|
||||
prm%gamma_char = lattice_characteristicShear_twin(N_tw,phase_lattice(ph),phase_cOverA(ph))
|
||||
|
||||
xi_0_tw = pl%get_as1dFloat('xi_0_tw',requiredSize=size(N_tw))
|
||||
|
||||
|
@ -370,28 +372,33 @@ module subroutine plastic_phenopowerlaw_results(ph,group)
|
|||
integer, intent(in) :: ph
|
||||
character(len=*), intent(in) :: group
|
||||
|
||||
integer :: o
|
||||
integer :: ou
|
||||
|
||||
|
||||
associate(prm => param(ph), stt => state(ph))
|
||||
outputsLoop: do o = 1,size(prm%output)
|
||||
select case(trim(prm%output(o)))
|
||||
|
||||
case('xi_sl')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%xi_sl,group,trim(prm%output(o)), &
|
||||
'resistance against plastic slip','Pa')
|
||||
case('gamma_sl')
|
||||
if(prm%sum_N_sl>0) call results_writeDataset(stt%gamma_sl,group,trim(prm%output(o)), &
|
||||
'plastic shear','1')
|
||||
do ou = 1,size(prm%output)
|
||||
|
||||
case('xi_tw')
|
||||
if(prm%sum_N_tw>0) call results_writeDataset(stt%xi_tw,group,trim(prm%output(o)), &
|
||||
'resistance against twinning','Pa')
|
||||
case('gamma_tw')
|
||||
if(prm%sum_N_tw>0) call results_writeDataset(stt%gamma_tw,group,trim(prm%output(o)), &
|
||||
'twinning shear','1')
|
||||
select case(trim(prm%output(ou)))
|
||||
|
||||
case('xi_sl')
|
||||
call results_writeDataset(stt%xi_sl,group,trim(prm%output(ou)), &
|
||||
'resistance against plastic slip','Pa',prm%systems_sl)
|
||||
case('gamma_sl')
|
||||
call results_writeDataset(stt%gamma_sl,group,trim(prm%output(ou)), &
|
||||
'plastic shear','1',prm%systems_sl)
|
||||
|
||||
case('xi_tw')
|
||||
call results_writeDataset(stt%xi_tw,group,trim(prm%output(ou)), &
|
||||
'resistance against twinning','Pa',prm%systems_tw)
|
||||
case('gamma_tw')
|
||||
call results_writeDataset(stt%gamma_tw,group,trim(prm%output(ou)), &
|
||||
'twinning shear','1',prm%systems_tw)
|
||||
|
||||
end select
|
||||
|
||||
enddo
|
||||
|
||||
end select
|
||||
enddo outputsLoop
|
||||
end associate
|
||||
|
||||
end subroutine plastic_phenopowerlaw_results
|
||||
|
|
|
@ -34,10 +34,11 @@ module results
|
|||
end interface results_writeDataset
|
||||
|
||||
interface results_addAttribute
|
||||
module procedure results_addAttribute_real
|
||||
module procedure results_addAttribute_int
|
||||
module procedure results_addAttribute_str
|
||||
module procedure results_addAttribute_int
|
||||
module procedure results_addAttribute_real
|
||||
|
||||
module procedure results_addAttribute_str_array
|
||||
module procedure results_addAttribute_int_array
|
||||
module procedure results_addAttribute_real_array
|
||||
end interface results_addAttribute
|
||||
|
@ -210,7 +211,7 @@ subroutine results_setLink(path,link)
|
|||
end subroutine results_setLink
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief adds a string attribute to an object in the results file
|
||||
!> @brief Add a string attribute to an object in the results file.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine results_addAttribute_str(attrLabel,attrValue,path)
|
||||
|
||||
|
@ -228,7 +229,7 @@ end subroutine results_addAttribute_str
|
|||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief adds an integer attribute an object in the results file
|
||||
!> @brief Add an integer attribute an object in the results file.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine results_addAttribute_int(attrLabel,attrValue,path)
|
||||
|
||||
|
@ -247,7 +248,7 @@ end subroutine results_addAttribute_int
|
|||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief adds a real attribute an object in the results file
|
||||
!> @brief Add a real attribute an object in the results file.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine results_addAttribute_real(attrLabel,attrValue,path)
|
||||
|
||||
|
@ -266,7 +267,26 @@ end subroutine results_addAttribute_real
|
|||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief adds an integer array attribute an object in the results file
|
||||
!> @brief Add a string array attribute an object in the results file.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine results_addAttribute_str_array(attrLabel,attrValue,path)
|
||||
|
||||
character(len=*), intent(in) :: attrLabel
|
||||
character(len=*), intent(in), dimension(:) :: attrValue
|
||||
character(len=*), intent(in), optional :: path
|
||||
|
||||
|
||||
if (present(path)) then
|
||||
call HDF5_addAttribute(resultsFile,attrLabel, attrValue, path)
|
||||
else
|
||||
call HDF5_addAttribute(resultsFile,attrLabel, attrValue)
|
||||
endif
|
||||
|
||||
end subroutine results_addAttribute_str_array
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Add an integer array attribute an object in the results file.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine results_addAttribute_int_array(attrLabel,attrValue,path)
|
||||
|
||||
|
@ -285,7 +305,7 @@ end subroutine results_addAttribute_int_array
|
|||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief adds a real array attribute an object in the results file
|
||||
!> @brief Add a real array attribute an object in the results file.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine results_addAttribute_real_array(attrLabel,attrValue,path)
|
||||
|
||||
|
@ -336,7 +356,6 @@ subroutine results_writeDataset_str(dataset,group,label,description)
|
|||
|
||||
end subroutine results_writeDataset_str
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Store real scalar dataset with associated metadata.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
@ -360,18 +379,24 @@ end subroutine results_writeScalarDataset_real
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Store real vector dataset with associated metadata.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine results_writeVectorDataset_real(dataset,group,label,description,SIunit)
|
||||
subroutine results_writeVectorDataset_real(dataset,group,label,description,SIunit,systems)
|
||||
|
||||
character(len=*), intent(in) :: label,group,description
|
||||
character(len=*), intent(in), optional :: SIunit
|
||||
character(len=*), intent(in), dimension(:), optional :: systems
|
||||
real(pReal), intent(in), dimension(:,:) :: dataset
|
||||
|
||||
integer(HID_T) :: groupHandle
|
||||
|
||||
|
||||
if (present(systems)) then
|
||||
if (size(systems)*size(dataset,2) == 0 ) return !ToDo: maybe also implement for other results_write (not sure about scalar)
|
||||
endif
|
||||
|
||||
groupHandle = results_openGroup(group)
|
||||
call HDF5_write(dataset,groupHandle,label)
|
||||
call executionStamp(group//'/'//label,description,SIunit)
|
||||
if (present(systems)) call HDF5_addAttribute(resultsFile,'systems',systems,group//'/'//label)
|
||||
call HDF5_closeGroup(groupHandle)
|
||||
|
||||
end subroutine results_writeVectorDataset_real
|
||||
|
@ -420,18 +445,24 @@ end subroutine results_writeTensorDataset_real
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Store integer vector dataset with associated metadata.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine results_writeVectorDataset_int(dataset,group,label,description,SIunit)
|
||||
subroutine results_writeVectorDataset_int(dataset,group,label,description,SIunit,systems)
|
||||
|
||||
character(len=*), intent(in) :: label,group,description
|
||||
character(len=*), intent(in), optional :: SIunit
|
||||
character(len=*), intent(in), dimension(:), optional :: systems
|
||||
integer, intent(in), dimension(:,:) :: dataset
|
||||
|
||||
integer(HID_T) :: groupHandle
|
||||
|
||||
|
||||
if (present(systems)) then
|
||||
if (size(systems)*size(dataset,2) == 0 ) return !ToDo: maybe also implement for other results_write (not sure about scalar)
|
||||
endif
|
||||
|
||||
groupHandle = results_openGroup(group)
|
||||
call HDF5_write(dataset,groupHandle,label)
|
||||
call executionStamp(group//'/'//label,description,SIunit)
|
||||
if (present(systems)) call HDF5_addAttribute(resultsFile,'systems',systems,group//'/'//label)
|
||||
call HDF5_closeGroup(groupHandle)
|
||||
|
||||
end subroutine results_writeVectorDataset_int
|
||||
|
|
Loading…
Reference in New Issue