Skip to content

Commit ce9c234

Browse files
authored
Add routines for saving/loading arrays in npy format (#581)
1 parent 3e49820 commit ce9c234

9 files changed

+1566
-2
lines changed

doc/specs/stdlib_io.md

+94-2
Original file line numberDiff line numberDiff line change
@@ -36,7 +36,7 @@ program demo_loadtxt
3636
use stdlib_io, only: loadtxt
3737
implicit none
3838
real, allocatable :: x(:,:)
39-
call loadtxt('example.dat', x)
39+
call loadtxt('example.dat', x)
4040
end program demo_loadtxt
4141
```
4242

@@ -128,6 +128,98 @@ program demo_savetxt
128128
use stdlib_io, only: savetxt
129129
implicit none
130130
real :: x(3,2) = 1
131-
call savetxt('example.dat', x)
131+
call savetxt('example.dat', x)
132132
end program demo_savetxt
133133
```
134+
135+
136+
## `load_npy`
137+
138+
### Status
139+
140+
Experimental
141+
142+
### Description
143+
144+
Loads an `array` from a npy formatted binary file.
145+
146+
### Syntax
147+
148+
`call [[stdlib_io_npy(module):load_npy(interface)]](filename, array[, iostat][, iomsg])`
149+
150+
### Arguments
151+
152+
`filename`: Shall be a character expression containing the file name from which to load the `array`.
153+
This argument is `intent(in)`.
154+
155+
`array`: Shall be an allocatable array of any rank of type `real`, `complex` or `integer`.
156+
This argument is `intent(out)`.
157+
158+
`iostat`: Default integer, contains status of loading to file, zero in case of success.
159+
It is an optional argument, in case not present the program will halt for non-zero status.
160+
This argument is `intent(out)`.
161+
162+
`iomsg`: Deferred length character value, contains error message in case `iostat` is non-zero.
163+
It is an optional argument, error message will be dropped if not present.
164+
This argument is `intent(out)`.
165+
166+
### Return value
167+
168+
Returns an allocated `array` with the content of `filename` in case of success.
169+
170+
### Example
171+
172+
```fortran
173+
program demo_loadnpy
174+
use stdlib_io_npy, only: load_npy
175+
implicit none
176+
real, allocatable :: x(:,:)
177+
call loadtxt('example.npy', x)
178+
end program demo_loadnpy
179+
```
180+
181+
182+
## `save_npy`
183+
184+
### Status
185+
186+
Experimental
187+
188+
### Description
189+
190+
Saves an `array` into a npy formatted binary file.
191+
192+
### Syntax
193+
194+
`call [[stdlib_io_npy(module):save_npy(interface)]](filename, array[, iostat][, iomsg])`
195+
196+
### Arguments
197+
198+
`filename`: Shall be a character expression containing the name of the file that will contain the `array`.
199+
This argument is `intent(in)`.
200+
201+
`array`: Shall be an array of any rank of type `real`, `complex` or `integer`.
202+
This argument is `intent(in)`.
203+
204+
`iostat`: Default integer, contains status of saving to file, zero in case of success.
205+
It is an optional argument, in case not present the program will halt for non-zero status.
206+
This argument is `intent(out)`.
207+
208+
`iomsg`: Deferred length character value, contains error message in case `iostat` is non-zero.
209+
It is an optional argument, error message will be dropped if not present.
210+
This argument is `intent(out)`.
211+
212+
### Output
213+
214+
Provides a npy file called `filename` that contains the rank-2 `array`.
215+
216+
### Example
217+
218+
```fortran
219+
program demo_savenpy
220+
use stdlib_io_npy, only: save_npy
221+
implicit none
222+
real :: x(3,2) = 1
223+
call save_npy('example.npy', x)
224+
end program demo_savenpy
225+
```

src/CMakeLists.txt

+3
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,9 @@ set(fppFiles
77
stdlib_bitsets_64.fypp
88
stdlib_bitsets_large.fypp
99
stdlib_io.fypp
10+
stdlib_io_npy.fypp
11+
stdlib_io_npy_load.fypp
12+
stdlib_io_npy_save.fypp
1013
stdlib_kinds.fypp
1114
stdlib_linalg.fypp
1215
stdlib_linalg_diag.fypp

src/Makefile.manual

+13
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,9 @@ SRCFYPP = \
44
stdlib_bitsets_large.fypp \
55
stdlib_bitsets.fypp \
66
stdlib_io.fypp \
7+
stdlib_io_npy.fypp \
8+
stdlib_io_npy_load.fypp \
9+
stdlib_io_npy_save.fypp \
710
stdlib_kinds.fypp \
811
stdlib_linalg.fypp \
912
stdlib_linalg_diag.fypp \
@@ -89,6 +92,16 @@ stdlib_io.o: \
8992
stdlib_optval.o \
9093
stdlib_kinds.o \
9194
stdlib_ascii.o
95+
stdlib_io_npy.o: \
96+
stdlib_kinds.o
97+
stdlib_io_npy_load.o: \
98+
stdlib_io_npy.o \
99+
stdlib_error.o \
100+
stdlib_strings.o
101+
stdlib_io_npy_save.o: \
102+
stdlib_io_npy.o \
103+
stdlib_error.o \
104+
stdlib_strings.o
92105
stdlib_linalg.o: \
93106
stdlib_kinds.o
94107
stdlib_linalg_diag.o: \

src/stdlib_io_npy.fypp

+126
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,126 @@
1+
! SPDX-Identifer: MIT
2+
3+
#:include "common.fypp"
4+
#:set RANKS = range(1, MAXRANK + 1)
5+
#:set KINDS_TYPES = REAL_KINDS_TYPES + INT_KINDS_TYPES + CMPLX_KINDS_TYPES
6+
7+
!> Description of the npy format taken from
8+
!> https://numpy.org/doc/stable/reference/generated/numpy.lib.format.html
9+
!>
10+
!>## Format Version 1.0
11+
!>
12+
!> The first 6 bytes are a magic string: exactly \x93NUMPY.
13+
!>
14+
!> The next 1 byte is an unsigned byte:
15+
!> the major version number of the file format, e.g. \x01.
16+
!>
17+
!> The next 1 byte is an unsigned byte:
18+
!> the minor version number of the file format, e.g. \x00.
19+
!> Note: the version of the file format is not tied to the version of the numpy package.
20+
!>
21+
!> The next 2 bytes form a little-endian unsigned short int:
22+
!> the length of the header data HEADER_LEN.
23+
!>
24+
!> The next HEADER_LEN bytes form the header data describing the array’s format.
25+
!> It is an ASCII string which contains a Python literal expression of a dictionary.
26+
!> It is terminated by a newline (\n) and padded with spaces (\x20) to make the total
27+
!> of len(magic string) + 2 + len(length) + HEADER_LEN be evenly divisible by 64 for
28+
!> alignment purposes.
29+
!>
30+
!> The dictionary contains three keys:
31+
!>
32+
!> - “descr”: dtype.descr
33+
!> An object that can be passed as an argument to the numpy.dtype constructor
34+
!> to create the array’s dtype.
35+
!>
36+
!> - “fortran_order”: bool
37+
!> Whether the array data is Fortran-contiguous or not. Since Fortran-contiguous
38+
!> arrays are a common form of non-C-contiguity, we allow them to be written directly
39+
!> to disk for efficiency.
40+
!>
41+
!> - “shape”: tuple of int
42+
!> The shape of the array.
43+
!>
44+
!> For repeatability and readability, the dictionary keys are sorted in alphabetic order.
45+
!> This is for convenience only. A writer SHOULD implement this if possible. A reader MUST
46+
!> NOT depend on this.
47+
!>
48+
!> Following the header comes the array data. If the dtype contains Python objects
49+
!> (i.e. dtype.hasobject is True), then the data is a Python pickle of the array.
50+
!> Otherwise the data is the contiguous (either C- or Fortran-, depending on fortran_order)
51+
!> bytes of the array. Consumers can figure out the number of bytes by multiplying the
52+
!> number of elements given by the shape (noting that shape=() means there is 1 element)
53+
!> by dtype.itemsize.
54+
!>
55+
!>## Format Version 2.0
56+
!>
57+
!> The version 1.0 format only allowed the array header to have a total size of 65535 bytes.
58+
!> This can be exceeded by structured arrays with a large number of columns.
59+
!> The version 2.0 format extends the header size to 4 GiB. numpy.save will automatically
60+
!> save in 2.0 format if the data requires it, else it will always use the more compatible
61+
!> 1.0 format.
62+
!>
63+
!> The description of the fourth element of the header therefore has become:
64+
!> “The next 4 bytes form a little-endian unsigned int: the length of the header data
65+
!> HEADER_LEN.”
66+
!>
67+
!>## Format Version 3.0
68+
!>
69+
!> This version replaces the ASCII string (which in practice was latin1) with a
70+
!> utf8-encoded string, so supports structured types with any unicode field names.
71+
module stdlib_io_npy
72+
use stdlib_kinds, only : int8, int16, int32, int64, sp, dp, xdp, qp
73+
implicit none
74+
private
75+
76+
public :: save_npy, load_npy
77+
78+
79+
!> Version: experimental
80+
!>
81+
!> Save multidimensional array in npy format
82+
!> ([Specification](../page/specs/stdlib_io.html#save_npy))
83+
interface save_npy
84+
#:for k1, t1 in KINDS_TYPES
85+
#:for rank in RANKS
86+
module subroutine save_npy_${t1[0]}$${k1}$_${rank}$(filename, array, iostat, iomsg)
87+
character(len=*), intent(in) :: filename
88+
${t1}$, intent(in) :: array${ranksuffix(rank)}$
89+
integer, intent(out), optional :: iostat
90+
character(len=:), allocatable, intent(out), optional :: iomsg
91+
end subroutine save_npy_${t1[0]}$${k1}$_${rank}$
92+
#:endfor
93+
#:endfor
94+
end interface save_npy
95+
96+
!> Version: experimental
97+
!>
98+
!> Load multidimensional array in npy format
99+
!> ([Specification](../page/specs/stdlib_io.html#load_npy))
100+
interface load_npy
101+
#:for k1, t1 in KINDS_TYPES
102+
#:for rank in RANKS
103+
module subroutine load_npy_${t1[0]}$${k1}$_${rank}$(filename, array, iostat, iomsg)
104+
character(len=*), intent(in) :: filename
105+
${t1}$, allocatable, intent(out) :: array${ranksuffix(rank)}$
106+
integer, intent(out), optional :: iostat
107+
character(len=:), allocatable, intent(out), optional :: iomsg
108+
end subroutine load_npy_${t1[0]}$${k1}$_${rank}$
109+
#:endfor
110+
#:endfor
111+
end interface load_npy
112+
113+
114+
character(len=*), parameter :: nl = achar(10)
115+
116+
character(len=*), parameter :: &
117+
type_iint8 = "<i1", type_iint16 = "<i2", type_iint32 = "<i4", type_iint64 = "<i8", &
118+
type_rsp = "<f4", type_rdp = "<f8", type_rxdp = "<f10", type_rqp = "<f16", &
119+
type_csp = "<c8", type_cdp = "<c16", type_cxdp = "<c20", type_cqp = "<c32"
120+
121+
character(len=*), parameter :: &
122+
& magic_number = char(int(z"93")), &
123+
& magic_string = "NUMPY"
124+
125+
126+
end module stdlib_io_npy

0 commit comments

Comments
 (0)