!> !> @file ex16.f90 !> !> @brief Read a sub-matrix A(s(1):e(2),s(2):e(2)) using getarr with offsets. !> !> @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 ! ! Read a sub-matrix A(s(1):e(2),s(2):e(2)) using getarr with offsets. ! USE futils IMPLICIT NONE CHARACTER(len=32) :: file='matrix.h5' INTEGER :: fid INTEGER :: nx=5, ny=8, i, j INTEGER, PARAMETER :: ndims=2 INTEGER :: s(ndims), e(ndims), offsets(ndims) INTEGER, ALLOCATABLE :: array(:,:), subarr(:,:) !=========================================================================== ! Create file ! CALL creatf(file, fid) ALLOCATE(array(nx,ny)) DO j=1,ny DO i=1,nx array(i,j) = 10*i + j END DO END DO CALL putarr(fid, "/array", array) CALL disp('array', array) CALL closef(fid) ! ! Reopen for read CALL openf(file,fid) ! ! Read a sub-array s = [2,3]; e = [MIN(nx,4),MIN(ny,5)] !!$ s = [1,4]; e = [MIN(nx,5),MIN(ny,5)] WRITE(*,'(a,4i6)') 's, e', s, e DO i=1,ndims offsets(i) = s(i)-1 END DO ALLOCATE(subarr(s(1):e(1),s(2):e(2))) CALL getarr(fid, "/array", subarr, offsets=offsets) CALL disp('subarr', subarr) ! CALL closef(fid) CONTAINS SUBROUTINE disp(str,a) CHARACTER(len=*), INTENT(in) :: str INTEGER, INTENT(in) :: a(:,:) INTEGER :: i WRITE(*,'(a)') TRIM(str) DO i=1,SIZE(a,1) WRITE(*,'(10i6)') a(i,:) END DO END SUBROUTINE disp END PROGRAM main