Learning C through Fortran: multidimensional arrays

Hello all,
I am now on lesson 4

This is my code

multi_dimensional.c

#include <stdio.h>

extern void average_grades_from_fortran(int subjects,int students,int grades[subjects][students]);

void calculate_the_average_of_subjects(int number_of_subjects,int number_of_students,int grades[number_of_subjects][number_of_students])
  {
    float average_grade;
    for (int i=0;i<number_of_subjects;i++)
      {
        average_grade = 0.0;
        for (int j=0;j<number_of_students;j++)
          {
            average_grade +=grades[i][j];
          }
        average_grade /= number_of_students;
        printf("From C the average marks for subject %d is: %.2f \n",i,average_grade);
      }
    average_grades_from_fortran(number_of_subjects,number_of_students,grades);
  }

multi_dimensional.f90

module calculate_the_average_grade
  use,intrinsic :: iso_c_binding,only: c_int,c_float
  implicit none
  private

  public :: intro

  interface
     subroutine what_is_the_average_grade(subjects,students,grades) bind(C,name="calculate_the_average_of_subjects")
       import :: c_int
       implicit none
       integer(kind=c_int),value,intent(in) :: subjects,students
       integer(kind=c_int),dimension(subjects,students),intent(in) :: grades
     end subroutine what_is_the_average_grade
  end interface

contains

  subroutine average_grades_from_fortran(subjects,students,grades) bind(C)
    integer(kind=c_int),intent(in),value :: subjects,students
    integer(kind=c_int),dimension(subjects,students),intent(in) :: grades
    real(kind=c_float) :: average_of_the_grades
    integer(c_int) :: i,j

    print *, " "
    do i=1,subjects
       average_of_the_grades=0.0
       do j=1,students
          average_of_the_grades=average_of_the_grades+real(grades(i,j),kind=c_float)
       end do
       average_of_the_grades=average_of_the_grades/size(grades,dim=2,kind=c_float)
       print "(a,1x,i0,1x,a,1x,f12.6)", "In Fortran the average for subject",i,"is:",average_of_the_grades
    end do
  end subroutine average_grades_from_fortran

  subroutine intro()
    integer(kind=c_int) :: given_subjects,given_students
    integer(kind=c_int),dimension(:,:),allocatable :: given_grades
    integer (kind=c_int) :: i,j

    write(unit=*,fmt="(a,1x)",advance="no") "Please enter the number of subjects"; read *, given_subjects
    write(unit=*,fmt="(a,1x)",advance="no") "Please enter the number of students"; read *, given_students
    allocate(given_grades(given_subjects,given_students))

    do i=1,given_subjects
       do j=1,given_students
          write(unit=*,fmt="(a,1x,i0,1x,a,1x,i0,1x,a,1x)",advance="no") "Please enter the grade for subject",i,"for student",j,":"
          read *, given_grades(i,j)
       end do
    end do

    call what_is_the_average_grade(given_subjects, given_students,given_grades)

  end subroutine intro

end module calculate_the_average_grade

main.f90

program main
  use calculate_the_average_grade
  implicit none

  call intro()

end program main

Compiled with:

gfortran -O3 multi_dimensional.c multi_dimensional.f90 main.f90 -o calculate_the_students_grades

Output:

Please enter the number of subjects 2
Please enter the number of students 2
Please enter the grade for subject 1 for student 1 : 34
Please enter the grade for subject 1 for student 2 : 22
Please enter the grade for subject 2 for student 1 : 12
Please enter the grade for subject 2 for student 2 : 23
From C the average marks for subject 0 is: 23.00 
From C the average marks for subject 1 is: 22.50 
  
In Fortran the average for subject 1 is:    28.000000
In Fortran the average for subject 2 is:    17.500000

Why is there such a difference in the output from Fortran vs C ? Did I mess up somewhere ?
I also know there is a more modern way to do things with the C descriptor , but I wanna learn this way first.

1 Like

C does its arrays backwards, so you need to declare the transpose of the matrix in fortran. This error might have been easier to catch with a rectangular array rather than a square array.

Everyone makes this error at some time or another, and you will continue to make it from time to time for the rest of your programming life.

1 Like

The other horror in Fortran vs C is arrays starting by default at 1 vs 0. I think of that as the Baby Worm problem because when I was aged about 8 I read this: “Father Worm, Mother Worm and Baby Worm were crossing a garden. On finding a concrete wall Father Worm dug a hole through the soil under it, followed by Mother and Baby Worm. When they got through, Baby Worm said ‘Look Mum! There’s 4 of us!’ Explain Baby Worm’s observation.”

The answer: Baby Worm was very young and was still learning how to count.:slight_smile:

2 Likes

Thanks @RonShepard and @Harper
For anyone else who wants to know,
EDIT : Corrected full program in a later post

Some resources to go with Ron’s answer:

1 Like

Thank you

1 Like

So as it turns out my earlier correction was wrong. Here is the complete correction with output.
multi_dimensional.c

#include <stdio.h>

extern void average_grades_from_fortran(int subjects,int students,int grades[subjects][students]);

