It’s my first time programming with Fortran and I’m still finding my feet.
I’m following along with the tutorials , but I’m wondering if the community here has any suggestions for beginner projects?
And I’ve noticed Tutorials outside Fortran-lang seem scarce, are there any other free resources folks would suggest/that I may not have heard about?
Well, it depends from what do you want to do with fortran and what is your main line of work/research. I would suggest to start with something you know about and that you have already coded in other languages. In this way you can compare the results and check step by step. Careful though, Fortran lacks a real library, so try to start from a problem you can implement completely.
For me, this go-to problem is the FEM procedure for the Poisson equation on the square, because multiple classes I attended used that example, and I have a good understanding of the (mathematical) problem. I coded it in Matlab when I had to learn Matlab, and in python when I needed to learn python, always double checking with the fortran implementation on the same dataset.
Try describing to us why you’re learning fortran, what brought you here and what you would like to achieve in Fortran. We might be able to give you better suggestions
Got it. I’m learning it for a job that involves a lot of HPC but I’m not overly familiar with the language. I have used Python in the past but this was specified instead. I was asking about modelling/numerical projects that are good for beginners. We used to do small problems back when I was a student, pendulum sim etc, but if there’s no real library, would working on something like that be too complex from scratch?
I don’t know what @kimala meant by “there’s no real library”, but if they meant “standard library”, then …
Fortran HAS a standard library, of course, but it’s provided through statements and intrinsic procedures (i.e., you don’t have to worry about which header has what). And there are also a bunch of intrinsic modules, one for compiler-specific stuff (ISO_FORTRAN_ENV) and the other for alignment with other standads (ISO_C_BINDING and IEEE_*).
But Fortran (like most ISO-guided languages) is agnostic operating systems, so for those specific cases you’re better off using either a compiler extension, or (preferred) invoking the C function that does what you need —using the bind(C) attribute/suffix and the ISO_C_BINDING module mentioned above.
If you want to get acquainted with stdlib, a quick way would be to play around at the Compiler Explorer platform and load stdlib as a library Stdlib in Compiler Explorer then you can copy-paste examples from the documentation to understand by doing. stdlib contains many nice API’s such a high level wrappers for BLAS/LAPACK à la Numpy linalg – Fortran-lang/stdlib, hash tables, quadrature rules and many more.
The way I got started with Fortran was my quantum mechanics professor gave me the following list of exercises and told me to come back in a week:
Quadratic Equation Solver (Real Solutions)
Write a program that solves a quadratic equation with real solutions. The program should prompt the user to enter the coefficients and output either one or two real solutions. If no real solutions exist, it should indicate this accordingly.
Quadratic Equation Solver (Complex Solutions)
Modify the previous program to handle complex solutions. The program should prompt the user for the coefficients and output the solutions in the form a + b i, where i represents the imaginary unit.
Angle Sum and Difference Calculator
Write a program that computes the sum and difference of two angles given in degrees, minutes, and seconds.
Trigonometric Function Tabulation
Write a program that opens a file named trig.txt and tabulates the values of sin(x), cos(x), and tan(x) for x ranging from 0 to 1000 degrees in increments of 0.5 degrees. The results should be written in degrees with two decimal places. Use gnuplot to plot the tabulated data.
Fibonacci Sequence Generator
Write a program that prompts the user for a real number n and computes the nth term of the Fibonacci sequence.
Prime Number Finder
Write a program that prompts the user for a natural number n and prints all prime numbers less than n.
I had never used a programming language or the terminal before. Luckily my older brother was able to install a compiler for me and show me how to compile a program.
I just dug out one of the exercises from my rotten archive ,
trig.f95
this is a bad example of what Fortran is supposed to look like
! trig.f95
!program ki tabelira sin cos in tan med 0 in 1000 stopinj s korakom 0.5 stopinje
program trig
implicit none
real,parameter::pi=3.14159265359
real:: i,x
open(unit=1, file="\\BERT-PC\Users\Public\Documents\fortran programs ivan\trig.txt")
write(1,1) 'x-stopinje','sin(x)','cos(x)','tan(x)'
1 format (A,3X,A,5X,A,5X,A)
do i=0,1000,.5000
x=(pi/180)*i
write(1,3) i, sin(x), cos(x), tan(x)
3 format (F7.1,3X, F8.3, 3X, F8.3, 3X, F10.3)
end do
close(1)
end program trig
I only started in 2014 . I was mainly referring to the fact I used a free-form file with “fixed-form” code. , not to mention the real-valued loop indexes.
An excellent resource for beginners is the book Modern Fortran: Building efficient parallel applications by @milancurcic, particularly if you’re interested in using Fortran for scientific computing applications. The common theme of all the chapters is the gradual implementation of a well-structured solver for the shallow water equation. The numerical techniques employed are sufficiently simple and intuitive that you don’t actually need to know much about numerical analysis (e.g. finite differences, time-integration schemes, etc) to understand the gist of it and can actually focus more on the good coding practices in Fortran. I’ve actually used the book as learning material for an introductory course on scientific computing in my university and received pretty positive feedback from the students. We’ve also used bits and pieces of it with high-school students who came to do a two weeks internship in the lab and they’ve been able to follow along pretty easily.
Then, it kind of depends on your background and possibly already existing skills in other languages. In general, whenever I learn a new language, I start by re-implementing relatively simple algorithms that I’m very familiar with in the other languages. In this phase, I usually put a lot of emphasis on using only intrinsic features of said language rather than looking at more advanced libraries. It often allows me to get a pretty good feeling for how similar or dissimilar the two languages are from a syntax point of view as well as some intuition about how easy (or not) one is to use compare to the others.
I have a background in applied mathematics (numerical linear algebra, convex optimization and control theory mostly) as well as computational fluid dynamics. The typical set of algorithms I tend to implement whenever learning a new language are the following:
Gaussian elimination for solving a square system of linear equations.
QR factorization using the modified Gram-Schmidt orthogonalization process.
All of these algorithms can easily be implemented using only intrinsic features of the language (e.g. matmul, dot_product, norm2, do and do concurrent etc). I usually restrict myself to fairly simple implementations first to really get the gist of it (e.g. typically, I do not use pivoting for Gaussian elimination or QR decomposition to begin with). My typical rule of thumb is to start with what seems to me like the most naïve way to implement a given algorithm and only incrementally improve the code to get a better understanding of what changes actually improve or degrade the performances. Do not hesitate to run your codes with matrices of varying sizes and to use even a simple call to system_clock to time your code and get somewhat quantitative measures of performances.
Convex optimization : minimizing a convex quadratic form f(x) = \dfrac12 x^T P x - x^T q
Gradient descent with fixed step size
Gradient descent with optimal step size (steepest descent)
Conjugate gradient
Once again, all of these algorithms can be implemented using only standard features of a language. If you’re familiar with convex optimization, you can eventually start making the problem more complex by introducing linear equality or inequality constraints.
Ordinary and partial differential equations
Simulating the Lorenz system in the chaotic regime (already mentioned by @hkvzjal) using a Runge-Kutta scheme.
Simulating the unsteady heat equation on a square domain using finite differences and a semi-implicit Crank-Nicolson scheme. This one allows you to potentially re-use the linear algebra bits implemented earlier.
Simulating the Navier-Stokes equations for the lid-driven cavity flow using a vorticity-streamfunction formulation. Admittedly a more advanced project, but once you’re familiar with the rest, it should still be relatively easy to do.
I do acknowledge that it is a fairly biased list of learning projects. They are however sufficiently simple that you should be able to easily find implementations in other languages against which to compare your solution for validation purposes. They are also sufficiently simple that each would typically require only a couple of hours to complete while still exploring a fairly large set of the language intrinsic features. Once I’ve implemented these and I’m happy with my understanding, I then start trying to understand how I can use more low-level language optimization to improve the peformances (e.g. cache blocking, loop unrolling, etc) and replace some bits and pieces with fairly standard libraries/packages (e.g. lapack).
First off I want to say thank you to everyone who shared advice thus far, it’s been beneficial. It’s good to know there is a package manager I can use like FPM, that’s simplified a lot for me. I was trying to approach this the way I would if I were a first-year student again, but dragging my mind back to what I would have worked on in Uni is easier said than done. It’s easy to try and look for shortcuts. A lot of common sense was given, and I will try my best to complete some short projects to help build up my computational programming skills again.
If you are just trying to learn the basic syntax and programming, a fun approach is to use the codingbat problems at https://codingbat.com/. They are intended for folks learning java or python. But it is fun to try them with other languages as well. They start out simple, and get progressively harder.
Since Fortran is obviously not one of their supported languages, you do have to write your own unit test driver - rather than use the test capability built into the web site. For example, one way to write the Warmup-1 sleepin problem (https://codingbat.com/prob/p187868) in Fortran is:
program warmup1_sleepin
implicit none
! Unit tests
print *, 'case 1: ', merge ('passed', 'failed', sleepin (.false., .false.))
print *, 'case 2: ', merge ('failed', 'passed', sleepin (.true., .false.))
print *, 'case 3: ', merge ('passed', 'failed', sleepin (.false., .true.))
contains
logical function sleepin (weekday, vacation)
logical, intent(in) :: weekday, vacation
if (weekday) then
sleepin = vacation
else
sleepin = .true.
end if
end function
end program
For the trigonometric functions sin, cos, tan, etc., the argument can be in degrees, but it makes no sense for the result to be in degrees.
For the inverse functions, the result can be in degrees if so desired. The wording of the assignment is cause for confusion.
The “results” in the problem was the table that was to be written to a file. The degrees specification was most likely to require the programmer to convert somehow from an integer loop index to a degree value, convert the degree value to a radian value, then to evaluate the specified trig functions, and finally to write the row of values to the output file. That all seems easy, but there are many ways to achieve that result, and a beginner programmer might not use the best approach (within fortran) on his first attempt. As pointed out above, the loop index might instead be a real value, which comes with its own set of programming problems, and the trig functions could (now, maybe not then) be done directly in degrees, which has some advantages (simpler and potentially more accurate) and some disadvantages (portability, since it is a new language feature). Does the programmer evaluate tan(x), or does he compute that value as sin(x)/cos(x)? If the latter, how does he account for small or zero denominators, and if the former what does he do near the 90 and 270 degree, and equivalent, values? There is also the challenge to open the output file with the correct name and file attributes and to print out the results in table form correctly. Then there is the gnuplot part, which is also somewhat of a challenge to a new programmer. I personally think this is a good assignment for the programmer to learn the features of the language and also for the supervisor who can judge the results to determine the programming experience and mathematical knowledge of the programmer.
The next problem, the Fibonacci sequence value, is also a bit of a challenge. That can be computed recursively or directly. For small n, one is more efficient, for large n, the other is best. And why is n a real number instead of an integer? Is this a test for the programmer to recognize when the specification might be incorrect and take it upon himself to correct it, or is it a test of how carefully the programmer reads the specification?
Any programmer working on such assignments would benefit greatly from reading about the Gimli Glider near-mishap, in which the wrong unit-conversion for the density of fuel for an AirCanada 767 was used (the density in pounds/litre vs kg/litre) to obtain the desired fuel load using a dipstick reading instead of a non-functioning fuel sensor)