aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-04-14 10:54:27 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-04-14 10:54:27 -0400
commit05b91a7ca0aace044621d8db1e82f4772181d893 (patch)
tree44bf7c8c284c3363f353553c12046e5ca4de40b7
parent14441b7f0d6dd0a101b38a4500fe1f662ae00215 (diff)
downloadlevitating-05b91a7ca0aace044621d8db1e82f4772181d893.tar.gz
levitating-05b91a7ca0aace044621d8db1e82f4772181d893.zip
Fixed binary transfers to maintain file integrity. Added globbed file upload capabilities. Fixed memory overrun issues due to problems parsing ls output.
-rw-r--r--captain/response.f9019
-rw-r--r--common/jessl.f902
-rw-r--r--common/protocol.f9027
-rw-r--r--common/request.f9012
-rw-r--r--common/utilities.F9044
-rw-r--r--player/instructions.f906
-rw-r--r--player/player.F901
-rw-r--r--player/talking.f904
-rw-r--r--player/tasks.f9081
9 files changed, 156 insertions, 40 deletions
diff --git a/captain/response.f90 b/captain/response.f90
index 09184f9..5a81411 100644
--- a/captain/response.f90
+++ b/captain/response.f90
@@ -426,26 +426,35 @@ contains
character(*), intent(in)::filename
integer::unum
- character, dimension(64)::buf
+ character(len=1), dimension(64)::buf
integer::bufread
- integer(kind=8)::bytes_to_go
+ integer(kind=8)::bytes_to_go, written
integer::i
- character(128)::msg
+ !character(128)::msg
- open(newunit=unum, file=filename, status="unknown", action="write", access="stream", form="formatted")
+ open(newunit=unum, file=filename, status="unknown", action="write", access='stream')
bytes_to_go = self%size
+ written = 0
do while(bytes_to_go > 0)
bufread = ssl_read(self%ssl_connection, buf)
bytes_to_go = bytes_to_go - bufread
+
+ !write(msg, '(A5, 1X, I8, 3X, A5, 1X, I8)') "READ:", bufread, "TOGO:", bytes_to_go
+ !call write_log(trim(msg))
+
do i = 1, bufread
- write(unum, '(A1)', advance='no') buf(i)
+ !write(unum, '(A1)', advance='no') buf(i)
+ write(unum) buf(i)
+ written = written + 1
end do
end do
+ !write(msg, '(A8, 1X, I8, 3x, A5, 1X, I8)') "WRITTEN:", written, "LAST:", ichar(buf(1))
+ !call write_log(trim(msg))
close(unum)
end subroutine titan_write_to_filename
diff --git a/common/jessl.f90 b/common/jessl.f90
index a03df09..5ad90fd 100644
--- a/common/jessl.f90
+++ b/common/jessl.f90
@@ -208,7 +208,7 @@ contains
implicit none
type(c_ptr)::ssl
- character, dimension(:), intent(out)::buf
+ character(len=1), dimension(:), intent(out)::buf
integer::ssl_read
integer::bufsize
diff --git a/common/protocol.f90 b/common/protocol.f90
index 992283c..46838b8 100644
--- a/common/protocol.f90
+++ b/common/protocol.f90
@@ -179,7 +179,8 @@ contains
else
- write(unit_number, '(A1)', advance='no') buffer(i)
+ !write(unit_number, '(A1)', advance='no') buffer(i)
+ write(unit_number) buffer(i)
end if
@@ -251,35 +252,43 @@ contains
if(conn%code == CONNECTION_OPEN) then
- successes(1) = send_string(conn%ssl, trim(url), trimming=.false.)
- successes(2) = send_string(conn%ssl, ";token="//trim(token), trimming=.false.)
+ successes(1) = send_string(conn%ssl, trim(url), trimming=.false., allow_trailing_null=.false.)
+ successes(2) = send_string(conn%ssl, ";token="//trim(token), &
+ trimming=.false., allow_trailing_null=.false.)
if(present(is_plain_text)) then
if(is_plain_text) then
- successes(3) = send_string(conn%ssl, ";mime=text/plain", trimming=.false.)
+ successes(3) = send_string(conn%ssl, ";mime=text/plain", &
+ trimming=.false., allow_trailing_null=.false.)
else
- successes(3) = send_string(conn%ssl, ";mime=application/octet-stream", trimming=.false.)
+ successes(3) = send_string(conn%ssl, ";mime=application/octet-stream", &
+ trimming=.false., allow_trailing_null=.false.)
end if
else
- successes(3) = send_string(conn%ssl, ";mime=application/octet-stream", trimming=.false.)
+ successes(3) = send_string(conn%ssl, ";mime=application/octet-stream", &
+ trimming=.false., allow_trailing_null=.false.)
end if
write(file_length_text, '(I14)') file_length
file_length_text = adjustl(file_length_text)
- successes(4) = send_string(conn%ssl, ";size="//trim(file_length_text)//c_carriage_return//c_new_line, trimming=.false.)
+
+ successes(4) = send_string(conn%ssl, &
+ ";size="//trim(file_length_text)//c_carriage_return//c_new_line, &
+ trimming=.false., &
+ allow_trailing_null=.false.)
if(all(successes, 1)) then
total_written = 0
bytes_read = read_into_buffer(unit_number, buffer)
- Print *, "bytes read for sending: ", bytes_read
+ !Print *, "bytes read for sending: ", bytes_read
do while(bytes_read > 0)
bytes_written = ssl_write(conn%ssl, buffer(1:bytes_read))
total_written = total_written + bytes_written
bytes_read = read_into_buffer(unit_number, buffer)
- Print *, "bytes read for sending now: ", bytes_read, " and so far, we wrote", total_written
+ !Print *, "bytes read for sending now: ", bytes_read, " and so far, we wrote", total_written
end do
if(total_written >= file_length) then
diff --git a/common/request.f90 b/common/request.f90
index d7b3120..fe4d970 100644
--- a/common/request.f90
+++ b/common/request.f90
@@ -218,7 +218,7 @@ contains
end subroutine get_server_from_url
- function send_string(ssl, str, trimming) result(success)
+ function send_string(ssl, str, trimming, allow_trailing_null) result(success)
use iso_c_binding
use jessl
implicit none
@@ -226,12 +226,13 @@ contains
logical::success
type(c_ptr)::ssl
character(*), intent(in)::str
- logical, intent(in), optional::trimming
+ logical, intent(in), optional::trimming, allow_trailing_null
integer::start_send
integer::chars_sent_this_time, chars_sending
integer::i
integer::string_length
+ logical::end_with_null
character, dimension(bufsize)::buffer
@@ -245,6 +246,11 @@ contains
string_length = len_trim(str)
end if
+ end_with_null = .true.
+ if(present(allow_trailing_null)) then
+ end_with_null = allow_trailing_null
+ end if
+
success = .true.
start_send = 1
do while(start_send <= string_length)
@@ -259,7 +265,7 @@ contains
end do
! A null character seems necessary at the end of the request
- if(i >= string_length) then
+ if(i >= string_length .and. end_with_null) then
chars_sending = chars_sending + 1
buffer(chars_sending) = c_null_char
end if
diff --git a/common/utilities.F90 b/common/utilities.F90
index ddc0c79..981dee3 100644
--- a/common/utilities.F90
+++ b/common/utilities.F90
@@ -334,7 +334,7 @@ contains
character(DIR_LIST_STRING_LENGTH), dimension(:), pointer::res
character(80)::line
character(len=:), pointer::tempfile
- integer::dcount, total_count, unum, ierr, i
+ integer::dcount, total_count, unum, ierr, i, n
tempfile => generate_temporary_filename()
res => null()
@@ -344,24 +344,33 @@ contains
open(newunit=unum, file=tempfile, action='read')
- ! First line is "total ###"
- read(unum, '(A)', iostat=ierr) line
-
dcount = 0
total_count = 0
+
+ ! Count directories first
read(unum, '(A)', iostat=ierr) line
do while(ierr == 0)
+
if(line(1:1) == 'd') then
dcount = dcount + 1
end if
- total_count = total_count + 1
+
+ ! ls puts a nonsense entry first. harmless, but we don't want it
+ if(line(1:6) /= "total ") then
+ total_count = total_count + 1
+ end if
+
read(unum, '(A)', iostat=ierr) line
end do
close(unum)
- if((total_count - dcount) > 0) then
- allocate(res(total_count - dcount))
+ n = total_count - dcount
+ !print *, "Total: ", total_count, "Dirs:", dcount, "Files:", n
+
+ if(n > 0) then
+ allocate(res(n))
+ !print *, "Size: ", size(res)
! Now call ls, but group directories first
call execute_command_line("ls --group-directories-first "//trim(directory)//" > "//trim(tempfile), &
@@ -369,11 +378,24 @@ contains
open(newunit=unum, file=tempfile, action='read')
i = 0
+
+ ! First, skip directories
+ do while(i < dcount)
+ read(unum, '(A)', iostat=ierr) line
+ if(line(1:6) /= "total ") then
+ i = i + 1
+ end if
+ end do
+
+ ! Now we can read files
+ i = 0
read(unum, '(A)', iostat=ierr) line
- do while(ierr == 0 .and. i <= total_count)
- i = i + 1
- if(i > dcount) then
- res(i-dcount) = trim(line)
+ do while(ierr == 0 .and. i < n)
+ if(line(1:6) /= "total ") then
+ i = i + 1
+ res(i) = trim(line)
+
+ !print *, i, trim(res(i))//"|"
end if
read(unum, '(A)', iostat=ierr) line
diff --git a/player/instructions.f90 b/player/instructions.f90
index a3dc97a..1bd25ea 100644
--- a/player/instructions.f90
+++ b/player/instructions.f90
@@ -265,7 +265,11 @@ contains
if(.not. all(found,1)) then
success = .false.
else
- success = upload(url, filename)
+ if(index(filename, "*") > 0 .or. index(filename, "?") > 0) then
+ success = upload_glob(url, filename)
+ else
+ success = upload(url, filename)
+ end if
end if
else if(trim(operation) == "download") then
diff --git a/player/player.F90 b/player/player.F90
index bac6d6f..d41ec99 100644
--- a/player/player.F90
+++ b/player/player.F90
@@ -106,6 +106,7 @@ contains
integer::i
identity = " "
+ token = "None"
i = 1
do while(i <= command_argument_count())
diff --git a/player/talking.f90 b/player/talking.f90
index 733f463..5cc3a48 100644
--- a/player/talking.f90
+++ b/player/talking.f90
@@ -23,7 +23,7 @@ contains
mod_url = url
open(newunit=unit_number, file=filename, status='UNKNOWN', &
- access='STREAM', form='FORMATTED', iostat=istatus)
+ access='STREAM', iostat=istatus) ! form='FORMATTED',
if(istatus == 0) then
status_code = request_url(mod_url, unit_number, return_type)
@@ -69,7 +69,7 @@ contains
allocate(character(len=len_trim(url)) :: mod_url)
mod_url = url
- open(newunit=io, form="formatted", status="scratch", access='stream')
+ open(newunit=io, status="scratch", access='stream')
status_code = request_url(mod_url, io, return_type)
close(io)
diff --git a/player/tasks.f90 b/player/tasks.f90
index 87b7d66..2487e73 100644
--- a/player/tasks.f90
+++ b/player/tasks.f90
@@ -69,30 +69,84 @@ contains
end function shell
- function upload(url, source_filename)
+ function upload_glob(url, mask) result(res)
+ use utilities
+ implicit none
+
+ logical::res
+ character(*), intent(in)::url
+ character(*), intent(in)::mask
+
+ character(DIR_LIST_STRING_LENGTH), dimension(:), pointer::files
+ logical, dimension(:), allocatable::statuses
+ integer::i
+
+ ! We can cheat by using the get_files_in_directory function since it
+ ! is merely calling ls/dir, which will resolve the glob
+ files => get_files_in_directory(mask)
+
+ !allocate(files(2))
+ !files(1) = "/tmp/example/jagcdenc2.zip"
+ !files(2) = "/tmp/example/jagenc2.zip"
+
+ if(associated(files)) then
+
+ allocate(statuses(size(files)))
+ do i = 1, size(files)
+ statuses(i) = upload(url, files(i))
+ end do
+
+ res = all(statuses)
+
+ deallocate(statuses)
+ deallocate(files)
+
+ else
+
+ res = .false.
+
+ end if
+
+ end function upload_glob
+
+ recursive function upload(url, source_filename) result(res)
use config, only: token, captain
use gemini_protocol, only: titan_post_url, STATUS_SUCCESS
implicit none
- logical::upload
+ logical::res
character(*), intent(in)::url
character(*), intent(in)::source_filename
character(len=:), allocatable::mod_url
integer(kind=8)::file_size
- integer::unit_number, istatus, url_length
+ integer::unit_number, istatus, url_length, i
+
+ ! Check for globbing - sloppy, but still...
+ if(index(source_filename, "*") > 0 .or. index(source_filename, "?") > 0) then
+ res = upload_glob(url, source_filename)
+ return
+
+ end if
+
+ ! If we're here, we have a single filename to upload
inquire(file=source_filename, size=file_size)
open(newunit=unit_number, file=trim(source_filename), status='UNKNOWN', &
access='STREAM', form='UNFORMATTED', iostat=istatus)
if(index(url, "://") > 0) then
- allocate(character(len=len_trim(url)) :: mod_url)
+ ! Leave room for a possble filename
+ url_length = len_trim(url) + len_trim(source_filename)
+
+ allocate(character(len=url_length) :: mod_url)
mod_url = url
else
- url_length = len_trim(url) + len_trim(captain) + 16
+ ! Leave room for a possble filename
+ url_length = len_trim(url) + len_trim(source_filename) + len_trim(captain) + 16
+
allocate(character(len=url_length) :: mod_url)
mod_url = "titan://"//trim(captain)
if(url(1:1) == "/") then
@@ -102,12 +156,23 @@ contains
end if
end if
+ ! If the URL ends in a slash, it's a folder, add the filename base.
+ if(mod_url(len_trim(mod_url):len_trim(mod_url)) == "/") then
+ i = max(index(source_filename, "/", back=.true.), index(source_filename, "\", back=.true.))
+ if(i > 0) then
+ mod_url = trim(mod_url)//source_filename(i+1:len_trim(source_filename))
+ else
+ mod_url = trim(mod_url)//trim(source_filename)
+ end if
+ end if
+
if(istatus == 0) then
+ Print *, "Writing "//trim(mod_url)
istatus = titan_post_url(mod_url, unit_number, file_size, token)
- upload = (istatus == STATUS_SUCCESS)
+ res = (istatus == STATUS_SUCCESS)
close(unit_number)
else
- upload = .false.
+ res = .false.
end if
deallocate(mod_url)
@@ -145,7 +210,7 @@ contains
end if
open(newunit=unit_number, file=trim(destination_filename), status='UNKNOWN', &
- access='STREAM', form='FORMATTED', iostat=istatus)
+ access='STREAM', iostat=istatus) ! , form='FORMATTED',
if(istatus == 0) then
istatus = request_url(mod_url, unit_number, mimetype)