Julia vs. Fortran syntax

I am trying Julia and have made some notes on equivalent syntax in Julia and Fortran.
Below the Julia syntax appears first and the Fortran syntax appears after “vs.”. Additions are welcomed.

x = 1.0 vs. x = 1.0d0 (Julia uses 64-bit floats)

x = zeros(5) # array of Float64 intialized to zero
vs.
real(kind=kind(1.0d0)), allocatable :: x(:)
allocate (x(5),source=0.0d0)

[] vs. () to index array elements

true and false vs. .true. and .false.

& vs .and.
| vs. .or.
! vs. .not.

^ vs. ** for exponentiation.

x = rand(n) puts n uniform random variates in x,
x = rand(n1,n2) fills a matrix with dimensions [n1,n2]

sum(x) like Fortran
sum(x,dims=1) vs. sum(x,dim=1)
sum(x,dims=[1,2]) = sum(x) for 2-D array
In general, Julia has a dims optional argument for array functions vs. dim in Fortran,

minimum() and maximum() vs. minval() and maxval()

size(x) returns tuple, size(x,dim) returns scalar. Fortran size(x) returns a scalar.
size(x) vs. shape(x)
length(x) vs. size(x)

x = [2,3] creates a 1-D array of integers
x = [2,3.1] creates a 1-D array of Float64, [2.0,3.1]. The integer value is coerced to Float64.

vec(x) converts x to 1-D array, vs. [x]

x .> 0 vs. merge(1,0,x>0) Note the . before >.
x[x .> 0] vs. pack(x,x>0)

* vs. // to concatenate strings

rstrip("foo ") vs. trim("foo ")

println(2," ",5) vs. print*,2,5 – Julia does not insert spaces between printed items by default.

print(2) vs. write(*,"(i0)",advance=“no”) 2 – Julia print does not append newline, unlike println

# vs. ! for comments

dog and Dog are distinct variables, unlike Fortran


loops:

for i in 1:3
   println(i," ",i^2)
end

vs.

do i=1,3
   print*,i,i**2
end do

if blocks:

if someVar > 10
    println("someVar is totally bigger than 10.")
elseif someVar < 10    # This elseif clause is optional.
    println("someVar is smaller than 10.")
else                    # The else clause is optional too.
    println("someVar is indeed 10.")
end

vs.

if (someVar > 10) then
    print*,"someVar is totally bigger than 10."
else if (someVar < 10) then ! This elseif clause is optional.
    print*,"someVar is smaller than 10."
else                    ! The else clause is optional too.
    print*,"someVar is indeed 10."
end if


function definition:

function power(i,a)
   return i^a
end

vs.

integer function power(i,a)
   power = i**a
end

5 Likes

Some remarks,

  1. The default integer and real kinds and constants can be also set via Fortran compiler flags, although some consider it not a good practice (and I agree to some extent). In that case, Fortran double declaration is as simple as,
real :: a = 1.
real, allocatable :: b(:)
b = [(0., integer :: i = 1,5)] # just another more flexible way of initialization to a pattern

Also, having an explicit notation for types, kinds, ranks helps with defining interfaces for libraries. I have recently read that Julia suffers from this issue at the moment.

  1. What I find highly useful in Fortran that I have not seen in any other language, perhaps including Julia, is the fact that all blocks and loops can be named in Fortran. That may not seem like a big deal, but it really improves code readability and saves a lot of control headaches and time in nested constructs. Concepts like, named exit and cycle do not exist in other languages that I know.

  2. Another extremely useful feature of Fortran arrays is the lack of a fixed base for array indexing. A lot of people say Fortran is 1-based indexing. That is not true. Any integer can be a starting index in Fortran and this is extremely powerful. No other language that I know of, has this capability. I have heard of an external package recently written in Julia that attempts to bring such functionality to Julia.

I wonder why other languages, especially the new ones that are designed from scratch like Julia, do not follow Fortran’s good conventions that have been around for decades, to the extent that people have to write external packages to bring the functionality to the language, which is nowhere near having it as part of the core language.

3 Likes

