Skip to content

Commit fb85f49

Browse files
committed
stdlib_experimental_io: remove _poly subroutine
1 parent dcd0d85 commit fb85f49

File tree

2 files changed

+1
-59
lines changed

2 files changed

+1
-59
lines changed

src/stdlib_experimental_io.f90

-42
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,6 @@ module stdlib_experimental_io
33
implicit none
44
private
55
public :: loadtxt, savetxt
6-
public :: savetxt_poly
76

87
interface loadtxt
98
module procedure sloadtxt
@@ -219,47 +218,6 @@ subroutine qsavetxt(filename, d)
219218
close(s)
220219
end subroutine
221220

222-
!OR
223-
224-
subroutine savetxt_poly(filename, d)
225-
! Saves a 2D array into a textfile.
226-
!
227-
! Arguments
228-
! ---------
229-
!
230-
character(len=*), intent(in) :: filename ! File to save the array to
231-
class(*), intent(in) :: d(:,:) ! The 2D array to save
232-
!
233-
! Example
234-
! -------
235-
!
236-
! real(sp) :: data(3, 2)
237-
! call savetxt("log.txt", data)
238-
239-
integer :: s, i
240-
open(newunit=s, file=filename, status="replace")
241-
242-
select type(d)
243-
type is(real(sp))
244-
do i = 1, size(d, 1)
245-
write(s, *) d(i, :)
246-
end do
247-
type is(real(dp))
248-
do i = 1, size(d, 1)
249-
write(s, *) d(i, :)
250-
end do
251-
type is(real(qp))
252-
do i = 1, size(d, 1)
253-
write(s, *) d(i, :)
254-
end do
255-
class default
256-
write(*,'(a)')'The proposed type is not supported'
257-
error stop
258-
end select
259-
260-
close(s)
261-
262-
end subroutine
263221

264222
!PRIVATE
265223
integer function number_of_columns(s)

src/tests/loadtxt/test_savetxt.f90

+1-17
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,11 @@
11
program test_loadtxt
22
use iso_fortran_env, only: sp=>real32, dp=>real64 ,qp=>real128
3-
use stdlib_experimental_io, only: loadtxt, savetxt ,savetxt_poly
3+
use stdlib_experimental_io, only: loadtxt, savetxt
44
use stdlib_experimental_error, only: assert
55
implicit none
66

77
call test_sp()
88
call test_dp()
9-
call test_dp_poly()
109
call test_qp()
1110

1211
contains
@@ -60,19 +59,4 @@ subroutine test_qp()
6059
call assert(all(abs(e-d2) < epsilon(1._qp)))
6160
end subroutine
6261

63-
subroutine test_dp_poly()
64-
real(dp) :: d(3, 2), e(2, 3)
65-
real(dp), allocatable :: d2(:, :)
66-
d = reshape([1, 2, 3, 4, 5, 6], [3, 2])
67-
call savetxt_poly("tmp.dat", d)
68-
call loadtxt("tmp.dat", d2)
69-
call assert(all(shape(d2) == [3, 2]))
70-
call assert(all(abs(d-d2) < epsilon(1._dp)))
71-
72-
e = reshape([1, 2, 3, 4, 5, 6], [2, 3])
73-
call savetxt_poly("tmp.dat", e)
74-
call loadtxt("tmp.dat", d2)
75-
call assert(all(shape(d2) == [2, 3]))
76-
call assert(all(abs(e-d2) < epsilon(1._dp)))
77-
end subroutine
7862
end program

0 commit comments

Comments
 (0)