void calculate_the_average_of_subjects(int number_of_subjects,int number_of_students,int grades[number_of_subjects][number_of_students])
  {
    float average_grade;
    for (int i=0;i<number_of_subjects;i++)
      {
        average_grade = 0.0;
        for (int j=0;j<number_of_students;j++)
          {
            average_grade += (float)grades[i][j];
          }
        average_grade /= (float)number_of_students;
        printf("From C the average marks for subject %d is: %.2f \n",i+1,average_grade);
      }
    average_grades_from_fortran(number_of_subjects,number_of_students,grades);
  }

multi_dimensional.f90

module calculate_the_average_grade
  use,intrinsic :: iso_c_binding,only: c_int,c_float
  implicit none
  private

  public :: intro

  interface
     subroutine what_is_the_average_grade(subjects,students,grades) bind(C,name="calculate_the_average_of_subjects")
       import :: c_int
       implicit none
       integer(kind=c_int),value,intent(in) :: subjects,students
       integer(kind=c_int),dimension(students,subjects),intent(in) :: grades
     end subroutine what_is_the_average_grade
  end interface

contains

  subroutine average_grades_from_fortran(subjects,students,grades) bind(C)
    integer(kind=c_int),intent(in),value :: subjects,students
    integer(kind=c_int),dimension(students,subjects),intent(in) :: grades
    real(kind=c_float) :: average_of_the_grades
    integer(c_int) :: i,j

    print *, " "
    do i=1,subjects
       average_of_the_grades=0.0
       do j=1,students
          average_of_the_grades=average_of_the_grades+real(grades(j,i),kind=c_float)
       end do
       average_of_the_grades=average_of_the_grades/size(grades,dim=1,kind=c_float)
       print "(a,1x,i0,1x,a,1x,f12.6)", "In Fortran the average for subject",i,"is:",average_of_the_grades
    end do
  end subroutine average_grades_from_fortran

  subroutine intro()
    integer(kind=c_int) :: given_subjects,given_students
    integer(kind=c_int),dimension(:,:),allocatable :: given_grades
    integer (kind=c_int) :: i,j

    write(unit=*,fmt="(a,1x)",advance="no") "Please enter the number of subjects"; read *, given_subjects
    write(unit=*,fmt="(a,1x)",advance="no") "Please enter the number of students"; read *, given_students
    allocate(given_grades(given_students,given_subjects))

    do i=1,given_subjects
       do j=1,given_students
          write(unit=*,fmt="(a,1x,i0,1x,a,1x,i0,1x,a,1x)",advance="no") "Please enter the grade for subject",i,"for student",j,":"
          read *, given_grades(j,i)
       end do
    end do

    call what_is_the_average_grade(given_subjects, given_students,given_grades)

  end subroutine intro

end module calculate_the_average_grade

main.f90

program main
  use calculate_the_average_grade
  implicit none

  call intro()

end program main

compiled with

gfortran -O3 multi_dimensional.c multi_dimensional.f90 main.f90 -o calculate_the_students_grades

Output

Please enter the number of subjects 2
Please enter the number of students 5
Please enter the grade for subject 1 for student 1 : 80
Please enter the grade for subject 1 for student 2 : 70
Please enter the grade for subject 1 for student 3 : 65
Please enter the grade for subject 1 for student 4 : 89
Please enter the grade for subject 1 for student 5 : 90
Please enter the grade for subject 2 for student 1 : 85
Please enter the grade for subject 2 for student 2 : 80
Please enter the grade for subject 2 for student 3 : 80
Please enter the grade for subject 2 for student 4 : 82
Please enter the grade for subject 2 for student 5 : 87
From C the average marks for subject 1 is: 78.80 
From C the average marks for subject 2 is: 82.80 
  
In Fortran the average for subject 1 is:    78.800003
In Fortran the average for subject 2 is:    82.800003

Once again thanks guys

Thank you for getting this right. Many people aren’t aware that, while Fortran’s default starting index is 1, it’s absolutely trivial to start from 0 if one prefers that, or use indexing that matches physics. For example, quantum chemistry programs have good reason to use arrays like Y(-L:L) for spherical harmonics.

3 Likes

The problem is several of the semantics, especially with received arguments in subprograms, in Fortran are counter-intuitive for domain-focused practitioners and it takes a fair amount of disciple to get it right. In effect, it becomes unwieldy for use in anything but toy programs and small (often single-author) applications.

1 Like

There are at least 255 instances of non-default-indexed arrays in NWChem, which is a multi-million line program with more than 100 authors.

1 Like

@JeffH, can you please source code links to a couple of those instances to see how it was achieved in NWChem? As I pointed out, it takes considerable discipline to work unformly with non-default indexed arrays in Fortran and a few projects can manage strong discipline but it is generally not the case.

I think it is tricky sometimes for the programmer to remember the cases when the array keeps it bounds and when the array assumes the default values. Adding the ALLOCATABLE attribute to a dummy argument, for example, causes the array to keep its bounds. I understand why, but it is somewhat of a special case.

Regarding the -L:L case, the language works well and fits the physics when L is an integer. When it is half-integer, then it doesn’t help as much, and the programmer ends up doing the heavy lifting.

1 Like

https://github.com/nwchemgit/nwchem/blob/master/src/symmetry/sym_abelian.F is a rather basic example.

https://github.com/nwchemgit/nwchem/blob/master/src/NWints/auxil/int_spcart.F#L2023 might be more interesting.

1 Like