Content from What is a Unit Test


Last updated on 2025-11-04 | Edit this page

Overview

Questions

  • What is unit testing?
  • Why do we need unit tests?

Objectives

  • Define the key aspects of a good unit test (isolated, testing minimal functionality, fast, etc).
  • Understand the key anatomy of a unit test in any language.
  • Explain the benefit of unit tests on top of other types of tests.
  • Understand when to run unit tests.

Unit testing is a way of verifying the validity of a code base by testing its smallest individual components, or units.

“If the parts don’t work by themselves, they probably won’t work well together” – (Thomas and Hunt, 2019, The pragmatic programmer, Topic 51).

Several key aspects define a unit test. They should be…

  • Isolated - Does not rely on any other unit of code within the repository.
  • Minimal - Tests only one unit of code.
  • Fast - Run on the scale of ms or s.
Callout

Other forms of testing

There are other forms of testing, such as integration testing in which two or more units of a code base are tested to verify that they work together, or that they are correctly integrated. However, today we are focusing on unit tests as it is often the case that many of these larger tests are written using the same test tools and frameworks, hence we will make progress with both by starting with unit testing.

What does a unit test look like?


All unit tests tend to follow the same pattern of Given-When-Then.

  • Given we are in some specific starting state
    • Units of code almost always have some inputs. These inputs may be scalars to be passed into a function, but they may also be an external dependency such as a database, file or array which must be allocated.
    • This database, file or array memory must exist before the unit can be tested. Hence, we must set up this state in advance of calling the unit we are testing.
  • When we carry out a specific action
    • This is the step in which we call the unit of code to be tested, such as a call to a function or subroutine.
    • We should limit the number of actions being performed here to ensure it is easy to determine which unit is failing in the event that a test fails.
  • Then some specific event/outcome will have occurred.
    • Once we have called our unit of code, we must check that what we expected to happen did indeed happen.
    • This could mean comparing a scalar or vector quantity returned from the called unit against some expected value. However, it could be something more complex such as validating the contents of a database or outputted file.
Challenge

Challenge 1: Write a unit test in sudo code.

Assuming you have a function reverse_array which reverses the order of an allocated array. Write a unit test in pseudo code for reverse_array using the pattern above.

! Given
Allocate the input array `input_array`
Fill `input_array`, for example with `(1,2,3,4)`
Allocate the expected output array `expected_output_array`
Fill `expected_output_array` with the correct expected output, i.e., `(4,3,2,1)`

! When
Call `reverse_array` with `input_array`

! Then
for each element in `input_array`:
   Assert that the corresponding element of `expected_output_array` matches that of `input_array`

When should unit tests be run?


A major benefit of unit tests is the ability to identify bugs at the earliest possible stage. Therefore, unit tests should be run frequently throughout the development process. Passing unit tests give you and your collaborators confidence that changes to your code aren’t modifying the previously expected behaviour, so run your unit tests…

  • if you make a change locally
  • if you raise a merge request
  • if you plan to do a release
  • if you are reviewing someone else’s changes
  • if you have recently installed your code into a new environment
  • if your dependencies have been updated

Basically, all the time.

Do we really need unit tests?


Yes!

You may be thinking that you don’t require unit tests as you already have some well-defined end-to-end test cases which demonstrate that your code base works as expected. However, consider the case where this end-to-end test begins to fail. The message for this failure is likely to be something along the lines of

Expected my_special_number to be 1.234 but got 5.678

If you have a comprehensive understanding of your code, perhaps this is all you need. However, assuming the newest feature that caused this failure was not written by you, it’s going to be difficult to identify what is going wrong without some lengthy debugging.

Now imagine the situation where this developer added unit tests for their new code. When running these unit tests, you may see something like

test_populate_arrays Failed: Expected 1 for index 1 but got 0

This is much clearer. We immediately have an idea of what could be going wrong and the unit test itself will help us determine the problematic code to investigate.

Challenge

Challenge 2: Unit test bad practices

Take a look at 1-into-to-unit-tests/challenge in the exercises repository.

A solution is provided in 1-into-to-unit-tests/solution.

References


Content from Refactoring Fortran


Last updated on 2025-12-05 | Edit this page

Overview

Questions

  • What does good Fortran code look like?
  • How do I refactor Fortran code to follow best practices?

Objectives

  • Be able to spot bad practice within Fortran code.
  • Understand why following best practice make Fortran more testable.

Within Fortran projects, it is common to find many instances of bad practice which makes it difficult, if not impossible to implement unit tests. Therefore, in many cases, the first step to writing unit tests for a Fortran project is to refactor some section of the code into a more testable state which follows best practice. Examples of what we mean by “bad practice” would be not limited to but could include…

  • Using global variables.
  • Large, multi-purpose procedures.
  • Undocumented variables, procedures, modules and programs.

To demonstrate the benefits of refactoring Fortran and how it can be done, we’re going to help John to improve his Fortran implementation of the game of life. A copy of John’s code can be found in the exercises repo at 2-refactoring-fortran/challenge.

Conway’s Game of life is a cellular automaton devised by the British mathematician John Horton Conway in 1970 (Gardner, 1970).

The universe of the Game of Life is an infinite, two-dimensional orthogonal grid of square cells, each of which is in one of two possible states, live or dead (or populated and unpopulated, respectively). Every cell interacts with its eight neighbours, which are the cells that are horizontally, vertically, or diagonally adjacent. At each step in time, the following transitions occur:

  1. Any live cell with fewer than two live neighbours dies, as if by underpopulation.
  2. Any live cell with two or three live neighbours lives on to the next generation.
  3. Any live cell with more than three live neighbours dies, as if by overpopulation.
  4. Any dead cell with exactly three live neighbours becomes a live cell, as if by reproduction.

See the Wikipedia article for more details.

Callout

Checking we haven’t broken anything

To ensure we don’t break anything during our refactoring we need to have some way to test our code. Since we don’t have any automated tests in place we will need to do this manually. Firstly, let’s generate a starting state which we know to be correct.

SH

