aboutsummaryrefslogtreecommitdiff
path: root/captain/queryutils.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-06-21 11:04:31 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-06-21 11:04:31 -0400
commit20091904b7bf4b2074b45e25c7eee0e56d19348b (patch)
tree5c31004eff65466c84ed88cde77cbc712ba04ea6 /captain/queryutils.f90
parentcd9283417a4b70335edf7ce0c5d15bfca111b807 (diff)
downloadlevitating-20091904b7bf4b2074b45e25c7eee0e56d19348b.tar.gz
levitating-20091904b7bf4b2074b45e25c7eee0e56d19348b.zip
Groups of instructions are now supported, allowing launching multiple jobs at once
Diffstat (limited to 'captain/queryutils.f90')
-rw-r--r--captain/queryutils.f909
1 files changed, 8 insertions, 1 deletions
diff --git a/captain/queryutils.f90 b/captain/queryutils.f90
index 6faec80..4f3d805 100644
--- a/captain/queryutils.f90
+++ b/captain/queryutils.f90
@@ -56,20 +56,23 @@ implicit none
contains
subroutine query_component_parse(self, comptext)
+ use logging
implicit none
class(query_component), intent(out)::self
character(*), intent(in)::comptext
- character(len=:), allocatable::decoded
+ character(len=:), pointer::decoded
integer::i_in, i_out, i_equals, chnum
allocate(character(len=len_trim(comptext)) :: decoded)
+ decoded = " "
i_equals = 0
i_out = 1
i_in = 1
do while(i_in <= len_trim(comptext))
+
if(comptext(i_in:i_in) /= '%') then
decoded(i_out:i_out) = comptext(i_in:i_in)
if(comptext(i_in:i_in) == '=') then
@@ -207,6 +210,8 @@ contains
integer, intent(in)::i
character(len=:), pointer::res
+ res => null()
+
if(i <= self%component_count()) then
res => self%components(i)%value
end if
@@ -222,6 +227,8 @@ contains
integer::i
+ res => null()
+
do i = 1, self%component_count()
if(self%components(i)%has_key()) then
if(self%components(i)%key == trim(k)) then