Skip to content

Commit 5e9565e

Browse files
committed
Implement single precision version
1 parent 559bfd7 commit 5e9565e

File tree

1 file changed

+30
-5
lines changed

1 file changed

+30
-5
lines changed

src/stdlib_experimental_io.f90

+30-5
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,31 @@
11
module stdlib_experimental_io
2-
use iso_fortran_env, only: dp=>real64
2+
use iso_fortran_env, only: sp=>real32, dp=>real64
33
implicit none
44
private
55
public :: loadtxt, savetxt
66

7+
interface loadtxt
8+
module procedure sloadtxt
9+
module procedure dloadtxt
10+
end interface
11+
12+
interface savetxt
13+
module procedure ssavetxt
14+
module procedure dsavetxt
15+
end interface
16+
717
contains
818

9-
subroutine loadtxt(filename, d)
19+
subroutine sloadtxt(filename, d)
20+
character(len=*), intent(in) :: filename
21+
real(sp), allocatable, intent(out) :: d(:,:)
22+
real(dp), allocatable :: tmp(:,:)
23+
call dloadtxt(filename, tmp)
24+
allocate(d(size(tmp,1),size(tmp,2)))
25+
d = real(tmp,sp)
26+
end subroutine
27+
28+
subroutine dloadtxt(filename, d)
1029
! Loads a 2D array from a text file.
1130
!
1231
! Arguments
@@ -15,7 +34,7 @@ subroutine loadtxt(filename, d)
1534
! Filename to load the array from
1635
character(len=*), intent(in) :: filename
1736
! The array 'd' will be automatically allocated with the correct dimensions
18-
real(dp), allocatable, intent(out) :: d(:, :)
37+
real(dp), allocatable, intent(out) :: d(:,:)
1938
!
2039
! Example
2140
! -------
@@ -67,14 +86,20 @@ subroutine loadtxt(filename, d)
6786
close(s)
6887
end subroutine
6988

70-
subroutine savetxt(filename, d)
89+
subroutine ssavetxt(filename, d)
90+
character(len=*), intent(in) :: filename
91+
real(sp), intent(in) :: d(:,:)
92+
call dsavetxt(filename, real(d,dp))
93+
end subroutine
94+
95+
subroutine dsavetxt(filename, d)
7196
! Saves a 2D array into a textfile.
7297
!
7398
! Arguments
7499
! ---------
75100
!
76101
character(len=*), intent(in) :: filename ! File to save the array to
77-
real(dp), intent(in) :: d(:, :) ! The 2D array to save
102+
real(dp), intent(in) :: d(:,:) ! The 2D array to save
78103
!
79104
! Example
80105
! -------

0 commit comments

Comments
 (0)