Sparse arrays (not matrix) storage and access

Using large sparse 3x3 dp arrays that I need to access many times, I want to use sparse array storage to save on memory. Although there are numerous libraries for sparse matrix (CSR format, etc …), I did not find for arrays. I do not need to do any operations on these arrays. Only to write them initially and then to retrieve efficiently the data for M(nx,ny,nz). I may not need a whole library for such a simple thing. Would there be a piece of code to do this?

1 Like

What do you mean by a “3x3 dp array” ? A 3x3 array has at most 9 elements. That is by no means “large”. Please provide more details on the retrieval patterns that you expect.

Yes my wording was confusing. I mean the array I read is M(nx,ny,nz)=real value or mostly zeros where nx, ny and nz are large integers. And I need to write M into a memory efficient format and to retrieve the values of M for any nx, ny, nz.

Welcome to the forum. Here are two ways to define a derived type to store the data.

module m1
type, public :: value_3d
   integer :: ix,iy,iz
   real    :: val
end type value_3d
type, public :: array_3d
   type(value_3d), allocatable :: elements(:)
end type array_3d
end module m1

module m2
type, public :: array_3d
   integer, allocatable :: ix(:),iy(:),iz(:) ! (n)
   real   , allocatable :: val(:)            ! (n)
end type array_3d
end module m2

I think the second way might be better expressed through a parameterized derived type (PDT), so that sizes of ix, iy, iz, and val are kept consistent. Someone more familiar with PDT may present a solution.

Here is my first-ever use of a PDT, following this tutorial by Iain Barrass

module m
implicit none
type :: array_3d(n)
   integer, len :: n
   integer      :: ix(n),iy(n),iz(n)
   real         :: x(n)
end type array_3d
end module m
!
program main
use m, only: array_3d
implicit none
type(array_3d(:)), allocatable :: arr
integer :: n
n = 2
allocate (array_3d(n) :: arr)
arr%ix = [1,5]
arr%iy = [6,3]
arr%iz = [3,7]
arr%x  = [1.2,4.6] 
print*,arr
end program main

It compiles and runs with gfortran 12 and Intel Fortran 2021.1 Build 20201112_000000, but with the gfortran the output is

2 1 5 6 3 3 7 1.20000005 4.59999990

and with Intel

1 5 6 3 3 7 1.200000 4.600000

so Intel does not print the len parameter for a list-directed write. Do both compilers conform to the standard here?

1 Like

I suggest that you read about associative arrays . Beliavsky has written about representing the data using a PDT. For retrieving the stored information, you may use a hashing method or a search tree.

Several years ago, I used a hash algorithm for a similar situation where nx, ny, nz ranged from -100 to +100, and the table had about 1,000 entries (compared to the 8 million possible entries given the ranges of nx, ny, nz).

I was looking into the wrong direction with sparse arrays. PDT + hash algorithm is the right one.