diff --git a/doc/specs/stdlib_io.md b/doc/specs/stdlib_io.md index 61b6d9578..971a8ee29 100644 --- a/doc/specs/stdlib_io.md +++ b/doc/specs/stdlib_io.md @@ -17,7 +17,7 @@ Loads a rank-2 `array` from a text file. ### Syntax -`call [[stdlib_io(module):loadtxt(interface)]](filename, array)` +`call [[stdlib_io(module):loadtxt(interface)]](filename, array [, skiprows] [, max_rows])` ### Arguments @@ -25,6 +25,10 @@ Loads a rank-2 `array` from a text file. `array`: Shall be an allocatable rank-2 array of type `real`, `complex` or `integer`. +`skiprows` (optional): Skip the first `skiprows` lines. If skipping more rows than present, a 0-sized array will be returned. The default is 0. + +`max_rows` (optional): Read `max_rows` lines of content after `skiprows` lines. A negative value results in reading all lines. A value of zero results in no lines to be read. The default value is -1. + ### Return value Returns an allocated rank-2 `array` with the content of `filename`. @@ -314,4 +318,4 @@ program demo_fmt_constants print FMT_COMPLEX_DP, c64 ! outputs: 1.0000000000000000E+002 0.0000000000000000E+000 end program demo_fmt_constants -``` \ No newline at end of file +``` diff --git a/src/stdlib_io.fypp b/src/stdlib_io.fypp index 4909c550a..c0f84932e 100644 --- a/src/stdlib_io.fypp +++ b/src/stdlib_io.fypp @@ -81,7 +81,7 @@ module stdlib_io contains #:for k1, t1 in KINDS_TYPES - subroutine loadtxt_${t1[0]}$${k1}$(filename, d) + subroutine loadtxt_${t1[0]}$${k1}$(filename, d, skiprows, max_rows) !! version: experimental !! !! Loads a 2D array from a text file. @@ -93,6 +93,13 @@ contains character(len=*), intent(in) :: filename !! The array 'd' will be automatically allocated with the correct dimensions ${t1}$, allocatable, intent(out) :: d(:,:) + !! Skip the first `skiprows` lines. If skipping more rows than present, a 0-sized array will be returned. The default is 0. + integer, intent(in), optional :: skiprows + !! Read `max_rows` lines of content after `skiprows` lines. + !! A negative value results in reading all lines. + !! A value of zero results in no lines to be read. + !! The default value is -1. + integer, intent(in), optional :: max_rows !! !! Example !! ------- @@ -111,21 +118,32 @@ contains !! ... !! integer :: s - integer :: nrow, ncol, i + integer :: nrow, ncol, i, skiprows_, max_rows_ + + skiprows_ = max(optval(skiprows, 0), 0) + max_rows_ = optval(max_rows, -1) s = open(filename) + ! determine number or rows + nrow = number_of_rows(s) + skiprows_ = min(skiprows_, nrow) + if ( max_rows_ < 0 .or. max_rows_ > (nrow - skiprows_) ) max_rows_ = nrow - skiprows_ + ! determine number of columns - ncol = number_of_columns(s) + ncol = 0 + if ( skiprows_ < nrow ) ncol = number_of_columns(s, skiprows=skiprows_) #:if 'complex' in t1 ncol = ncol / 2 #:endif - ! determine number or rows - nrow = number_of_rows(s) + allocate(d(max_rows_, ncol)) - allocate(d(nrow, ncol)) - do i = 1, nrow + do i = 1, skiprows_ + read(s, *) + end do + + do i = 1, max_rows_ #:if 'real' in t1 read(s, "(*"//FMT_REAL_${k1}$(1:len(FMT_REAL_${k1}$)-1)//",1x))") d(i, :) #:elif 'complex' in t1 @@ -179,17 +197,25 @@ contains #:endfor - integer function number_of_columns(s) + integer function number_of_columns(s, skiprows) !! version: experimental !! !! determine number of columns integer,intent(in) :: s + integer, intent(in), optional :: skiprows - integer :: ios + integer :: ios, skiprows_, i character :: c logical :: lastblank + skiprows_ = optval(skiprows, 0) + rewind(s) + + do i = 1, skiprows_ + read(s, *) + end do + number_of_columns = 0 lastblank = .true. do diff --git a/src/tests/io/test_loadtxt.f90 b/src/tests/io/test_loadtxt.f90 index cf2029ee7..a75c63e49 100644 --- a/src/tests/io/test_loadtxt.f90 +++ b/src/tests/io/test_loadtxt.f90 @@ -19,6 +19,7 @@ subroutine collect_loadtxt(testsuite) new_unittest("loadtxt_sp_huge", test_loadtxt_sp_huge), & new_unittest("loadtxt_sp_tiny", test_loadtxt_sp_tiny), & new_unittest("loadtxt_dp", test_loadtxt_dp), & + new_unittest("loadtxt_dp_max_skip", test_loadtxt_dp_max_skip), & new_unittest("loadtxt_dp_huge", test_loadtxt_dp_huge), & new_unittest("loadtxt_dp_tiny", test_loadtxt_dp_tiny), & new_unittest("loadtxt_complex", test_loadtxt_complex) & @@ -134,6 +135,29 @@ subroutine test_loadtxt_dp(error) end subroutine test_loadtxt_dp + subroutine test_loadtxt_dp_max_skip(error) + !> Error handling + type(error_type), allocatable, intent(out) :: error + real(dp), allocatable :: input(:,:), expected(:,:) + integer :: n, m + + allocate(input(10,10)) + + do m = 0, 5 + do n = 1, 11 + call random_number(input) + input = input - 0.5 + call savetxt('test_dp_max_skip.txt', input) + call loadtxt('test_dp_max_skip.txt', expected, skiprows=m, max_rows=n) + call check(error, all(input(m+1:min(n+m,10),:) == expected)) + deallocate(expected) + if (allocated(error)) return + end do + end do + + end subroutine test_loadtxt_dp_max_skip + + subroutine test_loadtxt_dp_huge(error) !> Error handling type(error_type), allocatable, intent(out) :: error