Integer value somehow becomes real after i call mod

function RandomRange(minimum, maximum)
    use :: cfunctions
    integer :: RandomRange
    integer :: minimum, maximum

    RandomRange = mod(c_rand() + minimum, maximum)
end function RandomRange

mod returns integer but somehow it becomes a real??

src/main.f90:101:53:

  101 |     NewAppleLocation = availablePositions(RandomRange(1, numberAvailable))
      |                                                     1
Error: Return type mismatch of function ‘randomrange’ at (1) (REAL(4)/INTEGER(4))
src/main.f90:101:42:

  101 |     NewAppleLocation = availablePositions(RandomRange(1, numberAvailable))
      |                                          1
Error: Legacy Extension: REAL array index at (1)
module cfunctions
   use, intrinsic :: iso_c_binding, only : c_int
   interface
      function c_rand() bind(c, name="rand")
         import c_int
         integer(c_int) c_rand
      end function c_rand
   end interface
end module cfunctions

this

Make sure all your functions are in a module, and put implicit none at the top of every module and program unit.

@yeti0904 , you know the long-standing Fortran joke, right!? “God is real unless declared integer”

See this thread below, with the teams I have worked with in industry I have seen some impressive and brilliant code attempts in Fortran by many bright minds who had arrived afresh to Fortran but whose works had to be absolutely sullied by the beyond-stupidity-for-21st-century, the-mind-numbing implicit none statements:

You have declared RandomRange as INTEGER in the function source code, but you probably did not declare its type in the place(s) where the function is used in other subprograms. If you do not use IMPLICIT NONE, the type of a variable or function of undeclared type whose first letter is (A-H, O-Z) is REAL, regardless of what type the declarations in other scopes made it to be.

The fortran mod() function is generic, it takes either integer or real arguments, and returns the corresponding integer or real value. As for the type of RandomRange(), that depends on how it is declared in the calling program. If it is real there, and declared as integer in the function body, then there is a mismatch. The compiler can sometimes catch this error, but sometimes not. Also, FWIW, this programmer error can occur either with or without implicit none, so the lack of that declaration might be a red herring.

managed to fix by declaring functions as variables in program/other functions, which left me with errors because i defined Vec2_t and Player_t twice inside of NewAppleLocation and program, so i moved them outside of both leaving me with lots of errors again

module cfunctions
   use, intrinsic :: iso_c_binding, only : c_int
   interface
      function c_rand() bind(c, name="rand")
         import c_int
         integer(c_int) c_rand
      end function c_rand
   end interface
end module cfunctions

subroutine IOHandle_Init()
    use, intrinsic :: iso_c_binding, only: c_null_char
    use :: m_ncurses
    implicit none

    integer :: rc

    stdscr = initscr()
    rc     = raw()
    rc     = nodelay(stdscr, true)
    rc     = keypad(stdscr, true)
    rc     = noecho()
    rc     = curs_set(0)
end subroutine IOHandle_Init

subroutine IOHandle_Quit()
    use, intrinsic :: iso_c_binding, only: c_null_char
    use :: m_ncurses
    implicit none
    
    integer :: rc
    rc = endwin()
end subroutine IOHandle_Quit

subroutine ClearScreen()
    use, intrinsic :: iso_c_binding, only: c_null_char
    use :: m_ncurses
    implicit none

    integer :: i, rc
    do i = 0, LINES - 1
        rc = mvhline(i, 0, ichar(' ', 8), COLS)
    end do
end subroutine ClearScreen

function RandomRange(minimum, maximum)
    use :: cfunctions
    implicit none
    integer :: RandomRange
    integer :: minimum, maximum

    integer :: ret
    ret = mod(c_rand() + minimum, maximum)

    RandomRange = ret
end function RandomRange

type Vec2_t
    integer :: x, y
end type
type Player_t
    type(Vec2_t)                            :: pos
    integer                                 :: direction
    type(Vec2_t), dimension(:), allocatable :: tail
end type

