I need someone to defeat my string splitting algo

General FreeBASIC programming questions.
Post Reply
dodicat
Posts: 7983
Joined: Jan 10, 2006 20:30
Location: Scotland

Re: I need someone to defeat my string splitting algo

Post by dodicat »

Thanks Marpon.
I have looked through all the posts here, and nobody had invoked strtok.
(Everything but it, I think)
IMHO, a strtok of genius on your part!
marpon
Posts: 342
Joined: Dec 28, 2012 13:31
Location: Paris - France

Re: I need someone to defeat my string splitting algo

Post by marpon »

A faster version improved 25% with 1 loop only
and adaptative redim of the array

I think i will win the challenge !

but remember that split function it is not a split function as vb was giving

for me it is a sort of split_any_delimiter with no empty string token
if you want an split function with all the tokens (even empty string) its a different story ( and slower of course)

Code: Select all

#include "crt/string.bi"   'needed for strtok function
'using strtok(s1 as zstring ptr, s2 as zstring ptr) as zstring ptr only 1 loop
'you can adapt to expected number of tokens to have less redim adaptation, changing the initial i1 value (set to 10 here)
Function String_strtok2(s_in As String , chars As String , result() As String) As Long
   Dim As Long 			ctr   
	dim as zstring ptr	p, p1, p2
	dim as long				i1 = 10  		'initial value to redim result
	dim as string s2 = s_in 				'copy because strtok will alter the input zstring
	
	p = strptr(s2)								'get pointers
	p2= strptr(chars)
	
	p1 = strtok(p , p2)
	while p1 <> NULL 			
		ctr +=1
		if ctr = 1  THEN
			Redim result(1 To i1)  	'redim the array first time
		elseif ctr > i1 then
			i1 *= 2
			redim preserve result(1 To i1)  	'redim the array to give more space (preserved existing content)
		END IF
		result(ctr)= *p1
		p1 = strtok(NULL, p2)
	WEND
	If ctr = 0 Then Return 0
	Redim preserve result(1 To ctr)  	'redim the array to fit exact need (preserved existing content)
   Return Ubound(result)
End Function
'====================================================================================
marpon
Posts: 342
Joined: Dec 28, 2012 13:31
Location: Paris - France

Re: I need someone to defeat my string splitting algo

Post by marpon »

last optimization: with byval s_in As String to avoid to make a copy before using strtok

remind : the strtok function from the clib is very fast but not thread-safe ,
that function incorporates a static value to store the initial pointer and uses it on the consecutive executions,
so that means if you create a multi thread prog using that function it will surely fail.

In most case not a problem, but if you need an other one : thread-safe, contact me,
i 've done 1 some time ago, not as faster as this one (almost 2 x times slower) but even faster than all the versions i've seen here.

Code: Select all

'warning not thread-safe using strtok(s1 as zstring ptr, s2 as zstring ptr) as zstring ptr only 1 loop
Function String_strtok4(byval s_in As String , byref chars As String , result() As String) As Long
   Dim As Long 			ctr   
	dim as zstring ptr	p, p1, p2
	dim as long			 i1 = 10  				'initial value to redim result
		
	p = strptr(s_in)								  'get pointers 
	p2= strptr(chars)
	p1 = strtok(p , p2)
	while p1 <> NULL 			
		ctr +=1
		if ctr = 1  THEN
			Redim result(1 To i1)  				'redim the array first time
		elseif ctr > i1 then
			i1 *= 2
			redim preserve result(1 To i1)  	'redim the array to give more space
		END IF
		result(ctr)= *p1
		p1 = strtok(NULL, p2)
	WEND
	If ctr = 0 Then Return 0
	'redim the array to fit exact need
	if Ubound(result) > ctr THEN  Redim preserve result(1 To ctr)  		
   Return Ubound(result)
End Function
'====================================================================================
WQ1980
Posts: 48
Joined: Sep 25, 2015 12:04
Location: Russia

Re: I need someone to defeat my string splitting algo

Post by WQ1980 »

Marpon
remind : the strtok function from the clib is very fast but not thread-safe ,
that function incorporates a static value to store the initial pointer and uses it on the consecutive executions,
so that means if you create a multi thread prog using that function it will surely fail.
1) compiling in dll
2) call from dll
marpon
Posts: 342
Joined: Dec 28, 2012 13:31
Location: Paris - France

Re: I need someone to defeat my string splitting algo

Post by marpon »

here my thread-safe version

not as fast as the strtok one but faster than all others found here

in fact it mimics the strtok_r existing in some c lib distributions ( _r for re-entrant)

notice also
Function String_strtok_r(Byval s_in As String , Byref chars As String , result() As String, Byval size1 As Long = 1) As Long
Byval is needed because we need a copy of the string , the f_strtok_r function will alter the input string (putting 0 to delimit the elements)

and in function f_strtok_r : Byref ps1 As Byte Ptr , is mandatory because the function will return back the modified ps1 pointer
Function f_strtok_r(Byref ps1 As Byte Ptr, Byref ps2 As Byte Ptr, Byval i As Long )As Byte Ptr

and the adaptative Redim , you can change the size1 optional parameter to try optimizing litle more according your split estimation

'with that version you can avoid dll and any work-arround , it will work safely!

Code: Select all

#include "crt/string.bi"   'needed for memchr function

Declare Function f_strtok_r(Byref ps1 As Byte Ptr, Byref ps2 As Byte Ptr, Byval i As Long )As Byte Ptr

'thread-safe function
Function String_strtok_r(Byval s_in As String , Byref chars As String ,  result() As String, Byval size1 As Long = 1) As Long
	Dim ptemp As Zstring Ptr
	Dim ctr As Long
	Dim As Byte Ptr p = Strptr(s_in)	'get pointers
	Dim As Byte Ptr d = Strptr(chars)
	Dim As Long ilen = Len(chars)
	ptemp = p 
	While ptemp <> NULL
		ptemp = f_strtok_r(p, d, ilen)  ' p is sent byref and it will be modified on the f_strtok_r function 
		if ptemp <> NULL Then
			ctr += 1
			If ctr = 1  Then
				Redim result(1 To size1)  	'redim the array
			Elseif ctr > size1 then
				size1 *= 2
				Redim Preserve result(1 To size1)  	'redim the array
         End If
			result(ctr)= *ptemp
		End If
	Wend
   If ctr = 0 Then Return 0
	If size1 > ctr Then Redim Preserve result(1 To ctr)  	'redim the array
	Return ctr
End Function

Function f_strtok_r(Byref ps1 As Byte Ptr, Byref ps2 As Byte Ptr, Byval i As Long )As Byte Ptr
	Dim p As Byte Ptr

	While memchr(ps2, *ps1,  i) <> NULL
      ps1 += 1
	Wend
	If *ps1 = 0 Then
		ps1 = NULL
		Return NULL
   End If
	p = ps1
	While memchr(ps2, *ps1, i) = NULL  
		ps1 += 1
		if *ps1 = 0 Then Exit While
	Wend
	If *ps1 <> 0 Then
		*ps1 = 0
		ps1 += 1
	End If
	Return p
End Function
marpon
Posts: 342
Joined: Dec 28, 2012 13:31
Location: Paris - France

Re: I need someone to defeat my string splitting algo

Post by marpon »

i've collected from my own archives the different versions of split functions

each of them is optimized for speed

Split : vb6 equivalent function , splits the input string using sub-string as delimiter, consecutive delimiters produce empty elements

Split_noempty : variation of Split, but the empty elements are not collected

Split_any : splits the input string using every char as char delimiter, consecutive char delimiters produce empty elements

Split_tok : variation of Split_any, but the empty elements are not collected, using strtok from c lib , not thread-safe but very fast

Split_tok_r : works as Split_tok , but thread-safe and bit slower

some of them do not need any include, but some need
#include "crt/string.bi" 'needed for strtok/memchr functions

i've put the indication on the source

source code and test comparaison

Code: Select all