cd episodes/7-refactoring-fortran/challenge
cmake -B build
cmake --build build
./build/game-of-life ../models/model-1.dat > initial-state.out

Then, whenever we make a change, we can test if the code still works as expected

SH

cmake --build build
./build/game-of-life ../models/model-1.dat > new-state.out
diff initial-state.out new-state.out

If there are no differences, we can assume we haven’t broken anything.

The known refactorings


The next few sections will present some known refactorings.

We’ll show before and after code, present any new coding techniques needed to do the refactoring, and describe code smells: how you know you need to refactor.

1. Replace magic numbers with constants

Smells

  • Raw numbers appear in your code.

Benefits

  • When we use constant with a clear name, it is instantly clear what that value represents.
  • If we use a constant in more than one place, when that value needs to be changed, there is only one place we need to make an update.

F90

do i = 1, 100
    x = i * 3.141 / 100.0
    data(i) = sin(x)
end do

F90

do i = 1, resolution
    x = i * pi / real(resolution)
    data(i) = sin(x)
end do
Challenge

Challenge

Replace all magic numbers in John’s game of life code with constants.

This can be achieved with the changes shown in this commit

2. Change of variable name

Smells

  • Code needs a comment to explain what it is for.

Benefits

  • Someone reading your code can instantly understand what a variable represents and is much more likely to understand the logic employed.

F90

a = a + b*dt

F90

velocity = velocity + acceleration * dt
Challenge

Challenge

Update any poorly named variables in John’s code to have clear names which make it clear what they are.

This can be achieved with the changes shown in this commit

3. Break large procedures into smaller units

Smells

  • A function or subroutine no longer fits on a page in your editor.
  • Multiple dummy arguments are updated (i.e. multiple intent(out) arguments)
  • A line of code is deeply indented
  • A piece of code interacts with the surrounding code through just a few variables.

Benefits

  • Procedures with only one purpose will be much easier to fix should a bug be introduced.
  • Unit testing becomes easier as there are less input/output variables and scenarios to consider when writing your tests.

F90

module process_marices_mod
    implicit none
    real, allocatable :: A(:,:), B(:,:), C(:,:)

contains
    subroutine process_matrices(filename)
        character(len=*), intent(in) :: filename
        integer :: n, iostat, i, j, k
        integer :: unit
        real :: trace

        open(newunit=unit, file=filename, status='old', action='read', iostat=iostat)
        if (iostat /= 0) then
            print *, 'Error opening file: ', trim(filename)
            stop
        end if

        read(unit, *, iostat=iostat) n
        if (iostat /= 0) stop 'Error reading matrix size.'

        allocate(A(n,n), B(n,n))

        print *, 'Reading matrix A (', n, 'x', n, ')'
        do i = 1, n
            read(unit, *, iostat=iostat) (A(i,j), j=1,n)
            if (iostat /= 0) stop 'Error reading matrix A.'
        end do

        print *, 'Reading matrix B (', n, 'x', n, ')'
        do i = 1, n
            read(unit, *, iostat=iostat) (B(i,j), j=1,n)
            if (iostat /= 0) stop 'Error reading matrix B.'
        end do

        close(unit)

        C = 0.0
        do i = 1, n
            do j = 1, n
                do k = 1, n
                    C(i,j) = C(i,j) + A(i,k) * B(k,j)
                end do
            end do
        end do

        n = size(C, 1)
        trace = 0.0
        do i = 1, n
            trace = trace + C(i,i)
        end do

        print *, 'Trace of matrix C = ', trace
    end subroutine process_matrices
end module process_marices_mod

F90

module process_marices_mod
    implicit none
    real, allocatable :: A(:,:), B(:,:), C(:,:)

contains

    subroutine read_matrices_from_file(filename)
        character(len=*), intent(in) :: filename
        integer :: n, iostat, i, j
        integer :: unit

        open(newunit=unit, file=filename, status='old', action='read', iostat=iostat)
        if (iostat /= 0) then
            print *, 'Error opening file: ', trim(filename)
            stop
        end if

        read(unit, *, iostat=iostat) n
        if (iostat /= 0) stop 'Error reading matrix size.'

        allocate(A(n,n), B(n,n))

        print *, 'Reading matrix A (', n, 'x', n, ')'
        do i = 1, n
            read(unit, *, iostat=iostat) (A(i,j), j=1,n)
            if (iostat /= 0) stop 'Error reading matrix A.'
        end do

        print *, 'Reading matrix B (', n, 'x', n, ')'
        do i = 1, n
            read(unit, *, iostat=iostat) (B(i,j), j=1,n)
            if (iostat /= 0) stop 'Error reading matrix B.'
        end do

        close(unit)
    end subroutine read_matrices_from_file

    subroutine multiply_matrices()
        integer :: i, j, k, n
        n = size(A, 1)

        allocate(C(n,n))

        C = 0.0
        do i = 1, n
            do j = 1, n
                do k = 1, n
                    C(i,j) = C(i,j) + A(i,k) * B(k,j)
                end do
            end do
        end do
    end subroutine multiply_matrices

    subroutine display_trace()
        integer :: i, n
        real :: trace

        n = size(C, 1)
        trace = 0.0
        do i = 1, n
            trace = trace + C(i,i)
        end do

        print *, 'Trace of matrix C = ', trace
    end subroutine display_trace
end module process_marices_mod
Challenge

Challenge

Update John’s code to reduce the responsibilities of any procedures to one

This can be achieved with the changes shown in this commit

4. Wrap program functionality in procedures

Smell

  • Logic is repeated outside a procedure.
  • Loops appear outside a procedure.
  • Lots of inline comments requited to explain what is happening in the main program.

Benefits

  • More of your code can be tested.
  • It becomes harder to introduce side effects which may impact other aspects of your code.

F90

program my_matrix_prog
    use process_marices_mod, only : process_matrices
    implicit none

    character(len=200) :: temp_string
    character(:), allocatable :: filename


    print *, 'Enter input filename:'
    read (*,*) temp_string
    filename = trim(temp_string)

    call process_matrices(filename)

