Skip to content

Commit e3373ca

Browse files
authored
Merge pull request #246 from vmagnin/fortran90org
Transferring fortran90.org "Fortran Best Practices" into a mini-book
2 parents f4b4e07 + c1e492a commit e3373ca

14 files changed

+1571
-5
lines changed

_data/learning.yml

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -53,6 +53,23 @@ books:
5353
- link: /learn/os_setup/ides
5454
- link: /learn/os_setup/tips
5555

56+
- title: Fortran Best Practices
57+
description: This tutorial collects a modern canonical way of doing things in Fortran.
58+
category: Getting started
59+
link: /learn/best_practices
60+
pages:
61+
- link: /learn/best_practices/style_guide
62+
- link: /learn/best_practices/floating_point
63+
- link: /learn/best_practices/integer_division
64+
- link: /learn/best_practices/modules_programs
65+
- link: /learn/best_practices/arrays
66+
- link: /learn/best_practices/multidim_arrays
67+
- link: /learn/best_practices/element_operations
68+
- link: /learn/best_practices/allocatable_arrays
69+
- link: /learn/best_practices/file_io
70+
- link: /learn/best_practices/callbacks
71+
- link: /learn/best_practices/type_casting
72+
5673
# Web links listed at the bottom of the 'Learn' landing page
5774
#
5875
reference-links:

learn/best_practices.md

Lines changed: 0 additions & 5 deletions
This file was deleted.
Lines changed: 131 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,131 @@
1+
---
2+
layout: book
3+
title: Allocatable Arrays
4+
permalink: /learn/best_practices/allocatable_arrays
5+
---
6+
7+
The ``allocatable`` attribute provides safe way for memory handling.
8+
In comparison to variables with ``pointer`` attribute the memory is managed
9+
automatically and will be deallocated automatically once the variable goes
10+
out-of-scope. Using ``allocatable`` variables removes the possibility to
11+
create memory leaks in an application.
12+
13+
They can be used in subroutines to create scratch or work arrays, where
14+
automatic arrays would become too large to fit on the stack.
15+
16+
```fortran
17+
real(dp), allocatable :: temp(:)
18+
allocate(temp(10))
19+
```
20+
21+
The allocation status can be checked using the ``allocated`` intrinsic
22+
to avoid uninitialized access
23+
24+
```fortran
25+
subroutine show_arr(arr)
26+
integer, allocatable, intent(in) :: arr(:)
27+
28+
if (allocated(arr)) then
29+
print *, arr
30+
end if
31+
end subroutine show_arr
32+
```
33+
34+
To allocate variables inside a procedure the dummy argument has to carry
35+
the ``allocatable`` attribute. Using it in combination with ``intent(out)``
36+
will deallocate previous allocations before entering the procedure:
37+
38+
```fortran
39+
subroutine foo(lam)
40+
real(dp), allocatable, intent(out) :: lam(:)
41+
allocate(lam(5))
42+
end subroutine foo
43+
```
44+
45+
The allocated array can be used afterwards like a normal array
46+
47+
```fortran
48+
real(dp), allocatable :: lam(:)
49+
call foo(lam)
50+
```
51+
52+
An already allocated array cannot be allocated again without prior deallocation.
53+
Similarly, deallocation can only be invoked for allocated arrays. To reallocate
54+
an array use
55+
56+
```fortran
57+
if (allocated(lam)) deallocate(lam)
58+
allocate(lam(10))
59+
```
60+
61+
Passing allocated arrays to procedures does not require the ``allocatable`` attribute
62+
for the dummy arguments anymore.
63+
64+
```fortran
65+
subroutine show_arr(arr)
66+
integer, intent(in) :: arr(:)
67+
68+
print *, arr
69+
end subroutine show_arr
70+
71+
subroutine proc
72+
integer :: i
73+
integer, allocatable :: arr
74+
75+
allocate(arr(5))
76+
77+
do i = 1, size(arr)
78+
arr(i) = 2*i + 1
79+
end do
80+
call show_arr(arr)
81+
end subroutine proc
82+
```
83+
84+
Passing an unallocated array in this context will lead to an invalid memory access.
85+
Allocatable arrays can be passed to ``optional`` dummy arguments, if they are unallocated
86+
the argument will not be present. The ``allocatable`` attribute is not limited to
87+
arrays and can also be associated with scalars, which can be useful in combination
88+
with ``optional`` dummy arguments.
89+
90+
Allocations can be moved between different arrays with ``allocatable`` attribute
91+
using the ``move_alloc`` intrinsic subroutine.
92+
93+
```fortran
94+
subroutine resize(var, n)
95+
real(wp), allocatable, intent(inout) :: var(:)
96+
integer, intent(in), optional :: n
97+
integer :: this_size, new_size
98+
integer, parameter :: inital_size = 16
99+
100+
if (allocated(var)) then
101+
this_size = size(var, 1)
102+
call move_alloc(var, tmp)
103+
else
104+
this_size = initial_size
105+
end if
106+
107+
if (present(n)) then
108+
new_size = n
109+
else
110+
new_size = this_size + this_size/2 + 1
111+
end if
112+
113+
allocate(var(new_size))
114+
115+
if (allocated(tmp)) then
116+
this_size = min(size(tmp, 1), size(var, 1))
117+
var(:this_size) = tmp(:this_size)
118+
end if
119+
end subroutine resize
120+
```
121+
122+
Finally, allocations do not initialize the array, the content of the uninitialized
123+
array is most likely just the bytes of whatever was previously at the respective address.
124+
The allocation supports initialization using the source attribute:
125+
126+
```fortran
127+
real(dp), allocatable :: arr(:)
128+
allocate(arr(10), source=0.0_dp)
129+
```
130+
131+
The ``source`` keyword supports scalar and array valued variables and constants.

