source: Include/api_system.sbp@ 121

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

#51対応

File size: 56.3 KB
Line 
1' api_system.sbp - System API
2
3#ifndef _INC_SYSTEM
4#define _INC_SYSTEM
5
6
7'-------------------
8' default constants
9Const NULL = 0
10Const TRUE = 1
11Const FALSE = 0
12
13Const _System_TRUE = -1
14Const _System_FALSE = 0
15
16Const MAX_PATH = 260
17Const INVALID_HANDLE_VALUE = -1 As HANDLE
18Const INVALID_SET_FILE_POINTER = &HFFFFFFFF
19
20Const SYNCHRONIZE = &H00100000
21Const STANDARD_RIGHTS_REQUIRED = &H000F0000
22
23Const MAXIMUM_WAIT_OBJECTS = 64
24
25'-----------------
26' data structs
27Type LARGE_INTEGER
28 LowPart As DWord
29 HighPart As Long
30End Type
31Type ULARGE_INTEGER
32 LowPart As DWord
33 HighPart As DWord
34End Type
35
36
37'Globally Unique Identifier 128 bit(16 byte)
38Type GUID
39 Data1 As DWord
40 Data2 As Word
41 Data3 As Word
42 Data4[7] As Byte
43End Type
44
45' File structure
46Type SECURITY_ATTRIBUTES
47 nLength As DWord
48 lpSecurityDescriptor As VoidPtr
49 bInheritHandle As BOOL
50End Type
51
52Type OVERLAPPED
53 Internal As ULONG_PTR
54 InternalHigh As ULONG_PTR
55 Offset As DWord
56 OffsetHigh As DWord
57 hEvent As HANDLE
58End Type
59
60Type FILETIME
61 dwLowDateTime As DWord
62 dwHighDateTime As DWord
63End Type
64
65' System time
66Type SYSTEMTIME
67 wYear As Word
68 wMonth As Word
69 wDayOfWeek As Word
70 wDay As Word
71 wHour As Word
72 wMinute As Word
73 wSecond As Word
74 wMilliseconds As Word
75End Type
76
77#ifdef _WIN64
78Const CONTEXT_AMD64 = &h100000
79
80Const CONTEXT_CONTROL = (CONTEXT_AMD64 Or &h1)
81Const CONTEXT_INTEGER = (CONTEXT_AMD64 Or &h2)
82Const CONTEXT_SEGMENTS = (CONTEXT_AMD64 Or &h4)
83Const CONTEXT_FLOATING_POINT = (CONTEXT_AMD64 Or &h8)
84Const CONTEXT_DEBUG_REGISTERS = (CONTEXT_AMD64 Or &h10)
85
86Const CONTEXT_FULL = (CONTEXT_CONTROL Or CONTEXT_INTEGER Or CONTEXT_FLOATING_POINT)
87
88Const CONTEXT_ALL = (CONTEXT_CONTROL Or CONTEXT_INTEGER Or CONTEXT_SEGMENTS Or CONTEXT_FLOATING_POINT Or CONTEXT_DEBUG_REGISTERS)
89
90Type Align(16) M128
91 Low As QWord
92 High As Int64
93End Type
94
95Type LEGACY_SAVE_AREA 'Winnt.h
96 ControlWord As Word
97 Reserved0 As Word
98 StatusWord As Word
99 Reserved1 As Word
100 TagWord As Word
101 Reserved2 As Word
102 ErrorOffset As DWord
103 ErrorSelector As Word
104 ErrorOpcode As Word
105 DataOffset As DWord
106 DataSelector As Word
107 Reserved3 As Word
108 FloatRegisters[ELM(8 * 10)] As Byte
109End Type
110
111Type Align(16) CONTEXT 'Winnt.h
112 'Register parameter home addresses.
113 P1Home As QWord
114 P2Home As QWord
115 P3Home As QWord
116 P4Home As QWord
117 P5Home As QWord
118 P6Home As QWord
119 'Control flags.
120 ContextFlags As DWord
121 MxCsr As DWord
122 'Segment Registers and processor flags.
123 SegCs As Word
124 SegDs As Word
125 SegEs As Word
126 SegFs As Word
127 SegGs As Word
128 SegSs As Word
129 EFlags As DWord
130 'Debug registers
131 Dr0 As QWord
132 Dr1 As QWord
133 Dr2 As QWord
134 Dr3 As QWord
135 Dr6 As QWord
136 Dr7 As QWord
137 'Integer registers.
138 Rax As QWord
139 Rcx As QWord
140 Rdx As QWord
141 Rbx As QWord
142 Rsp As QWord
143 Rbp As QWord
144 Rsi As QWord
145 Rdi As QWord
146 R8 As QWord
147 R9 As QWord
148 R10 As QWord
149 R11 As QWord
150 R12 As QWord
151 R13 As QWord
152 R14 As QWord
153 R15 As QWord
154 'Program counter.
155 Rip As QWord
156 'MMX/floating point state.
157 Header[ELM(2)] As M128
158 Legacy[ELM(8)] As M128
159 Xmm0 As M128
160 Xmm1 As M128
161 Xmm2 As M128
162 Xmm3 As M128
163 Xmm4 As M128
164 Xmm5 As M128
165 Xmm6 As M128
166 Xmm7 As M128
167 Xmm8 As M128
168 Xmm9 As M128
169 Xmm10 As M128
170 Xmm11 As M128
171 Xmm12 As M128
172 Xmm13 As M128
173 Xmm14 As M128
174 Xmm15 As M128
175 Reserve[ELM(96)] As Byte
176 'Vector registers
177 VectorRegisters[ELM(26)] As M128
178 VectorControl As QWord
179 'Special debug control registers.
180 DebugControl As QWord
181 LastBranchToRip As QWord
182 LastBranchFromRip As QWord
183 LastExceptionToRip As QWord
184 LastExceptionFromRip As QWord
185End Type
186
187#else
188
189Const SIZE_OF_80387_REGISTERS = 80
190Const MAXIMUM_SUPPORTED_EXTENSION = 512
191
192Type FLOATING_SAVE_AREA
193 ControlWord As DWord
194 StatusWord As DWord
195 TagWord As DWord
196 ErrorOffset As DWord
197 ErrorSelector As DWord
198 DataOffset As DWord
199 DataSelector As DWord
200 RegisterArea[ELM(SIZE_OF_80387_REGISTERS)] As Byte
201 Cr0NpxState As DWord
202End Type
203
204Const CONTEXT_i386 = &h00010000
205Const CONTEXT_i486 = &h00010000
206
207Const CONTEXT_CONTROL = (CONTEXT_i386 Or &h00000001) 'SS:SP, CS:IP, FLAGS, BP
208Const CONTEXT_INTEGER = (CONTEXT_i386 Or &h00000002) 'AX, BX, CX, DX, SI, DI
209Const CONTEXT_SEGMENTS = (CONTEXT_i386 Or &h00000004) 'DS, ES, FS, GS
210Const CONTEXT_FLOATING_POINT = (CONTEXT_i386 Or &h00000008) '387 state
211Const CONTEXT_DEBUG_REGISTERS = (CONTEXT_i386 Or &h00000010) 'DB 0-3,6,7
212Const CONTEXT_EXTENDED_REGISTERS = (CONTEXT_i386 Or &h0000002) 'cpu specific extensions
213
214Const CONTEXT_FULL = (CONTEXT_CONTROL Or CONTEXT_INTEGER Or CONTEXT_SEGMENTS)
215
216Const CONTEXT_ALL = (CONTEXT_CONTROL Or CONTEXT_INTEGER Or CONTEXT_SEGMENTS Or CONTEXT_FLOATING_POINT Or CONTEXT_DEBUG_REGISTERS Or CONTEXT_EXTENDED_REGISTERS)
217
218Type CONTEXT
219 ContextFlags As DWord
220
221 Dr0 As DWord
222 Dr1 As DWord
223 Dr2 As DWord
224 Dr3 As DWord
225 Dr6 As DWord
226 Dr7 As DWord
227
228 FloatSave As FLOATING_SAVE_AREA
229
230 SegGs As DWord
231 SegFs As DWord
232 SegEs As DWord
233 SegDs As DWord
234
235 Edi As DWord
236 Esi As DWord
237 Ebx As DWord
238 Edx As DWord
239 Ecx As DWord
240 Eax As DWord
241
242 Ebp As DWord
243 Eip As DWord
244 SegCs As DWord
245 EFlags As DWord
246 Esp As DWord
247 SegSs As DWord
248
249 ExtendedRegisters[ELM(MAXIMUM_SUPPORTED_EXTENSION)] As Byte
250End Type
251
252#endif
253
254' Global Memory Flags
255Const GMEM_FIXED = &H0000
256Const GMEM_MOVEABLE = &H0002
257Const GMEM_NOCOMPACT = &H0010
258Const GMEM_NODISCARD = &H0020
259Const GMEM_ZEROINIT = &H0040
260Const GMEM_MODIFY = &H0080
261Const GMEM_DISCARDABLE = &H0100
262Const GMEM_NOT_BANKED = &H1000
263Const GMEM_SHARE = &H2000
264Const GMEM_DDESHARE = &H2000
265Const GMEM_INVALID_HANDLE = &H8000
266Const GHND = GMEM_MOVEABLE or GMEM_ZEROINIT
267Const GPTR = GMEM_FIXED or GMEM_ZEROINIT
268Const GMEM_DISCARDED = &H4000
269
270
271' Heap
272Const HEAP_NO_SERIALIZE = &H00000001
273Const HEAP_GROWABLE = &H00000002
274Const HEAP_GENERATE_EXCEPTIONS = &H00000004
275Const HEAP_ZERO_MEMORY = &H00000008
276Const HEAP_REALLOC_IN_PLACE_ONLY = &H00000010
277
278
279' Locale
280Const LOCALE_SYSTEM_DEFAULT = &H400 'Standard Systemsprache
281Const LOCALE_USER_DEFAULT = &H800 'Standard Benutzersprache
282
283
284' Locale flag
285Const LOCALE_NOUSEROVERRIDE = &H80000000
286
287
288'Critical Section
289Type CRITICAL_SECTION
290 DebugInfo As VoidPtr
291 LockCount As Long
292 RecursionCount As Long
293 OwningThread As HANDLE
294 LockSemaphore As HANDLE
295 SpinCount As ULONG_PTR
296End Type
297
298
299'DllMain
300Const DLL_PROCESS_ATTACH = 1
301Const DLL_THREAD_ATTACH = 2
302Const DLL_THREAD_DETACH = 3
303Const DLL_PROCESS_DETACH = 0
304
305'Event
306Const EVENT_MODIFY_STATE = &H0002
307Const EVENT_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or SYNCHRONIZE Or &H3)
308
309'Mutex
310Const MUTANT_QUERY_STATE = &H0001
311Const MUTANT_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or SYNCHRONIZE Or MUTANT_QUERY_STATE)
312Const MUTEX_ALL_ACCESS = MUTANT_ALL_ACCESS
313
314'Semaphore
315Const SEMAPHORE_MODIFY_STATE = &H0002
316Const SEMAPHORE_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or SYNCHRONIZE Or &H3)
317
318'Timer
319Const TIMER_QUERY_STATE = &H0001
320Const TIMER_MODIFY_STATE = &H0002
321Const TIMER_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or SYNCHRONIZE Or TIMER_QUERY_STATE Or TIMER_MODIFY_STATE)
322
323'----------------------
324' Kernel Operation API
325Declare Function InterlockedIncrement Lib "kernel32" (ByRef lpAddend As Long) As Long
326Declare Function InterlockedDecrement Lib "kernel32" (ByRef lpAddend As Long) As Long
327Declare Function InterlockedExchange Lib "kernel32" (ByRef Target As Long, Value As Long) As Long
328Declare Function InterlockedCompareExchange Lib "kernel32" (ByRef Destination As Long, Exchange As Long, Comperand As Long) As Long
329Declare Function InterlockedExchangeAdd Lib "kernel32" (ByRef Addend As Long, Value As Long) As Long
330#ifdef _WIN64
331Declare Function InterlockedCompareExchangePointer Lib "kernel32" (ByRef Destination As VoidPtr, Exchange As VoidPtr, Comperand As VoidPtr) As VoidPtr
332Declare Function InterlockedExchangePointer Lib "kernel32" (ByRef Target As VoidPtr, Value As VoidPtr) As VoidPtr
333#else
334Declare Function InterlockedCompareExchangePointer Lib "kernel32" Alias "InterlockedCompareExchange" (ByRef Destination As VoidPtr, Exchange As VoidPtr, Comperand As VoidPtr) As VoidPtr
335Declare Function InterlockedExchangePointer Lib "kernel32" Alias "InterlockedExchange" (ByRef Target As VoidPtr, Value As VoidPtr) As VoidPtr
336#endif
337Declare Function Beep Lib "kernel32" (dwFreq As DWord, dwDuration As DWord) As BOOL
338Declare Function CloseHandle Lib "kernel32" (hObject As HANDLE) As BOOL
339
340Declare Function CompareFileTime Lib "kernel32" (ByRef FileTime1 As FILETIME, ByRef FileTime2 As FILETIME) As Long
341
342Const NORM_IGNORECASE = &H00000001
343Const NORM_IGNORENONSPACE = &H00000002
344Const NORM_IGNORESYMBOLS = &H00000004
345Const SORT_STRINGSORT = &H00001000
346Const NORM_IGNOREKANATYPE = &H00010000
347Const NORM_IGNOREWIDTH = &H00020000
348Const CSTR_LESS_THAN = 1
349Const CSTR_EQUAL = 2
350Const CSTR_GREATER_THAN = 3
351Declare Function CompareString Lib "kernel32" Alias "CompareStringA" (Locale As LCID, dwCmpFlags As DWord, pString1 As PCSTR, cchCount1 As Long, pString2 As PCSTR, cchCount2 As Long) As Long
352
353Declare Function CopyFile Lib "kernel32" Alias "CopyFileA" (lpExistingFileName As LPCSTR, lpNewFileName As LPCSTR, bFailIfExists As BOOL) As BOOL
354Declare Function CreateDirectory Lib "kernel32" Alias "CreateDirectoryA" (lpPathName As LPCSTR, lpSecurityAttributes As *SECURITY_ATTRIBUTES) As BOOL
355Declare Function CreateEvent Lib "kernel32" Alias "CreateEventA" (pEventAttributes As *SECURITY_ATTRIBUTES, bManualReset As BOOL, bInitialState As BOOL, pName As PCSTR) As HANDLE
356Declare Function CreateMutex Lib "kernel32" Alias "CreateMutexA" (lpMutexAttributes As *SECURITY_ATTRIBUTES, bInitialOwner As BOOL, lpName As PCSTR) As HANDLE
357Declare Function CreateSemaphore Lib "kernel32" Alias "CreateSemaphoreA" (lpSemaphoreAttributes As *SECURITY_ATTRIBUTES, lInitialCount As Long, lMaximumCount As Long, lpName As LPSTR) As HANDLE
358
359TypeDef PTIMERAPCROUTINE = *Sub(lpArgToCompletionRoutine As VoidPtr, dwTimerLowValue As DWord, dwTimerHighValue As DWord)
360Declare Function CreateWaitableTimer Lib "kernel32" Alias "CreateWaitableTimerA" (lpTimerAttributes As *SECURITY_ATTRIBUTES, bManualReset As BOOL, lpTimerName As LPSTR) As HANDLE
361Declare Function OpenWaitableTimer Lib "kernel32" Alias "OpenWaitableTimerA" (dwDesiredAccess As DWord, bInheritHandle As BOOL, lpTimerName As LPSTR) As HANDLE
362Declare Function SetWaitableTimer Lib "kernel32" (hTimer As HANDLE, lpDueTime As *LARGE_INTEGER, lPeriod As Long, pfnCompletionRoutine As PTIMERAPCROUTINE, lpArgToCompletionRoutine As VoidPtr, fResume As BOOL) As BOOL
363Declare Function CancelWaitableTimer Lib "kernel32" (hTimer As HANDLE) As BOOL
364
365Const GENERIC_READ = &H80000000
366Const GENERIC_WRITE = &H40000000
367Const FILE_SHARE_READ = &H00000001
368Const FILE_SHARE_WRITE = &H00000002
369Const FILE_SHARE_DELETE = &H00000004
370Const CREATE_NEW = 1
371Const CREATE_ALWAYS = 2
372Const OPEN_EXISTING = 3
373Const OPEN_ALWAYS = 4
374Const TRUNCATE_EXISTING = 5
375Const FILE_ATTRIBUTE_READONLY = &H00000001
376Const FILE_ATTRIBUTE_HIDDEN = &H00000002
377Const FILE_ATTRIBUTE_SYSTEM = &H00000004
378Const FILE_ATTRIBUTE_DIRECTORY = &H00000010
379Const FILE_ATTRIBUTE_ARCHIVE = &H00000020
380Const FILE_ATTRIBUTE_ENCRYPTED = &H00000040
381Const FILE_ATTRIBUTE_NORMAL = &H00000080
382Const FILE_ATTRIBUTE_TEMPORARY = &H00000100
383Const FILE_ATTRIBUTE_SPARSE_FILE = &H00000200
384Const FILE_ATTRIBUTE_REPARSE_POINT = &H00000400
385Const FILE_ATTRIBUTE_COMPRESSED = &H00000800
386Const FILE_ATTRIBUTE_OFFLINE = &H00001000
387Const FILE_FLAG_WRITE_THROUGH = &H80000000
388Const FILE_FLAG_OVERLAPPED = &H40000000
389Const FILE_FLAG_NO_BUFFERING = &H20000000
390Const FILE_FLAG_RANDOM_ACCESS = &H10000000
391Const FILE_FLAG_SEQUENTIAL_SCAN = &H08000000
392Const FILE_FLAG_DELETE_ON_CLOSE = &H04000000
393Const FILE_FLAG_BACKUP_SEMANTICS = &H02000000
394Const FILE_FLAG_POSIX_SEMANTICS = &H01000000
395Const FILE_FLAG_OPEN_REPARSE_POINT = &H00200000
396Const FILE_FLAG_OPEN_NO_RECALL = &H00100000
397Declare Function CreateFile Lib "kernel32" Alias "CreateFileA" (lpFileName As *Byte, dwDesiredAccess As DWord, dwShareMode As DWord, ByRef lpSecurityAttributes As SECURITY_ATTRIBUTES, dwCreationDisposition As DWord, dwFlagsAndAttributes As DWord, hTemplateFile As HANDLE) As HANDLE
398
399Const SECTION_QUERY = &H0001
400Const SECTION_MAP_WRITE = &H0002
401Const SECTION_MAP_READ = &H0004
402Const SECTION_MAP_EXECUTE = &H0008
403Const SECTION_EXTEND_SIZE = &H0010
404Const SECTION_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or SECTION_QUERY Or SECTION_MAP_WRITE Or SECTION_MAP_READ Or SECTION_MAP_EXECUTE Or SECTION_EXTEND_SIZE)
405
406Const FILE_MAP_COPY = SECTION_QUERY
407Const FILE_MAP_WRITE = SECTION_MAP_WRITE
408Const FILE_MAP_READ = SECTION_MAP_READ
409Const FILE_MAP_ALL_ACCESS = SECTION_ALL_ACCESS
410Declare Function CreateFileMapping Lib "kernel32" Alias "CreateFileMappingA" (hFile As HANDLE, lpFileMappingAttributes As *SECURITY_ATTRIBUTES, flProtect As DWord, dwMaximumSizeHigh As DWord, dwMaximumSizeLow As DWord, lpName As LPSTR) As HANDLE
411Declare Function OpenFileMapping Lib "kernel32" Alias "OpenFileMappingA" (dwDesiredAccess As DWord, bInheritHandle As BOOL, lpName As LPSTR) As HANDLE
412Declare Function MapViewOfFile Lib "kernel32" (hFileMappingObject As HANDLE, dwDesiredAccess As DWord, dwFileOffsetHigh As DWord, dwFileOffsetLow As DWord, dwNumberOfBytesToMap As DWord) As VoidPtr
413Declare Function MapViewOfFileEx Lib "kernel32" (hFileMappingObject As HANDLE, dwDesiredAccess As DWord, dwFileOffsetHigh As DWord, dwFileOffsetLow As DWord, dwNumberOfBytesToMap As DWord, lpBaseAddress As VoidPtr) As VoidPtr
414Declare Function FlushViewOfFile Lib "kernel32" (lpBaseAddress As VoidPtr, dwNumberOfBytesToFlush As DWord) As BOOL
415Declare Function UnmapViewOfFile Lib "kernel32" (lpBaseAddress As VoidPtr) As BOOL
416
417Const MAILSLOT_WAIT_FOREVER = &HFFFFFFFF
418Declare Function CreateMailslot Lib "kernel32" Alias "CreateMailslotA" (lpName As *Byte, nMaxMessageSize As DWord, lReadTimeout As DWord, ByRef lpSecurityAttributes As SECURITY_ATTRIBUTES) As HANDLE
419
420Const DEBUG_PROCESS = &H00000001
421Const DEBUG_ONLY_THIS_PROCESS = &H00000002
422Const CREATE_SUSPENDED = &H00000004
423Const DETACHED_PROCESS = &H00000008
424Const CREATE_NEW_CONSOLE = &H00000010
425Const NORMAL_PRIORITY_CLASS = &H00000020
426Const IDLE_PRIORITY_CLASS = &H00000040
427Const HIGH_PRIORITY_CLASS = &H00000080
428Const REALTIME_PRIORITY_CLASS = &H00000100
429Const CREATE_NEW_PROCESS_GROUP = &H00000200
430Const CREATE_UNICODE_ENVIRONMENT = &H00000400
431Const CREATE_SEPARATE_WOW_VDM = &H00000800
432Const CREATE_SHARED_WOW_VDM = &H00001000
433Const CREATE_FORCEDOS = &H00002000
434Const CREATE_DEFAULT_ERROR_MODE = &H04000000
435Const CREATE_NO_WINDOW = &H08000000
436Const PROFILE_USER = &H10000000
437Const PROFILE_KERNEL = &H20000000
438Const PROFILE_SERVER = &H40000000
439
440Const STARTF_USESHOWWINDOW = &H00000001
441Const STARTF_USESIZE = &H00000002
442Const STARTF_USEPOSITION = &H00000004
443Const STARTF_USECOUNTCHARS = &H00000008
444Const STARTF_USEFILLATTRIBUTE = &H00000010
445Const STARTF_RUNFULLSCREEN = &H00000020
446Const STARTF_FORCEONFEEDBACK = &H00000040
447Const STARTF_FORCEOFFFEEDBACK = &H00000080
448Const STARTF_USESTDHANDLES = &H00000100
449Const STARTF_USEHOTKEY = &H00000200
450Type STARTUPINFO
451 cb As DWord
452 lpReserved As *Byte
453 lpDesktop As *Byte
454 lpTitle As *Byte
455 dwX As DWord
456 dwY As DWord
457 dwXSize As DWord
458 dwYSize As DWord
459 dwXCountChars As DWord
460 dwYCountChars As DWord
461 dwFillAttribute As DWord
462 dwFlags As DWord
463 wShowWindow As Word
464 cbReserved2 As Word
465 lpReserved2 As *Byte
466 hStdInput As HANDLE
467 hStdOutput As HANDLE
468 hStdError As HANDLE
469End Type
470Type PROCESS_INFORMATION
471 hProcess As HANDLE
472 hThread As HANDLE
473 dwProcessId As DWord
474 dwThreadId As DWord
475End Type
476Declare Function CreateProcess Lib "kernel32" Alias "CreateProcessA" (lpApplicationName As BytePtr, lpCommandLine As BytePtr, ByRef lpProcessAttributes As SECURITY_ATTRIBUTES, ByRef lpThreadAttributes As SECURITY_ATTRIBUTES, bInheritHandles As BOOL, dwCreationFlags As DWord, lpEnvironment As VoidPtr, lpCurrentDirectory As BytePtr, ByRef lpStartupInfo As STARTUPINFO, ByRef lpProcessInformation As PROCESS_INFORMATION) As BOOL
477
478TypeDef LPTHREAD_START_ROUTINE = *Function(lpThreadParameter As VoidPtr) As DWord
479Declare Function CreateThread Lib "kernel32" Alias "CreateThread" (lpThreadAttributes As *SECURITY_ATTRIBUTES, dwStackSize As DWord, lpStartAddress As LPTHREAD_START_ROUTINE, lpParameter As VoidPtr, dwCreationFlags As DWord, ByRef lpThreadId As DWord) As HANDLE
480
481Declare Sub DebugBreak Lib "kernel32" ()
482Declare Sub DeleteCriticalSection Lib "kernel32" (ByRef lpCriticalSection As CRITICAL_SECTION)
483Declare Function DeleteFile Lib "kernel32" Alias "DeleteFileA" (pFileName As PCSTR) As BOOL
484Declare Function DeviceIoControl Lib "Kernel32" (
485 hDevice As HANDLE,
486 dwIoControlCode As DWord,
487 pInBuffer As VoidPtr,
488 nInBufferSize As DWord,
489 pOutBuffer As VoidPtr,
490 nOutBufferSize As DWord,
491 pBytesReturned As DWordPtr,
492 pOverlapped As *OVERLAPPED
493) As Long
494Declare Function DisableThreadLibraryCalls Lib "kernel32" (hLibModule As HINSTANCE) As BOOL
495Declare Function DosDateTimeToFileTime Lib "kernel32" (wFatDate As Word, wFatTime As Word, ByRef lpFileTime As FILETIME) As BOOL
496
497Const DUPLICATE_CLOSE_SOURCE = 1
498Const DUPLICATE_SAME_ACCESS = 2
499Declare Function DuplicateHandle Lib "kernel32" (hSourceProcessHandle As HANDLE, hSourceHandle As HANDLE, hTargetProcessHandle As HANDLE, ByRef TargetHandle As HANDLE, dwDesiredAccess As DWord, bInheritHandle As BOOL, dwOptions As DWord) As BOOL
500
501Declare Sub EnterCriticalSection Lib "kernel32" (ByRef lpCriticalSection As CRITICAL_SECTION)
502Declare Sub ExitProcess Lib "kernel32" (dwExitCode As DWord)
503Declare Sub ExitThread Lib "kernel32" (dwExitCode As DWord)
504Declare Sub FatalAppExit Lib "kernel32" Alias "FatalAppExitA" (Action As DWord, pMessageText As PCSTR)
505Declare Function FileTimeToDosDateTime Lib "kernel32" (ByRef lpFileTime As FILETIME, ByRef lpFatDate As Word, ByRef lpFatTime As Word) As BOOL
506Declare Function FileTimeToLocalFileTime Lib "kernel32" (ByRef lpFileTime As FILETIME, ByRef lpLocalFileTime As FILETIME) As BOOL
507Declare Function FileTimeToSystemTime Lib "kernel32" (ByRef lpFileTime As FILETIME, ByRef lpSystemTime As SYSTEMTIME) As BOOL
508Declare Sub FillMemory Lib "kernel32" Alias "RtlFillMemory" (pDest As VoidPtr, stLength As SIZE_T, c As Byte)
509Declare Function FindClose Lib "kernel32" (hFindFile As HANDLE) As BOOL
510Declare Function FindCloseChangeNotification Lib "kernel32" (hChangeHandle As HANDLE) As BOOL
511Declare Function FindFirstChangeNotification Lib "kernel32" Alias "FindFirstChangeNotificationA" (
512 pPathName As PCSTR,
513 bWatchSubtree As BOOL,
514 dwNotifyFilter As DWord
515) As HANDLE
516
517Type WIN32_FIND_DATA
518 dwFileAttributes As DWord
519 ftCreationTime As FILETIME
520 ftLastAccessTime As FILETIME
521 ftLastWriteTime As FILETIME
522 nFileSizeHigh As DWord
523 nFileSizeLow As DWord
524 dwReserved0 As DWord
525 dwReserved1 As DWord
526 cFileName[ELM(MAX_PATH)] As Byte
527 cAlternateFileName[13] As Byte
528End Type
529TypeDef LPWIN32_FIND_DATA = *WIN32_FIND_DATA
530Declare Function FindFirstFile Lib "kernel32" Alias "FindFirstFileA" (lpFileName As BytePtr, ByRef lpFindFildData As WIN32_FIND_DATA) As HANDLE
531Declare Function FindNextChangeNotification Lib "kernel32" (hChangeHandle As HANDLE) As BOOL
532Declare Function FindNextFile Lib "kernel32" Alias "FindNextFileA" (hFindFile As HANDLE, ByRef lpFindFildData As WIN32_FIND_DATA) As BOOL
533Declare Function FlushFileBuffers Lib "kernel32" (hFile As HANDLE) As BOOL
534Declare Function FlushInstructionCache Lib "kernel32"(hProcess As HANDLE, pBaseAddress As VoidPtr, Size As SIZE_T) As BOOL
535
536Const FORMAT_MESSAGE_ALLOCATE_BUFFER = &H00000100
537Const FORMAT_MESSAGE_IGNORE_INSERTS = &H00000200
538Const FORMAT_MESSAGE_FROM_STRING = &H00000400
539Const FORMAT_MESSAGE_FROM_HMODULE = &H00000800
540Const FORMAT_MESSAGE_FROM_SYSTEM = &H00001000
541Const FORMAT_MESSAGE_ARGUMENT_ARRAY = &H00002000
542Declare Function FormatMessage Lib "kernel32" Alias "FormatMessageA" (dwFlags As DWord, lpSource As VoidPtr, dwMessageId As DWord, dwLanguageId As DWord, lpBuffer As BytePtr, nSize As DWord, Arguments As DWordPtr) As DWord
543Declare Function FreeEnvironmentStrings Lib "kernel32" Alias "FreeEnvironmentStringsA" (pszEnvironmentBlock As PCSTR) As BOOL
544Declare Function FreeLibrary Lib "kernel32" (hLibModule As HINSTANCE) As BOOL
545Declare Sub FreeLibraryAndExitThread Lib "kernel32" (hModule As HANDLE, dwExitCode As DWord)
546Declare Function GetCommandLine Lib "kernel32" Alias "GetCommandLineA" () As BytePtr
547Declare Function GetCompressedFileSize Lib "kernel32" Alias "GetCompressedFileSizeA" (lpFileName As BytePtr, ByRef lpFileSizeHigh As DWord) As DWord
548
549Const MAX_COMPUTERNAME_LENGTH=15
550Declare Function GetComputerName Lib "kernel32" Alias "GetComputerNameA" (lpBuffer As BytePtr, ByRef nSize As Long) As Long
551
552Declare Function GetCurrentDirectory Lib "kernel32" Alias "GetCurrentDirectoryA" (nBufferLength As DWord, lpBuffer As BytePtr) As DWord
553Declare Function GetCurrentProcess Lib "kernel32" () As HANDLE
554Declare Function GetCurrentProcessId Lib "kernel32" () As DWord
555Declare Function GetCurrentThread Lib "kernel32" () As HANDLE
556Declare Function GetCurrentThreadId Lib "kernel32" () As DWord
557
558Const DATE_SHORTDATE = &H00000001
559Const DATE_LONGDATE = &H00000002
560Const DATE_USE_ALT_CALENDAR = &H00000004
561Declare Function GetDateFormat Lib "kernel32" Alias "GetDateFormatA" (Locale As LCID, dwFlags As DWord, ByRef lpDate As SYSTEMTIME, lpFormat As BytePtr, lpDateStr As BytePtr, cchDate As Long) As Long
562
563Declare Function GetDiskFreeSpace Lib "kernel32" Alias "GetDiskFreeSpaceA" (lpRootPathName As BytePtr, lpSectorsPerCluster As *DWord, lpBytesPerSector As *DWord, lpNumberOfFreeClusters As *DWord, lpTotalNumberOfClusters As *DWord) As BOOL
564Declare Function GetDiskFreeSpaceEx Lib "kernel32" Alias "GetDiskFreeSpaceExA" (lpDirectoryName As BytePtr, ByRef lpFreeBytesAvailableToCaller As ULARGE_INTEGER, ByRef lpTotalNumberOfBytes As ULARGE_INTEGER, ByRef lpTotalNumberOfFreeBytes As ULARGE_INTEGER) As BOOL
565
566Const DRIVE_UNKNOWN = 0
567Const DRIVE_NO_ROOT_DIR = 1
568Const DRIVE_REMOVABLE = 2
569Const DRIVE_FIXED = 3
570Const DRIVE_REMOTE = 4
571Const DRIVE_CDROM = 5
572Const DRIVE_RAMDISK = 6
573Declare Function GetVolumeInformation Lib "kernel32" Alias "GetVolumeInformationA" (lpRootPathName As LPCSTR, lpVolumeNameBuffer As LPSTR, nVolumeNameSize As DWord, lpVolumeSerialNumber As *Word, lpMaximumComponentLength As *Word, lpFileSystemFlags As *Word, lpFileSystemNameBuffer As LPSTR, nFileSystemNameSize As DWord) As BOOL
574Declare Function GetDriveType Lib "kernel32" Alias "GetDriveTypeA" (lpRootPathName As BytePtr) As DWord
575
576Declare Function GetEnvironmentVariable Lib "kernel32" Alias "GetEnvironmentVariableA" (lpName As BytePtr, lpBuffer As BytePtr, nSize As DWord) As DWord
577Declare Function GetEnvironmentStrings Lib "kernel32" Alias "GetEnvironmentStringsA" () As VoidPtr
578Const STILL_ACTIVE = &H00000103
579Declare Function GetExitCodeProcess Lib "kernel32" (hProcess As HANDLE, ByRef lpExitCode As DWord) As BOOL
580Declare Function GetExitCodeThread Lib "kernel32" (hThread As HANDLE, ByRef lpExitCode As DWord) As BOOL
581
582Declare Function GetFileAttributes Lib "kernel32" Alias "GetFileAttributesA" (lpFileName As BytePtr) As DWord
583Type BY_HANDLE_FILE_INFORMATION
584 dwFileAttributes As DWord
585 ftCreationTime As FILETIME
586 ftLastAccessTime As FILETIME
587 ftLastWriteTime As FILETIME
588 dwVolumeSerialNumber As DWord
589 nFileSizeHigh As DWord
590 nFileSizeLow As DWord
591 nNumberOfLinks As DWord
592 nFileIndexHigh As DWord
593 nFileIndexLow As DWord
594End Type
595Declare Function GetFileInformationByHandle Lib "kernel32" (
596 ByVal hFile As HANDLE,
597 ByRef FileInformation As BY_HANDLE_FILE_INFORMATION
598) As BOOL
599Declare Function GetFileSize Lib "kernel32" (hFile As HANDLE, lpFileSizeHigh As DWordPtr) As DWord
600Declare Function GetFileTime Lib "kernel32" (hFile As HANDLE, ByRef lpCreationTime As FILETIME, ByRef lpLastAccessTime As FILETIME, ByRef lpLastWriteTime As FILETIME) As BOOL
601
602Const FILE_TYPE_UNKNOWN = &H0000
603Const FILE_TYPE_DISK = &H0001
604Const FILE_TYPE_CHAR = &H0002
605Const FILE_TYPE_PIPE = &H0003
606Const FILE_TYPE_REMOTE = &H8000
607Declare Function GetFileType Lib "kernel32" (hFile As HANDLE) As DWord
608
609Declare Function GetFullPathName Lib "kernel32" Alias "GetFullPathNameA" (lpFileName As PCSTR, nBufferLength As DWord, pBuffer As PSTR, lpFilePart As *DWord) As DWord
610Declare Function GetLastError Lib "kernel32" () As DWord
611Declare Sub GetLocalTime Lib "kernel32" (ByRef lpSystemTime As SYSTEMTIME)
612Declare Function GetLogicalDrives Lib "kernel32" () As DWord
613Declare Function GetLogicalDriveStrings Lib "kernel32" Alias "GetLogicalDriveStringsA" (nBufferLength As DWord, pBuffer As PSTR) As DWord
614Declare Function GetModuleFileName Lib "kernel32" Alias "GetModuleFileNameA" (hModule As HINSTANCE, lpFileName As BytePtr, nSize As DWord) As DWord
615Declare Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleA" (lpModuleName As BytePtr) As HINSTANCE
616Declare Function GetOverlappedResult Lib "kernel32" (
617 hFile As HANDLE,
618 pOverlapped As *OVERLAPPED,
619 pNumberOfBytesTransferred AS *DWord,
620 bWait As BOOL
621) As BOOL
622Declare Function GetPriorityClass Lib "kernel32" (hProcess As HANDLE) As DWord
623Declare Function GetProcAddress Lib "kernel32" (hModule As HINSTANCE, lpProcName As BytePtr) As DWord
624Declare Function GetProcessAffinityMask Lib "kernel32" (
625 hProcess As HANDLE,
626 ByRef ProcessAffinityMask As ULONG_PTR,
627 ByRef SystemAffinityMask As ULONG_PTR
628) As BOOL
629Declare Function GetProcessHeap Lib "kernel32" () As HANDLE
630Declare Function GetShortPathName Lib "kernel32" Alias "GetShortPathNameA" (
631 pszLongPath As PCSTR,
632 pszShortPath As PSTR,
633 cchBuffer As DWord
634) As DWord
635
636Declare Sub GetStartupInfo Lib "kernel32" Alias "GetStartupInfoA" (ByRef lpStartupInfo As STARTUPINFO)
637
638Const STD_INPUT_HANDLE = -10
639Const STD_OUTPUT_HANDLE = -11
640Const STD_ERROR_HANDLE = -12
641Declare Function GetStdHandle Lib "kernel32" (nStdHandle As DWord) As HANDLE
642
643Declare Function GetSystemDirectory Lib "kernel32" Alias "GetSystemDirectoryA" (pBuffer As PSTR, uSize As DWord) As DWord
644
645Type SYSTEM_INFO
646 dwOemId As DWord
647 dwPageSize As DWord
648 lpMinimumApplicationAddress As VoidPtr
649 lpMaximumApplicationAddress As VoidPtr
650 dwActiveProcessorMask As ULONG_PTR
651 dwNumberOfProcessors As DWord
652 dwProcessorType As DWord
653 dwAllocationGranularity As DWord
654 wProcessorLevel As Word
655 wProcessorRevision As Word
656End Type
657Declare Sub GetSystemInfo Lib "kernel32" (ByRef lpSystemInfo As SYSTEM_INFO)
658
659Declare Sub GetSystemTime Lib "kernel32" (ByRef SystemTime As SYSTEMTIME)
660Declare Sub GetSystemTimeAsFileTime Lib "kernel32" (ByRef SystemTimeAsFileTime As FILETIME)
661
662Declare Function GetTempFileName Lib "kernel32" Alias "GetTempFileNameA" (
663 pPathName As PCSTR,
664 pPrefixString As PCSTR,
665 uUnique As DWord,
666 pTempFileName As PSTR
667) As DWord
668Declare Function GetTempPath Lib "kernel32" Alias "GetTempPathA" (nBufferLength As DWord, lpBuffer As BytePtr) As DWord
669Declare Function GetThreadContext Lib "kernel32" (hThread As HANDLE, ByRef Context As CONTEXT) As BOOL
670
671Const THREAD_BASE_PRIORITY_LOWRT = 15
672Const THREAD_BASE_PRIORITY_MAX = 2
673Const THREAD_BASE_PRIORITY_MIN = -2
674Const THREAD_BASE_PRIORITY_IDLE = -15
675Const THREAD_PRIORITY_LOWEST = THREAD_BASE_PRIORITY_MIN
676Const THREAD_PRIORITY_BELOW_NORMAL = THREAD_PRIORITY_LOWEST+1
677Const THREAD_PRIORITY_NORMAL = 0
678Const THREAD_PRIORITY_HIGHEST = THREAD_BASE_PRIORITY_MAX
679Const THREAD_PRIORITY_ABOVE_NORMAL = THREAD_PRIORITY_HIGHEST-1
680Const THREAD_PRIORITY_ERROR_RETURN = LONG_MAX
681Const THREAD_PRIORITY_TIME_CRITICAL = THREAD_BASE_PRIORITY_LOWRT
682Const THREAD_PRIORITY_IDLE = THREAD_BASE_PRIORITY_IDLE
683Declare Function GetThreadPriority Lib "kernel32" (hThread As HANDLE) As Long
684Declare Function GetThreadPriorityBoost Lib "kernel32" (
685 hThread As HANDLE,
686 ByRef pDisablePriorityBoost As BOOL) As BOOL
687Declare Function GetTickCount Lib "kernel32" () As DWord
688
689Const TIME_NOMINUTESORSECONDS = &H00000001
690Const TIME_NOSECONDS = &H00000002
691Const TIME_NOTIMEMARKER = &H00000004
692Const TIME_FORCE24HOURFORMAT = &H00000008
693Declare Function GetTimeFormat Lib "kernel32" Alias "GetTimeFormatA" (Locale As LCID, dwFlags As DWord, ByRef lpTime As SYSTEMTIME, lpFormat As BytePtr, lpTimeStr As BytePtr, cchTime As DWord) As BOOL
694
695Declare Function GetUserDefaultLCID Lib "kernel32" () As LCID
696Declare Function GetUserName Lib "advapi32" Alias "GetUserNameA" (pBuffer As PSTR, ByRef nSize As DWord) As BOOL
697
698Const VER_PLATFORM_WIN32s = 0
699Const VER_PLATFORM_WIN32_WINDOWS = 1
700Const VER_PLATFORM_WIN32_NT = 2
701Type OSVERSIONINFO
702 dwOSVersionInfoSize As DWord
703 dwMajorVersion As DWord
704 dwMinorVersion As DWord
705 dwBuildNumber As DWord
706 dwPlatformId As DWord
707 szCSDVersion[127] As Byte
708End Type
709Declare Function GetVersionEx Lib "kernel32" Alias "GetVersionExA" (ByRef lpVersionInformation As OSVERSIONINFO) As BOOL
710
711Declare Function GetWindowsDirectory Lib "kernel32" Alias "GetWindowsDirectoryA" (pBuffer As PSTR, uSize As DWord) As DWord
712Declare Function GlobalAlloc Lib "kernel32" (uFlags As DWord, dwBytes As SIZE_T) As HGLOBAL
713Declare Function GlobalFrags Lib "kernel32" (hMem As HGLOBAL) As DWord
714Declare Function GlobalFree Lib "kernel32" (hMem As HGLOBAL) As HGLOBAL
715Declare Function GlobalHandle Lib "kernel32" (pMem As VoidPtr) As HGLOBAL
716Declare Function GlobalLock Lib "kernel32" (hMem As HGLOBAL) As VoidPtr
717
718Type MEMORYSTATUS
719 dwLength As DWord
720 dwMemoryLoad As DWord
721 dwTotalPhys As SIZE_T
722 dwAvailPhys As SIZE_T
723 dwTotalPageFile As SIZE_T
724 dwAvailPageFile As SIZE_T
725 dwTotalVirtual As SIZE_T
726 dwAvailVirtual As SIZE_T
727End Type
728Declare Sub GlobalMemoryStatus Lib "kernel32" (ByRef lpMemStatus As MEMORYSTATUS)
729
730Declare Function GlobalReAlloc Lib "kernel32" (hMem As HGLOBAL, dwBytes As SIZE_T, uFlags As DWord) As HGLOBAL
731Declare Function GlobalSize Lib "kernel32" (hMem As HGLOBAL) As SIZE_T
732Declare Function GlobalUnlock Lib "kernel32" (hMem As HGLOBAL) As BOOL
733Declare Function HeapAlloc Lib "kernel32" (hHeap As HANDLE, dwFlags As DWord, dwBytes As SIZE_T) As VoidPtr
734Declare Function HeapCreate Lib "kernel32" (flOptions As DWord, dwInitialSize As SIZE_T, dwMaximumSize As SIZE_T) As HANDLE
735Declare Function HeapDestroy Lib "kernel32" (hHeap As HANDLE) As Long
736Declare Function HeapFree Lib "kernel32" (hHeap As HANDLE, dwFlags As DWord, lpMem As VoidPtr) As Long
737Declare Function HeapReAlloc Lib "kernel32" (hHeap As HANDLE, dwFlags As DWord, lpMem As VoidPtr, dwBytes As SIZE_T) As VoidPtr
738Declare Function HeapSize Lib "kernel32" (hHeap As HANDLE, dwFlags As DWord, lpMem As VoidPtr) As SIZE_T
739Declare Sub InitializeCriticalSection Lib "kernel32" (ByRef lpCriticalSection As CRITICAL_SECTION)
740Declare Function IsBadReadPtr Lib "kernel32" (lp As VoidPtr, ucb As ULONG_PTR) As BOOL
741Declare Function IsBadWritePtr Lib "kernel32" (lp As VoidPtr, ucb As ULONG_PTR) As BOOL
742Declare Function IsDBCSLeadByte Lib "kernel32" (TestChar As Byte) As BOOL
743
744#ifdef _WIN64
745Declare Function IsWow64Process Lib "kernel32" (hProcess As HANDLE, ByRef bWow64Process As BOOL) As BOOL
746#endif
747
748Const LCMAP_LOWERCASE = &H00000100 ' lower case letters
749Const LCMAP_UPPERCASE = &H00000200 ' upper case letters
750Const LCMAP_SORTKEY = &H00000400 ' WC sort key (normalize)
751Const LCMAP_BYTEREV = &H00000800 ' byte reversal
752Const LCMAP_HIRAGANA = &H00100000 ' map katakana to hiragana
753Const LCMAP_KATAKANA = &H00200000 ' map hiragana to katakana
754Const LCMAP_HALFWIDTH = &H00400000 ' map double byte to single byte
755Const LCMAP_FULLWIDTH = &H00800000 ' map single byte to double byte
756Const LCMAP_LINGUISTIC_CASING = &H01000000 ' use linguistic rules for casing
757Const LCMAP_SIMPLIFIED_CHINESE = &H02000000 ' map traditional chinese to simplified chinese
758Const LCMAP_TRADITIONAL_CHINESE = &H04000000 ' map simplified chinese to traditional chinese
759Declare Function LCMapString Lib "kernel32" Alias "LCMapStringA" (Locale As LCID, dwMapFlags As DWord, lpSrcStr As LPCSTR, cchSrc As Long, lpDestStr As LPSTR, cchDest As Long) As Long
760
761Declare Sub LeaveCriticalSection Lib "kernel32" (ByRef lpCriticalSection As CRITICAL_SECTION)
762Declare Function LocalAlloc Lib "kernel32" (uFlags As DWord, uBytes As SIZE_T) As HLOCAL
763Declare Function LocalFileTimeToFileTime Lib "kernel32" (ByRef lpLocalFileTime As FILETIME, ByRef lpFileTime As FILETIME) As BOOL
764Declare Function LocalFree Lib "kernel32" (hMem As HLOCAL) As HLOCAL
765Declare Function LocalHandle Lib "kernel32" (pMem As VoidPtr) As HLOCAL
766Declare Function LocalLock Lib "kernel32" (hMem As HLOCAL) As VoidPtr
767Declare Function LocalReAlloc Lib "kernel32" (hMem As HLOCAL, dwBytes As SIZE_T, uFlags As DWord) As HLOCAL
768Declare Function LocalSize Lib "kernel32" (hMem As HLOCAL) As SIZE_T
769Declare Function LocalUnlock Lib "kernel32" (hMem As HLOCAL) As BOOL
770Declare Function LockFile Lib "kernel32" (hFile As DWord, dwFileOffsetLow As DWord, dwFileOffsetHigh As DWord, nNumberOfBytesToLockLow As DWord, nNumberOfBytesToLockHigh As DWord) As BOOL
771Declare Function LoadLibrary Lib "kernel32" Alias "LoadLibraryA" (pLibFileName As PCSTR) As HINSTANCE
772
773Const DONT_RESOLVE_DLL_REFERENCES = &h00000001
774Const LOAD_LIBRARY_AS_DATAFILE = &h00000002
775Const LOAD_WITH_ALTERED_SEARCH_PATH = &h00000008
776Const LOAD_IGNORE_CODE_AUTHZ_LEVEL = &h00000010
777Declare Function LoadLibraryEx Lib "kernel32" Alias "LoadLibraryExA" (pLibFileName As PCSTR, hFile As HANDLE, dwFlags As DWord) As HINSTANCE
778
779Declare Function lstrcat Lib "kernel32" Alias "lstrcatA" (pString1 As PSTR, pString2 As PCSTR) As PSTR
780Declare Function lstrcmp Lib "kernel32" Alias "lstrcmpA" (pString1 As PCSTR, pString2 As PCSTR) As Long
781Declare Function lstrcmpi Lib "kernel32" Alias "lstrcmpiA" (pString1 As PCSTR, pString2 As PCSTR) As Long
782Declare Function lstrcpy Lib "kernel32" Alias "lstrcpyA" (pString1 As PSTR, pString2 As PCSTR) As PSTR
783Declare Function lstrlenA Lib "kernel32" (pString As PCSTR) As Long
784Declare Function lstrlenW Lib "kernel32" (pString As PCWSTR) As Long
785#ifdef UNICODE
786Declare Function lstrlen Lib "kernel32" Alias "lstrlenW" (lpString As PCTSTR) As Long
787#else
788Declare Function lstrlen Lib "kernel32" Alias "lstrlenA" (lpString As PCTSTR) As Long
789#endif
790Declare Sub memcpy Lib "kernel32" Alias "RtlMoveMemory" (pDest As VoidPtr, pSrc As VoidPtr, length As SIZE_T)
791Declare Function MoveFile Lib "kernel32" Alias "MoveFileA" (lpExistingFileName As BytePtr, lpNewFileName As BytePtr) As BOOL
792Declare Sub MoveMemory Lib "kernel32" Alias "RtlMoveMemory" (pDest As VoidPtr, pSrc As VoidPtr, length As SIZE_T)
793
794Declare Function MulDiv Lib "kernel32" (
795 nNumber As Long,
796 nNumerator As Long,
797 nDenominator As Long
798) As Long
799
800Const CP_ACP = 0 'default to ANSI code page
801Const CP_OEMCP = 1 'default to OEM code page
802Const CP_MACCP = 2 'default to MAC code page
803Const CP_THREAD_ACP = 3 'current thread's ANSI code page
804Const CP_SYMBOL = 42 'SYMBOL translations
805Const CP_UTF7 = 65000 'UTF-7 translation
806Const CP_UTF8 = 65001 'UTF-8 translation
807
808Declare Function MultiByteToWideChar Lib "kernel32" (CodePage As DWord, dwFlags As DWord, pMultiByteStr As PCSTR, cchMultiByte As Long, pWideCharStr As PWSTR, cchWideChar As Long) As Long
809
810Declare Function OpenEvent Lib "kernel32" Alias "OpenEventA" (dwDesiredAccess As DWord, bInheritHandle As BOOL, pName As PCSTR) As HANDLE
811Declare Function OpenMutex Lib "kernel32" Alias "OpenMutexA" (dwDesiredAccess As DWord, bInheritHandle As BOOL, lpName As LPSTR) As HANDLE
812Declare Function OpenSemaphore Lib "kernel32" Alias "OpenSemaphoreA" (dwDesiredAccess As DWord, bInheritHandle As BOOL, lpName As LPSTR) As HANDLE
813
814Const PROCESS_TERMINATE = &H0001
815Const PROCESS_CREATE_THREAD = &H0002
816Const PROCESS_SET_SESSIONID = &H0004
817Const PROCESS_VM_OPERATION = &H0008
818Const PROCESS_VM_READ = &H0010
819Const PROCESS_VM_WRITE = &H0020
820Const PROCESS_DUP_HANDLE = &H0040
821Const PROCESS_CREATE_PROCESS = &H0080
822Const PROCESS_SET_QUOTA = &H0100
823Const PROCESS_SET_INFORMATION = &H0200
824Const PROCESS_QUERY_INFORMATION = &H0400
825Const PROCESS_ALL_ACCESS = STANDARD_RIGHTS_REQUIRED or SYNCHRONIZE or &HFFF
826Declare Function OpenProcess Lib "kernel32" (dwDesiredAccess As DWord, bInheritHandle As Long, dwProcessId As DWord) As HANDLE
827
828Declare Sub OutputDebugString Lib "kernel32" Alias "OutputDebugStringA" (lpOutputString As BytePtr)
829Declare Function PulseEvent Lib "kernel32" (hEvent As HANDLE) As BOOL
830Declare Sub RaiseException Lib "kernel32" (
831 dwExceptionCode As DWord,
832 dwExceptionFlags As DWord,
833 NumberOfArguments As DWord,
834 pArguments As *ULONG_PTR)
835Declare Function ReadFile Lib "kernel32" (hFile As HANDLE, lpBuffer As VoidPtr, nNumberOfBytesToRead As DWord, lpNumberOfBytesRead As DWordPtr, ByRef lpOverlapped As OVERLAPPED) As BOOL
836Declare Function ReleaseMutex Lib "kernel32" (hMutex As HANDLE) As BOOL
837Declare Function ReleaseSemaphore Lib "kernel32" (hSemaphore As HANDLE, lReleaseCount As Long, ByRef lpPreviousCount As Long) As BOOL
838Declare Function RemoveDirectory Lib "kernel32" Alias "RemoveDirectoryA" (lpPathName As BytePtr) As BOOL
839Declare Function ResetEvent Lib "kernel32" (hEvent As HANDLE) As BOOL
840Declare Function ResumeThread Lib "kernel32" (hThread As HANDLE) As DWord
841Declare Function SetComputerName Lib "kernel32" Alias "SetComputerNameA" (lpComputerName As BytePtr) As BOOL
842Declare Function SetCurrentDirectory Lib "kernel32" Alias "SetCurrentDirectoryA" (lpPathName As BytePtr) As BOOL
843Declare Function SetEndOfFile Lib "kernel32" (hFile As HANDLE) As BOOL
844Declare Function SetEnvironmentVariable Lib "kernel32" Alias "SetEnvironmentVariableA" (lpName As BytePtr, lpValue As BytePtr) As BOOL
845
846Const SEM_FAILCRITICALERRORS = &h0001
847Const SEM_NOGPFAULTERRORBOX = &h0002
848Const SEM_NOALIGNMENTFAULTEXCEPT = &h0004
849Const SEM_NOOPENFILEERRORBOX = &h8000
850Declare Function SetErrorMode Lib "kernel32" (uMode As DWord) As DWord
851Declare Function SetEvent Lib "kernel32" (hEvent As HANDLE) As BOOL
852Declare Function SetFileAttributes Lib "kernel32" Alias "SetFileAttributesA" (lpFileName As BytePtr, dwFileAttributes As DWord) As BOOL
853
854Const FILE_BEGIN = 0
855Const FILE_CURRENT = 1
856Const FILE_END = 2
857Declare Function SetFilePointer Lib "kernel32" (hFile As HANDLE, lDistanceToMove As Long, lpDistanceToMoveHigh As DWordPtr, dwMoveMethod As DWord) As DWord
858
859Declare Function SetFileTime Lib "kernel32" (hFile As HANDLE, ByRef lpCreationTime As FILETIME, ByRef lpLastAccessTime As FILETIME, ByRef lpLastWriteTime As FILETIME) As BOOL
860Declare Function SetLastError Lib "kernel32" (dwErrCode As DWord)
861Declare Function SetLastErrorEx Lib "kernel32" (dwErrCode As DWord, dwType As DWord)
862Declare Function SetLocalTime Lib "kernel32" (ByRef lpSystemTime As SYSTEMTIME) As BOOL
863Declare Function SetPriorityClass Lib "kernel32" (hProcess As HANDLE, dwPriorityClass As DWord) As BOOL
864Declare Function SetThreadContext Lib "kernel32" (hThread As HANDLE, ByRef Context As CONTEXT) As BOOL
865Declare Function SetThreadPriority Lib "kernel32" (hThread As HANDLE, nPriority As Long) As BOOL
866Declare Function SetThreadPriorityBoost Lib "kernel32" (
867 hThread As HANDLE,
868 DisablePriorityBoost As BOOL
869) As BOOL
870
871Const EXCEPTION_MAXIMUM_PARAMETERS = ELM(15)
872
873Type EXCEPTION_RECORD
874 ExceptionCode As DWord
875 ExceptionFlags As DWord
876 ExceptionRecord As *EXCEPTION_RECORD
877 ExceptionAddress As VoidPtr
878 NumberParameters As DWord
879 ExceptionInformation[EXCEPTION_MAXIMUM_PARAMETERS] As ULONG_PTR
880End Type
881
882Type EXCEPTION_POINTERS
883 ExceptionRecord As *EXCEPTION_RECORD
884 ContextRecord As *CONTEXT
885End Type
886
887TypeDef PTOP_LEVEL_EXCEPTION_FILTER = *Function(ByRef ExceptionInfo As EXCEPTION_POINTERS) As Long
888
889Declare Function SetUnhandledExceptionFilter Lib "kernel32" (pTopLevelExceptionFilter As PTOP_LEVEL_EXCEPTION_FILTER) As PTOP_LEVEL_EXCEPTION_FILTER
890
891Const INFINITE = &HFFFFFFFF
892Declare Sub Sleep Lib "kernel32" (dwMilliseconds As DWord)
893Declare Function SleepEx Lib "kernel32" (dwMilliseconds As DWord, bAlertable As BOOL) As DWord
894
895Declare Function SuspendThread Lib "kernel32" (hThread As HANDLE) As DWord
896Declare Function SystemTimeToFileTime Lib "kernel32" (ByRef lpSystemTime As SYSTEMTIME, ByRef lpFileTime As FILETIME) As BOOL
897Declare Function TerminateProcess Lib "kernel32" (hProcess As HANDLE, dwExitCode As DWord) As BOOL
898Declare Function TerminateThread Lib "kernel32" (hThread As HANDLE, dwExitCode As DWord) As BOOL
899Declare Function TlsAlloc Lib "kernel32" () As DWord
900Declare Function TlsFree Lib "kernel32" (dwTlsIndex As DWord) As BOOL
901Declare Function TlsGetValue Lib "kernel32" (dwTlsIndex As DWord) As VoidPtr
902Declare Function TlsSetValue Lib "kernel32" (dwTlsIndex As DWord, pTlsValue As VoidPtr) As BOOL
903Declare Function UnlockFile Lib "kernel32" (hFile As HANDLE, dwFileOffsetLow As DWord, dwFileOffsetHigh As DWord, nNumberOfBytesToUnlockLow As DWord, nNumberOfBytesToUnlockHigh As DWord) As BOOL
904Declare Function UnhandledExceptionFilter Lib "kernel32" (ByRef ExceptionInfo As EXCEPTION_POINTERS) As Long
905
906Const PAGE_NOACCESS = &H01
907Const PAGE_READONLY = &H02
908Const PAGE_READWRITE = &H04
909Const PAGE_WRITECOPY = &H08
910Const PAGE_EXECUTE = &H10
911Const PAGE_EXECUTE_READ = &H20
912Const PAGE_EXECUTE_READWRITE = &H40
913Const PAGE_EXECUTE_WRITECOPY = &H80
914Const PAGE_GUARD = &H100
915Const PAGE_NOCACHE = &H200
916Const PAGE_WRITECOMBINE = &H400
917Const MEM_COMMIT = &H1000
918Const MEM_RESERVE = &H2000
919Const MEM_DECOMMIT = &H4000
920Const MEM_RELEASE = &H8000
921Const MEM_FREE = &H10000
922Const MEM_PRIVATE = &H20000
923Const MEM_MAPPED = &H40000
924Const MEM_RESET = &H80000
925Const MEM_TOP_DOWN = &H100000
926Const MEM_4MB_PAGES = &H80000000
927Declare Function VirtualAlloc Lib "kernel32" (lpAddress As VoidPtr, dwSize As SIZE_T, flAllocationType As DWord, flProtect As DWord) As VoidPtr
928Declare Function VirtualFree Lib "kernel32" (lpAddress As VoidPtr, dwSize As SIZE_T, dwFreeType As DWord) As BOOL
929Declare Function VirtualLock Lib "kernel32" (lpAddress As VoidPtr, dwSize As SIZE_T) As BOOL
930Declare Function VirtualProtect Lib "kernel32" (
931 pAddress As VoidPtr,
932 Size As SIZE_T,
933 flNewProtect As DWord,
934 ByRef flOldProtect As DWord
935) As BOOL
936Declare Function VirtualProtectEx Lib "kernel32" (
937 hProcess As HANDLE,
938 pAddress As VoidPtr,
939 Size As SIZE_T,
940 flNewProtect As DWord,
941 ByRef flOldProtect As DWord
942) As BOOL
943Type MEMORY_BASIC_INFORMATION
944 BaseAddress As VoidPtr
945 AllocationBase As VoidPtr
946 AllocationProtect As DWord
947 RegionSize As SIZE_T
948 State As DWord
949 Protect As DWord
950 MBIType As DWord
951End Type
952Declare Function VirtualQuery Lib "kernel32" (
953 pAddress As VoidPtr,
954 ByRef mbi As MEMORY_BASIC_INFORMATION,
955 Length As SIZE_T
956) As SIZE_T
957Declare Function VirtualQueryEx Lib "kernel32" (
958 hProcess As HANDLE,
959 pAddress As VoidPtr,
960 ByRef mbi As MEMORY_BASIC_INFORMATION,
961 Length As SIZE_T
962) As SIZE_T
963Declare Function VirtualUnlock Lib "kernel32" (lpAddress As VoidPtr, dwSize As SIZE_T) As BOOL
964Declare Function WaitForMultipleObjects Lib "kernel32" (nCount As DWord, pHandles As *HANDLE, fWaitAll As BOOL, dwMilliseconds As DWord) As DWord
965Declare Function WaitForMultipleObjectsEx Lib "kernel32" (nCount As DWord, pHandles As *HANDLE, fWaitAll As BOOL, dwMilliseconds As DWord, bAlertable As BOOL) As DWord
966Declare Function WaitForSingleObject Lib "kernel32" (hHandle As HANDLE, dwMilliseconds As DWord) As DWord
967Declare Function WaitForSingleObjectEx Lib "kernel32" (hHandle As HANDLE, dwMilliseconds As DWord, bAlertable As BOOL) As DWord
968
969Const WC_COMPOSITECHECK = &H00000200
970Const WC_DISCARDNS = &H00000010
971Const WC_SEPCHARS = &H00000020
972Const WC_DEFAULTCHAR = &H00000040
973Const WC_NO_BEST_FIT_CHARS = &H00000400
974Declare Function WideCharToMultiByte Lib "Kernel32" (
975 CodePage As DWord,
976 dwFlags As DWord,
977 pWideCharStr As PCWSTR,
978 cchWideChar As Long,
979 pMultiByteStr As PSTR,
980 cbMultiByte As Long,
981 pDefaultChar As PCSTR,
982 pUsedDefaultChar As *BOOL
983) As Long
984
985Declare Function WriteFile Lib "kernel32" (hFile As HANDLE, lpBuffer As VoidPtr, nNumberOfBytesToWrite As DWord, lpNumberOfBytesWritten As DWordPtr, ByRef lpOverlapped As OVERLAPPED) As BOOL
986Declare Sub ZeroMemory Lib "kernel32" Alias "RtlZeroMemory" (Destination As VoidPtr, dwLength As DWord)
987
988Const MAKELCID(lgid, srtid) = ((((srtid As Word) As DWord)<<16) or ((lgid As Word) As DWord))
989Const MAKELANGID(p, s) = (((s As Word) << 10) or (p As Word))
990Const PRIMARYLANGID(lgid) = ((lgid As Word) and &H3ff)
991Const SUBLANGID(lgid) = ((lgid As Word) >> 10)
992
993
994'
995' Primary language IDs.
996'
997
998Const LANG_NEUTRAL = &H00
999Const LANG_INVARIANT = &H7f
1000
1001Const LANG_AFRIKAANS = &H36
1002Const LANG_ALBANIAN = &H1c
1003Const LANG_ARABIC = &H01
1004Const LANG_ARMENIAN = &H2b
1005Const LANG_ASSAMESE = &H4d
1006Const LANG_AZERI = &H2c
1007Const LANG_BASQUE = &H2d
1008Const LANG_BELARUSIAN = &H23
1009Const LANG_BENGALI = &H45
1010Const LANG_BULGARIAN = &H02
1011Const LANG_CATALAN = &H03
1012Const LANG_CHINESE = &H04
1013Const LANG_CROATIAN = &H1a
1014Const LANG_CZECH = &H05
1015Const LANG_DANISH = &H06
1016Const LANG_DIVEHI = &H65
1017Const LANG_DUTCH = &H13
1018Const LANG_ENGLISH = &H09
1019Const LANG_ESTONIAN = &H25
1020Const LANG_FAEROESE = &H38
1021Const LANG_FARSI = &H29
1022Const LANG_FINNISH = &H0b
1023Const LANG_FRENCH = &H0c
1024Const LANG_GALICIAN = &H56
1025Const LANG_GEORGIAN = &H37
1026Const LANG_GERMAN = &H07
1027Const LANG_GREEK = &H08
1028Const LANG_GUJARATI = &H47
1029Const LANG_HEBREW = &H0d
1030Const LANG_HINDI = &H39
1031Const LANG_HUNGARIAN = &H0e
1032Const LANG_ICELANDIC = &H0f
1033Const LANG_INDONESIAN = &H21
1034Const LANG_ITALIAN = &H10
1035Const LANG_JAPANESE = &H11
1036Const LANG_KANNADA = &H4b
1037Const LANG_KASHMIRI = &H60
1038Const LANG_KAZAK = &H3f
1039Const LANG_KONKANI = &H57
1040Const LANG_KOREAN = &H12
1041Const LANG_KYRGYZ = &H40
1042Const LANG_LATVIAN = &H26
1043Const LANG_LITHUANIAN = &H27
1044Const LANG_MACEDONIAN = &H2f ' the Former Yugoslav Republic of Macedonia
1045Const LANG_MALAY = &H3e
1046Const LANG_MALAYALAM = &H4c
1047Const LANG_MANIPURI = &H58
1048Const LANG_MARATHI = &H4e
1049Const LANG_MONGOLIAN = &H50
1050Const LANG_NEPALI = &H61
1051Const LANG_NORWEGIAN = &H14
1052Const LANG_ORIYA = &H48
1053Const LANG_POLISH = &H15
1054Const LANG_PORTUGUESE = &H16
1055Const LANG_PUNJABI = &H46
1056Const LANG_ROMANIAN = &H18
1057Const LANG_RUSSIAN = &H19
1058Const LANG_SANSKRIT = &H4f
1059Const LANG_SERBIAN = &H1a
1060Const LANG_SINDHI = &H59
1061Const LANG_SLOVAK = &H1b
1062Const LANG_SLOVENIAN = &H24
1063Const LANG_SPANISH = &H0a
1064Const LANG_SWAHILI = &H41
1065Const LANG_SWEDISH = &H1d
1066Const LANG_SYRIAC = &H5a
1067Const LANG_TAMIL = &H49
1068Const LANG_TATAR = &H44
1069Const LANG_TELUGU = &H4a
1070Const LANG_THAI = &H1e
1071Const LANG_TURKISH = &H1f
1072Const LANG_UKRAINIAN = &H22
1073Const LANG_URDU = &H20
1074Const LANG_UZBEK = &H43
1075Const LANG_VIETNAMESE = &H2a
1076
1077'
1078' Sublanguage IDs.
1079'
1080' The name immediately following SUBLANG_ dictates which primary
1081' language ID that sublanguage ID can be combined with to form a
1082' valid language ID.
1083'
1084
1085Const SUBLANG_NEUTRAL = &H00 ' language neutral
1086Const SUBLANG_DEFAULT = &H01 ' user default
1087Const SUBLANG_SYS_DEFAULT = &H02 ' system default
1088
1089Const SUBLANG_ARABIC_SAUDI_ARABIA = &H01 ' Arabic (Saudi Arabia)
1090Const SUBLANG_ARABIC_IRAQ = &H02 ' Arabic (Iraq)
1091Const SUBLANG_ARABIC_EGYPT = &H03 ' Arabic (Egypt)
1092Const SUBLANG_ARABIC_LIBYA = &H04 ' Arabic (Libya)
1093Const SUBLANG_ARABIC_ALGERIA = &H05 ' Arabic (Algeria)
1094Const SUBLANG_ARABIC_MOROCCO = &H06 ' Arabic (Morocco)
1095Const SUBLANG_ARABIC_TUNISIA = &H07 ' Arabic (Tunisia)
1096Const SUBLANG_ARABIC_OMAN = &H08 ' Arabic (Oman)
1097Const SUBLANG_ARABIC_YEMEN = &H09 ' Arabic (Yemen)
1098Const SUBLANG_ARABIC_SYRIA = &H0a ' Arabic (Syria)
1099Const SUBLANG_ARABIC_JORDAN = &H0b ' Arabic (Jordan)
1100Const SUBLANG_ARABIC_LEBANON = &H0c ' Arabic (Lebanon)
1101Const SUBLANG_ARABIC_KUWAIT = &H0d ' Arabic (Kuwait)
1102Const SUBLANG_ARABIC_UAE = &H0e ' Arabic (U.A.E)
1103Const SUBLANG_ARABIC_BAHRAIN = &H0f ' Arabic (Bahrain)
1104Const SUBLANG_ARABIC_QATAR = &H10 ' Arabic (Qatar)
1105Const SUBLANG_AZERI_LATIN = &H01 ' Azeri (Latin)
1106Const SUBLANG_AZERI_CYRILLIC = &H02 ' Azeri (Cyrillic)
1107Const SUBLANG_CHINESE_TRADITIONAL = &H01 ' Chinese (Taiwan)
1108Const SUBLANG_CHINESE_SIMPLIFIED = &H02 ' Chinese (PR China)
1109Const SUBLANG_CHINESE_HONGKONG = &H03 ' Chinese (Hong Kong S.A.R., P.R.C.)
1110Const SUBLANG_CHINESE_SINGAPORE = &H04 ' Chinese (Singapore)
1111Const SUBLANG_CHINESE_MACAU = &H05 ' Chinese (Macau S.A.R.)
1112Const SUBLANG_DUTCH = &H01 ' Dutch
1113Const SUBLANG_DUTCH_BELGIAN = &H02 ' Dutch (Belgian)
1114Const SUBLANG_ENGLISH_US = &H01 ' English (USA)
1115Const SUBLANG_ENGLISH_UK = &H02 ' English (UK)
1116Const SUBLANG_ENGLISH_AUS = &H03 ' English (Australian)
1117Const SUBLANG_ENGLISH_CAN = &H04 ' English (Canadian)
1118Const SUBLANG_ENGLISH_NZ = &H05 ' English (New Zealand)
1119Const SUBLANG_ENGLISH_EIRE = &H06 ' English (Irish)
1120Const SUBLANG_ENGLISH_SOUTH_AFRICA = &H07 ' English (South Africa)
1121Const SUBLANG_ENGLISH_JAMAICA = &H08 ' English (Jamaica)
1122Const SUBLANG_ENGLISH_CARIBBEAN = &H09 ' English (Caribbean)
1123Const SUBLANG_ENGLISH_BELIZE = &H0a ' English (Belize)
1124Const SUBLANG_ENGLISH_TRINIDAD = &H0b ' English (Trinidad)
1125Const SUBLANG_ENGLISH_ZIMBABWE = &H0c ' English (Zimbabwe)
1126Const SUBLANG_ENGLISH_PHILIPPINES = &H0d ' English (Philippines)
1127Const SUBLANG_FRENCH = &H01 ' French
1128Const SUBLANG_FRENCH_BELGIAN = &H02 ' French (Belgian)
1129Const SUBLANG_FRENCH_CANADIAN = &H03 ' French (Canadian)
1130Const SUBLANG_FRENCH_SWISS = &H04 ' French (Swiss)
1131Const SUBLANG_FRENCH_LUXEMBOURG = &H05 ' French (Luxembourg)
1132Const SUBLANG_FRENCH_MONACO = &H06 ' French (Monaco)
1133Const SUBLANG_GERMAN = &H01 ' German
1134Const SUBLANG_GERMAN_SWISS = &H02 ' German (Swiss)
1135Const SUBLANG_GERMAN_AUSTRIAN = &H03 ' German (Austrian)
1136Const SUBLANG_GERMAN_LUXEMBOURG = &H04 ' German (Luxembourg)
1137Const SUBLANG_GERMAN_LIECHTENSTEIN = &H05 ' German (Liechtenstein)
1138Const SUBLANG_ITALIAN = &H01 ' Italian
1139Const SUBLANG_ITALIAN_SWISS = &H02 ' Italian (Swiss)
1140Const SUBLANG_KASHMIRI_SASIA = &H02 ' Kashmiri (South Asia)
1141Const SUBLANG_KOREAN = &H01 ' Korean (Extended Wansung)
1142Const SUBLANG_LITHUANIAN = &H01 ' Lithuanian
1143Const SUBLANG_MALAY_MALAYSIA = &H01 ' Malay (Malaysia)
1144Const SUBLANG_MALAY_BRUNEI_DARUSSALAM = &H02 ' Malay (Brunei Darussalam)
1145Const SUBLANG_NEPALI_INDIA = &H02 ' Nepali (India)
1146Const SUBLANG_NORWEGIAN_BOKMAL = &H01 ' Norwegian (Bokmal)
1147Const SUBLANG_NORWEGIAN_NYNORSK = &H02 ' Norwegian (Nynorsk)
1148Const SUBLANG_PORTUGUESE = &H02 ' Portuguese
1149Const SUBLANG_PORTUGUESE_BRAZILIAN = &H01 ' Portuguese (Brazilian)
1150Const SUBLANG_SERBIAN_LATIN = &H02 ' Serbian (Latin)
1151Const SUBLANG_SERBIAN_CYRILLIC = &H03 ' Serbian (Cyrillic)
1152Const SUBLANG_SPANISH = &H01 ' Spanish (Castilian)
1153Const SUBLANG_SPANISH_MEXICAN = &H02 ' Spanish (Mexican)
1154Const SUBLANG_SPANISH_MODERN = &H03 ' Spanish (Spain)
1155Const SUBLANG_SPANISH_GUATEMALA = &H04 ' Spanish (Guatemala)
1156Const SUBLANG_SPANISH_COSTA_RICA = &H05 ' Spanish (Costa Rica)
1157Const SUBLANG_SPANISH_PANAMA = &H06 ' Spanish (Panama)
1158Const SUBLANG_SPANISH_DOMINICAN_REPUBLIC = &H07 ' Spanish (Dominican Republic)
1159Const SUBLANG_SPANISH_VENEZUELA = &H08 ' Spanish (Venezuela)
1160Const SUBLANG_SPANISH_COLOMBIA = &H09 ' Spanish (Colombia)
1161Const SUBLANG_SPANISH_PERU = &H0a ' Spanish (Peru)
1162Const SUBLANG_SPANISH_ARGENTINA = &H0b ' Spanish (Argentina)
1163Const SUBLANG_SPANISH_ECUADOR = &H0c ' Spanish (Ecuador)
1164Const SUBLANG_SPANISH_CHILE = &H0d ' Spanish (Chile)
1165Const SUBLANG_SPANISH_URUGUAY = &H0e ' Spanish (Uruguay)
1166Const SUBLANG_SPANISH_PARAGUAY = &H0f ' Spanish (Paraguay)
1167Const SUBLANG_SPANISH_BOLIVIA = &H10 ' Spanish (Bolivia)
1168Const SUBLANG_SPANISH_EL_SALVADOR = &H11 ' Spanish (El Salvador)
1169Const SUBLANG_SPANISH_HONDURAS = &H12 ' Spanish (Honduras)
1170Const SUBLANG_SPANISH_NICARAGUA = &H13 ' Spanish (Nicaragua)
1171Const SUBLANG_SPANISH_PUERTO_RICO = &H14 ' Spanish (Puerto Rico)
1172Const SUBLANG_SWEDISH = &H01 ' Swedish
1173Const SUBLANG_SWEDISH_FINLAND = &H02 ' Swedish (Finland)
1174Const SUBLANG_URDU_PAKISTAN = &H01 ' Urdu (Pakistan)
1175Const SUBLANG_URDU_INDIA = &H02 ' Urdu (India)
1176Const SUBLANG_UZBEK_LATIN = &H01 ' Uzbek (Latin)
1177Const SUBLANG_UZBEK_CYRILLIC = &H02 ' Uzbek (Cyrillic)
1178
1179
1180Const LANG_SYSTEM_DEFAULT = (MAKELANGID(LANG_NEUTRAL, SUBLANG_SYS_DEFAULT))
1181Const LANG_USER_DEFAULT = (MAKELANGID(LANG_NEUTRAL, SUBLANG_DEFAULT))
1182
1183
1184'
1185' Sorting IDs.
1186'
1187
1188Const SORT_DEFAULT = &H0 ' sorting default
1189
1190Const SORT_JAPANESE_XJIS = &H0 ' Japanese XJIS order
1191Const SORT_JAPANESE_UNICODE = &H1 ' Japanese Unicode order
1192
1193Const SORT_CHINESE_BIG5 = &H0 ' Chinese BIG5 order
1194Const SORT_CHINESE_PRCP = &H0 ' PRC Chinese Phonetic order
1195Const SORT_CHINESE_UNICODE = &H1 ' Chinese Unicode order
1196Const SORT_CHINESE_PRC = &H2 ' PRC Chinese Stroke Count order
1197Const SORT_CHINESE_BOPOMOFO = &H3 ' Traditional Chinese Bopomofo order
1198
1199Const SORT_KOREAN_KSC = &H0 ' Korean KSC order
1200Const SORT_KOREAN_UNICODE = &H1 ' Korean Unicode order
1201
1202Const SORT_GERMAN_PHONE_BOOK = &H1 ' German Phone Book order
1203
1204Const SORT_HUNGARIAN_DEFAULT = &H0 ' Hungarian Default order
1205Const SORT_HUNGARIAN_TECHNICAL = &H1 ' Hungarian Technical order
1206
1207Const SORT_GEORGIAN_TRADITIONAL = &H0 ' Georgian Traditional order
1208Const SORT_GEORGIAN_MODERN = &H1 ' Georgian Modern order
1209
1210'
1211' Wait functions' results.
1212'
1213Const WAIT_FAILED = (&hFFFFFFFF As DWord)
1214Const WAIT_OBJECT_0 = 0 '((STATUS_WAIT_0 ) + 0)
1215
1216Const WAIT_ABANDONED = &h00000080 As DWord '((STATUS_ABANDONED_WAIT_0 ) + 0)
1217Const WAIT_ABANDONED_0 = WAIT_ABANDONED '((STATUS_ABANDONED_WAIT_0 ) + 0)
1218
1219Const WAIT_IO_COMPLETION = &h000000C0 'STATUS_USER_APC
1220
1221#endif '_INC_SYSTEM
Note: See TracBrowser for help on using the repository browser.