end program my_matrix_prog

F90

program my_matrix_prog
    use process_marices_mod, only : process_matrices
    implicit none

    character(:), allocatable :: filename

    call read_filename(filename)
    call process_matrices(filename)

contains

    subroutine read_filename(filename)
        character(:), allocatable, intent(out) :: filename

        character(len=200) :: temp_string

        print *, 'Enter input filename:'
        read (*,*) temp_string

        filename = trim(temp_string)
    end subroutine read_filename

end program my_matrix_prog
Challenge

Challenge

Update John’s code to reduce the responsibilities of any procedures to one

This can be achieved with the changes shown in this commit

5. Replace repeated code with a procedure

Smells

  • Fragments of repeated code appear.

Benefits

  • If logic needs to be updated in the future, there is now just one place this needs to be done
  • More of your code can be unit tested.

F90

subroutine read_matrices_from_file(filename)
    character(len=*), intent(in) :: filename
    integer :: n, iostat, i, j
    integer :: unit

    open(newunit=unit, file=filename, status='old', action='read', iostat=iostat)
    if (iostat /= 0) then
        print *, 'Error opening file: ', trim(filename)
        stop
    end if

    read(unit, *, iostat=iostat) n
    if (iostat /= 0) stop 'Error reading matrix size.'

    allocate(A(n,n), B(n,n))

    print *, 'Reading matrix A (', n, 'x', n, ')'
    do i = 1, n
        read(unit, *, iostat=iostat) (A(i,j), j=1,n)
        if (iostat /= 0) stop 'Error reading matrix A.'
    end do

    print *, 'Reading matrix B (', n, 'x', n, ')'
    do i = 1, n
        read(unit, *, iostat=iostat) (B(i,j), j=1,n)
        if (iostat /= 0) stop 'Error reading matrix B.'
    end do

    close(unit)
end subroutine read_matrices_from_file

F90

subroutine read_matrices_from_file(filename)
    character(len=*), intent(in) :: filename
    integer :: n, iostat, i, j
    integer :: unit

    open(newunit=unit, file=filename, status='old', action='read', iostat=iostat)
    if (iostat /= 0) then
        print *, 'Error opening file: ', trim(filename)
        stop
    end if

    read(unit, *, iostat=iostat) n
    if (iostat /= 0) stop 'Error reading matrix size.'

    allocate(A(n,n), B(n,n))

    print *, 'Reading matrix A (', n, 'x', n, ')'
    call read_next_matrix_from_file(A, unit)

    print *, 'Reading matrix B (', n, 'x', n, ')'
    call read_next_matrix_from_file(B, unit)

    close(unit)
end subroutine read_matrices_from_file

subroutine read_next_matrix_from_file(matrix, unit)
    real, allocatable, intent(inout) :: matrix(:,:)
    integer, intent(in) :: unit

    integer :: i, j, iostat, n

    n = size(matrix, 1)

    do i = 1, n
        read(unit, *, iostat=iostat) (matrix(i,j), j=1,n)
        if (iostat /= 0) stop 'Error reading matrix.'
    end do
end subroutine read_next_matrix_from_file
Callout

There’s a delicate balance between reducing code repetition and make your code unreadable. Try not to go too far when refactoring!

Challenge

Challenge

Update John’s code to move any repeated code into a procedure.

This can be achieved with the changes shown in this commit

6. Replace global variables with procedure arguments

Smells

  • A global variable is assigned and then used inside a called function.
  • A variable is edited within a procedure in which it is not declared.

Benefits

  • Testing becomes much easier because your code is more isolated and thus less code is required within your tests to setup state.
  • You get more help from your compiler and it t is much clearer what your code is doing as you can provide more information about dummy arguments such as their intent.

F90

subroutine multiply_matrices()
    integer :: i, j, k, n
    n = size(A, 1)

    allocate(C(n,n))

    C = 0.0
    do i = 1, n
        do j = 1, n
            do k = 1, n
                C(i,j) = C(i,j) + A(i,k) * B(k,j)
            end do
        end do
    end do
end subroutine multiply_matrices

F90

subroutine multiply_matrices(A, B, C)
    real, allocatable, intent(int) :: A(:,:), B(:,:)
    real, allocatable, intent(out) :: C(:,:)

    integer :: i, j, k, n
    n = size(A, 1)

    allocate(C(n,n))
    
    C = 0.0
    do i = 1, n
        do j = 1, n
            do k = 1, n
                C(i,j) = C(i,j) + A(i,k) * B(k,j)
            end do
        end do
    end do
end subroutine multiply_matrices
Challenge

Challenge

Update John’s code to replace any global variables accessed within procedures with dummy arguments.

This can be achieved with the changes shown in this commit

7. Separate code concepts into files or modules

Smells

  • You find it hard to locate a piece of code.
  • You get a lot of version control conflicts.

Benefits

  • This adds further clarity about what each unit of code is responsible for.
  • Allows further isolation of code as you can scope some procedures or variables to be private.

Using the example we have seen so far, we start with two files my_matrix_prog.f90 and process_marices_mod.f90.

|-- project/directory/
    |-- my_matrix_prog.f90
    |   |-- subroutine read_filename
    |-- process_marices_mod.f90
        |-- subroutine read_matrices_from_file
        |-- subroutine read_next_matrix_from_file
        |-- subroutine multiply_matrices
        |-- subroutine display_trace

If we split the procedures in these files across multiple modules which focus on different tasks, we could end up with something like this.

|-- project/directory/
    |-- my_matrix_prog.f90
    |-- io.f90
    |   |-- subroutine read_filename
    |   |-- subroutine read_matrices_from_file
    |   |-- subroutine read_next_matrix_from_file
    |-- matrix_operations.f90
        |-- subroutine multiply_matrices
        |-- subroutine display_trace

Note: there isn’t one correct way to group these subroutines. For example, we could place display_trace in io.f90.

Challenge

Challenge

Update John’s code to separate code concepts into modules.

You should end up with a module structure. For example, like this…

