!> !> @file ex15.f90 !> !> @brief Test "getatt" with optional argumenet "err" !> !> @copyright !> Copyright (©) 2021 EPFL (Ecole Polytechnique Fédérale de Lausanne) !> SPC (Swiss Plasma Center) !> !> futils is free software: you can redistribute it and/or modify it under !> the terms of the GNU Lesser General Public License as published by the Free !> Software Foundation, either version 3 of the License, or (at your option) !> any later version. !> !> futils is distributed in the hope that it will be useful, but WITHOUT ANY !> WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS !> FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. !> !> You should have received a copy of the GNU Lesser General Public License !> along with this program. If not, see . !> !> @authors !> (in alphabetical order) !> @author Trach-Minh Tran !> PROGRAM main ! ! Test "getatt" with optional argumenet "err" ! USE hdf5 USE futils IMPLICIT NONE CHARACTER(len=128) :: file='sim.h5', label INTEGER :: fid INTEGER :: n, ierr CHARACTER(len=16), DIMENSION(:), ALLOCATABLE :: attnames CHARACTER(len=1), DIMENSION(:), ALLOCATABLE :: atttypes INTEGER(SIZE_T), DIMENSION(:), ALLOCATABLE :: attsizes INTEGER :: i, natts INTEGER :: ival REAL :: sval DOUBLE PRECISION :: rval CHARACTER(len=32) :: cval ! IF( command_argument_count() > 0 ) THEN CALL get_command_argument(1, file, n, ierr) END IF CALL openf(file, fid) WRITE(*,'(a)') file(1:LEN_TRIM(file))//' open' ! CALL getatt(fid, '/', 'prec', ival, ierr) IF( ierr .EQ. -2 ) THEN CALL getatt(fid, '/', 'prec', cval, ierr) PRINT*, 'prec is a string = ', TRIM(cval) ELSE PRINT*, 'prec is a integer =', ival END IF CALL closef(fid) ! END PROGRAM main