! Copyright (c) 2021 Approximatrix, LLC ! ! Permission is hereby granted, free of charge, to any person obtaining a copy ! of this software and associated documentation files (the "Software"), to deal ! in the Software without restriction, including without limitation the rights ! to use, copy, modify, merge, publish, distribute, sublicense, and/or sell ! copies of the Software, and to permit persons to whom the Software is ! furnished to do so, subject to the following conditions: ! ! The above copyright notice and this permission notice shall be included in ! all copies or substantial portions of the Software. ! ! The Software shall be used for Good, not Evil. ! ! THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR ! IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, ! FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE ! AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER ! LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, ! OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE ! SOFTWARE. module query_utilities implicit none type :: query_component character(len=:), pointer::key character(len=:), pointer::value contains procedure :: parse => query_component_parse procedure :: destroy => query_component_destroy procedure :: has_key => query_component_has_key end type query_component type :: query character(len=:), pointer::full type(query_component), dimension(:), pointer::components contains procedure :: init => query_init procedure :: init_with_separator => query_init_generic 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 procedure :: has_key => query_has_key generic, public :: get_value => get_value_by_index, get_value_by_key end type query type, extends(query) :: cookies contains procedure :: init => cookies_init end type cookies contains subroutine query_component_parse(self, comptext) implicit none class(query_component), intent(out)::self character(*), intent(in)::comptext character(len=:), pointer::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 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 i_equals = i_out end if i_in = i_in + 1 else i_in = i_in + 1 read(comptext(i_in:i_in+1), '(Z2)') chnum decoded(i_out:i_out) = achar(chnum) i_in = i_in + 2 end if i_out = i_out + 1 end do if(i_equals == 0) then allocate(character(len=len_trim(decoded)) :: self%value) self%value = decoded self%key => null() else allocate(character(len=i_equals-1) :: self%key) self%key = decoded(1:i_equals-1) allocate(character(len=len_trim(decoded)-i_equals) :: self%value) self%value = decoded(i_equals+1:len_trim(decoded)) end if end subroutine query_component_parse elemental subroutine query_component_destroy(self) implicit none class(query_component), intent(inout)::self if(associated(self%key)) then deallocate(self%key) end if if(associated(self%value)) then deallocate(self%value) end if end subroutine query_component_destroy pure function query_component_has_key(self) result(res) implicit none class(query_component), intent(in)::self logical::res res = associated(self%key) end function query_component_has_key subroutine query_init_generic(self, separator, str) use logging implicit none class(query), intent(out)::self character::separator character(len=*), intent(in), optional::str integer::ampersands, i, i_end, i_comp, n self%components => null() self%full => null() if(present(str)) then n = len_trim(str) else n = 0 end if if(n > 0) then allocate(character(len=n) :: self%full) self%full = str ampersands = 0 do i = 1, len(self%full) if(self%full(i:i) == separator) then ampersands = ampersands + 1 end if end do allocate(self%components(ampersands + 1)) ! Split and parse each component if(ampersands == 0) then call self%components(1)%parse(self%full) else i_comp = 1 i = 1 i_end = index(self%full, separator) do while(i_comp < ampersands + 1) call self%components(i_comp)%parse(self%full(i:i_end-1)) i = i_end + 1 do i_end = i, len_trim(self%full) if(self%full(i_end:i_end) == separator) then exit end if end do i_comp = i_comp + 1 end do call self%components(i_comp)%parse(self%full(i:i_end-1)) end if end if end subroutine query_init_generic subroutine query_init(self, str) implicit none class(query)::self character(len=*), intent(in), optional::str if(present(str)) then call query_init_generic(self, "&", str) else call query_init_generic(self, "&") end if end subroutine query_init subroutine cookies_init(self, str) implicit none class(cookies)::self character(len=*), intent(in), optional::str if(present(str)) then call query_init_generic(self, ";", str) else call query_init_generic(self, ";") end if end subroutine cookies_init pure function query_component_count(self) implicit none class(query), intent(in)::self integer::query_component_count if(associated(self%components)) then query_component_count = size(self%components) else query_component_count = 0 end if end function query_component_count subroutine query_destroy(self) implicit none class(query), intent(inout)::self if(associated(self%full)) then deallocate(self%full) self%full => null() end if if(associated(self%components)) then call self%components%destroy() deallocate(self%components) self%components => null() end if 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 res => null() 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 res => null() do i = 1, self%component_count() if(self%components(i)%has_key()) then if(self%components(i)%key == trim(k)) then res => get_query_value_from_index(self, i) end if end if end do end function get_query_value_from_key function query_has_key(self, key) implicit none class(query), intent(in)::self character(*), intent(in)::key logical::query_has_key query_has_key = associated(self%get_value_by_key(key)) end function query_has_key end module query_utilities