|-- src/
    |-- main.f90
    |-- animation.f90
    |   |-- subroutine draw_board
    |-- cli.f90
    |   |-- subroutine read_cli_arg
    |-- game_of_life.f90
    |   |-- subroutine find_steady_state
    |   |-- subroutine evolve_board
    |   |-- subroutine check_for_steady_state
    |-- io.f90
        |-- subroutine read_model_from_file

This can be achieved with the changes shown in this commit

Callout

Working effectively with legacy code

When working with Fortran it is very common that you will be working with legacy code and a large scale refactor can feel daunting. Therefore, a great resource for us is Working Effectively with Legacy Code (Feathers, 2004)

If you don’t have time to read the entire book, there is a good summary of the key point in this blog post The key points of Working Effectively with Legacy Code

References


Content from Writing your first unit test


Last updated on 2025-12-05 | Edit this page

Overview

Questions

  • What does a unit test look like?

Objectives

  • Understand the benefits of parameterized tests.
  • Able to write a unit test which is isolated, minimal and fast.

The key aspects of a unit test are the same no matter the language being testing (python, Fortran, etc) or the framework we are using (pFUnit, etc). Therefore, when we are first learning unit testing, it can be useful to think about what the content of a unit test might look like before we try to learn the specific syntax of any one tool.

Testing the temperature


We’ll now use an example Fortran library which converts between units of temperature. This code can be found in the exercises repo under 3-writing-your-first-unit-test/challenge/src/temp_conversions.f90. This library contains two functions, one to convert from Fahrenheit to Celsius (fahrenheit_to_celsius) and another to convert from Celsius to Kelvin (celsius_to_kelvin).

Imagine we want to use this library to do some temperature conversions from Fahrenheit to Kelvin. To ensure the library contains the functionality we need, we decide to write some unit tests.

Challenge

Challenge: Pseudo test

Write a unit test in pseudocode for the temperature library to check that it can convert from Fahrenheit to Kelvin.

Your test could look something like this…

Set some input value of Fahrenheit, for example 32.0
Call fahrenheit_to_celsius with this input
Check that the output is equal to the expected value of 0.0

Set some input value of Celsius, for example 0.0
Call celsius_to_kelvin with this input
Check that the output is equal to the expected value of 273.15

Writing a test


All unit tests tend to follow a similar pattern.

  1. Define the inputs to your unit of code to be tested as well as the outputs you expect from execution with these inputs.

  2. Setup and verify any state required for successful execution (verify a file exists, allocate memory, etc)

  3. Call the unit of code to be tested using the inputs defined in the first step.

  4. Verify the actual outputs of your unit of code with the expected outputs defined in the first step.

Challenge

Challenge: Standard Fortran test

Write a unit test in standard Fortran for the temperature library to check that it can convert from Fahrenheit to Kelvin. You can use your pseudocode as a starting point.

As we are not yet using a testing framework, some boilerplate code has been provided to help you create a test-suite. Take a look at part one of the exercise 3-writing-your-first-unit-test/challenge.

A solution is provided in 3-writing-your-first-unit-test/solution.

Content from Fortran Unit Test Syntax


Last updated on 2026-01-06 | Edit this page

Overview

Questions

  • What is the syntax of writing a unit test in Fortran?
  • How do I build my tests with my existing build system?

Objectives

  • Able to write a unit test for a Fortran procedure with test-drive, veggies and/or pFUnit.
  • Understand the similarities between each framework and where they differ.

What framework will we look at?


There are multiple frameworks available for writing unit tests in Fortran, as detailed on the Fortran Lang website. However, we recommend the use of pFUnit as it is…

  • the most feature rich framework.
  • the most widely used framework.
  • being maintained.
  • able to integrate with CMake and make.

Key features of pFUnit:

  • Supports MPI: Supports testing MPI parallelized code, including parametrizing tests by number of MPI ranks.
  • Simple interface: Tests are written in .pf format which is then pre-processed by a tool provided by pFUnit into .f90 before compilation. This removes the need to write a lot of boilerplate code.

The structure of a test module


All test modules share a basic structure…

F90

module test_something
    ! use funit
    ! use the src to be tested
    implicit none

    ! Derived types: Define types to act as test parameters and test cases.
contains

    ! Test Suite: Define a test suite (collection of tests) to be returned from a procedure.

    ! Test Logic: Define the actual test execution code which will call the src and execute assertions.

    ! Type Constructors: Define constructors for your derived types (test parameters/cases).
end module test_something

Let’s dive into the syntax


We will continue to use the temperature conversion example from the previous episode to cover the syntax of pFUnit.

This uses standard Fortran syntax to define some derived types.

Test parameters

The test parameter type should contain the inputs and expected outputs of the code we are testing.

Callout

Treat the src to be tested like a black box

When writing a unit test,

  • The inputs and outputs are the important aspects to understand about our src code to be tested.
  • The implementation should not influence how we write our test. Not every test needs to be parametrized, but you will always need to consider the inputs and outputs of the src code you are testing.

Firstly, the test parameter derived-type is written as…

F90

@testParameter
type, extends(AbstractTestParameter) :: my_test_params
    integer :: input, expected_output
contains
    procedure :: toString => my_test_params_toString
end type my_test_params

Key points:

  • Our parameter type must be decorated with @testParameter so that the pFUnit pre-processor understands that this derived type defines a test parameter.
  • We must extend one of the base types provided by pFUnit, in this case AbstractTestParameter which is the most generic.
  • We have declared a type-bound procedure toString which maps to the procedure my_test_params_toString. This allows pFUnit to log a helpful description of our parameter set which should be returned from my_test_params_toString (we’ll see more on this later).

Test case

Then we can write our test case derived-type as…

F90

@TestCase(constructor=my_test_params_to_my_test_case, testParameters={my_test_suite()})
type, extends(ParameterizedTestCase) :: my_test_case
    type(my_test_params) :: params
end type my_test_case

