Skip to content

Commit b8f3493

Browse files
committed
Deploying to stdlib-fpm from @ 57cfaf0 🚀
1 parent e4e10b9 commit b8f3493

39 files changed

+599
-11171
lines changed

fpm.toml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,3 +7,4 @@ copyright = "2019-2021 stdlib contributors"
77

88
[dev-dependencies]
99
test-drive.git = "https://github.com/fortran-lang/test-drive"
10+
test-drive.tag = "v0.4.0"

src/stdlib_io.f90

Lines changed: 3 additions & 154 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ module stdlib_io
44
!! Provides a support for file handling
55
!! ([Specification](../page/specs/stdlib_io.html))
66

7-
use stdlib_kinds, only: sp, dp, qp, &
7+
use stdlib_kinds, only: sp, dp, xdp, qp, &
88
int8, int16, int32, int64
99
use stdlib_error, only: error_stop
1010
use stdlib_optval, only: optval
@@ -22,9 +22,11 @@ module stdlib_io
2222
FMT_INT = '(*(i0,1x))', &
2323
FMT_REAL_SP = '(*(es15.8e2,1x))', &
2424
FMT_REAL_DP = '(*(es24.16e3,1x))', &
25+
FMT_REAL_XDP = '(*(es26.18e3,1x))', &
2526
FMT_REAL_QP = '(*(es44.35e4,1x))', &
2627
FMT_COMPLEX_SP = '(*(es15.8e2,1x,es15.8e2))', &
2728
FMT_COMPLEX_DP = '(*(es24.16e3,1x,es24.16e3))', &
29+
FMT_COMPLEX_XDP = '(*(es26.18e3,1x,es26.18e3))', &
2830
FMT_COMPLEX_QP = '(*(es44.35e4,1x,es44.35e4))'
2931