Other languages use negative indices to mean different things than Fortran does. In Python, -n means n positions from the end of the list. In R, negative indices are the positive indices to be excluded, for example

> x = c(1,4,9)
> x
[1] 1 4 9
> x[-2]
[1] 1 9

I forgot about Python. That is correct.

It seems that some languages like Pascal and Ada allow us to specify arbitrary bounds of arrays, though I have no experience of using them so not sure if they are as flexible as arrays in Fortran…

Arrays in Pascal
https://www.tutorialspoint.com/pascal/pascal_arrays.htm

Arrays in Ada

For more “newly developed” languages, I guess Chapel is very flexible in specifying array bounds (in a builtin way).

http://www.hpc-carpentry.org/hpc-chapel/03-ranges-arrays/index.html

Static arrays in Nim also allow to have arbitrary bounds. I feel it would have been great if dynamic arrays supported such arbitrary indexing, but it seems not…

https://nim-lang.org/docs/tut1.html#advanced-types-arrays

RE Julia, I guess “OffsetArrays” may be useful for using arbitrary bounds, though I am not sure about their performance as compared to their builtin “Array” types… (the latest version might give better performance than before?)

Overall, I think Fortran’s arrays are very straightforward to use for arbitrary indexing (although there are some inconvenience for keeping array bounds for argument passing…)

1 Like

Do you really want to use the variable named a, which will default to type REAL ?

1 Like

Hey, Julia user chiming in here.

  1. AFAIK, Julia does not have loop naming.
  2. We share the Fortran idea of 1-based indexing, and recognize that in some places (like FFT windows) negative indexes are useful. There is actually a wide and extensible interface for arrays and their indexing in Julia, so much so that even joke packages with Star-Wars-movie-indexing like StarWarsArrays.jl exist, just for funsies.
    In fact, many of the good ideas in the Linear Algebra libraries of Julia are Fortran inspired, where it was worth it. (We also use columnar indexing, unlike C.)
3 Likes

We don’t have a section for Fortran users in the Noteworthy differences from other languages page in the official Julia manual, but those are a decent start.

Some very nice syntax sugars that people here may appreciate are

  1. Haskell-like generators
julia> x = [i^2 for i in 1:10 if iseven(i)]
5-element Vector{Int64}:
   4
  16
  36
  64
 100

Which can also work inside functions

julia> sum(i^2 for i in 1:10)
385
  1. Broadcasting, or using the . after any function to map that function all the elements in a collection
julia> foo.(1:5)
5-element Vector{Int64}:
  1
  4
  9
 16
 25
  1. You can get Float32s if you just write an f0 after the numbers

julia> sizeof(1.0f0)
4
  1. You can use BigFloats out-of-the-box
big(2)^100
...
  1. And you can curry functions too, which readers of Milan Curcic's Modern Fortran book I’m sure will appreciate :smiley:
julia> any(==(3), [1, 2, 4, 5, 6])
false

At any rate, hope you keep trying out Julia - our package manager kicks ass and we’re a friendly bunch.

6 Likes

Fortran expressions corresponding to first two examples above, using the implied do loop feature, are

[(i**2,i=2,10,2)]
sum([(i**2,i=1,10)])

The Fortran equivalent of broadcasting would be the use of ELEMENTAL functions, which can be intrinsic or user-defined.

2 Likes

Thanks for sharing your experience and insights into Julia. A few follow-up questions and remarks,

  1. Haskell-like generators: I suppose Julia should have loops with strides (?), in which case your example could be simplified. The Fortran style would be,
x = [( i**2, i = 2,10,2 )]
sum( [( i**2, i = 2,10,2 )] )
  1. I guess that is equivalent to elemental attribute for Fortran functions,

  2. I guess this is similar to what Fortran does, albeit Fortran does it a bit more explicitly by suffixing the constant with _int8, _int16, _int32, int64 or _real32, _real64, _real128 or by an alias to one of these (or to the kind returned by selected_real_kind([p, r, radix])).

  3. To set the range and precision, Fortran is a bit more explicit again by asking the user to specify both via selected_real_kind([p, r, radix]).

  4. I am not sure about the last one, could you explain further if it is different from any( [1, 2, 4, 5, 6] == 3 ) (the Fortran style)?