Key points:

  • Our parameter type must be decorated with @TestCase so that the pFUnit pre-processor understands that this derived type defines a test case.
  • The @TestCase decorator includes some extra information to tell the pre-processor how the test case should be constructed. What we have defined is…
    • To convert from an instance of my_test_params to an instance of my_test_case, one must call my_test_params_to_my_test_case.
    • The list of parameter sets which define each individual parametrized test will be returned from the function my_test_suite
  • Just like with the test parameter type, we must extend one of the base types provided by pFUnit, in this case ParameterizedTestCase which indicates that this test should be parametrized.
  • We then define a single type-bound value which is of the test parameter type we have just defined.
Challenge

Challenge: Add derived types to pFUnit tests of temperature conversions

Continuing with part two of 3-writing-your-first-unit-test/challenge from the exercises repo. Begin re-writing your standard Fortran test using pFUnit. First, add some derived types to the provided template file, test_temp_conversions.pf.

These types could look something like this…

F90

!> Test parameter type to package the test parameters
@TestParameter
type, extends(AbstractTestParameter) :: temp_conversions_test_params_t
    !> The temperature to input into the function being tested
    real :: input
    !> Theb temperature expected to be returned from the function being tested
    real :: expected_output
    !> A description of the test to be outputted for logging
    character(len=100) :: description
contains
    procedure :: toString => temp_conversions_test_params_t_toString
end type temp_conversions_test_params_t

!> Test case type to specify the style of test (paramaterized)
@TestCase(constructor=new_test_case)
type, extends(ParameterizedTestCase) :: temp_conversions_test_case_t
    type(temp_conversions_test_params_t) :: params
end type temp_conversions_test_case_t

A full solution is provided in 3-writing-your-first-unit-test/solution.

In this section we define our parameter sets (or test suite). We define a function which returns our test parameters like so…

F90

function my_test_suite() result(params)
    type(my_test_params), allocatable :: params(:)

    params = [ &
        my_test_params(1, 2), & ! Given input is 1, output is 2
        my_test_params(3, 4) & ! Given input is 3, output is 4
    ]
end function my_test_suite

Key points:

  • The function returns an array of my_test_params.
  • We are using a constructor function to define each parameter set which we do not need to define ourselves.
Challenge

Challenge: Add a test suite to pFUnit tests of temperature conversions

Continuing with your pFUnit test of temp_conversions, add a test suite for tests of the function fahrenheit_to_celsius in the indicated section of the template file, test_temp_conversions.pf

This test suites could look something like this…

F90

!> Test Suite for tests of fahrenheit_to_celsius
function fahrenheit_to_celsius_testsuite() result(params)
    !> An array of test parameters, each specifying an individual test
    class(temp_conversions_test_params_t), allocatable :: params(:)

    params = [ &
        temp_conversions_test_params_t(0.0, -17.777779, "0.0 °F"), &
        temp_conversions_test_params_t(32.0, 0.0, "0.0 °C"), &
        temp_conversions_test_params_t(-100.0, -73.333336, "100 °F"), &
        temp_conversions_test_params_t(1.23,-17.094444, "Decimal °F") &
    ]
end function fahrenheit_to_celsius_testsuite

A full solution is provided in 3-writing-your-first-unit-test/solution.

This is where we actually call our src procedure and carry out assertions…

F90

@Test
subroutine TestMySrcProcedure(this)
    class (my_test_case), intent(inout) :: this

    integer :: actual_output

    call my_src_procedure(this%params%input, actual_output)

    @assertEqual(this%params%expected_output, actual_output, "Unexpected output from my_src_procedure")
end subroutine TestMySrcProcedure

Key points:

  • We must decorate the test subroutine with the pFUnit annotation @Test so the pre-processor knows this is a test.
  • We are utilising a pre-processor directive provided by pFUnit @assertEqual which allows the exact comparison of two values (also works for comparing arrays). For a full list of the available assertion directives see pFUnit documentation page for their preprocessor directives
    • As is done here, it is recommended to provide a helpful message in case of an assertion failing to help diagnose the issue.
Callout

Parametrize on a test by test basis

It is also possible to parametrize a test at this point, instead of when defining the derived-types. This can be useful if you wish to reuse a test parameter type for multiple test cases…

F90

@Test(testParameters={my_test_suite()})
subroutine TestMySrcProcedure(this)
    class (my_test_case), intent(inout) :: this
    ...
Challenge

Challenge: Add a test function to pFUnit tests of temperature conversions

Continuing with your pFUnit test of temp_conversions, add some test logic for tests of the function fahrenheit_to_celsius in the indicated section of the template file, test_temp_conversions.pf

This test logic could look something like this…

F90

!> Test Logic, unit test subroutine for fahrenheit_to_celsius
@Test(testParameters={fahrenheit_to_celsius_testsuite()})
subroutine test_fahrenheit_to_celsius(this)
    !> The test case which indicates the type of test we are running
    class(temp_conversions_test_case_t), intent(inout) :: this

    character(len=200) :: failure_message
    real :: actual_output

    ! Get the actual celsius value returned from fahrenheit_to_celsius
    actual_output = fahrenheit_to_celsius(this%params%input)

    ! Populate the failure message
    write(failure_message, '(A,F7.2,A,F7.2,A,F7.2,A)') "Failed With ", this%params%input, " °F: Expected ", &
            this%params%expected_output, "°C but got ", actual_output, "°C"
    @assertEqual(this%params%expected_output, actual_output, tolerance=1e-6, message=trim(failure_message))

end subroutine test_fahrenheit_to_celsius

A full solution is provided in 3-writing-your-first-unit-test/solution.

We are required to define two functions.

A conversion from test parameters to a test case:

F90

function my_test_params_to_my_test_case(testParameter) result(tst)
    type (my_test_case) :: tst
    type (my_test_params), intent(in) :: testParameter

    tst%params = testParameter
end function my_test_params_to_my_test_case

It may be necessary to individually map each type-bound value within the testParameter to that in the tst, depending on their complexity.

A conversion from test parameters to a string:

This function helps to provide a clearer description of each test case. The result of this function will be displayed alongside the name of the test for each parameter set.

