aboutsummaryrefslogtreecommitdiff
path: root/captain/db.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/db.f90')
-rw-r--r--captain/db.f90355
1 files changed, 346 insertions, 9 deletions
diff --git a/captain/db.f90 b/captain/db.f90
index 2cf8e4f..e4b4a4b 100644
--- a/captain/db.f90
+++ b/captain/db.f90
@@ -38,16 +38,27 @@ implicit none
character(1024)::database_file
type(c_ptr)::db
- type :: job
+ type :: work_pair
- integer::id
integer::instruction
integer::player
+
+ end type
+
+ type, extends(work_pair) :: job
+
+ integer::id
integer::status
character(32)::time
end type
+ type, extends(work_pair) :: group_entry
+
+ integer::group
+
+ end type
+
type :: task
integer::job
@@ -189,21 +200,48 @@ contains
end function get_player_names
- function get_instuctions_count()
+ function get_instructions_count()
implicit none
type(sqlite3_stmt)::stmt
- integer::get_instuctions_count
+ integer::get_instructions_count
- get_instuctions_count = 0
+ get_instructions_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)
+ get_instructions_count = stmt%column_int(0)
end if
end if
call stmt%finalize()
- end function get_instuctions_count
+ end function get_instructions_count
+
+ function get_instruction_ids() result(res)
+ implicit none
+
+ type(sqlite3_stmt)::stmt
+ integer, dimension(:), pointer::res
+ integer::i,n
+
+ res => null()
+
+ n = get_instructions_count()
+ if(n > 0) then
+ allocate(res(n))
+ res = -1
+
+ if(stmt%prepare(db, "SELECT id, name FROM instructions ORDER BY name") == 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
+ call stmt%finalize()
+
+ end if
+
+ end function get_instruction_ids
function get_instruction_names() result(res)
implicit none
@@ -212,7 +250,7 @@ contains
character(len=PLAYER_NAME_LENGTH), dimension(:), pointer::res
integer::i,n
- n = get_instuctions_count()
+ n = get_instructions_count()
if(n > 0) then
allocate(res(n))
if(stmt%prepare(db, "SELECT name FROM instructions ORDER BY name") == SQLITE_OK) then
@@ -295,7 +333,7 @@ contains
type(sqlite3_stmt)::stmt
str = " "
-
+ Print *, id
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
@@ -776,4 +814,303 @@ contains
end subroutine scan_instructions_for_db
+ subroutine add_group_db(name)
+ implicit none
+
+ character(*), intent(in)::name
+
+ type(sqlite3_stmt)::stmt
+
+ if(stmt%prepare(db, "INSERT INTO groups(name) VALUES(?)") == 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 add_group_db
+
+ subroutine get_group_name_db(id, name)
+ implicit none
+
+ integer, intent(in)::id
+ character(*), intent(out)::name
+ type(sqlite3_stmt)::stmt
+
+ if(stmt%prepare(db, "SELECT name FROM groups 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, name)
+ end if
+
+ end if
+ end if
+ call stmt%finalize()
+
+ end subroutine get_group_name_db
+
+ function get_group_id_db(name)
+ implicit none
+
+ character(*), intent(in)::name
+ integer::get_group_id_db
+ type(sqlite3_stmt)::stmt
+
+ get_group_id_db = -1
+
+ if(stmt%prepare(db, "SELECT id FROM groups WHERE name=?") == SQLITE_OK) then
+ if(stmt%bind_text(1, name) == SQLITE_OK) then
+
+ if(stmt%step() == SQLITE_ROW) then
+ get_group_id_db = stmt%column_int(0)
+ end if
+
+ end if
+ end if
+ call stmt%finalize()
+
+ end function get_group_id_db
+
+ subroutine delete_group_db(id)
+ implicit none
+
+ integer, intent(in)::id
+ type(sqlite3_stmt)::stmt
+
+ if(stmt%prepare(db, "DELETE FROM groups WHERE id=?") == SQLITE_OK) then
+ if(stmt%bind_int(1, id) == SQLITE_OK) then
+
+ call stmt%step_now()
+
+ end if
+ end if
+ call stmt%finalize()
+
+ end subroutine delete_group_db
+
+ function get_group_count_db()
+ implicit none
+
+ integer::get_group_count_db
+ type(sqlite3_stmt)::stmt
+
+ get_group_count_db = 0
+
+ if(stmt%prepare(db, "SELECT COUNT(*) FROM groups") == SQLITE_OK) then
+ if(stmt%step() == SQLITE_ROW) then
+ get_group_count_db = stmt%column_int(0)
+ end if
+ end if
+ call stmt%finalize()
+
+ end function get_group_count_db
+
+ function get_groups_db() result(res)
+ implicit none
+
+ integer, dimension(:), pointer::res
+ type(sqlite3_stmt)::stmt
+ integer::i, n
+
+ res => null()
+ n = get_group_count_db()
+
+ if(n > 0) then
+
+ allocate(res(n))
+ res = -1
+
+ if(stmt%prepare(db, "SELECT id FROM groups") == SQLITE_OK) then
+ i = 0
+ do while(stmt%step() == SQLITE_ROW .AND. i <= n)
+ i = i + 1
+ res(i) = stmt%column_int(0)
+ end do
+ end if
+ call stmt%finalize()
+
+ end if
+
+ end function get_groups_db
+
+ function is_entry_in_group_db(group, instruction, player)
+ implicit none
+
+ integer, intent(in)::group, instruction, player
+ type(sqlite3_stmt)::stmt
+ logical::is_entry_in_group_db
+
+ is_entry_in_group_db = .FALSE.
+
+ if(stmt%prepare(db, &
+ "SELECT COUNT(*) FROM group_instructions WHERE group_id=? AND instruction=? AND player=?") == SQLITE_OK) &
+ then
+ if(stmt%bind_int(1, group) == SQLITE_OK .AND. &
+ stmt%bind_int(2, instruction) == SQLITE_OK .AND. &
+ stmt%bind_int(3, player) == SQLITE_OK) &
+ then
+
+ if(stmt%step() == SQLITE_ROW) then
+ is_entry_in_group_db = (stmt%column_int(0) > 0)
+ end if
+
+ end if
+ end if
+ call stmt%finalize()
+
+ end function is_entry_in_group_db
+
+ subroutine add_entry_to_group_db(group, instruction, player)
+ implicit none
+
+ integer, intent(in)::group, instruction, player
+ type(sqlite3_stmt)::stmt
+
+ if(instruction >= 0 .AND. player >= 0 .AND. group >= 0 .AND. &
+ .NOT. is_entry_in_group_db(group, instruction, player)) &
+ then
+
+ if(stmt%prepare(db, "INSERT INTO group_instructions(group_id, instruction, player) VALUES(?, ?, ?)") == SQLITE_OK) then
+ if(stmt%bind_int(1, group) == SQLITE_OK .AND. &
+ stmt%bind_int(2, instruction) == SQLITE_OK .AND. &
+ stmt%bind_int(3, player) == SQLITE_OK) &
+ then
+
+ call stmt%step_now()
+
+ end if
+ end if
+ call stmt%finalize()
+
+ end if
+
+ end subroutine add_entry_to_group_db
+
+ subroutine remove_entry_from_group_db(group, instruction, player)
+ implicit none
+
+ integer, intent(in)::group, instruction, player
+ type(sqlite3_stmt)::stmt
+
+ if(stmt%prepare(db, "DELETE FROM group_instructions WHERE group_id=? AND instruction=? AND player=?") == SQLITE_OK) then
+ if(stmt%bind_int(1, group) == SQLITE_OK .AND. &
+ stmt%bind_int(2, instruction) == SQLITE_OK .AND. &
+ stmt%bind_int(3, player) == SQLITE_OK) &
+ then
+
+ call stmt%step_now()
+
+ end if
+ end if
+ call stmt%finalize()
+
+ end subroutine remove_entry_from_group_db
+
+ function get_group_entries_count_db(group)
+ implicit none
+
+ integer, intent(in)::group
+ integer::get_group_entries_count_db
+ type(sqlite3_stmt)::stmt
+
+ get_group_entries_count_db = 0
+
+ if(stmt%prepare(db, "SELECT COUNT(*) FROM group_instructions WHERE group_id=?") == SQLITE_OK) then
+ if(stmt%bind_int(1, group) == SQLITE_OK) then
+
+ if(stmt%step() == SQLITE_ROW) then
+ get_group_entries_count_db = stmt%column_int(0)
+ end if
+
+ end if
+ end if
+ call stmt%finalize()
+
+ end function get_group_entries_count_db
+
+ function get_group_entries_db(group) result(res)
+ implicit none
+
+ integer, intent(in)::group
+ type(group_entry), dimension(:), pointer::res
+ type(sqlite3_stmt)::stmt
+ integer::i, n
+
+ res => null()
+
+ n = get_group_entries_count_db(group)
+ if(n > 0) then
+
+ allocate(res(n))
+ res%instruction = -1
+ res%player = -1
+ res%group = group
+
+ if(stmt%prepare(db, "SELECT instruction, player FROM group_instructions WHERE group_id=?") == SQLITE_OK) then
+ if(stmt%bind_int(1, group) == SQLITE_OK) then
+
+ i = 0
+ do while(stmt%step() == SQLITE_ROW .and. i <= n)
+ i = i + 1
+ res(i)%instruction = stmt%column_int(0)
+ res(i)%player = stmt%column_int(1)
+ end do
+
+ end if
+ end if
+ call stmt%finalize()
+
+ end if
+
+ end function get_group_entries_db
+
+ function get_available_count_db()
+ implicit none
+
+ integer::get_available_count_db
+ type(sqlite3_stmt)::stmt
+
+ get_available_count_db = 0
+
+ if(stmt%prepare(db, "SELECT COUNT(*) FROM available") == SQLITE_OK) then
+ if(stmt%step() == SQLITE_ROW) then
+ get_available_count_db = stmt%column_int(0)
+ end if
+ end if
+ call stmt%finalize()
+
+ end function get_available_count_db
+
+ function get_available_work_pairs_db() result(res)
+ implicit none
+
+ type(work_pair), dimension(:), pointer::res
+ integer::n, i
+ type(sqlite3_stmt)::stmt
+
+ n = get_available_count_db()
+ res => null()
+
+ if(n > 0) then
+ allocate(res(n))
+ res%instruction = -1
+ res%player = -1
+
+ if(stmt%prepare(db, "SELECT instruction, player FROM available") == SQLITE_OK) then
+ i = 1
+ do while(stmt%step() == SQLITE_ROW .AND. i <= n)
+ res(i)%instruction = stmt%column_int(0)
+ res(i)%player = stmt%column_int(1)
+ i = i + 1
+ end do
+ end if
+ call stmt%finalize()
+
+ end if
+
+ end function get_available_work_pairs_db
+
end module captain_db