learn/best_practices/arrays.md

Lines changed: 200 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,200 @@
1+
---
2+
layout: book
3+
title: Arrays
4+
permalink: /learn/best_practices/arrays
5+
---
6+
7+
Arrays are a central object in Fortran. The creation of dynamic sized arrays
8+
is discussed in the [allocatable arrays arrays](./allocatable_arrays.html).
9+
10+
To pass arrays to procedures four ways are available
11+
12+
1. *assumed-shape* arrays
13+
4. *assumed-rank* arrays
14+
2. *explicit-shape* arrays
15+
3. *assumed-size* arrays
16+
17+
The preferred way to pass arrays to procedures is as *assumed-shape* arrays
18+
19+
```fortran
20+
subroutine f(r)
21+
real(dp), intent(out) :: r(:)
22+
integer :: n, i
23+
n = size(r)
24+
do i = 1, n
25+
r(i) = 1.0_dp / i**2
26+
end do
27+
end subroutine f
28+
```
29+
30+
Higher dimensional arrays can be passed in a similar way.
31+
32+
```fortran
33+
subroutine g(A)
34+
real(dp), intent(in) :: A(:, :)
35+
...
36+
end subroutine g
37+
```
38+
39+
The array is simply passed by
40+
41+
```fortran
42+
real(dp) :: r(5)
43+
call f(r)
44+
```
45+
46+
In this case no array copy is done, which has the advantage that the shape and size
47+
information is automatically passed along and checked at compile and optionally at
48+
runtime.
49+
Similarly, array strides can be passed without requiring a copy of the array but as
50+
*assumed-shape* discriptor:
51+
52+
```fortran
53+
real(dp) :: r(10)
54+
call f(r(1:10:2))
55+
call f(r(2:10:2))
56+
```
57+
58+
This should always be your default way of passing arrays in and out of subroutines.
59+
Avoid passing arrays as whole slices, as it obfuscates the actual intent of the code:
60+
61+
```fortran
62+
real(dp) :: r(10)
63+
call f(r(:))
64+
```
65+
66+
In case more general arrays should be passed to a procedure the *assumed-rank*
67+
functionality introduced in the Fortran 2018 standard can be used
68+
69+
```fortran
70+
subroutine h(r)
71+
real(dp), intent(in) :: r(..)
72+
select rank(r)
73+
rank(1)
74+
! ...
75+
rank(2)
76+
! ...
77+
end select
78+
end subroutine h
79+
```
80+
81+
The actual rank can be queried at runtime using the ``select rank`` construct.
82+
This easily allows to create more generic functions that have to deal with
83+
differnet array ranks.
84+
85+
*Explicit-shape* arrays can be useful for returning data from functions.
86+
Most of their functionality can be provided by *assumed-shape* and *assumed-rank*
87+
arrays but they find frequent use for interfacing with C or in legacy Fortran
88+
procedures, therefore they will be discussed briefly here.
89+
90+
To use *explicit-shape* arrays, the dimension has to be passed explicitly as dummy
91+
argument like in the example below
92+
93+
``` fortran
94+
subroutine f(n, r)
95+
integer, intent(in) :: n
96+
real(dp), intent(out) :: r(n)
97+
integer :: i
98+
do i = 1, n
99+
r(i) = 1.0_dp / i**2
100+
end do
101+
end subroutine
102+
```
103+
104+
For high-dimensional arrays additional indices have to be passed.
105+
106+
``` fortran
107+
subroutine g(m, n, A)
108+
integer, intent(in) :: m, n
109+
real(dp), intent(in) :: A(m, n)
110+
...
111+
end subroutine
112+
```
113+
114+
The routines can be invoked by
115+
116+
``` fortran
117+
real(dp) :: r(5), s(3, 4)
118+
call f(size(r), r)
119+
call g(size(s, 1), size(s, 2), s)
120+
```
121+
122+
Note that the shape is not checked, therefore the following would be valid code
123+
with will potentially yield incorrect results:
124+
125+
```fortran
126+
real(dp) :: s(3, 4)
127+
call g(size(s), 1, s) ! s(12, 1) in g
128+
call g(size(s, 2), size(s, 1), s) ! s(4, 3) in g
129+
```
130+
131+
In this case the memory layout is preserved but the shape is changed.
132+
Also, *explicit-shape* arrays require contiguous memory and will create temporary
133+
arrays in case non-contiguous array strides are passed.
134+
135+
To return an array from a function with *explicit-shape* use
136+
137+
``` fortran
138+
function f(n) result(r)
139+
integer, intent(in) :: n
140+
real(dp) :: r(n)
141+
integer :: i
142+
do i = 1, n
143+
r(i) = 1.0_dp / i**2
144+
end do
145+
end function
146+
```
147+
148+
Finally, there are *assumed-size* arrays, which provide the least compile and runtime
149+
checking and can be found be found frequently in legacy code, they should be avoided
150+
in favour of *assumed-shape* or *assumed-rank* arrays.
151+
An *assumed-size* array dummy argument is identified by an asterisk as the last dimension,
152+
this disables the usage of this array with many intrinsic functions, like ``size`` or
153+
``shape``.
154+
155+
To check for the correct size and shape of an *assumed-shape* array the ``size`` and
156+
``shape`` intrinsic functions can be used to query for those properties
157+
158+
```fortran
159+
if (size(r) /= 4) error stop "Incorrect size of 'r'"
160+
if (any(shape(r) /= [2, 2])) error stop "Incorrect shape of 'r'"
161+
```
162+
163+
Note that ``size`` returns the total size of all dimensions, to obtain the shape of
164+
a specific dimension add it as second argument to the function.
165+
166+
Arrays can be initialized by using an array constructor
167+
168+
```fortran
169+
integer :: r(5)
170+
r = [1, 2, 3, 4, 5]
171+
```
172+
173+
The array constructor can be annoted with the type of the constructed array
174+
175+
```fortran
176+
real(dp) :: r(5)
177+
r = [real(dp) :: 1, 2, 3, 4, 5]
178+
```
179+
180+
Implicit do loops can be used inside an array constructor as well
181+
182+
```fortran
183+
integer :: i
184+
real(dp) :: r(5)
185+
r = [(real(i**2, dp), i = 1, size(r))]
186+
```
187+
188+
In order for the array to start with different index than 1, do:
189+
190+
```fortran
191+
subroutine print_eigenvalues(kappa_min, lam)
192+
integer, intent(in) :: kappa_min
193+
real(dp), intent(in) :: lam(kappa_min:)
194+
195+
integer :: kappa
196+
do kappa = kappa_min, ubound(lam, 1)
197+
print *, kappa, lam(kappa)
198+
end do
199+
end subroutine print_eigenvalues
200+
```

0 commit comments

Comments
 (0)