Fpm test with veggies and mpi

Hi,

When I run the the following commands

cart test/main.f90 test/mumps_test.f90
fpm test --flag '-I/usr/include' --runner-args=' -np 3'

I get this error

 + which mpiexec
mumpsSolver.f90                        done.
debug_test.f90                         done.
mumps_test.f90                         done.
libmumps2.a                            done.
main.f90                               done.
main.f90                               done.
mumps2                                 done.
mumps2-test                            done.
check                                  done.
[100%] Project compiled successfully.
Running Tests

Test that
    mumps tests
        check_mumps

A total of 1 test cases

 Unrecoverable Error in DMUMPS initialization:  MPI is not running.
 ERROR RETURN:   mumps_par%INFOG(1)=    -23  mumps_par%INFOG(2)=         0
Running Tests
Failed
Took 2.24538e-4 seconds

Test that
    mumps tests
        check_mumps
            Expected
                    |[20.0, 24.0, 9.0, 6.0, 13.0]|
                to be within |±1.0e-14| of
                    |[1.0, 2.0, 3.0, 4.0, 5.0]|
                User Message:
                    |rhs|

1 of 1 cases failed
1 of 1 assertions failed

STOP 1

Test that
    mumps tests
        check_mumps

A total of 1 test cases

 Unrecoverable Error in DMUMPS initialization:  MPI is not running.
 ERROR RETURN:   mumps_par%INFOG(1)=    -23  mumps_par%INFOG(2)=         0
Failed
Took 3.18546e-4 seconds

Test that
    mumps tests
        check_mumps
            Expected
                    |[20.0, 24.0, 9.0, 6.0, 13.0]|
                to be within |±1.0e-14| of
                    |[1.0, 2.0, 3.0, 4.0, 5.0]|
                User Message:
                    |rhs|

1 of 1 cases failed
1 of 1 assertions failed

STOP 1
--------------------------------------------------------------------------
Primary job  terminated normally, but 1 process returned
a non-zero exit code. Per user-direction, the job has been aborted.
--------------------------------------------------------------------------
Running Tests

Test that
    mumps tests
        check_mumps

A total of 1 test cases

 Unrecoverable Error in DMUMPS initialization:  MPI is not running.
 ERROR RETURN:   mumps_par%INFOG(1)=    -23  mumps_par%INFOG(2)=         0
Failed
Took 2.09794e-4 seconds

Test that
    mumps tests
        check_mumps
            Expected
                    |[20.0, 24.0, 9.0, 6.0, 13.0]|
                to be within |±1.0e-14| of
                    |[1.0, 2.0, 3.0, 4.0, 5.0]|
                User Message:
                    |rhs|

1 of 1 cases failed
1 of 1 assertions failed

STOP 1
 Put some tests in here!
 Put some tests in here!
 Put some tests in here!
<ERROR> Execution for object " mumps2-test " returned exit code  1
<ERROR> *cmd_run*:stopping due to failed executions
STOP 1

My code is the following:

test/mumps_test.f90

module mumps_test
   use veggies, only: result_t, test_item_t, assert_equals_within_absolute, describe, it
   use lapackPrecision, only: dp

   implicit none

   private
   public :: test_mumps

contains

   function test_mumps() result(tests)
      type(test_item_t) :: tests

      tests = describe(&
         "mumps tests", [&
         it("check_mumps", check_mumps) &
         ])
   end function test_mumps

   function check_mumps() result(rslt)
      use mumpsSolver, only: solve
      type(result_t) :: rslt

      integer                 :: n
      integer                 :: nnz

      integer, allocatable    :: irn(:) ! list of row numbers for non-zero matrix entries
      integer, allocatable    :: jcn(:) ! list of column numbers for non-zero matrix entries
      real(dp), allocatable   :: A(:)
      real(dp), allocatable   :: rhs(:)
      real(dp), allocatable   :: sol(:)

      n = 5
      nnz = 12

      allocate(irn(nnz))
      irn = [1,2,4,5,2,1,5,3,2,3,1,3]

      allocate(jcn(nnz))
      jcn = [2,3,3,5,1,1,2,4,5,2,3,3]

      allocate(a(nnz))
      a = [3._dp,-3._dp,2._dp,1._dp,3._dp,2._dp,4._dp,2._dp,6._dp,-1._dp,4._dp,1._dp]

      allocate(rhs(n))
      rhs = [20._dp,24._dp,9._dp,6._dp,13._dp]

      allocate(sol(n))
      sol = [1._dp, 2._dp, 3._dp, 4._dp, 5._dp]

      call solve(n, nnz, irn, jcn, A, rhs)

      rslt = assert_equals_within_absolute(sol, rhs, 1.e-14_dp,"rhs")

   end function check_mumps
