!> !> @file ex5.f90 !> !> @brief Example with "putfile" !> !> @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 ! ! Put files in HDF5 file ! USE futils IMPLICIT NONE CHARACTER(len=256) :: file='file.h5', path, name, base, dir, line INTEGER :: n, fid, ierr !=========================================================================== ! 1. Prologue ! ! IF( command_argument_count() > 0 ) THEN CALL get_command_argument(1, file, n, ierr) END IF ! CALL creatf(file, fid, 'A simple simulation') CALL creatg(fid, "/inputs", "Inputs specific to the run") !=========================================================================== ! 2. Put some files ! path = 'README.txt' CALL split(path, dir, base) name = '/inputs/' // base(1:LEN_TRIM(path)) CALL putfile(fid, name, path, compress=.TRUE.) PRINT*, 'dataset ', TRIM(name), ' written' ! path = 'Makefile' CALL split(path, dir, base) name = '/inputs/' // base(1:LEN_TRIM(path)) CALL putfile(fid, name, path, compress=.TRUE.) PRINT*, 'dataset ', TRIM(name), ' written' !=========================================================================== ! 3. Save standard input ! DO READ(*,'(a)', END=110) line ! Capture stdin WRITE(90, '(a)') TRIM(line) END DO 110 CONTINUE CALL FLUSH(90) REWIND(90) ! ! Now read stdin using "READ(90" instead of "READ(*," ! INQUIRE(unit=90, name=path) CALL putfile(fid, '/inputs/STDIN', TRIM(path)) ! Save stdin in /inputs/STDIN PRINT*, 'dataset /inputs/STDIN written' CLOSE(90,status='delete') ! Clean up !=========================================================================== ! 9. Epilogue ! 9900 CONTINUE CALL closef(fid) END PROGRAM main