Floating point exception

module Util
    use, intrinsic :: iso_c_binding, only : c_int
    interface
        function Util_Rand() bind(c, name = "rand")
            import c_int
            integer(c_int) :: Util_Rand
        end function Util_Rand
        subroutine Util_SeedRand(seed) bind(c, name = "srand")
            import c_int
            integer(c_int) :: seed
        end subroutine Util_SeedRand
    end interface
    contains
    function Util_RandomRange(minimum, maximum)
        integer :: Util_RandomRange
        integer :: minimum, maximum
        integer :: randReturn

        randReturn = Util_Rand()
        Util_RandomRange = mod(randReturn + minimum, maximum)
    end function Util_RandomRange
end module Util

at line 20:

Util_RandomRange = mod(randReturn + minimum, maximum)

there is a floating point exception error

Program received signal SIGFPE: Floating-point exception - erroneous arithmetic operation.

Backtrace for this error:
#0  0x7ffaa6e519ff in ???
#1  0x55a77658b530 in __util_MOD_util_randomrange
        at src/util.f90:20
#2  0x55a77658b9e7 in __minefield_MOD_minefield_init
        at src/minefield.f90:32
#3  0x55a77658bee7 in ygms
        at src/main.f90:14
#4  0x55a77658bf6e in main
        at src/main.f90:3

Hello,

Could you give a minimal reproducible example (.i.e. the smallest possible piece of code that can be compiled and run) where it fails? And which command line you used to compile?

I compiled it with gfortran and just repeatedly call Util_RandomRange() with random integers, and couldn’t see a single error. And a floating point error in a code that involves only integers looks quite strange.

module Minefield
    ! modules
    use            :: Util
    use, intrinsic :: iso_c_binding

    ! types
    implicit none
    type :: Vec2_t
        integer :: x, y
    end type
    type :: Minefield_Tile_t
        logical :: mine
        integer :: around
        logical :: covered
    end type 

    ! variables
    type(Minefield_Tile_t), dimension(:, :), allocatable :: Minefield_array
    type(Vec2_t)                                         :: Minefield_boardSize

    ! functions
    contains
    subroutine Minefield_Init()
        integer      :: i, j ! iterator
        integer      :: number
        integer      :: mineX
        integer      :: mineY

        allocate(Minefield_array(Minefield_boardSize%y, Minefield_boardSize%x))

        ! randomly place mines
        do i = 0, 10
            mineX = Util_RandomRange(1, Minefield_boardSize%x)
            mineY = Util_RandomRange(1, Minefield_boardSize%y)

            Minefield_array(mineX, mineY)%mine = .true.
        end do

        ! calculate numbers
        do i = 1, Minefield_boardSize%x
            do j = 1, Minefield_boardSize%y
                number = 0
                Minefield_array(i, j)%around  = 0
                Minefield_array(i, j)%covered = .true.
                if (.not. Minefield_array(i, j)%mine) then
                    if ((i > 1) .and. (Minefield_array(i - 1, j)%mine)) then
                        number = number + 1
                    end if
                    if ((i < Minefield_boardSize%x) .and. (Minefield_array(i + 1, j)%mine)) then
                        number = number + 1
                    end if
                    if ((j > 1) .and. (Minefield_array(i, j - 1)%mine)) then
                        number = number + 1
                    end if
                    if ((j < Minefield_boardSize%y) .and. (Minefield_array(i, j + 1)%mine)) then
                        number = number + 1
                    end if
                    ! diagonal
                    if ( &
                        (i > 1) .and. (j > 1) .and. &
                        (Minefield_array(i - 1, j - 1)%mine) &
                    ) then
                        number = number + 1
                    end if
                    if ( &
                        (i > 1) .and. (j < Minefield_boardSize%y) .and. &
                        (Minefield_array(i - 1, j + 1)%mine) &
                    ) then
                        number = number + 1
                    end if
                    if ( &
                        (i < Minefield_boardSize%x) .and. (j > 1) .and. &
                        (Minefield_array(i + 1, j - 1)%mine) &
                    ) then
                        number = number + 1
                    end if
                    if ( &
                        (i < Minefield_boardSize%x) .and. (j < Minefield_boardSize%y) .and. &
                        (Minefield_array(i + 1, j + 1)%mine) &
                    ) then
                        number = number + 1
                    end if
                end if

                Minefield_array(i, j)%around = 0
            end do
        end do
    end subroutine Minefield_Init
end module Minefield

this is the module that contains the function that calls Util_RandomRange, so to run it i guess you just do

program main
    using :: Minefield
    call Minefield_Init
end program main

In Minefield_Init() , Minefield_boardSize is not initialized before you use it. Ultimately you are doing mod(0,0), which is illegal.

2 Likes

thanks, it doesn’t crash now