'====================================================================================
'splits TEXT using DELIMIT as sub-string delimiter, 
'1 splitted element for each delimiter found or +1  if delimiter does not finish TEXT
' elements can be empty
' vb6 Split equivalent function
'no include needed and thread-safe
'uses array  on the heap, so no problem of capacity with the number of elements < 2147483647
Private Function Split(byref TEXT As String , byref DELIMIT As String , RET() As String) As long
   Dim As long DMAX = 0
   Dim         As long I1
   Dim         As long I2
   Dim         As ulong size = 1
   Dim         As ZString Ptr p
   Dim         As ZString Ptr p1
   Dim         As ZString Ptr p2
	Dim         As ZString Ptr ptemp
   Dim 			As long LDelimit = Len(DELIMIT)
	Dim 			As long LT = Len(TEXT)
   Dim         As uinteger ptr Posi
	Dim         As uinteger ptr Posi2

	If LT = 0 or LDelimit = 0 Or LDelimit > LT Then
      ReDim RET(1 to 1)
      RET(1) = TEXT                              ' copy the full TEXT
      Return 1
   End If
	ptemp = allocate(Len(TEXT) + 1)
	If ptemp = 0 Then Print "Error Allocating p": End
	*ptemp = TEXT                             ' copy the full text
   p1 = ptemp
	p = ptemp
   ' counts the number of element and stores the position on the string
	Do While *p
		I2 = 0
		If p[0] = DELIMIT[0] Then
			p2 = p
			If LDelimit > 1 Then                 ' more than 1 character as delimiter
				For I1 = 1 To LDelimit - 1
					I2 = 0
					If p[1] <> DELIMIT[I1] Then Exit For
					p += 1
					I2 = 1
				Next
			Else
				I2 = 1
			End If
			If I2 = 1 Then
				DMAX += 1
				if DMAX = 1 THEN
					Posi = allocate((size + 1) * sizeof(uinteger))
					If Posi = 0 Then Print "Error Allocating Posi": End
				elseif DMAX > size THEN 		   ' need more space to store the position
					size *= 2
					Posi2 = reallocate(Posi, (size + 1) * sizeof(uinteger))
					If Posi2 = 0 Then Print "Error ReAllocating Posi": End
					Posi = Posi2
				END IF
				Posi[DMAX - 1] = cast(uinteger, p1)
				*p2 = 0									' put null byte to finish the string element
				p1 = p2 + LDelimit
			End If
		End If
		p += 1
	Loop
	if p1 < p THEN
		DMAX += 1
		if DMAX = 1 THEN
			size = 1
			Posi = allocate( sizeof(uinteger) )
			If Posi = 0 Then Print "Error Allocating Posi": End
		end if
		Posi[DMAX - 1] = cast(uinteger, p1)
   END IF
	' dimention the array
	ReDim RET(1 To DMAX)
	' step through the posi array, setting pointers for each element
	For I1 = 1 To DMAX
		RET(I1) = *cptr(zstring ptr, Posi[I1 - 1]) 	' get element, by retrieving the pointer from Posi	array
	Next
	Deallocate (ptemp)
	Deallocate (Posi)
   Return DMAX
End Function
'====================================================================================


'====================================================================================
'splits TEXT using DELIMIT as sub-string delimiter, almost as Split, 
' but only the non-empty elements will be on the RET array 
'no include needed and thread-safe
'uses array on the heap, so no problem of capacity with the number of elements < 2147483647
Private Function Split_noempty(byref TEXT As String , byref DELIMIT As String , RET() As String) As long
   Dim As long DMAX = 0
   Dim         As long I1
   Dim         As long I2
   Dim         As ulong size = 1
   Dim         As ZString Ptr p
   Dim         As ZString Ptr p1
   Dim         As ZString Ptr p2
	Dim         As ZString Ptr ptemp
   Dim 			As long LDelimit = Len(DELIMIT)
	Dim 			As long LT = Len(TEXT)
   Dim         As uinteger ptr Posi
	Dim         As uinteger ptr Posi2

   If LT = 0 Then Return 0
	if size < 1 THEN size = 1
	If LDelimit = 0 Or LDelimit > LT Then
      ReDim RET(1 to 1)
      RET(1) = TEXT                              ' copy the full TEXT
      Return 1
   End If
	ptemp = allocate(Len(TEXT) + 1)
	If ptemp = 0 Then Print "Error Allocating p": End
	*ptemp = TEXT                             ' copy the full text
   p1 = ptemp
	p = ptemp
   ' counts the number of element and stores the position on the string
	Do While *p
		I2 = 0
		If p[0] = DELIMIT[0] Then
			p2 = p
			If LDelimit > 1 Then                 ' more than 1 character as delimiter
				For I1 = 1 To LDelimit - 1
					I2 = 0
					If p[1] <> DELIMIT[I1] Then Exit For
					p += 1
					I2 = 1
				Next
			Else
				I2 = 1
			End If
			If I2 = 1 Then
				*p2 = 0									' put null byte to finish the string element
				if *p1 <> "" then
					DMAX += 1
					if DMAX = 1 THEN
						Posi = allocate((size + 1) * sizeof(uinteger))
						If Posi = 0 Then Print "Error Allocating Posi": End
					elseif DMAX > size THEN 		   ' need more space to store the position
						size *= 2
						Posi2 = reallocate(Posi, (size + 1) * sizeof(uinteger))
						If Posi2 = 0 Then Print "Error ReAllocating Posi": End
						Posi = Posi2
					END IF
					Posi[DMAX - 1] = cast(uinteger, p1)
				end if
				p1 = p2 + LDelimit
			End If
		End If
		p += 1
	Loop
	if p1 < p and *p1 <> "" THEN
		DMAX += 1
		if DMAX = 1 THEN
			size = 1
			Posi = allocate( sizeof(uinteger) )
			If Posi = 0 Then Print "Error Allocating Posi": End
		end if
		Posi[DMAX - 1] = cast(uinteger, p1)
   END IF
	' dimention the array
	ReDim RET(1 To DMAX)
	' step through the posi array, setting pointers for each element
	For I1 = 1 To DMAX
		RET(I1) = *cptr(zstring ptr, Posi[I1 - 1]) 	' get element, by retrieving the pointer from Posi	array
	Next
	Deallocate (ptemp)
	Deallocate (Posi)
   Return DMAX
End Function
'====================================================================================


'====================================================================================
#include "crt/string.bi"   'needed for memchr function
'splits TEXT using every char of DELIMIT as delimiter,  
'1 splitted element for each char delimiter found or +1  if char delimiter does not finish TEXT
' elements can be empty
'uses array on the heap, so no problem of capacity with the number of elements < 2147483647
Private Function Split_any(byref TEXT As String , byref DELIMIT As String , RET() As String) As long
   Dim As long DMAX = 0
   Dim         As long I1
   Dim         As long I2
	Dim         As long L1 = len(TEXT)
	Dim         As long L2 = Len(DELIMIT)
	Dim         As ZString Ptr ptemp
   Dim         As byte Ptr p
   Dim         As byte Ptr p1
	Dim         As byte Ptr p2
	Dim			As ulong size = 1
   Dim         As uinteger ptr Posi
	Dim         As uinteger ptr Posi2
	Dim 			as zstring ptr pdelim = strptr(DELIMIT)

	If L2 = 0 or L1 = 0 Then
      ReDim RET(1 to 1)
      RET(1) = TEXT                              ' copy the full TEXT
      Return 1
   End If
   ptemp = allocate(L1 + 1)
	*ptemp = TEXT                              ' copy the full TEXT
   p1 = ptemp
	p = ptemp
   ' counts the number of element and stores the position on the string
	Do While p[0]
		I2 = 0
		p2 = pdelim
		if l2 = 1 THEN
			if p2[0] = p[0] then I2 = 1
      else
			if memchr(pdelim, p[0], L2)<> 0 THEN I2 = 1
		END IF
		If I2 = 1 Then
			DMAX += 1
			if DMAX = 1 THEN
				Posi = allocate( (size + 1) * sizeof(uinteger) )
				If Posi = 0 Then Print "Error Allocating Posi": End
			elseif DMAX > size THEN 		   ' need more space to store the position
				size *= 2
				Posi2 = reallocate( Posi, (size + 1) * sizeof(uinteger))
				If Posi2 = 0 Then Print "Error ReAllocating Posi": End
				Posi = Posi2
			END IF
			Posi[DMAX - 1] = cast(uinteger, p1)
			*p = 0									' put null byte to finish the string element
			p1 = p + 1
		End If
		p += 1
	Loop
	if p1 < p THEN
		DMAX += 1
		if DMAX = 1 THEN
			size = 1
			Posi = allocate( sizeof(uinteger) )
			If Posi = 0 Then Print "Error Allocating Posi": End
		end if
		Posi[DMAX - 1] = cast(uinteger, p1)
   END IF
	' dimention the array
	ReDim RET(1 To DMAX)
	For I1 = 1 To DMAX
		RET(I1) = *cptr(zstring ptr, Posi[I1 - 1]) 	' get element, by retrieving the pointer from Posi	array
	Next
	Deallocate (ptemp)
	Deallocate (Posi)
   Return DMAX
End Function


'====================================================================================
#include "crt/string.bi"   'needed for strtok function

'splits TEXT using every char of DELIMIT as delimiter,  
'works as Split_any but only the non-empty elements will be on the RET array  
'
'warning not thread-safe using strtok(s1 as zstring ptr, s2 as zstring ptr) as zstring ptr only 1 loop
Private Function Split_tok(byref TEXT As String , byref DELIMIT As String , RET() As String) As Long
   Dim As Long 			ctr
	dim as zstring ptr	p, p1, p2
	dim as ulong			i1 = 1  			'initial value to redim RET
	
	if(len(TEXT) = 0 or len(DELIMIT) = 0) then
		Redim RET(1 To 1) 
		RET(1) = TEXT
		return 1
	end if
	dim as string			s1 = TEXT 		'copy TEXT to avoid alteration of the input
	p = strptr(s1)								'get pointers
	p2= strptr(DELIMIT)
	p1 = strtok(p , p2)
	while p1 <> 0
		ctr +=1
		if ctr = 1  THEN
			Redim RET(1 To i1)  				'redim the array first time
		elseif ctr > i1 then
			i1 *= 2
			redim preserve RET(1 To i1)  	'redim the array to give more space
		END IF
		RET(ctr)= *p1
		p1 = strtok(0, p2)
	WEND
	If ctr = 0 Then Return 0
	'redim the array to fit exact need
	if i1 > ctr THEN  Redim preserve RET(1 To ctr)
   Return ctr
