program main use www implicit none character, dimension(:), allocatable :: form_data character(len=32) :: index_path character(len=128):: db_path integer :: err, i, length logical :: exist inquire (file="debug.log", exist=exist) if (exist) then open (12, file="debug.log", status="old", position="append", action="write") else open (12, file="debug.log", status="new", action="write") end if call getarg(1, index_path) call getarg(2, db_path) call request(form_data, length) if (length .gt. 0) then inquire (file=trim(adjustl(db_path)), exist=exist) if (.not. exist) then call create_db(db_path) end if call add_user(db_path, form_data, length) end if call write_index(index_path) if (allocated(form_data)) deallocate (form_data, stat=err) if (err /= 0) print *, "index_html: Deallocation request denied" close (unit=12) contains subroutine create_db(db_path) character(len=128), intent(in) :: db_path character(len=:), allocatable :: command command = 'sqlite3 '//trim(adjustl(db_path)) & //' ''CREATE TABLE users ' & //'(id INTEGER PRIMARY KEY ASC, ' & //'username TEXT, password TEXT, ' & //'apperance TEXT, x_pos INTEGER, ' & //'y_pos INTEGER, last_login INTEGER, ' & //' created INTEGER);''' write (12, *) command call execute_command_line(command) end subroutine create_db subroutine add_user(db_path, request, length) character(len=128), intent(in) :: db_path character, dimension(:), allocatable, intent(in) :: request integer, intent(in) :: length character(len=:), allocatable :: command character(len=32) :: created integer :: i, s_u_idx, e_u_idx, s_p_idx, e_p_idx, s_a_idx get_username: do i = 1, length if (request(i) .eq. '=') then s_u_idx = i + 1 end if if (request(i) .eq. '&') then e_u_idx = i - 1 exit get_username end if end do get_username ! username = transfer(request(s_idx:e_idx), username) get_password: do i = e_u_idx + 2, length if (request(i) .eq. '=') then s_p_idx = i + 1 end if if (request(i) .eq. '&') then e_p_idx = i - 1 exit get_password end if end do get_password ! password = transfer(request(s_idx:e_idx), password) get_appearance: do i = e_p_idx + 2, length if (request(i) .eq. '=') then s_a_idx = i + 1 end if end do get_appearance ! appearance = transfer(request(s_a_idx:length), appearance) write (created, *) time() command = 'sqlite3 ' & //trim(adjustl(db_path)) & //' "INSERT INTO users (username,password' & //',apperance,x_pos,y_pos,last_login,created) VALUES (''' & //request(s_u_idx:e_u_idx) & //''',''' & //request(s_p_idx:e_p_idx) & //''',''' & //request(s_a_idx:length) & //''',0,0,0,' & //created//');"' write (12, *) command call execute_command_line(command) end subroutine add_user end program main