Skip to content

Commit b3fdb18

Browse files
committed
Extract zip, unfinished array mapping
1 parent 90a3e9c commit b3fdb18

17 files changed

+1022
-307
lines changed

CMakeLists.txt

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,9 @@ if(NOT FYPP)
4848
message(FATAL_ERROR "Preprocessor fypp not found! Please install fypp following the instructions in https://fypp.readthedocs.io/en/stable/fypp.html#installing")
4949
endif()
5050

51+
# --- find dependencies
52+
find_library(MINIZIP_LIBRARY NAMES minizip HINTS /opt/homebrew/Caskroom/miniconda/base/envs/minizip/lib)
53+
5154
# Custom preprocessor flags
5255
if(DEFINED CMAKE_MAXIMUM_RANK)
5356
set(fyppFlags "-DMAXRANK=${CMAKE_MAXIMUM_RANK}")

example/io/example_loadnpy.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
program example_loadnpy
2-
use stdlib_io_npy, only: load_npy
2+
use stdlib_io_np, only: load_npy
33
implicit none
44
real, allocatable :: x(:, :)
55
call load_npy('example.npy', x)

example/io/example_savenpy.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
program example_savenpy
2-
use stdlib_io_npy, only: save_npy
2+
use stdlib_io_np, only: save_npy
33
implicit none
44
real :: x(3, 2) = 1
55
call save_npy('example.npy', x)

src/CMakeLists.txt

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22