End Function
'====================================================================================


'====================================================================================
#include "crt/string.bi"   'needed for memchr function

'helper function for String_tok_r
Private Function h_tok_r(byref ps1 as byte ptr, byref ps2 as byte ptr, byval i as long )as byte ptr
	dim p as byte ptr
	if i > 1 THEN
		while memchr(ps2, *ps1 ,  i) <> 0
			ps1 += 1
		wend
	else
		while *ps1 = *ps2
			ps1 += 1
		wend	
   END IF	
	if *ps1 = 0 THEN
		ps1 = 0
		return 0
   END IF
	p = ps1
	if i > 1 THEN
		while memchr(ps2, *ps1 , i) = 0  
			ps1 += 1
			if *ps1 = 0 then exit while
		wend
	else
		while *ps1 <> *ps2 
			ps1 += 1
			if *ps1 = 0 then exit while
		wend	
	end if		
	if *ps1 <> 0 THEN
		*ps1 = 0
		ps1 += 1
	end if
	return p
end function  

'------------------------------------------------------------------------------------
'#include "crt/string.bi"   'needed for memchr function
'thread-safe alternative to Split_tok
'splits TEXT using every char of DELIMIT as delimiter,  
'works as Split_any but only the non-empty elements will be on the RET array  
Private Function Split_tok_r(byref TEXT As String , byref DELIMIT As String ,  RET() As String) As Long
	Dim ptemp As Zstring Ptr
	Dim ctr As Long
	Dim size1 As uLong 
	
	dim as long ilen = len(DELIMIT)
	if(len(TEXT) = 0 or ilen = 0) then
		Redim RET(1 To 1) 
		RET(1) = TEXT
		return 1
	end if
	dim as string s1 = TEXT				'copy TEXT to avoid alteration of the input
	dim As byte Ptr p = strptr(s1)	'get pointers
	dim As byte Ptr d = strptr(DELIMIT)
	ptemp = p 
	while ptemp <> 0
		ptemp = h_tok_r(p, d, ilen)  ' p is sent byref and it will be modified on the f_strtok_r function 
		if ptemp <> 0 THEN
			ctr += 1
			if ctr = 1  THEN
				size1 = 1
				Redim RET(1 To size1)  	'redim the array
			elseif ctr > size1 then
				size1 *= 2
				redim preserve RET(1 To size1)  	'redim the array
         END IF
			RET(ctr)= *ptemp
		end if
	WEND
   If ctr = 0 Then Return 0
	if size1 > ctr then Redim preserve RET(1 To ctr)  	'redim the array
	Return ctr
end function
'====================================================================================


'====================================================================================
	'tests
'====================================================================================

'####################################################################################
dim as string s1 = "fortests fforforfor verifications how it is f"
dim as string s2 = "for"
'####################################################################################


dim as long icount
dim as long x
dim as string a()


icount = Split(s1 , s2 , a())
'====================================================================================
print "Split"
print	"initial = >" & s1 & "<" & chr(10) & "delim = >"& s2 & "<" & chr(10)
If LBound( a ) > UBound( a ) Then
	Print "array is empty"
Else
	if ubound(a) <> - 1 then
		print "icount = " & icount & "   lbound = " & lbound(a) & "   ubound = " & ubound(a)
		for x = lbound(a) to icount
			print " x= " & x , ">"& a(x)&"<"
		NEXT
		erase(a)
	end if
End If

Print : print


icount =  Split_noempty(s1 , s2 , a())
'====================================================================================
print "Split_noempty"
print	"initial = >" & s1 & "<" & chr(10) & "delim = >"& s2 & "<" & chr(10)
If LBound( a ) > UBound( a ) Then
	Print "array is empty"
Else
	if ubound(a) <> - 1 then
		print "icount = " & icount & "   lbound = " & lbound(a) & "   ubound = " & ubound(a)
		for x = lbound(a) to icount
			print " x= " & x , ">"& a(x)&"<"
		NEXT
		erase(a)
	end if
End If
Print : print


icount = Split_any(s1 , s2 , a())
'====================================================================================
print "Split_any"
print	"initial = >" & s1 & "<" & chr(10) & "delim = >"& s2 & "<" & chr(10)
If LBound( a ) > UBound( a ) Then
	Print "array is empty"
Else
	if ubound(a) <> - 1 then
		print "icount = " & icount & "   lbound = " & lbound(a) & "   ubound = " & ubound(a)
		for x = lbound(a) to icount
			print " x= " & x , ">"& a(x)&"<"
		NEXT
		erase(a)
	end if
End If
Print : print


icount = Split_tok(s1 , s2 , a())
'====================================================================================
print "Split_tok"
print	"initial = >" & s1 & "<" & chr(10) & "delim = >"& s2 & "<" & chr(10)
If LBound( a ) > UBound( a ) Then
	Print "array is empty"
Else
	if ubound(a) <> - 1 then
		print "icount = " & icount & "   lbound = " & lbound(a) & "   ubound = " & ubound(a)
		for x = lbound(a) to icount
			print " x= " & x , ">"& a(x)&"<"
		NEXT
		erase(a)
	end if
End If
Print : print


icount = Split_tok_r(s1 , s2 , a())
'====================================================================================
print "Split_tok_r"
print	"initial = >" & s1 & "<" & chr(10) & "delim = >"& s2 & "<" & chr(10)
If LBound( a ) > UBound( a ) Then
	Print "array is empty"
Else
	if ubound(a) <> - 1 then
		print "icount = " & icount & "   lbound = " & lbound(a) & "   ubound = " & ubound(a)
		for x = lbound(a) to icount
			print " x= " & x , ">"& a(x)&"<"
		NEXT
		erase(a)
	end if
End If
Print : print

sleep
feel free to test and use...
waiting for comments/remarks or faster solutions
Tourist Trap
Posts: 2958
Joined: Jun 02, 2015 16:24

Re: I need someone to defeat my string splitting algo

Post by Tourist Trap »

marpon wrote:i've collected from my own archives the different versions of split functions
each of them is optimized for speed
feel free to test and use...
waiting for comments/remarks or faster solutions
Thanks, that looks like the ultimate splitter collection.
ike
Posts: 387
Joined: Jan 17, 2011 18:59

Re: I need someone to defeat my string splitting algo

Post by ike »

I use V1ctors split and it works for me well

I tested yours on long string and it crashes

Code: Select all

dim as string txt
dim as integer i
open "data1.txt" for input as #1
line input #1, txt
close #1

'test v1ctor

'split_v1ctor(txt, ":", a())
'for i = 0 to ubound(a)-1
'? a (i)
'next i


split(txt, ":", a())
for i = 0 to ubound(a)-1
? a (i)
next i



Code: Select all

