Python Fortran Rosetta Stone Ported from Fortran 90!

We’re thrilled to announce that the Python Fortran Rosetta Stone has been successfully ported from fortran90.org! to fortran-lang.org

We are grateful to the original owners (@certik) of the content for opensourcing it . This content has been taken from GitHub - certik/fortran90.org: Sources of fortran90.org . This content has been formatted with pandoc and converted to myst markdown for consistency and formatting.

NOTE: All the python 2 codes have been refactored to python 3.

The Python Fortran Rosetta Stone becomes an even more versatile resource, empowering programmers with flexibility, speed, and accuracy.

Explore the newly ported Python Fortran Rosetta Stone and master both Python and Fortran Here.

Thanks to all the Contributors and Reviewers for their Contributions.

Thanks and Regards,
Henil Panchal

20 Likes

Great work @henilp105 ! Thanks for it.

On the page Learn — Fortran Programming Language I don’t see the Rosetta Stone in the mini-books section (but it appears in the left margin when you are inside another tutorial).

1 Like

Sure @vmagnin , That is mainly because we have set a workflow (fortran_packages) which converts the YAML data and the contributers info into json as github artifacts which runs on a daily basis , I have manually rerun that github action It will be patched soon automatically.

Thanks and Regards,
Henil

1 Like

It looks great, thanks! Here are some comments.

For your Python

from numpy import array, size, shape, min, max, sum
a = array([1, 2, 3])
print(shape(a))
print(size(a))
print(max(a))
print(min(a))
print(sum(a))

You give the Fortran equivalent as

integer :: a(3)
a = [1, 2, 3]
print *, shape(a)
print *, size(a)
print *, maxval(a)
print *, minval(a)
print *, sum(a)
end program

But I suggest the declaration

integer, allocatable :: a(:)

since the Python counterpart a can later be resized.

When you are showing Python and Fortran output, I suggest labeling the boxes Python output and Fortran output.

I don’t agree with

Strings and Formatting#

The functionality of both Python and Fortran is pretty much equivalent, only the syntax is a litte different.

In Python can write s = ["boy", "girl"] and have two elements of length 3 and 4, but the closest Fortran equivalents are s = [character(len=4) :: "boy", "girl"] or s = ["boy ", "girl"], which gives you two elements of length 4.

I suggest mentioning that return has a different role in a Python function and a Fortran procedure.

Numpy has a function random.uniform. Maybe compare that to Fortran’s random_number(). Fortran has no equivalent to np.random.normal, but such a function could be written. But maybe the current Rosetta Stone should be left as is to avoid clutter, and links can be added to further discussion of Fortran equivalents to Python/NumPy.

Spelling: “ommit” should be “omit”, “litte” should be “little”.

Beautiful!

  • Let’s add the Rosetta Stone at Learn — Fortran Programming Language.

  • @Beliavsky please go ahead and submit PRs against this file here: webpage/rosetta_stone.md at main · fortran-lang/webpage · GitHub. We can then discuss each change in the PR.

  • Yes, in Python everything is dynamic and happens at runtime, but in Fortran for speed reasons I think you only should use allocatable when you have to, otherwise static arrays I think are better. (Although a good compiler might be able to convert allocatable to static reliably, so maybe it doesn’t matter.)

  • Yes, you can’t have arrays of strings of different lengths in Fortran, although I would like to revisit it, see below.

Arrays of strings

We support lists of strings in LPython, e.g. this works:

from lpython import i32
l: list[str] = ["boy", "girl"]
print(l)
i: i32
for i in range(len(l)):
    print(l[i], len(l[i]))

and prints in both CPython and LPython:

$ PYTHONPATH=$(lpython --get-rtl-dir)/lpython python a.py
['boy', 'girl']
boy 3
girl 4
$ lpython a.py                                           
['boy', 'girl']
boy 3
girl 4

And consequently LFortran’s intermediate representation (ASR) and backends already support this. We could introduce a list type into Fortran via stdlib and have it be routed via the same path in the compiler.

We currently don’t support arrays of strings in LPython. But I don’t know if there is any fundamental limitation why we couldn’t. The same for Fortran. I know there is some ambiguity regarding character(:), allocatable :: l(10) whether it is the string itself that is allocatable, or the whole array is allocatable, but that’s just syntax that could be resolved. Currently one has to “hide” the allocatable elements in a derived type. I think it achieves the same thing, but it’s more verbose / noisy.

One can argue whether putting the allocatable string within a derived type “hides” it or “exposes” it. I think of it from the latter perspective. Compare this to z%re and z%im which references the real and imaginary parts of the complex z. The pseudo-component notation exposes the two components, it doesn’t hide them. They were hidden before this component notation was adopted.

But given that syntax distinction, another important missing feature is that such data types cannot be initialized upon declaration. This is because of the general restriction in fortran that allocatable entities of any type cannot be initialized. If that overall restriction were eliminated, lots of things in fortran would become simpler and more robust, not just character strings.

The other problem with the current fortran approach is that the string type must be defined by the programmer. For example

type string
   character(:), allocatable :: s
end type string

But when a programmer wants to merge or mix two projects, each with their own definitions (maybe with different type or component names), then these entities must be copied or converted from one project type to the other. If this were an intrinsic fortran type, that would promote interoperability.

3 Likes

@RonShepard that’s exactly right.

Thinking about it, I don’t think I’ve ever used arrays of strings in NumPy. But lists of strings I use often. So another option is to add a list data structure to Fortran and allow allocatable strings in it, whether as new syntax, or using existing syntax simply as a “blessed” derived type, say in stdlib.

It appeared today. :+1:

1 Like

Just noticed that most of the Fortran code-snippets have an end program but no program main or something of the sorts at the beginning. Wouldn’t it be better to have a consistency with these snippets? either wrap-it up with program/end program, or not at all?

Also, there is a use types, only: dp used before arriving to the actual example in which the module is defined. For this particular case wouldn’t it be better to advise for use iso_fortran_env, only: dp=>real64?

Sometimes it is better to localize the type parameter definitions in a single place (e.g. the types module) and then reference that definition consistently throughout the project, and other times it is better to define a standard and force everyone to follow it (e.g. dp=>real64).

If there is ever even a remote possibility that the definition of dp would ever change for some future compiler (e.g. to real80 or real128, or to decimal_real64, etc.), then the former is the best approach. If there is ever even a remote possibility that a fortran compiler might not define real64, then the former is best. Otherwise, forcing the convention to use dp=>real64 means that there is one less level of abstraction for developers to worry about when adding new codes or when maintaining existing ones.

1 Like

Totaly agree. It could confuse that non-existent module is tried to use.

As alternative integer, kind :: dp = kind(0.0d0) could be used.

Also “Rosetta stone” isn’t presented on Quickstart tutorial — Fortran Programming Language (i.e. English page) but is presented on Quickstart tutorial — Fortran Programming Language

2 Likes

The new Python-Fortran Rosetta stone looks quite nice. I especially like the fact the knowledge taught along the various sections is finally put together to solve a couple of simple, yet cool, mathematical examples.

I was wondering if we could conclude with a cheat sheet. Maybe something along the lines of this one: MATLAB–Python–Julia cheatsheet. What do you think?

2 Likes

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
1 Like

I believe I can see the analogy you are trying to make. However, I doubt someone proficient in “numerical” python would implement such a class. The more natural way would be to use a Pandas DataFrame or a numpy structured datatype.