aboutsummaryrefslogtreecommitdiff
path: root/captain/queryutils.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/queryutils.f90')
-rw-r--r--captain/queryutils.f9021
1 files changed, 11 insertions, 10 deletions
diff --git a/captain/queryutils.f90 b/captain/queryutils.f90
index 4f3d805..550a2f3 100644
--- a/captain/queryutils.f90
+++ b/captain/queryutils.f90
@@ -56,18 +56,18 @@ 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=:), pointer::decoded
- integer::i_in, i_out, i_equals, chnum
-
- allocate(character(len=len_trim(comptext)) :: decoded)
- decoded = " "
-
+ integer::i_in, i_out, i_equals, chnum, n
+
+ n = len_trim(comptext)
+ allocate(character(len=n) :: decoded)
+ decoded = repeat(" ", n)
+
i_equals = 0
i_out = 1
i_in = 1
@@ -100,8 +100,6 @@ contains
self%value = decoded(i_equals+1:len_trim(decoded))
end if
- deallocate(decoded)
-
end subroutine query_component_parse
elemental subroutine query_component_destroy(self)
@@ -130,14 +128,17 @@ contains
end function query_component_has_key
subroutine query_init(self, str)
+ use logging
implicit none
class(query), intent(out)::self
character(len=*), intent(in)::str
+ character(64)::msg
- integer::ampersands, i, i_end, i_comp
+ integer::ampersands, i, i_end, i_comp, n
- allocate(character(len=len_trim(str)) :: self%full)
+ n = len_trim(str)
+ allocate(character(len=n) :: self%full)
self%full = str
ampersands = 0