! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
!   Copyright by The HDF Group.                                               *
!   Copyright by the Board of Trustees of the University of Illinois.         *
!   All rights reserved.                                                      *
!                                                                             *
!   This file is part of HDF5.  The full HDF5 copyright notice, including     *
!   terms governing use, modification, and redistribution, is contained in    *
!   the files COPYING and Copyright.html.  COPYING can be found at the root   *
!   of the source code distribution tree; Copyright.html can be found at the  *
!   root level of an installed copy of the electronic HDF5 document set and   *
!   is linked from the top-level documents page.  It can also be found at     *
!   http://hdfgroup.org/HDF5/doc/Copyright.html.  If you do not have          *
!   access to either file, you may request a copy from help@hdfgroup.org.     *
! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
!
!
! This example shows how to create a dataset in a particular group.
! It opens the file created in the previous example and creates two datasets.
! Absolute and relative dataset names are used.
!
! This example is used in the HDF5 Tutorial.
PROGRAM H5_CRTGRPD
  USE HDF5 ! This module contains all necessary modules
  IMPLICIT NONE
  CHARACTER(LEN=10), PARAMETER :: filename = "groupsf.h5" ! File name
  CHARACTER(LEN=15), PARAMETER :: groupname = "MyGroup/Group_A" ! Group name
  CHARACTER(LEN=13), PARAMETER :: dsetname1 = "MyGroup/dset1"  ! Dataset name
  CHARACTER(LEN=5),  PARAMETER :: dsetname2 = "dset2" ! dataset name
  INTEGER(HID_T) :: file_id       ! File identifier
  INTEGER(HID_T) :: group_id      ! Group identifier
  INTEGER(HID_T) :: dataset_id    ! Dataset identifier
  INTEGER(HID_T) :: dataspace_id  ! Data space identifier
  INTEGER ::  i, j
  INTEGER ::   error ! Error flag
  INTEGER, DIMENSION(3,3) :: dset1_data  ! Data arrays
  INTEGER, DIMENSION(2,10) :: dset2_data !
  INTEGER(HSIZE_T), DIMENSION(2) :: dims1 = (/3,3/) ! Datasets dimensions
  INTEGER(HSIZE_T), DIMENSION(2) :: dims2 = (/2,10/)!
  INTEGER(HSIZE_T), DIMENSION(2) :: data_dims
  INTEGER     ::   rank = 2 ! Datasets rank
  !