function NewAppleLocation(boardSize, player)
    use, intrinsic :: iso_c_binding, only : c_int
    use :: cfunctions
    implicit none
    type(Vec2_t) :: NewAppleLocation
    type(Player_t) :: player
    type(Vec2_t)   :: boardSize
    integer        :: i ! iterator
    integer        :: j ! iterator

    ! functions
    integer :: RandomRange
    logical :: valid

    type(Vec2_t), dimension(:), allocatable :: availablePositions
    type(Vec2_t) :: add
    integer      :: posIndex = 1

    ! generate an array of valid apple positions
    logical, dimension(boardSize%y, boardSize%x) :: available
    integer                                      :: numberAvailable
    integer                                      :: randomIndex
    numberAvailable = boardSize%y * boardSize%x
    do i = 1, boardSize%y
        do j = 1, boardSize%x
            available(i, j) = .true.
        end do
    end do
    do i = 1, size(player%tail) ! remove taken places
        available(player%tail(i)%y, player%tail(i)%x) = .false.
        numberAvailable                               = numberAvailable - 1
    end do
    available(player%pos%y, player%pos%x) = .false.
    allocate(availablePositions(numberAvailable))
    do i = 1, boardSize%y
        do j = 1, boardSize%x
            if (available(i, j)) then
                add%x                        = j
                add%y                        = i
                availablePositions(posIndex) = add
                posIndex                     = posIndex + 1
            end if
        end do
    end do

    randomIndex = RandomRange(1, numberAvailable)

    NewAppleLocation = availablePositions(randomIndex)
    deallocate(availablePositions)
end function NewAppleLocation

program snake
    use, intrinsic :: iso_c_binding, only: c_null_char
    use :: m_ncurses
    implicit none

    enum, bind(c)
        enumerator :: SnakeDirection_Up = 1
        enumerator :: SnakeDirection_Down
        enumerator :: SnakeDirection_Left
        enumerator :: SnakeDirection_Right
        enumerator :: SnakeDirection_None
    end enum

    integer             :: rc
    integer (kind = 16) :: input
    logical             :: run = .true.
    type(Player_t)      :: player
    integer             :: sleepTime = 100 ! 1000/10 ms (10fps)
    integer             :: i ! iterator
    type(Vec2_t)        :: boardSize
    integer             :: score = 0
    type(Vec2_t)        :: apple

    ! functions
    type(Vec2_t) :: NewAppleLocation

    player%pos%x     = 5
    player%pos%y     = 5
    player%direction = SnakeDirection_None
    allocate(player%tail(0))

    boardSize%x = 30
    boardSize%y = 15
    
    call IOHandle_Init
    apple = NewAppleLocation(boardSize, player)

    do while (run)
        ! handle input
        input = getch()
        select case (input)
            case (KEY_RIGHT)
                player%direction = SnakeDirection_Right
            case (KEY_LEFT)
                player%direction = SnakeDirection_Left
            case (KEY_UP)
                player%direction = SnakeDirection_Up
            case (KEY_DOWN)
                player%direction = SnakeDirection_Down
            case (ichar('q'))
                run = .false.
        end select

        ! update player
        select case (player%direction)
            case (SnakeDirection_Right)
                player%pos%x = player%pos%x + 1
            case (SnakeDirection_Left)
                player%pos%x = player%pos%x - 1
            case (SnakeDirection_Down)
                player%pos%y = player%pos%y + 1
            case (SnakeDirection_Up)
                player%pos%y = player%pos%y - 1
        end select

        ! render
        call ClearScreen
        do i = 0, boardSize%y
            rc = mvhline(i, 0, ichar('.', 8), boardSize%x)
        end do

        rc = attron(A_REVERSE);
        rc = mvaddch(player%pos%y, player%pos%x, ichar('#', 8))
        rc = attroff(A_REVERSE);

        rc = refresh()
        
        rc = napms(sleepTime)
    end do

    deallocate(player%tail)
    call IOHandle_Quit

    print *, "Your score was", score
end program snake

src/main.f90:67:1:

   67 | function NewAppleLocation(boardSize, player)
      | 1
Error: Unclassifiable statement at (1)
src/main.f90:68:49:

   61 | type Player_t
      |             2                                    