33
# Create a list of the files to be preprocessed
44
set(fppFiles
5+
stdlib_array.fypp
56
stdlib_ascii.fypp
67
stdlib_bitsets.fypp
78
stdlib_bitsets_64.fypp
@@ -15,9 +16,12 @@ set(fppFiles
1516
stdlib_hash_64bit_pengy.fypp
1617
stdlib_hash_64bit_spookyv2.fypp
1718
stdlib_io.fypp
18-
stdlib_io_npy.fypp
19+
stdlib_io_np.fypp
1920
stdlib_io_npy_load.fypp
21+
stdlib_io_npz_load.fypp
2022
stdlib_io_npy_save.fypp
23+
stdlib_io_npz_load.fypp
24+
stdlib_io_npz_save.fypp
2125
stdlib_kinds.fypp
2226
stdlib_linalg.fypp
2327
stdlib_linalg_diag.fypp
@@ -83,6 +87,8 @@ set(SRC
8387
stdlib_specialfunctions_legendre.f90
8488
stdlib_quadrature_gauss.f90
8589
stdlib_stringlist_type.f90
90+
stdlib_io_zip.f90
91+
stdlib_io_minizip.f90
8692
${outFiles}
8793
)
8894

src/stdlib_array.f90

Lines changed: 0 additions & 68 deletions
This file was deleted.

src/stdlib_array.fypp

Lines changed: 88 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,88 @@
1+
! SPDX-Identifier: 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+
!> Module for index manipulation and general array handling
8+
!>
9+
!> The specification of this module is available [here](../page/specs/stdlib_array.html).
10+
module stdlib_array
11+
use stdlib_kinds, only: int8, int16, int32, int64, sp, dp, xdp, qp
12+
implicit none
13+
private
14+
15+
public :: trueloc, falseloc
16+
17+
type, public :: t_array_bundle
18+
class(t_array), allocatable :: files(:)
19+
end type
20+
21+
type, abstract, public :: t_array
22+
character(:), allocatable :: name
23+
end type
24+
25+
#:for k1, t1 in KINDS_TYPES
26+
#:for rank in RANKS
27+
type, extends(t_array), public :: t_array_${t1[0]}$${k1}$_${rank}$
28+
${t1}$, allocatable :: values${ranksuffix(rank)}$
29+
end type
30+
#:endfor
31+
#:endfor
32+
33+
contains
34+
35+
!> Version: experimental
36+
!>
37+
!> Return the positions of the true elements in array.
38+
!> [Specification](../page/specs/stdlib_array.html#trueloc)
39+
pure function trueloc(array, lbound) result(loc)
40+
!> Mask of logicals
41+
logical, intent(in) :: array(:)
42+
!> Lower bound of array to index
43+
integer, intent(in), optional :: lbound
44+
!> Locations of true elements
45+
integer :: loc(count(array))
46+
47+
call logicalloc(loc, array, .true., lbound)
48+
end function trueloc
49+
50+
!> Version: experimental
51+
!>
52+
!> Return the positions of the false elements in array.
53+
!> [Specification](../page/specs/stdlib_array.html#falseloc)
54+
pure function falseloc(array, lbound) result(loc)
55+
!> Mask of logicals
56+
logical, intent(in) :: array(:)
57+
!> Lower bound of array to index
58+
integer, intent(in), optional :: lbound
59+
!> Locations of false elements
60+
integer :: loc(count(.not. array))
61+
62+
call logicalloc(loc, array, .false., lbound)
63+
end
64+
65+
!> Return the positions of the truthy elements in array
66+
pure subroutine logicalloc(loc, array, truth, lbound)
67+
!> Locations of truthy elements
68+
integer, intent(out) :: loc(:)
69+
!> Mask of logicals
70+
logical, intent(in) :: array(:)
71+
!> Truthy value
72+
logical, intent(in) :: truth
73+
!> Lower bound of array to index
74+
integer, intent(in), optional :: lbound
75+
integer :: i, pos, offset
76+
77+
offset = 0
78+
if (present(lbound)) offset = lbound - 1
79+
80+
i = 0
81+
do pos = 1, size(array)
82+
if (array(pos) .eqv. truth) then
83+
i = i + 1
84+
loc(i) = pos + offset
85+
end if
86+
end do
87+
end
88+
end

src/stdlib_io_minizip.f90

Lines changed: 124 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,124 @@
1+
!> Interface to the minizip library for creating and extracting zip files.
2+
module stdlib_io_minizip
3+
use, intrinsic :: iso_c_binding, only: c_char, c_ptr, c_int, c_long
4+
implicit none
5+
private
6+
7+
integer, parameter, public :: UNZ_OK = 0
8+
integer, parameter, public :: UNZ_END_OF_LIST_OF_FILE = -100
9+
integer, parameter, public :: UNZ_ERRNO = -1
10+
integer, parameter, public :: UNZ_EOF = 0
11+
integer, parameter, public :: UNZ_PARAMERROR = -102
12+
integer, parameter, public :: UNZ_BADZIPFILE = -103
13+
integer, parameter, public :: UNZ_INTERNALERROR = -104
14+
integer, parameter, public :: UNZ_CRCERROR = -105
15+
16+
public :: unz_get_global_info
17+
public :: unz_open
18+
public :: unz_go_to_first_file
19+
public :: unz_get_current_file_info
20+
public :: unz_open_current_file
21+
public :: unz_read_current_file
22+
public :: unz_close_current_file
23+
public :: unz_go_to_next_file
24+
public :: unz_close
25+
26+
type, bind(c), public :: unz_global_info
27+
integer(kind=c_long) :: number_of_files
28+
integer(kind=c_long) :: comment_size
29+
end type
30+
31+
type, bind(c), public :: unz_file_info
32+
integer(kind=c_long) :: version
33+
integer(kind=c_long) :: version_needed
34+
integer(kind=c_long) :: flag
35+
integer(kind=c_long) :: compression_method
36+
integer(kind=c_long) :: dos_date
37+
integer(kind=c_long) :: crc
38+
integer(kind=c_long) :: compressed_size
39+
integer(kind=c_long) :: uncompressed_size
40+
integer(kind=c_long) :: size_filename
41+
integer(kind=c_long) :: size_file_extra
42+
integer(kind=c_long) :: size_file_comment
43+
integer(kind=c_long) :: disk_num_start
44+
integer(kind=c_long) :: internal_file_attributes
45+
integer(kind=c_long) :: external_file_attributes
46+
end type
47+
48+
interface
49+
function unz_open(path) bind(c, name='unzOpen')
50+
import :: c_char, c_ptr
51+
implicit none
52+
character(kind=c_char), intent(in) :: path
53+
type(c_ptr) :: unz_open
54+
end
55+
56+
function unz_get_global_info(file, global_info) bind(c, name='unzGetGlobalInfo')
57+
import :: c_ptr, c_int, unz_global_info
58+
implicit none
59+
type(c_ptr), intent(in), value :: file
60+
type(unz_global_info), intent(out) :: global_info
61+
integer(kind=c_int) :: unz_get_global_info
62+
end
63+
64+
function unz_go_to_first_file(file) bind(c, name='unzGoToFirstFile')
65+
import :: c_ptr, c_int
66+
implicit none
67+
type(c_ptr), intent(in), value :: file
68+
integer(kind=c_int) :: unz_go_to_first_file
69+
end
70+
71+
function unz_get_current_file_info(file, file_info, filename, filename_buffer_size, &
72+
& extra_field, extra_field_buffer_size, comment, comment_buffer_size) &
73+
& bind(c, name='unzGetCurrentFileInfo')
74+
import :: c_ptr, c_int, c_char, c_long, unz_file_info
75+
implicit none
76+
type(c_ptr), intent(in), value :: file
77+
type(unz_file_info), intent(out) :: file_info
78+
character(kind=c_char), intent(out) :: filename(*)
79+
integer(kind=c_long), intent(in), value :: filename_buffer_size
80+
character(kind=c_char), intent(out) :: extra_field(*)
81+
integer(kind=c_long), intent(in), value :: extra_field_buffer_size
82+
character(kind=c_char), intent(out) :: comment(*)
83+
integer(kind=c_long), intent(in), value :: comment_buffer_size
84+
integer(kind=c_int) :: unz_get_current_file_info
85+
end
86+
87+
function unz_open_current_file(file) bind(c, name='unzOpenCurrentFile')
88+
import :: c_ptr, c_int
89+
implicit none
90+
type(c_ptr), intent(in), value :: file
91+
integer(kind=c_int) :: unz_open_current_file
92+
end
93+
94+
function unz_read_current_file(file, buffer, size) bind(c, name='unzReadCurrentFile')
95+
import :: c_ptr, c_int, c_char
96+
implicit none
97+
type(c_ptr), intent(in), value :: file
98+
character(kind=c_char), intent(out) :: buffer(*)
99+
integer(kind=c_int), intent(in), value :: size
100+
integer(kind=c_int) :: unz_read_current_file
101+
end
102+
103+
function unz_go_to_next_file(file) bind(c, name='unzGoToNextFile')
104+
import :: c_ptr, c_int
105+
implicit none
106+
type(c_ptr), intent(in), value :: file
107+
integer(kind=c_int) :: unz_go_to_next_file
108+
end
109+
110+
function unz_close_current_file(file) bind(c, name='unzCloseCurrentFile')
111+
import :: c_ptr, c_int
112+
implicit none
113+
type(c_ptr), intent(in), value :: file
114+
integer(kind=c_int) :: unz_close_current_file
115+
end
116+
117+
function unz_close(file) bind(c, name='unzClose')
118+
import :: c_ptr, c_int
119+
implicit none
120+
type(c_ptr), intent(in), value :: file
121+
integer(kind=c_int) :: unz_close
122+
end
123+
end interface
124+
end

0 commit comments

Comments
 (0)