aboutsummaryrefslogtreecommitdiff
path: root/captain/queryutils.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/queryutils.f90')
-rw-r--r--captain/queryutils.f9034
1 files changed, 34 insertions, 0 deletions
diff --git a/captain/queryutils.f90 b/captain/queryutils.f90
index c6b5d83..5e97023 100644
--- a/captain/queryutils.f90
+++ b/captain/queryutils.f90
@@ -24,6 +24,10 @@ implicit none
procedure :: init => query_init
procedure :: destroy => query_destroy
procedure :: component_count => query_component_count
+ procedure :: get_value_by_index => get_query_value_from_index
+ procedure :: get_value_by_key => get_query_value_from_key
+
+ generic, public :: get_value => get_value_by_index, get_value_by_key
end type query
@@ -173,4 +177,34 @@ contains
end subroutine query_destroy
+ function get_query_value_from_index(self, i) result(res)
+ implicit none
+
+ class(query), intent(in)::self
+ integer, intent(in)::i
+ character(len=:), pointer::res
+
+ if(i <= self%component_count()) then
+ res => self%components(i)%value
+ end if
+
+ end function get_query_value_from_index
+
+ function get_query_value_from_key(self, k) result(res)
+ implicit none
+
+ class(query), intent(in)::self
+ character(len=*), intent(in)::k
+ character(len=:), pointer::res
+
+ integer::i
+
+ do i = 1, self%component_count()
+ if(associated(self%components(i)%key) .and. self%components(i)%key == trim(k)) then
+ res => get_query_value_from_index(self, i)
+ end if
+ end do
+
+ end function get_query_value_from_key
+
end module query_utilities