......
   68 |     use, intrinsic :: iso_c_binding, only : c_int
      |                                                 1
Error: USE statement at (1) cannot follow derived type declaration statement at (2)
src/main.f90:69:21:

   61 | type Player_t
      |             2        
......
   69 |     use :: cfunctions
      |                     1
Error: USE statement at (1) cannot follow derived type declaration statement at (2)
src/main.f90:70:17:

   61 | type Player_t
      |             2    
......
   70 |     implicit none
      |                 1
Error: IMPLICIT NONE statement at (1) cannot follow derived type declaration statement at (2)
src/main.f90:86:61:

   86 |     logical, dimension(boardSize%y, boardSize%x) :: available
      |                                                             1
Error: Explicit shaped array with nonconstant bounds at (1)
src/main.f90:116:3:

  116 | end function NewAppleLocation
      |   1
Error: Expecting END PROGRAM statement at (1)
src/main.f90:118:13:

  118 | program snake
      |             1
Error: Unexpected PROGRAM statement at (1)
src/main.f90:119:54:

  119 |     use, intrinsic :: iso_c_binding, only: c_null_char
      |                                                      1
Error: Unexpected USE statement at (1)
src/main.f90:120:20:

  120 |     use :: m_ncurses
      |                    1
Error: Unexpected USE statement at (1)
src/main.f90:121:17:

  121 |     implicit none
      |                 1
Error: Duplicate IMPLICIT NONE statement at (1)
src/main.f90:123:17:

  123 |     enum, bind(c)
      |                 1
Error: Unexpected ENUM DEFINITION statement at (1)
src/main.f90:124:23:

  124 |         enumerator :: SnakeDirection_Up = 1
      |                       1
Error: ENUM definition statement expected before (1)
src/main.f90:125:23:

  125 |         enumerator :: SnakeDirection_Down
      |                       1
Error: ENUM definition statement expected before (1)
src/main.f90:126:23:

  126 |         enumerator :: SnakeDirection_Left
      |                       1
Error: ENUM definition statement expected before (1)
src/main.f90:127:23:

  127 |         enumerator :: SnakeDirection_Right
      |                       1
Error: ENUM definition statement expected before (1)
src/main.f90:128:23:

  128 |         enumerator :: SnakeDirection_None
      |                       1
Error: ENUM definition statement expected before (1)
src/main.f90:129:7:

  129 |     end enum
      |       1
Error: Expecting END PROGRAM statement at (1)
src/main.f90:131:29:

  131 |     integer             :: rc
      |                             1
Error: Unexpected data declaration statement at (1)
src/main.f90:132:32:

  132 |     integer (kind = 16) :: input
      |                                1
Error: Unexpected data declaration statement at (1)
src/main.f90:133:39:

  133 |     logical             :: run = .true.
      |                                       1
Error: Unexpected data declaration statement at (1)
src/main.f90:134:33:

  134 |     type(Player_t)      :: player
      |                                 1
Error: Symbol ‘player’ at (1) already has basic type of DERIVED
src/main.f90:135:63:

  135 |     integer             :: sleepTime = 100 ! 1000/10 ms (10fps)
      |                                                               1
Error: Unexpected data declaration statement at (1)
src/main.f90:136:28:

  136 |     integer             :: i ! iterator
      |                            1
Error: Symbol ‘i’ at (1) already has basic type of INTEGER
src/main.f90:137:36:

  137 |     type(Vec2_t)        :: boardSize
      |                                    1
Error: Symbol ‘boardsize’ at (1) already has basic type of DERIVED
src/main.f90:138:36:

  138 |     integer             :: score = 0
      |                                    1
Error: Unexpected data declaration statement at (1)
src/main.f90:139:32:

  139 |     type(Vec2_t)        :: apple
      |                                1
Error: Unexpected data declaration statement at (1)
src/main.f90:142:36:

  142 |     type(Vec2_t) :: NewAppleLocation
      |                                    1
Error: Symbol ‘newapplelocation’ at (1) already has basic type of DERIVED
src/main.f90:160:55:

  160 |                 player%direction = SnakeDirection_Right
      |                                                       1
