DAMASK with grid solvers  Revision: v2.0.3-2204-gdb1f2151
The Düsseldorf Advanced Material Simulation Kit with Grid Solvers
results.f90
Go to the documentation of this file.
1 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/results.f90"
2 # 1 "<built-in>"
3 # 1 "<command-line>"
4 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/results.f90"
5 !--------------------------------------------------------------------------------------------------
10 !--------------------------------------------------------------------------------------------------
11 module results
13  use rotations
14  use numerics
15  use hdf5_utilities
16 
17  use petsc
18 
19 
20  implicit none
21  private
22 
23  integer(HID_T) :: resultsfile
24 
26 
27  module procedure results_writetensordataset_real
28  module procedure results_writevectordataset_real
29  module procedure results_writescalardataset_real
30 
31  module procedure results_writetensordataset_int
32  module procedure results_writevectordataset_int
33 
35 
36  end interface results_writedataset
37 
39 
40  module procedure results_addattribute_real
41  module procedure results_addattribute_int
42  module procedure results_addattribute_str
43 
44  module procedure results_addattribute_int_array
45  module procedure results_addattribute_real_array
46 
47  end interface results_addattribute
48 
49  public :: &
50  results_init, &
64 contains
65 
66 subroutine results_init
67 
68  character(len=pStringLen) :: commandline
69 
70  write(6,'(/,a)') ' <<<+- results init -+>>>'
71 
72  write(6,'(/,a)') ' Diehl et al., Integrating Materials and Manufacturing Innovation 6(1):83–91, 2017'
73  write(6,'(a)') ' https://doi.org/10.1007/s40192-017-0084-5'
74 
75  resultsfile = hdf5_openfile(trim(getsolverjobname())//'.hdf5','w',.true.)
76  call results_addattribute('DADF5_version_major',0)
77  call results_addattribute('DADF5_version_minor',6)
78  call results_addattribute('DAMASK_version',damaskversion)
79  call get_command(commandline)
80  call results_addattribute('call',trim(commandline))
81  call results_closegroup(results_addgroup('mapping'))
82  call results_closegroup(results_addgroup('mapping/cellResults'))
84 
85 end subroutine results_init
86 
87 
88 !--------------------------------------------------------------------------------------------------
90 !--------------------------------------------------------------------------------------------------
91 subroutine results_openjobfile
92 
93  resultsfile = hdf5_openfile(trim(getsolverjobname())//'.hdf5','a',.true.)
94 
95 end subroutine results_openjobfile
96 
97 
98 !--------------------------------------------------------------------------------------------------
100 !--------------------------------------------------------------------------------------------------
101 subroutine results_closejobfile
102 
104 
105 end subroutine results_closejobfile
106 
107 
108 !--------------------------------------------------------------------------------------------------
110 !--------------------------------------------------------------------------------------------------
111 subroutine results_addincrement(inc,time)
112 
113  integer, intent(in) :: inc
114  real(preal), intent(in) :: time
115  character(len=pStringLen) :: incchar
116 
117  write(incchar,'(i10)') inc
118  call results_closegroup(results_addgroup(trim('inc'//trim(adjustl(incchar)))))
119  call results_setlink(trim('inc'//trim(adjustl(incchar))),'current')
120  call results_addattribute('time/s',time,trim('inc'//trim(adjustl(incchar))))
121  call results_closegroup(results_addgroup('current/constituent'))
122  call results_closegroup(results_addgroup('current/materialpoint'))
123 
124 end subroutine results_addincrement
125 
126 
127 !--------------------------------------------------------------------------------------------------
130 !--------------------------------------------------------------------------------------------------
131 subroutine results_finalizeincrement
132 
133  call results_removelink('current')
134 
135 end subroutine results_finalizeincrement
136 
137 
138 !--------------------------------------------------------------------------------------------------
140 !--------------------------------------------------------------------------------------------------
141 integer(HID_T) function results_opengroup(groupName)
142 
143  character(len=*), intent(in) :: groupname
144 
146 
147 end function results_opengroup
148 
149 
150 !--------------------------------------------------------------------------------------------------
152 !--------------------------------------------------------------------------------------------------
153 integer(HID_T) function results_addgroup(groupName)
154 
155  character(len=*), intent(in) :: groupname
156 
158 
159 end function results_addgroup
160 
161 
162 !--------------------------------------------------------------------------------------------------
164 !--------------------------------------------------------------------------------------------------
165 subroutine results_closegroup(group_id)
166 
167  integer(HID_T), intent(in) :: group_id
168 
169  call hdf5_closegroup(group_id)
170 
171 end subroutine results_closegroup
172 
173 
174 !--------------------------------------------------------------------------------------------------
176 !--------------------------------------------------------------------------------------------------
177 subroutine results_setlink(path,link)
178 
179  character(len=*), intent(in) :: path, link
180 
181  call hdf5_setlink(resultsfile,path,link)
182 
183 end subroutine results_setlink
184 
185 
186 !--------------------------------------------------------------------------------------------------
188 !--------------------------------------------------------------------------------------------------
189 subroutine results_addattribute_str(attrLabel,attrValue,path)
190 
191  character(len=*), intent(in) :: attrLabel, attrValue
192  character(len=*), intent(in), optional :: path
193 
194  if (present(path)) then
195  call hdf5_addattribute(resultsfile,attrlabel, attrvalue, path)
196  else
197  call hdf5_addattribute(resultsfile,attrlabel, attrvalue)
198  endif
199 
200 end subroutine results_addattribute_str
201 
202 
203 !--------------------------------------------------------------------------------------------------
205 !--------------------------------------------------------------------------------------------------
206 subroutine results_addattribute_int(attrLabel,attrValue,path)
207 
208  character(len=*), intent(in) :: attrLabel
209  integer, intent(in) :: attrValue
210  character(len=*), intent(in), optional :: path
211 
212  if (present(path)) then
213  call hdf5_addattribute(resultsfile,attrlabel, attrvalue, path)
214  else
215  call hdf5_addattribute(resultsfile,attrlabel, attrvalue)
216  endif
217 
218 end subroutine results_addattribute_int
219 
220 
221 !--------------------------------------------------------------------------------------------------
223 !--------------------------------------------------------------------------------------------------
224 subroutine results_addattribute_real(attrLabel,attrValue,path)
225 
226  character(len=*), intent(in) :: attrLabel
227  real(pReal), intent(in) :: attrValue
228  character(len=*), intent(in), optional :: path
229 
230  if (present(path)) then
231  call hdf5_addattribute(resultsfile,attrlabel, attrvalue, path)
232  else
233  call hdf5_addattribute(resultsfile,attrlabel, attrvalue)
234  endif
235 
236 end subroutine results_addattribute_real
237 
238 
239 !--------------------------------------------------------------------------------------------------
241 !--------------------------------------------------------------------------------------------------
242 subroutine results_addattribute_int_array(attrLabel,attrValue,path)
243 
244  character(len=*), intent(in) :: attrLabel
245  integer, intent(in), dimension(:) :: attrValue
246  character(len=*), intent(in), optional :: path
247 
248  if (present(path)) then
249  call hdf5_addattribute(resultsfile,attrlabel, attrvalue, path)
250  else
251  call hdf5_addattribute(resultsfile,attrlabel, attrvalue)
252  endif
253 
254 end subroutine results_addattribute_int_array
255 
256 
257 !--------------------------------------------------------------------------------------------------
259 !--------------------------------------------------------------------------------------------------
260 subroutine results_addattribute_real_array(attrLabel,attrValue,path)
261 
262  character(len=*), intent(in) :: attrLabel
263  real(pReal), intent(in), dimension(:) :: attrValue
264  character(len=*), intent(in), optional :: path
265 
266  if (present(path)) then
267  call hdf5_addattribute(resultsfile,attrlabel, attrvalue, path)
268  else
269  call hdf5_addattribute(resultsfile,attrlabel, attrvalue)
270  endif
271 
272 end subroutine results_addattribute_real_array
273 
274 
275 !--------------------------------------------------------------------------------------------------
277 !--------------------------------------------------------------------------------------------------
278 subroutine results_removelink(link)
279 
280  character(len=*), intent(in) :: link
281  integer :: hdferr
282 
283  call h5ldelete_f(resultsfile,link, hdferr)
284  if (hdferr < 0) call io_error(1,ext_msg = 'results_removeLink: h5ldelete_soft_f ('//trim(link)//')')
285 
286 end subroutine results_removelink
287 
288 
289 !--------------------------------------------------------------------------------------------------
291 !--------------------------------------------------------------------------------------------------
292 subroutine results_writescalardataset_real(group,dataset,label,description,SIunit)
293 
294  character(len=*), intent(in) :: label,group,description
295  character(len=*), intent(in), optional :: SIunit
296  real(pReal), intent(inout), dimension(:) :: dataset
297 
298  integer(HID_T) :: groupHandle
299 
300  grouphandle = results_opengroup(group)
301 
302 
303  call hdf5_write(grouphandle,dataset,label,.true.)
304 
305 
306 
307 
308  if (hdf5_objectexists(grouphandle,label)) &
309  call hdf5_addattribute(grouphandle,'Description',description,label)
310  if (hdf5_objectexists(grouphandle,label) .and. present(siunit)) &
311  call hdf5_addattribute(grouphandle,'Unit',siunit,label)
312  if (hdf5_objectexists(grouphandle,label)) &
313  call hdf5_addattribute(grouphandle,'Creator','DAMASK '//damaskversion,label)
314  call hdf5_closegroup(grouphandle)
315 
316 end subroutine results_writescalardataset_real
317 
318 !--------------------------------------------------------------------------------------------------
320 !--------------------------------------------------------------------------------------------------
321 subroutine results_writevectordataset_real(group,dataset,label,description,SIunit)
322 
323  character(len=*), intent(in) :: label,group,description
324  character(len=*), intent(in), optional :: SIunit
325  real(pReal), intent(inout), dimension(:,:) :: dataset
326 
327  integer(HID_T) :: groupHandle
328 
329  grouphandle = results_opengroup(group)
330 
331 
332  call hdf5_write(grouphandle,dataset,label,.true.)
333 
334 
335 
336 
337  if (hdf5_objectexists(grouphandle,label)) &
338  call hdf5_addattribute(grouphandle,'Description',description,label)
339  if (hdf5_objectexists(grouphandle,label) .and. present(siunit)) &
340  call hdf5_addattribute(grouphandle,'Unit',siunit,label)
341  if (hdf5_objectexists(grouphandle,label)) &
342  call hdf5_addattribute(grouphandle,'Creator','DAMASK '//damaskversion,label)
343  call hdf5_closegroup(grouphandle)
344 
345 end subroutine results_writevectordataset_real
346 
347 
348 !--------------------------------------------------------------------------------------------------
350 !--------------------------------------------------------------------------------------------------
351 subroutine results_writetensordataset_real(group,dataset,label,description,SIunit,transposed)
352 
353  character(len=*), intent(in) :: label,group,description
354  character(len=*), intent(in), optional :: SIunit
355  logical, intent(in), optional :: transposed
356  real(pReal), intent(in), dimension(:,:,:) :: dataset
357 
358  integer :: i
359  logical :: transposed_
360  integer(HID_T) :: groupHandle
361  real(pReal), dimension(:,:,:), allocatable :: dataset_transposed
362 
363 
364  if(present(transposed)) then
365  transposed_ = transposed
366  else
367  transposed_ = .true.
368  endif
369 
370  if(transposed_) then
371  if(size(dataset,1) /= size(dataset,2)) call io_error(0,ext_msg='transpose non-symmetric tensor')
372  allocate(dataset_transposed,mold=dataset)
373  do i=1,size(dataset_transposed,3)
374  dataset_transposed(:,:,i) = transpose(dataset(:,:,i))
375  enddo
376  else
377  allocate(dataset_transposed,source=dataset)
378  endif
379 
380  grouphandle = results_opengroup(group)
381 
382 
383  call hdf5_write(grouphandle,dataset_transposed,label,.true.)
384 
385 
386 
387 
388  if (hdf5_objectexists(grouphandle,label)) &
389  call hdf5_addattribute(grouphandle,'Description',description,label)
390  if (hdf5_objectexists(grouphandle,label) .and. present(siunit)) &
391  call hdf5_addattribute(grouphandle,'Unit',siunit,label)
392  if (hdf5_objectexists(grouphandle,label)) &
393  call hdf5_addattribute(grouphandle,'Creator','DAMASK '//damaskversion,label)
394  call hdf5_closegroup(grouphandle)
395 
396 end subroutine results_writetensordataset_real
397 
398 
399 !--------------------------------------------------------------------------------------------------
401 !--------------------------------------------------------------------------------------------------
402 subroutine results_writevectordataset_int(group,dataset,label,description,SIunit)
403 
404  character(len=*), intent(in) :: label,group,description
405  character(len=*), intent(in), optional :: SIunit
406  integer, intent(inout), dimension(:,:) :: dataset
407 
408  integer(HID_T) :: groupHandle
409 
410  grouphandle = results_opengroup(group)
411 
412 
413  call hdf5_write(grouphandle,dataset,label,.true.)
414 
415 
416 
417 
418  if (hdf5_objectexists(grouphandle,label)) &
419  call hdf5_addattribute(grouphandle,'Description',description,label)
420  if (hdf5_objectexists(grouphandle,label) .and. present(siunit)) &
421  call hdf5_addattribute(grouphandle,'Unit',siunit,label)
422  if (hdf5_objectexists(grouphandle,label)) &
423  call hdf5_addattribute(grouphandle,'Creator','DAMASK '//damaskversion,label)
424  call hdf5_closegroup(grouphandle)
425 
426 end subroutine results_writevectordataset_int
427 
428 
429 !--------------------------------------------------------------------------------------------------
431 !--------------------------------------------------------------------------------------------------
432 subroutine results_writetensordataset_int(group,dataset,label,description,SIunit)
433 
434  character(len=*), intent(in) :: label,group,description
435  character(len=*), intent(in), optional :: SIunit
436  integer, intent(inout), dimension(:,:,:) :: dataset
437 
438  integer(HID_T) :: groupHandle
439 
440  grouphandle = results_opengroup(group)
441 
442 
443  call hdf5_write(grouphandle,dataset,label,.true.)
444 
445 
446 
447 
448  if (hdf5_objectexists(grouphandle,label)) &
449  call hdf5_addattribute(grouphandle,'Description',description,label)
450  if (hdf5_objectexists(grouphandle,label) .and. present(siunit)) &
451  call hdf5_addattribute(grouphandle,'Unit',siunit,label)
452  if (hdf5_objectexists(grouphandle,label)) &
453  call hdf5_addattribute(grouphandle,'Creator','DAMASK '//damaskversion,label)
454  call hdf5_closegroup(grouphandle)
455 
456 end subroutine results_writetensordataset_int
457 
458 
459 !--------------------------------------------------------------------------------------------------
461 !--------------------------------------------------------------------------------------------------
462 subroutine results_writescalardataset_rotation(group,dataset,label,description,lattice_structure)
463 
464  character(len=*), intent(in) :: label,group,description
465  character(len=*), intent(in), optional :: lattice_structure
466  type(rotation), intent(inout), dimension(:) :: dataset
467 
468  integer(HID_T) :: groupHandle
469 
470  grouphandle = results_opengroup(group)
471 
472 
473  call hdf5_write(grouphandle,dataset,label,.true.)
474 
475 
476 
477 
478  if (hdf5_objectexists(grouphandle,label)) &
479  call hdf5_addattribute(grouphandle,'Description',description,label)
480  if (hdf5_objectexists(grouphandle,label) .and. present(lattice_structure)) &
481  call hdf5_addattribute(grouphandle,'Lattice',lattice_structure,label)
482  if (hdf5_objectexists(grouphandle,label)) &
483  call hdf5_addattribute(grouphandle,'Creator','DAMASK '//damaskversion,label)
484  call hdf5_closegroup(grouphandle)
485 
487 
488 
489 !--------------------------------------------------------------------------------------------------
491 !--------------------------------------------------------------------------------------------------
492 subroutine results_mapping_constituent(phaseAt,memberAtLocal,label)
493 
494  integer, dimension(:,:), intent(in) :: phaseat
495  integer, dimension(:,:,:), intent(in) :: memberatlocal
496  character(len=pStringLen), dimension(:), intent(in) :: label
497 
498  integer, dimension(size(memberAtLocal,1),size(memberAtLocal,2),size(memberAtLocal,3)) :: &
499  phaseatmaterialpoint, &
500  memberatglobal
501  integer, dimension(size(label),0:worldsize-1) :: memberoffset
502  integer, dimension(0:worldsize-1) :: writesize
503  integer(HSIZE_T), dimension(2) :: &
504  myshape, & !< shape of the dataset (this process)
505  myoffset, &
506  totalshape
507 
508  integer(HID_T) :: &
509  loc_id, & !< identifier of group in file
510  dtype_id, & !< identifier of compound data type
511  name_id, & !< identifier of name (string) in compound data type
512  position_id, & !< identifier of position/index (integer) in compound data type
513  dset_id, &
514  memspace_id, &
515  filespace_id, &
516  plist_id, &
517  dt_id
518 
519 
520  integer(SIZE_T) :: type_size_string, type_size_int
521  integer :: ierr, i
522 
523 !---------------------------------------------------------------------------------------------------
524 ! compound type: name of phase section + position/index within results array
525  call h5tcopy_f(h5t_native_character, dt_id, ierr)
526  call h5tset_size_f(dt_id, int(len(label(1)),size_t), ierr)
527  call h5tget_size_f(dt_id, type_size_string, ierr)
528 
529  call h5tget_size_f(h5t_native_integer, type_size_int, ierr)
530 
531  call h5tcreate_f(h5t_compound_f, type_size_string + type_size_int, dtype_id, ierr)
532  call h5tinsert_f(dtype_id, "Name", 0_size_t, dt_id,ierr)
533  call h5tinsert_f(dtype_id, "Position", type_size_string, h5t_native_integer, ierr)
534 
535 !--------------------------------------------------------------------------------------------------
536 ! create memory types for each component of the compound type
537  call h5tcreate_f(h5t_compound_f, type_size_string, name_id, ierr)
538  call h5tinsert_f(name_id, "Name", 0_size_t, dt_id, ierr)
539 
540  call h5tcreate_f(h5t_compound_f, type_size_int, position_id, ierr)
541  call h5tinsert_f(position_id, "Position", 0_size_t, h5t_native_integer, ierr)
542 
543  call h5tclose_f(dt_id, ierr)
544 
545 !--------------------------------------------------------------------------------------------------
546 ! prepare MPI communication (transparent for non-MPI runs)
547  call h5pcreate_f(h5p_dataset_xfer_f, plist_id, ierr)
548  memberoffset = 0
549  do i=1, size(label)
550  memberoffset(i,worldrank) = count(phaseat == i)*size(memberatlocal,2) ! number of points/instance of this process
551  enddo
552  writesize = 0
553  writesize(worldrank) = size(memberatlocal(1,:,:)) ! total number of points by this process
554 
555 !--------------------------------------------------------------------------------------------------
556 ! MPI settings and communication
557 
558  call h5pset_dxpl_mpio_f(plist_id, h5fd_mpio_collective_f, ierr)
559  if (ierr < 0) call io_error(1,ext_msg='results_mapping_constituent: h5pset_dxpl_mpio_f')
560 
561  call mpi_allreduce(mpi_in_place,writesize,worldsize,mpi_int,mpi_sum,petsc_comm_world,ierr) ! get output at each process
562  if (ierr /= 0) call io_error(894,ext_msg='results_mapping_constituent: MPI_allreduce/writeSize')
563 
564  call mpi_allreduce(mpi_in_place,memberoffset,size(memberoffset),mpi_int,mpi_sum,petsc_comm_world,ierr)! get offset at each process
565  if (ierr /= 0) call io_error(894,ext_msg='results_mapping_constituent: MPI_allreduce/memberOffset')
566 
567 
568  myshape = int([size(phaseat,1),writesize(worldrank)], hsize_t)
569  myoffset = int([0,sum(writesize(0:worldrank-1))], hsize_t)
570  totalshape = int([size(phaseat,1),sum(writesize)], hsize_t)
571 
572 !--------------------------------------------------------------------------------------------------
573 ! create dataspace in memory (local shape = hyperslab) and in file (global shape)
574  call h5screate_simple_f(2,myshape,memspace_id,ierr,myshape)
575  if (ierr < 0) call io_error(1,ext_msg='results_mapping_constituent: h5screate_simple_f/memspace_id')
576 
577  call h5screate_simple_f(2,totalshape,filespace_id,ierr,totalshape)
578  if (ierr < 0) call io_error(1,ext_msg='results_mapping_constituent: h5screate_simple_f/filespace_id')
579 
580  call h5sselect_hyperslab_f(filespace_id, h5s_select_set_f, myoffset, myshape, ierr)
581  if (ierr < 0) call io_error(1,ext_msg='results_mapping_constituent: h5sselect_hyperslab_f')
582 
583 !---------------------------------------------------------------------------------------------------
584 ! expand phaseAt to consider IPs (is not stored per IP)
585  do i = 1, size(phaseatmaterialpoint,2)
586  phaseatmaterialpoint(:,i,:) = phaseat
587  enddo
588 
589 !---------------------------------------------------------------------------------------------------
590 ! renumber member from my process to all processes
591  do i = 1, size(label)
592  where(phaseatmaterialpoint == i) memberatglobal = memberatlocal + sum(memberoffset(i,0:worldrank-1)) -1 ! convert to 0-based
593  enddo
594 
595 !--------------------------------------------------------------------------------------------------
596 ! write the components of the compound type individually
597  call h5pset_preserve_f(plist_id, .true., ierr)
598 
599  loc_id = results_opengroup('/mapping/cellResults')
600  call h5dcreate_f(loc_id, 'constituent', dtype_id, filespace_id, dset_id, ierr)
601  if (ierr < 0) call io_error(1,ext_msg='results_mapping_constituent: h5dcreate_f')
602 
603  call h5dwrite_f(dset_id, name_id, reshape(label(pack(phaseatmaterialpoint,.true.)),myshape), &
604  myshape, ierr, file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
605  if (ierr < 0) call io_error(1,ext_msg='results_mapping_constituent: h5dwrite_f/name_id')
606  call h5dwrite_f(dset_id, position_id, reshape(pack(memberatglobal,.true.),myshape), &
607  myshape, ierr, file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
608  if (ierr < 0) call io_error(1,ext_msg='results_mapping_constituent: h5dwrite_f/position_id')
609 
610 !--------------------------------------------------------------------------------------------------
611 ! close all
612  call hdf5_closegroup(loc_id)
613  call h5pclose_f(plist_id, ierr)
614  call h5sclose_f(filespace_id, ierr)
615  call h5sclose_f(memspace_id, ierr)
616  call h5dclose_f(dset_id, ierr)
617  call h5tclose_f(dtype_id, ierr)
618  call h5tclose_f(name_id, ierr)
619  call h5tclose_f(position_id, ierr)
620 
621 end subroutine results_mapping_constituent
622 
623 
624 !--------------------------------------------------------------------------------------------------
626 !--------------------------------------------------------------------------------------------------
627 subroutine results_mapping_materialpoint(homogenizationAt,memberAtLocal,label)
628 
629  integer, dimension(:), intent(in) :: homogenizationat
630  integer, dimension(:,:), intent(in) :: memberatlocal
631  character(len=pStringLen), dimension(:), intent(in) :: label
632 
633  integer, dimension(size(memberAtLocal,1),size(memberAtLocal,2)) :: &
634  homogenizationatmaterialpoint, &
635  memberatglobal
636  integer, dimension(size(label),0:worldsize-1) :: memberoffset
637  integer, dimension(0:worldsize-1) :: writesize
638  integer(HSIZE_T), dimension(1) :: &
639  myshape, & !< shape of the dataset (this process)
640  myoffset, &
641  totalshape
642 
643  integer(HID_T) :: &
644  loc_id, & !< identifier of group in file
645  dtype_id, & !< identifier of compound data type
646  name_id, & !< identifier of name (string) in compound data type
647  position_id, & !< identifier of position/index (integer) in compound data type
648  dset_id, &
649  memspace_id, &
650  filespace_id, &
651  plist_id, &
652  dt_id
653 
654 
655  integer(SIZE_T) :: type_size_string, type_size_int
656  integer :: ierr, i
657 
658 !---------------------------------------------------------------------------------------------------
659 ! compound type: name of phase section + position/index within results array
660  call h5tcopy_f(h5t_native_character, dt_id, ierr)
661  call h5tset_size_f(dt_id, int(len(label(1)),size_t), ierr)
662  call h5tget_size_f(dt_id, type_size_string, ierr)
663 
664  call h5tget_size_f(h5t_native_integer, type_size_int, ierr)
665 
666  call h5tcreate_f(h5t_compound_f, type_size_string + type_size_int, dtype_id, ierr)
667  call h5tinsert_f(dtype_id, "Name", 0_size_t, dt_id,ierr)
668  call h5tinsert_f(dtype_id, "Position", type_size_string, h5t_native_integer, ierr)
669 
670 !--------------------------------------------------------------------------------------------------
671 ! create memory types for each component of the compound type
672  call h5tcreate_f(h5t_compound_f, type_size_string, name_id, ierr)
673  call h5tinsert_f(name_id, "Name", 0_size_t, dt_id, ierr)
674 
675  call h5tcreate_f(h5t_compound_f, type_size_int, position_id, ierr)
676  call h5tinsert_f(position_id, "Position", 0_size_t, h5t_native_integer, ierr)
677 
678  call h5tclose_f(dt_id, ierr)
679 
680 !--------------------------------------------------------------------------------------------------
681 ! prepare MPI communication (transparent for non-MPI runs)
682  call h5pcreate_f(h5p_dataset_xfer_f, plist_id, ierr)
683  memberoffset = 0
684  do i=1, size(label)
685  memberoffset(i,worldrank) = count(homogenizationat == i)*size(memberatlocal,1) ! number of points/instance of this process
686  enddo
687  writesize = 0
688  writesize(worldrank) = size(memberatlocal) ! total number of points by this process
689 
690 !--------------------------------------------------------------------------------------------------
691 ! MPI settings and communication
692 
693  call h5pset_dxpl_mpio_f(plist_id, h5fd_mpio_collective_f, ierr)
694  if (ierr < 0) call io_error(1,ext_msg='results_mapping_materialpoint: h5pset_dxpl_mpio_f')
695 
696  call mpi_allreduce(mpi_in_place,writesize,worldsize,mpi_int,mpi_sum,petsc_comm_world,ierr) ! get output at each process
697  if (ierr /= 0) call io_error(894,ext_msg='results_mapping_materialpoint: MPI_allreduce/writeSize')
698 
699  call mpi_allreduce(mpi_in_place,memberoffset,size(memberoffset),mpi_int,mpi_sum,petsc_comm_world,ierr)! get offset at each process
700  if (ierr /= 0) call io_error(894,ext_msg='results_mapping_materialpoint: MPI_allreduce/memberOffset')
701 
702 
703  myshape = int([writesize(worldrank)], hsize_t)
704  myoffset = int([sum(writesize(0:worldrank-1))], hsize_t)
705  totalshape = int([sum(writesize)], hsize_t)
706 
707 !--------------------------------------------------------------------------------------------------
708 ! create dataspace in memory (local shape = hyperslab) and in file (global shape)
709  call h5screate_simple_f(1,myshape,memspace_id,ierr,myshape)
710  if (ierr < 0) call io_error(1,ext_msg='results_mapping_materialpoint: h5screate_simple_f/memspace_id')
711 
712  call h5screate_simple_f(1,totalshape,filespace_id,ierr,totalshape)
713  if (ierr < 0) call io_error(1,ext_msg='results_mapping_materialpoint: h5screate_simple_f/filespace_id')
714 
715  call h5sselect_hyperslab_f(filespace_id, h5s_select_set_f, myoffset, myshape, ierr)
716  if (ierr < 0) call io_error(1,ext_msg='results_mapping_materialpoint: h5sselect_hyperslab_f')
717 
718 !---------------------------------------------------------------------------------------------------
719 ! expand phaseAt to consider IPs (is not stored per IP)
720  do i = 1, size(homogenizationatmaterialpoint,1)
721  homogenizationatmaterialpoint(i,:) = homogenizationat
722  enddo
723 
724 !---------------------------------------------------------------------------------------------------
725 ! renumber member from my process to all processes
726  do i = 1, size(label)
727  where(homogenizationatmaterialpoint == i) memberatglobal = memberatlocal + sum(memberoffset(i,0:worldrank-1)) - 1 ! convert to 0-based
728  enddo
729 
730 !--------------------------------------------------------------------------------------------------
731 ! write the components of the compound type individually
732  call h5pset_preserve_f(plist_id, .true., ierr)
733 
734  loc_id = results_opengroup('/mapping/cellResults')
735  call h5dcreate_f(loc_id, 'materialpoint', dtype_id, filespace_id, dset_id, ierr)
736  if (ierr < 0) call io_error(1,ext_msg='results_mapping_materialpoint: h5dcreate_f')
737 
738  call h5dwrite_f(dset_id, name_id, reshape(label(pack(homogenizationatmaterialpoint,.true.)),myshape), &
739  myshape, ierr, file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
740  if (ierr < 0) call io_error(1,ext_msg='results_mapping_materialpoint: h5dwrite_f/name_id')
741  call h5dwrite_f(dset_id, position_id, reshape(pack(memberatglobal,.true.),myshape), &
742  myshape, ierr, file_space_id = filespace_id, mem_space_id = memspace_id, xfer_prp = plist_id)
743  if (ierr < 0) call io_error(1,ext_msg='results_mapping_materialpoint: h5dwrite_f/position_id')
744 
745 !--------------------------------------------------------------------------------------------------
746 ! close all
747  call hdf5_closegroup(loc_id)
748  call h5pclose_f(plist_id, ierr)
749  call h5sclose_f(filespace_id, ierr)
750  call h5sclose_f(memspace_id, ierr)
751  call h5dclose_f(dset_id, ierr)
752  call h5tclose_f(dtype_id, ierr)
753  call h5tclose_f(name_id, ierr)
754  call h5tclose_f(position_id, ierr)
755 
756 end subroutine results_mapping_materialpoint
757 
758 
759 !!--------------------------------------------------------------------------------------------------
760 !!> @brief adds the backward mapping from spatial position and constituent ID to results
761 !!--------------------------------------------------------------------------------------------------
762 !subroutine HDF5_backwardMappingPhase(material_phase,phasememberat,phase_name,dataspace_size,mpiOffset,mpiOffset_phase)
763 
764 ! integer(pInt), intent(in), dimension(:,:,:) :: material_phase, phasememberat
765 ! character(len=*), intent(in), dimension(:) :: phase_name
766 ! integer(pInt), intent(in), dimension(:) :: dataspace_size, mpiOffset_phase
767 ! integer(pInt), intent(in) :: mpiOffset
768 
769 ! integer(pInt) :: hdferr, NmatPoints, Nconstituents, i, j
770 ! integer(HID_T) :: mapping_id, dtype_id, dset_id, space_id, position_id, plist_id, memspace
771 ! integer(SIZE_T) :: type_size
772 
773 ! integer(pInt), dimension(:,:), allocatable :: arr
774 
775 ! integer(HSIZE_T), dimension(1) :: counter
776 ! integer(HSSIZE_T), dimension(1) :: fileOffset
777 
778 ! character(len=64) :: phaseID
779 
780 ! Nconstituents = size(phasememberat,1)
781 ! NmatPoints = count(material_phase /=0)/Nconstituents
782 
783 ! allocate(arr(2,NmatPoints*Nconstituents))
784 
785 ! do i=1, NmatPoints
786 ! do j=Nconstituents-1, 0, -1
787 ! arr(1,Nconstituents*i-j) = i-1
788 ! enddo
789 ! enddo
790 ! arr(2,:) = pack(material_phase,material_phase/=0)
791 
792 ! do i=1, size(phase_name)
793 ! write(phaseID, '(i0)') i
794 ! mapping_ID = results_openGroup('/current/constitutive/'//trim(phaseID)//'_'//phase_name(i))
795 ! NmatPoints = count(material_phase == i)
796 
797 !!--------------------------------------------------------------------------------------------------
798 ! ! create dataspace
799 ! call h5screate_simple_f(1, int([dataspace_size(i)],HSIZE_T), space_id, hdferr, &
800 ! int([dataspace_size(i)],HSIZE_T))
801 ! if (hdferr < 0) call IO_error(1,ext_msg='HDF5_writeBackwardMapping')
802 
803 !!--------------------------------------------------------------------------------------------------
804 ! ! compound type
805 ! call h5tget_size_f(H5T_STD_I32LE, type_size, hdferr)
806 ! call h5tcreate_f(H5T_COMPOUND_F, type_size, dtype_id, hdferr)
807 ! if (hdferr < 0) call IO_error(1,ext_msg='HDF5_writeBackwardMapping: h5tcreate_f dtype_id')
808 
809 ! call h5tinsert_f(dtype_id, "Position", 0_SIZE_T, H5T_STD_I32LE, hdferr)
810 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase: h5tinsert_f 0')
811 
812 !!--------------------------------------------------------------------------------------------------
813 ! ! create Dataset
814 ! call h5dcreate_f(mapping_id, 'mapGeometry', dtype_id, space_id, dset_id, hdferr)
815 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase')
816 
817 !!--------------------------------------------------------------------------------------------------
818 ! ! Create memory types (one compound datatype for each member)
819 ! call h5tcreate_f(H5T_COMPOUND_F, int(pInt,SIZE_T), position_id, hdferr)
820 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase: h5tcreate_f position_id')
821 ! call h5tinsert_f(position_id, "Position", 0_SIZE_T, H5T_STD_I32LE, hdferr)
822 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase: h5tinsert_f position_id')
823 
824 !!--------------------------------------------------------------------------------------------------
825 ! ! Define and select hyperslabs
826 ! counter = NmatPoints ! how big i am
827 ! fileOffset = mpiOffset_phase(i) ! where i start to write my data
828 
829 ! call h5screate_simple_f(1, counter, memspace, hdferr)
830 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase: h5screate_simple_f')
831 ! call h5dget_space_f(dset_id, space_id, hdferr)
832 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase: h5dget_space_f')
833 ! call h5sselect_hyperslab_f(space_id, H5S_SELECT_SET_F, fileOffset, counter, hdferr)
834 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase: h5sselect_hyperslab_f')
835 
836 !!--------------------------------------------------------------------------------------------------
837 ! ! Create property list for collective dataset write
838 !#ifdef 1
839 ! call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
840 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase: h5pcreate_f')
841 ! call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
842 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase: h5pset_dxpl_mpio_f')
843 !#endif
844 
845 !!--------------------------------------------------------------------------------------------------
846 ! ! write data by fields in the datatype. Fields order is not important.
847 ! call h5dwrite_f(dset_id, position_id, pack(arr(1,:),arr(2,:)==i)+mpiOffset, int([dataspace_size(i)],HSIZE_T),&
848 ! hdferr, file_space_id = space_id, mem_space_id = memspace, xfer_prp = plist_id)
849 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase: h5dwrite_f instance_id')
850 
851 !!--------------------------------------------------------------------------------------------------
852 ! !close types, dataspaces
853 ! call h5tclose_f(dtype_id, hdferr)
854 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase: h5tclose_f dtype_id')
855 ! call h5tclose_f(position_id, hdferr)
856 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase: h5tclose_f position_id')
857 ! call h5dclose_f(dset_id, hdferr)
858 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase: h5dclose_f')
859 ! call h5sclose_f(space_id, hdferr)
860 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase: h5sclose_f space_id')
861 ! call h5sclose_f(memspace, hdferr)
862 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase: h5sclose_f memspace')
863 ! call h5pclose_f(plist_id, hdferr)
864 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingPhase: h5pclose_f')
865 ! call HDF5_closeGroup(mapping_ID)
866 
867 ! enddo
868 
869 !end subroutine HDF5_backwardMappingPhase
870 
871 
872 !!--------------------------------------------------------------------------------------------------
873 !!> @brief adds the backward mapping from spatial position and constituent ID to results
874 !!--------------------------------------------------------------------------------------------------
875 !subroutine HDF5_backwardMappingHomog(material_homog,homogmemberat,homogenization_name,dataspace_size,mpiOffset,mpiOffset_homog)
876 
877 ! integer(pInt), intent(in), dimension(:,:) :: material_homog, homogmemberat
878 ! character(len=*), intent(in), dimension(:) :: homogenization_name
879 ! integer(pInt), intent(in), dimension(:) :: dataspace_size, mpiOffset_homog
880 ! integer(pInt), intent(in) :: mpiOffset
881 
882 ! integer(pInt) :: hdferr, NmatPoints, i
883 ! integer(HID_T) :: mapping_id, dtype_id, dset_id, space_id, position_id, plist_id, memspace
884 ! integer(SIZE_T) :: type_size
885 
886 ! integer(pInt), dimension(:,:), allocatable :: arr
887 
888 ! integer(HSIZE_T), dimension(1) :: counter
889 ! integer(HSSIZE_T), dimension(1) :: fileOffset
890 
891 ! character(len=64) :: homogID
892 
893 ! NmatPoints = count(material_homog /=0)
894 ! allocate(arr(2,NmatPoints))
895 
896 ! arr(1,:) = (/(i, i=0,NmatPoints-1)/)
897 ! arr(2,:) = pack(material_homog,material_homog/=0)
898 
899 ! do i=1, size(homogenization_name)
900 ! write(homogID, '(i0)') i
901 ! mapping_ID = results_openGroup('/current/homogenization/'//trim(homogID)//'_'//homogenization_name(i))
902 
903 !!--------------------------------------------------------------------------------------------------
904 ! ! create dataspace
905 ! call h5screate_simple_f(1, int([dataspace_size(i)],HSIZE_T), space_id, hdferr, &
906 ! int([dataspace_size(i)],HSIZE_T))
907 ! if (hdferr < 0) call IO_error(1,ext_msg='HDF5_writeBackwardMapping')
908 
909 !!--------------------------------------------------------------------------------------------------
910 ! ! compound type
911 ! call h5tget_size_f(H5T_STD_I32LE, type_size, hdferr)
912 ! call h5tcreate_f(H5T_COMPOUND_F, type_size, dtype_id, hdferr)
913 ! if (hdferr < 0) call IO_error(1,ext_msg='HDF5_writeBackwardMapping: h5tcreate_f dtype_id')
914 
915 ! call h5tinsert_f(dtype_id, "Position", 0_SIZE_T, H5T_STD_I32LE, hdferr)
916 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog: h5tinsert_f 0')
917 
918 !!--------------------------------------------------------------------------------------------------
919 ! ! create Dataset
920 ! call h5dcreate_f(mapping_id, 'mapGeometry', dtype_id, space_id, dset_id, hdferr)
921 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog')
922 
923 !!--------------------------------------------------------------------------------------------------
924 ! ! Create memory types (one compound datatype for each member)
925 ! call h5tcreate_f(H5T_COMPOUND_F, int(pInt,SIZE_T), position_id, hdferr)
926 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog: h5tcreate_f position_id')
927 ! call h5tinsert_f(position_id, "Position", 0_SIZE_T, H5T_STD_I32LE, hdferr)
928 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog: h5tinsert_f position_id')
929 
930 !!--------------------------------------------------------------------------------------------------
931 ! ! Define and select hyperslabs
932 ! counter = NmatPoints ! how big i am
933 ! fileOffset = mpiOffset_homog(i) ! where i start to write my data
934 
935 ! call h5screate_simple_f(1, counter, memspace, hdferr)
936 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog: h5screate_simple_f')
937 ! call h5dget_space_f(dset_id, space_id, hdferr)
938 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog: h5dget_space_f')
939 ! call h5sselect_hyperslab_f(space_id, H5S_SELECT_SET_F, fileOffset, counter, hdferr)
940 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog: h5sselect_hyperslab_f')
941 
942 !!--------------------------------------------------------------------------------------------------
943 ! ! Create property list for collective dataset write
944 !#ifdef 1
945 ! call h5pcreate_f(H5P_DATASET_XFER_F, plist_id, hdferr)
946 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog: h5pcreate_f')
947 ! call h5pset_dxpl_mpio_f(plist_id, H5FD_MPIO_COLLECTIVE_F, hdferr)
948 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog: h5pset_dxpl_mpio_f')
949 !#endif
950 
951 !!--------------------------------------------------------------------------------------------------
952 ! ! write data by fields in the datatype. Fields order is not important.
953 ! call h5dwrite_f(dset_id, position_id, pack(arr(1,:),arr(2,:)==i)+mpiOffset,int([dataspace_size(i)],HSIZE_T),&
954 ! hdferr, file_space_id = space_id, mem_space_id = memspace, xfer_prp = plist_id)
955 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog: h5dwrite_f instance_id')
956 
957 !!--------------------------------------------------------------------------------------------------
958 ! !close types, dataspaces
959 ! call h5tclose_f(dtype_id, hdferr)
960 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog: h5tclose_f dtype_id')
961 ! call h5tclose_f(position_id, hdferr)
962 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog: h5tclose_f position_id')
963 ! call h5dclose_f(dset_id, hdferr)
964 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog: h5dclose_f')
965 ! call h5sclose_f(space_id, hdferr)
966 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog: h5sclose_f space_id')
967 ! call h5sclose_f(memspace, hdferr)
968 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog: h5sclose_f memspace')
969 ! call h5pclose_f(plist_id, hdferr)
970 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_backwardMappingHomog: h5pclose_f')
971 ! call HDF5_closeGroup(mapping_ID)
972 
973 ! enddo
974 
975 !end subroutine HDF5_backwardMappingHomog
976 
977 
978 !!--------------------------------------------------------------------------------------------------
979 !!> @brief adds the unique cell to node mapping
980 !!--------------------------------------------------------------------------------------------------
981 !subroutine HDF5_mappingCells(mapping)
982 
983 ! integer(pInt), intent(in), dimension(:) :: mapping
984 
985 ! integer :: hdferr, Nnodes
986 ! integer(HID_T) :: mapping_id, dset_id, space_id
987 
988 ! Nnodes=size(mapping)
989 ! mapping_ID = results_openGroup("mapping")
990 
991 !!--------------------------------------------------------------------------------------------------
992 !! create dataspace
993 ! call h5screate_simple_f(1, int([Nnodes],HSIZE_T), space_id, hdferr, &
994 ! int([Nnodes],HSIZE_T))
995 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_mappingCells: h5screate_simple_f')
996 
997 !!--------------------------------------------------------------------------------------------------
998 !! create Dataset
999 ! call h5dcreate_f(mapping_id, "Cell",H5T_NATIVE_INTEGER, space_id, dset_id, hdferr)
1000 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_mappingCells')
1001 
1002 !!--------------------------------------------------------------------------------------------------
1003 !! write data by fields in the datatype. Fields order is not important.
1004 ! call h5dwrite_f(dset_id, H5T_NATIVE_INTEGER, mapping, int([Nnodes],HSIZE_T), hdferr)
1005 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_mappingCells: h5dwrite_f instance_id')
1006 
1007 !!--------------------------------------------------------------------------------------------------
1008 !!close types, dataspaces
1009 ! call h5dclose_f(dset_id, hdferr)
1010 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_mappingConstitutive: h5dclose_f')
1011 ! call h5sclose_f(space_id, hdferr)
1012 ! if (hdferr < 0) call IO_error(1,ext_msg='IO_mappingConstitutive: h5sclose_f')
1013 ! call HDF5_closeGroup(mapping_ID)
1014 
1015 !end subroutine HDF5_mappingCells
1016 
1017 end module results
results::results_setlink
subroutine, public results_setlink(path, link)
set link to object in results file
Definition: results.f90:178
hdf5_utilities::hdf5_addgroup
integer(hid_t) function hdf5_addgroup(fileHandle, groupName)
adds a new group to the fileHandle
Definition: HDF5_utilities.f90:182
rotations
rotation storage and conversion
Definition: rotations.f90:53
results::results_addattribute_real_array
subroutine results_addattribute_real_array(attrLabel, attrValue, path)
adds a real array attribute an object in the results file
Definition: results.f90:261
results::results_closejobfile
subroutine, public results_closejobfile
closes the results file
Definition: results.f90:102
hdf5_utilities::hdf5_closegroup
subroutine hdf5_closegroup(group_id)
close a group
Definition: HDF5_utilities.f90:251
hdf5_utilities::hdf5_addattribute
attached attributes of type char, integer or real to a file/dataset/group
Definition: HDF5_utilities.f90:76
rotations::rotation
Definition: rotations.f90:63
results::results_addattribute
Definition: results.f90:38
results::results_opengroup
integer(hid_t) function, public results_opengroup(groupName)
open a group from the results file
Definition: results.f90:142
results::results_mapping_materialpoint
subroutine, public results_mapping_materialpoint(homogenizationAt, memberAtLocal, label)
adds the unique mapping from spatial position and constituent ID to results
Definition: results.f90:628
results::results_init
subroutine, public results_init
Definition: results.f90:67
hdf5_utilities
Definition: HDF5_utilities.f90:11
hdf5_utilities::hdf5_openfile
integer(hid_t) function hdf5_openfile(fileName, mode, parallel)
open and initializes HDF5 output file
Definition: HDF5_utilities.f90:119
numerics::worldsize
integer, public, protected worldsize
MPI worldsize (/=1 for MPI simulations only)
Definition: numerics.f90:1470
results::results_writetensordataset_real
subroutine results_writetensordataset_real(group, dataset, label, description, SIunit, transposed)
stores a tensor dataset in a group
Definition: results.f90:352
results::results_writescalardataset_real
subroutine results_writescalardataset_real(group, dataset, label, description, SIunit)
stores a scalar dataset in a group
Definition: results.f90:293
results::results_removelink
subroutine, public results_removelink(link)
remove link to an object
Definition: results.f90:279
results::results_writedataset
Definition: results.f90:25
results::results_writetensordataset_int
subroutine results_writetensordataset_int(group, dataset, label, description, SIunit)
stores a tensor dataset in a group
Definition: results.f90:433
hdf5_utilities::hdf5_objectexists
logical function hdf5_objectexists(loc_id, path)
check whether a group or a dataset exists
Definition: HDF5_utilities.f90:265
results::results_addattribute_int
subroutine results_addattribute_int(attrLabel, attrValue, path)
adds an integer attribute an object in the results file
Definition: results.f90:207
results::results_addincrement
subroutine, public results_addincrement(inc, time)
creates the group of increment and adds time as attribute to the file
Definition: results.f90:112
results::results_addgroup
integer(hid_t) function, public results_addgroup(groupName)
adds a new group to the results file
Definition: results.f90:154
results::results_mapping_constituent
subroutine, public results_mapping_constituent(phaseAt, memberAtLocal, label)
adds the unique mapping from spatial position and constituent ID to results
Definition: results.f90:493
results::results_addattribute_str
subroutine results_addattribute_str(attrLabel, attrValue, path)
adds a string attribute to an object in the results file
Definition: results.f90:190
results::resultsfile
integer(hid_t) resultsfile
Definition: results.f90:23
results::results_addattribute_real
subroutine results_addattribute_real(attrLabel, attrValue, path)
adds a real attribute an object in the results file
Definition: results.f90:225
damask_interface
Interfacing between the 1-based solvers and the material subroutines provided by DAMASK.
Definition: DAMASK_interface.f90:22
results::results_openjobfile
subroutine, public results_openjobfile
opens the results file to append data
Definition: results.f90:92
results
Definition: results.f90:11
results::results_writevectordataset_int
subroutine results_writevectordataset_int(group, dataset, label, description, SIunit)
stores a vector dataset in a group
Definition: results.f90:403
results::results_addattribute_int_array
subroutine results_addattribute_int_array(attrLabel, attrValue, path)
adds an integer array attribute an object in the results file
Definition: results.f90:243
results::results_finalizeincrement
subroutine, public results_finalizeincrement
finalize increment
Definition: results.f90:132
hdf5_utilities::hdf5_closefile
subroutine hdf5_closefile(fileHandle)
close the opened HDF5 output file
Definition: HDF5_utilities.f90:167
numerics::worldrank
integer, public, protected worldrank
MPI worldrank (/=0 for MPI simulations only)
Definition: numerics.f90:1470
damask_interface::getsolverjobname
character(len=:) function, allocatable, public getsolverjobname()
solver job name (no extension) as combination of geometry and load case name
Definition: DAMASK_interface.f90:1737
results::results_writevectordataset_real
subroutine results_writevectordataset_real(group, dataset, label, description, SIunit)
stores a vector dataset in a group
Definition: results.f90:322
results::results_closegroup
subroutine, public results_closegroup(group_id)
close a group
Definition: results.f90:166
hdf5_utilities::hdf5_setlink
subroutine hdf5_setlink(loc_id, target_name, link_name)
set link to object in results file
Definition: HDF5_utilities.f90:509
numerics
Managing of parameters related to numerics.
Definition: numerics.f90:10
hdf5_utilities::hdf5_opengroup
integer(hid_t) function hdf5_opengroup(fileHandle, groupName)
open an existing group of a file
Definition: HDF5_utilities.f90:215
results::results_writescalardataset_rotation
subroutine results_writescalardataset_rotation(group, dataset, label, description, lattice_structure)
stores a scalar dataset in a group
Definition: results.f90:463
hdf5_utilities::hdf5_write
writes integer or real data of defined shape to file ! ToDo: order of arguments wrong
Definition: HDF5_utilities.f90:52