|
| 1 | +module stdlib_io |
| 2 | +use stdlib_types |
| 3 | +implicit none |
| 4 | +private |
| 5 | +public loadtxt, savetxt |
| 6 | + |
| 7 | +contains |
| 8 | + |
| 9 | +subroutine loadtxt(filename, d) |
| 10 | +! Loads a 2D array from a text file. |
| 11 | +! |
| 12 | +! Arguments |
| 13 | +! --------- |
| 14 | +! |
| 15 | +! Filename to load the array from |
| 16 | +character(len=*), intent(in) :: filename |
| 17 | +! The array 'd' will be automatically allocated with the correct dimensions |
| 18 | +real(dp), allocatable, intent(out) :: d(:, :) |
| 19 | +! |
| 20 | +! Example |
| 21 | +! ------- |
| 22 | +! |
| 23 | +! real(dp), allocatable :: data(:, :) |
| 24 | +! call loadtxt("log.txt", data) ! 'data' will be automatically allocated |
| 25 | +! |
| 26 | +! Where 'log.txt' contains for example:: |
| 27 | +! |
| 28 | +! 1 2 3 |
| 29 | +! 2 4 6 |
| 30 | +! 8 9 10 |
| 31 | +! 11 12 13 |
| 32 | +! ... |
| 33 | +! |
| 34 | +character :: c |
| 35 | +integer :: s, ncol, nrow, ios, i |
| 36 | +logical :: lastwhite |
| 37 | +real(dp) :: r |
| 38 | + |
| 39 | +open(newunit=s, file=filename, status="old") |
| 40 | + |
| 41 | +! determine number of columns |
| 42 | +ncol = 0 |
| 43 | +lastwhite = .true. |
| 44 | +do |
| 45 | + read(s, '(a)', advance='no', iostat=ios) c |
| 46 | + if (ios /= 0) exit |
| 47 | + if (lastwhite .and. .not. whitechar(c)) ncol = ncol + 1 |
| 48 | + lastwhite = whitechar(c) |
| 49 | +end do |
| 50 | + |
| 51 | +rewind(s) |
| 52 | + |
| 53 | +! determine number or rows |
| 54 | +nrow = 0 |
| 55 | +do |
| 56 | + read(s, *, iostat=ios) r |
| 57 | + if (ios /= 0) exit |
| 58 | + nrow = nrow + 1 |
| 59 | +end do |
| 60 | + |
| 61 | +rewind(s) |
| 62 | + |
| 63 | +allocate(d(nrow, ncol)) |
| 64 | +do i = 1, nrow |
| 65 | + read(s, *) d(i, :) |
| 66 | +end do |
| 67 | +close(s) |
| 68 | +end subroutine |
| 69 | + |
| 70 | +subroutine savetxt(filename, d) |
| 71 | +! Saves a 2D array into a textfile. |
| 72 | +! |
| 73 | +! Arguments |
| 74 | +! --------- |
| 75 | +! |
| 76 | +character(len=*), intent(in) :: filename ! File to save the array to |
| 77 | +real(dp), intent(in) :: d(:, :) ! The 2D array to save |
| 78 | +! |
| 79 | +! Example |
| 80 | +! ------- |
| 81 | +! |
| 82 | +! real(dp) :: data(3, 2) |
| 83 | +! call savetxt("log.txt", data) |
| 84 | + |
| 85 | +integer :: s, i |
| 86 | +open(newunit=s, file=filename, status="replace") |
| 87 | +do i = 1, size(d, 1) |
| 88 | + write(s, *) d(i, :) |
| 89 | +end do |
| 90 | +close(s) |
| 91 | +end subroutine |
| 92 | + |
| 93 | + |
| 94 | +logical function whitechar(char) ! white character |
| 95 | +! returns .true. if char is space (32) or tab (9), .false. otherwise |
| 96 | +character, intent(in) :: char |
| 97 | +if (iachar(char) == 32 .or. iachar(char) == 9) then |
| 98 | + whitechar = .true. |
| 99 | +else |
| 100 | + whitechar = .false. |
| 101 | +end if |
| 102 | +end function |
| 103 | + |
| 104 | +end module |
0 commit comments