F90

function my_test_params_toString(testParameter) result(string)
    class (my_test_params), intent(in) :: this
    character(:), allocatable :: string

    character(len=80) :: buffer

    write(buffer,'("Given ",i4," we expect to get ",i4)') this%input, this%expected_output
    string = trim(buffer)
end function my_test_params_toString
Challenge

Challenge: Add type constructors to pFUnit tests of temperature conversions

Continuing with your pFUnit test of temp_conversions, add some type constructors for tests of the temp_conversions in the indicated section of the template file, test_temp_conversions.pf

These type constructors could look something like this…

F90

!> Constructor for converting test parameters into a test case
function new_test_case(testParameter) result(tst)
    !> The parameters to be converted to a test case
    type(temp_conversions_test_params_t), intent(in) :: testParameter
    !> The test case to return after conversion from parameters
    type(temp_conversions_test_case_t) :: tst

    tst%params = testParameter
end function new_test_case

!> Constructor for converting test parameters into a string
function temp_conversions_test_params_t_toString(this) result(string)
    !> The parameters to be converted to a string
    class(temp_conversions_test_params_t), intent(in) :: this
    character(:), allocatable :: string

    string = trim(this%description)
end function temp_conversions_test_params_t_toString

A full solution is provided in 3-writing-your-first-unit-test/solution.

Challenge

Challenge: Test temperature conversions using pFUnit

Finalising your pFUnit test of temp_conversions, add an additional test of the function celsius_to_kelvin.

The full solution is provided in 3-writing-your-first-unit-test/solution.

Content from Integrating with build systems


Last updated on 2026-01-06 | Edit this page

Overview

Questions

  • How do we go from .pf files to an executable test?
  • How do we identify which test is failing and where?

Objectives

  • Be able to add a new test to an existing Make and CMake build system.
  • Understand where we name tests within the build system.

Integrating pFUnit with Make


Let’s look at the steps required to add pFUnit tests to a project built using Make. Firstly, assume we have the following file structure.

|-- ROOT_DIR/
    | Makefile
    |-- src/
    |   |-- main.f90
    |   |-- something.f90
    |
    |-- tests/
        |-- Makefile
        |-- test_something.pf
        |-- test_something_else.pf

The top level Makefile is responsible for compiling the src code but should do very little regarding building the tests. However, it should…

  • Export relevant variables for the tests/Makefile to pick up.

    export SRC_BUILD_DIR
    export ROOT_DIR
    export SRC_OBJS
    export FC
    export FC_FLAGS
    export LIBS
  • Define targets which pass through to targets in the tests/Makefile.

    tests: $(SRC_OBJS)
    	@echo "Building pFUnit test suite..."
    	@$(MAKE) -C $(TEST_DIR) tests
    
    clean:
    	rm -rf $(BUILD_DIR)
    	$(MAKE) -C $(TEST_DIR) clean

The full top level Makefile may look something like this…

# Top level variables
ROOT_DIR = $(shell dirname $(realpath $(firstword $(MAKEFILE_LIST))))
FC ?= gfortran
FC_FLAGS = #... Some flags required for compilation
LIBS = #... Some libs to link to

#------------------------------------#
#      Targets for compiling src     #
#------------------------------------#
SRC_DIR = $(ROOT_DIR)/src
BUILD_DIR = $(ROOT_DIR)/build

# List src files
SRC_FILES = \
    something.f90 \
    main.f90

# Map src files to .o files
SRC_OBJS = $(patsubst %.f90, $(BUILD_DIR)/%.o, $(SRC_FILES))

# Build src .o files
$(BUILD_DIR)/%.o: $(SRC_DIR)/%.f90 | $(BUILD_DIR)
	@echo "Building $@"
	$(FC) -c -J $(BUILD_DIR) -o $@ $<

# Build src executable
$(BUILD_DIR)/a.exe: $(SRC_OBJS)
	$(FC) -o $@ $(FC_FLAGS) $^ $(LIBS)

# Map exe target to building executable
exe: $(BUILD_DIR)/a.exe

# Ensure the build dirs exists
$(BUILD_DIR):
	mkdir -p $@

#------------------------------------#
#         Targets for testing        #
#------------------------------------#
TEST_DIR = $(ROOT_DIR)/tests

# Include make command from tests Makefile
tests: $(SRC_OBJS)
	@echo "Building pFUnit test suite..."
	@$(MAKE) -C $(TEST_DIR) tests


#------------------------------------#
#        Targets for cleaning        #
#------------------------------------#
# Define target for cleaning the build dir
clean:
	rm -rf $(BUILD_DIR)
	$(MAKE) -C $(TEST_DIR) clean

.PHONY: clean

#--------------------------------------#
# Export variables for child Makefiles #
#--------------------------------------#
# Export variables for the other Makefiles to use
export BUILD_DIR
export ROOT_DIR
export SRC_OBJS
export FC
export FC_FLAGS
export LIBS

The tests/Makefile would then look like this…

PFUNIT_INCLUDE_DIR ?= $(ROOT_DIR)/../pfunit/build/installed/PFUNIT-4.12/include

# Don't try to include if we're cleaning as this doesn't depend on pFUnit
ifneq ($(MAKECMDGOALS),clean)
include $(PFUNIT_INCLUDE_DIR)/PFUNIT.mk
TEST_FLAGS = -I$(BUILD_DIR) $(FC_FLAGS) $(LIBS) $(PFUNIT_EXTRA_FFLAGS)
endif

# Define variables to be picked up by make_pfunit_test
tests_TESTS = \
  test_something.pf \
  test_something_else.pf
tests_OTHER_SOURCES = $(filter-out $(BUILD_DIR)/main.o, $(SRC_OBJS))
tests_OTHER_LIBRARIES = $(TEST_FLAGS)

# Triggers pre-processing and defines rule for building test executable
$(eval $(call make_pfunit_test,tests))

# Converts pre-processed test files into objects ready for building of the executable
%.o: %.F90
	$(FC) -c $(TEST_FLAGS) $<

