aboutsummaryrefslogtreecommitdiff
path: root/captain/db.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/db.f90')
-rw-r--r--captain/db.f90138
1 files changed, 138 insertions, 0 deletions
diff --git a/captain/db.f90 b/captain/db.f90
index b7712fa..00ec00e 100644
--- a/captain/db.f90
+++ b/captain/db.f90
@@ -1395,4 +1395,142 @@ contains
end subroutine queue_scheduled_jobs
+ function new_user_db(username, password, email, auth_level)
+ use config, only: app_salt
+ use m_crypt, only: hash
+ use auth_levels, only: AUTH_NORMAL_USER
+ implicit none
+
+ character(*), intent(in)::username, password, email
+ integer, intent(in), optional::auth_level
+ logical::new_user_db
+ type(sqlite3_stmt)::stmt
+
+ character(len=:), pointer::hashed_pass
+
+ integer::user_auth_level
+
+ if(present(auth_level)) then
+ user_auth_level = auth_level
+ else
+ user_auth_level = AUTH_NORMAL_USER
+ end if
+
+ new_user_db = .FALSE.
+
+ hashed_pass => hash(trim(password)//trim(app_salt))
+ if(associated(hashed_pass)) then
+
+ if(stmt%prepare(db, "INSERT INTO users(username, password, email, level) VALUES(?, ?, ?, ?)") == SQLITE_OK) then
+ if(stmt%bind_text(1, username) == SQLITE_OK .and. &
+ stmt%bind_text(2, hashed_pass) == SQLITE_OK .and. &
+ stmt%bind_text(3, email) == SQLITE_OK .and. &
+ stmt%bind_int(4, user_auth_level) == SQLITE_OK) then
+
+ new_user_db = any(stmt%step() == (/ SQLITE_OK, SQLITE_DONE /))
+
+ end if
+ end if
+ call stmt%finalize()
+
+ deallocate(hashed_pass)
+ end if
+
+ end function new_user_db
+
+ function get_password_hash_pointer_db(username) result(password)
+ implicit none
+
+ character(len=*), intent(in)::username
+ character(len=:), pointer::password
+ type(sqlite3_stmt)::stmt
+ integer::textlength
+
+ password => null()
+
+ if(stmt%prepare(db, "SELECT password FROM users WHERE username=? LIMIT 1") == SQLITE_OK) then
+ if(stmt%bind_text(1, username) == SQLITE_OK) then
+ if(stmt%step() == SQLITE_ROW) then
+
+ textlength = stmt%column_text_length(0)
+ if(textlength > 0) then
+ allocate(character(len=textlength) :: password)
+ call stmt%column_text(0, password)
+ end if
+ end if
+ end if
+ call stmt%finalize()
+ end if
+
+ end function get_password_hash_pointer_db
+
+ function validate_user_db(username, password)
+ use config, only: app_salt
+ use m_crypt, only: hash
+ implicit none
+
+ character(len=*), intent(in)::username, password
+ logical::validate_user_db
+
+ character(len=:), pointer::hashed_pass, db_hashed_pass
+
+ validate_user_db = .FALSE.
+
+ hashed_pass => hash(trim(password)//trim(app_salt))
+ if(associated(hashed_pass)) then
+ db_hashed_pass => get_password_hash_pointer_db(username)
+ if(associated(db_hashed_pass)) then
+
+ validate_user_db = (hashed_pass == db_hashed_pass)
+
+ deallocate(db_hashed_pass)
+ end if
+
+ deallocate(hashed_pass)
+ end if
+
+ end function validate_user_db
+
+ function get_user_auth_db(username)
+ implicit none
+
+ character(len=*), intent(in)::username
+ integer::get_user_auth_db
+
+ type(sqlite3_stmt)::stmt
+
+ get_user_auth_db = -1
+
+ if(stmt%prepare(db, "SELECT level FROM users WHERE username=? LIMIT 1") == SQLITE_OK) then
+ if(stmt%bind_text(1, username) == SQLITE_OK) then
+ if(stmt%step() == SQLITE_ROW) then
+ get_user_auth_db = stmt%column_int(0)
+ end if
+ end if
+ call stmt%finalize()
+ end if
+
+ end function get_user_auth_db
+
+ function get_session_auth_db(session)
+ implicit none
+
+ character(len=*), intent(in)::session
+ integer::get_session_auth_db
+
+ type(sqlite3_stmt)::stmt
+
+ get_session_auth_db = -1
+
+ if(stmt%prepare(db, "SELECT level FROM session_auth WHERE session=? LIMIT 1") == SQLITE_OK) then
+ if(stmt%bind_text(1, session) == SQLITE_OK) then
+ if(stmt%step() == SQLITE_ROW) then
+ get_session_auth_db = stmt%column_int(0)
+ end if
+ end if
+ call stmt%finalize()
+ end if
+
+ end function get_session_auth_db
+
end module captain_db