3 Likes

Oh, neat, I don’t mind learning some functional Fortran every now and then.

Does sum([( ...)]) allow for the condiitonal at the end? Where can one find the resources to look for these implementations and examples? Do these iteration patterns have a performance penalty?

I’ll just note that sum(1:5) is a specific optimized implementation in Julia, because the 1:5 UnitRange, (representing the integer numbers 1 2 3 4 5) has the optimized gaussian sum implementation of O(1).

As to your point in 5, I think they are equivalent, (assuming the any short circuits). What’s nice about many of the iterator functions is that you an pass other functions, like so

julia> any(startswith("J"), ["Julia", "Fortran", "BFFs"])
true

any is also much more generic, allowing for generators:

julia> any(sinpi(i) == 0 for i in 1:10)
true

Fortran might also be able to optimize away the array created in my example, Julia requires a bit more care to avoid those allocations.

1 Like

There is a pretty major difference between broadcasting in Julia and elemental. In Julia, the caller decides whether to operate on elements. This might not sound like a big deal, but it means that you can use it on any function, not just the ones where someone thought “maybe someone will want to use this over elements of an array”. Also, there isn’t a clear distinction. Matmul clearly isn’t an elemental function, except that lots of machine learning will want to multiply a vector by each element of an array of matrices. As such, leaving it up to the caller provides much more flexibility.

3 Likes

SUM and many other Fortran intrinsic functions with array arguments have an optional MASK argument. The gfortran documentation is here. Fortran also has a PACK function to select elements. To illustrate, the program

integer :: i
integer, allocatable :: ivec(:)
print*,[(i**2,i=2,10,2)] ! squares of even integers from 2 to 10
print*,sum([(i**2,i=1,10)]) ! sum of squares of integers from 1 to 10
print*,sum([(i**2,i=1,5)],mask=[(modulo(i,2)==0,i=1,5)]) ! sum of squared even integers from 1 to 5
ivec = [(i,i=1,5)]
print*,sum(ivec**2,mask=modulo(ivec,2)==0) ! sum of squared even integers from 1 to 5
print*,sum(pack(ivec**2,modulo(ivec,2)==0)) ! sum of squared even integers from 1 to 5
end

gives output

   4          16          36          64         100
 385
  20
  20
  20

sum(x,mask=tf) is equivalent to sum(x,tf)

2 Likes

A Julia const can be changed, although a warning is given. A function can be defined twice in the same file. Running

const pi = 3.14
println(pi)
pi = 3.1
println(pi)

function area(r)
   return 3.0*r^2
end

function area(r)
   return pi*r^2
end

println(area(10))

gives

3.14
WARNING: redefinition of constant pi. This may fail, cause incorrect answers, or produce other errors.
3.1
310.0

A Fortran PARAMETER cannot be changed, and a function cannot have duplicate definitions (there is overloading, which is distinct). Redefining a function in a REPL makes sense, just as one can redefine a variable, but conventions for a REPL may not be optimal for a large program. There has been discussion of whether in Julia Redefinition of a constant should be an error, rather than a warning (I’d prefer error).

3 Likes

I guess @Beliavsky has answered the questions. The algorithmic speedup of sum(1:5) is an interesting point worth checking with compilers. There may be Fortran compilers that take this into account.

@oscardssmith Thanks for noting the difference. With this approach, however, I suppose the user will have to compile the library every time for a (re)usage. One of the main utilities of Fortran is to build shared or static libraries once and use them frequently elsewhere. I am sure there are also Julia packages that have Fortran libraries in their core.

gfortran 11.1 knows

1 Like

Thanks for the feedback @miguelraz and welcome to the forum!

3 Likes

Thanks to you - I appreciate your work with the fpm and bridging with the Julia community. Godspeed!

3 Likes

I second this, this is a great start. In particular with the feedback of the Fortran community. The early attempts to build such a list did not succeed, particularly because not many people who thought of that (myself included) is aware of the advances in the syntax of modern Fortran.

3 Likes

Correction:
in Julia we have @label and @goto: Essentials · The Julia Language