polishing

This commit is contained in:
Martin Diehl 2019-04-07 14:28:08 +02:00
parent 2fa8691335
commit 0b70f01e04
2 changed files with 71 additions and 33 deletions

View File

@ -208,7 +208,7 @@ integer(HID_T) function HDF5_addGroup(fileHandle,groupName)
call h5gcreate_f(fileHandle, trim(groupName), HDF5_addGroup, hdferr, OBJECT_NAMELEN_DEFAULT_F,gapl_id = aplist_id) call h5gcreate_f(fileHandle, trim(groupName), HDF5_addGroup, hdferr, OBJECT_NAMELEN_DEFAULT_F,gapl_id = aplist_id)
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_addGroup: h5gcreate_f ('//trim(groupName)//')') if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_addGroup: h5gcreate_f ('//trim(groupName)//')')
call h5pclose_f(aplist_id) call h5pclose_f(aplist_id,hdferr)
end function HDF5_addGroup end function HDF5_addGroup
@ -244,7 +244,7 @@ integer(HID_T) function HDF5_openGroup(fileHandle,groupName)
call h5gopen_f(fileHandle, trim(groupName), HDF5_openGroup, hdferr, gapl_id = aplist_id) call h5gopen_f(fileHandle, trim(groupName), HDF5_openGroup, hdferr, gapl_id = aplist_id)
if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_openGroup: h5gopen_f ('//trim(groupName)//')') if (hdferr < 0) call IO_error(1_pInt,ext_msg = 'HDF5_openGroup: h5gopen_f ('//trim(groupName)//')')
call h5pclose_f(aplist_id) call h5pclose_f(aplist_id,hdferr)
end function HDF5_openGroup end function HDF5_openGroup

View File