2933 6932 0 2928.587 6924.250000000001 0 D:2928.587 6924.250000000001 0 2924.936000000001 6917.160000000002 0 D:2924.936000000001 6917.160000000002 0 2922.029 6910.67 0 D:2922.029 6910.67 0 2919.848 6904.72 0 D:2919.848 6904.72 0 2918.375 6899.25 0 D:2918.375 6899.25 0 2917.592 6894.2 0 D:2917.592 6894.2 0 2917.481 6889.51 0 D:2917.481 6889.51 0 2918.024 6885.12 0 D:2918.024 6885.12 0 2919.203 6880.97 0 D:2919.203 6880.97 0 2921 6877 0 D:2921 6877 0 2923.1 6873.365000000001 0 D:2923.1 6873.365000000001 0 2924.600000000001 6870.240000000003 0 D:2924.600000000001 6870.240000000003 0 2925.5 6867.594999999999 0 D:2925.5 6867.594999999999 0 2925.8 6865.400000000001 0 D:2925.8 6865.400000000001 0 2925.5 6863.625 0 D:2925.5 6863.625 0 2924.6 6862.24 0 D:2924.6 6862.24 0 2923.1 6861.215 0 D:2923.1 6861.215 0 2921 6860.52 0 D:2921 6860.52 0 2918.3 6860.125 0 D:2918.3 6860.125 0 2915 6860 0 D:2915 6860 0 2912.278000000001 6860.263000000001 0 D:2912.278000000001 6860.263000000001 0 2909.544000000001 6861.024000000001 0 D:2909.544000000001 6861.024000000001 0 2906.846 6862.241 0 D:2906.846 6862.241 0 2904.232 6863.871999999999 0 D:2904.232 6863.871999999999 0 2901.75 6865.875 0 D:2901.75 6865.875 0 2899.448 6868.208 0 D:2899.448 6868.208 0 2897.374 6870.829 0 D:2897.374 6870.829 0 2895.576 6873.696 0 D:2895.576 6873.696 0 2894.102 6876.767 0 D:2894.102 6876.767 0 2893 6880 0 D:2893 6880 0 2890.301 6885.923000000001 0 D:2890.301 6885.923000000001 0 2885.568 6891.024000000001 0 D:2885.568 6891.024000000001 0 2879.347 6895.200999999999 0 D:2879.347 6895.200999999999 0 2872.184000000001 6898.352 0 D:2872.184000000001 6898.352 0 2864.625 6900.375 0 D:2864.625 6900.375 0 2857.216 6901.168 0 D:2857.216 6901.168 0 2850.503 6900.629 0 D:2850.503 6900.629 0 2845.032 6898.656 0 D:2845.032 6898.656 0 2841.349 6895.147 0 D:2841.349 6895.147 0 2840 6890 0 D:2840 6890 0 2839.796 6888.505000000001 0 D:2839.796 6888.505000000001 0 2839.208000000001 6887.040000000002 0 D:2839.208000000001 6887.040000000002 0 2838.272 6885.635 0 D:2838.272 6885.635 0 2837.024 6884.320000000001 0 D:2837.024 6884.320000000001 0 2835.5 6883.125 0 D:2835.5 6883.125 0 2833.735999999999 6882.08 0 D:2833.735999999999 6882.08 0 2831.768 6881.214999999999 0 D:2831.768 6881.214999999999 0 2829.632 6880.56 0 D:2829.632 6880.56 0 2827.364 6880.145 0 D:2827.364 6880.145 0 2825 6880 0 D:2825 6880 0 2822.402 6879.883000000001 0 D:2822.402 6879.883000000001 0 2819.456000000001 6879.544000000002 0 D:2819.456000000001 6879.544000000002 0 2816.234 6879.000999999999 0 D:2816.234 6879.000999999999 0 2812.808 6878.272 0 D:2812.808 6878.272 0 2809.25 6877.375 0 D:2809.25 6877.375 0 2805.632 6876.327999999999 0 D:2805.632 6876.327999999999 0 2802.026 6875.149 0 D:2802.026 6875.149 0 2798.504 6873.856 0 D:2798.504 6873.856 0 2795.138 6872.467 0 D:2795.138 6872.467 0 2792 6871 0 D:2792 6871 0 2783.596000000001 6866.779000000001 0 D:2783.596000000001 6866.779000000001 0 2774.688000000001 6862.552000000002 0 D:2774.688000000001 6862.552000000002 0 2765.432 6858.373 0 D:2765.432 6858.373 0 2755.984 6854.296 0 D:2755.984 6854.296 0 2746.5 6850.375 0 D:2746.5 6850.375 0 2737.136 6846.663999999999 0 D:2737.136 6846.663999999999 0 2728.048 6843.217 0 D:2728.048 6843.217 0 2719.392 6840.088000000001 0 D:2719.392 6840.088000000001 0 2711.324 6837.331 0 D:2711.324 6837.331 0 2704 6835 0 D:2704 6835 0 2699.556000000001 6833.701000000001 0 D:2699.556000000001 6833.701000000001 0 2695.808000000001 6832.168000000002 0 D:2695.808000000001 6832.168000000002 0 2692.732 6830.346999999999 0 D:2692.732 6830.346999999999 0 2690.304000000001 6828.184 0 D:2690.304000000001 6828.184 0 2688.5 6825.625 0 D:2688.5 6825.625 0 2687.295999999999 6822.616 0 D:2687.295999999999 6822.616 0 2686.668 6819.103 0 D:2686.668 6819.103 0 2686.592 6815.032 0 D:2686.592 6815.032 0 2687.044 6810.349 0 D:2687.044 6810.349 0 2688 6805 0 D:2688 6805 0 2688.859 6794.545000000001 0 D:2688.859 6794.545000000001 0 2687.792 6784.120000000003 0 D:2687.792 6784.120000000003 0 2684.733 6773.635 0 D:2684.733 6773.635 0 2679.616 6763.000000000001 0 D:2679.616 6763.000000000001 0 2672.375 6752.125 0 D:2672.375 6752.125 0 2662.944 6740.919999999999 0 D:2662.944 6740.919999999999 0 2651.257 6729.294999999999 0 D:2651.257 6729.294999999999 0 2637.248 6717.16 0 D:2637.248 6717.16 0 2620.851 6704.425 0 D:2620.851 6704.425 0 2602 6691 0 D:2602 6691 0 2580.493 6676.172000000001 0 D:2580.493 6676.172000000001 0 2562.664000000001 6663.336000000002 0 D:2562.664000000001 6663.336000000002 0 2548.351 6652.263999999999 0 D:2548.351 6652.263999999999 0 2537.392 6642.728000000001 0 D:2537.392 6642.728000000001 0 2529.625 6634.5 0 D:2529.625 6634.5 0 2524.888 6627.351999999999 0 D:2524.888 6627.351999999999 0 2523.019 6621.056 0 D:2523.019 6621.056 0 2523.856 6615.384 0 D:2523.856 6615.384 0 2527.237 6610.108 0 D:2527.237 6610.108 0 2533 6605 0 D:2533 6605 0 2540.83 6597.837000000001 0 D:2540.83 6597.837000000001 0 2546.320000000001 6589.576000000002 0 D:2546.320000000001 6589.576000000002 0 2549.469999999999 6580.259 0 D:2549.469999999999 6580.259 0 2550.28 6569.928000000001 0 D:2550.28 6569.928000000001 0 2548.75 6558.625 0 D:2548.75 6558.625 0 2544.88 6546.391999999999 0 D:2544.88 6546.391999999999 0 2538.67 6533.271000000001 0 D:2538.67 6533.271000000001 0 2530.12 6519.304 0 D:2530.12 6519.304 0 2519.23 6504.533 0 D:2519.23 6504.533 0 2506 6489 0 D:2506 6489 0 2481.108000000001 6459.445000000002 0 D:2481.108000000001 6459.445000000002 0 2461.064000000001 6431.600000000001 0 D:2461.064000000001 6431.600000000001 0 2445.916 6405.794999999999 0 D:2445.916 6405.794999999999 0 2435.712 6382.360000000001 0 D:2435.712 6382.360000000001 0 2430.5 6361.625 0 D:2430.5 6361.625 0 2430.328 6343.92 0 D:2430.328 6343.92 0 2435.244 6329.574999999999 0 D:2435.244 6329.574999999999 0 2445.296 6318.92 0 D:2445.296 6318.92 0 2460.532 6312.285 0 D:2460.532 6312.285 0 2481 6310 0 D:2481 6310 0 2484.934000000001 6309.785 0 D:2484.934000000001 6309.785 0 2488.352000000001 6309.120000000001 0 D:2488.352000000001 6309.120000000001 0 2491.278 6307.975 0 D:2491.278 6307.975 0 2493.736 6306.320000000001 0 D:2493.736 6306.320000000001 0 2495.75 6304.125 0 D:2495.75 6304.125 0 2497.344 6301.36 0 D:2497.344 6301.36 0 2498.542 6297.995 0 D:2498.542 6297.995 0 2499.368 6294 0 D:2499.368 6294 0 2499.846 6289.345 0 D:2499.846 6289.345 0 2500 6284 0 D:2500 6284 0 2500.147000000001 6279.606000000002 0 D:2500.147000000001 6279.606000000002 0 2500.576000000001 6274.888000000002 0 D:2500.576000000001 6274.888000000002 0 2501.269 6269.942 0 D:2501.269 6269.942 0 2502.208 6264.864 0 D:2502.208 6264.864 0 2503.375 6259.75 0 D:2503.375 6259.75 0 2504.752 6254.696 0 D:2504.752 6254.696 0 2506.321 6249.798 0 D:2506.321 6249.798 0 2508.064 6245.152 0 D:2508.064 6245.152 0 2509.963 6240.854 0 D:2509.963 6240.854 0 2512 6237 0 D:2512 6237 0 2513.824000000001 6232.153 0 D:2513.824000000001 6232.153 0 2515.672000000001 6224.984000000001 0 D:2515.672000000001 6224.984000000001 0 2517.508 6215.751 0 D:2517.508 6215.751 0 2519.296 6204.712 0 D:2519.296 6204.712 0 2521 6192.125 0 D:2521 6192.125 0 2522.584 6178.248 0 D:2522.584 6178.248 0 2524.012 6163.339 0 D:2524.012 6163.339 0 2525.248 6147.656 0 D:2525.248 6147.656 0 2526.256 6131.457 0 D:2526.256 6131.457 0 2527 6115 0 D:2527 6115 0 2528.423 6082.686000000002 0 D:2528.423 6082.686000000002 0 2530.344000000001 6053.888000000001 0 D:2530.344000000001 6053.888000000001 0 2532.841 6028.222 0 D:2532.841 6028.222 0 2535.992 6005.304 0 D:2535.992 6005.304 0 2539.875 5984.75 0 D:2539.875 5984.75 0 2544.568 5966.176 0 D:2544.568 5966.176 0 2550.149 5949.197999999999 0 D:2550.149 5949.197999999999 0 2556.696 5933.432 0 D:2556.696 5933.432 0 2564.287 5918.494 0 D:2564.287 5918.494 0 2573 5904 0 D:2573 5904 0 2581.680000000001 5892.275000000001 0 D:2581.680000000001 5892.275000000001 0 2590.72 5882.920000000002 0 D:2590.72 5882.920000000002 0 2599.82 5875.964999999999 0 D:2599.82 5875.964999999999 0 2608.68 5871.440000000001 0 D:2608.68 5871.440000000001 0 2617 5869.375 0 D:2617 5869.375 0 2624.48 5869.799999999999 0 D:2624.48 5869.799999999999 0 2630.82 5872.745 0 D:2630.82 5872.745 0 2635.72 5878.24 0 D:2635.72 5878.24 0 2638.88 5886.315 0 D:2638.88 5886.315 0 2640 5897 0 D:2640 5897 0 2640.35 5901.715000000001 0 D:2640.35 5901.715000000001 0 2641.360000000001 5907.360000000002 0 D:2641.360000000001 5907.360000000002 0 2642.97 5913.785 0 D:2642.97 5913.785 0 2645.12 5920.84 0 D:2645.12 5920.84 0 2647.75 5928.375 0 D:2647.75 5928.375 0 2650.8 5936.239999999999 0 D:2650.8 5936.239999999999 0 2654.21 5944.285 0 D:2654.21 5944.285 0 2657.92 5952.36 0 D:2657.92 5952.36 0 2661.87 5960.315 0 D:2661.87 5960.315 0 2666 5968 0 D:2666 5968 0 2675.641000000001 5983.755 0 D:2675.641000000001 5983.755 0 2683.728000000001 5994.680000000001 0 D:2683.728000000001 5994.680000000001 0 2690.507 6000.264999999999 0 D:2690.507 6000.264999999999 0 2696.224 6000.000000000001 0 D:2696.224 6000.000000000001 0 2701.125 5993.375 0 D:2701.125 5993.375 0 2705.456 5979.88 0 D:2705.456 5979.88 0 2709.463 5959.005 0 D:2709.463 5959.005 0 2713.392 5930.240000000001 0 D:2713.392 5930.240000000001 0 2717.489 5893.075 0 D:2717.489 5893.075 0 2722 5847 0 D:2722 5847 0 2725.293 5806.772000000001 0 D:2725.293 5806.772000000001 0 2727.344000000001 5772.256 0 D:2727.344000000001 5772.256 0 2728.111 5743.103999999999 0 D:2728.111 5743.103999999999 0 2727.552 5718.968 0 D:2727.552 5718.968 0 2725.625 5699.5 0 D:2725.625 5699.5 0 2722.288 5684.351999999999 0 D:2722.288 5684.351999999999 0 2717.499 5673.176 0 D:2717.499 5673.176 0 2711.216 5665.624 0 D:2711.216 5665.624 0 2703.397 5661.348 0 D:2703.397 5661.348 0 2694 5660 0 D:2694 5660 0 2690.427 5659.769000000001 0 D:2690.427 5659.769000000001 0 2687.496000000001 5658.992000000002 0 D:2687.496000000001 5658.992000000002 0 2685.189 5657.543 0 D:2685.189 5657.543 0 2683.488 5655.295999999999 0 D:2683.488 5655.295999999999 0 2682.375 5652.125 0 D:2682.375 5652.125 0 2681.832 5647.904000000001 0 D:2681.832 5647.904000000001 0 2681.841 5642.507 0 D:2681.841 5642.507 0 2682.384 5635.808 0 D:2682.384 5635.808 0 2683.443 5627.681 0 D:2683.443 5627.681 0 2685 5618 0 D:2685 5618 0 2687.567000000001 5603.762000000001 0 D:2687.567000000001 5603.762000000001 0 2689.936000000001 5592.176000000001 0 D:2689.936000000001 5592.176000000001 0 2692.209 5583.134 0 D:2692.209 5583.134 0 2694.488 5576.528 0 D:2694.488 5576.528 0 2696.875 5572.25 0 D:2696.875 5572.25 0 2699.472 5570.191999999999 0 D:2699.472 5570.191999999999 0 2702.381 5570.246 0 D:2702.381 5570.246 0 2705.704 5572.304 0 D:2705.704 5572.304 0 2709.543 5576.258 0 D:2709.543 5576.258 0 2714 5582 0 D:2714 5582 0 2718.690000000001 5587.002000000001 0 D:2718.690000000001 5587.002000000001 0 2724.160000000001 5590.096000000002 0 D:2724.160000000001 5590.096000000002 0 2730.11 5591.414 0 D:2730.11 5591.414 0 2736.24 5591.088 0 D:2736.24 5591.088 0 2742.25 5589.25 0 D:2742.25 5589.25 0 2747.84 5586.031999999999 0 D:2747.84 5586.031999999999 0 2752.71 5581.566 0 D:2752.71 5581.566 0 2756.56 5575.984 0 D:2756.56 5575.984 0 2759.09 5569.418 0 D:2759.09 5569.418 0 2760 5562 0 D:2760 5562 0 2760.903 5555.441000000002 0 D:2760.903 5555.441000000002 0 2762.904000000001 5548.528000000001 0 D:2762.904000000001 5548.528000000001 0 2765.841 5541.507000000001 0 D:2765.841 5541.507000000001 0 2769.552 5534.624000000001 0 D:2769.552 5534.624000000001 0 2773.875 5528.125 0 D:2773.875 5528.125 0 2778.648 5522.255999999999 0 D:2778.648 5522.255999999999 0 2783.709 5517.263 0 D:2783.709 5517.263 0 2788.896 5513.392000000001 0 D:2788.896 5513.392000000001 0 2794.047 5510.889 0 D:2794.047 5510.889 0 2799 5510 0 D:2799 5510 0 2800.766 5509.824000000001 0 D:2800.766 5509.824000000001 0 2802.448000000001 5509.312000000002 0 D:2802.448000000001 5509.312000000002 0 2804.022 5508.487999999999 0 D:2804.022 5508.487999999999 0 2805.464 5507.376 0 D:2805.464 5507.376 0 2806.75 5506 0 D:2806.75 5506 0 2807.856 5504.383999999999 0 D:2807.856 5504.383999999999 0 2808.758 5502.552 0 D:2808.758 5502.552 0 2809.432 5500.528 0 D:2809.432 5500.528 0 2809.854 5498.336 0 D:2809.854 5498.336 0 2810 5496 0 D:2810 5496 0 2810.585 5493.168000000001 0 D:2810.585 5493.168000000001 0 2812.280000000001 5489.544000000002 0 D:2812.280000000001 5489.544000000002 0 2814.995 5485.236 0 D:2814.995 5485.236 0 2818.64 5480.352000000001 0 D:2818.64 5480.352000000001 0 2823.125 5475 0 D:2823.125 5475 0 2828.36 5469.288 0 D:2828.36 5469.288 0 2834.255 5463.324 0 D:2834.255 5463.324 0 2840.72 5457.216 0 D:2840.72 5457.216 0 2847.665 5451.072 0 D:2847.665 5451.072 0 2855 5445 0 D:2855.000000 5445.000000 0 2899.000000 5408.000000 0 D:2899.000000 5408.000000 0 2870.000000 5356.000000 0 D:2870 5356 0 2865.029000000001 5347.205000000001 0 D:2865.029000000001 5347.205000000001 0 2860.352 5338.320000000002 0 D:2860.352 5338.320000000002 0 2856.023 5329.495 0 D:2856.023 5329.495 0 2852.096000000001 5320.88 0 D:2852.096000000001 5320.88 0 2848.625 5312.625 0 D:2848.625 5312.625 0 2845.664 5304.88 0 D:2845.664 5304.88 0 2843.267 5297.795 0 D:2843.267 5297.795 0 2841.488 5291.52 0 D:2841.488 5291.52 0 2840.381 5286.205 0 D:2840.381 5286.205 0 2840 5282 0 D:2840 5282 0 2839.737000000001 5278.321000000001 0 D:2839.737000000001 5278.321000000001 0 2838.976000000001 5274.528000000002 0 D:2838.976000000001 5274.528000000002 0 2837.759 5270.686999999999 0 D:2837.759 5270.686999999999 0 2836.128 5266.864000000001 0 D:2836.128 5266.864000000001 0 2834.125 5263.125 0 D:2834.125 5263.125 0 2831.792 5259.536 0 D:2831.792 5259.536 0 2829.171 5256.163 0 D:2829.171 5256.163 0 2826.304 5253.072 0 D:2826.304 5253.072 0 2823.233 5250.329 0 D:2823.233 5250.329 0 2820 5248 0 D:2820 5248 0 2816.767 5245.702 0 D:2816.767 5245.702 0 2813.696000000001 5243.056000000001 0 D:2813.696000000001 5243.056000000001 0 2810.829 5240.134 0 D:2810.829 5240.134 0 2808.208 5237.008 0 D:2808.208 5237.008 0 2805.875 5233.75 0 D:2805.875 5233.75 0 2803.871999999999 5230.432 0 D:2803.871999999999 5230.432 0 2802.241 5227.126 0 D:2802.241 5227.126 0 2801.024 5223.904000000001 0 D:2801.024 5223.904000000001 0 2800.263 5220.838 0 D:2800.263 5220.838 0 2800 5218 0 D:2800 5218 0 2799.97 5215.066 0 D:2799.97 5215.066 0 2799.880000000001 5212.288000000001 0 D:2799.880000000001 5212.288000000001 0 2799.73 5209.701999999999 0 D:2799.73 5209.701999999999 0 2799.52 5207.344 0 D:2799.52 5207.344 0 2799.25 5205.25 0 D:2799.25 5205.25 0 2798.92 5203.456 0 D:2798.92 5203.456 0 2798.53 5201.998 0 D:2798.53 5201.998 0 2798.08 5200.912 0 D:2798.08 5200.912 0 2797.57 5200.234 0 D:2797.57 5200.234 0 2797 5200 0 D:2797 5200 0 2795.525000000001 5200.438000000001 0 D:2795.525000000001 5200.438000000001 0 2792.400000000001 5201.704000000001 0 D:2792.400000000001 5201.704000000001 0 2787.775 5203.726 0 D:2787.775 5203.726 0 2781.8 5206.432000000001 0 D:2781.8 5206.432000000001 0 2774.625 5209.75 0 D:2774.625 5209.75 0 2766.4 5213.607999999999 0 D:2766.4 5213.607999999999 0 2757.275 5217.934 0 D:2757.275 5217.934 0 2747.4 5222.656 0 D:2747.4 5222.656 0 2736.925 5227.702 0 D:2736.925 5227.702 0 2726 5233 0 D:2726 5233 0 2709.867 5240.966 0 D:2709.867 5240.966 0 2696.056000000001 5248.248000000001 0 D:2696.056000000001 5248.248000000001 0 2684.249 5255.121999999999 0 D:2684.249 5255.121999999999 0 2674.128 5261.864 0 D:2674.128 5261.864 0 2665.375 5268.75 0 D:2665.375 5268.75 0 2657.672 5276.056 0 D:2657.672 5276.056 0 2650.701 5284.058 0 D:2650.701 5284.058 0 2644.144 5293.032 0 D:2644.144 5293.032 0 2637.683 5303.254 0 D:2637.683 5303.254 0 2631 5315 0 D:2631 5315 0 2616.934000000001 5337.081000000001 0 D:2616.934000000001 5337.081000000001 0 2603.312 5352.568000000001 0 D:2603.312 5352.568000000001 0 2590.698 5361.826999999999 0 D:2590.698 5361.826999999999 0 2579.656 5365.224 0 D:2579.656 5365.224 0 2570.75 5363.125 0 D:2570.75 5363.125 0 2564.544 5355.896 0 D:2564.544 5355.896 0 2561.602 5343.903 0 D:2561.602 5343.903 0 2562.488 5327.512 0 D:2562.488 5327.512 0 2567.766 5307.089 0 D:2567.766 5307.089 0 2578 5283 0 D:2578 5283 0 2586.094000000001 5268.611000000001 0 D:2586.094000000001 5268.611000000001 0 2594.992000000001 5255.248000000001 0 D:2594.992000000001 5255.248000000001 0 2605.018 5242.616999999999 0 D:2605.018 5242.616999999999 0 2616.496 5230.424000000001 0 D:2616.496 5230.424000000001 0 2629.75 5218.375 0 D:2629.75 5218.375 0 2645.104 5206.176 0 D:2645.104 5206.176 0 2662.882 5193.533 0 D:2662.882 5193.533 0 2683.408 5180.152 0 D:2683.408 5180.152 0 2707.006 5165.739 0 D:2707.006 5165.739 0 2734 5150 0 D:2734 5150 0 2766.304 5131.351000000001 0 D:2766.304 5131.351000000001 0 2793.472000000001 5114.448000000001 0 D:2793.472000000001 5114.448000000001 0 2816.188 5098.457 0 D:2816.188 5098.457 0 2835.136 5082.544000000001 0 D:2835.136 5082.544000000001 0 2851 5065.875 0 D:2851 5065.875 0 2864.464 5047.616 0 D:2864.464 5047.616 0 2876.212 5026.933 0 D:2876.212 5026.933 0 2886.928 5002.992 0 D:2886.928 5002.992 0 2897.296 4974.959 0 D:2897.296 4974.959 0 2908 4942 0 D:2908.000000 4942.000000 0 2941.000000 4841.000000 0 D:2941.000000 4841.000000 0 2980.000000 4868.000000 0 D:2980 4868 0 2988.136 4873.555000000001 0 D:2988.136 4873.555000000001 0 2995.168000000001 4878.840000000001 0 D:2995.168000000001 4878.840000000001 0 3001.132 4883.884999999999 0 D:3001.132 4883.884999999999 0 3006.064 4888.72 0 D:3006.064 4888.72 0 3010 4893.375 0 D:3010 4893.375 0 3012.976 4897.879999999999 0 D:3012.976 4897.879999999999 0 3015.028 4902.264999999999 0 D:3015.028 4902.264999999999 0 3016.192 4906.56 0 D:3016.192 4906.56 0 3016.504 4910.795 0 D:3016.504 4910.795 0 3016 4915 0 D:3016 4915 0 3015.168000000001 4919.314 0 D:3015.168000000001 4919.314 0 3013.904000000001 4925.512000000002 0 D:3013.904000000001 4925.512000000002 0 3012.256 4933.378 0 D:3012.256 4933.378 0 3010.272 4942.696 0 D:3010.272 4942.696 0 3008 4953.25 0 D:3008 4953.25 0 3005.487999999999 4964.824 0 D:3005.487999999999 4964.824 0 3002.784 4977.201999999999 0 D:3002.784 4977.201999999999 0 2999.936 4990.168000000001 0 D:2999.936 4990.168000000001 0 2996.992 5003.506 0 D:2996.992 5003.506 0 2994 5017 0 D:2994 5017 0 2989.144 5039.318 0 D:2989.144 5039.318 0 2985.392000000001 5057.664000000002 0 D:2985.392000000001 5057.664000000002 0 2982.768 5072.926 0 D:2982.768 5072.926 0 2981.296 5085.992 0 D:2981.296 5085.992 0 2981 5097.75 0 D:2981 5097.75 0 2981.904 5109.088 0 D:2981.904 5109.088 0 2984.032 5120.894 0 D:2984.032 5120.894 0 2987.408 5134.056000000001 0 D:2987.408 5134.056000000001 0 2992.056 5149.462 0 D:2992.056 5149.462 0 2998 5168 0 D:2998 5168 0 3001.532000000001 5179.605000000001 0 D:3001.532000000001 5179.605000000001 0 3004.896000000001 5191.480000000001 0 D:3004.896000000001 5191.480000000001 0 3008.044 5203.415 0 D:3008.044 5203.415 0 3010.928 5215.200000000001 0 D:3010.928 5215.200000000001 0 3013.5 5226.625 0 D:3013.5 5226.625 0 3015.712 5237.48 0 D:3015.712 5237.48 0 3017.516 5247.555 0 D:3017.516 5247.555 0 3018.864 5256.64 0 D:3018.864 5256.64 0 3019.708 5264.525 0 D:3019.708 5264.525 0 3020 5271 0 D:3020 5271 0 3020.263 5276.977000000002 0 D:3020.263 5276.977000000002 0 3021.024000000001 5283.416000000002 0 D:3021.024000000001 5283.416000000002 0 3022.241 5290.179 0 D:3022.241 5290.179 0 3023.872 5297.128000000001 0 D:3023.872 5297.128000000001 0 3025.875 5304.125 0 D:3025.875 5304.125 0 3028.208 5311.031999999999 0 D:3028.208 5311.031999999999 0 3030.829 5317.710999999999 0 D:3030.829 5317.710999999999 0 3033.696 5324.024 0 D:3033.696 5324.024 0 3036.767 5329.833 0 D:3036.767 5329.833 0 3040 5335 0 D:3040 5335 0 3046.272 5344.765000000001 0 D:3046.272 5344.765000000001 0 3051.296000000001 5353.120000000002 0 D:3051.296000000001 5353.120000000002 0 3055.084 5360.155 0 D:3055.084 5360.155 0 3057.648 5365.96 0 D:3057.648 5365.96 0 3059 5370.625 0 D:3059 5370.625 0 3059.152 5374.24 0 D:3059.152 5374.24 0 3058.116 5376.895 0 D:3058.116 5376.895 0 3055.904 5378.68 0 D:3055.904 5378.68 0 3052.528 5379.685 0 D:3052.528 5379.685 0 3048 5380 0 D:3048 5380 0 3045.673000000001 5380.351000000001 0 D:3045.673000000001 5380.351000000001 0 3042.944000000001 5381.368000000002 0 D:3042.944000000001 5381.368000000002 0 3039.891 5382.996999999999 0 D:3039.891 5382.996999999999 0 3036.592 5385.184 0 D:3036.592 5385.184 0 3033.125 5387.875 0 D:3033.125 5387.875 0 3029.568 5391.016 0 D:3029.568 5391.016 0 3025.999 5394.553 0 D:3025.999 5394.553 0 3022.496 5398.432 0 D:3022.496 5398.432 0 3019.137 5402.599 0 D:3019.137 5402.599 0 3016 5407 0 D:3016 5407 0 3011.407 5413.326000000001 0 D:3011.407 5413.326000000001 0 3007.816000000001 5418.608000000001 0 D:3007.816000000001 5418.608000000001 0 3005.209 5423.002 0 D:3005.209 5423.002 0 3003.568 5426.664000000001 0 D:3003.568 5426.664000000001 0 3002.875 5429.75 0 D:3002.875 5429.75 0 3003.112 5432.415999999999 0 D:3003.112 5432.415999999999 0 3004.261 5434.818 0 D:3004.261 5434.818 0 3006.304 5437.112 0 D:3006.304 5437.112 0 3009.223 5439.454 0 D:3009.223 5439.454 0 3013 5442 0 D:3013 5442 0 3015.81 5443.759000000001 0 D:3015.81 5443.759000000001 0 3018.800000000001 5445.992000000001 0 D:3018.800000000001 5445.992000000001 0 3021.91 5448.632999999999 0 D:3021.91 5448.632999999999 0 3025.08 5451.616 0 D:3025.08 5451.616 0 3028.25 5454.875 0 D:3028.25 5454.875 0 3031.36 5458.343999999999 0 D:3031.36 5458.343999999999 0 3034.35 5461.956999999999 0 D:3034.35 5461.956999999999 0 3037.16 5465.648 0 D:3037.16 5465.648 0 3039.73 5469.351 0 D:3039.73 5469.351 0 3042 5473 0 D:3042 5473 0 3046.462 5483.323000000001 0 D:3046.462 5483.323000000001 0 3050.216000000001 5496.304000000002 0 D:3050.216000000001 5496.304000000002 0 3053.214 5511.061 0 D:3053.214 5511.061 0 3055.408 5526.712 0 D:3055.408 5526.712 0 3056.75 5542.375 0 D:3056.75 5542.375 0 3057.192 5557.168 0 D:3057.192 5557.168 0 3056.686 5570.209 0 D:3056.686 5570.209 0 3055.184 5580.616 0 D:3055.184 5580.616 0 3052.638 5587.507 0 D:3052.638 5587.507 0 3049 5590 0 D:3049 5590 0 3047.079000000001 5590.418000000001 0 D:3047.079000000001 5590.418000000001 0 3045.512000000001 5591.664000000002 0 D:3045.512000000001 5591.664000000002 0 3044.293 5593.726 0 D:3044.293 5593.726 0 3043.416 5596.592 0 D:3043.416 5596.592 0 3042.875 5600.25 0 D:3042.875 5600.25 0 3042.664 5604.688 0 D:3042.664 5604.688 0 3042.777 5609.893999999999 0 D:3042.777 5609.893999999999 0 3043.208 5615.856 0 D:3043.208 5615.856 0 3043.951 5622.562 0 D:3043.951 5622.562 0 3045 5630 0 D:3045 5630 0 3046.316 5638.653000000001 0 D:3046.316 5638.653000000001 0 3047.248000000001 5646.064000000001 0 D:3047.248000000001 5646.064000000001 0 3047.772 5652.311 0 D:3047.772 5652.311 0 3047.864000000001 5657.472000000001 0 D:3047.864000000001 5657.472000000001 0 3047.5 5661.625 0 D:3047.5 5661.625 0 3046.656 5664.848 0 D:3046.656 5664.848 0 3045.308 5667.219 0 D:3045.308 5667.219 0 3043.432 5668.816 0 D:3043.432 5668.816 0 3041.004 5669.717 0 D:3041.004 5669.717 0 3038 5670 0 D:3038 5670 0 3032.929000000001 5669.127 0 D:3032.929000000001 5669.127 0 3027.912000000001 5666.496000000002 0 D:3027.912000000001 5666.496000000002 0 3022.943 5662.089 0 D:3022.943 5662.089 0 3018.016 5655.888000000001 0 D:3018.016 5655.888000000001 0 3013.125 5647.875 0 D:3013.125 5647.875 0 3008.264 5638.031999999999 0 D:3008.264 5638.031999999999 0 3003.427 5626.340999999999 0 D:3003.427 5626.340999999999 0 2998.608 5612.784000000001 0 D:2998.608 5612.784000000001 0 2993.801 5597.343 0 D:2993.801 5597.343 0 2989 5580 0 D:2989 5580 0 2986.442000000001 5570.118 0 D:2986.442000000001 5570.118 0 2984.136 5562.024000000001 0 D:2984.136 5562.024000000001 0 2982.034 5555.646000000001 0 D:2982.034 5555.646000000001 0 2980.088 5550.912 0 D:2980.088 5550.912 0 2978.25 5547.75 0 D:2978.25 5547.75 0 2976.472 5546.087999999999 0 D:2976.472 5546.087999999999 0 2974.706 5545.853999999999 0 D:2974.706 5545.853999999999 0 2972.904 5546.976 0 D:2972.904 5546.976 0 2971.018 5549.382 0 D:2971.018 5549.382 0 2969 5553 0 D:2969 5553 0 2966.91 5555.906000000001 0 D:2966.91 5555.906000000001 0 2964.280000000001 5558.608000000002 0 D:2964.280000000001 5558.608000000002 0 2961.17 5561.082 0 D:2961.17 5561.082 0 2957.64 5563.304000000001 0 D:2957.64 5563.304000000001 0 2953.75 5565.25 0 D:2953.75 5565.25 0 2949.56 5566.896 0 D:2949.56 5566.896 0 2945.13 5568.218 0 D:2945.13 5568.218 0 2940.52 5569.192 0 D:2940.52 5569.192 0 2935.79 5569.794 0 D:2935.79 5569.794 0 2931 5570 0 D:2931 5570 0 2913.629 5571.302000000001 0 D:2913.629 5571.302000000001 0 2899.072 5576.096000000001 0 D:2899.072 5576.096000000001 0 2886.963 5585.714 0 D:2886.963 5585.714 0 2876.936000000001 5601.488 0 D:2876.936000000001 5601.488 0 2868.625 5624.75 0 D:2868.625 5624.75 0 2861.664 5656.831999999999 0 D:2861.664 5656.831999999999 0 2855.687 5699.066 0 D:2855.687 5699.066 0 2850.328 5752.784000000001 0 D:2850.328 5752.784000000001 0 2845.221 5819.318 0 D:2845.221 5819.318 0 2840 5900 0 D:2840 5900 0 2836.356000000001 5967.81 0 D:2836.356000000001 5967.81 0 2834.608000000001 6025.720000000002 0 D:2834.608000000001 6025.720000000002 0 2835.032 6075.05 0 D:2835.032 6075.05 0 2837.904000000001 6117.12 0 D:2837.904000000001 6117.12 0 2843.5 6153.25 0 D:2843.5 6153.25 0 2852.096 6184.759999999999 0 D:2852.096 6184.759999999999 0 2863.968 6212.969999999999 0 D:2863.968 6212.969999999999 0 2879.392 6239.200000000001 0 D:2879.392 6239.200000000001 0 2898.644 6264.77 0 D:2898.644 6264.77 0 2922 6291 0 D:2922 6291 0 2933.587 6302.976000000001 0 D:2933.587 6302.976000000001 0 2943.776000000001 6313.128000000002 0 D:2943.776000000001 6313.128000000002 0 2952.609 6321.492 0 D:2952.609 6321.492 0 2960.128000000001 6328.104 0 D:2960.128000000001 6328.104 0 2966.375 6333 0 D:2966.375 6333 0 2971.391999999999 6336.215999999999 0 D:2971.391999999999 6336.215999999999 0 2975.221 6337.788 0 D:2975.221 6337.788 0 2977.904 6337.752 0 D:2977.904 6337.752 0 2979.483 6336.144 0 D:2979.483 6336.144 0 2980 6333 0 D:2980 6333 0 2980.997 6324.174000000001 0 D:2980.997 6324.174000000001 0 2983.296000000001 6315.792000000001 0 D:2983.296000000001 6315.792000000001 0 2986.759 6307.998000000001 0 D:2986.759 6307.998000000001 0 2991.248000000001 6300.936 0 D:2991.248000000001 6300.936 0 2996.625 6294.75 0 D:2996.625 6294.75 0 3002.752 6289.584 0 D:3002.752 6289.584 0 3009.491 6285.582 0 D:3009.491 6285.582 0 3016.704 6282.888 0 D:3016.704 6282.888 0 3024.253 6281.646 0 D:3024.253 6281.646 0 3032 6282 0 D:3032 6282 0 3042.600000000001 6286.197000000001 0 D:3042.600000000001 6286.197000000001 0 3052.720000000001 6295.536000000002 0 D:3052.720000000001 6295.536000000002 0 3062.239999999999 6309.639 0 D:3062.239999999999 6309.639 0 3071.04 6328.128000000001 0 D:3071.04 6328.128000000001 0 3079 6350.625 0 D:3079 6350.625 0 3086 6376.752 0 D:3086 6376.752 0 3091.92 6406.130999999999 0 D:3091.92 6406.130999999999 0 3096.64 6438.384 0 D:3096.64 6438.384 0 3100.04 6473.133 0 D:3100.04 6473.133 0 3102 6510 0 D:3102 6510 0 3102.658 6526.165000000001 0 D:3102.658 6526.165000000001 0 3103.424000000001 6541.520000000002 0 D:3103.424000000001 6541.520000000002 0 3104.286 6555.855 0 D:3104.286 6555.855 0 3105.232 6568.96 0 D:3105.232 6568.96 0 3106.25 6580.625 0 D:3106.25 6580.625 0 3107.328 6590.64 0 D:3107.328 6590.64 0 3108.454 6598.795 0 D:3108.454 6598.795 0 3109.616 6604.88 0 D:3109.616 6604.88 0 3110.802 6608.685 0 D:3110.802 6608.685 0 3112 6610 0 D:3112 6610 0 3113.569 6609.182000000001 0 D:3113.569 6609.182000000001 0 3116.392000000001 6606.816000000002 0 D:3116.392000000001 6606.816000000002 0 3120.343 6603.034000000001 0 D:3120.343 6603.034000000001 0 3125.296 6597.968 0 D:3125.296 6597.968 0 3131.125 6591.75 0 D:3131.125 6591.75 0 3137.704 6584.511999999999 0 D:3137.704 6584.511999999999 0 3144.907 6576.386 0 D:3144.907 6576.386 0 3152.608 6567.504 0 D:3152.608 6567.504 0 3160.681 6557.998 0 D:3160.681 6557.998 0 3169 6548 0 D:3169 6548 0 3183.624 6530.312 0 D:3183.624 6530.312 0 3197.432000000001 6514.496000000002 0 D:3197.432000000001 6514.496000000002 0 3210.328 6500.624 0 D:3210.328 6500.624 0 3222.216 6488.768 0 D:3222.216 6488.768 0 3233 6479 0 D:3233 6479 0 3242.584 6471.392 0 D:3242.584 6471.392 0 3250.872 6466.016 0 D:3250.872 6466.016 0 3257.768 6462.944 0 D:3257.768 6462.944 0 3263.176 6462.248 0 D:3263.176 6462.248 0 3267 6464 0 D:3267 6464 0 3267.752 6465.044000000001 0 D:3267.752 6465.044000000001 0 3268.216000000001 6466.352000000002 0 D:3268.216000000001 6466.352000000002 0 3268.404 6467.888 0 D:3268.404 6467.888 0 3268.328 6469.616 0 D:3268.328 6469.616 0 3268 6471.5 0 D:3268 6471.5 0 3267.432 6473.504 0 D:3267.432 6473.504 0 3266.636 6475.592 0 D:3266.636 6475.592 0 3265.624 6477.728 0 D:3265.624 6477.728 0 3264.408 6479.876 0 D:3264.408 6479.876 0 3263 6482 0 D:3263 6482 0 3261.271000000001 6484.736000000001 0 D:3261.271000000001 6484.736000000001 0 3259.128000000001 6488.648000000002 0 D:3259.128000000001 6488.648000000002 0 3256.637 6493.592 0 D:3256.637 6493.592 0 3253.864 6499.424000000001 0 D:3253.864 6499.424000000001 0 3250.875 6506 0 D:3250.875 6506 0 3247.735999999999 6513.176 0 D:3247.735999999999 6513.176 0 3244.513 6520.808 0 D:3244.513 6520.808 0 3241.272 6528.752 0 D:3241.272 6528.752 0 3238.079 6536.864 0 D:3238.079 6536.864 0 3235 6545 0 D:3235 6545 0 3231.569000000001 6554.198000000001 0 D:3231.569000000001 6554.198000000001 0 3227.352000000001 6564.824000000002 0 D:3227.352000000001 6564.824000000002 0 3222.463 6576.626 0 D:3222.463 6576.626 0 3217.016 6589.352000000001 0 D:3217.016 6589.352000000001 0 3211.125 6602.75 0 D:3211.125 6602.75 0 3204.904 6616.567999999999 0 D:3204.904 6616.567999999999 0 3198.467 6630.553999999999 0 D:3198.467 6630.553999999999 0 3191.928 6644.456 0 D:3191.928 6644.456 0 3185.401 6658.022 0 D:3185.401 6658.022 0 3179 6671 0 D:3179 6671 0 3172.753000000001 6684.203 0 D:3172.753000000001 6684.203 0 3166.104000000001 6698.984 0 D:3166.104000000001 6698.984 0 3159.191 6715.000999999999 0 D:3159.191 6715.000999999999 0 3152.152 6731.912 0 D:3152.152 6731.912 0 3145.125 6749.375 0 D:3145.125 6749.375 0 3138.248 6767.048 0 D:3138.248 6767.048 0 3131.659 6784.589 0 D:3131.659 6784.589 0 3125.496 6801.656 0 D:3125.496 6801.656 0 3119.897 6817.907 0 D:3119.897 6817.907 0 3115 6833 0 D:3115 6833 0 3109.004000000001 6852.787000000001 0 D:3109.004000000001 6852.787000000001 0 3103.512000000001 6869.736000000002 0 D:3103.512000000001 6869.736000000002 0 3098.368 6884.129 0 D:3098.368 6884.129 0 3093.416 6896.248000000001 0 D:3093.416 6896.248000000001 0 3088.5 6906.375 0 D:3088.5 6906.375 0 3083.464 6914.792 0 D:3083.464 6914.792 0 3078.152 6921.781 0 D:3078.152 6921.781 0 3072.408 6927.624000000001 0 D:3072.408 6927.624000000001 0 3066.076 6932.603 0 D:3066.076 6932.603 0 3059 6937 0 D:3059 6937 0 3054.300000000001 6939.779000000001 0 D:3054.300000000001 6939.779000000001 0 3049.840000000001 6942.672000000001 0 D:3049.840000000001 6942.672000000001 0 3045.68 6945.612999999999 0 D:3045.68 6945.612999999999 0 3041.880000000001 6948.536000000001 0 D:3041.880000000001 6948.536000000001 0 3038.5 6951.375 0 D:3038.5 6951.375 0 3035.6 6954.063999999999 0 D:3035.6 6954.063999999999 0 3033.24 6956.536999999999 0 D:3033.24 6956.536999999999 0 3031.48 6958.728 0 D:3031.48 6958.728 0 3030.38 6960.571 0 D:3030.38 6960.571 0 3030 6962 0 D:3030 6962 0 3029.503000000001 6963.196000000001 0 D:3029.503000000001 6963.196000000001 0 3028.064000000001 6964.368000000001 0 D:3028.064000000001 6964.368000000001 0 3025.761 6965.492 0 D:3025.761 6965.492 0 3022.672 6966.544000000001 0 D:3022.672 6966.544000000001 0 3018.875 6967.5 0 D:3018.875 6967.5 0 3014.448 6968.335999999999 0 D:3014.448 6968.335999999999 0 3009.469 6969.027999999999 0 D:3009.469 6969.027999999999 0 3004.016 6969.552 0 D:3004.016 6969.552 0 2998.167 6969.884 0 D:2998.167 6969.884 0 2992 6970 0 D:2992 6970 0 2982.572000000001 6969.854000000001 0 D:2982.572000000001 6969.854000000001 0 2974.536000000001 6969.312000000002 0 D:2974.536000000001 6969.312000000002 0 2967.664 6968.218 0 D:2967.664 6968.218 0 2961.728 6966.416000000001 0 D:2961.728 6966.416000000001 0 2956.5 6963.75 0 D:2956.5 6963.75 0 2951.752 6960.063999999999 0 D:2951.752 6960.063999999999 0 2947.256 6955.201999999999 0 D:2947.256 6955.201999999999 0 2942.784 6949.008000000001 0 D:2942.784 6949.008000000001 0 2938.108 6941.326 0 D:2938.108 6941.326 0 2933 6932 0 D:
marpon
Posts: 342
Joined: Dec 28, 2012 13:31
Location: Paris - France

Re: I need someone to defeat my string splitting algo

Post by marpon »

@ike

you probably made a mistake , my split function returns an array with lbound = 1 , that means the first element is a(1) not a(0)

according the code you let, i suppose the split_v1ctor is returning and array with lbound = 0

please check with following code

Code: Select all

dim as string txt
dim as integer i
open "data1.txt" for input as #1
line input #1, txt
close #1

print "len = " & len(txt)

dim as string a()
i = Split(txt, ":", a())
print "nb elements = " & i
print "lbound = " & lbound(a)  
print "ubound = " & ubound(a) 

? "     press key to continue"
sleep
for i = lbound(a) to ubound(a)
? a (i)
next i
? "     press key to finish"
sleep
you will see it works without any problem

if you want to have lbound = 0 change all the redim's in my split function...

but at the end, if you are happy with split_v1ctor , why to change, mine only tries to be the fastest, i did not compare with split_v1ctor
could you post the code?
Post Reply