source: Include/basic/function.sbp@ 10

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

misc

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