|
From: Tim R. <row...@us...> - 2003-05-09 01:07:19
|
Update of /cvsroot/squeak/squeak/platforms/RiscOS/vm In directory sc8-pr-cvs1:/tmp/cvs-serv6982/RiscOS/vm Modified Files: fperrors.s osExports.c sqArgument.c sqPlatformSpecific.h sqRPCClipboard.c sqRPCEvents.c sqRPCExternalPrims.c sqRPCFormPrint.c sqRPCSyscall.c sqRPCWindows.c Added Files: sqRPCVersion.c Log Message: Modified Files: RiscOS/plugins/FileCopyPlugin/sqRPCFileCopy.c comment change RiscOS/plugins/FilePlugin/sqRPCDirectory.c timezone/stamp calculation fixes RiscOS/plugins/SocketPlugin/sqRPCNetPlugin.c comment change RiscOS/plugins/SoundPlugin/sqRPCSound.c RiscOS/vm/fperrors.s remove dead code, 32bit fix RiscOS/vm/osExports.c RiscOS/vm/sqArgument.c new window label argument RiscOS/vm/sqPlatformSpecific.h RiscOS/vm/sqRPCClipboard.c clipboard works! RiscOS/vm/sqRPCEvents.c RiscOS/vm/sqRPCExternalPrims.c comment change RiscOS/vm/sqRPCFormPrint.c RiscOS/vm/sqRPCSyscall.c comment change RiscOS/vm/sqRPCWindows.c RiscOS/vm/dsc/block,fff add timezone related call Added Files: RiscOS/vm/sqRPCVersion.c use as a kind of vm compiletime timestamp --- NEW FILE: sqRPCVersion.c --- /**************************************************************************/ /* A Squeak VM for Acorn RiscOS machines by Tim Rowledge */ /* ti...@su... & http://sumeru.stanford.edu/tim */ /* Known to work on RiscOS >3.7 for StrongARM RPCs and Iyonix, */ /* other machines not yet tested. */ /* sqRPCVersion.c */ /* A trivial file to recompile every time a VM is built so as to track */ /* the exact time and date of build */ /**************************************************************************/ char VMVersion[] = "3.4 of "__DATE__"@"__TIME__; Index: fperrors.s =================================================================== RCS file: /cvsroot/squeak/squeak/platforms/RiscOS/vm/fperrors.s,v retrieving revision 1.1.1.1 retrieving revision 1.2 diff -C2 -d -r1.1.1.1 -r1.2 *** fperrors.s 24 Oct 2001 23:14:02 -0000 1.1.1.1 --- fperrors.s 9 May 2003 01:07:16 -0000 1.2 *************** *** 5,17 **** pc RN 15 - XOS_ReadMonotonicTime * &42 + (1 :SHL: 17) - ioc * &3200000 - ioc_ctrl * &106 - t0_low * &40 - t0_high * &44 - t0_go * &48 - t0_latch * &4C - - ; Macro to provide labels in ASM code to suit C linker/debugger --- 5,8 ---- *************** *** 21,25 **** size SETA &FF000000 + (( (:LEN: "$string") + 4 ) :AND: &FFFFFFFC) ! $label DCB "$string" ALIGN DCD size --- 12,16 ---- size SETA &FF000000 + (( (:LEN: "$string") + 4 ) :AND: &FFFFFFFC) ! $label DCB "$string",0 ALIGN DCD size *************** *** 32,37 **** EXPORT setFPStatus EXPORT readFPStatus - ; EXPORT readCSecClock - ; EXPORT readMSecClock ;***************************************************************** --- 23,26 ---- *************** *** 49,91 **** AND R0, R0, #&F MOV pc, lk - - ;***************************************************************** - ; The following two functions were part of an experiment in making - ; a faster and higher resolution clock. It failed. - ; Reading the timer0 would need to be in a module to work :-( - ; C_Label "readCSecClock" - ;readCSecClock - ; ; return the centisecond clock value * 10, ie rough millisecs - ; STMFD sp!, {lr} - ; SWI XOS_ReadMonotonicTime - ; ADD R0,R0,R0 ; double RO - ; ADD R0,R0,R0,LSL#2 ; then R0 = 2r0 + 2r0*4 -> 10r0 - ; LDMFD sp!, {pc} - ; - ;***************************************************************** - ; C_Label "readMSecClock" - ;readMSecClock - ; ; return the centisec * 10 + ~result of checking the timer0 - ; ; gives reasonably accurate millisecs - ; STMFD sp!, {lr} - ; MOV R1,#ioc ; read IOC timer - ; STRB R0,[R1,#t0_latch] ; make value appear on latch - ; LDRB R0,[R1,#t0_low] - ; LDRB R1,[R1,#t0_high] - ; ADD R0,R0,R1,LSL#8 ; add high and low - ; MOV R1,#2048 - ; SUB R1,R1,#49 ; leaves 1999 in R1 - ; SUB R1,R1,R0 ; reverse countdown to count up - ; MOV R1,R1,LSR#11 ; divide by 2048, close enough to 2000! - ; - ; SWI XOS_ReadMonotonicTime - ; - ; ADD R0,R0,R0 ; double RO - ; ADD R0,R0,R0,LSL#2 ; then R0 = 2r0 + 2r0*4 -> 10r0 - ; ADD R0,R0,R1 - ; - ; LDMFD sp!, {pc} - ; - ;***************************************************************** AREA |C$$data| --- 38,41 ---- Index: osExports.c =================================================================== RCS file: /cvsroot/squeak/squeak/platforms/RiscOS/vm/osExports.c,v retrieving revision 1.2 retrieving revision 1.3 diff -C2 -d -r1.2 -r1.3 *** osExports.c 4 Feb 2003 21:10:20 -0000 1.2 --- osExports.c 9 May 2003 01:07:16 -0000 1.3 *************** *** 1,6 **** /* note: this file is only a backward compatible wrapper ! for the old-style "platform.exports" definitions. ! If your platform has migrated to the new exports ! style you may as well insert the exports right here */ #include <stdio.h> /* duh ... this is ugly */ --- 1,20 ---- + /**************************************************************************/ + /* A Squeak VM for Acorn RiscOS machines by Tim Rowledge */ + /* ti...@su... & http://sumeru.stanford.edu/tim */ + /* Known to work on RiscOS >3.7 for StrongARM RPCs and Iyonix, */ + /* other machines not yet tested. */ + /* osExports.c */ + /* internal plugin hookups */ + /**************************************************************************/ + + /* To recompile this reliably you will need */ + /* OSLib - http://ro-oslib.sourceforge.net/ */ + /* Castle/AcornC/C++, the Acorn TCPIPLib */ + /* and a little luck */ /* note: this file is only a backward compatible wrapper ! * for the old-style "platform.exports" definitions. ! * If your platform has migrated to the new exports ! * style you may as well insert the exports right here ! */ #include <stdio.h> /* duh ... this is ugly */ Index: sqArgument.c =================================================================== RCS file: /cvsroot/squeak/squeak/platforms/RiscOS/vm/sqArgument.c,v retrieving revision 1.4 retrieving revision 1.5 diff -C2 -d -r1.4 -r1.5 *** sqArgument.c 14 Jan 2003 03:41:09 -0000 1.4 --- sqArgument.c 9 May 2003 01:07:16 -0000 1.5 *************** *** 1,2 **** --- 1,15 ---- + /**************************************************************************/ + /* A Squeak VM for Acorn RiscOS machines by Tim Rowledge */ + /* ti...@su... & http://sumeru.stanford.edu/tim */ + /* Known to work on RiscOS >3.7 for StrongARM RPCs and Iyonix, */ + /* other machines not yet tested. */ + /* sqArgument.c */ + /* handle commandline arguments */ + /**************************************************************************/ + + /* To recompile this reliably you will need */ + /* OSLib - http://ro-oslib.sourceforge.net/ */ + /* Castle/AcornC/C++, the Acorn TCPIPLib */ + /* and a little luck */ #include <string.h> #include <stdlib.h> *************** *** 18,25 **** static int IsImage(char *name) { ! /* check the named file to see if it is a decent candidate for a Squeak image file. Remember to check both the very beginning of the file and 512 bytes into it, just in case it was written from a unix machine - which adds a short extra header */ ! FILE *fp; ! int magic; ! int byteSwapped(int); extern int readableFormat(int imageVersion); --- 31,42 ---- static int IsImage(char *name) { ! /* check the named file to see if it is a decent candidate for a Squeak image ! * file. Remember to check both the very beginning of the file and 512 bytes ! * into it, just in case it was written from a unix machine - which adds a ! * short extra header ! */ ! FILE *fp; ! int magic; ! int byteSwapped(int); extern int readableFormat(int imageVersion); *************** *** 65,71 **** /* parse an unsigned integer argument */ static char *parseUnsignedArg(char *src, unsigned *dst) { ! char buf[50]; ! char *tmp = buf; ! int factor = 1; while(isdigit(*src)) *(tmp++) = *(src++); --- 82,88 ---- /* parse an unsigned integer argument */ static char *parseUnsignedArg(char *src, unsigned *dst) { ! char buf[50]; ! char *tmp = buf; ! int factor = 1; while(isdigit(*src)) *(tmp++) = *(src++); *************** *** 85,90 **** /* parse a (possibly signed) integer argument */ static char *parseSignedArg(char *src, int *dst) { ! int negative; ! unsigned value; negative = *src == '-'; --- 102,107 ---- /* parse a (possibly signed) integer argument */ static char *parseSignedArg(char *src, int *dst) { ! int negative; ! unsigned value; negative = *src == '-'; *************** *** 99,105 **** /* parse all arguments meaningful to the VM */ static int parseVMArgs(vmArg args[]) { ! vmArg *arg; ! int arglen; ! char * string; while(1) --- 116,122 ---- /* parse all arguments meaningful to the VM */ static int parseVMArgs(vmArg args[]) { ! vmArg *arg; ! int arglen; ! char * string; while(1) *************** *** 127,131 **** return NULL; /* done */ ! // if the char at the end of the option name is ':', null it out and skip ahead one string += (arglen-1); if(*string== ':') *(string++) = 0; --- 144,150 ---- return NULL; /* done */ ! /* if the char at the end of the option name is ':', ! * null it out and skip ahead one ! */ string += (arglen-1); if(*string== ':') *(string++) = 0; *************** *** 162,168 **** /* parse all arguments starting with the image name */ static int parseGenericArgs(void) { ! char *string; ! extern char vmPath[]; ! extern void decodePath(char*, char*); if (!(string = nextOption()) ) { --- 181,187 ---- /* parse all arguments starting with the image name */ static int parseGenericArgs(void) { ! char *string; ! extern char vmPath[]; ! extern void decodePath(char*, char*); if (!(string = nextOption()) ) { *************** *** 189,194 **** // now go through any more options while((string = nextOption()) && *string) { ! if(numOptionsImage > MAX_OPTIONS) return NULL; /* too many args */ ! while(*string && *string == ' ') string++; /* skip blanks */ imageOptions[numOptionsImage++] = string; if(!string) return NULL; --- 208,215 ---- // now go through any more options while((string = nextOption()) && *string) { ! if(numOptionsImage > MAX_OPTIONS) ! return NULL; /* too many args */ ! while(*string && *string == ' ') ! string++; /* skip blanks */ imageOptions[numOptionsImage++] = string; if(!string) return NULL; *************** *** 199,208 **** int parseArguments(char *argv[], int argc, vmArg args[]) { ! extern char vmPath[]; ! extern void decodeVMPath(char*); ! numOptionsVM = 0; ! numOptionsImage = 0; ! numOptions = argc; ! optionArray = &argv[0]; /* argv[0] = executable name */ --- 220,229 ---- int parseArguments(char *argv[], int argc, vmArg args[]) { ! extern char vmPath[]; ! extern void decodeVMPath(char*); ! numOptionsVM = 0; ! numOptionsImage = 0; ! numOptions = argc; ! optionArray = &argv[0]; /* argv[0] = executable name */ Index: sqPlatformSpecific.h =================================================================== RCS file: /cvsroot/squeak/squeak/platforms/RiscOS/vm/sqPlatformSpecific.h,v retrieving revision 1.6 retrieving revision 1.7 diff -C2 -d -r1.6 -r1.7 *** sqPlatformSpecific.h 4 Feb 2003 21:10:20 -0000 1.6 --- sqPlatformSpecific.h 9 May 2003 01:07:16 -0000 1.7 *************** *** 52,58 **** #undef ioMicroMSecs #undef ioMSecs ! #define ioMSecs() (10* (int)os_read_monotonic_time()) #undef ioLowResMSecs ! #define ioLowResMSecs() (ioMSecs()) #else #endif /* ACORN */ --- 52,59 ---- #undef ioMicroMSecs #undef ioMSecs ! #define ioMSecs() (ioMicroMSecs()) #undef ioLowResMSecs ! #define ioLowResMSecs() (ioMicroMSecs()) #else + #endif /* ACORN */ Index: sqRPCClipboard.c =================================================================== RCS file: /cvsroot/squeak/squeak/platforms/RiscOS/vm/sqRPCClipboard.c,v retrieving revision 1.2 retrieving revision 1.3 diff -C2 -d -r1.2 -r1.3 *** sqRPCClipboard.c 23 Apr 2002 22:08:47 -0000 1.2 --- sqRPCClipboard.c 9 May 2003 01:07:16 -0000 1.3 *************** *** 2,18 **** /* A Squeak VM for Acorn RiscOS machines by Tim Rowledge */ /* ti...@su... & http://sumeru.stanford.edu/tim */ ! /* Known to work on RiscOS 3.7 for StrongARM RPCs, other machines */ ! /* not yet tested. */ ! /* sqRPCClipb.c */ ! /* attempt to hook up to RiscOS clipboard stuff */ /**************************************************************************/ /* To recompile this reliably you will need */ ! /* Jonathon Coxhead's OSLib, */ ! /* AcornC_C++, the Acorn sockets libs */ /* and a little luck */ #include "oslib/os.h" #include "oslib/osbyte.h" #include "oslib/osfscontrol.h" #include "oslib/wimp.h" #include "oslib/wimpspriteop.h" --- 2,19 ---- /* A Squeak VM for Acorn RiscOS machines by Tim Rowledge */ /* ti...@su... & http://sumeru.stanford.edu/tim */ ! /* Known to work on RiscOS >3.7 for StrongARM RPCs and Iyonix, */ ! /* other machines not yet tested. */ ! /* sqRPCClipboard.c */ ! /* hook up to RiscOS clipboard stuff */ /**************************************************************************/ /* To recompile this reliably you will need */ ! /* OSLib - http://ro-oslib.sourceforge.net/ */ ! /* Castle/AcornC/C++, the Acorn TCPIPLib */ /* and a little luck */ #include "oslib/os.h" #include "oslib/osbyte.h" #include "oslib/osfscontrol.h" + #include "oslib/osfile.h" #include "oslib/wimp.h" #include "oslib/wimpspriteop.h" *************** *** 24,268 **** // CBDEBUG is for printfs related to the clipboard stuff #define CBDEBUG 0 ! extern wimp_t Task_Handle; ! extern wimp_w sqWindowHandle; ! int sqHasInputFocus = false; ! int sqHasClipboard = false; ! void claimCaret(wimp_pointer * wblock); void ClaimEntity( int flags) { wimp_message wmessage; ! // broadcast the Message_ClaimEntity using the flags value to decide whether it is a claim of the caret or the clipboard or both ! // Message_ClaimEntity (15)<BR> ! // 0 message size (24)<BR> ! // 4 task handle of task making the claim ! // 8 message id<BR> ! // 12 your_ref (0)<BR> ! // 16 Message_ClaimEntity<BR> ! // 20 flags:<BR> ! // <PRE> ! // bits 0 and 1 set => caret or selection being claimed ! // bit 2 set => clipboard being claimed ! // all other bits reserved (must be 0) ! // </PRE> ! // ! // <p> ! // This message should be broadcast to all tasks as the caret / selection or ! // clipboard are claimed. ! // When claiming the input focus or clipboard, a task should check to see if it ! // already owns that entity, and if so, there is no need to issue the broadcast. ! // It should then take care of updating the caret / selection / clipboard to the ! // new value (updating the display in the case of the selection). wmessage.size = 24; ! wmessage.sender = Task_Handle; ! wmessage.my_ref = (int)Task_Handle; // some better message id ?? wmessage.your_ref = 0; wmessage.action = message_CLAIM_ENTITY; wmessage.data.claim_entity.flags = (wimp_claim_flags)flags; xwimp_send_message(wimp_USER_MESSAGE, &wmessage, wimp_BROADCAST); ! if(CBDEBUG) { printf("ClaimEntity sent message with flags %x\n", flags); if (sqHasInputFocus) printf("has focus "); if (sqHasClipboard) printf("has clipboard\n"); ! } } void claimCaret(wimp_pointer * wblock) { ! #define flagsForClaimingInputFocus 0x03 ! // claim the input focus if I dont already have it if (!sqHasInputFocus) { ! ClaimEntity( flagsForClaimingInputFocus); sqHasInputFocus = true; } - // When the user positions the caret or makes a selection, the application - // should claim ownership of the input focus by broadcasting this message with - // bits 0 and 1 set. When positioning the caret, the application can choose - // whether to use the Wimp's caret or draw its own representation of the caret - // more appropriate to the type of data being edited. When making a selection, - // the application must hide the caret; it should do this by setting the Wimp's - // caret to the window containing the selection, but invisible. This is - // necessary to direct keystroke events to this window. } void claimClipboard(void) { ! #define flagsForClaimingClipboard 0x04 ! // claim the clipboard if I dont already have it if (!sqHasClipboard ) { ! ClaimEntity( flagsForClaimingClipboard); sqHasClipboard = true; } - // When the user performs a Cut or Copy operation, the application should claim - // ownership of the clipboard by broadcasting this message with bit 2 set. - } void receivedClaimEntity(wimp_message * wblock) { ! // When a task receives this message with bits 0 or 1 set, it should check to ! // see if any of its windows currently own the input focus. If so, it should ! // update its flag to indicate that it no longer has the focus, and remove any ! // representation of the caret which it has drawn (unless it uses the Wimp ! // caret, which will be undrawn automatically.) It may optionally alter the ! // appearance of its window to emphasize the fact that it does not have the ! // input focus, for example by shading the selection. A task that receives ! // Message_ClaimEntity with only one of bits 0 and 1 set should act as if both ! // bits were set. ! ! // When a task receives this message with bit 2 set it should set a flag to ! // indicate that the clipboard is held by another application and deallocate the ! // memory being used to store the clipboard contents. ! if(CBDEBUG) { ! printf("receivedClaimEntity with flags %x\n", wblock->data.claim_entity.flags); if (sqHasInputFocus) printf("has focus "); if (sqHasClipboard) printf("has clipboard\n"); ! } ! if ( (wblock->data.claim_entity.flags & flagsForClaimingInputFocus) > 0 ) { sqHasInputFocus = false; } ! if ( wblock->data.claim_entity.flags == flagsForClaimingClipboard) { sqHasClipboard = false; } ! if(CBDEBUG) { ! printf("post claim entity sq now "); if (sqHasInputFocus) printf("has focus "); if (sqHasClipboard) printf("has clipboard\n"); ! } } ! void fetchClipboard(void) { ! // fetch the clipboard from the current owner ! // send a data request, put the returned clipboard text into the buffer etc. ! if(CBDEBUG) { ! printf("fetchClipboard "); ! if (sqHasInputFocus) printf("has focus "); ! if (sqHasClipboard) printf("has clipboard\n"); } ! // we can't fetch the outside clipboard yet, so fake it ! sqHasClipboard = true; ! clipboardSize(); } ! void sendDataRequest(void) { ! // Paste related fetching of clipboard text ! // ! // <p> ! // The application should first check to see if it owns the clipboard, and use ! // the data directly if so. If is does not own it, it should broadcast the ! // following message: ! // ! // <p> ! // Message_DataRequest (16)<BR> ! // 0 message size<BR> ! // 4 task handle of task requesting data ! // 8 message id<BR> ! // 12 your_ref (0)<BR> ! // 16 Message_DataRequest<BR> ! // 20 window handle<BR> ! // 24 internal handle to indicate destination of data ! // 28 x<BR> ! // 32 y<BR> ! // 36 flags:<BR> ! // <PRE> ! // bit 2 set => send data from clipboard (must be 1) ! // all other bits reserved (must be 0) ! // </PRE> ! // 40 list of filetypes in order of preference, ! // <PRE> ! // terminated by -1 ! // </PRE> ! // ! // <p> ! // The sender must set flags bit 2, and the receiver must check this bit, and ! // ignore the message if it is not set. All other flags bits must be cleared by ! // the sender and ignored by the receiver. ! wimp_message wmessage; ! if(CBDEBUG) { ! printf("sendDataRequest "); ! if (sqHasInputFocus) printf("has focus "); ! if (sqHasClipboard) printf("has clipboard\n"); } ! wmessage.size = 0; ! wmessage.sender = Task_Handle; ! wmessage.my_ref = (int)Task_Handle; // some better message id ?? ! wmessage.your_ref = 0; ! wmessage.action = message_DATA_REQUEST; ! wmessage.data.data_request.w = sqWindowHandle; ! wmessage.data.data_request.i = wimp_ICON_WINDOW; ! wmessage.data.data_request.pos.x = 0; ! wmessage.data.data_request.pos.y = 0; ! wmessage.data.data_request.flags = 0x04; ! // fill in filetypes somehow ! wmessage.data.data_request.file_types[0] = 0xFFF; //TEXT ! wmessage.data.data_request.file_types[1] = 0xFFD; // DATA ! wmessage.data.data_request.file_types[2] = -1; ! xwimp_send_message(wimp_USER_MESSAGE, &wmessage, wimp_BROADCAST); } void receivedDataRequest(wimp_message * wmessage) { ! if ( sqHasClipboard ) { ! // somebody requested data & I have the clipboard ! // If an application receiving this message owns the clipboard, it should choose ! // the earliest filetype in the list that it can provide, and if none are ! // possible it should provide the data its original (native) format. Note that ! // the list can be null, to indicate that the native data should be sent. ! // check the filetype list. My native format is text for this purpose ! if(CBDEBUG) { printf("receivedDataRequest "); if (sqHasInputFocus) printf("has focus "); if (sqHasClipboard) printf("has clipboard\n"); ! } ! ! // loop until filetype is -1 or we find TEXT ! // (- types are 'bits' which is unsigned int) in a list up to 54 words long. ! // since I will only handle text, and I am using it as native format, I can skip ! // this test. It would always suceed! ! ! // It ! // should reply using the normal Message_DataSave protocol. Bytes 20 through 35 ! // of the DataSave block should be copied directly from the corresponding bytes ! // of the Message_DataRequest block, whilst the estimated size field, filetype ! // and filename must be filled in. ! //make up a datasave block ! //send the data save message ! //sendDataSave(dsblock); ! // <p> ! // If your application needs to find out whether there is data available to ! // paste, but does not actually want to receive the data, you should broadcast ! // a Message_DataRequest as described above. If no task replies (i.e. you get ! // the message back) then there is no clipboard data available. If a ! // Message_DataSave is received, then you should ignore it (fail to reply), ! // which will cause the operation to be silently aborted by the other task. You ! // can then use the filetype field of the Message_DataSave to determine whether ! // the data being offered by the other task is in a suitable format for you to ! // receive. ! } ! // what to do if I don't have the clipboard? No reply? } ! void receivedDataSave(wimp_message * wblock) { ! // ! // <p> ! // When the application that initiated the Paste receives the Message_DataSave, ! // it should check the filetype to ensure that it knows how to deal with it - it ! // may be the clipboard owner's native format. If it cannot, it may back out of ! // the transaction by ignoring the message. Otherwise, it should continue with ! // the DataSave protocol as detailed in the Programmer's Reference Manual. ! // check the filetype - only deal with text for now. What others might be useful ? ! // Do the data save protocols to get the clipboard text ! // ! if(CBDEBUG) { ! printf("receivedDataSave "); if (sqHasInputFocus) printf("has focus "); if (sqHasClipboard) printf("has clipboard\n"); } ! } --- 25,405 ---- // CBDEBUG is for printfs related to the clipboard stuff #define CBDEBUG 0 ! int sqHasInputFocus = false; ! int sqHasClipboard = false; ! char * clipboardBuffer = NULL; ! int clipboardByteSize = 0; ! int clipboardMessageID = 0; ! int allocClipboard(size_t size); ! ! /* caret (input focus) and clipboard claiming functions */ void ClaimEntity( int flags) { wimp_message wmessage; ! /* broadcast the Message_ClaimEntity using the flags value to decide whether ! * it is a claim of the caret or the clipboard (or both?) ! * When claiming the input focus or clipboard, a task should check to see if ! * it already owns that entity, and if so, there is no need to issue the ! * broadcast. ! * It should then take care of updating the caret / selection / clipboard ! * to the new value (updating the display in the case of the selection). ! */ wmessage.size = 24; ! wmessage.sender = (wimp_t)NULL; ! wmessage.my_ref = 0; wmessage.your_ref = 0; wmessage.action = message_CLAIM_ENTITY; wmessage.data.claim_entity.flags = (wimp_claim_flags)flags; xwimp_send_message(wimp_USER_MESSAGE, &wmessage, wimp_BROADCAST); ! #if CBDEBUG printf("ClaimEntity sent message with flags %x\n", flags); if (sqHasInputFocus) printf("has focus "); if (sqHasClipboard) printf("has clipboard\n"); ! #endif } void claimCaret(wimp_pointer * wblock) { ! /* claim the input focus if I dont already have it */ if (!sqHasInputFocus) { ! ClaimEntity( wimp_CLAIM_CARET_OR_SELECTION); sqHasInputFocus = true; } } void claimClipboard(void) { ! /* claim the clipboard if I dont already have it */ if (!sqHasClipboard ) { ! ClaimEntity( wimp_CLAIM_CLIPBOARD); sqHasClipboard = true; } } void receivedClaimEntity(wimp_message * wblock) { ! /* When a task receives this message with bits 0 or 1 set, it should check ! *to see if any of its windows currently own the input focus. If so, it ! * should update its flag to indicate that it no longer has the focus, and ! * remove any representation of the caret which it has drawn (unless it uses ! * the Wimp caret, which will be undrawn automatically.) It may optionally ! * alter the appearance of its window to emphasize the fact that it does not ! * have the input focus, for example by shading the selection. A task that ! * receives Message_ClaimEntity with only one of bits 0 and 1 set should act ! * as if both bits were set. ! * ! * When a task receives this message with bit 2 set it should set a flag to ! * indicate that the clipboard is held by another application and deallocate ! * the memory being used to store the clipboard contents. ! */ ! #if CBDEBUG ! printf("receivedClaimEntity with flags %x\n", ! wblock->data.claim_entity.flags); if (sqHasInputFocus) printf("has focus "); if (sqHasClipboard) printf("has clipboard\n"); ! #endif ! if ( (wblock->data.claim_entity.flags ! & wimp_CLAIM_CARET_OR_SELECTION) > 0 ) { sqHasInputFocus = false; } ! if ( wblock->data.claim_entity.flags == wimp_CLAIM_CLIPBOARD) { sqHasClipboard = false; + allocClipboard(1); } ! #if CBDEBUG ! printf("post claim entity sq now "); if (sqHasInputFocus) printf("has focus "); if (sqHasClipboard) printf("has clipboard\n"); ! #endif } ! /* clipboard buffer management */ ! int allocClipboard(size_t size) { ! void * ptr; ! ptr = realloc(clipboardBuffer, size); ! if( ptr == NULL) { ! /* failed to reallocate but old buffer is stil in place ! * so remember to clear it ! */ ! memset(clipboardBuffer,0, (size_t)clipboardByteSize); ! return false; } ! clipboardBuffer = ptr; ! clipboardByteSize = (int)size; ! memset(clipboardBuffer,0, (size_t)clipboardByteSize); ! return true; ! } ! ! void freeClipboard(void) { ! free(clipboardBuffer); ! clipboardBuffer = NULL; ! clipboardByteSize = 0; } + + /* clipboard fetching - we don't own the clipboard and do want the contents */ ! void sendDataRequest(wimp_message* wmessage) { ! /* We want to fetch the clipboard contents from some other application ! * Broadcast the message_DATA_REQUEST message ! */ ! extern wimp_w sqWindowHandle; ! #if CBDEBUG ! printf("sendDataRequest "); ! if (sqHasInputFocus) printf("has focus "); ! if (sqHasClipboard) printf("has clipboard\n"); ! #endif ! wmessage->size = 52; ! wmessage->sender = (wimp_t)NULL; ! wmessage->my_ref = 0; ! wmessage->your_ref = 0; ! wmessage->action = message_DATA_REQUEST; ! wmessage->data.data_request.w = sqWindowHandle; ! wmessage->data.data_request.i = wimp_ICON_WINDOW; ! wmessage->data.data_request.pos.x = 0; ! wmessage->data.data_request.pos.y = 0; ! wmessage->data.data_request.flags = 0x04; // request clipboard ! wmessage->data.data_request.file_types[0] = 0xFFF; //TEXT ! wmessage->data.data_request.file_types[1] = 0xFFD; // DATA ! wmessage->data.data_request.file_types[2] = -1; ! xwimp_send_message(wimp_USER_MESSAGE, wmessage, wimp_BROADCAST); ! clipboardMessageID = wmessage->my_ref; ! } ! ! ! int receivedClipboardDataSave(wimp_message * wmessage) { ! /* When the application that initiated the Paste receives the ! * Message_DataSave, it should check the filetype to ensure that it ! * knows how to deal with it - it may be the clipboard owner's native ! * format. If it cannot, it may back out of the transaction by ignoring ! * the message. Otherwise, it should continue with the DataSave ! * protocol as detailed in the Programmer's Reference Manual. ! */ ! #if CBDEBUG ! printf("receivedClipboardDataSave "); ! if (sqHasInputFocus) printf("has focus "); ! if (sqHasClipboard) printf("has clipboard\n"); ! #endif ! if(wmessage->data.data_xfer.file_type != (bits)0xfff) { ! /* if not text type, empty clipboard buffer & return */ ! memset(clipboardBuffer,0, (size_t)clipboardByteSize); ! return false; } + /* We modify the received block and return to sender */ + wmessage->size = 60; + wmessage->action = message_DATA_SAVE_ACK; + wmessage->your_ref = wmessage->my_ref; + wmessage->data.data_xfer.est_size = -1; + wmessage->data.data_xfer.file_type = (bits)0xfff; + strcpy(&(wmessage->data.data_xfer.file_name[0]), "<Wimp$Scrap>"); + xwimp_send_message(wimp_USER_MESSAGE, wmessage, wmessage->sender); + return true; + } + void receivedClipboardDataLoad(wimp_message * wmessage) { + /* we got a dataload message, so grab the <Wimp$Scrap> file, then delete it + * and return a dataloadack to the sender + */ + bits load_addr, exec_addr, file_type; + fileswitch_attr attr; + fileswitch_object_type obj_type; + int length; + #if CBDEBUG + printf("receivedClipboardDataLoad "); + if (sqHasInputFocus) printf("has focus "); + if (sqHasClipboard) printf("has clipboard\n"); + #endif + /* find the file size */ + xosfile_read_stamped_no_path(&(wmessage->data.data_xfer.file_name[0]), + &obj_type, &load_addr, &exec_addr, &length, &attr, &file_type); + /* if the obj_type is not-found, clear the buffer and return */ + if(obj_type == fileswitch_NOT_FOUND) { + allocClipboard(1); + return; + } + /* make sure we have enough buffer space for it + * fail if not */ + if(!allocClipboard(length+1)) + return; + /* now load the file */ + xosfile_load_stamped_no_path(&(wmessage->data.data_xfer.file_name[0]), (byte*)clipboardBuffer, &obj_type, + &load_addr, &exec_addr, &length, &attr); + /* delete the file */ + xosfscontrol_wipe(&(wmessage->data.data_xfer.file_name[0]), osfscontrol_WIPE_FORCE, 0,0,0,0); + /* We modify the received block and return it to sender */ + wmessage->action = message_DATA_LOAD_ACK; + wmessage->your_ref = wmessage->my_ref; + xwimp_send_message(wimp_USER_MESSAGE, wmessage, wmessage->sender); + } ! int pollForClipboardMessage(bits messageAction, wimp_block* wblock) { ! /* poll for a message relating to the clipboard protocols (either datasave or ! * dataload usually) and return true if one is found or false if we either get ! * a null or go round more than a few times (avoid loop-of-death) ! */ ! wimp_event_no reason; ! int pollword, i; ! extern void WindowOpen(wimp_open* wblock); ! extern void WindowClose(wimp_close* wblock); ! extern void PointerLeaveWindow(wimp_block* wblock); ! extern void PointerEnterWindow(wimp_block* wblock); ! for(i=0;i<100;i++) { ! xwimp_poll((wimp_MASK_POLLWORD| wimp_MASK_GAIN | wimp_MASK_LOSE ! | wimp_SAVE_FP | wimp_QUEUE_REDRAW | wimp_QUEUE_MOUSE | wimp_QUEUE_KEY), wblock, &pollword, &reason); ! switch(reason) { ! case wimp_NULL_REASON_CODE: ! return false; break; ! case wimp_OPEN_WINDOW_REQUEST : ! WindowOpen(&wblock->open); break; ! case wimp_CLOSE_WINDOW_REQUEST : ! WindowClose(&wblock->close); break; ! case wimp_POINTER_LEAVING_WINDOW : ! PointerLeaveWindow(wblock); break; ! case wimp_POINTER_ENTERING_WINDOW: ! PointerEnterWindow(wblock); break; ! case wimp_USER_MESSAGE : ! case wimp_USER_MESSAGE_RECORDED : ! if( wblock->message.action == messageAction) ! return true; break; ! } ! } ! return false; ! } + void fetchClipboard(void) { + /* fetch the clipboard from the current owner */ + wimp_block wblock; + #if CBDEBUG + printf("fetchClipboard "); + if (sqHasInputFocus) printf("has focus "); + if (sqHasClipboard) printf("has clipboard\n"); + #endif + /* ask for the clipboard contents */ + sendDataRequest(&wblock.message); + if( !pollForClipboardMessage(message_DATA_SAVE, &wblock)) + /* didn't get any reply, so return empty */ + return ; + if( !receivedClipboardDataSave(&wblock.message)) + return; /* no acceptable filetype, so give up */ + if( !pollForClipboardMessage(message_DATA_LOAD, &wblock)) + /* didn't get any reply, so return empty */ + return; + receivedClipboardDataLoad(&wblock.message); + return; } + /* clipboard serving - what to do when we own the clipboard and somebody + * else wants the contents + */ void receivedDataRequest(wimp_message * wmessage) { ! if ( !sqHasClipboard ) return; ! ! /* somebody requested data & I have the clipboard ! * If an application receiving this message owns the clipboard, ! * it should choose the earliest filetype in the list that it ! * can provide, and if none are possible it should provide the ! * data its original (native) format. Note that the list can be ! * null, to indicate that the native data should be sent. ! */ ! #if CBDEBUG printf("receivedDataRequest "); if (sqHasInputFocus) printf("has focus "); if (sqHasClipboard) printf("has clipboard\n"); ! #endif ! /* reply using the normal Message_DataSave protocol. ! * Bytes 20 through 35 of the DataSave block should be copied directly ! * from the corresponding bytes of the Message_DataRequest block, ! * whilst the estimated size field, filetype and filename must be ! * filled in. ! */ ! /* We modify the received block and return to sender */ ! wmessage->size = 52; ! wmessage->action = message_DATA_SAVE; ! wmessage->your_ref = wmessage->my_ref; ! wmessage->data.data_xfer.est_size = strlen(clipboardBuffer); ! wmessage->data.data_xfer.file_type = (bits) 0xfff; ! strcpy(&(wmessage->data.data_xfer.file_name[0]), "SqClip"); ! xwimp_send_message(wimp_USER_MESSAGE, wmessage, wmessage->sender); } ! ! void receivedDataSaveAck(wimp_message * wmessage) { ! /* we've been asked to save the clipboard contents to the wimpScrap */ ! #if CBDEBUG ! printf("receivedDataSaveAck "); if (sqHasInputFocus) printf("has focus "); if (sqHasClipboard) printf("has clipboard\n"); + #endif + osfile_save_stamped(&(wmessage->data.data_xfer.file_name[0]), + (bits)0xfff, (byte const *)clipboardBuffer, + (byte const *)(clipboardBuffer + + strlen(clipboardBuffer))); + /* modify the block to be a data load message and return to sender */ + wmessage->action = message_DATA_LOAD; + wmessage->your_ref = wmessage->my_ref; + wmessage->data.data_xfer.est_size = strlen(clipboardBuffer); + xwimp_send_message(wimp_USER_MESSAGE, wmessage, wmessage->sender); + } + + /*** Clipboard Support interface to interp.c ***/ + + int clipboardSize(void) { + /* return the number of characters in the clipboard entry */ + if (!sqHasClipboard) { + /* if squeak doesn't have the clipboard, we need to + * fetch the clipboard contents from the current holder + */ + fetchClipboard(); + } + return strlen(clipboardBuffer); + } + + int clipboardReadIntoAt(int count, int byteArrayIndex, int startIndex) { + // paste - clipboardSize() will actually do any fetching + int clipSize, charsToMove, i; + char *srcPtr, *dstPtr, cc; + clipSize = strlen(clipboardBuffer); + charsToMove = (count < clipSize) ? count : clipSize; + + srcPtr = (char *) clipboardBuffer; + dstPtr = (char *) byteArrayIndex + startIndex; + for (i = 0; i < charsToMove; i++, srcPtr++, dstPtr++) { + *dstPtr = cc = *srcPtr; + /* swap CR/LF */ + if( cc == (char)10) *dstPtr = (char)13; + if( cc == (char)13) *dstPtr = (char)10; } ! ! return charsToMove; } + int clipboardWriteFromAt(int count, int byteArrayIndex, int startIndex) { + /* copy count bytes, starting from startIndex, from byteArrayIndex to the + * clipboard. return value not (yet) used but send the number of chars moved + * the prim code has no way to handle any failure as yet, so do our best + */ + int charsToMove, i; + char *srcPtr, *dstPtr, cc; + + /* buffer size must be at least 1 more than count to allow for + * terminating \0. Realloc if needed and then recheck size + */ + allocClipboard(count + 1); + charsToMove = (count < clipboardByteSize) ? count : clipboardByteSize-1; + + srcPtr = (char *) byteArrayIndex + startIndex; + dstPtr = (char *) clipboardBuffer; + for (i = 0; i < charsToMove; i++, srcPtr++, dstPtr++) { + *dstPtr = cc = *srcPtr; + /* swap CR/LF */ + if( cc == (char)10) *dstPtr = (char)13; + if( cc == (char)13) *dstPtr = (char)10; + } + *dstPtr = (char)NULL; + + claimClipboard(); + + return charsToMove; + } Index: sqRPCEvents.c =================================================================== RCS file: /cvsroot/squeak/squeak/platforms/RiscOS/vm/sqRPCEvents.c,v retrieving revision 1.4 retrieving revision 1.5 diff -C2 -d -r1.4 -r1.5 *** sqRPCEvents.c 4 Feb 2003 21:10:21 -0000 1.4 --- sqRPCEvents.c 9 May 2003 01:07:16 -0000 1.5 *************** *** 2,14 **** /* A Squeak VM for Acorn RiscOS machines by Tim Rowledge */ /* ti...@su... & http://sumeru.stanford.edu/tim */ ! /* Known to work on RiscOS 3.7 for StrongARM RPCs, other machines */ ! /* not yet tested. */ ! /* sqRPCEvents.c */ /* OS interface stuff */ /**************************************************************************/ /* To recompile this reliably you will need */ ! /* Jonathon Coxhead's OSLib, */ ! /* AcornC_C++, the Acorn sockets libs */ /* and a little luck */ #include "oslib/os.h" --- 2,14 ---- /* A Squeak VM for Acorn RiscOS machines by Tim Rowledge */ /* ti...@su... & http://sumeru.stanford.edu/tim */ ! /* Known to work on RiscOS >3.7 for StrongARM RPCs and Iyonix, */ ! /* other machines not yet tested. */ ! /* sqRPCEvents.c */ /* OS interface stuff */ /**************************************************************************/ /* To recompile this reliably you will need */ ! /* OSLib - http://ro-oslib.sourceforge.net/ */ ! /* Castle/AcornC/C++, the Acorn TCPIPLib */ /* and a little luck */ #include "oslib/os.h" *************** *** 37,68 **** /*** Variables -- Event Recording ***/ ! // TPR ultra simplistic event queue stuff ! /* For now events will all be 5 words - ! event type ! mouse x ! mouse y ! button state ! keypress ! so that it is easy to handle the circular buffer. ! When an event is pulled, the keyBuf will be flushed, to hopefully avoid ! the blast of chars when moving away from a Morphic window. ! When a keyBuf entry is pulled, the event Q will likewise be flushed */ #define EVENTQ_SIZE 1024 ! struct SQEvent { ! int type; ! int mx; ! int my; ! int b; ! int k; ! }; ! struct SQEvent eventBuf[EVENTQ_SIZE ]; /* circular buffer */ int eventBufGet = 0; int eventBufPut = 0; - #define SQ_KEYPRESS 1 - #define SQ_MOUSE_DOWN 2 - #define SQ_MOUSE_UP 3 - #define SQ_MOUSE_MOVE 4 - #define KEYBUF_SIZE 64 int keyBuf[KEYBUF_SIZE]; /* circular buffer */ --- 37,47 ---- /*** Variables -- Event Recording ***/ ! int inputSemaphoreIndex = 0; #define EVENTQ_SIZE 1024 ! sqInputEvent eventBuf[EVENTQ_SIZE ]; /* circular buffer */ int eventBufGet = 0; int eventBufPut = 0; + /* older polling stuff still needs supporting */ #define KEYBUF_SIZE 64 int keyBuf[KEYBUF_SIZE]; /* circular buffer */ *************** *** 251,254 **** --- 230,234 ---- extern void receivedDataRequest(wimp_message * wmessage); extern void receivedDataSave(wimp_message * wblock); + extern void receivedDataSaveAck(wimp_message * wblock); void eventBufAppendKey( int key, int buttons, int x, int y); void eventBufAppendMouseDown(int buttons, int x, int y); *************** *** 280,284 **** pollDelay = microSecondsToDelay /* * CLOCKS_PER_SEC / 1000000 */ ! >> 14 /* will always give small answer, but good enough */; if ( mouseButtonDown | windowActive) { /* if the window is active or mouse buttons are supposedly down, */ --- 260,264 ---- pollDelay = microSecondsToDelay /* * CLOCKS_PER_SEC / 1000000 */ ! >> 14 /* will always give small answer, but good enough */; if ( mouseButtonDown | windowActive) { /* if the window is active or mouse buttons are supposedly down, */ *************** *** 347,355 **** case wimp_SCROLL_REQUEST : DoNothing(); break; - // dont use gain/lose when using clipboard protocols - //case wimp_LOSE_CARET : - // DeactivateWindow(&wimpPollBlock); break; - //case wimp_GAIN_CARET : - // ActivateWindow(&wimpPollBlock); break; case wimp_USER_MESSAGE : UserMessage(&wimpPollBlock.message); break; --- 327,330 ---- *************** *** 689,703 **** void KeyPressed( wimp_key * wblock) { ! /* deal with a keypress. This is complicated by the RiscOS habit of "helpfully" cinverting keycodes into fully processed key events. We do not even get notification of most alt presses, for example. We also have to convert to Mac numbering in order to satisfy the image code */ int keystate, testkey; ! // basically keystate will be the event idea of the key pressed keystate = wblock->c; if (keystate == getInterruptKeycode() || ( (keystate == wimp_KEY_PRINT)) ) { ! // The image tends to set the interruptKeycode to suit the Mac cmd-. nonsense ! // this is decidedly not Acorn compatible, so check for printscrn/SysRq as well ! // interrupt is a meta-event; do not report it as a keypress setInterruptPending(true); setInterruptCheckCounter(0); --- 664,684 ---- void KeyPressed( wimp_key * wblock) { ! /* deal with a keypress. This is complicated by the RiscOS habit of "helpfully" ! * converting keycodes into fully processed key events. We do not even get ! * notification of most alt presses, for example. We also have to convert to ! * Mac numbering in order to satisfy the image code ! */ int keystate, testkey; ! /* basically keystate will be the event idea of the key pressed */ keystate = wblock->c; if (keystate == getInterruptKeycode() || ( (keystate == wimp_KEY_PRINT)) ) { ! /* The image tends to set the interruptKeycode to suit the Mac ! * cmd-. nonsense this is decidedly not Acorn compatible, so ! * check for printscrn/SysRq as well ! * interrupt is a meta-event; do not report it as a keypress ! */ setInterruptPending(true); setInterruptCheckCounter(0); *************** *** 706,716 **** if ( buttonState & 0x70) { ! // if a metakey is pressed, try looking up the magic number and dealing with a metakey situation xosbyte1(osbyte_SCAN_KEYBOARD_LIMITED , 0, 0, &testkey); ! // if a key is scanned ok and it maps, replace the keystate with the result if ( (testkey != 0xFF) && (testkey = keymap[testkey]) ) keystate = testkey; } else { ! // no metakey, so check for special key values. switch(keystate) { case wimp_KEY_TAB: keystate = 0x09; break; --- 687,701 ---- if ( buttonState & 0x70) { ! /* if a metakey is pressed, try looking up the magic number ! * and dealing with a metakey situation ! */ xosbyte1(osbyte_SCAN_KEYBOARD_LIMITED , 0, 0, &testkey); ! /* if a key is scanned ok and it maps, replace the keystate ! * with the result ! */ if ( (testkey != 0xFF) && (testkey = keymap[testkey]) ) keystate = testkey; } else { ! /* no metakey, so check for special key values. */ switch(keystate) { case wimp_KEY_TAB: keystate = 0x09; break; *************** *** 729,781 **** } ! void keyBufAppend(int keystate) { ! keyBuf[keyBufPut] = keystate; ! keyBufPut = (keyBufPut + 1) % KEYBUF_SIZE; ! if (keyBufGet == keyBufPut) { ! keyBufGet = (keyBufGet + 1) % KEYBUF_SIZE; ! keyBufOverflows++; ! } } ! void eventBufAppendEvent(int type, int mouseX, int mouseY, int buttons, int key) { ! /* append an event to the queue. DO NOT signal the input semaphore here since the ! * HandleEvents() routine is called from place where that causes segfaults!! ! * Leave the signalling to the ioEventsCount() routine. ! */ ! int peek; ! /* first check there is room on the queue */ ! peek = (eventBufPut + 1) % EVENTQ_SIZE; ! if ( peek == eventBufGet) {/* no room, drop the whole thing */ ! return; ! } ! /* now add the event to the queue - */ ! ! /* if the previous event is still on the q and was a mouse move, just overwrite it */ ! if ( (type == SQ_MOUSE_MOVE) && (eventBufPut != eventBufGet)) { ! int prevEvent; ! prevEvent = eventBufPut -1; ! if ( prevEvent == -1) ! prevEvent = EVENTQ_SIZE -1 ; /* wrap around */ ! if ( eventBuf[prevEvent].type == SQ_MOUSE_MOVE ) { ! /* overwrite previous event data */ ! eventBuf[eventBufPut].type = type; ! eventBuf[eventBufPut].mx = mouseX; ! eventBuf[eventBufPut].my = mouseY; ! eventBuf[eventBufPut].b = buttons; ! eventBuf[eventBufPut].k = key; ! return; ! } ! } ! eventBuf[eventBufPut].type = type; ! eventBuf[eventBufPut].mx = mouseX; ! eventBuf[eventBufPut].my = mouseY; ! eventBuf[eventBufPut].b = buttons; ! /* the key value NOT the 12bit keystate! */ ! eventBuf[eventBufPut].k = key; ! /* finally advance the eventBufPut pointer */ ! eventBufPut = peek; } --- 714,749 ---- } ! /* set an asynchronous input semaphore index for events */ ! int ioSetInputSemaphore(int semaIndex) { ! if( semaIndex < 1) ! return primitiveFail(); ! inputSemaphoreIndex = semaIndex; ! return true; } ! void signalInputEvent(void) { ! if(inputSemaphoreIndex > 0) ! signalSemaphoreWithIndex(inputSemaphoreIndex); ! } ! /* Event buffer functions */ ! #define iebEmptyP() (eventBufPut == eventBufGet) ! #define iebAdvance(P) (P= ((P + 1) % EVENTQ_SIZE)) + sqInputEvent *eventBufAppendEvent(int type) { + /* code stolen from ikp's unix code. blame him if it doesn't work. + * complement me if it does. + */ + sqInputEvent *evt= &eventBuf[eventBufPut]; + iebAdvance(eventBufPut); + if (iebEmptyP()) { + /* overrun: discard oldest event */ + iebAdvance(eventBufGet); + } + evt->type= type; + evt->timeStamp= ioMSecs(); + signalInputEvent(); + return evt; } *************** *** 784,834 **** /* add an event record for a keypress */ ! eventBufAppendEvent( SQ_KEYPRESS, x, y, buttons, keyValue); } void eventBufAppendMouseDown( int buttons, int x, int y) { /* add an event record for a mouse press */ ! eventBufAppendEvent( SQ_MOUSE_DOWN, x, y, buttons, 0); } void eventBufAppendMouseUp( int buttons, int x, int y) { /* add an event record for a mouse up */ ! eventBufAppendEvent( SQ_MOUSE_UP, x, y, buttons, 0); } void eventBufAppendMouseMove( int x, int y) { /* add an event record for a mouse up */ ! eventBufAppendEvent( SQ_MOUSE_MOVE, x, y, buttonState, 0); } - int ioLoadNextEvent( int arrayPtr) { - /* fill the array with - * event type - * mouse pos x - * mouse pos y - * button state - * keypress - */ - extern int nilObject (void); - if ( eventBufGet == eventBufPut ) { - /* no events left to fetch, so put nil in at least the type slot of the array*/ - ((int*)arrayPtr)[0] = nilObject(); - ((int*)arrayPtr)[1] = nilObject(); - ((int*)arrayPtr)[2] = nilObject(); - ((int*)arrayPtr)[3] = nilObject(); - ((int*)arrayPtr)[4] = nilObject(); - return false; - } - #define INT_OBJ(val) (((val) <<1) | 1) - ((int*)arrayPtr)[0] = INT_OBJ(eventBuf[eventBufGet].type); - ((int*)arrayPtr)[1] = INT_OBJ(eventBuf[eventBufGet].mx); - ((int*)arrayPtr)[2] = INT_OBJ(eventBuf[eventBufGet].my); - ((int*)arrayPtr)[3] = INT_OBJ(eventBuf[eventBufGet].b); - ((int*)arrayPtr)[4] = INT_OBJ(eventBuf[eventBufGet].k); ! eventBufGet = (eventBufGet+1) % EVENTQ_SIZE; ! return true; } int nextKeyPressOrNil(void) { --- 752,790 ---- /* add an event record for a keypress */ ! eventBufAppendEvent( EventTypeKeyboard); } void eventBufAppendMouseDown( int buttons, int x, int y) { /* add an event record for a mouse press */ ! eventBufAppendEvent( EventTypeMouse); } void eventBufAppendMouseUp( int buttons, int x, int y) { /* add an event record for a mouse up */ ! eventBufAppendEvent( EventTypeMouse); } void eventBufAppendMouseMove( int x, int y) { /* add an event record for a mouse up */ ! eventBufAppendEvent( EventTypeMouse); } ! ! /* retrieve the next input event from the OS */ ! int ioGetNextEvent(sqInputEvent *evt) { ! HandleEvents(0); ! primitiveFail(); } + /* key buffer functions to support older images */ + void keyBufAppend(int keystate) { + keyBuf[keyBufPut] = keystate; + keyBufPut = (keyBufPut + 1) % KEYBUF_SIZE; + if (keyBufGet == keyBufPut) { + keyBufGet = (keyBufGet + 1) % KEYBUF_SIZE; + keyBufOverflows++; + } + } int nextKeyPressOrNil(void) { *************** *** 854,860 **** return keystate; } void UserMessage(wimp_message * wblock) { ! /* Deal with user messages; only Quit and MODE_CHANGE for now */ switch( wblock->action) { case message_QUIT: ioExit(); --- 810,865 ---- return keystate; } + int ioGetButtonState(void) { + ioProcessEvents(); /* process all pending events */ + return buttonState; + } + + int ioGetKeystroke(void) { + ioProcessEvents(); /* process all pending events */ + return nextKeyPressOrNil(); + } + + int ioMousePoint(void) { + /* return the mouse point as 16bits of x | 16bits of y */ + ioProcessEvents(); /* process all pending events */ + return (savedMousePosition.x << 16 | savedMousePosition.y & 0xFFFF); + } + + int ioPeekKeystroke(void) { + ioProcessEvents(); /* process all pending events */ + return peekKeyPressOrNil(); + } + + /*** I/O Primitives ***/ + + int ioProcessEvents(void) { + static clock_t nextPollTick = 0; + clock_t currentTick; + + // if( (currentTick = clock()) >= nextPollTick) { + HandleEvents(0 ); + // nextPollTick = currentTick + 1; + // } + return true; + } + + int ioRelinquishProcessorForMicroseconds(int microSeconds) { + /* This operation is platform dependent. On the Mac, it simply calls + * HandleEvents(), which gives other applications a chance to run. + * Here, we use microSeconds as the parameter to HandleEvents, so that wimpPollIdle + * gets a timeout. + */ + + HandleEvents(microSeconds); + return microSeconds; + } void UserMessage(wimp_message * wblock) { ! /* Deal with user messages */ ! extern wimp_t Task_Handle; ! if( wblock->sender == Task_Handle) { ! /* it's me - do nothing */ ! return; ! } switch( wblock->action) { case message_QUIT: ioExit(); *************** *** 862,872 **** case message_MODE_CHANGE: displayModeChanged(); break; - // add message claimentity, messagedatarequest & messagedatasave handling case message_CLAIM_ENTITY: receivedClaimEntity(wblock); break; case message_DATA_REQUEST: receivedDataRequest(wblock); break; ! case message_DATA_SAVE: receivedDataSave(wblock); ! break; default: return; } --- 867,887 ---- case message_MODE_CHANGE: displayModeChanged(); break; case message_CLAIM_ENTITY: receivedClaimEntity(wblock); break; + /* these are the two messages we respond to in order + * to initiate clipboard transactions + * DATA_REQUEST is another app asking for our clipboard + * and DATA_SAVE_ACK is part of the dance for giving + * it to them. Us asking for some outside clipboard + * can be found in sqRPCCLipboard>fetchClipboard() + */ case message_DATA_REQUEST: receivedDataRequest(wblock); break; ! case message_DATA_SAVE_ACK: receivedDataSaveAck(wblock); ! break; ! /* We _might_ sometime respond to DATA_LOAD & DATA_SAVE ! * here in order to allo dropping of text files via the ! * DropPlugin ! */ default: return; } Index: sqRPCExternalPrims.c =================================================================== RCS file: /cvsroot/squeak/squeak/platforms/RiscOS/vm/sqRPCExternalPrims.c,v retrieving revision 1.4 retrieving revision 1.5 diff -C2 -d -r1.4 -r1.5 *** sqRPCExternalPrims.c 4 Feb 2003 21:10:21 -0000 1.4 --- sqRPCExternalPrims.c 9 May 2003 01:07:16 -0000 1.5 *************** *** 2,10 **** /* A Squeak VM for Acorn RiscOS machines by Tim Rowledge */ /* ti...@su... & http://sumeru.stanford.edu/tim */ ! /* Known to work on RiscOS 3.7 for StrongARM RPCs, other machines */ ! /* not yet tested. */ /* sqRPCExternalPrims.c */ /* hook up to RiscOS external code modules using 'rink' */ /**************************************************************************/ #include "oslib/os.h" #include "sq.h" --- 2,15 ---- /* A Squeak VM for Acorn RiscOS machines by Tim Rowledge */ /* ti...@su... & http://sumeru.stanford.edu/tim */ ! /* Known to work on RiscOS >3.7 for StrongARM RPCs and Iyonix, */ ! /* other machines not yet tested. */ /* sqRPCExternalPrims.c */ /* hook up to RiscOS external code modules using 'rink' */ /**************************************************************************/ + + /* To recompile this reliably you will need */ + /* OSLib - http://ro-oslib.sourceforge.net/ */ + /* Castle/AcornC/C++, the Acorn TCPIPLib */ + /* and a little luck */ #include "oslib/os.h" #include "sq.h" *************** *** 30,34 **** int ioFindExternalFunctionIn(char *symbol, int moduleHandle) { ! // find the function named symbol in the known loaded module moduleHandle int fnIndex= 0, address; const char * foundName; --- 35,39 ---- int ioFindExternalFunctionIn(char *symbol, int moduleHandle) { ! /* find the function named symbol in the known loaded module moduleHandle */ int fnIndex= 0, address; const char * foundName; *************** *** 43,47 **** } ! // failed to find the function... FPRINTF((privateErr.errmess, " did not find: %s", symbol)); return 0; --- 48,52 ---- } ! /* failed to find the function... */ FPRINTF((privateErr.errmess, " did not find: %s", symbol)); return 0; *************** *** 49,54 **** int ioLoadModule(char *modName) { ! // a routine to load a segment(module). Takes a pointer to the name ! // of the directory the code and links files are stored in extern char vmPath[]; const rink_version *Version; --- 54,60 ---- int ioLoadModule(char *modName) { ! /* a routine to load a segment(module). Takes a pointer to the name ! * of the directory the code and links files are stored in ! */ extern char vmPath[]; const rink_version *Version; *************** *** 59,67 **** ! // make filename of the code sprintf(codeName, "%splugins.%s", vmPath, modName); FPRINTF((privateErr.errmess, "Load: %s",modName)); ! // load the segment... if((e = rink_load(&CheckBlock, codeName, &moduleHandle)) != NULL) { FPRINTF((privateErr.errmess, "Plugin load failed: %s", codeName)); --- 65,73 ---- ! /* make filename of the code */ sprintf(codeName, "%splugins.%s", vmPath, modName); FPRINTF((privateErr.errmess, "Load: %s",modName)); ! /* load the segment... */ if((e = rink_load(&CheckBlock, codeName, &moduleHandle)) != NULL) { FPRINTF((privateErr.errmess, "Plugin load failed: %s", codeName)); *************** *** 69,77 **** } ! // OK, let's have a look at the version of the segment we've just loaded. ! // It might be nice to check them to see that it's acceptable. ! // It is a bad plan to alter the returned structure. Version = rink_readversion(moduleHandle); ! // report the version //FPRINTF( (privateErr.errmess, "Plugin version: %d:%d", Version->main, Version->code)); --- 75,84 ---- } ! /* OK, let's have a look at the version of the segment we've just ! * loaded. It might be nice to check them to see that it's acceptable. ! * It is a bad plan to alter the returned structure. ! */ Version = rink_readversion(moduleHandle); ! /* report the version */ //FPRINTF( (privateErr.errmess, "Plugin version: %d:%d", Version->main, Version->code)); Index: sqRPCFormPrint.c =================================================================== RCS file: /cvsroot/squeak/squeak/platforms/RiscOS/vm/sqRPCFormPrint.c,v retrieving revision 1.1.1.1 retrieving revision 1.2 diff -C2 -d -r1.1.1.1 -r1.2 *** sqRPCFormPrint.c 24 Oct 2001 23:14:03 -0000 1.1.1.1 --- sqRPCFormPrint.c 9 May 2003 01:07:16 -0000 1.2 *************** *** 2,11 **** /* A Squeak VM for Acorn RiscOS machines by Tim Rowledge */ /* ti...@su... & http://sumeru.stanford.edu/tim */ ! /* Known to work on RiscOS 3.7 for StrongARM RPCs, other machines */ ! /* not yet tested. */ /* sqRPCFormPrint.c */ /* Print a Form - except we can't do thatright now. Another day maybe */ /**************************************************************************/ #include "sq.h" --- 2,16 ---- /* A Squeak VM for Acorn RiscOS machines by Tim Rowledge */ /* ti...@su... & http://sumeru.stanford.edu/tim */ ! /* Known to work on RiscOS >3.7 for StrongARM RPCs and Iyonix, */ ! /* other machines not yet tested. */ /* sqRPCFormPrint.c */ /* Print a Form - except we can't do thatright now. Another day maybe */ /****************************************... [truncated message content] |