@ -1083,6 +1083,7 @@ subroutine crystallite_results
#if defined(PETSc) || defined(DAMASK_HDF5) #if defined(PETSc) || defined(DAMASK_HDF5)
use results use results
use HDF5_utilities use HDF5_utilities
use rotations
use config, only: & use config, only: &
config_name_phase => phase_name ! anticipate logical name config_name_phase => phase_name ! anticipate logical name
@ -1091,76 +1092,81 @@ subroutine crystallite_results
implicit none implicit none
integer :: p,o integer :: p,o
real(pReal), allocatable, dimension(:,:,:) :: selected real(pReal), allocatable, dimension(:,:,:) :: selected_tensors
type(rotation), allocatable, dimension(:) :: selected_rotations
character(len=256) :: group character(len=256) :: group
character(len=16) :: j
call HDF5_closeGroup(results_addGroup('current/constituent')) call HDF5_closeGroup(results_addGroup('current/constituent'))
do p=1,size(config_name_phase) do p=1,size(config_name_phase)
write(j,('(i2.2)')) p ! allow 99 groups group = trim('current/constituent')//'/'//trim(config_name_phase(p))
group = trim('current/constituent')//'/'//trim(j)//'_'//trim(config_name_phase(p))
call HDF5_closeGroup(results_addGroup(group)) call HDF5_closeGroup(results_addGroup(group))
do o = 1, size(output_constituent(p)%label) do o = 1, size(output_constituent(p)%label)
select case (output_constituent(p)%label(o)) select case (output_constituent(p)%label(o))
case('f') case('f')
selected = packed(crystallite_partionedF,p) selected_tensors = select_tensors(crystallite_partionedF,p)
call results_writeDataset(group,selected,'F',& call results_writeDataset(group,selected_tensors,'F',&
'deformation gradient','1') 'deformation gradient','1')
case('fe') case('fe')
selected = packed(crystallite_Fe,p) selected_tensors = select_tensors(crystallite_Fe,p)
call results_writeDataset(group,selected,'Fe',& call results_writeDataset(group,selected_tensors,'Fe',&
'elastic deformation gradient','1') 'elastic deformation gradient','1')
case('fp') case('fp')
selected = packed(crystallite_Fp,p) selected_tensors = select_tensors(crystallite_Fp,p)
call results_writeDataset(group,selected,'Fp',& call results_writeDataset(group,selected_tensors,'Fp',&
'plastic deformation gradient','1') 'plastic deformation gradient','1')
case('fi') case('fi')
selected = packed(crystallite_Fi,p) selected_tensors = select_tensors(crystallite_Fi,p)
call results_writeDataset(group,selected,'Fi',& call results_writeDataset(group,selected_tensors,'Fi',&
'inelastic deformation gradient','1') 'inelastic deformation gradient','1')
case('lp') case('lp')
selected = packed(crystallite_Lp,p) selected_tensors = select_tensors(crystallite_Lp,p)
call results_writeDataset(group,selected,'Lp',& call results_writeDataset(group,selected_tensors,'Lp',&
'plastic velocity gradient','1/s') 'plastic velocity gradient','1/s')
case('li') case('li')
selected = packed(crystallite_Li,p) selected_tensors = select_tensors(crystallite_Li,p)
call results_writeDataset(group,selected,'Li',& call results_writeDataset(group,selected_tensors,'Li',&
'inelastic velocity gradient','1/s') 'inelastic velocity gradient','1/s')
case('p') case('p')
selected = packed(crystallite_P,p) selected_tensors = select_tensors(crystallite_P,p)
call results_writeDataset(group,selected,'P',& call results_writeDataset(group,selected_tensors,'P',&
'1st Piola-Kirchoff stress','Pa') '1st Piola-Kirchoff stress','Pa')
case('s') case('s')
selected = packed(crystallite_S,p) selected_tensors = select_tensors(crystallite_S,p)
call results_writeDataset(group,selected,'S',& call results_writeDataset(group,selected_tensors,'S',&
'2nd Piola-Kirchoff stress','Pa') '2nd Piola-Kirchoff stress','Pa')
case('orientation')
selected_rotations = select_rotations(crystallite_orientation,p)
call results_writeDataset(group,selected_rotations,'orientation',&
'crystal orientation as quaternion','1')
end select end select
enddo enddo
enddo enddo
contains contains
function packed(res,instance) !--------------------------------------------------------------------------------------------------
!> @brief select tensors for output
!--------------------------------------------------------------------------------------------------
function select_tensors(dataset,instance)
use material, only: & use material, only: &
homogenization_maxNgrains, & homogenization_maxNgrains, &
material_phaseAt material_phaseAt
integer, intent(in) :: instance integer, intent(in) :: instance
real(pReal), dimension(:,:,:,:,:), intent(in) :: res real(pReal), dimension(:,:,:,:,:), intent(in) :: dataset
real(pReal), allocatable, dimension(:,:,:) :: packed real(pReal), allocatable, dimension(:,:,:) :: select_tensors
integer :: e,i,c,j integer :: e,i,c,j
allocate(packed(3,3,count(material_phaseAt==instance)*homogenization_maxNgrains)) allocate(select_tensors(3,3,count(material_phaseAt==instance)*homogenization_maxNgrains))
!---------------------------------------------------------------------------------------------------
! expand phaseAt to consider IPs (is not stored per IP)
j=1 j=1
do e = 1, size(material_phaseAt,2) do e = 1, size(material_phaseAt,2)
do i = 1, homogenization_maxNgrains do i = 1, homogenization_maxNgrains !ToDo: this needs to be changed for varying Ngrains
do c = 1, size(material_phaseAt,1) do c = 1, size(material_phaseAt,1)
if (material_phaseAt(c,e) == instance) then if (material_phaseAt(c,e) == instance) then
packed(1:3,1:3,j) = res(1:3,1:3,c,i,e) select_tensors(1:3,1:3,j) = dataset(1:3,1:3,c,i,e)
j = j + 1 j = j + 1
endif endif
enddo enddo
@ -1168,7 +1174,39 @@ subroutine crystallite_results
enddo enddo
end function packed end function select_tensors
!--------------------------------------------------------------------------------------------------
!> @brief select rotations for output
!--------------------------------------------------------------------------------------------------
function select_rotations(dataset,instance)
use material, only: &
homogenization_maxNgrains, &
material_phaseAt
integer, intent(in) :: instance
type(rotation), dimension(:,:,:), intent(in) :: dataset
type(rotation), allocatable, dimension(:) :: select_rotations
integer :: e,i,c,j
allocate(select_rotations(count(material_phaseAt==instance)*homogenization_maxNgrains))
j=1
do e = 1, size(material_phaseAt,2)
do i = 1, homogenization_maxNgrains !ToDo: this needs to be changed for varying Ngrains
do c = 1, size(material_phaseAt,1)
if (material_phaseAt(c,e) == instance) then
select_rotations(j) = dataset(c,i,e)
j = j + 1
endif
enddo
enddo
enddo
end function select_rotations
#endif #endif