!> !> @file getfile.f90 !> !> @brief Extract files from HDF5 datasets !> !> @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 USE futils IMPLICIT NONE CHARACTER(len=256) :: file, path, name INTEGER :: n, fid, ierr, nargs !=========================================================================== ! nargs = command_argument_count() IF( nargs .GE. 2 ) THEN CALL get_command_argument(1, file, n, ierr) CALL get_command_argument(2, name, n, ierr) IF (nargs .EQ. 3) THEN CALL get_command_argument(3, path, n, ierr) END IF ELSE WRITE(*,'(a)') 'Usage: getfile [path]' STOP END IF ! CALL openf(file, fid, mode='r') IF( nargs .EQ. 2 ) THEN CALL getfile(fid, name) ELSE CALL getfile(fid, name, path) END IF ! CALL closef(fid) END PROGRAM main