I suggest showing how a class is defined and an object instantiated in Python and Fortran. Here is an example of a matrix with row and column labels in Python and Fortran.
import numpy as np
class LabeledArray:
def __init__(self, array, row_labels, col_labels):
if array.shape[0] != len(row_labels) or array.shape[1] != len(col_labels):
raise ValueError("Dimensions of array must match lengths of row and column labels")
self.array = np.array(array)
self.row_labels = list(row_labels)
self.col_labels = list(col_labels)
def display(self):
col_header = "".join([f"{col_label:^10}" for col_label in self.col_labels])
print("\t" + col_header)
for row_label, row in zip(self.row_labels, self.array):
row_str = "".join([f"{value:10.4f}" for value in row])
print(f"{row_label}\t{row_str}")
from LabeledArray import LabeledArray
import numpy as np
n1 = 2
n2 = 3
array = np.random.uniform(size=[n1, n2])
row_labels = ["row" + str(i+1) for i in range(n1)]
col_labels = ["col" + str(i+1) for i in range(n2)]
labeled_array = LabeledArray(array, row_labels, col_labels)
labeled_array.row_names = ["a","b"] # can add an attribute anywhere
labeled_array.display()
Output:
col1 col2 col3
row1 0.8466 0.1996 0.0462
row2 0.4358 0.3760 0.2093
module labeled_array_module
implicit none
private
public :: LabeledArray, nlen
integer, parameter :: nlen = 10
type :: LabeledArray
real, allocatable :: array(:,:)
character(len=nlen), allocatable :: row_labels(:), col_labels(:)
contains
procedure :: initialize => labeled_array_initialize
procedure :: display => labeled_array_display
end type LabeledArray
contains
subroutine labeled_array_initialize(self, array, row_labels, col_labels)
class(LabeledArray), intent(in out) :: self
real , intent(in) :: array(:, :)
character(len=nlen), intent(in) :: row_labels(:), col_labels(:)
if (size(array, 1) /= size(row_labels) .or. size(array, 2) /= size(col_labels)) &
stop "Dimensions of array must match lengths of row and column labels"
allocate(self%array(size(array, 1), size(array, 2)), self%row_labels(size(row_labels)), &
self%col_labels(size(col_labels)))
self%array = array
self%row_labels = row_labels
self%col_labels = col_labels
end subroutine labeled_array_initialize
subroutine labeled_array_display(self)
class(LabeledArray), intent(in) :: self
integer :: i
write (*, "(3x, *(1x,a10))") "",self%col_labels
do i=1,size(self%row_labels)
write (*,"(a10, *(1x,f10.4))") self%row_labels(i),self%array(i, :)
end do
end subroutine labeled_array_display
end module labeled_array_module
program test_labeled_array
use labeled_array_module, only: LabeledArray, nlen
implicit none
integer, parameter :: n1 = 2, n2 = 3
type(LabeledArray) :: my_array
real :: input_array(n1, n2)
character(len=nlen) :: row_labels(n1)
character(len=nlen) :: col_labels(n2)
integer :: i
call random_number(input_array)
do i=1,n1 ! set row labels
write (row_labels(i),"('row',i0)") i
end do
do i=1,n2 ! set column labels
write (col_labels(i),"('col',i0)") i
end do
call my_array%initialize(input_array, row_labels, col_labels)
call my_array%display()
my_array = LabeledArray(10*input_array, row_labels, col_labels) ! use default constructor
call my_array%display()
end program test_labeled_array
Output:
col1 col2 col3
row1 0.3946 0.6590 0.3213
row2 0.7932 0.2133 0.7886
col1 col2 col3
row1 3.9457 6.5903 3.2127
row2 7.9323 2.1333 7.8864