mmo-project/fortran/www/app/main.f90

111 lines
3.3 KiB
Fortran

program main
use www
use sqliteff
use SM3_module, only: SM3
use iso_varying_string
use, intrinsic :: iso_c_binding, only: c_signed_char, c_size_t
implicit none
character, dimension(:), allocatable :: form_data
character(len=32) :: index_path
character(len=128) :: db_path
integer :: err, i, length
logical :: exist
call getarg(1, index_path)
index_path = trim(index_path)
call getarg(2, db_path)
db_path = trim(db_path)
call request(form_data, length)
if (length .gt. 0) then
call createDB(db_path)
inquire(file="debug.log", exist=exist)
if (exist) then
open(12, file="debug.log", status="old", position="rewind", action="write")
else
open(12, file="debug.log", status="new", action="write")
end if
do i=1,length
write(12, '(A)', advance="NO") form_data(i)
end do
write(12, '(A)')
close(unit=12)
call write_index(index_path)
else
call write_index(index_path)
end if
if (allocated(form_data)) deallocate (form_data, stat=err)
if (err /= 0) print *, "index_html: Deallocation request denied"
contains
subroutine createDB(db_path)
character(len=128), intent(in) :: db_path
type(SqliteDatabase_t) :: connection
type(SqliteStatement_t) :: statement
type(VARYING_STRING) :: remaining
integer :: status
status = sqliteff_open(db_path, connection)
status = sqliteff_prepare( &
connection, &
var_str("CREATE TABLE users (identifier INTEGER PRIMARY KEY ASC, " &
// "username TEXT, password TEXT, apperance TEXT, x_pos INTEGER, " &
// "y_pos INTEGER, last_login INTEGER, created INTEGER);"), &
statement, &
remaining)
if (status .eq. SQLITE_OK) then
status = sqliteff_step(statement)
status = sqliteff_finalize(statement)
status = sqliteff_close(connection)
end if
end subroutine createDB
subroutine addUser(db_path, username, password, appearance)
character(len=128), intent(in) :: db_path
character(len=24), intent(in) :: username
character(len=24), intent(in) :: password
character(len=8), intent(in) :: appearance
character(len=32) :: encrypted_password
type(SqliteDatabase_t) :: connection
type(VARYING_STRING) :: errmsg
integer :: status
integer(8) :: created
character(len=32) :: created_str
integer(c_signed_char) :: dgst(32)
integer(c_signed_char) :: msg(25)
msg = transfer(password, msg)
call SM3(msg, 25_c_size_t, dgst)
write (encrypted_password, *) dgst
encrypted_password = adjustl(encrypted_password)
created = time()
write (created_str, *) created
created_str = adjustl(created_str)
status = sqliteff_open(db_path, connection)
status = sqliteff_exec( &
connection, &
'INSERT INTO users (username, password, apperance, x_pos, y_pos, last_login, created) &
VALUES ("'//username//'", "'//encrypted_password//'", "#'//appearance//'", &
0, 0, 0, '//created_str//'");', &
errmsg)
status = sqliteff_close(connection)
end subroutine addUser
end program main