Update of /cvsroot/vba/VisualBoyAdvance/src/win32 In directory sc8-pr-cvs9.sourceforge.net:/tmp/cvs-serv29806/src/win32 Modified Files: AcceleratorManager.cpp Direct3D.cpp DirectDraw.cpp DirectInput.cpp Display.h GBCheatsDlg.cpp GBCheatsDlg.h GBMapView.cpp Input.h Joypad.cpp Joypad.h Logging.cpp MainWndFile.cpp MainWndOptions.cpp MainWndTools.cpp MapView.cpp ModeConfirm.cpp ModeConfirm.h ResizeDlg.cpp TileView.cpp VBA.h VideoMode.cpp skin.cpp vba.rc Log Message: make compilable for Windows x64 Index: Display.h =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/Display.h,v retrieving revision 1.2 retrieving revision 1.3 diff -C2 -d -r1.2 -r1.3 *** Display.h 13 May 2004 15:06:49 -0000 1.2 --- Display.h 6 Jun 2006 21:04:21 -0000 1.3 *************** *** 18,21 **** --- 18,23 ---- // Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. + #pragma once + enum DISPLAY_TYPE { GDI = 0, *************** *** 43,44 **** --- 45,48 ---- virtual int selectFullScreenMode(GUID **) = 0; }; + + void copyImage( void *source, void *destination, unsigned int width, unsigned int height, unsigned int destinationPitch, unsigned int colorDepth ); Index: Input.h =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/Input.h,v retrieving revision 1.2 retrieving revision 1.3 diff -C2 -d -r1.2 -r1.3 *** Input.h 13 May 2004 15:06:50 -0000 1.2 --- Input.h 6 Jun 2006 21:04:21 -0000 1.3 *************** *** 44,48 **** virtual bool readDevices() = 0; virtual u32 readDevice(int which) = 0; ! virtual CString getKeyName(int key) = 0; virtual void checkKeys() = 0; virtual void checkMotionKeys() = 0; --- 44,48 ---- virtual bool readDevices() = 0; virtual u32 readDevice(int which) = 0; ! virtual CString getKeyName(LONG_PTR key) = 0; virtual void checkKeys() = 0; virtual void checkMotionKeys() = 0; Index: MainWndTools.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/MainWndTools.cpp,v retrieving revision 1.3 retrieving revision 1.4 diff -C2 -d -r1.3 -r1.4 *** MainWndTools.cpp 13 May 2004 15:06:50 -0000 1.3 --- MainWndTools.cpp 6 Jun 2006 21:04:21 -0000 1.4 *************** *** 52,56 **** extern bool debugger; extern int emulating; ! extern int remoteSocket; extern void remoteCleanUp(); --- 52,56 ---- extern bool debugger; extern int emulating; ! extern SOCKET remoteSocket; extern void remoteCleanUp(); Index: Joypad.h =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/Joypad.h,v retrieving revision 1.3 retrieving revision 1.4 diff -C2 -d -r1.3 -r1.4 *** Joypad.h 27 May 2006 14:47:33 -0000 1.3 --- Joypad.h 6 Jun 2006 21:04:21 -0000 1.4 *************** *** 61,65 **** public: void assignKeys(); ! void assignKey(int id, int key); JoypadConfig(int w, CWnd* pParent = NULL); // standard constructor --- 61,65 ---- public: void assignKeys(); ! void assignKey(int id, LONG_PTR key); JoypadConfig(int w, CWnd* pParent = NULL); // standard constructor *************** *** 100,104 **** afx_msg void OnOk(); afx_msg void OnDestroy(); ! afx_msg void OnTimer(UINT nIDEvent); afx_msg void OnKeyDown(UINT nChar, UINT nRepCnt, UINT nFlags); virtual BOOL OnInitDialog(); --- 100,104 ---- afx_msg void OnOk(); afx_msg void OnDestroy(); ! afx_msg void OnTimer(UINT_PTR nIDEvent); afx_msg void OnKeyDown(UINT nChar, UINT nRepCnt, UINT nFlags); virtual BOOL OnInitDialog(); *************** *** 114,118 **** public: void assignKeys(); ! void assignKey(int id, int key); MotionConfig(CWnd* pParent = NULL); // standard constructor --- 114,118 ---- public: void assignKeys(); ! void assignKey(int id, LONG_PTR key); MotionConfig(CWnd* pParent = NULL); // standard constructor *************** *** 143,147 **** virtual BOOL OnInitDialog(); afx_msg void OnKeyDown(UINT nChar, UINT nRepCnt, UINT nFlags); ! afx_msg void OnTimer(UINT nIDEvent); DECLARE_MESSAGE_MAP() private: --- 143,147 ---- virtual BOOL OnInitDialog(); afx_msg void OnKeyDown(UINT nChar, UINT nRepCnt, UINT nFlags); ! afx_msg void OnTimer(UINT_PTR nIDEvent); DECLARE_MESSAGE_MAP() private: Index: Direct3D.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/Direct3D.cpp,v retrieving revision 1.8 retrieving revision 1.9 diff -C2 -d -r1.8 -r1.9 *** Direct3D.cpp 13 May 2006 16:32:16 -0000 1.8 --- Direct3D.cpp 6 Jun 2006 21:04:21 -0000 1.9 *************** *** 36,39 **** --- 36,41 ---- #include "resource.h" + #include "Display.h" + #ifdef _DEBUG #define new DEBUG_NEW *************** *** 502,506 **** if(!pDevice) return; ! // Test the cooperative level to see if it's okay to render if( FAILED( pDevice->TestCooperativeLevel() ) ) --- 504,508 ---- if(!pDevice) return; ! // Test the cooperative level to see if it's okay to render if( FAILED( pDevice->TestCooperativeLevel() ) ) *************** *** 542,600 **** copyY = 144; } ! } ! // MMX doesn't seem to be faster to copy the data ! __asm { ! mov eax, copyX; ! mov ebx, copyY; ! ! mov esi, pix; ! mov edi, locked.pBits; ! mov edx, locked.Pitch; ! cmp systemColorDepth, 16; ! jnz gbaOtherColor; ! sub edx, eax; ! sub edx, eax; ! lea esi,[esi+2*eax+4]; ! shr eax, 1; ! gbaLoop16bit: ! mov ecx, eax; ! repz movsd; ! inc esi; ! inc esi; ! inc esi; ! inc esi; ! add edi, edx; ! dec ebx; ! jnz gbaLoop16bit; ! jmp gbaLoopEnd; ! gbaOtherColor: ! cmp systemColorDepth, 32; ! jnz gbaOtherColor2; ! ! sub edx, eax; ! sub edx, eax; ! sub edx, eax; ! sub edx, eax; ! lea esi, [esi+4*eax+4]; ! gbaLoop32bit: ! mov ecx, eax; ! repz movsd; ! add esi, 4; ! add edi, edx; ! dec ebx; ! jnz gbaLoop32bit; ! jmp gbaLoopEnd; ! gbaOtherColor2: ! lea eax, [eax+2*eax]; ! sub edx, eax; ! gbaLoop24bit: ! mov ecx, eax; ! shr ecx, 2; ! repz movsd; ! add edi, edx; ! dec ebx; ! jnz gbaLoop24bit; ! gbaLoopEnd: ! } } --- 544,549 ---- copyY = 144; } ! } ! copyImage( pix, locked.pBits, theApp.sizeX, theApp.sizeY, locked.Pitch, systemColorDepth ); } *************** *** 713,715 **** return new Direct3DDisplay(); } - --- 662,663 ---- Index: GBCheatsDlg.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/GBCheatsDlg.cpp,v retrieving revision 1.4 retrieving revision 1.5 diff -C2 -d -r1.4 -r1.5 *** GBCheatsDlg.cpp 13 May 2004 15:06:49 -0000 1.4 --- GBCheatsDlg.cpp 6 Jun 2006 21:04:21 -0000 1.5 *************** *** 638,642 **** m_desc.GetWindowText(buffer); ! int bank = (address >> 16); address &= 0xFFFF; --- 638,642 ---- m_desc.GetWindowText(buffer); ! LONG_PTR bank = (address >> 16); address &= 0xFFFF; *************** *** 690,696 **** m_address.SetWindowText(buffer); m_address.EnableWindow(FALSE); ! ::SetWindowLong(m_address, ! GWL_USERDATA, ! address); numberType = regQueryDwordValue("gbCheatsNumberType", 2); --- 690,694 ---- m_address.SetWindowText(buffer); m_address.EnableWindow(FALSE); ! ::SetWindowLongPtr( m_address.GetSafeHwnd(), GWLP_USERDATA, address); numberType = regQueryDwordValue("gbCheatsNumberType", 2); *************** *** 827,833 **** if(m_list.GetItem(&item)) { if(gbCheatList[item.lParam].enabled) ! gbCheatDisable(item.lParam); else ! gbCheatEnable(item.lParam); refresh(); } --- 825,831 ---- if(m_list.GetItem(&item)) { if(gbCheatList[item.lParam].enabled) ! gbCheatDisable((int)item.lParam); else ! gbCheatEnable((int)item.lParam); refresh(); } *************** *** 845,849 **** item.iItem = mark; if(m_list.GetItem(&item)) { ! gbCheatRemove(item.lParam); refresh(); } --- 843,847 ---- item.iItem = mark; if(m_list.GetItem(&item)) { ! gbCheatRemove((int)item.lParam); refresh(); } *************** *** 873,879 **** (((l->uNewState & LVIS_STATEIMAGEMASK)>>12))) { if(m_list.GetCheck(l->iItem)) ! gbCheatEnable(l->lParam); else ! gbCheatDisable(l->lParam); refresh(); } --- 871,877 ---- (((l->uNewState & LVIS_STATEIMAGEMASK)>>12))) { if(m_list.GetCheck(l->iItem)) ! gbCheatEnable((int)l->lParam); else ! gbCheatDisable((int)l->lParam); refresh(); } Index: GBCheatsDlg.h =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/GBCheatsDlg.h,v retrieving revision 1.3 retrieving revision 1.4 diff -C2 -d -r1.3 -r1.4 *** GBCheatsDlg.h 13 May 2004 15:06:49 -0000 1.3 --- GBCheatsDlg.h 6 Jun 2006 21:04:21 -0000 1.4 *************** *** 122,126 **** // Implementation protected: ! u32 address; // Generated message map functions --- 122,126 ---- // Implementation protected: ! LONG_PTR address; // Generated message map functions Index: Logging.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/Logging.cpp,v retrieving revision 1.6 retrieving revision 1.7 diff -C2 -d -r1.6 -r1.7 *** Logging.cpp 5 Jan 2006 14:55:31 -0000 1.6 --- Logging.cpp 6 Jun 2006 21:04:21 -0000 1.7 *************** *** 238,242 **** void Logging::log(const char *s) { ! int size = ::SendMessage(m_log, WM_GETTEXTLENGTH, 0, 0); m_log.SetSel(size, size); m_log.ReplaceSel(s); --- 238,242 ---- void Logging::log(const char *s) { ! DWORD size = (DWORD)::SendMessage(m_log, WM_GETTEXTLENGTH, 0, 0); m_log.SetSel(size, size); m_log.ReplaceSel(s); Index: AcceleratorManager.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/AcceleratorManager.cpp,v retrieving revision 1.6 retrieving revision 1.7 diff -C2 -d -r1.6 -r1.7 *** AcceleratorManager.cpp 4 Nov 2003 14:09:51 -0000 1.6 --- AcceleratorManager.cpp 6 Jun 2006 21:04:20 -0000 1.7 *************** *** 248,252 **** } ! int nAccel = arrayACCEL.GetSize(); LPACCEL lpAccel = (LPACCEL)LocalAlloc(LPTR, nAccel * sizeof(ACCEL)); if (!lpAccel) { --- 248,252 ---- } ! INT_PTR nAccel = arrayACCEL.GetSize(); LPACCEL lpAccel = (LPACCEL)LocalAlloc(LPTR, nAccel * sizeof(ACCEL)); if (!lpAccel) { *************** *** 269,273 **** arrayACCEL.RemoveAll(); ! HACCEL hNewTable = CreateAcceleratorTable(lpAccel, nAccel); if (!hNewTable) { ::LocalFree(lpAccel); --- 269,273 ---- arrayACCEL.RemoveAll(); ! HACCEL hNewTable = CreateAcceleratorTable(lpAccel, (int)nAccel); if (!hNewTable) { ::LocalFree(lpAccel); *************** *** 710,714 **** // AccelsDatasArray.InsertAt(0, MAKELONG(65535, iCount)); ! int count = AccelsDatasArray.GetSize(); DWORD *data = (DWORD *)malloc(count * sizeof(DWORD)); ASSERT(data != NULL); --- 710,714 ---- // AccelsDatasArray.InsertAt(0, MAKELONG(65535, iCount)); ! INT_PTR count = AccelsDatasArray.GetSize(); DWORD *data = (DWORD *)malloc(count * sizeof(DWORD)); ASSERT(data != NULL); *************** *** 717,721 **** data[index] = AccelsDatasArray[index]; ! regSetBinaryValue("keyboard", (char *)data, count*sizeof(DWORD)); AccelsDatasArray.RemoveAll(); --- 717,721 ---- data[index] = AccelsDatasArray[index]; ! regSetBinaryValue("keyboard", (char *)data, (int)(count*sizeof(DWORD))); AccelsDatasArray.RemoveAll(); Index: ModeConfirm.h =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/ModeConfirm.h,v retrieving revision 1.3 retrieving revision 1.4 diff -C2 -d -r1.3 -r1.4 *** ModeConfirm.h 27 May 2006 14:47:33 -0000 1.3 --- ModeConfirm.h 6 Jun 2006 21:04:21 -0000 1.4 *************** *** 61,65 **** afx_msg void OnDestroy(); virtual BOOL OnInitDialog(); ! afx_msg void OnTimer(UINT nIDEvent); //}}AFX_MSG DECLARE_MESSAGE_MAP() --- 61,65 ---- afx_msg void OnDestroy(); virtual BOOL OnInitDialog(); ! afx_msg void OnTimer(UINT_PTR nIDEvent); //}}AFX_MSG DECLARE_MESSAGE_MAP() Index: GBMapView.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/GBMapView.cpp,v retrieving revision 1.7 retrieving revision 1.8 diff -C2 -d -r1.7 -r1.8 *** GBMapView.cpp 27 May 2006 14:47:33 -0000 1.7 --- GBMapView.cpp 6 Jun 2006 21:04:21 -0000 1.8 *************** *** 501,505 **** int x = (int)(wParam & 0xffff); ! int y = wParam >> 16; CString buffer; --- 501,505 ---- int x = (int)(wParam & 0xffff); ! int y = (int)(wParam >> 16); CString buffer; Index: MapView.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/MapView.cpp,v retrieving revision 1.9 retrieving revision 1.10 diff -C2 -d -r1.9 -r1.10 *** MapView.cpp 3 Sep 2005 12:29:23 -0000 1.9 --- MapView.cpp 6 Jun 2006 21:04:21 -0000 1.10 *************** *** 787,792 **** mapViewZoom.setColors(colors); ! int x = wParam & 0xffff; ! int y = (wParam >> 16); CString buffer; --- 787,792 ---- mapViewZoom.setColors(colors); ! int x = (int)(wParam & 0xffff); ! int y = (int)(wParam >> 16); CString buffer; Index: ModeConfirm.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/ModeConfirm.cpp,v retrieving revision 1.2 retrieving revision 1.3 diff -C2 -d -r1.2 -r1.3 *** ModeConfirm.cpp 13 May 2004 15:06:55 -0000 1.2 --- ModeConfirm.cpp 6 Jun 2006 21:04:21 -0000 1.3 *************** *** 101,105 **** } ! void ModeConfirm::OnTimer(UINT nIDEvent) { CString buffer; --- 101,105 ---- } ! void ModeConfirm::OnTimer(UINT_PTR nIDEvent) { CString buffer; Index: TileView.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/TileView.cpp,v retrieving revision 1.3 retrieving revision 1.4 diff -C2 -d -r1.3 -r1.4 *** TileView.cpp 3 Sep 2005 12:29:23 -0000 1.3 --- TileView.cpp 6 Jun 2006 21:04:21 -0000 1.4 *************** *** 530,535 **** zoom.setColors(colors); ! int x = (wParam & 0xFFFF)/8; ! int y = ((wParam >> 16) & 0xFFFF)/8; u32 address = 0x6000000 + 0x4000 * charBase; --- 530,535 ---- zoom.setColors(colors); ! int x = (int)((wParam & 0xFFFF) / 8); ! int y = (int)(((wParam >> 16) & 0xFFFF) / 8); u32 address = 0x6000000 + 0x4000 * charBase; Index: vba.rc =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/vba.rc,v retrieving revision 1.55 retrieving revision 1.56 diff -C2 -d -r1.55 -r1.56 *** vba.rc 27 May 2006 14:47:33 -0000 1.55 --- vba.rc 6 Jun 2006 21:04:21 -0000 1.56 *************** *** 13,18 **** #undef APSTUDIO_READONLY_SYMBOLS - ///////////////////////////////////////////////////////////////////////////// - // English (U.S.) resources #if !defined(AFX_RESOURCE_DLL) || defined(AFX_TARG_ENU) --- 13,16 ---- *************** *** 77,81 **** FONT 8, "MS Sans Serif", 0, 0, 0x0 BEGIN ! ICON 101,IDC_STATIC,6,6,20,20 CTEXT "VisualBoyAdvance Emulator",IDC_STATIC,30,6,120,8 CTEXT "Copyright © 2006 VBA development team",IDC_STATIC,6,36,144,8 --- 75,79 ---- FONT 8, "MS Sans Serif", 0, 0, 0x0 BEGIN ! ICON IDI_ICON,IDC_STATIC,6,6,20,20 CTEXT "VisualBoyAdvance Emulator",IDC_STATIC,30,6,120,8 CTEXT "Copyright © 2006 VBA development team",IDC_STATIC,6,36,144,8 *************** *** 1826,1836 **** ///////////////////////////////////////////////////////////////////////////// // - // RT_MANIFEST - // - - 1 RT_MANIFEST "VisualBoyAdvance.exe.manifest" - - ///////////////////////////////////////////////////////////////////////////// - // // String Table // --- 1824,1827 ---- Index: DirectDraw.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/DirectDraw.cpp,v retrieving revision 1.8 retrieving revision 1.9 diff -C2 -d -r1.8 -r1.9 *** DirectDraw.cpp 13 May 2006 16:32:16 -0000 1.8 --- DirectDraw.cpp 6 Jun 2006 21:04:21 -0000 1.9 *************** *** 34,37 **** --- 34,39 ---- #include "resource.h" + #include "Display.h" + #ifdef _DEBUG #define new DEBUG_NEW *************** *** 632,635 **** --- 634,638 ---- { HRESULT hret; + unsigned int nBytesPerPixel = systemColorDepth>>3; if(pDirectDraw == NULL || *************** *** 704,761 **** } } ! // MMX doesn't seem to be faster to copy the data ! __asm { ! mov eax, copyX; ! mov ebx, copyY; ! ! mov esi, pix; ! mov edi, ddsDesc.lpSurface; ! mov edx, ddsDesc.lPitch; ! cmp systemColorDepth, 16; ! jnz gbaOtherColor; ! sub edx, eax; ! sub edx, eax; ! lea esi,[esi+2*eax+4]; ! shr eax, 1; ! gbaLoop16bit: ! mov ecx, eax; ! repz movsd; ! inc esi; ! inc esi; ! inc esi; ! inc esi; ! add edi, edx; ! dec ebx; ! jnz gbaLoop16bit; ! jmp gbaLoopEnd; ! gbaOtherColor: ! cmp systemColorDepth, 32; ! jnz gbaOtherColor2; ! ! sub edx, eax; ! sub edx, eax; ! sub edx, eax; ! sub edx, eax; ! lea esi, [esi+4*eax+4]; ! gbaLoop32bit: ! mov ecx, eax; ! repz movsd; ! add esi, 4; ! add edi, edx; ! dec ebx; ! jnz gbaLoop32bit; ! jmp gbaLoopEnd; ! gbaOtherColor2: ! lea eax, [eax+2*eax]; ! sub edx, eax; ! gbaLoop24bit: ! mov ecx, eax; ! shr ecx, 2; ! repz movsd; ! add edi, edx; ! dec ebx; ! jnz gbaLoop24bit; ! gbaLoopEnd: ! } } if(theApp.showSpeed && (theApp.videoOption > VIDEO_4X || theApp.skin != NULL)) { --- 707,711 ---- } } ! copyImage( pix, ddsDesc.lpSurface, copyX, copyY, ddsDesc.lPitch, systemColorDepth ); } if(theApp.showSpeed && (theApp.videoOption > VIDEO_4X || theApp.skin != NULL)) { *************** *** 829,833 **** SetBkMode(hdc,TRANSPARENT); TextOut(hdc, theApp.dest.left+10, theApp.dest.bottom - 20, theApp.screenMessageBuffer, ! strlen(theApp.screenMessageBuffer)); ddsPrimary->ReleaseDC(hdc); } else { --- 779,783 ---- SetBkMode(hdc,TRANSPARENT); TextOut(hdc, theApp.dest.left+10, theApp.dest.bottom - 20, theApp.screenMessageBuffer, ! (int)_tcslen(theApp.screenMessageBuffer)); ddsPrimary->ReleaseDC(hdc); } else { Index: VideoMode.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/VideoMode.cpp,v retrieving revision 1.6 retrieving revision 1.7 diff -C2 -d -r1.6 -r1.7 *** VideoMode.cpp 13 May 2006 16:32:16 -0000 1.6 --- VideoMode.cpp 6 Jun 2006 21:04:21 -0000 1.7 *************** *** 111,115 **** sprintf(buffer, "%4dx%4dx%2d", surf->dwWidth, surf->dwHeight, surf->ddpfPixelFormat.dwRGBBitCount); ! int pos = ::SendMessage(h, LB_ADDSTRING, 0, (LPARAM)buffer); ::SendMessage(h, LB_SETITEMDATA, pos, (surf->ddpfPixelFormat.dwRGBBitCount << 24) | --- 111,115 ---- sprintf(buffer, "%4dx%4dx%2d", surf->dwWidth, surf->dwHeight, surf->ddpfPixelFormat.dwRGBBitCount); ! WPARAM pos = ::SendMessage(h, LB_ADDSTRING, 0, (LPARAM)buffer); ::SendMessage(h, LB_SETITEMDATA, pos, (surf->ddpfPixelFormat.dwRGBBitCount << 24) | *************** *** 185,189 **** VideoDriverSelect d(pWnd); ! selected = d.DoModal(); if(selected == -1) { --- 185,189 ---- VideoDriverSelect d(pWnd); ! INT_PTR selected = d.DoModal(); if(selected == -1) { *************** *** 230,234 **** VideoMode dlg(ddraw, pWnd); ! int res = dlg.DoModal(); if(res != -1) { --- 230,234 ---- VideoMode dlg(ddraw, pWnd); ! INT_PTR res = dlg.DoModal(); if(res != -1) { *************** *** 246,250 **** #endif ! return res; } --- 246,250 ---- #endif ! return (int)res; } *************** *** 297,306 **** void VideoMode::OnOk() { ! int cur = m_modes.GetCurSel(); if(cur != -1) { ! cur = m_modes.GetItemData(cur); } ! EndDialog(cur); } --- 297,306 ---- void VideoMode::OnOk() { ! DWORD_PTR cur = m_modes.GetCurSel(); if(cur != -1) { ! cur = m_modes.GetItemData((int)cur); } ! EndDialog((int)cur); } Index: ResizeDlg.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/ResizeDlg.cpp,v retrieving revision 1.3 retrieving revision 1.4 diff -C2 -d -r1.3 -r1.4 *** ResizeDlg.cpp 4 Nov 2003 14:09:52 -0000 1.3 --- ResizeDlg.cpp 6 Jun 2006 21:04:21 -0000 1.4 *************** *** 90,94 **** if(res == IDRETRY) { ! __asm int 3; } else if(res == IDABORT) SendMessage(*theApp.m_pMainWnd, WM_QUIT, 0, 0); --- 90,94 ---- if(res == IDRETRY) { ! DebugBreak(); } else if(res == IDABORT) SendMessage(*theApp.m_pMainWnd, WM_QUIT, 0, 0); *************** *** 144,148 **** ::SendMessage(*theApp.m_pMainWnd, WM_QUIT, 0, 0); } else if(nCode == IDRETRY) ! __asm int 3; } --- 144,148 ---- ::SendMessage(*theApp.m_pMainWnd, WM_QUIT, 0, 0); } else if(nCode == IDRETRY) ! DebugBreak(); } Index: MainWndFile.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/MainWndFile.cpp,v retrieving revision 1.15 retrieving revision 1.16 diff -C2 -d -r1.15 -r1.16 *** MainWndFile.cpp 6 Jun 2006 14:33:43 -0000 1.15 --- MainWndFile.cpp 6 Jun 2006 21:04:21 -0000 1.16 *************** *** 707,711 **** if(game != -1) { ! return cheatsImportGSACodeFile(fileName, game, v3); } --- 707,711 ---- if(game != -1) { ! return cheatsImportGSACodeFile(fileName, (int)game, v3); } Index: Joypad.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/Joypad.cpp,v retrieving revision 1.7 retrieving revision 1.8 diff -C2 -d -r1.7 -r1.8 *** Joypad.cpp 6 Jun 2006 14:33:43 -0000 1.7 --- Joypad.cpp 6 Jun 2006 21:04:21 -0000 1.8 *************** *** 31,36 **** #endif ! extern USHORT joypad[4][13]; ! extern USHORT motion[4]; ///////////////////////////////////////////////////////////////////////////// --- 31,36 ---- #endif ! extern LONG_PTR joypad[4][13]; ! extern LONG_PTR motion[4]; ///////////////////////////////////////////////////////////////////////////// *************** *** 55,63 **** LRESULT JoypadEditControl::OnJoyConfig(WPARAM wParam, LPARAM lParam) { ! #ifdef _WIN64 ! SetWindowLongPtr( GetSafeHwnd(), GWL_USERDATA, ((wParam<<8)|lParam) ); ! #else ! SetWindowLongPtr( GetSafeHwnd(), GWL_USERDATA, PtrToLong((wParam<<8)|lParam) ); ! #endif this->SetWindowText( theApp.input->getKeyName( (int)((wParam<<8)|lParam) ) ); GetParent()->GetNextDlgTabItem(this, FALSE)->SetFocus(); --- 55,59 ---- LRESULT JoypadEditControl::OnJoyConfig(WPARAM wParam, LPARAM lParam) { ! SetWindowLongPtr( this->GetSafeHwnd(), GWLP_USERDATA, (wParam<<8) | lParam ); this->SetWindowText( theApp.input->getKeyName( (int)((wParam<<8)|lParam) ) ); GetParent()->GetNextDlgTabItem(this, FALSE)->SetFocus(); *************** *** 140,144 **** } ! void JoypadConfig::OnTimer(UINT nIDEvent) { theApp.input->checkDevices(); --- 136,140 ---- } ! void JoypadConfig::OnTimer(UINT_PTR nIDEvent) { theApp.input->checkDevices(); *************** *** 157,197 **** timerId = SetTimer(0,50,NULL); ! SetWindowLongPtr(up, GWL_USERDATA,joypad[which][KEY_UP]); up.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_UP])); ! SetWindowLongPtr(down, GWL_USERDATA,joypad[which][KEY_DOWN]); down.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_DOWN])); ! SetWindowLongPtr(left, GWL_USERDATA,joypad[which][KEY_LEFT]); left.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_LEFT])); ! SetWindowLongPtr(right, GWL_USERDATA,joypad[which][KEY_RIGHT]); right.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_RIGHT])); ! SetWindowLongPtr(buttonA, GWL_USERDATA,joypad[which][KEY_BUTTON_A]); buttonA.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_A])); ! SetWindowLongPtr(buttonB, GWL_USERDATA,joypad[which][KEY_BUTTON_B]); buttonB.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_B])); ! SetWindowLongPtr(buttonL, GWL_USERDATA,joypad[which][KEY_BUTTON_L]); buttonL.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_L])); ! SetWindowLongPtr(buttonR, GWL_USERDATA,joypad[which][KEY_BUTTON_R]); buttonR.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_R])); ! SetWindowLongPtr(buttonSelect, GWL_USERDATA,joypad[which][KEY_BUTTON_SELECT]); buttonSelect.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_SELECT])); ! SetWindowLongPtr(buttonStart, GWL_USERDATA,joypad[which][KEY_BUTTON_START]); buttonStart.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_START])); ! SetWindowLongPtr(speed, GWL_USERDATA,joypad[which][KEY_BUTTON_SPEED]); speed.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_SPEED])); ! SetWindowLongPtr(capture, GWL_USERDATA,joypad[which][KEY_BUTTON_CAPTURE]); capture.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_CAPTURE])); ! SetWindowLongPtr(buttonGS, GWL_USERDATA,joypad[which][KEY_BUTTON_GS]); buttonGS.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_GS])); --- 153,193 ---- timerId = SetTimer(0,50,NULL); ! SetWindowLongPtr(up, GWLP_USERDATA,joypad[which][KEY_UP]); up.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_UP])); ! SetWindowLongPtr(down, GWLP_USERDATA,joypad[which][KEY_DOWN]); down.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_DOWN])); ! SetWindowLongPtr(left, GWLP_USERDATA,joypad[which][KEY_LEFT]); left.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_LEFT])); ! SetWindowLongPtr(right, GWLP_USERDATA,joypad[which][KEY_RIGHT]); right.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_RIGHT])); ! SetWindowLongPtr(buttonA, GWLP_USERDATA,joypad[which][KEY_BUTTON_A]); buttonA.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_A])); ! SetWindowLongPtr(buttonB, GWLP_USERDATA,joypad[which][KEY_BUTTON_B]); buttonB.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_B])); ! SetWindowLongPtr(buttonL, GWLP_USERDATA,joypad[which][KEY_BUTTON_L]); buttonL.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_L])); ! SetWindowLongPtr(buttonR, GWLP_USERDATA,joypad[which][KEY_BUTTON_R]); buttonR.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_R])); ! SetWindowLongPtr(buttonSelect, GWLP_USERDATA,joypad[which][KEY_BUTTON_SELECT]); buttonSelect.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_SELECT])); ! SetWindowLongPtr(buttonStart, GWLP_USERDATA,joypad[which][KEY_BUTTON_START]); buttonStart.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_START])); ! SetWindowLongPtr(speed, GWLP_USERDATA,joypad[which][KEY_BUTTON_SPEED]); speed.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_SPEED])); ! SetWindowLongPtr(capture, GWLP_USERDATA,joypad[which][KEY_BUTTON_CAPTURE]); capture.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_CAPTURE])); ! SetWindowLongPtr(buttonGS, GWLP_USERDATA,joypad[which][KEY_BUTTON_GS]); buttonGS.SetWindowText(theApp.input->getKeyName(joypad[which][KEY_BUTTON_GS])); *************** *** 202,206 **** } ! void JoypadConfig::assignKey(int id, int key) { switch(id) { --- 198,202 ---- } ! void JoypadConfig::assignKey(int id, LONG_PTR key) { switch(id) { *************** *** 252,292 **** id = IDC_EDIT_UP; ! assignKey(id, GetWindowLongPtr(up, GWL_USERDATA)); id = IDC_EDIT_DOWN; ! assignKey(id, GetWindowLongPtr(down, GWL_USERDATA)); id = IDC_EDIT_LEFT; ! assignKey(id, GetWindowLongPtr(left, GWL_USERDATA)); id = IDC_EDIT_RIGHT; ! assignKey(id, GetWindowLongPtr(right, GWL_USERDATA)); id = IDC_EDIT_BUTTON_A; ! assignKey(id, GetWindowLongPtr(buttonA, GWL_USERDATA)); id = IDC_EDIT_BUTTON_B; ! assignKey(id, GetWindowLongPtr(buttonB, GWL_USERDATA)); id = IDC_EDIT_BUTTON_L; ! assignKey(id, GetWindowLongPtr(buttonL, GWL_USERDATA)); id = IDC_EDIT_BUTTON_R; ! assignKey(id, GetWindowLongPtr(buttonR, GWL_USERDATA)); id = IDC_EDIT_BUTTON_SELECT; ! assignKey(id, GetWindowLongPtr(buttonSelect, GWL_USERDATA)); id = IDC_EDIT_BUTTON_START; ! assignKey(id, GetWindowLongPtr(buttonStart, GWL_USERDATA)); id = IDC_EDIT_SPEED; ! assignKey(id, GetWindowLongPtr(speed, GWL_USERDATA)); id = IDC_EDIT_CAPTURE; ! assignKey(id, GetWindowLongPtr(capture, GWL_USERDATA)); id = IDC_EDIT_BUTTON_GS; ! assignKey(id, GetWindowLongPtr(buttonGS, GWL_USERDATA)); // winSaveKeys(); --- 248,288 ---- id = IDC_EDIT_UP; ! assignKey(id, GetWindowLongPtr(up, GWLP_USERDATA)); id = IDC_EDIT_DOWN; ! assignKey(id, GetWindowLongPtr(down, GWLP_USERDATA)); id = IDC_EDIT_LEFT; ! assignKey(id, GetWindowLongPtr(left, GWLP_USERDATA)); id = IDC_EDIT_RIGHT; ! assignKey(id, GetWindowLongPtr(right, GWLP_USERDATA)); id = IDC_EDIT_BUTTON_A; ! assignKey(id, GetWindowLongPtr(buttonA, GWLP_USERDATA)); id = IDC_EDIT_BUTTON_B; ! assignKey(id, GetWindowLongPtr(buttonB, GWLP_USERDATA)); id = IDC_EDIT_BUTTON_L; ! assignKey(id, GetWindowLongPtr(buttonL, GWLP_USERDATA)); id = IDC_EDIT_BUTTON_R; ! assignKey(id, GetWindowLongPtr(buttonR, GWLP_USERDATA)); id = IDC_EDIT_BUTTON_SELECT; ! assignKey(id, GetWindowLongPtr(buttonSelect, GWLP_USERDATA)); id = IDC_EDIT_BUTTON_START; ! assignKey(id, GetWindowLongPtr(buttonStart, GWLP_USERDATA)); id = IDC_EDIT_SPEED; ! assignKey(id, GetWindowLongPtr(speed, GWLP_USERDATA)); id = IDC_EDIT_CAPTURE; ! assignKey(id, GetWindowLongPtr(capture, GWLP_USERDATA)); id = IDC_EDIT_BUTTON_GS; ! assignKey(id, GetWindowLongPtr(buttonGS, GWLP_USERDATA)); // winSaveKeys(); *************** *** 355,368 **** timerId = SetTimer(0,200,NULL); ! SetWindowLongPtr(up, GWL_USERDATA,motion[KEY_UP]); up.SetWindowText(theApp.input->getKeyName(motion[KEY_UP])); ! SetWindowLongPtr(down, GWL_USERDATA,motion[KEY_DOWN]); down.SetWindowText(theApp.input->getKeyName(motion[KEY_DOWN])); ! SetWindowLongPtr(left, GWL_USERDATA,motion[KEY_LEFT]); left.SetWindowText(theApp.input->getKeyName(motion[KEY_LEFT])); ! SetWindowLongPtr(right, GWL_USERDATA,motion[KEY_RIGHT]); right.SetWindowText(theApp.input->getKeyName(motion[KEY_RIGHT])); --- 351,364 ---- timerId = SetTimer(0,200,NULL); ! SetWindowLongPtr(up, GWLP_USERDATA,motion[KEY_UP]); up.SetWindowText(theApp.input->getKeyName(motion[KEY_UP])); ! SetWindowLongPtr(down, GWLP_USERDATA,motion[KEY_DOWN]); down.SetWindowText(theApp.input->getKeyName(motion[KEY_DOWN])); ! SetWindowLongPtr(left, GWLP_USERDATA,motion[KEY_LEFT]); left.SetWindowText(theApp.input->getKeyName(motion[KEY_LEFT])); ! SetWindowLongPtr(right, GWLP_USERDATA,motion[KEY_RIGHT]); right.SetWindowText(theApp.input->getKeyName(motion[KEY_RIGHT])); *************** *** 377,381 **** } ! void MotionConfig::OnTimer(UINT nIDEvent) { theApp.input->checkDevices(); --- 373,377 ---- } ! void MotionConfig::OnTimer(UINT_PTR nIDEvent) { theApp.input->checkDevices(); *************** *** 384,388 **** } ! void MotionConfig::assignKey(int id, int key) { switch(id) { --- 380,384 ---- } ! void MotionConfig::assignKey(int id, LONG_PTR key) { switch(id) { *************** *** 407,419 **** id = IDC_EDIT_UP; ! assignKey(id, GetWindowLongPtr(up, GWL_USERDATA)); id = IDC_EDIT_DOWN; ! assignKey(id, GetWindowLongPtr(down, GWL_USERDATA)); id = IDC_EDIT_LEFT; ! assignKey(id, GetWindowLongPtr(left, GWL_USERDATA)); id = IDC_EDIT_RIGHT; ! assignKey(id, GetWindowLongPtr(right, GWL_USERDATA)); } --- 403,415 ---- id = IDC_EDIT_UP; ! assignKey(id, GetWindowLongPtr(up, GWLP_USERDATA)); id = IDC_EDIT_DOWN; ! assignKey(id, GetWindowLongPtr(down, GWLP_USERDATA)); id = IDC_EDIT_LEFT; ! assignKey(id, GetWindowLongPtr(left, GWLP_USERDATA)); id = IDC_EDIT_RIGHT; ! assignKey(id, GetWindowLongPtr(right, GWLP_USERDATA)); } Index: DirectInput.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/DirectInput.cpp,v retrieving revision 1.6 retrieving revision 1.7 diff -C2 -d -r1.6 -r1.7 *** DirectInput.cpp 27 May 2006 14:47:33 -0000 1.6 --- DirectInput.cpp 6 Jun 2006 21:04:21 -0000 1.7 *************** *** 50,54 **** virtual bool readDevices(); virtual u32 readDevice(int which); ! virtual CString getKeyName(int key); virtual void checkKeys(); virtual void checkMotionKeys(); --- 50,54 ---- virtual bool readDevices(); virtual u32 readDevice(int which); ! virtual CString getKeyName(LONG_PTR key); virtual void checkKeys(); virtual void checkMotionKeys(); *************** *** 85,89 **** static int axisNumber = 0; ! USHORT joypad[4][13] = { { DIK_LEFT, DIK_RIGHT, --- 85,89 ---- static int axisNumber = 0; ! LONG_PTR joypad[4][13] = { { DIK_LEFT, DIK_RIGHT, *************** *** 100,104 **** }; ! USHORT motion[4] = { DIK_NUMPAD4, DIK_NUMPAD6, DIK_NUMPAD8, DIK_NUMPAD2 }; --- 100,104 ---- }; ! LONG_PTR motion[4] = { DIK_NUMPAD4, DIK_NUMPAD6, DIK_NUMPAD8, DIK_NUMPAD2 }; *************** *** 172,176 **** } ! static void winSaveKey(char *name, int num, USHORT value) { char buffer[80]; --- 172,176 ---- } ! static void winSaveKey(char *name, int num, LONG_PTR value) { char buffer[80]; *************** *** 178,182 **** sprintf(buffer, "Joy%d_%s", num, name); ! regSetDwordValue(buffer, value); } --- 178,182 ---- sprintf(buffer, "Joy%d_%s", num, name); ! regSetDwordValue(buffer, (DWORD)value); } *************** *** 200,211 **** regSetDwordValue("joyVersion", 1); ! regSetDwordValue("Motion_Left", ! motion[KEY_LEFT]); ! regSetDwordValue("Motion_Right", ! motion[KEY_RIGHT]); ! regSetDwordValue("Motion_Up", ! motion[KEY_UP]); ! regSetDwordValue("Motion_Down", ! motion[KEY_DOWN]); } --- 200,207 ---- regSetDwordValue("joyVersion", 1); ! regSetDwordValue("Motion_Left", (DWORD)motion[KEY_LEFT]); ! regSetDwordValue("Motion_Right", (DWORD)motion[KEY_RIGHT]); ! regSetDwordValue("Motion_Up", (DWORD)motion[KEY_UP]); ! regSetDwordValue("Motion_Down", (DWORD)motion[KEY_DOWN]); } *************** *** 333,337 **** static void checkKeys() { ! int dev = 0; int i; --- 329,333 ---- static void checkKeys() { ! LONG_PTR dev = 0; int i; *************** *** 628,636 **** } ! BOOL checkKey(int key) { ! int dev = (key >> 8); ! int k = (key & 255); if(dev == 0) { --- 624,632 ---- } ! BOOL checkKey(LONG_PTR key) { ! LONG_PTR dev = (key >> 8); ! LONG_PTR k = (key & 255); if(dev == 0) { *************** *** 638,642 **** } else { if(k < 16) { ! int axis = k >> 1; LONG value = pDevices[dev].axis[axis].center; switch(pDevices[dev].axis[axis].offset) { --- 634,638 ---- } else { if(k < 16) { ! LONG_PTR axis = k >> 1; LONG value = pDevices[dev].axis[axis].center; switch(pDevices[dev].axis[axis].offset) { *************** *** 671,675 **** return value < pDevices[dev].axis[axis].negative; } else if(k < 48) { ! int hat = (k >> 2) & 3; int state = getPovState(pDevices[dev].state.rgdwPOV[hat]); BOOL res = FALSE; --- 667,671 ---- return value < pDevices[dev].axis[axis].negative; } else if(k < 48) { ! LONG_PTR hat = (k >> 2) & 3; int state = getPovState(pDevices[dev].state.rgdwPOV[hat]); BOOL res = FALSE; *************** *** 923,930 **** } ! CString DirectInput::getKeyName(int key) { ! int d = (key >> 8); ! int k = key & 255; DIDEVICEOBJECTINSTANCE di; --- 919,926 ---- } ! CString DirectInput::getKeyName(LONG_PTR key) { ! LONG_PTR d = (key >> 8); ! LONG_PTR k = key & 255; DIDEVICEOBJECTINSTANCE di; *************** *** 937,941 **** if(d == 0) { ! pDevices[0].device->GetObjectInfo(&di,key,DIPH_BYOFFSET); winBuffer = di.tszName; } else { --- 933,937 ---- if(d == 0) { ! pDevices[0].device->GetObjectInfo( &di, (DWORD)key, DIPH_BYOFFSET ); winBuffer = di.tszName; } else { *************** *** 966,975 **** } } else if(k < 48) { ! int hat = (k >> 2) & 3; pDevices[d].device->GetObjectInfo(&di, ! DIJOFS_POV(hat), DIPH_BYOFFSET); char *dir = "up"; ! int dd = k & 3; if(dd == 1) dir = "down"; --- 962,971 ---- } } else if(k < 48) { ! LONG_PTR hat = (k >> 2) & 3; pDevices[d].device->GetObjectInfo(&di, ! (DWORD)DIJOFS_POV(hat), DIPH_BYOFFSET); char *dir = "up"; ! LONG_PTR dd = k & 3; if(dd == 1) dir = "down"; *************** *** 981,985 **** } else { pDevices[d].device->GetObjectInfo(&di, ! DIJOFS_BUTTON(k-128), DIPH_BYOFFSET); winBuffer.Format(winResLoadString(IDS_JOY_BUTTON),d,di.tszName); --- 977,981 ---- } else { pDevices[d].device->GetObjectInfo(&di, ! (DWORD)DIJOFS_BUTTON(k-128), DIPH_BYOFFSET); winBuffer.Format(winResLoadString(IDS_JOY_BUTTON),d,di.tszName); Index: MainWndOptions.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/MainWndOptions.cpp,v retrieving revision 1.8 retrieving revision 1.9 diff -C2 -d -r1.8 -r1.9 *** MainWndOptions.cpp 27 May 2006 14:47:33 -0000 1.8 --- MainWndOptions.cpp 6 Jun 2006 21:04:21 -0000 1.9 *************** *** 1534,1537 **** --- 1534,1538 ---- void MainWnd::OnOptionsFilterDisablemmx() { + #ifdef MMX theApp.disableMMX = !theApp.disableMMX; if(!theApp.disableMMX) *************** *** 1539,1542 **** --- 1540,1544 ---- else cpu_mmx = 0; + #endif } Index: VBA.h =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/VBA.h,v retrieving revision 1.8 retrieving revision 1.9 diff -C2 -d -r1.8 -r1.9 *** VBA.h 27 May 2006 14:47:33 -0000 1.8 --- VBA.h 6 Jun 2006 21:04:21 -0000 1.9 *************** *** 232,237 **** HMODULE winLoadLanguage(const char *name); void winSetLanguageOption(int option, bool force); - bool detectMMX(); #ifdef MMX #endif void updatePriority(); --- 232,237 ---- HMODULE winLoadLanguage(const char *name); void winSetLanguageOption(int option, bool force); #ifdef MMX + bool detectMMX(); #endif void updatePriority(); Index: skin.cpp =================================================================== RCS file: /cvsroot/vba/VisualBoyAdvance/src/win32/skin.cpp,v retrieving revision 1.8 retrieving revision 1.9 diff -C2 -d -r1.8 -r1.9 *** skin.cpp 6 Jun 2006 14:33:43 -0000 1.8 --- skin.cpp 6 Jun 2006 21:04:21 -0000 1.9 *************** *** 151,159 **** m_dOldStyle = dwStyle; dwStyle &= ~(WS_CAPTION|WS_SIZEBOX); - #ifdef _WIN64 SetWindowLongPtr(m_hWnd, GWL_STYLE, dwStyle); - #else - SetWindowLongPtr(m_hWnd, GWL_STYLE, (LONG)dwStyle); - #endif RECT r; --- 151,155 ---- *************** *** 173,181 **** // subclass the window procedure ! #ifdef _WIN64 ! m_OldWndProc = (WNDPROC)SetWindowLongPtr(m_hWnd, GWL_WNDPROC, (LONG_PTR)SkinWndProc); ! #else ! m_OldWndProc = (WNDPROC)LongToPtr(SetWindowLongPtr(m_hWnd, GWL_WNDPROC, PtrToLong(SkinWndProc))); ! #endif // store a pointer to our class instance inside the window procedure. --- 169,173 ---- // subclass the window procedure ! m_OldWndProc = (WNDPROC)SetWindowLongPtr( m_hWnd, GWLP_WNDPROC, (LONG_PTR)SkinWndProc ); // store a pointer to our class instance inside the window procedure. *************** *** 223,231 **** // unsubclass the window procedure ! #ifdef _WIN64 ! OurWnd = (WNDPROC)SetWindowLongPtr(m_hWnd, GWL_WNDPROC, (LONG_PTR)m_OldWndProc); ! #else ! OurWnd = (WNDPROC)LongToPtr(SetWindowLongPtr(m_hWnd, GWL_WNDPROC, PtrToLong(m_OldWndProc))); ! #endif // remove the pointer to our class instance, but if we fail we don't care. --- 215,219 ---- // unsubclass the window procedure ! OurWnd = (WNDPROC)SetWindowLongPtr( m_hWnd, GWLP_WNDPROC, (LONG_PTR)m_OldWndProc ); // remove the pointer to our class instance, but if we fail we don't care. *************** *** 236,244 **** m_bHooked = ( OurWnd ? false : true ); - #ifdef _WIN64 SetWindowLongPtr(m_hWnd, GWL_STYLE, m_dOldStyle); - #else - SetWindowLongPtr(m_hWnd, GWL_STYLE, (LONG)m_dOldStyle); - #endif RECT r; --- 224,228 ---- *************** *** 550,554 **** // we will need a pointer to the associated class instance // (it was stored in the window before, remember?) ! CSkin *pSkin = (CSkin*)GetProp(hWnd, "skin"); // to handle WM_PAINT --- 534,538 ---- // we will need a pointer to the associated class instance // (it was stored in the window before, remember?) ! CSkin *pSkin = (CSkin*)GetProp(hWnd, _T("skin")); // to handle WM_PAINT |