aboutsummaryrefslogtreecommitdiff
path: root/captain/db.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/db.f90')
-rw-r--r--captain/db.f9077
1 files changed, 64 insertions, 13 deletions
diff --git a/captain/db.f90 b/captain/db.f90
index b9d1e61..152f61b 100644
--- a/captain/db.f90
+++ b/captain/db.f90
@@ -32,8 +32,9 @@ implicit none
integer, parameter::JOB_STATUS_WORKING = 3
integer, parameter::JOB_STATUS_PENDING = 0
- integer, parameter::PLAYER_STATUS_BUSY = JOB_STATUS_WORKING
- integer, parameter::PLAYER_STATUS_IDLE = 100
+ integer, parameter::PLAYER_STATUS_BUSY = JOB_STATUS_WORKING
+ integer, parameter::PLAYER_STATUS_IDLE = 100
+ integer, parameter::PLAYER_STATUS_OFFLINE = 101
character(1024)::database_file
type(c_ptr)::db
@@ -1248,28 +1249,27 @@ contains
integer, dimension(8), intent(out)::values
type(sqlite3_stmt)::stmt
- integer::i
! This call properly retrieves the offset from UTC if you want it...
+ values = 0
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
+ values(1) = stmt%column_int(0)
+ values(2) = stmt%column_int(1)
+ values(3) = stmt%column_int(2)
+ values(5) = stmt%column_int(3)
+ values(6) = stmt%column_int(4)
+ values(7) = stmt%column_int(5)
+ else
+ values = 0
end if
end if
end if
call stmt%finalize()
-
+
end subroutine get_last_checkin_time
subroutine get_player_platform(player, platform)
@@ -1295,4 +1295,55 @@ contains
end subroutine get_player_platform
+ pure function julian_date(values) result(jd)
+ implicit none
+
+ integer, dimension(3), intent(in)::values
+ integer::jd
+
+ jd = (1461 * (values(1) + 4800 + (values(2)-14)/12))/4 + &
+ (367 * (values(2) - 2 - 12*((values(2)-14)/12)))/12 - &
+ (3*((values(1) + 4900 + (values(2)-14)/12)/100))/4 + &
+ values(3) - 32075
+
+ end function julian_date
+
+ pure function seconds_difference(first, second) result(diff)
+ implicit none
+
+ integer, dimension(8), intent(in)::first, second
+ integer(kind=8)::diff
+
+ diff = (julian_date(first(1:3)) - julian_date(second(1:3))) * 24 * 3600
+
+ diff = diff + (first(5) - second(5)) * 3600
+ diff = diff + (first(6) - second(6)) * 60
+ diff = diff + (first(7) - second(7))
+
+ end function seconds_difference
+
+ function is_player_online(player) result(ret)
+ implicit none
+
+ integer, intent(in)::player
+ logical::ret
+
+ integer, dimension(8)::now, last
+
+ call date_and_time(values=now)
+ call get_last_checkin_time(player, last)
+
+ ! All zeroes mean that it was never online
+ if(all(last == 0)) then
+
+ ret = .false.
+
+ else
+
+ ret = (seconds_difference(now, last) <= 60)
+
+ end if
+
+ end function is_player_online
+
end module captain_db