|
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 nativ... [truncated message content] |