-
Notifications
You must be signed in to change notification settings - Fork 178
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Extract zip, unfinished array mapping
- Loading branch information
Showing
17 changed files
with
1,022 additions
and
307 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file was deleted.
Oops, something went wrong.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,88 @@ | ||
! SPDX-Identifier: MIT | ||
|
||
#:include "common.fypp" | ||
#:set RANKS = range(1, MAXRANK + 1) | ||
#:set KINDS_TYPES = REAL_KINDS_TYPES + INT_KINDS_TYPES + CMPLX_KINDS_TYPES | ||
|
||
!> Module for index manipulation and general array handling | ||
!> | ||
!> The specification of this module is available [here](../page/specs/stdlib_array.html). | ||
module stdlib_array | ||
use stdlib_kinds, only: int8, int16, int32, int64, sp, dp, xdp, qp | ||
implicit none | ||
private | ||
|
||
public :: trueloc, falseloc | ||
|
||
type, public :: t_array_bundle | ||
class(t_array), allocatable :: files(:) | ||
end type | ||
|
||
type, abstract, public :: t_array | ||
character(:), allocatable :: name | ||
end type | ||
|
||
#:for k1, t1 in KINDS_TYPES | ||
#:for rank in RANKS | ||
type, extends(t_array), public :: t_array_${t1[0]}$${k1}$_${rank}$ | ||
${t1}$, allocatable :: values${ranksuffix(rank)}$ | ||
end type | ||
#:endfor | ||
#:endfor | ||
|
||
contains | ||
|
||
!> Version: experimental | ||
!> | ||
!> Return the positions of the true elements in array. | ||
!> [Specification](../page/specs/stdlib_array.html#trueloc) | ||
pure function trueloc(array, lbound) result(loc) | ||
!> Mask of logicals | ||
logical, intent(in) :: array(:) | ||
!> Lower bound of array to index | ||
integer, intent(in), optional :: lbound | ||
!> Locations of true elements | ||
integer :: loc(count(array)) | ||
|
||
call logicalloc(loc, array, .true., lbound) | ||
end function trueloc | ||
|
||
!> Version: experimental | ||
!> | ||
!> Return the positions of the false elements in array. | ||
!> [Specification](../page/specs/stdlib_array.html#falseloc) | ||
pure function falseloc(array, lbound) result(loc) | ||
!> Mask of logicals | ||
logical, intent(in) :: array(:) | ||
!> Lower bound of array to index | ||
integer, intent(in), optional :: lbound | ||
!> Locations of false elements | ||
integer :: loc(count(.not. array)) | ||
|
||
call logicalloc(loc, array, .false., lbound) | ||
end | ||
|
||
!> Return the positions of the truthy elements in array | ||
pure subroutine logicalloc(loc, array, truth, lbound) | ||
!> Locations of truthy elements | ||
integer, intent(out) :: loc(:) | ||
!> Mask of logicals | ||
logical, intent(in) :: array(:) | ||
!> Truthy value | ||
logical, intent(in) :: truth | ||
!> Lower bound of array to index | ||
integer, intent(in), optional :: lbound | ||
integer :: i, pos, offset | ||
|
||
offset = 0 | ||
if (present(lbound)) offset = lbound - 1 | ||
|
||
i = 0 | ||
do pos = 1, size(array) | ||
if (array(pos) .eqv. truth) then | ||
i = i + 1 | ||
loc(i) = pos + offset | ||
end if | ||
end do | ||
end | ||
end |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,124 @@ | ||
!> Interface to the minizip library for creating and extracting zip files. | ||
module stdlib_io_minizip | ||
use, intrinsic :: iso_c_binding, only: c_char, c_ptr, c_int, c_long | ||
implicit none | ||
private | ||
|
||
integer, parameter, public :: UNZ_OK = 0 | ||
integer, parameter, public :: UNZ_END_OF_LIST_OF_FILE = -100 | ||
integer, parameter, public :: UNZ_ERRNO = -1 | ||
integer, parameter, public :: UNZ_EOF = 0 | ||
integer, parameter, public :: UNZ_PARAMERROR = -102 | ||
integer, parameter, public :: UNZ_BADZIPFILE = -103 | ||
integer, parameter, public :: UNZ_INTERNALERROR = -104 | ||
integer, parameter, public :: UNZ_CRCERROR = -105 | ||
|
||
public :: unz_get_global_info | ||
public :: unz_open | ||
public :: unz_go_to_first_file | ||
public :: unz_get_current_file_info | ||
public :: unz_open_current_file | ||
public :: unz_read_current_file | ||
public :: unz_close_current_file | ||
public :: unz_go_to_next_file | ||
public :: unz_close | ||
|
||
type, bind(c), public :: unz_global_info | ||
integer(kind=c_long) :: number_of_files | ||
integer(kind=c_long) :: comment_size | ||
end type | ||
|
||
type, bind(c), public :: unz_file_info | ||
integer(kind=c_long) :: version | ||
integer(kind=c_long) :: version_needed | ||
integer(kind=c_long) :: flag | ||
integer(kind=c_long) :: compression_method | ||
integer(kind=c_long) :: dos_date | ||
integer(kind=c_long) :: crc | ||
integer(kind=c_long) :: compressed_size | ||
integer(kind=c_long) :: uncompressed_size | ||
integer(kind=c_long) :: size_filename | ||
integer(kind=c_long) :: size_file_extra | ||
integer(kind=c_long) :: size_file_comment | ||
integer(kind=c_long) :: disk_num_start | ||
integer(kind=c_long) :: internal_file_attributes | ||
integer(kind=c_long) :: external_file_attributes | ||
end type | ||
|
||
interface | ||
function unz_open(path) bind(c, name='unzOpen') | ||
import :: c_char, c_ptr | ||
implicit none | ||
character(kind=c_char), intent(in) :: path | ||
type(c_ptr) :: unz_open | ||
end | ||
|
||
function unz_get_global_info(file, global_info) bind(c, name='unzGetGlobalInfo') | ||
import :: c_ptr, c_int, unz_global_info | ||
implicit none | ||
type(c_ptr), intent(in), value :: file | ||
type(unz_global_info), intent(out) :: global_info | ||
integer(kind=c_int) :: unz_get_global_info | ||
end | ||
|
||
function unz_go_to_first_file(file) bind(c, name='unzGoToFirstFile') | ||
import :: c_ptr, c_int | ||
implicit none | ||
type(c_ptr), intent(in), value :: file | ||
integer(kind=c_int) :: unz_go_to_first_file | ||
end | ||
|
||
function unz_get_current_file_info(file, file_info, filename, filename_buffer_size, & | ||
& extra_field, extra_field_buffer_size, comment, comment_buffer_size) & | ||
& bind(c, name='unzGetCurrentFileInfo') | ||
import :: c_ptr, c_int, c_char, c_long, unz_file_info | ||
implicit none | ||
type(c_ptr), intent(in), value :: file | ||
type(unz_file_info), intent(out) :: file_info | ||
character(kind=c_char), intent(out) :: filename(*) | ||
integer(kind=c_long), intent(in), value :: filename_buffer_size | ||
character(kind=c_char), intent(out) :: extra_field(*) | ||
integer(kind=c_long), intent(in), value :: extra_field_buffer_size | ||
character(kind=c_char), intent(out) :: comment(*) | ||
integer(kind=c_long), intent(in), value :: comment_buffer_size | ||
integer(kind=c_int) :: unz_get_current_file_info | ||
end | ||
|
||
function unz_open_current_file(file) bind(c, name='unzOpenCurrentFile') | ||
import :: c_ptr, c_int | ||
implicit none | ||
type(c_ptr), intent(in), value :: file | ||
integer(kind=c_int) :: unz_open_current_file | ||
end | ||
|
||
function unz_read_current_file(file, buffer, size) bind(c, name='unzReadCurrentFile') | ||
import :: c_ptr, c_int, c_char | ||
implicit none | ||
type(c_ptr), intent(in), value :: file | ||
character(kind=c_char), intent(out) :: buffer(*) | ||
integer(kind=c_int), intent(in), value :: size | ||
integer(kind=c_int) :: unz_read_current_file | ||
end | ||
|
||
function unz_go_to_next_file(file) bind(c, name='unzGoToNextFile') | ||
import :: c_ptr, c_int | ||
implicit none | ||
type(c_ptr), intent(in), value :: file | ||
integer(kind=c_int) :: unz_go_to_next_file | ||
end | ||
|
||
function unz_close_current_file(file) bind(c, name='unzCloseCurrentFile') | ||
import :: c_ptr, c_int | ||
implicit none | ||
type(c_ptr), intent(in), value :: file | ||
integer(kind=c_int) :: unz_close_current_file | ||
end | ||
|
||
function unz_close(file) bind(c, name='unzClose') | ||
import :: c_ptr, c_int | ||
implicit none | ||
type(c_ptr), intent(in), value :: file | ||
integer(kind=c_int) :: unz_close | ||
end | ||
end interface | ||
end |
Oops, something went wrong.