Error: Symbol ‘snakedirection_right’ at (1) has no IMPLICIT type
src/main.f90:174:47:

  174 |                 player%pos%x = player%pos%x + 1
      |                                               1
Error: Expected a CASE or END SELECT statement following SELECT CASE at (1)
src/main.f90:162:54:

  162 |                 player%direction = SnakeDirection_Left
      |                                                      1
Error: Symbol ‘snakedirection_left’ at (1) has no IMPLICIT type
src/main.f90:176:47:

  176 |                 player%pos%x = player%pos%x - 1
      |                                               1
Error: Expected a CASE or END SELECT statement following SELECT CASE at (1)
src/main.f90:166:54:

  166 |                 player%direction = SnakeDirection_Down
      |                                                      1
Error: Symbol ‘snakedirection_down’ at (1) has no IMPLICIT type
src/main.f90:178:47:

  178 |                 player%pos%y = player%pos%y + 1
      |                                               1
Error: Expected a CASE or END SELECT statement following SELECT CASE at (1)
src/main.f90:164:52:

  164 |                 player%direction = SnakeDirection_Up
      |                                                    1
Error: Symbol ‘snakedirection_up’ at (1) has no IMPLICIT type
src/main.f90:180:47:

  180 |                 player%pos%y = player%pos%y - 1
      |                                               1
Error: Expected a CASE or END SELECT statement following SELECT CASE at (1)
src/main.f90:202:17:

  202 | end program snake
      |                 1
Error: Expected label ‘vec2_t’ for END PROGRAM statement at (1)
f951: Error: Unexpected end of file in ‘src/main.f90’

No, you don’t need to declare functions as variables and you certainly should not have to declare anything twice. Put all the functions and types in a module. Then you use that module in your program. You can’t have type declaration outside of a module. You can have functions, but I do not recommend it. Put everything in a module and that will save you a lot of trouble.

thanks, i have no more errors now

Something like this:

module cfunctions
   use, intrinsic :: iso_c_binding, only : c_int
   implicit none
   interface
      function c_rand() bind(c, name="rand")
         import :: c_int
         integer(c_int) c_rand
      end function c_rand
   end interface
end module cfunctions


module my_module
    use, intrinsic :: iso_c_binding 
    use :: m_ncurses
    use :: cfunctions

    implicit none 

    type Vec2_t
        integer :: x, y
    end type
    
    type Player_t
        type(Vec2_t)                            :: pos
        integer                                 :: direction
        type(Vec2_t), dimension(:), allocatable :: tail
    end type
    
    contains 

    subroutine IOHandle_Init()

        integer :: rc

        stdscr = initscr()
        rc     = raw()
        rc     = nodelay(stdscr, true)
        rc     = keypad(stdscr, true)
        rc     = noecho()
        rc     = curs_set(0)
    end subroutine IOHandle_Init

    subroutine IOHandle_Quit()
        
        integer :: rc
        rc = endwin()
    end subroutine IOHandle_Quit

    subroutine ClearScreen()

        integer :: i, rc
        do i = 0, LINES - 1
            rc = mvhline(i, 0, ichar(' ', 8), COLS)
        end do
    end subroutine ClearScreen

    function RandomRange(minimum, maximum)
        integer :: RandomRange
        integer :: minimum, maximum

        integer :: ret
        ret = mod(c_rand() + minimum, maximum)

        RandomRange = ret
    end function RandomRange

    function NewAppleLocation(boardSize, player)
        type(Vec2_t) :: NewAppleLocation
        type(Player_t) :: player
        type(Vec2_t)   :: boardSize
        integer        :: i ! iterator
        integer        :: j ! iterator

        type(Vec2_t), dimension(:), allocatable :: availablePositions
        type(Vec2_t) :: add
        integer      :: posIndex = 1

        ! generate an array of valid apple positions
        logical, dimension(boardSize%y, boardSize%x) :: available
        integer                                      :: numberAvailable
        integer                                      :: randomIndex
        numberAvailable = boardSize%y * boardSize%x
        do i = 1, boardSize%y
            do j = 1, boardSize%x
                available(i, j) = .true.
            end do
        end do
        do i = 1, size(player%tail) ! remove taken places
            available(player%tail(i)%y, player%tail(i)%x) = .false.
            numberAvailable                               = numberAvailable - 1
        end do
        available(player%pos%y, player%pos%x) = .false.
        allocate(availablePositions(numberAvailable))
        do i = 1, boardSize%y
            do j = 1, boardSize%x
                if (available(i, j)) then
                    add%x                        = j
                    add%y                        = i
                    availablePositions(posIndex) = add
                    posIndex                     = posIndex + 1
                end if
            end do
        end do

        randomIndex = RandomRange(1, numberAvailable)

        NewAppleLocation = availablePositions(randomIndex)
        deallocate(availablePositions)
    end function NewAppleLocation