end module mumps_test

src/mumpsSolver.f90

module mumpsSolver
   use lapackPrecision, only: dp
   implicit none
   private
   public :: solve

contains
   subroutine solve(n, nnz, irn, jcn, A, rhs)
      use iso_fortran_env, only: stdout=>output_unit
      use mpi_f08, only: MPI_COMM_WORLD

      IMPLICIT NONE
      INCLUDE 'dmumps_struc.h'

      type(dmumps_struc)                     :: mumps_par
      integer                                :: i
      integer, intent(in)                    :: n
      integer, intent(in)                    :: nnz
      integer, allocatable, intent(in)       :: irn(:) ! list of row numbers for non-zero matrix entries
      integer, allocatable, intent(in)       :: jcn(:) ! list of column numbers for non-zero matrix entries
      real(dp), allocatable, intent(in)      :: A(:)
      real(dp), allocatable, intent(inout)   :: rhs(:)

      mumps_par%COMM = MPI_COMM_WORLD%MPI_VAL

      mumps_par%JOB = -1 ! initialize mumps instance
      mumps_par%SYM = 0 ! A is unsymmetric
      mumps_par%PAR = 1 ! host processor also invoved in factorization and computation phase

      CALL DMUMPS(mumps_par)

      IF (mumps_par%INFOG(1) < 0) THEN ! if init failed
         WRITE(stdout,'(A,A,I6,A,I9)') " ERROR RETURN: ",&
            "  mumps_par%INFOG(1)= ", mumps_par%INFOG(1),&
            "  mumps_par%INFOG(2)= ", mumps_par%INFOG(2)
      else ! if init succeeded
         IF (mumps_par%MYID == 0) THEN
            mumps_par%n = n
            mumps_par%nnz = nnz
            allocate(mumps_par%irn, source=irn)
            allocate(mumps_par%jcn, source=jcn)
            allocate(mumps_par%a, source=a)
            allocate(mumps_par%rhs, source=rhs)
         END IF

         mumps_par%icntl(1:4) = -1 ! suppress solver output
         mumps_par%JOB = 6 ! perform job 1 (analysis), 2 (factorization) and 3 (computation)
         CALL DMUMPS(mumps_par)

         IF (mumps_par%INFOG(1) < 0) THEN ! if solve failed
            WRITE(stdout,'(A,A,I6,A,I9)') " ERROR RETURN: ",&
               "  mumps_par%INFOG(1)= ", mumps_par%INFOG(1),&
               "  mumps_par%INFOG(2)= ", mumps_par%INFOG(2)
         else ! if solve succeeded
            IF (mumps_par%MYID == 0) THEN
               WRITE(stdout,*) 'Solution is ',(mumps_par%RHS(i),i=1,mumps_par%N)
               rhs = mumps_par%rhs
            END IF

            mumps_par%JOB = -2 ! terminate mumps instance
            CALL DMUMPS(mumps_par)
            IF (mumps_par%INFOG(1) < 0) THEN ! if terminate failed
               WRITE(stdout,'(A,A,I6,A,I9)') " ERROR RETURN: ",&
                  "  mumps_par%INFOG(1)= ", mumps_par%INFOG(1),&
                  "  mumps_par%INFOG(2)= ", mumps_par%INFOG(2)
            END IF
         END IF
      END IF
   end subroutine solve
end module mumpsSolver

src/lapackPrecision.f90

Module lapackPrecision
   implicit none
   private

   public:: dp, sp

   integer, parameter :: dp = kind(0.0D0)
   integer, parameter :: sp = kind(0.0)
end module lapackPrecision

fpm.toml

name = "mumps2"
version = "0.1.0"
license = "license"
author = "Jane Doe"
maintainer = "jane.doe@example.com"
copyright = "Copyright 2025, Jane Doe"

[build]
auto-executables = true
auto-tests = true
auto-examples = true
module-naming = false
link = ["dmumps"]

[install]
library = false
test = false

[fortran]
implicit-typing = true
implicit-external = true
source-form = "free"

[dependencies]
mpi = "*"
rojff = { git = "https://gitlab.com/everythingfunctional/rojff.git", tag = "v1.0.1" }
[dev-dependencies]
veggies = { git = "https://gitlab.com/everythingfunctional/veggies.git", tag = "v1.0.0" }

