!> !> @file ex12.f90 !> !> @brief Test copy_file/move_file (which calls copy_file) from cutils.c !> !> @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 ! ! Create an HDF5 file and test copy_file/move_file ! USE futils IMPLICIT NONE CHARACTER(len=32) :: file0='file.h5' CHARACTER(len=32) :: file1='file.h5_cp' CHARACTER(len=32) :: file2='file.h5_mv' INTEGER :: fid LOGICAL :: ex REAL, DIMENSION(1000,1000) :: array, a ! ! Create the hdf5 file CALL RANDOM_NUMBER(array) CALL creatf(file0,fid) CALL putarr(fid,'/RANDOM',array) CALL closef(fid) ! ! move/copy the file CALL copy_file(file0, LEN_TRIM(file0), file1, LEN_TRIM(file1)) CALL move_file(file0, LEN_TRIM(file0), file2, LEN_TRIM(file2)) INQUIRE(file=TRIM(file0), exist=ex) IF( ex ) THEN PRINT*, TRIM(file0), " is still here!" ELSE PRINT*, TRIM(file0), " is gone!" END IF ! ! Check contents of file1 CALL openf(file1,fid) CALL getarr(fid,'/RANDOM',a) CALL closef(fid) PRINT*, 'Min/max of diff', MINVAL(array-a), MAXVAL(array-a) END PROGRAM main