end module my_module

program snake

    use my_module

    enum, bind(c)
        enumerator :: SnakeDirection_Up = 1
        enumerator :: SnakeDirection_Down
        enumerator :: SnakeDirection_Left
        enumerator :: SnakeDirection_Right
        enumerator :: SnakeDirection_None
    end enum

    integer             :: rc
    integer (kind = 16) :: input
    logical             :: run = .true.
    type(Player_t)      :: player
    integer             :: sleepTime = 100 ! 1000/10 ms (10fps)
    integer             :: i ! iterator
    type(Vec2_t)        :: boardSize
    integer             :: score = 0
    type(Vec2_t)        :: apple

    player%pos%x     = 5
    player%pos%y     = 5
    player%direction = SnakeDirection_None
    allocate(player%tail(0))

    boardSize%x = 30
    boardSize%y = 15
    
    call IOHandle_Init
    apple = NewAppleLocation(boardSize, player)

    do while (run)
        ! handle input
        input = getch()
        select case (input)
            case (KEY_RIGHT)
                player%direction = SnakeDirection_Right
            case (KEY_LEFT)
                player%direction = SnakeDirection_Left
            case (KEY_UP)
                player%direction = SnakeDirection_Up
            case (KEY_DOWN)
                player%direction = SnakeDirection_Down
            case (ichar('q'))
                run = .false.
        end select

        ! update player
        select case (player%direction)
            case (SnakeDirection_Right)
                player%pos%x = player%pos%x + 1
            case (SnakeDirection_Left)
                player%pos%x = player%pos%x - 1
            case (SnakeDirection_Down)
                player%pos%y = player%pos%y + 1
            case (SnakeDirection_Up)
                player%pos%y = player%pos%y - 1
        end select

        ! render
        call ClearScreen
        do i = 0, boardSize%y
            rc = mvhline(i, 0, ichar('.', 8), boardSize%x)
        end do

        rc = attron(A_REVERSE);
        rc = mvaddch(player%pos%y, player%pos%x, ichar('#', 8))
        rc = attroff(A_REVERSE);

        rc = refresh()
        
        rc = napms(sleepTime)
    end do

    deallocate(player%tail)
    call IOHandle_Quit

    print *, "Your score was", score
end program snake

This doesn’t compile since there are undeclared variables and I don’t think you have given us all the code…but this is the idea.

Also: each module and program unit should be in a separate file.

what i sent was all the code, it was all in 1 file
im not sure how fortran code in multiple files works, do i just compile all of them together like gfortran src/*.f90 and they work together?

Don’t do that or the compiler will complain that you have 2 or more main programs, unless your src/*f90 really contains only one. Just list the f90 files with the current main program and whatever modules etc that must be linked to it.

im still really confused on how to use multiple source files

If for example your program is in file a.f90 possibly with some external subroutines/functions and
modules and it also uses modules b.f90 and c.f90 then you could compile it with
gfortran a.f90 b.f90 c.f90
if you have successfully installed gfortran, and if a.f90, b.f90 and c.f90 are each bug-free. To test whether you have installed gfortran try the command
gfortran -v
which should produce several lines of output telling you which version of gfortran you have used.

thanks, i have managed to make a rewrite with more than 1 source file