clean:
	\rm -f *.o *.mod *.F90 *.inc tests

Key points:

  • We must include the pre-installed pFUnit dependencies and Makefile options via the PFUNIT.mk file.
    • The version of pFUnit that has been built will affect the path to this file (i.e. …/installed/PFUNIT-4.12/include/…)
  • We are utilising the function provided by pFUnit make_pfunit_test
    • This will create a target of the provided name (in this case tests)
    • We define the variables pFUnit requires to build the tests target as variables prefixed with tests_.
      • tests_TESTS - A list of the .pf test files to be pre-processed before compilation.
      • tests_OTHER_SOURCES - A list of src object files required for the tests (excluding the src main/program file)
      • tests_OTHER_LIBRARIES - A list of library flags to pass to the compiler when compiling the test code
  • We must create a target for compiling object files which uses the same flags as tests_OTHER_LIBRARIES

We can then build and run our tests with the following commands

SH

$ make tests
...
$ ./tests/tests --verbose
 

 Start: <test_something_suite.test_do_something_1>
.   end: <test_something_suite.test_do_something_1>
 

 Start: <test_something_else_suite.test_do_something_2>
.   end: <test_something_else_suite.test_do_something_2>

Time:         0.001 seconds
  
 OK
 (2 tests)

Naming our tests with Make

In the output shown above we have ran using the –verbose flag. This flag includes the name of our test suites and test subroutines in the output. For example, we have 2 tests which here indicates two test functions in total, test_do_something_1 and test_do_something_2. However, we can see that these two test functions are each stored within their own test suite test_something_suite and test_something_else_suite respectively.

Here, we are defining a test suite as a single test module file (.pf file). Therefore, we can see that the name of the test suite comes from the name of the module. The name of the test is then taken from the name of the test subroutine. For example, test_something.pf would look like this.

F90

module test_something
    use something, only : do_something
    use funit
    implicit none

contains

    @Test
    subroutine test_do_something_1()
        integer :: input, actual_output

        input = 1

        call do_something(input, actual_output)

        @assertEqual(2, actual_output, "Unexpected output from do_something")
    end subroutine test_do_something_1
end module test_something
Challenge

Challenge: Practice integrating with Make

To verify your newly implemented tests of temp_conversions from the previous episode, complete part i of the building-the-test section of 3-writing-your-first-unit-test/challenge and integrate your test(s) with the Make build system provided in the exercise.

A solution is provided in 3-writing-your-first-unit-test/solution.

Integrating pFUnit with CMake


Let’s now look at the steps required to add pFUnit tests to a project built using CMake. Similar to before, let’s assume we have the following file structure.

|-- ROOT_DIR/
    | CMakeLists.txt
    |-- src/
    |   |-- main.f90
    |   |__ ... Some module files containing src code
    |
    |-- tests/
        |-- CMakeLists.txt
        |-- test_something.pf
        |-- test_something_else.pf

Just like with Make, the top level CMakeLists.txt file is responsible for compiling the src code but should do very little regarding building the tests. However, it should…

  • Define a variable which stores a list of src files

    CMAKE

    set(SRC_DIR "${PROJECT_SOURCE_DIR}/src")
    set(PROJ_SRC_FILES 
      "${SRC_DIR}/main.f90"
      "${SRC_DIR}/something.f90"
    )
  • Enable testing.

    CMAKE

    enable_testing()
  • Add the tests/ dir as a subdirectory.

    CMAKE

    add_subdirectory("tests")

The full top level CMakeLists.txt may look something like this…

CMAKE

cmake_minimum_required(VERSION 3.9 FATAL_ERROR)

# Set project name
project(
  "something_interesting"
  LANGUAGES "Fortran"
  VERSION "0.0.1"
  DESCRIPTION "Doing something"
)

# Define a variable which stores a list of src files
set(SRC_DIR "${PROJECT_SOURCE_DIR}/src")
set(PROJ_SRC_FILES 
  "${SRC_DIR}/main.f90"
  "${SRC_DIR}/something.f90"
)

# Build src executables
add_executable("${PROJECT_NAME}" "${PROJ_SRC_FILES}")

# Enable testing.
enable_testing()

# Add the tests dir as a subdirectory.
add_subdirectory("tests")

The tests/CMakeLists.txt file would then look like this…

CMAKE

find_package(PFUNIT REQUIRED)

# Filter out the main.f90 file. We can only have one main() function in our tests
set(PROJ_SRC_FILES_EXEC_MAIN ${PROJ_SRC_FILES})
list(FILTER PROJ_SRC_FILES_EXEC_MAIN EXCLUDE REGEX ".*main.f90")

# Create library for src code
add_library (SUT STATIC ${PROJ_SRC_FILES_EXEC_MAIN})

# List all test files
set(test_srcs
  "${PROJECT_SOURCE_DIR}/tests/test_something.pf"
  "${PROJECT_SOURCE_DIR}/tests/test_something_else.pf"
)

# Add the test target
add_pfunit_ctest (test_something_interesting
  TEST_SOURCES ${test_srcs}
  LINK_LIBRARIES SUT # your application library
  )

Key points:

  • First, we find the pFUnit package to ensure the required libraries and cmake functions are available
  • We then filter the main.f90 program file from the list of src files.
  • We store the src files in a library (SUT, stands for system under test) to be referenced later.
  • We list the test .pf files we wish to include within test_srcs.
  • We then create a test with pFUnit and CTest using the function provided by pFUnit, add_pfunit_ctest. Here we are…
    • naming the test test_something_interesting.
    • informing pFUnit of the relevant src files via TEST_SOURCES.
    • linking to the src library via LINK_LIBRARIES.

Building with CMake

We can then build our tests with the following commands

SH

cmake -B build -DCMAKE_PREFIX_PATH=/path/to/pfunit/build/installed
cmake --build build
ctest --test-dir build # or ./build/tests/test_something_interesting
Callout

Mixing CTest and pFUnit