On ubuntu 24.10 I got the mumps library like so

sudo apt install libmumps-headers-dev libmumps-dev

When I run the core of the code within my main program it works with veggies. However when I do ‘cart’ and ‘fpm test’ I get unstuck.

Any advice as to how to get fpm test with veggies working?

To start answering my own question.

I changed test/main.f90, which gets generated by cart, by adding calls to MPI_INIT() and MPI_FINALIZE() like so

! Generated by cart. DO NOT EDIT
program main
   use mpi_f08, only: MPI_INIT, MPI_FINALIZE
   implicit none

   integer                       :: ierr
   CALL MPI_INIT(ierr)
   if (.not.run()) stop 1
   CALL MPI_FINALIZE(IERR)

contains
   function run() result(passed)
      use mumps_test, only: &
         mumps_mumps => &
         test_mumps
      use veggies, only: test_item_t, test_that, run_tests



      logical :: passed

      type(test_item_t) :: tests
      type(test_item_t) :: individual_tests(1)

      individual_tests(1) = mumps_mumps()
      tests = test_that(individual_tests)


      passed = run_tests(tests)

   end function
end program

Now one of my processes runs a sucessful test with

fpm test --flag '-I/usr/include' --runner-args=' -np 3'

How should I go about suppressing the other processes from running the test suite?

 + which mpiexec
main.f90                               done.
mumps2-test                            done.
[100%] Project compiled successfully.
Running Tests

Running Tests

Test that
    mumps tests
        check_mumps

A total of 1 test cases

Test that
    mumps tests
        check_mumps

A total of 1 test cases

Running Tests

Test that
    mumps tests
        check_mumps

A total of 1 test cases

 Solution is   0.99999999999999856        1.9999999999999998        2.9999999999999996        3.9999999999999996        5.0000000000000018     
All Passed
Took 5.78793e-2 seconds

A total of 1 test cases containing a total of 1 assertions

Failed
Took 5.88298e-2 seconds

Test that
    mumps tests
        check_mumps
            Expected
                    |[20.0, 24.0, 9.0, 6.0, 13.0]|
                to be within |±1.0e-14| of
                    |[1.0, 2.0, 3.0, 4.0, 5.0]|
                User Message:
                    |rhs|
Failed
Took 5.95095e-2 seconds

Test that
    mumps tests
        check_mumps
            Expected
                    |[20.0, 24.0, 9.0, 6.0, 13.0]|
                to be within |±1.0e-14| of
                    |[1.0, 2.0, 3.0, 4.0, 5.0]|
                User Message:
                    |rhs|

1 of 1 cases failed
1 of 1 assertions failed

STOP 1

1 of 1 cases failed
1 of 1 assertions failed

STOP 1
--------------------------------------------------------------------------
Primary job  terminated normally, but 1 process returned
a non-zero exit code. Per user-direction, the job has been aborted.
--------------------------------------------------------------------------
--------------------------------------------------------------------------
mpiexec detected that one or more processes exited with non-zero status, thus causing
the job to be terminated. The first process to do so was:

  Process name: [[11895,1],2]
  Exit code:    1
--------------------------------------------------------------------------
<ERROR> Execution for object " mumps2-test " returned exit code  1
<ERROR> *cmd_run*:stopping due to failed executions
STOP 1

Hi @ggerber,

thank you for sharing some of your code - I’ve cooked an MWE for your configuration (without MUMPS dependency) and I get

federico@Federicos-MBP mpi_test % fpm test --verbose --runner-args=' -np 3'

\+ which mpiexec

[...]

<INFO> INCLUDE DIRECTORIES:  
\[100%\] Project compiled successfully.

\+ /opt/homebrew/bin//mpiexec  -np 3 build/gfortran_BB27EC4546BE1CC9/test/mumps2-test

Running Tests

So as you see, the MPI runner seems to be picked correctly.

My understanding is you’re trying to run a simple test solve on an MPI code (MUMPS) that should be run on 1 CPU only, because it’s tiny (like, 5 equations).

In this case, you should pass MPI_COMM_SELF to the subroutine, instead of MPI_COMM_WORLD. So the solver will only run on the local CPU, without attempting to communicate with others.

Then in the driver, you may want to restrict the runner program to the master rank only:

call MPI_COMM_RANK(COMM, rank, ierr)
if (rank==0) then 
   ! on master node
endif

but don’t forget to sync the error codes from all images after execution.

Thank you! It works.

Not sure how to sync the error codes. but will investigate.

1 Like