3032
interface loadtxt
@@ -34,14 +36,12 @@ module stdlib_io
3436
!! ([Specification](../page/specs/stdlib_io.html#description))
3537
module procedure loadtxt_rsp
3638
module procedure loadtxt_rdp
37-
module procedure loadtxt_rqp
3839
module procedure loadtxt_iint8
3940
module procedure loadtxt_iint16
4041
module procedure loadtxt_iint32
4142
module procedure loadtxt_iint64
4243
module procedure loadtxt_csp
4344
module procedure loadtxt_cdp
44-
module procedure loadtxt_cqp
4545
end interface loadtxt
4646

4747
interface savetxt
@@ -51,14 +51,12 @@ module stdlib_io
5151
!! ([Specification](../page/specs/stdlib_io.html#description_2))
5252
module procedure savetxt_rsp
5353
module procedure savetxt_rdp
54-
module procedure savetxt_rqp
5554
module procedure savetxt_iint8
5655
module procedure savetxt_iint16
5756
module procedure savetxt_iint32
5857
module procedure savetxt_iint64
5958
module procedure savetxt_csp
6059
module procedure savetxt_cdp
61-
module procedure savetxt_cqp
6260
end interface
6361

6462
contains
@@ -157,53 +155,6 @@ subroutine loadtxt_rdp(filename, d)
157155
close(s)
158156

159157
end subroutine loadtxt_rdp
160-
subroutine loadtxt_rqp(filename, d)
161-
!! version: experimental
162-
!!
163-
!! Loads a 2D array from a text file.
164-
!!
165-
!! Arguments
166-
!! ---------
167-
!!
168-
!! Filename to load the array from
169-
character(len=*), intent(in) :: filename
170-
!! The array 'd' will be automatically allocated with the correct dimensions
171-
real(qp), allocatable, intent(out) :: d(:,:)
172-
!!
173-
!! Example
174-
!! -------
175-
!!
176-
!!```fortran
177-
!! real(qp), allocatable :: data(:, :)
178-
!! call loadtxt("log.txt", data) ! 'data' will be automatically allocated
179-
!!```
180-
!!
181-
!! Where 'log.txt' contains for example::
182-
!!
183-
!! 1 2 3
184-
!! 2 4 6
185-
!! 8 9 10
186-
!! 11 12 13
187-
!! ...
188-
!!
189-
integer :: s
190-
integer :: nrow, ncol, i
191-
192-
s = open(filename)
193-
194-
! determine number of columns
195-
ncol = number_of_columns(s)
196-
197-
! determine number or rows
198-
nrow = number_of_rows(s)
199-
200-
allocate(d(nrow, ncol))
201-
do i = 1, nrow
202-
read(s, FMT_REAL_qp) d(i, :)
203-
end do
204-
close(s)
205-
206-
end subroutine loadtxt_rqp
207158
subroutine loadtxt_iint8(filename, d)
208159
!! version: experimental
209160
!!
@@ -488,54 +439,6 @@ subroutine loadtxt_cdp(filename, d)
488439
close(s)
489440

490441
end subroutine loadtxt_cdp
491-
subroutine loadtxt_cqp(filename, d)
492-
!! version: experimental
493-
!!
494-
!! Loads a 2D array from a text file.
495-
!!
496-
!! Arguments
497-
!! ---------
498-
!!
499-
!! Filename to load the array from
500-
character(len=*), intent(in) :: filename
501-
!! The array 'd' will be automatically allocated with the correct dimensions
502-
complex(qp), allocatable, intent(out) :: d(:,:)
503-
!!
504-
!! Example
505-
!! -------
506-
!!
507-
!!```fortran
508-
!! complex(qp), allocatable :: data(:, :)
509-
!! call loadtxt("log.txt", data) ! 'data' will be automatically allocated
510-
!!```
511-
!!
512-
!! Where 'log.txt' contains for example::
513-
!!
514-
!! 1 2 3
515-
!! 2 4 6
516-
!! 8 9 10
517-
!! 11 12 13
518-
!! ...
519-
!!
520-
integer :: s
521-
integer :: nrow, ncol, i
522-
523-
s = open(filename)
524-
525-
! determine number of columns
526-
ncol = number_of_columns(s)
527-
ncol = ncol / 2
528-
529-
! determine number or rows
530-
nrow = number_of_rows(s)
531-
532-
allocate(d(nrow, ncol))
533-
do i = 1, nrow
534-
read(s, FMT_COMPLEX_qp) d(i, :)
535-
end do
536-
close(s)
537-
538-
end subroutine loadtxt_cqp
539442

540443

541444
subroutine savetxt_rsp(filename, d)
@@ -592,33 +495,6 @@ subroutine savetxt_rdp(filename, d)
592495
end do
593496
close(s)
594497
end subroutine savetxt_rdp
595-
subroutine savetxt_rqp(filename, d)
596-
!! version: experimental
597-
!!
598-
!! Saves a 2D array into a text file.
599-
!!
600-
!! Arguments
601-
!! ---------
602-
!!
603-
character(len=*), intent(in) :: filename ! File to save the array to
604-
real(qp), intent(in) :: d(:,:) ! The 2D array to save
605-
!!
606-
!! Example
607-
!! -------
608-
!!
609-
!!```fortran
610-
!! real(qp) :: data(3, 2)
611-
!! call savetxt("log.txt", data)
612-
!!```
613-
!!
614-
615-
integer :: s, i
616-
s = open(filename, "w")
617-
do i = 1, size(d, 1)
618-
write(s, FMT_REAL_qp) d(i, :)
619-
end do
620-
close(s)
621-
end subroutine savetxt_rqp
622498
subroutine savetxt_iint8(filename, d)
623499
!! version: experimental
624500
!!
@@ -781,33 +657,6 @@ subroutine savetxt_cdp(filename, d)
781657
end do
782658
close(s)
783659
end subroutine savetxt_cdp
784-
subroutine savetxt_cqp(filename, d)
785-
!! version: experimental
786-
!!
787-
!! Saves a 2D array into a text file.
788-
!!
789-
!! Arguments
790-
!! ---------
791-
!!
792-
character(len=*), intent(in) :: filename ! File to save the array to
793-
complex(qp), intent(in) :: d(:,:) ! The 2D array to save
794-
!!
795-
!! Example
796-
!! -------
797-
!!
798-
!!```fortran
799-
!! complex(qp) :: data(3, 2)
800-
!! call savetxt("log.txt", data)
801-
!!```
802-
!!
803-
804-
integer :: s, i
805-
s = open(filename, "w")
806-
do i = 1, size(d, 1)
807-
write(s, FMT_COMPLEX_qp) d(i, :)
808-
end do
809-
close(s)
810-
end subroutine savetxt_cqp
811660

812661

813662
integer function number_of_columns(s)

src/stdlib_kinds.f90

Lines changed: 24 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,26 @@
1+
!> Version: experimental
2+
!>
3+
!> The specification of this module is available [here](../page/specs/stdlib_kinds.html).
14
module stdlib_kinds
2-
!! version: experimental
3-
use iso_fortran_env, only: sp=>real32, dp=>real64, qp=>real128
4-
use iso_fortran_env, only: int8, int16, int32, int64
5-
use iso_c_binding, only: c_bool
6-
! If we decide later to use iso_c_binding instead of iso_fortran_env:
7-
!use iso_c_binding, only: sp=>c_float, dp=>c_double, qp=>c_float128
8-
!use iso_c_binding, only: int8=>c_int8_t, int16=>c_int16_t, int32=>c_int32_t, int64=>c_int64_t
9-
implicit none
10-
private
11-
public sp, dp, qp, int8, int16, int32, int64, lk, c_bool
12-
13-
integer, parameter :: lk = kind(.true.)
5+
use iso_fortran_env, only: int8, int16, int32, int64
6+
use iso_c_binding, only: c_bool
7+
implicit none
8+
private
9+
public :: sp, dp, xdp, qp, int8, int16, int32, int64, lk, c_bool
10+
11+
!> Single precision real numbers
12+
integer, parameter :: sp = selected_real_kind(6)
13+
14+
!> Double precision real numbers
15+
integer, parameter :: dp = selected_real_kind(15)
16+
17+
!> Extended double precision real numbers
18+
integer, parameter :: xdp = -1
19+
20+
!> Quadruple precision real numbers
21+
integer, parameter :: qp = -1
22+
23+
!> Default logical kind parameter
24+
integer, parameter :: lk = kind(.true.)
25+
1426
end module stdlib_kinds

0 commit comments

Comments
 (0)