Changeset 142


Ignore:
Timestamp:
Mar 9, 2007, 10:15:34 PM (17 years ago)
Author:
イグトランス (egtra)
Message:

Environment, OperatingSystem, Versionの追加、Unicode対応修正ほか

Location:
Include
Files:
4 added
17 edited

Legend:

Unmodified
Added
Removed
  • Include/Classes/System/Drawing/Font.ab

    r137 r142  
    131131        /*IN const*/ ByRef fontCollection As FontCollection)
    132132#ifdef __STRING_IS_NOT_UNICODE
    133         Dim name = _System_MultiByteToWideChar(familyName)
     133        Dim oldAlloc = _System_AllocForConvertedString
     134        _System_AllocForConvertedString = AddressOf (_System_malloc)
     135        Dim name = ToWCStr(familyName)
    134136        Font(name, emSize, style, unit, fontCollection)
    135137        _System_free(name)
     138        _System_AllocForConvertedString = oldAlloc
    136139#else
    137140        Font(familyName.Chars, emSize, style, unit, fontCollection)
     
    285288            ((lf.fdwUnderline <> FALSE) And FontStyle.Underline)) As FontStyle
    286289    End Function
    287        
     290
    288291    'Const Function SystemFontName() As String
    289292
  • Include/Classes/System/IO/DirectoryInfo.ab

    r129 r142  
    1818
    1919    Function Root() As DirectoryInfo
    20         Dim dirInfo as DirectoryInfo(Path.GetPathRoot(FullPath))
     20        Dim dirInfo As DirectoryInfo(Path.GetPathRoot(FullPath))
    2121        Return dirInfo
    2222    End Function
     
    2424    'Public Method
    2525    Sub Create()
    26         CreateDirectory(FullPath, NULL)
     26        CreateDirectory(ToTCStr(FullPath), NULL)
    2727    End Sub
    2828
     
    3131
    3232    Override Sub Delete()
    33         RemoveDirectory(FullPath)
     33        RemoveDirectory(ToTCStr(FullPath))
    3434    End Sub
    3535
     
    5454/*  Function GetFiles() As Array
    5555    End Function*/
    56    
     56
    5757/*  Function GetFiles(searchPattern As String) As Array
    5858    End Function*/
    59    
     59
    6060/*  Function GetFiles(searchPattern As String, searchOption As SearchOption) As Array
    6161    End Function*/
     
    6868
    6969    Sub MoveTo(destDirName As String)
    70         If MoveFile(FullPath, destDirName) = False Then
     70        If MoveFile(ToTCStr(FullPath), ToTCStr(destDirName)) = FALSE Then
    7171            'Exception
    7272        End If
  • Include/Classes/System/IO/DriveInfo.ab

    r64 r142  
    3535
    3636    Function DriveFormat() As String
    37         Dim systemName As String
    38         systemName.ReSize(15)
    39         If GetVolumeInformation(m_DriveName, NULL, NULL, NULL, NULL, NULL, systemName, 16) Then
     37        Dim systemName[15] As TCHAR
     38        If GetVolumeInformation(m_DriveName, NULL, NULL, NULL, NULL, NULL, systemName, Len (systemName)) Then
    4039            Return systemName
    4140        Else
     
    4847    End Function
    4948
    50     Function IsReady() As BOOL
     49    Function IsReady() As Boolean
    5150        If GetVolumeInformation(m_DriveName, NULL, NULL, NULL, NULL, NULL, NULL, NULL) Then
    52             Return _System_TRUE
     51            Return True
    5352        Else
    54             Return _System_FALSE
     53            Return False
    5554        End If
    5655    End Function
     
    8281
    8382    Function VolumeLabel() As String
    84         Dim volumeName As String
    85         volumeName.ReSize(63)
     83        Dim volumeName[63] As TCAHR
    8684        If GetVolumeInformation(m_DriveName, volumeName, 64, NULL, NULL, NULL, NULL, NULL) Then
    8785            Return volumeName
  • Include/Classes/System/IO/FileSystemInfo.ab

    r130 r142  
    167167    Virtual Sub Refresh()
    168168        Dim data As WIN32_FIND_DATA
    169         Dim hFind As HANDLE
    170         hFind = FindFirstFile(FullPath, data)
     169        Dim hFind = FindFirstFile(ToTCStr(FullPath), data)
    171170        FindClose(hFind)
    172171
     
    179178Private
    180179    Function setFileTime() As Boolean
    181         Dim hFile As HANDLE
    182         hFile = CreateFile(FullPath, GENERIC_WRITE, FILE_SHARE_READ Or FILE_SHARE_WRITE, ByVal 0, OPEN_EXISTING, FILE_FLAG_BACKUP_SEMANTICS, 0)
     180        Dim hFile = CreateFile(ToTCStr(FullPath), GENERIC_WRITE, FILE_SHARE_READ Or FILE_SHARE_WRITE, ByVal 0, OPEN_EXISTING, FILE_FLAG_BACKUP_SEMANTICS, 0)
    183181        If hFile = INVALID_HANDLE_VALUE Then
    184182            setFileTime = False
  • Include/Classes/System/IO/Path.ab

    r136 r142  
     1' System/IO/Path.ab
     2
     3#require <Classes/System/Environment.ab>
     4
    15Class Path
    26Public
     
    3640        Return path.Remove(0, extPos)
    3741    End Function
    38    
     42
    3943    Static Function ChangeExtension(path As String, extension As String) As String
    4044        Dim extPos As Long
     
    4953    Static Function HasExtension(ByRef path As String) As Boolean
    5054        If GetExtension(path) <> "" Then
    51             Return _System_TRUE
     55            Return True
    5256        Else
    53             Return _System_FALSE
     57            Return False
    5458        End If
    5559    End Function
     
    7478
    7579    Static Function GetTempPath() As String
    76         GetTempPath.ReSize(__GetTempPath(0, 0) - 1)
    77         __GetTempPath(GetTempPath.Length + 1, GetTempPath)
     80        Dim size = GetTempPath(0, 0
     81        Dim tempPath = _System_malloc(size))
     82        __GetTempPath(size, tempPath)
     83        GetTempPath = tempPath
     84        _System_free(tempPath)
    7885    End Function
    7986
    8087    Static Function GetFullPath(path As String) As String
    81         Dim cd As String
    82         Dim dirSepChar As String(Chr$(DirectorySeparatorChar))
    83         If IsPathRooted(path) Then Return path
    84 
    85         cd.ReSize = GetCurrentDirectory(0, 0) - 1
    86         GetCurrentDirectory(cd.Length + 1, cd)
    87         Return cd + dirSepChar + path
     88        If IsPathRooted(path) Then
     89            Return path
     90        Else
     91            Return Environment.CurrentDirectory + Chr$(DirectorySeparatorChar) + path
     92        End If
    8893    End Function
    8994
     
    108113    End Function
    109114
    110     Static Function IsPathRooted(path As String) As BOOL
     115    Static Function IsPathRooted(path As String) As Boolean
    111116        Dim volSepChar As String(Chr$(VolumeSeparatorChar))
    112117        If path.IndexOf(volSepChar, 1, 1) = 1 Then
    113             Return _System_TRUE
     118            Return True
    114119        Else
    115             Return _System_FALSE
     120            Return False
    116121        End If
    117122    End Function
  • Include/Classes/System/String.ab

    r139 r142  
    1010#else
    1111TypeDef StrChar = WCHAR
     12#ifndef UNICODE
     13#define __STRING_UNICODE_WINDOWS_ANSI
     14#endif
    1215#endif
    1316
     
    494497            Dim i As Long
    495498            For i = 0 To ELM(.m_Length)
    496                 If .Chars[i] = .oldChar Then
    497                     .Chars[i] = .newChar
     499                If .Chars[i] = oldChar Then
     500                    .Chars[i] = newChar
    498501                End If
    499502            Next
     
    558561
    559562    Static Function Copy(s As String) As String
    560         Copy.Resize(s.m_Length)
     563        Copy.ReSize(s.m_Length)
    561564        memcpy(Copy.Chars, This.Chars, SizeOf (StrChar) * m_Length)
    562565    End Function
  • Include/Classes/System/index.ab

    r106 r142  
    44#require "String.ab"
    55#require "TimeSpan.ab"
     6#require "OperatingSystem.ab"
     7#require "Version.ab"
     8#require "Environment.ab"
  • Include/api_console.sbp

    r141 r142  
    33#ifndef _INC_CONSOLE
    44#define _INC_CONSOLE
     5
     6#ifdef UNICODE
     7Const _FuncName_PeekConsoleInput = "PeekConsoleInputW"
     8Const _FuncName_ReadConsoleInput = "ReadConsoleInputW"
     9Const _FuncName_WriteConsoleInput = "WriteConsoleInputW"
     10Const _FuncName_ReadConsoleOutput = "ReadConsoleOutputW"
     11Const _FuncName_WriteConsoleOutput = "WriteConsoleOutputW"
     12Const _FuncName_ReadConsoleOutputCharacter = "ReadConsoleOutputCharacterW"
     13Const _FuncName_WriteConsoleOutputCharacter = "WriteConsoleOutputCharacterW"
     14Const _FuncName_FillConsoleOutputCharacter = "FillConsoleOutputCharacterW"
     15Const _FuncName_ScrollConsoleScreenBuffer = "ScrollConsoleScreenBufferW"
     16Const _FuncName_GetConsoleTitle = "GetConsoleTitleW"
     17Const _FuncName_SetConsoleTitle = "SetConsoleTitleW"
     18Const _FuncName_ReadConsole = "ReadConsoleW"
     19Const _FuncName_WriteConsole = "WriteConsoleW"
     20#else
     21Const _FuncName_PeekConsoleInput = "PeekConsoleInputA"
     22Const _FuncName_ReadConsoleInput = "ReadConsoleInputA"
     23Const _FuncName_WriteConsoleInput = "WriteConsoleInputA"
     24Const _FuncName_ReadConsoleOutput = "ReadConsoleOutputA"
     25Const _FuncName_WriteConsoleOutput = "WriteConsoleOutputA"
     26Const _FuncName_ReadConsoleOutputCharacter = "ReadConsoleOutputCharacterA"
     27Const _FuncName_WriteConsoleOutputCharacter = "WriteConsoleOutputCharacterA"
     28Const _FuncName_FillConsoleOutputCharacter = "FillConsoleOutputCharacterA"
     29Const _FuncName_ScrollConsoleScreenBuffer = "ScrollConsoleScreenBufferA"
     30Const _FuncName_GetConsoleTitle = "GetConsoleTitleA"
     31Const _FuncName_SetConsoleTitle = "SetConsoleTitleA"
     32Const _FuncName_ReadConsole = "ReadConsoleA"
     33Const _FuncName_WriteConsole = "WriteConsoleA"
     34#endif
    535
    636Type COORD
     
    153183Const ENABLE_WRAP_AT_EOL_OUTPUT = &H0002
    154184
    155 Declare Function PeekConsoleInput Lib "kernel32" Alias "PeekConsoleInputA" (hConsoleInput As HANDLE, ByRef lpBuffer As INPUT_RECORD, nLength As DWord, ByRef lpNumberOfEventsRead As DWord) As BOOL
    156 Declare Function ReadConsoleInput Lib "kernel32" Alias "ReadConsoleInputA" (hConsoleInput As HANDLE, ByRef lpBuffer As INPUT_RECORD, nLength As DWord, ByRef lpNumberOfEventsRead As DWord) As BOOL
    157 Declare Function WriteConsoleInput Lib "kernel32" Alias "WriteConsoleInputA" (hConsoleInput As HANDLE, ByRef lpBuffer As INPUT_RECORD, nLength As DWord, ByRef lpNumberOfEventsWritten As DWord) As BOOL
    158 Declare Function ReadConsoleOutput Lib "kernel32" Alias "ReadConsoleOutputA" (hConsoleOutput As HANDLE, lpBuffer As *CHAR_INFO, ByRef dwBufferSize As COORD, ByRef dwBufferCoord As COORD, ByRef lpReadRegion As SMALL_RECT) As BOOL
    159 Declare Function WriteConsoleOutput Lib "kernel32" Alias "WriteConsoleOutputA" (hConsoleOutput As HANDLE, lpBuffer As *CHAR_INFO, ByRef dwBufferSize As COORD, ByRef dwBufferCoord As COORD, ByRef lpWriteRegion As SMALL_RECT) As BOOL
    160 Declare Function ReadConsoleOutputCharacter Lib "kernel32" Alias "ReadConsoleOutputCharacterA" (hConsoleOutput As HANDLE, lpCharacter As LPSTR, nLength As DWord, ByRef dwReadCoord As COORD, ByRef lpNumberOfCharsRead As DWord) As BOOL
     185Declare Function PeekConsoleInput Lib "kernel32" Alias _FuncName_PeekConsoleInput (hConsoleInput As HANDLE, ByRef lpBuffer As INPUT_RECORD, nLength As DWord, ByRef lpNumberOfEventsRead As DWord) As BOOL
     186Declare Function ReadConsoleInput Lib "kernel32" Alias _FuncName_ReadConsoleInput (hConsoleInput As HANDLE, ByRef lpBuffer As INPUT_RECORD, nLength As DWord, ByRef lpNumberOfEventsRead As DWord) As BOOL
     187Declare Function WriteConsoleInput Lib "kernel32" Alias _FuncName_WriteConsoleInput (hConsoleInput As HANDLE, ByRef lpBuffer As INPUT_RECORD, nLength As DWord, ByRef lpNumberOfEventsWritten As DWord) As BOOL
     188Declare Function ReadConsoleOutput Lib "kernel32" Alias _FuncName_ReadConsoleOutput (hConsoleOutput As HANDLE, lpBuffer As *CHAR_INFO, ByRef dwBufferSize As COORD, ByRef dwBufferCoord As COORD, ByRef lpReadRegion As SMALL_RECT) As BOOL
     189Declare Function WriteConsoleOutput Lib "kernel32" Alias _FuncName_WriteConsoleOutput (hConsoleOutput As HANDLE, lpBuffer As *CHAR_INFO, ByRef dwBufferSize As COORD, ByRef dwBufferCoord As COORD, ByRef lpWriteRegion As SMALL_RECT) As BOOL
     190Declare Function ReadConsoleOutputCharacter Lib "kernel32" Alias _FuncName_ReadConsoleOutputCharacter (hConsoleOutput As HANDLE, lpCharacter As LPSTR, nLength As DWord, ByRef dwReadCoord As COORD, ByRef lpNumberOfCharsRead As DWord) As BOOL
    161191Declare Function ReadConsoleOutputAttribute Lib "kernel32" (hConsoleOutput As HANDLE, lpAttribute As *Word, nLength As DWord, ByRef dwReadCoord As COORD, ByRef lpNumberOfAttrsRead As DWord) As BOOL
    162 Declare Function WriteConsoleOutputCharacter Lib "kernel32" Alias "WriteConsoleOutputCharacterA" (hConsoleOutput As HANDLE, lpCharacter As LPSTR, nLength As DWord, ByRef dwWriteCoord As COORD, ByRef lpNumberOfCharsWritten As DWord) As BOOL
     192Declare Function WriteConsoleOutputCharacter Lib "kernel32" Alias _FuncName_WriteConsoleOutputCharacter (hConsoleOutput As HANDLE, lpCharacter As LPSTR, nLength As DWord, ByRef dwWriteCoord As COORD, ByRef lpNumberOfCharsWritten As DWord) As BOOL
    163193Declare Function WriteConsoleOutputAttribute Lib "kernel32" (hConsoleOutput As HANDLE, lpAttribute As *Word, nLength As DWord, ByRef dwWriteCoord As COORD, ByRef lpNumberOfAttrsWritten As DWord) As BOOL
    164 Declare Function FillConsoleOutputCharacter Lib "kernel32" Alias "FillConsoleOutputCharacterA" (hConsoleOutput As HANDLE, cCharacter As Char, nLength As DWord, ByRef dwWriteCoord As COORD, ByRef lpNumberOfCharsWritten As DWord) As BOOL
     194Declare Function FillConsoleOutputCharacter Lib "kernel32" Alias _FuncName_FillConsoleOutputCharacter (hConsoleOutput As HANDLE, cCharacter As Char, nLength As DWord, ByRef dwWriteCoord As COORD, ByRef lpNumberOfCharsWritten As DWord) As BOOL
    165195Declare Function FillConsoleOutputAttribute Lib "kernel32" (hConsoleOutput As HANDLE, wAttribute As Word, nLength As DWord, ByRef dwWriteCoord As COORD, ByRef lpNumberOfAttrsWritten As DWord) As BOOL
    166196Declare Function GetConsoleMode Lib "kernel32" (hConsoleHandle As HANDLE, ByRef lpMode As DWord) As BOOL
     
    176206Declare Function SetConsoleCursorPosition Lib "kernel32" (hConsoleOutput As HANDLE, dwCursorPosition As DWord) As BOOL
    177207Declare Function SetConsoleCursorInfo Lib "kernel32" (hConsoleOutput As HANDLE, ByRef lpConsoleCursorInfo As CONSOLE_CURSOR_INFO) As BOOL
    178 Declare Function ScrollConsoleScreenBuffer Lib "kernel32" Alias "ScrollConsoleScreenBufferA" (hConsoleOutput As HANDLE, ByRef lpScrollRectangle As SMALL_RECT, lpClipRectangle As *SMALL_RECT, ByRef dwDestinationOrigin As COORD, lpFill As *CHAR_INFO) As BOOL
     208Declare Function ScrollConsoleScreenBuffer Lib "kernel32" Alias _FuncName_ScrollConsoleScreenBuffer (hConsoleOutput As HANDLE, ByRef lpScrollRectangle As SMALL_RECT, lpClipRectangle As *SMALL_RECT, ByRef dwDestinationOrigin As COORD, lpFill As *CHAR_INFO) As BOOL
    179209Declare Function SetConsoleWindowInfo Lib "kernel32" (hConsoleOutput As HANDLE, bAbsolute As BOOL, ByRef lpConsoleWindow As SMALL_RECT) As BOOL
    180210Declare Function SetConsoleTextAttribute Lib "kernel32" (hConsoleOutput As HANDLE, wAttributes As Word) As BOOL
     
    183213Declare Function AllocConsole Lib "kernel32" () As BOOL
    184214Declare Function FreeConsole Lib "kernel32" () As BOOL
    185 Declare Function GetConsoleTitle Lib "kernel32" Alias "GetConsoleTitleA" (lpConsoleTitle As LPSTR, nSize As DWord) As DWord
    186 Declare Function SetConsoleTitle Lib "kernel32" Alias "SetConsoleTitleA" (lpConsoleTitle As LPSTR) As BOOL
    187 Declare Function ReadConsole Lib "kernel32" Alias "ReadConsoleA" (hConsoleInput As HANDLE, lpBuffer As VoidPtr, nNumberOfCharsToRead As DWord, ByRef lpNumberOfCharsRead As DWord, lpReserved As VoidPtr) As BOOL
    188 Declare Function WriteConsole Lib "kernel32" Alias "WriteConsoleA" (hConsoleOutput As HANDLE, lpBuffer As VoidPtr, nNumberOfCharsToWrite As DWord, ByRef lpNumberOfCharsWritten As DWord, lpReserved As VoidPtr) As BOOL
     215Declare Function GetConsoleTitle Lib "kernel32" Alias _FuncName_GetConsoleTitle (lpConsoleTitle As LPSTR, nSize As DWord) As DWord
     216Declare Function SetConsoleTitle Lib "kernel32" Alias _FuncName_SetConsoleTitle (lpConsoleTitle As LPSTR) As BOOL
     217Declare Function ReadConsole Lib "kernel32" Alias _FuncName_ReadConsole (hConsoleInput As HANDLE, lpBuffer As VoidPtr, nNumberOfCharsToRead As DWord, ByRef lpNumberOfCharsRead As DWord, lpReserved As VoidPtr) As BOOL
     218Declare Function WriteConsole Lib "kernel32" Alias _FuncName_WriteConsole (hConsoleOutput As HANDLE, lpBuffer As VoidPtr, nNumberOfCharsToWrite As DWord, ByRef lpNumberOfCharsWritten As DWord, lpReserved As VoidPtr) As BOOL
    189219
    190220Const CONSOLE_TEXTMODE_BUFFER = 1
  • Include/api_psapi.sbp

    r141 r142  
    8585#endif
    8686
    87 Declare Function GetProcessMemoryInfo Lib "psapi" (Process As HANDLE, ppsmemCounters As PPROCESS_MEMORY_COUNTERS, cb As DWord)
     87Declare Function GetProcessMemoryInfo Lib "psapi" (Process As HANDLE, ppsmemCounters As PPROCESS_MEMORY_COUNTERS, cb As DWord) As BOOL
    8888
    8989Type PERFORMANCE_INFORMATION
     
    107107TypeDef PPERFORMACE_INFORMATION = *PERFORMANCE_INFORMATION
    108108
    109 Declare Function GetPerformanceInfo Lib "psapi" (pPerformanceInformation As PPERFORMACE_INFORMATION, cb As DWord)
     109Declare Function GetPerformanceInfo Lib "psapi" (pPerformanceInformation As PPERFORMACE_INFORMATION, cb As DWord) As BOOL
    110110
    111111Type ENUM_PAGE_FILE_INFORMATION
  • Include/api_system.sbp

    r141 r142  
    875875Const VER_PLATFORM_WIN32_WINDOWS = 1
    876876Const VER_PLATFORM_WIN32_NT      = 2
     877Const VER_PLATFORM_WIN32_CE      = 3
    877878Type OSVERSIONINFOW
    878879    dwOSVersionInfoSize As DWord
  • Include/basic.sbp

    r121 r142  
    3131'Single
    3232'Double
     33
     34TypeDef Int16 = Integer
     35TypeDef Int8 = SByte
    3336
    3437TypeDef BOOL = Long
  • Include/basic/command.sbp

    r123 r142  
    55#define _INC_COMMAND
    66
     7#require <windows.sbp>
     8#require <Classes/System/Environment.ab>
    79
    810Const _System_Type_SByte = 1
     
    3335Macro END()
    3436    _System_Call_Destructor_of_GlobalObject()
    35     ExitProcess(0)
    36 End Macro
    37 
    38 Macro EXEC(lpFilePath As *Byte)(lpCmdLine As *Byte)
    39     ShellExecute(0,"open",lpFilePath,lpCmdLine,0,SW_SHOWNORMAL)
     37    ExitProcess(Environment.ExitCode)
     38End Macro
     39
     40Macro EXEC(filePath As String)(cmdLine As String)
     41    ShellExecute(0, "open", ToTCStr(filePath), ToTCStr(cmdLine), 0, SW_SHOWNORMAL)
    4042End Macro
    4143
     
    5254Macro WRITE()   'dummy(PRINT_ToFile、PRINT_ToPromptを参照)
    5355End Macro
    54 
    5556
    5657'----------------
     
    5859'----------------
    5960
    60 Macro MSGBOX(hWnd As HWND, lpStr As String)(lpTitle As String, BoxType As DWord, ByRef retAns As DWord)
     61Function _System_MessageBox(hw As HWND, s As PCSTR, t As PCSTR, b As DWord) As DWord
     62    Return MessageBoxA(hw, s, t, b)
     63End Function
     64
     65Function _System_MessageBox(hw As HWND, s As PCWSTR, t As PCWSTR, b As DWord) As DWord
     66    Return MessageBoxW(hw, s, t, b)
     67End Function
     68
     69Macro MSGBOX(hwnd As HWND, str As String)(title As String, boxType As DWord, ByRef retAns As DWord)
    6170    If VarPtr(retAns) Then
    62         retAns=MessageBox(hWnd,lpStr,lpTitle,BoxType)
     71        retAns = _System_MessageBox(hwnd, str, title, boxType)
    6372    Else
    64         MessageBox(hWnd,lpStr,lpTitle,BoxType)
     73        _System_MessageBox(hwnd, str, title, boxType)
    6574    End If
    6675End Macro
    6776
    68 Macro WINDOW(ByRef hWnd As HWND, hOwner As HWND, x As Long, y As Long, nWidth As Long, nHeight As Long, lpTitle As String, dwStyle As DWord)(lpClass As String, id As HMENU, lpFunc As DWord, dwExStyle As DWord)
    69     If VarPtr(hWnd) Then
    70         hWnd=CreateWindowEx(dwExStyle,lpClass,lpTitle,dwStyle,x,y,nWidth,nHeight,hOwner,id,GetModuleHandle(0),NULL)
    71     Else
    72         CreateWindowEx(dwExStyle,lpClass,lpTitle,dwStyle,x,y,nWidth,nHeight,hOwner,id,GetModuleHandle(0),NULL)
     77Macro WINDOW(ByRef hwndRet As HWND, hOwner As HWND, x As Long, y As Long, width As Long, height As Long, title As String, dwStyle As DWord)(className As String, id As HMENU, lpFunc As DWord, dwExStyle As DWord)
     78    Dim hwnd = CreateWindowEx(dwExStyle, ToTCStr(className), ToTCStr(title), dwStyle, x, y, width, height, hOwner, id, GetModuleHandle(0), 0)
     79    If VarPtr(hwndRet) Then
     80        hwndRet = hwnd
    7381    End If
    7482End Macro
     
    7886End Macro
    7987
    80 Macro INSMENU(hMenu As HMENU, PosID As Long, flag As Long)(lpString As String, id As Long, hSubMenu As HMENU, state As Long)
     88Macro INSMENU(hMenu As HMENU, PosID As Long, flag As Long)(str As String, id As Long, hSubMenu As HMENU, state As Long)
    8189    Dim mii As MENUITEMINFO
    8290    ZeroMemory(VarPtr(mii), Len(mii))
     
    9098            .fType = MFT_STRING
    9199            .fMask = .fMask or MIIM_STATE or MIIM_ID
    92             .dwTypeData = StrPtr(lpString)
     100            .dwTypeData = ToTCStr(str)
    93101            .wID = id
    94102            If hSubMenu Then
     
    96104                .hSubMenu = hSubMenu
    97105            End If
    98             .fState=state
     106            .fState = state
    99107        End If
    100108    End With
     
    108116
    109117Dim _System_hFile(255) As HANDLE
    110 Macro OPEN(lpFileName As String, AccessFor As Long, FileNumber As Long)
    111     Dim dwAccess As Long
    112     Dim bAppend = 0 As Long
    113     Dim dwCreationDisposition As Long
     118Macro OPEN(fileName As String, AccessFor As Long, FileNumber As Long)
     119    Dim access As Long
     120    Dim bAppend = False As Boolean
     121    Dim creationDisposition As Long
    114122
    115123    FileNumber--
     
    117125    Select Case AccessFor
    118126        Case 0
    119             dwAccess=GENERIC_READ or GENERIC_WRITE
    120             dwCreationDisposition=OPEN_ALWAYS
     127            access = GENERIC_READ or GENERIC_WRITE
     128            creationDisposition = OPEN_ALWAYS
    121129        Case 1
    122             dwAccess=GENERIC_READ
    123             dwCreationDisposition=OPEN_EXISTING
     130            access = GENERIC_READ
     131            creationDisposition = OPEN_EXISTING
    124132        Case 2
    125             dwAccess=GENERIC_WRITE
    126             dwCreationDisposition=CREATE_ALWAYS
     133            access = GENERIC_WRITE
     134            creationDisposition = CREATE_ALWAYS
    127135        Case 3
    128             dwAccess=GENERIC_WRITE
    129             dwCreationDisposition=OPEN_ALWAYS
    130             bAppend=1
     136            access = GENERIC_WRITE
     137            creationDisposition = OPEN_ALWAYS
     138            bAppend = True
    131139    End Select
    132140
    133     _System_hFile(FileNumber)=CreateFile(lpFileName,dwAccess,0,ByVal NULL,dwCreationDisposition,FILE_ATTRIBUTE_NORMAL,NULL)
    134 
    135     If bAppend Then SetFilePointer(_System_hFile(FileNumber),0,NULL,FILE_END)
     141    _System_hFile(FileNumber) = CreateFile(ToTCStr(fileName), access, 0, ByVal 0, creationDisposition, FILE_ATTRIBUTE_NORMAL, 0)
     142
     143    If bAppend Then SetFilePointer(_System_hFile(FileNumber), 0, 0, FILE_END)
    136144End Macro
    137145
     
    151159    Dim i As Long ,i2 As Long, i3 As Long
    152160    Dim buffer As String
    153     Dim temp[1] As Char
     161    Dim temp[1] As StrChar
    154162    Dim dwAccessBytes As DWord
    155163    Dim IsStr As Long
     
    163171        '次のデータをサーチ
    164172        Do
    165             i2=ReadFile(_System_hFile[FileNumber],temp,1,VarPtr(dwAccessBytes),ByVal 0)
     173            i2=ReadFile(_System_hFile[FileNumber],temp,SizeOf (StrChar),VarPtr(dwAccessBytes),ByVal 0)
    166174            If i2=0 or dwAccessBytes=0 Then
    167175                'error
     
    177185            i3++
    178186
    179             i2=ReadFile(_System_hFile[FileNumber],temp,1,VarPtr(dwAccessBytes),ByVal 0)
     187            i2=ReadFile(_System_hFile[FileNumber],temp,SizeOf (StrChar),VarPtr(dwAccessBytes),ByVal 0)
    180188            If i2=0 or (i3=0 and dwAccessBytes=0) Then
    181189                'error
     
    187195            If dwAccessBytes=0 or temp[0]=0 or temp[0]=13 or temp[0]=10 or (IsStr=0 and temp[0]=Asc(",")) or (IsStr=0 and (temp[0]=32 or temp[0]=9) and _System_InputDataType[i]<>_System_Type_String) Then
    188196                If temp[0]=13 Then
    189                     ReadFile(_System_hFile[FileNumber],temp,1,VarPtr(dwAccessBytes),ByVal 0)
     197                    ReadFile(_System_hFile[FileNumber],temp,SizeOf (StrChar),VarPtr(dwAccessBytes),ByVal 0)
    190198                    If Not(dwAccessBytes<>0 And temp[0]=10) Then
    191199                        SetFilePointer(_System_hFile[FileNumber],-1,0,FILE_CURRENT)
     
    240248            pTempStr = arg As *String
    241249            pTempStr->ReSize(bufLen)
    242             memcpy(pTempStr->Chars, buf.Chars, SizeOf (Char) * pTempStr->Length)
     250            memcpy(pTempStr->Chars, buf.Chars, SizeOf (StrChar) * pTempStr->Length)
    243251            pTempStr->Chars[pTempStr->Length] = 0
    244252    End Select
     
    249257    FileNumber--
    250258
    251     WriteFile(_System_hFile(FileNumber),buf,Len(buf),VarPtr(dwAccessByte),ByVal NULL)
     259    WriteFile(_System_hFile(FileNumber), buf, Len(buf), VarPtr(dwAccessByte), ByVal 0)
    252260End Sub
    253261
     
    257265Function _System_GetUsingFormat(UsingStr As String) As String
    258266    Dim i2 As Long, i3 As Long, i4 As Long, i5 As Long, ParmNum As Long
    259     Dim temporary[255] As Char
     267    Dim temporary[255] As StrChar
    260268    Dim buffer As String
    261269
    262     buffer=ZeroString(1024)
    263 
    264     ParmNum=0
    265     i2=0
     270    buffer = ZeroString(1024)
     271
     272    ParmNum = 0
     273    i2 = 0
    266274    While 1
    267275        While 1
     
    277285        If UsingStr[i2]=Asc("#") Then
    278286            Dim dec As Long, sign As Long
    279             Dim temp2 As *Char
     287            Dim temp2 As *StrChar
    280288
    281289            Dim length_num As Long, length_buf As Long
     
    332340
    333341                If dec > 0 Then
    334                     memcpy(VarPtr(buffer[i3]), temp2, SizeOf (Char) * length_num)
     342                    memcpy(VarPtr(buffer[i3]), temp2, SizeOf (StrChar) * length_num)
    335343                Else
    336344                    buffer[i3] = &H30
     
    367375            'lstrcat(StrPtr(buffer)+i3,_System_UsingStrData[ParmNum])
    368376            memcpy(VarPtr(buffer[i3 + lstrlen(VarPtr(buffer[i3]))]), _System_UsingStrData[ParmNum], _
    369                 SizeOf (Char) * lstrlen(_System_UsingStrData[ParmNum]))
     377                SizeOf (StrChar) * lstrlen(_System_UsingStrData[ParmNum]))
    370378            i3 += lstrlen(_System_UsingStrData[ParmNum])
    371379        ElseIf UsingStr[i2]=Asc("&") Then
     
    385393                    _System_FillChar(VarPtr(buffer[i3]), i4, &h20) 'Asc(" ")
    386394                End If
    387                 memcpy(VarPtr(buffer[i3]), _System_UsingStrData[ParmNum], SizeOf (Char) * i5)
     395                memcpy(VarPtr(buffer[i3]), _System_UsingStrData[ParmNum], SizeOf (StrChar) * i5)
    388396                i3 += i4
    389397            Else
     
    423431    RecodeNumber--
    424432
    425     SetFilePointer(_System_hFile(FileNumber),RecodeNumber*_System_FieldSize(FileNumber),NULL,FILE_BEGIN)
    426     lpBuffer=ZeroString(_System_FieldSize(FileNumber))
    427     ReadFile(_System_hFile(FileNumber),StrPtr(lpBuffer),_System_FieldSize(FileNumber),VarPtr(dwAccessByte),ByVal NULL)
     433    SetFilePointer(_System_hFile(FileNumber), SizeOf (StrChar) * RecodeNumber * _System_FieldSize(FileNumber), 0, FILE_BEGIN)
     434    lpBuffer = ZeroString(_System_FieldSize(FileNumber))
     435    ReadFile(_System_hFile(FileNumber), StrPtr(lpBuffer), SizeOf (StrChar) * _System_FieldSize(FileNumber), VarPtr(dwAccessByte),ByVal 0)
    428436    If Not dwAccessByte=_System_FieldSize(FileNumber) Then
    429         lpBuffer=Left$(lpBuffer,dwAccessByte)
     437        lpBuffer = Left$(lpBuffer, dwAccessByte)
    430438    End If
    431439End Macro
     
    436444    RecodeNumber--
    437445
    438     SetFilePointer(_System_hFile(FileNumber),RecodeNumber*_System_FieldSize(FileNumber),NULL,FILE_BEGIN)
    439     WriteFile(_System_hFile(FileNumber),StrPtr(lpBuffer),_System_FieldSize(FileNumber),VarPtr(dwAccessByte),ByVal NULL)
     446    SetFilePointer(_System_hFile(FileNumber), SizeOf (StrChar) * RecodeNumber*_System_FieldSize(FileNumber), 0, FILE_BEGIN)
     447    WriteFile(_System_hFile(FileNumber), StrPtr(lpBuffer),SizeOf (StrChar) * _System_FieldSize(FileNumber), VarPtr(dwAccessByte), ByVal 0)
    440448End Macro
    441449
    442450Macro CHDIR(path As String)
    443     SetCurrentDirectory(path)
     451    SetCurrentDirectory(ToTCStr(path))
    444452End Macro
    445453Macro MKDIR(path As String)
    446     CreateDirectory(path, 0)
     454    CreateDirectory(ToTCStr(path), 0)
    447455End Macro
    448456Macro KILL(path As String)
    449     DeleteFile(path)
     457    DeleteFile(ToTCStr(path))
    450458End Macro
    451459
  • Include/basic/dos_console.sbp

    r123 r142  
    2020    Dim i As Long, i2 As Long, i3 As Long
    2121    Dim buf As String
    22     Dim InputStr[1023] As Byte
     22    Dim InputBuf[1023] As TCHAR
    2323    Dim dwAccessBytes As DWord
    2424
     
    2828
    2929    '入力
    30     ReadConsole(_System_hConsoleIn, InputStr, Len(InputStr), dwAccessBytes, 0)
    31     If InputStr[dwAccessBytes-2] = &h0d And InputStr[dwAccessBytes-1] = &h0a Then
    32         InputStr[dwAccessBytes-2] = 0
     30    ReadConsole(_System_hConsoleIn, InputBuf, Len(InputBuf), dwAccessBytes, 0)
     31    If InputBuf[dwAccessBytes-2] = &h0d And InputBuf[dwAccessBytes-1] = &h0a Then
     32        InputBuf[dwAccessBytes-2] = 0
    3333    End If
     34    Dim InputStr As String(InputBuf)
    3435
    3536    'データを変数に格納
     
    5960        i++
    6061        If _System_InputDataPtr[i]=0 And InputStr[i2]=comma Then
    61             PRINT_ToPrompt("入力データの個数が多すぎます"+Chr$(10))
     62            PRINT_ToPrompt(Ex"入力データの個数が多すぎます\r\n")
    6263            Goto *InputReStart
    6364        ElseIf InputStr[i2]=0 Then
    6465            If _System_InputDataPtr[i]<>0 Then
    65                 PRINT_ToPrompt("入力データの個数が足りません"+Chr$(10))
     66                PRINT_ToPrompt(Ex"入力データの個数が足りません\r\n")
    6667                Goto *InputReStart
    6768            Else
     
    8081Sub PRINT_ToPrompt(buf As String)
    8182    Dim dwAccessBytes As DWord
     83#ifdef __STRING_UNICODE_WINDOWS_ANSI
     84'   Debug
     85    Dim oldAlloc = _System_AllocForConvertedString
     86    _System_AllocForConvertedString = AddressOf (_System_malloc)
     87    Dim pszOut As PCSTR
     88    Dim len = GetStr(buf, pszOut)
     89    _System_AllocForConvertedString = oldAlloc
     90    WriteConsole(_System_hConsoleOut, pszOut, len, dwAccessBytes, 0)
     91    _System_free(pszOut)
     92#else
    8293    WriteConsole(_System_hConsoleOut, buf.Chars, buf.Length, dwAccessBytes, 0)
     94#endif
    8395End Sub
    8496
  • Include/basic/function.sbp

    r137 r142  
    344344'------------
    345345
    346 Function Asc(buf As *Char) As Char
     346Function Asc(buf As *StrChar) As StrChar
    347347    Asc = buf[0]
    348348End Function
    349349
    350 Function Chr$(code As Char) As String
     350Function Chr$(code As StrChar) As String
    351351    Chr$ = ZeroString(1)
    352352    Chr$[0] = code
    353353End Function
    354354
    355 #ifdef UNICODE
     355#ifndef __STRING_IS_NOT_UNICODE
    356356Function AscW(s As *WCHAR) As UCSCHAR
    357357    If s.Length = 0 Then
     
    487487
    488488    Mid$=ZeroString(ReadLength)
    489     memcpy(StrPtr(Mid$), VarPtr(buf[StartPos]), SizeOf (Char) * ReadLength)
     489    memcpy(StrPtr(Mid$), VarPtr(buf.Chars[StartPos]), SizeOf (Char) * ReadLength)
    490490End Function
    491491
     
    515515    If i>length Then
    516516        Right$=ZeroString(length)
    517         memcpy(StrPtr(Right$), VarPtr(buf[i-length]), SizeOf (Char) * length)
     517        memcpy(StrPtr(Right$), VarPtr(buf.Chars[i-length]), SizeOf (Char) * length)
    518518    Else
    519519        Right$=buf
     
    691691    Return MakeStr(buffer)
    692692End Function
    693 Function Str$(value As LONG_PTR) As String
     693Function Str$(value As Int64) As String
    694694    Dim temp[255] As Char
    695 #ifdef _WIN64
    696695    _sntprintf(temp, Len (temp) \ SizeOf (Char), "%I64d", value)
    697 #else
    698     _sntprintf(temp, Len (temp) \ SizeOf (Char), "%d", value)
    699 #endif
    700696    Str$ = temp
    701697End Function
     
    881877
    882878Function Lof(FileNum As Long) As Long
    883     Lof=GetFileSize(_System_hFile(FileNum-1),NULL)
     879    Lof = GetFileSize(_System_hFile(FileNum-1), 0)
    884880End Function
    885881
     
    10591055End Function
    10601056
     1057'--------
     1058' 文字列関数その2
     1059'--------
    10611060Function _System_IsSurrogatePair(wcHigh As WCHAR, wcLow As WCHAR) As Boolean
    10621061    If &hD800 <= wcHigh And wcHigh < &hDC00 Then
     
    10681067End Function
    10691068
    1070 Function _System_IsDoubleUnitChar(lead As Char, trail As Char) As Boolean
    1071 #ifdef UNICODE
     1069Function _System_IsDoubleUnitChar(lead As WCHAR, trail As WCHAR) As Boolean
    10721070    Return _System_IsSurrogatePair(lead, trail)
    1073 #else
     1071End Function
     1072
     1073Function _System_IsDoubleUnitChar(lead As SByte, trail As SByte) As Boolean
    10741074    Return IsDBCSLeadByte(lead) <> FALSE
    1075 #endif
    1076 End Function
    1077 
    1078 Sub _System_FillChar(p As *Char, n As SIZE_T, c As Char)
     1075End Function
     1076
     1077Sub _System_FillChar(p As PWSTR, n As SIZE_T, c As WCHAR)
    10791078    Dim i As SIZE_T
    10801079    For i = 0 To ELM(n)
     
    10831082End Sub
    10841083
    1085 Function _System_ASCII_IsUpper(c As Char) As Boolean
     1084Sub _System_FillChar(p As PSTR, n As SIZE_T, c As SByte)
     1085    Dim i As SIZE_T
     1086    For i = 0 To ELM(n)
     1087        p[i] = c
     1088    Next
     1089End Sub
     1090
     1091Function _System_ASCII_IsUpper(c As WCHAR) As Boolean
    10861092    Return c As DWord - &h41 < 26 ' &h41 = Asc("A")
    10871093End Function
    10881094
     1095Function _System_ASCII_IsUpper(c As SByte) As Boolean
     1096    Return _System_ASCII_IsUpper(c As Byte As WCHAR)
     1097End Function
     1098
     1099Function _System_ASCII_IsLower(c As WCHAR) As Boolean
     1100    Return c As DWord - &h61 < 26 ' &h61 = Asc("a")
     1101End Function
     1102
    10891103Function _System_ASCII_IsLower(c As Char) As Boolean
    1090     Return c As DWord - &h61 < 26 ' &h61 = Asc("a")
    1091 End Function
    1092 
    1093 Function _System_ASCII_ToLower(c As Char) As Char
     1104    Return _System_ASCII_IsLower(c As Byte As WCHAR)
     1105End Function
     1106
     1107Function _System_ASCII_ToLower(c As WCHAR) As WCHAR
    10941108    If _System_ASCII_IsUpper(c) Then
    10951109        Return c Or &h20
     
    10971111        Return c
    10981112    End If
     1113End Function
     1114
     1115Function _System_ASCII_ToLower(c As SByte) As SByte
     1116    Return _System_ASCII_ToLower(c As Byte As WCHAR) As Byte As SByte
    10991117End Function
    11001118
     
    11071125End Function
    11081126
    1109 Function _System_WideCharToMultiByte(s As PCWSTR) As PSTR
    1110     Return _System_WideCharToMultiByte(s, lstrlenW(s) + 1, 0)
    1111 End Function
    1112 
    1113 Function _System_WideCharToMultiByte(s As PCWSTR, size As Long) As PSTR
    1114     Return _System_WideCharToMultiByte(s, size, 0)
    1115 End Function
    1116 
    1117 Function _System_WideCharToMultiByte(ws As PCWSTR, size As Long, flag As DWord) As PSTR
    1118     Dim sizeMBS = WideCharToMultiByte(CP_THREAD_ACP, flag, s, size, 0, 0, 0, 0)
    1119     Dim mbs = _System_malloc(sizeMBS) As PSTR
    1120     WideCharToMultiByte(CP_THREAD_ACP, flag, s, size, mbs, sizeMBS, 0, 0)
    1121     Return mbs
    1122 End Function
    1123 
    1124 Function _System_MultiByteToWideChar(s As PCSTR) As PWSTR
    1125     Return _System_MultiByteToWideChar(s, lstrlenA(s) + 1, 0)
    1126 End Function
    1127 
    1128 Function _System_MultiByteToWideChar(s As PCSTR, size As Long) As PWSTR
    1129     Return _System_MultiByteToWideChar(s, size, 0)
    1130 End Function
    1131 
    1132 Function _System_MultiByteToWideChar(s As PCSTR, size As Long, flag As DWord) As PWSTR
    1133     Dim sizeMBS = MultiByteToWideChar(CP_THREAD_ACP, flag, s, size, 0, 0)
    1134     Dim mbs = _System_malloc(SizeOf (WCHAR) * sizeMBS) As PWSTR
    1135     MultiByteToWideChar(CP_THREAD_ACP, flag, s, size, mbs, sizeMBS)
    1136     Return mbs
    1137 End Function
     1127Function _System_ASCII_ToUpper(c As SByte) As SByte
     1128    Return _System_ASCII_ToUpper(c As Byte As WCHAR) As Byte As SByte
     1129End Function
     1130
    11381131
    11391132Function _System_StrCmp(s1 As PCSTR, s2 As PCSTR) As Long
     
    11581151    _System_StrCmp = s1[i] - s2[i]
    11591152End Function
     1153
    11601154#endif '_INC_FUNCTION
  • Include/basic/prompt.sbp

    r137 r142  
    88#require <api_imm.sbp>
    99#require <Classes/System/Math.ab>
     10
     11Function _PromptSys_GetTextExtentPoint32(hdc As HDC, psz As PCSTR, cb As Long, ByRef Size As SIZE) As Long
     12    _PromptSys_GetTextExtentPoint32 = GetTextExtentPoint32A(hdc, psz, cb, Size)
     13End Function
     14
     15Function _PromptSys_GetTextExtentPoint32(hdc As HDC, psz As PCWSTR, cb As Long, ByRef Size As SIZE) As Long
     16    _PromptSys_GetTextExtentPoint32 = GetTextExtentPoint32W(hdc, psz, cb, Size)
     17End Function
     18
     19Function _PromptSys_TextOut(hdc As HDC, x As Long, y As Long, psz As PCSTR, cb As Long) As Long
     20    _PromptSys_TextOut = TextOutA(hdc, x, y, psz, cb)
     21End Function
     22
     23Function _PromptSys_TextOut(hdc As HDC, x As Long, y As Long, psz As PCWSTR, cb As Long) As Long
     24    _PromptSys_TextOut = TextOutW(hdc, x, y, psz, cb)
     25End Function
     26
     27Function _PromptSys_ImmGetCompositionString(himc As HIMC, index As DWord, pBuf As PSTR, bufLen As DWord) As Long
     28    _PromptSys_ImmGetCompositionString = ImmGetCompositionStringA(himc, index, pBuf, bufLen)
     29End Function
     30
     31Function _PromptSys_ImmGetCompositionString(himc As HIMC, index As DWord, pBuf As PWSTR, bufLen As DWord) As Long
     32    _PromptSys_ImmGetCompositionString = ImmGetCompositionStringW(himc, index, pBuf, bufLen)
     33End Function
    1034
    1135Dim _PromptSys_hWnd As HWND
     
    2246Type _PromptSys_LineInformation
    2347    Length As Long
    24     Text As *Char
     48    Text As *StrChar
    2549    CharInfo As *_PromptSys_CharacterInformation
    2650End Type
     
    2953Dim _PromptSys_hFont As HFONT
    3054Dim _PromptSys_FontSize As SIZE
    31 Dim _PromptSys_InputStr[255] As Char
     55Dim _PromptSys_InputStr[255] As StrChar
    3256Dim _PromptSys_InputLen As Long
    3357Dim _PromptSys_KeyChar As Byte
     
    3862Dim _PromptSys_SectionOfBufferAccess As CRITICAL_SECTION
    3963
     64Dim _System_OSVersionInfo As OSVERSIONINFO
    4065
    4166_PromptSys_InputLen = -1
     
    4873
    4974_PromptSys_hInitFinish = CreateEvent(0, FALSE, FALSE, 0)
    50 CreateThread(0, 0, AddressOf(PromptMain) As LPTHREAD_START_ROUTINE, 0, 0, _PromptSys_dwThreadID)
     75Dim _PromptSys_hThread As HANDLE
     76_PromptSys_hThread = CreateThread(0, 0, AddressOf(PromptMain) As LPTHREAD_START_ROUTINE, 0, 0, _PromptSys_dwThreadID)
     77If _PromptSys_hThread = 0 Then
     78    Debug
     79    ExitProcess(1)
     80End If
    5181WaitForSingleObject(_PromptSys_hInitFinish, INFINITE)
    5282
     
    6898        Next
    6999        _PromptSys_TextLine[100].Length = 0
    70         _PromptSys_TextLine[100].Text = _System_calloc(SizeOf (Char) * 255)
     100        _PromptSys_TextLine[100].Text = _System_calloc(SizeOf (StrChar) * 255)
    71101        _PromptSys_TextLine[100].CharInfo = _System_calloc(SizeOf (_PromptSys_CharacterInformation) * 255)
    72102        _PromptSys_CurPos.y--
     
    83113            Dim sz As SIZE
    84114            i3 = _PromptSys_TextLine[i].Length
    85             GetTextExtentPoint32(hDC, _PromptSys_TextLine[i].Text, i3, sz)
     115            _PromptSys_GetTextExtentPoint32(hDC, _PromptSys_TextLine[i].Text, i3, sz)
    86116
    87117            BitBlt(hDC,_
     
    106136                End If
    107137                With _PromptSys_FontSize
    108                     TextOut(hDC, currentLineCharInfo[i2].StartPos, i * .cy, VarPtr(_PromptSys_TextLine[i].Text[i2]), tempLen)
     138                    _PromptSys_TextOut(hDC, currentLineCharInfo[i2].StartPos, i * .cy, VarPtr(_PromptSys_TextLine[i].Text[i2]) As *StrChar, tempLen)
    109139                End With
    110140                i2 += tempLen
     
    127157        Dim doubleUnitChar = False As Boolean
    128158        'Addition
    129         Dim i2 = 0 As Long, i3 As Long' : Debug
     159        Dim i2 = 0 As Long, i3 As Long
    130160        For i2 = 0 To ELM(bufLen)
    131161            If buf[i2] = &h0d Then 'CR \r
     
    158188                            charLen = 1
    159189                        EndIf
    160                         GetTextExtentPoint32(hdc, VarPtr(buf.Chars[i2]), charLen, sz)
     190                        _PromptSys_GetTextExtentPoint32(hdc, VarPtr(buf.Chars[i2]) As *StrChar, charLen, sz)
    161191                        currentLineCharInfo[.x + 1].StartPos = currentLineCharInfo[.x].StartPos + sz.cx
    162192/*
     
    305335            TempStr = Ex"\r\n"
    306336        ElseIf wParam = &H16 Then
     337/*
    307338            'Paste Command(Use Clippboard)
    308339            OpenClipboard(hwnd)
     
    324355            GlobalUnlock(hGlobal)
    325356            CloseClipboard()
     357*/
    326358        Else
    327359            _PromptSys_InputStr[_PromptSys_InputLen] = wParam As Byte
     
    337369    End If
    338370End Sub
     371
     372Function _PromptWnd_GetCompositionStringW(himc As HIMC, ByRef rpsz As PWSTR) As Long
     373    Dim size = ImmGetCompositionStringW(himc, GCS_RESULTSTR, 0, 0) 'sizeはバイト単位
     374    rpsz = _System_malloc(size) As PTSTR
     375    If rpsz = 0 Then
     376        'Debug
     377        Return 0
     378    End If
     379    Return ImmGetCompositionStringW(himc, GCS_RESULTSTR, rpsz, size)
     380End Function
     381
     382Function _PromptWnd_GetCompositionStringA(himc As HIMC, ByRef rpsz As PSTR) As Long
     383    Dim size = ImmGetCompositionStringA(himc, GCS_RESULTSTR, 0, 0) 'sizeはバイト単位
     384    rpsz = _System_malloc(size) As PTSTR
     385    If rpsz = 0 Then
     386        'Debug
     387        Return 0
     388    End If
     389    Return ImmGetCompositionStringA(himc, GCS_RESULTSTR, rpsz, size)
     390End Function
    339391
    340392Function _PromptWnd_OnImeCompostion(hwnd As HWND, wp As WPARAM, lp As LPARAM) As LRESULT
     
    345397            Return 0
    346398        End If
    347         Dim size = ImmGetCompositionString(himc, GCS_RESULTSTR, 0, 0) 'sizeはバイト単位
    348         Dim str = _System_malloc(size) As PTSTR
    349         If str = 0 Then
    350             'Debug
    351             Return 0
    352         End If
    353         ImmGetCompositionString(himc, GCS_RESULTSTR, str, size)
     399        Dim tempStr As String
     400        Dim str As *StrChar
     401#ifdef __STIRNG_IS_NOT_UNICODE
     402        Dim size = _PromptWnd_GetCompositionStringA(himc, str)
     403        tempStr.Assign(str, size)
     404#else
     405        With _System_OSVersionInfo
     406            ' GetCompositionStringW is not implimented in Windows 95
     407            If .dwMajorVersion = 4 And .dwMinorVersion = 0 And .dwPlatformId = VER_PLATFORM_WIN32_WINDOWS Then
     408                Dim strA As PCSTR
     409                Dim sizeA = _PromptWnd_GetCompositionStringA(himc, strA)
     410                tempStr.AssignFromMultiByte(strA, sizeA)
     411            Else
     412                Dim size = _PromptWnd_GetCompositionStringW(himc, str)
     413                tempStr.Assign(str, size \ SizeOf (WCHAR))
     414            End If
     415        End With
     416#endif
    354417        ImmReleaseContext(hwnd, himc)
    355 
    356         memcpy(VarPtr(_PromptSys_InputStr[_PromptSys_InputLen]), str, size)
    357         _PromptSys_InputLen += size \ SizeOf (Char)
    358 
    359         Dim tempStr As String(str, size \ SizeOf (Char))
    360418        _System_free(str)
    361419
    362         SendMessage(hwnd, WM_KILLFOCUS, 0, 0)
     420        memcpy(VarPtr(_PromptSys_InputStr[_PromptSys_InputLen]), tempStr.Chars, SizeOf (StrChar) * tempStr.Length)
     421        _PromptSys_InputLen += tempStr.Length
     422
     423        SendMessage(hwnd, WM_KILLFOCUS, 0, 0) : Debug
    363424        PRINT_ToPrompt(tempStr)
    364425        SendMessage(hwnd, WM_SETFOCUS, 0, 0)
     
    371432
    372433Function PromptMain(dwData As Long) As Long
     434    GetVersionEx(_System_OSVersionInfo)
     435
    373436    Dim i As Long
    374 
    375437    'Allocate
    376438    For i = 0 To 100
    377439        With _PromptSys_TextLine[i]
    378440            .Length = 0
    379             .Text = _System_calloc(SizeOf (Char) * 255)
     441            .Text = _System_calloc(SizeOf (StrChar) * 255)
    380442            .CharInfo = _System_calloc(SizeOf (_PromptSys_CharacterInformation) * 255)
    381443        End With
     
    515577'----------------------------------------------
    516578Sub INPUT_FromPrompt(ShowStr As String)
    517     Dim i As Long ,i2 As Long, i3 As Long
     579    Dim i As Long, i2 As Long, i3 As Long
    518580    Dim buf As String
    519581
  • Include/com/bstring.ab

    r138 r142  
    1111
    1212    Sub BString(len As DWord)
    13         bs = SysAllocStringLen(len)
     13        bs = SysAllocStringLen(0, len)
    1414    End Sub
    1515
     
    4040    End Sub
    4141
     42    Sub ~BString()
     43        Clear()
     44    End Sub
     45
    4246    Sub Operator =(ByRef bstr As BString)
    43         ~BString()
     47        Clear()
    4448        BString(bstr)
    4549    End Sub
    4650
    47     Sub ~BString()
     51    Sub Operator =(s As LPCOLESTR)
    4852        Clear()
     53        BString(s)
     54    End Sub
     55
     56    Sub Assign(ByRef bstr As BString)
     57        Clear()
     58        BString(bstr)
     59    End Sub
     60
     61    Sub Assign(s As LPCOLESTR)
     62        Clear()
     63        BString(s)
     64    End Sub
     65
     66    Sub AssignFromBStr(bstr As BSTR)
     67        Clear()
     68        BString(bstr)
    4969    End Sub
    5070
     
    7494    End Function
    7595
    76     Const Function Operator [](i As SIZE_T)
     96    Const Function Operator [](i As SIZE_T) As OLECHAR
    7797#ifdef _DEBUG
    7898        If i > Length Then
  • Include/system/string.sbp

    r119 r142  
    1515End Function
    1616
    17 Function MakeStr(pBuf As *Char) As String
     17Function MakeStr(pBuf As PSTR) As String
    1818    Dim temp As String(pBuf)
    1919    Return temp
    2020End Function
    2121
     22Function MakeStr(pBuf As PWSTR) As String
     23    Dim temp As String(pBuf)
     24    Return temp
     25End Function
     26
     27Dim _System_AllocForConvertedString As *Function(size As SIZE_T) As VoidPtr
     28_System_AllocForConvertedString = AddressOf (GC_malloc_atomic)
     29
     30Function GetStr(psz As PSTR, ByRef wcs As PWSTR) As SIZE_T
     31    If psz <> 0 Then
     32        Return GetStr(psz, lstrlenA(psz), wcs)
     33    Else
     34        Return 0
     35    End If
     36End Function
     37
     38Function GetStr(psz As PSTR, len As SIZE_T, ByRef wcs As PWSTR) As SIZE_T
     39    If psz = 0 Then Return 0
     40    Dim sizeWCS = MultiByteToWideChar(CP_THREAD_ACP, 0, psz, len, 0, 0)
     41    wcs = _System_AllocForConvertedString(SizeOf (WCHAR) * sizeWCS) As PWSTR
     42    GetWCStr = MultiByteToWideChar(CP_THREAD_ACP, 0, psz, len, wcs, sizeWCS)
     43    wcs[GetWCStr] = 0
     44End Function
     45
     46Function GetStr(psz As PWSTR, ByRef wcs As PWSTR) As SIZE_T
     47    wcs = psz
     48    If psz <> 0 Then
     49        Return lstrlenW(psz)
     50    Else
     51        Return 0
     52    End If
     53End Function
     54
     55Function GetStr(psz As PWSTR, len As SIZE_T, ByRef wcs As PWSTR) As SIZE_T
     56    wcs = psz
     57    If psz <> 0 Then
     58        Return lstrlenW(psz)
     59    Else
     60        Return 0
     61    End If
     62End Function
     63
     64Function GetStr(psz As PWSTR, ByRef mbs As PSTR) As SIZE_T
     65    If psz = 0 Then
     66        Return 0
     67    Else
     68        Return GetStr(psz, lstrlenW(psz), mbs)
     69    End If
     70End Function
     71
     72Function GetStr(psz As PWSTR, len As SIZE_T, ByRef mbs As PSTR) As SIZE_T
     73    If psz = 0 Then Return 0
     74    Dim sizeMBS = WideCharToMultiByte(CP_THREAD_ACP, 0, psz, len, 0, 0, 0, 0)
     75    mbs = _System_AllocForConvertedString(SizeOf (SByte) * (sizeMBS + 1)) As PSTR
     76    GetStr = WideCharToMultiByte(CP_THREAD_ACP, 0, psz, len, mbs, sizeMBS, 0, 0) As SIZE_T
     77    mbs[GetStr] = 0
     78End Function
     79
     80Function GetStr(psz As PSTR, ByRef mbs As PSTR) As SIZE_T
     81    mbs = psz
     82    If psz <> 0 Then
     83        Return lstrlenA(psz)
     84    Else
     85        Return 0
     86    End If
     87End Function
     88
     89Function GetStr(psz As PSTR, len As SIZE_T, ByRef mbs As PSTR) As SIZE_T
     90    mbs = psz
     91    Return len
     92End Function
     93
     94Function GetStr(ByRef s As String, ByRef mbs As PSTR) As SIZE_T
     95    Return GetStr(s.Chars, s.Length As SIZE_T, mbs)
     96End Function
     97
     98Function GetStr(ByRef s As String, ByRef wcs As PWSTR) As SIZE_T
     99    Return GetStr(s.Chars, s.Length As SIZE_T, wcs)
     100End Function
     101
     102Function GetWCStr(psz As PSTR, ByRef wcs As PWSTR) As SIZE_T
     103    Return GetStr(psz, wcs)
     104End Function
     105
     106Function GetWCStr(psz As PSTR, len As SIZE_T, ByRef wcs As PWSTR) As SIZE_T
     107    Return GetStr(psz, len, wcs)
     108End Function
     109
     110Function GetWCStr(psz As PWSTR, ByRef wcs As PWSTR) As SIZE_T
     111    Return GetStr(psz, wcs)
     112End Function
     113
     114Function GetWCStr(psz As PWSTR, len As SIZE_T, ByRef wcs As PWSTR) As SIZE_T
     115    Return GetStr(psz, len, wcs)
     116End Function
     117
     118Function GetWCStr(ByRef s As String, ByRef wcs As PWSTR) As SIZE_T
     119    Return GetStr(s.Chars, s.Length, wcs)
     120End Function
     121
     122Function GetMBStr(psz As PWSTR, ByRef mbs As PSTR) As SIZE_T
     123    Return GetStr(psz, mbs)
     124End Function
     125
     126Function GetMBStr(psz As PWSTR, len As SIZE_T, ByRef mbs As PSTR) As SIZE_T
     127    Return GetStr(psz, len, mbs)
     128End Function
     129
     130Function GetMBStr(psz As PSTR, ByRef mbs As PSTR) As SIZE_T
     131    Return GetStr(psz, mbs)
     132End Function
     133
     134Function GetMBStr(psz As PSTR, len As SIZE_T, ByRef mbs As PSTR) As SIZE_T
     135    Return GetStr(psz, len, mbs)
     136End Function
     137
     138Function GetMBStr(ByRef s As String, ByRef mbs As PSTR) As SIZE_T
     139    Return GetStr(s.Chars, s.Length, mbs)
     140End Function
     141
     142Function GetTCStr(psz As PSTR, ByRef tcs As PCTSTR) As SIZE_T
     143    Return GetStr(psz, tcs)
     144End Function
     145
     146Function GetTCStr(psz As PSTR, len As SIZE_T, ByRef tcs As PCTSTR) As SIZE_T
     147    Return GetStr(psz, len, tcs)
     148End Function
     149
     150Function GetTCStr(psz As PWSTR, ByRef tcs As PCTSTR) As SIZE_T
     151    Return GetStr(psz, tcs)
     152End Function
     153
     154Function GetTCStr(psz As PWSTR, len As SIZE_T, ByRef tcs As PCTSTR) As SIZE_T
     155    Return GetStr(psz, len, tcs)
     156End Function
     157
     158Function GetTCStr(ByRef s As String, ByRef wcs As PCTSTR) As SIZE_T
     159    Return GetStr(s.Chars, s.Length, tcs)
     160End Function
     161
     162Function GetSCStr(psz As PSTR, ByRef ss As *StrChar) As SIZE_T
     163    Return GetStr(psz, ss)
     164End Function
     165
     166Function GetSCStr(psz As PSTR, len As SIZE_T, ByRef ss As *StrChar) As SIZE_T
     167    Return GetStr(psz, len, ss)
     168End Function
     169
     170Function GetSCStr(psz As PWSTR, ByRef ss As *StrChar) As SIZE_T
     171    Return GetStr(psz, ss)
     172End Function
     173
     174Function GetSCStr(psz As PWSTR, len As SIZE_T, ByRef ss As *StrChar) As SIZE_T
     175    Return GetStr(psz, len, ss)
     176End Function
     177
     178Function GetSCStr(ByRef s As String, ByRef wcs As *StrChar) As SIZE_T
     179    Return GetStr(s.Chars, s.Length, ss)
     180End Function
     181
     182Function ToWCStr(psz As PSTR) As PWSTR
     183    Return GetStr(psz, ToWCStr)
     184End Function
     185
     186Function ToWCStr(psz As PSTR, len As SIZE_T) As PWSTR
     187    Return GetStr(psz, len, ToWCStr)
     188End Function
     189
     190Function ToWCStr(psz As PWSTR) As PWSTR
     191    Return GetStr(psz, ToWCStr)
     192End Function
     193
     194Function ToWCStr(psz As PWSTR, len As SIZE_T) As PWSTR
     195    Return GetStr(psz, len, ToWCStr)
     196End Function
     197
     198Function ToWCStr(ByRef s As String) As PWSTR
     199    Return GetStr(s.Chars, s.Length, ToWCStr)
     200End Function
     201
     202Function ToMBStr(psz As PSTR) As PSTR
     203    Return GetStr(psz, ToMBStr)
     204End Function
     205
     206Function ToMBStr(psz As PSTR, len As SIZE_T) As PSTR
     207    Return GetStr(psz, len, ToMBStr)
     208End Function
     209
     210Function ToMBStr(psz As PWSTR) As PSTR
     211    Return GetStr(psz, ToMBStr)
     212End Function
     213
     214Function ToMBStr(psz As PWSTR, len As SIZE_T) As PSTR
     215    Return GetStr(psz, len, ToMBStr)
     216End Function
     217
     218Function ToMBStr(ByRef s As String) As PSTR
     219    Return GetStr(s.Chars, s.Length, ToMBStr)
     220End Function
     221
     222Function ToTCStr(psz As PSTR) As PCTSTR
     223    Return GetStr(psz, ToTCStr)
     224End Function
     225
     226Function ToTCStr(psz As PSTR, len As SIZE_T) As PCTSTR
     227    Return GetStr(psz, len, ToTCStr)
     228End Function
     229
     230Function ToTCStr(psz As PWSTR) As PCTSTR
     231    Return GetStr(psz, ToTCStr)
     232End Function
     233
     234Function ToTCStr(psz As PWSTR, len As SIZE_T) As PCTSTR
     235    Return GetStr(psz, len, ToTCStr)
     236End Function
     237
     238Function ToTCStr(ByRef s As String) As PCTSTR
     239    Return GetStr(s.Chars, s.Length, ToTCStr)
     240End Function
     241
     242Function ToSCStr(psz As PSTR) As *StrChar
     243    Return GetStr(psz, ToSCStr)
     244End Function
     245
     246Function ToSCStr(psz As PSTR, len As SIZE_T) As *StrChar
     247    Return GetStr(psz, len, ToSCStr)
     248End Function
     249
     250Function ToSCStr(psz As PWSTR) As *StrChar
     251    Return GetStr(psz, ToSCStr)
     252End Function
     253
     254Function ToSCStr(psz As PWSTR, len As SIZE_T) As *StrChar
     255    Return GetStr(psz, len, ToSCStr)
     256End Function
     257
     258Function ToSCStr(ByRef s As String) As *StrChar
     259    Return GetStr(s.Chars, s.Length, ToSCStr)
     260End Function
     261
    22262#endif '_INC_BASIC_STRING
Note: See TracChangeset for help on using the changeset viewer.