module captain_db use sqlite implicit none integer, parameter::PLAYER_NAME_LENGTH = 128 character(1024)::database_file type(c_ptr)::db contains subroutine initialize_db(filename) use logging implicit none character(*), intent(in)::filename logical::exists inquire(file=filename, exist=exists) if(.not. exists) then call write_log("Database does not exist, exiting") call shutdown() stop end if if(sqlite3_open(filename, db) == SQLITE_OK) then database_file = filename else Print *, "ERROR: Could not open db" stop end if end subroutine initialize_db subroutine shutdown_db() implicit none integer::i i = sqlite3_close(db) end subroutine shutdown_db subroutine add_player_db(name, token) implicit none character(*), intent(in)::name character(*), intent(in), optional::token type(sqlite3_stmt)::stmt character(64)::my_token if(present(token)) then my_token = token else my_token = "None" end if if(stmt%prepare(db, "INSERT INTO players(name, token) VALUES(?, ?)") == SQLITE_OK) then if(stmt%bind_text(1, name) == SQLITE_OK .and. stmt%bind_text(2, my_token) == SQLITE_OK) then call stmt%step_now() end if end if call stmt%finalize() end subroutine add_player_db subroutine update_player_token_db(name, token) implicit none character(*), intent(in)::name character(*), intent(in)::token type(sqlite3_stmt)::stmt if(stmt%prepare(db, "UPDATE players SET token=? WHERE name=?") == SQLITE_OK) then if(stmt%bind_text(2, name) == SQLITE_OK .and. stmt%bind_text(1, token) == SQLITE_OK) then call stmt%step_now() end if end if call stmt%finalize() end subroutine update_player_token_db subroutine remove_player_db(name) implicit none character(*), intent(in)::name type(sqlite3_stmt)::stmt if(stmt%prepare(db, "DELETE FROM players WHERE name=?") == SQLITE_OK) then if(stmt%bind_text(1, name) == SQLITE_OK) then call stmt%step_now() end if end if call stmt%finalize() end subroutine remove_player_db function get_player_count() implicit none type(sqlite3_stmt)::stmt integer::get_player_count get_player_count = 0 if(stmt%prepare(db, "SELECT COUNT(*) FROM players") == SQLITE_OK) then if(stmt%step() == SQLITE_ROW) then get_player_count = stmt%column_int(0) end if end if call stmt%finalize() end function get_player_count function get_player_names() result(res) implicit none type(sqlite3_stmt)::stmt character(len=PLAYER_NAME_LENGTH), dimension(:), pointer::res integer::i,n n = get_player_count() if(n > 0) then allocate(res(n)) if(stmt%prepare(db, "SELECT name FROM players ORDER BY name") == SQLITE_OK) then i = 1 do while(stmt%step() == SQLITE_ROW .and. i <= n) call stmt%column_text(0, res(i)) i = i + 1 end do end if call stmt%finalize() end if end function get_player_names end module captain_db