module captain_db use sqlite implicit none integer, parameter::PLAYER_NAME_LENGTH = 128 integer, parameter::FILENAME_NAME_LENGTH = 1024 integer, parameter::JOB_STATUS_SUCCESS = 1 integer, parameter::JOB_STATUS_FAILURE = 2 integer, parameter::JOB_STATUS_WORKING = 3 integer, parameter::PLAYER_STATUS_BUSY = JOB_STATUS_WORKING integer, parameter::PLAYER_STATUS_IDLE = 100 character(1024)::database_file type(c_ptr)::db type :: job integer::id integer::instruction integer::player integer::status character(32)::time end type interface is_player_busy module procedure is_player_busy_by_id module procedure is_player_busy_by_name end interface is_player_busy 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 function get_instuctions_count() implicit none type(sqlite3_stmt)::stmt integer::get_instuctions_count get_instuctions_count = 0 if(stmt%prepare(db, "SELECT COUNT(*) FROM instructions") == SQLITE_OK) then if(stmt%step() == SQLITE_ROW) then get_instuctions_count = stmt%column_int(0) end if end if call stmt%finalize() end function get_instuctions_count function get_instruction_names() result(res) implicit none type(sqlite3_stmt)::stmt character(len=PLAYER_NAME_LENGTH), dimension(:), pointer::res integer::i,n n = get_instuctions_count() if(n > 0) then allocate(res(n)) if(stmt%prepare(db, "SELECT name FROM instructions 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_instruction_names function get_jobs_count() implicit none type(sqlite3_stmt)::stmt integer::get_jobs_count get_jobs_count = 0 if(stmt%prepare(db, "SELECT COUNT(*) FROM jobs") == SQLITE_OK) then if(stmt%step() == SQLITE_ROW) then get_jobs_count = stmt%column_int(0) end if end if call stmt%finalize() end function get_jobs_count subroutine get_player_name(id, str) implicit none integer, intent(in)::id character(*), intent(out)::str type(sqlite3_stmt)::stmt str = " " if(stmt%prepare(db, "SELECT name FROM players WHERE id=?") == SQLITE_OK) then if(stmt%bind_int(1, id) == SQLITE_OK) then if(stmt%step() == SQLITE_ROW) then call stmt%column_text(0,str) end if end if end if call stmt%finalize() end subroutine get_player_name function get_player_id(name) implicit none integer::get_player_id character(*), intent(in)::name type(sqlite3_stmt)::stmt get_player_id = -1 if(stmt%prepare(db, "SELECT id FROM players WHERE name=?") == SQLITE_OK) then if(stmt%bind_text(1, name) == SQLITE_OK) then if(stmt%step() == SQLITE_ROW) then get_player_id = stmt%column_int(0) end if end if end if call stmt%finalize() end function get_player_id subroutine get_instruction_name(id, str) implicit none integer, intent(in)::id character(*), intent(out)::str type(sqlite3_stmt)::stmt str = " " if(stmt%prepare(db, "SELECT name FROM instructions WHERE id=?") == SQLITE_OK) then if(stmt%bind_int(1, id) == SQLITE_OK) then if(stmt%step() == SQLITE_ROW) then call stmt%column_text(0,str) end if end if end if call stmt%finalize() end subroutine get_instruction_name function get_instruction_id(name) implicit none integer::get_instruction_id character(*), intent(in)::name type(sqlite3_stmt)::stmt get_instruction_id = -1 if(stmt%prepare(db, "SELECT id FROM instructions WHERE name=?") == SQLITE_OK) then if(stmt%bind_text(1, name) == SQLITE_OK) then if(stmt%step() == SQLITE_ROW) then get_instruction_id = stmt%column_int(0) end if end if end if call stmt%finalize() end function get_instruction_id function get_jobs() result(jobs) implicit none type(job), dimension(:), pointer::jobs type(sqlite3_stmt)::stmt integer::i, n n = get_jobs_count() jobs => null() if(n > 0) then allocate(jobs(n)) if(stmt%prepare(db, "SELECT id,instruction,player,status,time FROM jobs ORDER BY id DESC") == SQLITE_OK) then i = 1 do while(stmt%step() == SQLITE_ROW .and. i <= n) jobs(i)%id = stmt%column_int(0) jobs(i)%instruction = stmt%column_int(1) jobs(i)%player = stmt%column_int(2) jobs(i)%status = stmt%column_int(3) call stmt%column_text(4, jobs(i)%time) i = i + 1 end do end if call stmt%finalize() end if end function get_jobs function get_jobs_for_instruction(id) result(jobs) implicit none type(job), dimension(:), pointer::jobs integer, intent(in)::id type(sqlite3_stmt)::stmt integer::n, i jobs => null() n = 0 if(stmt%prepare(db, "SELECT COUNT(*) FROM jobs WHERE instruction=?") == SQLITE_OK) then if(stmt%bind_int(1, id) == SQLITE_OK) then if(stmt%step() == SQLITE_ROW) then n = stmt%column_int(0) end if end if end if call stmt%finalize() if(n > 0) then allocate(jobs(n)) if(stmt%prepare(db, & "SELECT id,player,status,time FROM jobs WHERE instruction=? ORDER BY id DESC") & == SQLITE_OK) then if(stmt%bind_int(1, id) == SQLITE_OK) then i = 1 do while(stmt%step() == SQLITE_ROW .and. i <= n) jobs(i)%id = stmt%column_int(0) jobs(i)%instruction = id jobs(i)%player = stmt%column_int(1) jobs(i)%status = stmt%column_int(2) call stmt%column_text(3, jobs(i)%time) i = i + 1 end do end if end if call stmt%finalize() end if end function get_jobs_for_instruction function is_player_busy_by_id(id) implicit none logical::is_player_busy_by_id integer, intent(in)::id type(sqlite3_stmt)::stmt is_player_busy_by_id = .false. if(stmt%prepare(db, "SELECT COUNT(*) FROM jobs WHERE player=? AND status=?") == SQLITE_OK) then if(stmt%bind_int(1, id) == SQLITE_OK .and. stmt%bind_int(2, JOB_STATUS_WORKING) == SQLITE_OK) then if(stmt%step() == SQLITE_ROW) then is_player_busy_by_id = (stmt%column_int(0) > 0) end if end if end if call stmt%finalize() end function is_player_busy_by_id function is_player_busy_by_name(name) implicit none logical::is_player_busy_by_name character(*), intent(in)::name integer::id is_player_busy_by_name = .false. id = get_player_id(name) is_player_busy_by_name = is_player_busy_by_id(id) end function is_player_busy_by_name function get_instruction_players(id) result(res) implicit none integer, dimension(:), pointer::res integer, intent(in)::id type(sqlite3_stmt)::stmt integer::n, i res => null() if(stmt%prepare(db, "SELECT COUNT(*) FROM available WHERE instruction=?") == SQLITE_OK) then if(stmt%bind_int(1, id) == SQLITE_OK) then if(stmt%step() == SQLITE_ROW) then n = stmt%column_int(0) end if end if end if call stmt%finalize() if(n > 0) then allocate(res(n)) res = -1 if(stmt%prepare(db, "SELECT player FROM available WHERE instruction=?") == SQLITE_OK) then if(stmt%bind_int(1, id) == SQLITE_OK) then i = 1 do while(stmt%step() == SQLITE_ROW .and. i <= n) res(i) = stmt%column_int(0) i = i + 1 end do end if end if call stmt%finalize() end if end function get_instruction_players subroutine add_player_for_instruction(instruction, player) implicit none integer, intent(in)::instruction, player type(sqlite3_stmt)::stmt if(stmt%prepare(db, "INSERT OR IGNORE INTO available(instruction, player) VALUES(?,?)") == SQLITE_OK) then if(stmt%bind_int(1, instruction) == SQLITE_OK .and. stmt%bind_int(2, player) == SQLITE_OK) then call stmt%step_now() end if end if call stmt%finalize() end subroutine add_player_for_instruction subroutine remove_player_for_instruction(instruction, player) implicit none integer, intent(in)::instruction, player type(sqlite3_stmt)::stmt if(stmt%prepare(db, "DELETE FROM available WHERE instruction=? AND player=?") == SQLITE_OK) then if(stmt%bind_int(1, instruction) == SQLITE_OK .and. stmt%bind_int(2, player) == SQLITE_OK) then call stmt%step_now() end if end if call stmt%finalize() end subroutine remove_player_for_instruction subroutine scan_instructions_for_db() use config use utilities use logging implicit none character(len=2048)::cmdline call combine_paths(script_dir, "scan_instructions.sh", cmdline) cmdline = trim(cmdline)//" "//trim(database_file)//" "//trim(instructions_dir)//" 1>/dev/null 2>/dev/null" call write_log("Scan Command: "//trim(cmdline)) call execute_command_line(trim(cmdline), wait=.true.) end subroutine scan_instructions_for_db end module captain_db