-
Notifications
You must be signed in to change notification settings - Fork 170
/
stdlib_io_npy_save.fypp
139 lines (112 loc) · 4.53 KB
/
stdlib_io_npy_save.fypp
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
! SPDX-Identifer: MIT
#:include "common.fypp"
#:set RANKS = range(1, MAXRANK + 1)
#:set KINDS_TYPES = REAL_KINDS_TYPES + INT_KINDS_TYPES + CMPLX_KINDS_TYPES
!> Implementation of saving multidimensional arrays to npy files
submodule (stdlib_io_npy) stdlib_io_npy_save
use stdlib_error, only : error_stop
use stdlib_strings, only : to_string
implicit none
contains
!> Generate magic header string for npy format
pure function magic_header(major, minor) result(str)
!> Major version of npy format
integer, intent(in) :: major
!> Minor version of npy format
integer, intent(in) :: minor
!> Magic string for npy format
character(len=8) :: str
str = magic_number // magic_string // achar(major) // achar(minor)
end function magic_header
!> Generate header for npy format
pure function npy_header(vtype, vshape) result(str)
!> Type of variable
character(len=*), intent(in) :: vtype
!> Shape of variable
integer, intent(in) :: vshape(:)
!> Header string for npy format
character(len=:), allocatable :: str
integer, parameter :: len_v10 = 8 + 2, len_v20 = 8 + 4, block_size = 64
str = &
"{'descr': '"//vtype//&
"', 'fortran_order': True, 'shape': "//&
shape_str(vshape)//", }"
if (len(str) + len_v10 >= 65535) then
str = str // &
& repeat(" ", block_size - mod(len(str) + len_v20 + 1, block_size)) // nl
str = magic_header(2, 0) // to_bytes_i4(int(len(str))) // str
else
str = str // &
& repeat(" ", block_size - mod(len(str) + len_v10 + 1, block_size)) // nl
str = magic_header(1, 0) // to_bytes_i2(int(len(str))) // str
end if
end function npy_header
!> Write integer as byte string in little endian encoding
pure function to_bytes_i4(val) result(str)
!> Integer value to convert to bytes
integer, intent(in) :: val
!> String of bytes
character(len=4) :: str
str = achar(mod(val, 256**1)) // &
& achar(mod(val, 256**2) / 256**1) // &
& achar(mod(val, 256**3) / 256**2) // &
& achar(val / 256**3)
end function to_bytes_i4
!> Write integer as byte string in little endian encoding, 2-byte truncated version
pure function to_bytes_i2(val) result(str)
!> Integer value to convert to bytes
integer, intent(in) :: val
!> String of bytes
character(len=2) :: str
str = achar(mod(val, 2**8)) // &
& achar(mod(val, 2**16) / 2**8)
end function to_bytes_i2
!> Print array shape as tuple of int
pure function shape_str(vshape) result(str)
!> Shape of variable
integer, intent(in) :: vshape(:)
!> Shape string for npy format
character(len=:), allocatable :: str
integer :: i
str = "("
do i = 1, size(vshape)
str = str//to_string(vshape(i))//", "
enddo
str = str//")"
end function shape_str
#:for k1, t1 in KINDS_TYPES
#:for rank in RANKS
!> Save ${rank}$-dimensional array in npy format
module subroutine save_npy_${t1[0]}$${k1}$_${rank}$(filename, array, iostat, iomsg)
!> Name of the npy file to load from
character(len=*), intent(in) :: filename
!> Array to be loaded from the npy file
${t1}$, intent(in) :: array${ranksuffix(rank)}$
!> Error status of loading, zero on success
integer, intent(out), optional :: iostat
!> Associated error message in case of non-zero status code
character(len=:), allocatable, intent(out), optional :: iomsg
character(len=*), parameter :: vtype = type_${t1[0]}$${k1}$
integer :: io, stat
open(newunit=io, file=filename, form="unformatted", access="stream", iostat=stat)
if (stat == 0) then
write(io, iostat=stat) npy_header(vtype, shape(array))
end if
if (stat == 0) then
write(io, iostat=stat) array
end if
close(io, iostat=stat)
if (present(iostat)) then
iostat = stat
else if (stat /= 0) then
call error_stop("Failed to write array to file '"//filename//"'")
end if
if (present(iomsg)) then
if (stat /= 0) then
iomsg = "Failed to write array to file '"//filename//"'"
end if
end if
end subroutine save_npy_${t1[0]}$${k1}$_${rank}$
#:endfor
#:endfor
end submodule stdlib_io_npy_save