source: Include/basic/function.sbp@ 167

Last change on this file since 167 was 167, checked in by イグトランス (egtra), 17 years ago

String関連の変更とHex$の修正

File size: 24.3 KB
Line 
1'function.sbp
2
3
4#ifndef _INC_FUNCTION
5#define _INC_FUNCTION
6
7
8Const _System_PI = 3.14159265358979323846264
9Const _System_LOG2 = 0.6931471805599453094172321214581765680755
10Const _System_SQRT2 = 1.41421356237309504880168872421
11
12
13#require <Classes/System/Math.ab>
14
15
16'------------- サポート関数の定義 -------------
17
18Function ldexp(x As Double, n As Long) As Double
19 If x = 0 Then
20 ldexp = 0
21 Exit Function
22 End If
23 Dim pSrc As *QWord, pDest As *QWord
24 pSrc = VarPtr(x) As *QWord
25 pDest = VarPtr(ldexp) As *QWord
26
27 n += (pSrc[0] >> 52) As DWord And &h7FF
28
29 pDest[0] = n << 52 Or (pSrc[0] And &h800FFFFFFFFFFFFF)
30End Function
31
32Function frexp(x As Double, ByRef n As Long) As Double
33 If x = 0 Then
34 n = 0
35 frexp = 0
36 Exit Function
37 End If
38
39 Dim pSrc As *QWord, pDest As *QWord
40 pSrc = VarPtr(x) As *QWord
41 pDest = VarPtr(frexp) As *QWord
42 n = ((pSrc[0] >> 52) As DWord And &h7FF) - 1022
43 pDest[0] = (pSrc[0] And &h800FFFFFFFFFFFFF) Or &h3FE0000000000000
44End Function
45
46Function frexp(x As Single, ByRef n As Long) As Single
47 If x = 0 Then
48 n = 0
49 frexp = 0
50 Exit Function
51 End If
52
53 Dim pSrc As *DWord, pDest As *DWord
54 pSrc = VarPtr(x) As *DWord
55 pDest = VarPtr(frexp) As *DWord
56 n = ((pSrc[0] >> 23) And &hFF) - 126
57 pDest[0] = (pSrc[0] And &h807FFFFF) Or &h7E000000
58End Function
59
60Function ipow(x As Double, n As Long) As Double
61 Dim abs_n As Long
62 Dim r = 1 As Double
63
64 abs_n=Abs(n) As Long
65 While abs_n<>0
66 If abs_n and 1 Then r *= x
67 x = x * x
68 abs_n >>= 1 ' abs_n \= 2
69 Wend
70
71 If n>=0 Then
72 ipow=r
73 Else
74 ipow=1/r
75 End If
76End Function
77
78Function pow(x As Double, y As Double) As Double
79 If -LONG_MAX<=y and y<=LONG_MAX and y=CDbl(Int(y)) Then
80 pow=ipow(x,y As Long)
81 Exit Function
82 End If
83
84 If x>0 Then
85 pow=Exp(y*Log(x))
86 Exit Function
87 End If
88
89 If x<>0 or y<=0 Then
90 'error
91 End If
92
93 pow=0
94End Function
95
96#ifdef _WIN64
97
98Function _System_GetNaN() As Double
99 SetQWord(VarPtr(_System_GetNaN) As *QWord, &H7FF8000000000000)
100End Function
101
102Function _System_GetInf(sign As BOOL) As Double
103 Dim s = 0 As QWord
104 If sign Then s = 1 << 63
105 SetQWord(VarPtr(_System_GetInf) As *QWord, &h7FF0000000000000 Or s)
106End Function
107
108#else
109
110Function _System_GetNaN() As Double
111 Dim p As *DWord
112 p = VarPtr(_System_GetNaN) As *DWord
113 p[0] = 0
114 p[1] = &H7FF80000
115End Function
116
117Function _System_GetInf(sign As BOOL) As Double
118 Dim s = 0 As DWord
119 If sign Then s = (1 As DWord) << 31
120 Dim p As *DWord
121 p = VarPtr(_System_GetInf) As *DWord
122 p[0] = 0
123 p[1] = &h7FF00000 Or s
124End Function
125
126#endif
127
128' xの符号だけをyのものにした値を返す。
129' 引数 x 元となる絶対値
130' 引数 y 元となる符号
131Function CopySign(x As Double, y As Double) As Double
132 SetQWord(VarPtr(CopySign), (GetQWord(VarPtr(x)) And &h7fffffffffffffff) Or (GetQWord(VarPtr(y)) And &h8000000000000000))
133End Function
134
135Function CopySign(x As Single, y As Single) As Single
136 SetDWord(VarPtr(CopySign), (GetDWord(VarPtr(x)) And &h7fffffff) Or (GetDWord(VarPtr(y)) And &h80000000))
137End Function
138
139Function _System_SetSign(x As Double, isNegative As Long) As Double
140#ifdef _WIN64
141 SetQWord(AddressOf(CopySign), (GetQWord(VarPtr(x)) And &h7fffffffffffffff) Or (isNegative << 63))
142#else
143 SetDWord(AddressOf(CopySign), GetDWord(VarPtr(x)))
144 SetDWord(AddressOf(CopySign) + SizeOf (DWord), GetQWord(VarPtr(x) + SizeOf (DWord)) And &h7fffffff Or (isNegative << 31))
145#endif
146End Function
147
148Const RAND_MAX=&H7FFFFFFF
149Dim _System_RndNext=1 As DWord
150
151Function rand() As Long
152 _System_RndNext = _System_RndNext * 1103515245 + 12345
153 rand = _System_RndNext >> 1
154End Function
155
156Sub srand(dwSeek As DWord)
157 _System_RndNext = dwSeek
158End Sub
159
160
161'------------- ここからBasic標準関数の定義 -------------
162
163
164'------------------
165' データ型変換関数
166'------------------
167
168Function CDbl(number As Double) As Double
169 CDbl=number
170End Function
171
172Function _CUDbl(number As QWord) As Double
173 _CUDbl=number As Double
174End Function
175
176Function CDWord(num As Double) As DWord
177 CDWord=num As DWord
178End Function
179
180Function CInt(number As Double) As Long
181 CInt=number As Long
182End Function
183
184Function CSng(number As Double) As Single
185 CSng=number As Single
186End Function
187
188#ifdef _WIN64
189Function Fix(number As Double) As Long
190 Fix=number As Long
191End Function
192#else
193'Fix関数はコンパイラに組み込まれている
194'Function Fix(number As Double) As Long
195#endif
196
197Function Int(number As Double) As Long
198 Int=Fix(number)
199 If number<0 Then
200 If number<Fix(number) Then Int=Int-1
201 End If
202End Function
203
204
205'-------------------------------------
206' ポインタ関数(コンパイラに組み込み)
207'-------------------------------------
208
209'Function GetDouble(p As DWord) As Double
210'Function GetSingle(p As DWord) As Single
211'Function GetDWord(p As DWord) As DWord
212'Function GetWord(p As DWord) As Word
213'Function GetByte(p As DWord) As Byte
214'Sub SetDouble(p As DWord, dblData As Double)
215'Sub SetSingle(p As DWord, fltData As Single)
216'Sub SetDWord(p As DWord, dwData As DWord)
217'Sub SetWord(p As DWord, wData As Word)
218'Sub SetByte(p As DWord, byteData As Byte)
219
220
221'----------
222' 算術関数
223'----------
224
225Function Abs(number As Double) As Double
226 'Abs = Math.Abs(number)
227 If number < 0 then
228 return -number
229 Else
230 return number
231 End If
232End Function
233
234Function Exp(x As Double) As Double
235 Exp = Math.Exp(x)
236End Function
237
238Function Log(x As Double) As Double
239 Log = Math.Log(x)
240End Function
241
242Function Sgn(number As Double) As Long
243 Sgn = Math.Sign(number)
244End Function
245
246Function Sqr(number As Double) As Double
247 Sqr = Math.Sqrt(number)
248End Function
249
250Function Atn(number As Double) As Double
251 Atn = Math.Atan(number)
252End Function
253
254Function _Support_tan(x As Double, ByRef k As Long) As Double
255 Dim i As Long
256 Dim t As Double, x2 As Double
257
258 If x>=0 Then
259 k=Fix(x/(_System_PI/2)+0.5)
260 Else
261 k=Fix(x/(_System_PI/2)-0.5)
262 End If
263
264 x=(x-(CDbl(3217)/CDbl(2048))*k)+4.4544551033807686783083602485579e-6*k
265
266 x2=x*x
267 t=0
268
269 For i=19 To 3 Step -2
270 t=x2/(i-t)
271 Next
272
273 _Support_tan=x/(1-t)
274End Function
275
276Function Atn2(y As Double, x As Double) As Double
277 Atn2 = Math.Atan2(y, x)
278End Function
279
280Function Sin(number As Double) As Double
281 Sin = Math.Sin(number)
282End Function
283
284Function Cos(number As Double) As Double
285 Cos = Math.Cos(number)
286End Function
287
288Function Tan(number As Double) As Double
289 Tan = Math.Tan(number)
290End Function
291
292Function IsNaN(ByVal x As Double) As Boolean
293 Dim p As *DWord
294 p = VarPtr(x) As *DWord
295 IsNaN = FALSE
296 If (p[1] And &H7FF00000) = &H7FF00000 Then
297 If (p[0] <> 0) Or ((p[1] And &HFFFFF) <> 0) Then
298 IsNaN = True
299 End If
300 End If
301
302' IsNaN=FALSE
303End Function
304
305Function IsInf(x As Double) As Boolean
306 Dim p As *DWord, nan As Double
307 p = VarPtr(x) As *DWord
308 p[1] And= &h7fffffff
309 nan = _System_GetInf(FALSE)
310 IsInf = (memcmp(p As *Byte, VarPtr(nan), SizeOf (Double)) = 0)
311End Function
312
313Function IsNaNOrInf(x As Double) As Boolean
314 IsNaNOrInf = IsFinite(x)
315End Function
316
317Function IsFinite(x As Double) As Boolean
318 Dim p As *DWord, nan As Double
319 p = VarPtr(x) As *DWord
320' p[1] And= &h7ffe0000
321 p[1] And= &H7FF00000
322 p[0] = 0
323 nan = _System_GetInf(/*x,*/ FALSE)
324 IsFinite = (memcmp(p As BytePtr, VarPtr(nan), SizeOf (Double)) = 0)
325End Function
326
327Const RAND_UNIT = (1.0 / (LONG_MAX + 1.0))
328Function Rnd() As Double
329 Rnd = RAND_UNIT * rand()
330End Function
331
332Const HIBYTE(w) = (((w As Word) >> 8) And &HFF) As Byte
333Const LOBYTE(w) = ((w As Word) And &HFF) As Byte
334Const HIWORD(dw) = (((dw As DWord) >> 16) And &HFFFF) As Word
335Const LOWORD(dw) = ((dw As DWord) And &HFFFF) As Word
336Const HIDWORD(qw) = (((qw As QWord) >> 32) And &HFFFFFFFF) As DWord
337Const LODWORD(qw) = ((qw As QWord) And &HFFFFFFFF) As DWord
338
339Const MAKEWORD(l, h) = (((l As Word) And &HFF) Or (((h As Word) And &HFF) << 8)) As Word
340Const MAKEDWORD(l, h) = (((l As DWord) And &HFFFF) Or (((h As DWord) And &HFFFF) << 16)) As DWord
341Const MAKEQWORD(l, h) = (((l As QWord) And &HFFFFFFFF) Or (((h As QWord) And &HFFFFFFFF) << 32)) As QWord
342Const MAKELONG(l, h) = MAKEDWORD(l, h) As Long
343
344'------------
345' 文字列関数
346'------------
347
348Function Asc(buf As *StrChar) As StrChar
349 Asc = buf[0]
350End Function
351
352Function Chr$(code As StrChar) As String
353 Chr$ = ZeroString(1)
354 Chr$[0] = code
355End Function
356
357#ifndef __STRING_IS_NOT_UNICODE
358Function AscW(s As *WCHAR) As UCSCHAR
359 If s.Length = 0 Then
360 AscW = 0
361 Else
362 If _System_IsSurrogatePair(s[0], s[1]) Then
363 AscW = ((s[0] And &h3FF) As DWord << 10) Or (s[1] And &h3FF)
364 Else
365 AscW = s[0]
366 End If
367 End If
368End Function
369
370Function ChrW(c As UCSCHAR) As String
371 If c <= &hFFFF Then
372 ChrW.ReSize(1)
373 ChrW[0] = c As WCHAR
374 ElseIf c < &h10FFFF Then
375 ChrW.ReSize(2)
376 ChrW[0] = &hD800 Or (c >> 10)
377 ChrW[1] = &hDC00 Or (c And &h3FF)
378 Else
379 ' OutOfRangeException
380 End If
381End Function
382#endif
383
384Function Date$() As String
385 Dim st As SYSTEMTIME
386 GetLocalTime(st)
387
388 'year
389 Date$=Str$(st.wYear)
390
391 'month
392 If st.wMonth<10 Then
393 Date$=Date$+"/0"
394 Else
395 Date$=Date$+"/"
396 End If
397 Date$=Date$+Str$(st.wMonth)
398
399 'day
400 If st.wDay<10 Then
401 Date$=Date$+"/0"
402 Else
403 Date$=Date$+"/"
404 End If
405 Date$=Date$+Str$(st.wDay)
406End Function
407
408Dim _System_HexadecimalTable[&h10] = [&h30, &h31, &h32, &h33, &h34, &h35, &h36, &h37, &h38, &h39, &h41, &h42, &h43, &h44, &h45, &h46] As Byte
409
410Function _System_Hex(x As DWord, zeroSuppress As Boolean) As String
411 Dim s[7] As StrChar
412 Dim i As Long
413 For i = 0 To ELM(Len (s) \ SizeOf (StrChar))
414 s[i] = _System_HexadecimalTable[x >> 28] As StrChar
415 x <<= 4
416 Next
417 If zeroSuppress Then
418 Dim i As Long
419 For i = 0 To 6
420 If s[i] <> &h30 Then 'Asc("0")
421 Exit For
422 End If
423 Next
424 Return New String(VarPtr(s[i]) As *StrChar, Len (s) \ SizeOf (StrChar) - i)
425 Else
426 Return New String(s As *StrChar, Len (s) \ SizeOf (StrChar))
427 End If
428End Function
429
430Function Hex$(x As DWord) As String
431 Hex$ = _System_Hex(x, True)
432End Function
433
434Function Hex$(x As QWord) As String
435 Hex$ = _System_Hex(HIDWORD(x), True) + _System_Hex(LODWORD(x), False)
436End Function
437
438Function InStr(StartPos As Long, buf1 As String, buf2 As String) As Long
439 Dim i As Long, i2 As Long, i3 As Long
440
441 Dim len1 = buf1.Length
442 Dim len2 = buf2.Length
443
444 If len2=0 Then
445 InStr=StartPos
446 Exit Function
447 End If
448
449 StartPos--
450 If StartPos<0 Then
451 'error
452 InStr=0
453 Exit Function
454 End If
455
456 i=StartPos:InStr=0
457 While i<=len1-len2
458 i2=i:i3=0
459 Do
460 If i3=len2 Then
461 InStr=i+1
462 Exit Do
463 End If
464 If buf1[i2]<>buf2[i3] Then Exit Do
465
466 i2++
467 i3++
468 Loop
469 If InStr Then Exit While
470 i++
471 Wend
472End Function
473
474Function Left$(buf As String, length As Long) As String
475 Left$ = ZeroString(length)
476 memcpy(StrPtr(Left$), StrPtr(buf), SizeOf (StrChar) * length)
477End Function
478
479Function Mid$(buf As String, StartPos As Long)(ReadLength As Long) As String
480 Dim length As Long
481
482 StartPos--
483 If StartPos<0 Then
484 'error
485 'Debug
486 Exit Function
487 End If
488
489 length=Len(buf)
490 If length<=StartPos Then Exit Function
491
492 If ReadLength=0 Then
493 ReadLength=length-StartPos
494 End If
495
496 If ReadLength>length-StartPos Then
497 ReadLength=length-StartPos
498 End If
499
500 Mid$=ZeroString(ReadLength)
501 memcpy(StrPtr(Mid$), VarPtr(buf.Chars[StartPos]), SizeOf (StrChar) * ReadLength)
502End Function
503
504Function Oct$(num As DWord) As String
505 Dim i As DWord, i2 As DWord
506
507 For i=10 To 1 Step -1
508 If (num\CDWord(8^i)) And &H07 Then
509 Exit For
510 End If
511 Next
512
513 Oct$=ZeroString(i+1)
514 i2=0
515 Do
516 Oct$[i2] = &h30 +((num \ CDWord(8 ^ i)) And &H07) ' &h30 = Asc("0")
517 If i=0 Then Exit Do
518 i--
519 i2++
520 Loop
521End Function
522
523Function Right$(buf As String, length As Long) As String
524 Dim i As Long
525
526 i=Len(buf)
527 If i>length Then
528 Right$=ZeroString(length)
529 memcpy(StrPtr(Right$), VarPtr(buf.Chars[i-length]), SizeOf (StrChar) * length)
530 Else
531 Right$=buf
532 End If
533End Function
534
535Function Space$(length As Long) As String
536 Space$.ReSize(length, &H20 As StrChar)
537End Function
538
539Dim _System_ecvt_buffer[16] As StrChar
540Sub _ecvt_support(count As Long)
541 Dim i As Long
542 If _System_ecvt_buffer[count]=9 Then
543 _System_ecvt_buffer[count]=0
544 If count=0 Then
545 For i=16 To 1 Step -1
546 _System_ecvt_buffer[i]=_System_ecvt_buffer[i-1]
547 Next
548 _System_ecvt_buffer[0]=1
549 Else
550 _ecvt_support(count-1)
551 End If
552 Else
553 _System_ecvt_buffer[count]++
554 End If
555End Sub
556Function _ecvt(value As Double, count As Long, ByRef dec As Long, ByRef sign As Long) As *StrChar
557 Dim i As Long, i2 As Long
558
559 _ecvt=_System_ecvt_buffer
560
561 '値が0の場合
562 If value = 0 Then
563 _System_FillChar(_System_ecvt_buffer, count, &H30)
564 _System_ecvt_buffer[count] = 0
565 dec = 0
566 sign = 0
567 Exit Function
568 End If
569
570 '符号の判断(同時に符号を取り除く)
571 If value < 0 Then
572 sign = 1
573 value = -value
574 Else
575 sign = 0
576 End If
577
578 '正規化
579 dec = 1
580 While value < 0.999999999999999 'value<1
581 value *= 10
582 dec--
583 Wend
584 While 9.99999999999999 <= value '10<=value
585 value /= 10
586 dec++
587 Wend
588
589 For i=0 To count-1
590 _System_ecvt_buffer[i] = Int(value) As StrChar
591
592 value = (value-CDbl(Int(value))) * 10
593 Next
594 _System_ecvt_buffer[i] = 0
595
596 i--
597 If value >= 5 Then
598 '切り上げ処理
599 _ecvt_support(i)
600 End If
601
602 For i=0 To ELM(count)
603 _System_ecvt_buffer[i] += &H30
604 Next
605 _System_ecvt_buffer[i] = 0
606End Function
607
608Function Str$(dbl As Double) As String
609 If IsNaN(dbl) Then
610 Return "NaN"
611 ElseIf IsInf(dbl) Then
612 If dbl > 0 Then
613 Return "Infinity"
614 Else
615 Return "-Infinity"
616 End If
617 End If
618 Dim dec As Long, sign As Long
619 Dim buffer[32] As StrChar, temp As *StrChar
620 Dim i As Long, i2 As Long, i3 As Long
621
622 '浮動小数点を文字列に変換
623 temp = _ecvt(dbl, 15, dec, sign)
624
625 i=0
626
627 '符号の取り付け
628 If sign Then
629 buffer[i] = Asc("-")
630 i++
631 End If
632
633 If dec>15 Then
634 '指数表示(桁が大きい場合)
635 buffer[i] = temp[0]
636 i++
637 buffer[i] = Asc(".")
638 i++
639 memcpy(VarPtr(buffer[i]), VarPtr(temp[1]), SizeOf (StrChar) * 14)
640 i += 14
641 buffer[i] = Asc("e")
642 i++
643 _stprintf(VarPtr(buffer[i]), "+%03d", dec - 1)
644
645 Return MakeStr(buffer)
646 End If
647
648 If dec < -3 Then
649 '指数表示(桁が小さい場合)
650 buffer[i] = temp[0]
651 i++
652 buffer[i] = Asc(".")
653 i++
654 memcpy(VarPtr(buffer[i]), VarPtr(temp[1]), SizeOf (StrChar) * 14)
655 i+=14
656 buffer[i] = Asc("e")
657 i++
658 _stprintf(VarPtr(buffer[i]), "+%03d", dec - 1)
659
660 Return MakeStr(buffer)
661 End If
662
663 '整数部
664 i2=dec
665 i3=0
666 If i2>0 Then
667 While i2>0
668 buffer[i]=temp[i3]
669 i++
670 i3++
671 i2--
672 Wend
673 buffer[i]=Asc(".")
674 i++
675 Else
676 buffer[i]=&H30
677 i++
678 buffer[i]=Asc(".")
679 i++
680
681 i2=dec
682 While i2<0
683 buffer[i]=&H30
684 i++
685 i2++
686 Wend
687 End If
688
689 '小数部
690 While i3<15
691 buffer[i]=temp[i3]
692 i++
693 i3++
694 Wend
695
696 While buffer[i-1]=&H30
697 i--
698 Wend
699 If buffer[i-1]=Asc(".") Then i--
700
701 buffer[i]=0
702 Return MakeStr(buffer)
703End Function
704
705Function Str$(value As Int64) As String
706 Dim temp[255] As Char
707 _sntprintf(temp, Len (temp) \ SizeOf (Char), "%I64d", value)
708 Str$ = New String( temp )
709End Function
710
711Function String$(num As Long, buf As String) As String
712 Dim dwStrPtr As DWord
713 Dim length As Long
714
715 length=Len(buf)
716
717 'バッファ領域を確保
718 String$=ZeroString(length*num)
719
720 '文字列をコピー
721 Dim i As Long
722 For i=0 To num-1
723 memcpy(VarPtr(String$[i*length]), StrPtr(buf), SizeOf (StrChar) * length)
724 Next
725End Function
726
727Function Time$() As String
728 Dim st As SYSTEMTIME
729
730 GetLocalTime(st)
731
732 'hour
733 If st.wHour<10 Then
734 Time$="0"
735 End If
736 Time$=Time$+Str$(st.wHour)
737
738 'minute
739 If st.wMinute<10 Then
740 Time$=Time$+":0"
741 Else
742 Time$=Time$+":"
743 End If
744 Time$=Time$+Str$(st.wMinute)
745
746 'second
747 If st.wSecond<10 Then
748 Time$=Time$+":0"
749 Else
750 Time$=Time$+":"
751 End If
752 Time$=Time$+Str$(st.wSecond)
753End Function
754
755Function Val(buf As *StrChar) As Double
756 Dim i As Long, i2 As Long, i3 As Long, i4 As Long
757 Dim temporary As String
758 Dim TempPtr As *StrChar
759 Dim dbl As Double
760 Dim i64data As Int64
761
762 Val=0
763
764 While buf[0]=Asc(" ") or buf[0]=Asc(Ex"\t")
765 buf++
766 Wend
767
768 If buf[0]=Asc("&") Then
769 temporary = New String( buf )
770 temporary.ToUpper()
771 TempPtr = StrPtr(temporary)
772 If TempPtr(1)=Asc("O") Then
773 '8進数
774 i=2
775 While 1
776 '数字以外の文字の場合は抜け出す
777 i3=TempPtr[i]-&H30
778 If Not (0<=i3 And i3<=7) Then Exit While
779
780 TempPtr[i]=i3 As StrChar
781 i++
782 Wend
783 i--
784
785 i64data=1
786 While i>=2
787 Val += i64data * TempPtr[i]
788
789 i64data *= &O10
790 i--
791 Wend
792 ElseIf TempPtr(1)=Asc("H") Then
793 '16進数
794 i=2
795 While 1
796 '数字以外の文字の場合は抜け出す
797 i3=TempPtr[i]-&H30
798 If Not(0<=i3 and i3<=9) Then
799 i3=TempPtr[i]-&H41+10
800 If Not(&HA<=i3 and i3<=&HF) Then Exit While
801 End If
802
803 TempPtr[i]=i3 As StrChar
804 i++
805 Wend
806 i--
807
808 i64data=1
809 While i>=2
810 Val += (i64data*TempPtr[i]) As Double
811
812 i64data *= &H10
813 i--
814 Wend
815 End If
816 Else
817 '10進数
818 If buf[0]=&H2D Then
819 'マイナス値
820 i4=1
821 buf++
822 Else
823 'プラス値
824 i4=0
825 If buf[0]=&H2B Then
826 buf++
827 End If
828 End If
829
830 i=0
831
832 While 1
833 '数字以外の文字の場合は抜け出す
834 i3=buf[i]-&H30
835 If Not (0<=i3 And i3<=9) Then Exit While
836
837 i++
838 Wend
839
840 '整数部
841 dbl=1
842 i3=i-1
843 While i3>=0
844 Val += dbl*(buf[i3]-&H30)
845
846 dbl *= 10
847 i3--
848 Wend
849
850 If buf[i]=Asc(".") Then
851 '小数部
852 i++
853 dbl=10
854 While 1
855 '数字以外の文字の場合は抜け出す
856 i3=buf[i]-&H30
857 If Not (0<=i3 And i3<=9) Then Exit While
858
859 Val += (buf[i] - &H30) / dbl
860 dbl *= 10
861 i++
862 Wend
863 End If
864
865 If i4 Then Val=-Val
866 End If
867End Function
868
869
870'--------------
871' ファイル関数
872'--------------
873
874Function Eof(FileNum As Long) As Long
875 Dim dwCurrent As DWord, dwEnd As DWord
876
877 FileNum--
878
879 dwCurrent=SetFilePointer(_System_hFile(FileNum),0,NULL,FILE_CURRENT)
880 dwEnd=SetFilePointer(_System_hFile(FileNum),0,NULL,FILE_END)
881 SetFilePointer(_System_hFile(FileNum),dwCurrent,NULL,FILE_BEGIN)
882
883 If dwCurrent>=dwEnd Then
884 Eof=-1
885 Else
886 Eof=0
887 End If
888End Function
889
890Function Lof(FileNum As Long) As Long
891 Lof = GetFileSize(_System_hFile(FileNum-1), 0)
892End Function
893
894Function Loc(FileNum As Long) As Long
895 Dim NowPos As Long, BeginPos As Long
896
897 FileNum--
898
899 NowPos=SetFilePointer(_System_hFile(FileNum),0,NULL,FILE_CURRENT)
900 BeginPos=SetFilePointer(_System_hFile(FileNum),0,NULL,FILE_BEGIN)
901 SetFilePointer(_System_hFile(FileNum),NowPos-BeginPos,NULL,FILE_BEGIN)
902
903 Loc=NowPos-BeginPos
904End Function
905
906
907'------------------
908' メモリ関連の関数
909'------------------
910
911Function malloc(stSize As SIZE_T) As VoidPtr
912 Return _System_pGC->__malloc(stSize,_System_GC_FLAG_NEEDFREE or _System_GC_FLAG_ATOMIC)
913End Function
914
915Function calloc(stSize As SIZE_T) As VoidPtr
916 Return _System_pGC->__malloc(stSize,_System_GC_FLAG_NEEDFREE or _System_GC_FLAG_ATOMIC or _System_GC_FLAG_INITZERO)
917End Function
918
919Function realloc(lpMem As VoidPtr, stSize As SIZE_T) As VoidPtr
920 If lpMem = 0 Then
921 Return malloc(stSize)
922 Else
923 Return _System_pGC->__realloc(lpMem,stSize)
924 End If
925End Function
926
927Sub free(lpMem As VoidPtr)
928 _System_pGC->__free(lpMem)
929End Sub
930
931
932Function _System_malloc(stSize As SIZE_T) As VoidPtr
933 Return HeapAlloc(_System_hProcessHeap,0,stSize)
934End Function
935
936Function _System_calloc(stSize As SIZE_T) As VoidPtr
937 Return HeapAlloc(_System_hProcessHeap,HEAP_ZERO_MEMORY,stSize)
938End Function
939
940Function _System_realloc(lpMem As VoidPtr, stSize As SIZE_T) As VoidPtr
941 If lpMem = 0 Then
942 Return HeapAlloc(_System_hProcessHeap, 0, stSize)
943 Else
944 Return HeapReAlloc(_System_hProcessHeap, 0, lpMem, stSize)
945 End If
946End Function
947
948Sub _System_free(lpMem As VoidPtr)
949 HeapFree(_System_hProcessHeap,0,lpMem)
950End Sub
951
952
953'--------
954' その他
955'--------
956
957Sub _splitpath(path As PCSTR, drive As PSTR, dir As PSTR, fname As PSTR, ext As PSTR)
958 Dim i As Long, i2 As Long, i3 As Long, length As Long
959 Dim buffer[MAX_PATH] As SByte
960
961 '":\"をチェック
962 If not(path[1]=&H3A and path[2]=&H5C) Then Exit Sub
963
964 'ドライブ名をコピー
965 If drive Then
966 drive[0]=path[0]
967 drive[1]=path[1]
968 drive[2]=0
969 End If
970
971 'ディレクトリ名をコピー
972 i=2
973 i2=0
974 Do
975 If IsDBCSLeadByte(path[i]) <> FALSE and path[i + 1] <> 0 Then
976 If dir Then
977 dir[i2]=path[i]
978 dir[i2+1]=path[i+1]
979 End If
980
981 i += 2
982 i2 += 2
983 Continue
984 End If
985
986 If path[i]=0 Then Exit Do
987
988 If path[i]=&H5C Then '"\"記号であるかどうか
989 i3=i2+1
990 End If
991
992 If dir Then dir[i2]=path[i]
993
994 i++
995 i2++
996 Loop
997 If dir Then dir[i3]=0
998 i3 += i-i2
999
1000 'ファイル名をコピー
1001 i=i3
1002 i2=0
1003 i3=-1
1004 Do
1005'#ifdef UNICODE
1006' If _System_IsSurrogatePair(path[i], path[i + 1]) Then
1007'#else
1008 If IsDBCSLeadByte(path[i]) <> FALSE and path[i + 1] <> 0 Then
1009'#endif
1010 If fname Then
1011 fname[i2]=path[i]
1012 fname[i2+1]=path[i+1]
1013 End If
1014
1015 i += 2
1016 i2 += 2
1017 Continue
1018 End If
1019
1020 If path[i]=0 Then Exit Do
1021
1022 If path[i]=&H2E Then '.'記号であるかどうか
1023 i3=i2
1024 End If
1025
1026 If fname Then fname[i2]=path[i]
1027
1028 i++
1029 i2++
1030 Loop
1031 If i3=-1 Then i3=i2
1032 If fname Then fname[i3]=0
1033 i3 += i-i2
1034
1035 '拡張子名をコピー
1036 If ext Then
1037 If i3 Then
1038 lstrcpy(ext,path+i3)
1039 End If
1040 else ext[0]=0
1041 End If
1042End Sub
1043
1044Function GetBasicColor(ColorCode As Long) As Long
1045 Select Case ColorCode
1046 Case 0
1047 GetBasicColor=RGB(0,0,0)
1048 Case 1
1049 GetBasicColor=RGB(0,0,255)
1050 Case 2
1051 GetBasicColor=RGB(255,0,0)
1052 Case 3
1053 GetBasicColor=RGB(255,0,255)
1054 Case 4
1055 GetBasicColor=RGB(0,255,0)
1056 Case 5
1057 GetBasicColor=RGB(0,255,255)
1058 Case 6
1059 GetBasicColor=RGB(255,255,0)
1060 Case 7
1061 GetBasicColor=RGB(255,255,255)
1062 End Select
1063End Function
1064
1065Function _System_BSwap(x As Word) As Word
1066 Dim src = VarPtr(x) As *Byte
1067 Dim dst = VarPtr(_System_BSwap) As *SByte
1068 dst[0] = src[1]
1069 dst[1] = src[0]
1070End Function
1071
1072Function _System_BSwap(x As DWord) As DWord
1073 Dim src = VarPtr(x) As *Byte
1074 Dim dst = VarPtr(_System_BSwap) As *SByte
1075 dst[0] = src[3]
1076 dst[1] = src[2]
1077 dst[2] = src[1]
1078 dst[3] = src[0]
1079End Function
1080
1081Function _System_BSwap(x As QWord) As QWord
1082 Dim src = VarPtr(x) As *Byte
1083 Dim dst = VarPtr(_System_BSwap) As *SByte
1084 dst[0] = src[7]
1085 dst[1] = src[6]
1086 dst[2] = src[5]
1087 dst[3] = src[4]
1088 dst[4] = src[3]
1089 dst[5] = src[2]
1090 dst[6] = src[1]
1091 dst[7] = src[0]
1092End Function
1093
1094'--------
1095' 文字列関数その2
1096'--------
1097Function _System_IsSurrogatePair(wcHigh As WCHAR, wcLow As WCHAR) As Boolean
1098 If &hD800 <= wcHigh And wcHigh < &hDC00 Then
1099 If &hDC00 <= wcLow And wcLow < &hE000 Then
1100 Return True
1101 End If
1102 End If
1103 Return False
1104End Function
1105
1106Function _System_IsDoubleUnitChar(lead As WCHAR, trail As WCHAR) As Boolean
1107 Return _System_IsSurrogatePair(lead, trail)
1108End Function
1109
1110Function _System_IsDoubleUnitChar(lead As SByte, trail As SByte) As Boolean
1111 Return IsDBCSLeadByte(lead) <> FALSE
1112End Function
1113
1114Sub _System_FillChar(p As PWSTR, n As SIZE_T, c As WCHAR)
1115 Dim i As SIZE_T
1116 For i = 0 To ELM(n)
1117 p[i] = c
1118 Next
1119End Sub
1120
1121Sub _System_FillChar(p As PSTR, n As SIZE_T, c As SByte)
1122 Dim i As SIZE_T
1123 For i = 0 To ELM(n)
1124 p[i] = c
1125 Next
1126End Sub
1127
1128Function _System_ASCII_IsUpper(c As WCHAR) As Boolean
1129 Return c As DWord - &h41 < 26 ' &h41 = Asc("A")
1130End Function
1131
1132Function _System_ASCII_IsUpper(c As SByte) As Boolean
1133 Return _System_ASCII_IsUpper(c As Byte As WCHAR)
1134End Function
1135
1136Function _System_ASCII_IsLower(c As WCHAR) As Boolean
1137 Return c As DWord - &h61 < 26 ' &h61 = Asc("a")
1138End Function
1139
1140Function _System_ASCII_IsLower(c As SByte) As Boolean
1141 Return _System_ASCII_IsLower(c As Byte As WCHAR)
1142End Function
1143
1144Function _System_ASCII_ToLower(c As WCHAR) As WCHAR
1145 If _System_ASCII_IsUpper(c) Then
1146 Return c Or &h20
1147 Else
1148 Return c
1149 End If
1150End Function
1151
1152Function _System_ASCII_ToLower(c As SByte) As SByte
1153 Return _System_ASCII_ToLower(c As Byte As WCHAR) As Byte As SByte
1154End Function
1155
1156Function _System_ASCII_ToUpper(c As WCHAR) As WCHAR
1157 If _System_ASCII_IsLower(c) Then
1158 Return c And (Not &h20)
1159 Else
1160 Return c
1161 End If
1162End Function
1163
1164Function _System_ASCII_ToUpper(c As SByte) As SByte
1165 Return _System_ASCII_ToUpper(c As Byte As WCHAR) As Byte As SByte
1166End Function
1167
1168
1169Function _System_StrCmp(s1 As PCSTR, s2 As PCSTR) As Long
1170 Dim i = 0 As SIZE_T
1171 While s1[i] = s2[i]
1172 If s1[i] = 0 Then
1173 Exit While
1174 End If
1175 i++
1176 Wend
1177 _System_StrCmp = s1[i] - s2[i]
1178End Function
1179
1180Function _System_StrCmp(s1 As PCWSTR, s2 As PCWSTR) As Long
1181 Dim i = 0 As SIZE_T
1182 While s1[i] = s2[i]
1183 If s1[i] = 0 Then
1184 Exit While
1185 End If
1186 i++
1187 Wend
1188 _System_StrCmp = s1[i] - s2[i]
1189End Function
1190
1191#endif '_INC_FUNCTION
Note: See TracBrowser for help on using the repository browser.