In this case we have called add_pfunit_ctest once with all of our .pf test files. This results in there being one CTest test (i.e. one executable ./build/tests/test_something) which runs all tests. However, it may be preferable to call add_pfunit_ctest more than once, thus creating multiple executables to further divide up your tests.

Note that the tests can still be filtered by calling the executable itself and using pFUnit’s inbuilt filtering option, like so.

SH

$ ./build/tests/test_something_interesting -f test_something_else -v
 

 Start: <test_something_else_suite.test_do_something_2>
.   end: <test_something_else_suite.test_do_something_2>

Time:         0.001 seconds
  
 OK
 (1 test)

Naming our tests with CMake

When we run our tests by directly calling the executable as shown above, we can see that the test suite names and test subroutine names are identical to when built using make. However, when using CMake we have control of one other name. The name of the CTest test. This name is set when we call add_pfunit_ctest. For example the below will create a test named test_something_interesting.

CMAKE

add_pfunit_ctest (test_something_interesting
  TEST_SOURCES ${test_srcs}
  LINK_LIBRARIES sut # your application library
  )
Challenge

Challenge: Practice integrating with CMake

To verify your newly implemented tests of temp_conversions from the previous episode, complete part ii of the building-the-test section of 3-writing-your-first-unit-test/challenge and integrate your test(s) with the CMake build system provided in the exercise.

A solution is provided in 3-writing-your-first-unit-test/solution.

Content from Testing parallel code


Last updated on 2025-12-05 | Edit this page

Overview

Questions

  • How do I unit test a procedure which makes MPI calls?
  • How do I easily test different numbers of MPI ranks?
  • How do I test a procedure which uses OMP directives?
  • How do I easily test different numbers of OMP threads?

Objectives

  • Understand what is different when testing parallel vs serial code.

What’s the difference?


Depending on the parallelisation tool and strategy employed, the implementation of parallel code can be very different to that of serial code. This is especially true for code which utilises the message passing interface (MPI). These codes almost always contain some functionality in which processes, or ranks, communicate by exchanging messages. This message passing is often complex and will always benefit from testing.

There is added complexity when testing MPI code compared to serial as the logical path through the code is changed depending on the number of ranks with which the code is executed. Therefore, it is important that we test for a range of numbers of ranks. This will require controlling the number of ranks running the src and is not something we want to implement ourselves. This limits the tools available to us. pFUnit is currently the only tool which supports testing MPI code. Therefore, we will be focusing on pFUnit for this section.

Tips for writing testable MPI code


Where possible, separate calls to the MPI library into units (subroutines or functions).

If a procedure does not contain any calls to the MPI library, then it can be tested with a serial unit test. Therefore, separating MPI calls into their own units makes for a simpler test suite for most of your logic. Only, procedures with MPI library calls will require the more complex parallel pFUnit tests.

Pass the MPI communicator information into each procedure to be tested.

If we pass the MPI communicator into a procedure, we can define this to be whatever we wish in our tests. This allows us to use the communicator provided by pFUnit or some other communicator specific to our problem.

Creating types to wrap this information along with any other MPI specific information (neighbour ranks, etc) can be a convenient approach.

## Syntax of writing MPI enabled pFUnit tests

Firstly, we must change how we define our test parameters:

  • We now use MPITestParameter instead of AbstractTestParameter.
    • MPITestParameter inherits from AbstractTestParameter and provides an additional parameter in its constructor which corresponds to the number of processors for which a particular test should be ran.
  • We can’t know for certain the rank of each process for the pFUnit communicator until the test case runs. Therefore, we now need to build arrays of input parameters with the rank of a process matching the index of the parameter array. For example, rank 0 would access index 1 of the input array during testing, rank 1 would access index 2 and so on. See below for an example.

F90

@testParameter(constructor=new_exchange_boundaries_test_params)
type, extends(MPITestParameter) :: my_test_params
    integer, allocatable :: input(:), expected_output(:)
contains
    procedure :: toString => my_test_params_toString
end type my_test_params

We therefore need to update how we populate our test parameters to take into account the rank indexing:

F90

function my_test_suite() result(params)
    type(my_test_params), allocatable :: params(:)
    integer, allocatable :: input(:), expected_output(:)
    integer, max_number_of_ranks

    max_number_of_ranks = 2
    allocate(params(max_number_of_ranks))
    allocate(input(max_number_of_ranks))
    allocate(expected_output(max_number_of_ranks))

    ! Tests with one rank
    input(1) = 1
    expected_output(1) = 2
    params(1) = my_test_params(1, input, expected_output)

    ! Tests with two ranks
    !     rank 0
    input(1) = 1
    expected_output(1) = 1
    !     rank 1
    input(2) = 1
    expected_output(2) = 1
    params(2) = my_test_params(2, input, expected_output)
end function my_test_suite

We also need to change how we define our test case:

  • We now use MPITestCase instead of ParameterizedTestCase
    • MPITestCase provides several helpful methods for us to use whilst testing
      • getProcessRank() returns the rank of the current process allowing per rank selection of inputs and expected outputs.
      • getMpiCommunicator() returns the MPI communicator created by pFUnit to control the number of ranks per test.
      • getNumProcesses() returns the number of MPI ranks for the current test.

F90

@TestCase(testParameters={my_test_suite()}, constructor=my_test_params_to_my_test_case)
type, extends(MPITestCase) :: my_test_case
    type(my_test_params) :: params
end type my_test_case

Finally, we ensure each process accesses the correct rank index parameters during the test

F90

@Test
subroutine TestMySrcProcedure(this)
    class (my_test_case), intent(inout) :: this

    integer :: actual_output, rank_index

    rank_index = this%getProcessRank() + 1

    call my_src_procedure(this%params%input(rank_index), actual_output)

    @assertEqual(this%params%expected_output(rank_index), actual_output, "Unexpected output from my_src_procedure")
end subroutine TestMySrcProcedure
Challenge

Challenge 1: Testing MPI parallel code

Take a look at 6-testing-parallel-code/challenge in the exercises repository.

A solution is provided in 6-testing-parallel-code/solution.