aboutsummaryrefslogtreecommitdiff
path: root/captain/db.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/db.f90')
-rw-r--r--captain/db.f90164
1 files changed, 150 insertions, 14 deletions
diff --git a/captain/db.f90 b/captain/db.f90
index e4b4a4b..b789280 100644
--- a/captain/db.f90
+++ b/captain/db.f90
@@ -200,44 +200,84 @@ contains
end function get_player_names
- function get_instructions_count()
+ function get_instructions_count(player)
implicit none
type(sqlite3_stmt)::stmt
+ integer, intent(in), optional::player
integer::get_instructions_count
get_instructions_count = 0
- if(stmt%prepare(db, "SELECT COUNT(*) FROM instructions") == SQLITE_OK) then
- if(stmt%step() == SQLITE_ROW) then
- get_instructions_count = stmt%column_int(0)
+
+ if(present(player)) then
+
+ if(stmt%prepare(db, "SELECT COUNT(*) FROM available WHERE player=?") == SQLITE_OK) then
+ if(stmt%bind_int(1, player) == SQLITE_OK) then
+ if(stmt%step() == SQLITE_ROW) then
+ get_instructions_count = stmt%column_int(0)
+ end if
+ end if
+ end if
+ call stmt%finalize()
+
+ else
+
+ if(stmt%prepare(db, "SELECT COUNT(*) FROM instructions") == SQLITE_OK) then
+ if(stmt%step() == SQLITE_ROW) then
+ get_instructions_count = stmt%column_int(0)
+ end if
end if
+ call stmt%finalize()
+
end if
- call stmt%finalize()
end function get_instructions_count
- function get_instruction_ids() result(res)
+ function get_instruction_ids(player) result(res)
implicit none
type(sqlite3_stmt)::stmt
+ integer, intent(in), optional::player
integer, dimension(:), pointer::res
integer::i,n
res => null()
- n = get_instructions_count()
+ if(present(player)) then
+ n = get_instructions_count(player)
+ else
+ n = get_instructions_count()
+ end if
+
if(n > 0) then
allocate(res(n))
res = -1
+
+ if(present(player)) then
+
+ if(stmt%prepare(db, "SELECT instruction FROM available WHERE player=?") == SQLITE_OK) then
+ if(stmt%bind_int(1, player) == 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()
+
+ else
- 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
+ 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
- call stmt%finalize()
end if
@@ -1113,4 +1153,100 @@ contains
end function get_available_work_pairs_db
+ subroutine acknowledge_checkin(player, platform)
+ implicit none
+
+ integer, intent(in)::player
+ character(*), intent(in), optional::platform
+ type(sqlite3_stmt)::stmt
+ integer, dimension(8)::right_now
+ integer::res
+
+ call date_and_time(values=right_now)
+
+ if(stmt%prepare(db, &
+ "INSERT OR UPDATE INTO checkin(player, year, month, day, hour, minute, second, platform) VALUES(?, ?, ?)") &
+ == SQLITE_OK) &
+ then
+ if(stmt%bind_int(1, player) == SQLITE_OK .AND. &
+ stmt%bind_int(2, right_now(1)) == SQLITE_OK .AND. &
+ stmt%bind_int(3, right_now(2)) == SQLITE_OK .AND. &
+ stmt%bind_int(4, right_now(3)) == SQLITE_OK .AND. &
+ stmt%bind_int(5, right_now(5)) == SQLITE_OK .AND. &
+ stmt%bind_int(6, right_now(6)) == SQLITE_OK .AND. &
+ stmt%bind_int(7, right_now(7)) == SQLITE_OK ) &
+ then
+
+ if(.not. present(platform)) then
+ res = stmt%bind_null(8)
+ else
+ res = stmt%bind_text(8, platform)
+ end if
+
+ if(res == SQLITE_OK) then
+ call stmt%step_now()
+ end if
+
+ end if
+ end if
+ call stmt%finalize()
+
+ end subroutine acknowledge_checkin
+
+ ! For definition of values. see Fortran's DATE_AND_TIME
+ subroutine get_last_checkin_time(player, values)
+ use sqlite
+ implicit none
+
+ integer, intent(in)::player
+ integer, dimension(8), intent(out)::values
+
+ type(sqlite3_stmt)::stmt
+ integer::i
+
+ ! This call properly retrieves the offset from UTC if you want it...
+ call date_and_time(values=values)
+ values(1:3) = 0
+ values(5:8) = 0
+
+ if(stmt%prepare(db, "SELECT year, month, day, hour, minute, second FROM checkin WHERE player=? LIMIT 1") == SQLITE_OK) then
+ if(stmt%bind_int(1, player) == SQLITE_OK) then
+ if(stmt%step() == SQLITE_ROW) then
+ do i = 1, 7
+ if(i < 4) then
+ values(i) = stmt%column_int(i-1)
+ else if(i >= 5) then
+ values(i-1) = stmt%column_int(i-1)
+ end if
+ end do
+ end if
+ end if
+ end if
+ call stmt%finalize()
+
+ end subroutine get_last_checkin_time
+
+ subroutine get_player_platform(player, platform)
+ use sqlite
+ implicit none
+
+ integer, intent(in)::player
+ character(*), intent(out)::platform
+ type(sqlite3_stmt)::stmt
+
+ platform = " "
+
+ if(stmt%prepare(db, "SELECT platform FROM checkin WHERE player=? LIMIT 1") == SQLITE_OK) then
+ if(stmt%bind_int(1, player) == SQLITE_OK) then
+ if(stmt%step() == SQLITE_ROW) then
+ if(stmt%column_type(0) == SQLITE_TEXT) then
+ call stmt%column_text(0, platform)
+ end if
+ end if
+ end if
+ end if
+ call stmt%finalize()
+
+ end subroutine get_player_platform
+
end module captain_db