Update of /cvsroot/squeak/squeak/platforms/unix/vm
In directory sc8-pr-cvs1:/tmp/cvs-serv18302
Modified Files:
Makefile.in aio.c aio.h dlfcn-dyld.c sqPlatformSpecific.h
sqUnixExternalPrims.c
Added Files:
SqDisplay.h SqModule.h SqSound.h acinclude.m4 debug.c debug.h
feedback.h sqUnixCharConv.c sqUnixCharConv.h sqUnixEvent.c
sqUnixGL.h sqUnixGlobals.h sqUnixMain.c sqUnixMain.h
sqUnixWindow.h
Log Message:
Ian Piumarta's release 3.5-1devel
--- NEW FILE: SqDisplay.h ---
#ifndef __sq_SqDisplay_h
#define __sq_SqDisplay_h
#define USE_VM_STRUCT 1
extern int uxDropFileCount;
extern char **uxDropFileNames;
#define SqDisplayVersionMajor 1
#define SqDisplayVersionMinor 1
#define SqDisplayVersion ((SqDisplayVersionMajor << 16) | (SqDisplayVersionMinor))
#include "sqUnixOpenGL.h"
struct SqDisplay
{
int version;
/* system attributes */
char *(*winSystemName)(void);
/* window startup/shutown */
void (*winInit)(void);
void (*winOpen)(void);
void (*winSetName)(char *title);
int (*winImageFind)(char *imageName, int size);
void (*winImageNotFound)(void);
void (*winExit)(void);
/* display primitives */
int (*ioFormPrint)(int bitsAddr, int width, int height, int depth, double hScale, double vScale, int landscapeFlag);
int (*ioBeep)(void);
int (*ioRelinquishProcessorForMicroseconds)(int microSeconds);
int (*ioProcessEvents)(void);
int (*ioScreenDepth)(void);
int (*ioScreenSize)(void);
int (*ioSetCursorWithMask)(int cursorBitsIndex, int cursorMaskIndex, int offsetX, int offsetY);
int (*ioSetFullScreen)(int fullScreen);
int (*ioForceDisplayUpdate)(void);
int (*ioShowDisplay)(int dispBitsIndex, int width, int height, int depth, int l, int r, int t, int b);
int (*ioHasDisplayDepth)(int i);
int (*ioSetDisplayMode)(int width, int height, int depth, int fullscreenFlag);
int (*clipboardSize)(void);
int (*clipboardWriteFromAt)(int count, int byteArrayIndex, int startIndex);
int (*clipboardReadIntoAt)(int count, int byteArrayIndex, int startIndex);
int (*ioGetButtonState)(void);
int (*ioPeekKeystroke)(void);
int (*ioGetKeystroke)(void);
int (*ioGetNextEvent)(sqInputEvent *evt);
int (*ioMousePoint)(void);
/* OpenGL */
void *(*ioGetDisplay)(void);
void *(*ioGetWindow)(void);
int (*ioGLinitialise)(void);
int (*ioGLcreateRenderer)(glRenderer *r, int x, int y, int w, int h, int flags);
int (*ioGLmakeCurrentRenderer)(glRenderer *r);
void (*ioGLdestroyRenderer)(glRenderer *r);
void (*ioGLswapBuffers)(glRenderer *r);
void (*ioGLsetBufferRect)(glRenderer *r, int x, int y, int w, int h);
/* browser plugin */
int (*primitivePluginBrowserReady)(void);
int (*primitivePluginRequestURLStream)(void);
int (*primitivePluginRequestURL)(void);
int (*primitivePluginPostURL)(void);
int (*primitivePluginRequestFileHandle)(void);
int (*primitivePluginDestroyRequest)(void);
int (*primitivePluginRequestState)(void);
};
#define SqDisplayDefine(NAME) \
static struct SqDisplay display_##NAME##_itf= { \
SqDisplayVersion, \
display_winSystemName, \
display_winInit, \
display_winOpen, \
display_winSetName, \
display_winImageFind, \
display_winImageNotFound, \
display_winExit, \
display_ioFormPrint, \
display_ioBeep, \
display_ioRelinquishProcessorForMicroseconds, \
display_ioProcessEvents, \
display_ioScreenDepth, \
display_ioScreenSize, \
display_ioSetCursorWithMask, \
display_ioSetFullScreen, \
display_ioForceDisplayUpdate, \
display_ioShowDisplay, \
display_ioHasDisplayDepth, \
display_ioSetDisplayMode, \
display_clipboardSize, \
display_clipboardWriteFromAt, \
display_clipboardReadIntoAt, \
display_ioGetButtonState, \
display_ioPeekKeystroke, \
display_ioGetKeystroke, \
display_ioGetNextEvent, \
display_ioMousePoint, \
display_ioGetDisplay, \
display_ioGetWindow, \
display_ioGLinitialise, \
display_ioGLcreateRenderer, \
display_ioGLmakeCurrentRenderer, \
display_ioGLdestroyRenderer, \
display_ioGLswapBuffers, \
display_ioGLsetBufferRect, \
display_primitivePluginBrowserReady, \
display_primitivePluginRequestURLStream, \
display_primitivePluginRequestURL, \
display_primitivePluginPostURL, \
display_primitivePluginRequestFileHandle, \
display_primitivePluginDestroyRequest, \
display_primitivePluginRequestState \
}
extern struct SqDisplay *ioGetDisplayModule(void);
#endif /* __sq_SqDisplay_h */
--- NEW FILE: SqModule.h ---
#ifndef __sq_SqModule_h
#define __sq_SqModule_h
#define SqModuleVersionMajor 1
#define SqModuleVersionMinor 1
#define SqModuleVersion ((SqModuleVersionMajor << 16) | (SqModuleVersionMinor))
struct SqModule
{
int version;
char *name;
char *type;
int (*parseArgument)(int, char **);
void (*parseEnvironment)(void);
void (*printUsage)(void);
void (*printUsageNotes)(void);
void *(*makeInterface)(void);
struct SqModule *next;
};
#define SqModuleDefine(TYPE, NAME) \
struct SqModule TYPE##_##NAME= { \
SqModuleVersion, \
#NAME, \
#TYPE, \
TYPE##_parseArgument, \
TYPE##_parseEnvironment, \
TYPE##_printUsage, \
TYPE##_printUsageNotes, \
TYPE##_makeInterface, \
0 \
}
#endif /* __sq_SqModule_h */
--- NEW FILE: SqSound.h ---
#ifndef __sq_SqSound_h
#define __sq_SqSound_h
#define SqSoundVersionMajor 1
#define SqSoundVersionMinor 1
#define SqSoundVersion ((SqSoundVersionMajor << 16) | (SqSoundVersionMinor))
struct SqSound
{
int version;
/* output */
int (*snd_AvailableSpace)(void);
int (*snd_InsertSamplesFromLeadTime)(int frameCount, int srcBufPtr, int samplesOfLeadTime);
int (*snd_PlaySamplesFromAtLength)(int frameCount, int arrayIndex, int startIndex);
int (*snd_PlaySilence)(void);
int (*snd_Start)(int frameCount, int samplesPerSec, int stereo, int semaIndex);
int (*snd_Stop)(void);
/* input */
int (*snd_StartRecording)(int desiredSamplesPerSec, int stereo, int semaIndex);
int (*snd_StopRecording)(void);
double (*snd_GetRecordingSampleRate)(void);
int (*snd_RecordSamplesIntoAtLength)(int buf, int startSliceIndex, int bufferSizeInBytes);
/* mixer */
void (*snd_Volume)(double *left, double *right);
void (*snd_SetVolume)(double left, double right);
int (*snd_SetRecordLevel)(int level);
};
#define SqSoundDefine(NAME) \
static struct SqSound sound_##NAME##_itf= { \
SqSoundVersion, \
sound_AvailableSpace, \
sound_InsertSamplesFromLeadTime, \
sound_PlaySamplesFromAtLength, \
sound_PlaySilence, \
sound_Start, \
sound_Stop, \
sound_StartRecording, \
sound_StopRecording, \
sound_GetRecordingSampleRate, \
sound_RecordSamplesIntoAtLength, \
sound_Volume, \
sound_SetVolume, \
sound_SetRecordLevel \
}
#endif /* __sq_SqSound_h */
--- NEW FILE: acinclude.m4 ---
AC_DEFUN([AC_LANGINFO_CODESET], [
AC_CACHE_CHECK([for nl_langinfo and CODESET], ac_cv_langinfo_codeset,
[AC_TRY_LINK([#include <langinfo.h>], [char *cs= nl_langinfo(CODESET);],
ac_cv_langinfo_codeset=yes,
ac_cv_langinfo_codeset=no)
])
if test $ac_cv_langinfo_codeset = yes; then
AC_DEFINE(HAVE_LANGINFO_CODESET, 1,
[Define if you have <langinfo.h> and nl_langinfo(CODESET).])
fi
AC_SUBST(HAVE_LANGINFO_CODESET)
])
AC_DEFUN([AC_ICONV], [
AC_CHECK_LIB(iconv, iconv_open, ac_cv_iconv=yes, [
AC_CHECK_LIB(iconv, libiconv_open, ac_cv_iconv=yes, ac_cv_iconv=no)
])
if test $ac_cv_iconv = yes; then
LIBS="$LIBS -liconv"
fi
])
AC_CHECK_HEADERS(iconv.h)
AC_ICONV
AC_LANGINFO_CODESET
case $host_os in
darwin*) LIBS="$LIBS -framework CoreFoundation";;
*) ;;
esac
--- NEW FILE: debug.c ---
#include "debug.h"
#include <stdio.h>
#include <stdarg.h>
#include <string.h>
void __sq_dprintf(const char *fmt, ...)
{
va_list ap;
va_start(ap, fmt);
vprintf(fmt, ap);
va_end(ap);
}
void __sq_assert(char *file, int line, char *func, char *expr)
{
__sq_errfile= file;
__sq_errline= line;
__sq_errfunc= func;
__sq_eprintf("assertion failed: %s\n", expr);
abort();
}
char *__sq_errfile;
int __sq_errline;
char *__sq_errfunc;
void __sq_eprintf(const char *fmt, ...)
{
va_list ap;
char *file= strrchr(__sq_errfile, '/');
file= file ? file + 1 : __sq_errfile;
va_start(ap, fmt);
fprintf(stderr, "%s(%d): %s:\n", file, __sq_errline, __sq_errfunc);
fprintf(stderr, "%s(%d): ", file, __sq_errline);
vfprintf(stderr, fmt, ap);
va_end(ap);
}
--- NEW FILE: debug.h ---
#ifndef __sq_debug_h
#define __sq_debug_h
#ifndef DEBUG
# define DEBUG 0
#endif
#if (DEBUG)
/* the thing to use here is a variadic macro, but Apple's gcc barfs on
** them when running in precomp mode. did they _really_ have to break
** the preprocessor just to implement precomp? good _grief_.
*/
extern void __sq_dprintf(const char *fmt, ...);
# define dprintf(ARGS) __sq_dprintf ARGS
#else
# define dprintf(ARGS) ((void)0)
#endif
#undef assert
#if (DEBUG)
extern void __sq_assert(char *file, int line, char *func, char *expr);
# define assert(E) \
((void)((E) ? 0 : __sq_assert(__FILE__, __LINE__, __FUNCTION__, #E)))
#else
# define assert(E) ((void)0)
#endif
extern char *__sq_errfile;
extern int __sq_errline;
extern char *__sq_errfunc;
extern void __sq_eprintf(const char *fmt, ...);
# define eprintf \
( __sq_errfile= __FILE__, \
__sq_errline= __LINE__, \
__sq_errfunc= __FUNCTION__, \
__sq_eprintf )
#endif /* __sq_debug_h */
--- NEW FILE: feedback.h ---
--- NEW FILE: sqUnixCharConv.c ---
/* sqUnixCharConv.c -- conversion between character encodings
*
* Author: Ian...@IN...
*
* Copyright (C) 1996-2002 Ian Piumarta and other authors/contributors
* as listed elsewhere in this file.
* All rights reserved.
*
* You are NOT ALLOWED to distribute modified versions of this file
* under its original name. If you want to modify it and then make
* your modifications available publicly, rename the file first.
*
* This file is part of Unix Squeak.
*
* This file is distributed in the hope that it will be useful, but WITHOUT
* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
* FITNESS FOR A PARTICULAR PURPOSE.
*
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
* this distribution, subject to the following additional restrictions:
*
* 1. The origin of this software must not be misrepresented; you must not
* claim that you wrote the original software. If you use this software
* in a product, an acknowledgment to the original author(s) (and any
* other contributors mentioned herein) in the product documentation
* would be appreciated but is not required.
*
* 2. You must not distribute (or make publicly available by any
* means) a modified copy of this file unless you first rename it.
*
* 3. This notice must not be removed or altered in any source distribution.
*
* Using (or modifying this file for use) in any context other than Squeak
* changes these copyright conditions. Read the file `COPYING' in the
* directory `platforms/unix/doc' before proceeding with any such use.
*
* Last edited: 2003-03-04 03:22:54 by piumarta on emilia.inria.fr
*/
#if !defined(__MACH__)
# include "config.h"
#endif
#include "sqUnixCharConv.h"
#include <stdio.h>
#include <stdlib.h>
#include <string.h>
static inline int min(int x, int y) { return (x < y) ? x : y; }
static int convertCopy(char *from, int fromLen, char *to, int toLen, int term)
{
int len= min(toLen - term, fromLen);
strncpy(to, from, len);
if (term) to[len]= '\0';
return len;
}
#if defined(__MACH__)
// we have to do something special on MacOSX (surprise surprise) because:
// - MacOSX isn't Unix98 compliant and lacks builtin iconv functions
// - the free libiconv cannot handle the canonical decomposition used in HFS+
// ho hum dee dumb
# include <CoreFoundation/CoreFoundation.h>
typedef struct
{
char *alias;
void *encoding;
} alias;
static alias encodings[]=
{
{ "MACROMAN", (void *)kCFStringEncodingMacRoman },
{ "MAC", (void *)kCFStringEncodingMacRoman },
{ "MACINTOSH", (void *)kCFStringEncodingMacRoman },
{ "CSMACINTOSH", (void *)kCFStringEncodingMacRoman },
{ "UTF8", (void *)kCFStringEncodingUTF8 },
{ "UTF-8", (void *)kCFStringEncodingUTF8 },
{ "ISOLATIN9", (void *)kCFStringEncodingISOLatin9 },
{ "LATIN9", (void *)kCFStringEncodingISOLatin9 },
{ "ISO-8859-15", (void *)kCFStringEncodingISOLatin9 },
{ "ISOLATIN1", (void *)kCFStringEncodingISOLatin1 },
{ "LATIN1", (void *)kCFStringEncodingISOLatin1 },
{ "ISO-8859-1", (void *)kCFStringEncodingISOLatin1 },
// there are many tens of these and I can't be bothered.
{ 0, 0 }
};
// defaults
void *sqTextEncoding= ((void *)kCFStringEncodingISOLatin9); // xxxFIXME -> kCFStringEncodingISOLatin9
void *uxTextEncoding= ((void *)kCFStringEncodingISOLatin9);
void *uxPathEncoding= ((void *)kCFStringEncodingUTF8);
void *uxUTF8Encoding= ((void *)kCFStringEncodingUTF8);
void *uxXWinEncoding= ((void *)kCFStringEncodingISOLatin1);
void setEncoding(void **encoding, char *rawName)
{
char *name= strdup(rawName);
int len= strlen(name);
int i;
int utf8= 0;
for (i= 0; i < len; ++i)
name[i]= toupper(name[i]);
alias *ap= encodings;
while (ap->alias)
if (!strcmp(name, ap->alias))
{
*encoding= ap->encoding;
goto done;
}
else
++ap;
fprintf(stderr, "setEncoding: could not set encoding '%s'\n", name);
done:
free(name);
}
int convertChars(char *from, int fromLen, void *fromCode, char *to, int toLen, void *toCode, int norm, int term)
{
convertCopy(from, fromLen, to, toLen, 1);
{
CFStringRef cfs= CFStringCreateWithCString(NULL, to, (CFStringEncoding)fromCode);
CFMutableStringRef str= CFStringCreateMutableCopy(NULL, 0, cfs);
CFRelease(cfs);
if (norm) // HFS+ imposes Unicode2.1 decomposed UTF-8 encoding on all path elements
CFStringNormalize(str, kCFStringNormalizationFormD); // canonical decomposition
{
CFRange rng= CFRangeMake(0, CFStringGetLength(str));
CFIndex len= 0;
CFIndex num= CFStringGetBytes(str, rng, (CFStringEncoding)toCode, '?', 0, (UInt8 *)to, toLen - term, &len);
CFRelease(str);
if (!num)
return convertCopy(from, fromLen, to, toLen, term);
if (term)
to[len]= '\0';
return len;
}
}
}
#elif defined(HAVE_ICONV_H)
#include <iconv.h>
typedef char ichar_t;
void *sqTextEncoding= (void *)"MACINTOSH"; /* xxxFIXME -> "ISO-8859-15" */
void *uxTextEncoding= (void *)"ISO-8859-15";
void *uxPathEncoding= (void *)"UTF-8";
void *uxUTF8Encoding= (void *)"UTF-8";
void *uxXWinEncoding= (void *)"ISO-8859-1";
void setEncoding(void **encoding, char *rawName)
{
char *name= strdup(rawName);
int len= strlen(name);
int i;
for (i= 0; i < len; ++i)
name[i]= toupper(name[i]);
if (!strcmp(name, "MACROMAN")) *encoding= "MACINTOSH";
else if (!strcmp(name, "MAC-ROMAN")) *encoding= "MACINTOSH";
else
*encoding= (void *)name;
}
int convertChars(char *from, int fromLen, void *fromCode, char *to, int toLen, void *toCode, int norm, int term)
{
ichar_t *inbuf= from;
size_t inbytes= fromLen;
char *outbuf= to;
size_t outbytes= toLen - term;
static iconv_t cd= (iconv_t)-1;
static void *pfc= 0;
static void *ptc= 0;
if ((pfc != fromCode) || (ptc != toCode))
{
if (cd != (iconv_t)-1) iconv_close(cd);
pfc= ptc= (void *)-1;
cd= iconv_open((const char *)toCode, (const char *)fromCode);
if ((iconv_t)-1 != cd)
{
pfc= fromCode;
ptc= toCode;
}
}
if ((iconv_t)-1 != cd)
{
int n= iconv(cd, &inbuf, &inbytes, &outbuf, &outbytes);
if ((size_t)-1 != n)
{
if (term) *outbuf= '\0';
return outbuf - to;
}
else
perror("iconv");
}
else
perror("iconv_open");
return convertCopy(from, fromLen, to, toLen, term);
}
#else /* !__MACH__ && !HAVE_LIBICONV */
void *sqTextEncoding= 0;
void *uxTextEncoding= 0;
void *uxPathEncoding= 0;
void *uxUTF8Encoding= 0;
void *uxXWinEncoding= 0;
void setEncoding(void **encoding, char *name) { }
int convertChars(char *from, int fromLen, void *fromCode, char *to, int toLen, void *toCode, int norm, int term)
{
return convertCopy(from, fromLen, to, toLen, term);
}
#endif
static inline void sq2uxLines(char *string, int n)
{
while (n--)
{
if ('\015' == *string) *string= '\012';
++string;
}
}
static inline void ux2sqLines(char *string, int n)
{
while (n--)
{
if ('\012' == *string) *string= '\015';
++string;
}
}
#define Convert(sq,ux, type, F, T, N, L) \
int sq##2##ux##type(char *from, int fromLen, char *to, int toLen, int term) \
{ \
int n= convertChars(from, fromLen, F, to, toLen, T, N, term); \
if (L) sq##2##ux##Lines(to, n); \
return n; \
}
Convert(sq,ux, Text, sqTextEncoding, uxTextEncoding, 0, 1);
Convert(ux,sq, Text, uxTextEncoding, sqTextEncoding, 0, 1);
#if defined(__MACH__)
Convert(sq,ux, Path, sqTextEncoding, uxPathEncoding, 1, 0); // normalised paths for HFS+
#else
Convert(sq,ux, Path, sqTextEncoding, uxPathEncoding, 0, 0); // composed paths for others
#endif
Convert(ux,sq, Path, uxPathEncoding, sqTextEncoding, 0, 0);
Convert(sq,ux, UTF8, sqTextEncoding, uxUTF8Encoding, 0, 1);
Convert(ux,sq, UTF8, uxUTF8Encoding, sqTextEncoding, 0, 1);
#undef Convert
#if defined(CONV_TEST)
#if defined(HAVE_LANGINFO_CODESET)
# include <langinfo.h>
#endif
int main()
{
#if defined(HAVE_LANGINFO_CODESET)
if (0 == strcmp(nl_langinfo(CODESET)), "UTF-8")
printf("UTF-8 codeset selected\n");
#else
{
char *s;
if ((( (s = getenv("LC_ALL")) && *s)
|| ((s = getenv("LC_CTYPE")) && *s)
|| ((s = getenv("LANG")) && *s))
&& strstr(s, "UTF-8"))
printf("UTF-8 locale selected\n");
}
#endif
{
char *in, out[256];
int n;
in= "tésté"; // UTF-8 composed Unicode
n= convertChars(in, strlen(in), uxPathEncoding, out, sizeof(out), uxTextEncoding, 0, 1);
printf("%d: %s -> %s\n", n, in, out);
in= "teÌsteÌ"; // UTF-8 decomposed Unicode (libiconv fails on this one, MacOSX passes)
n= convertChars(in, strlen(in), uxPathEncoding, out, sizeof(out), uxTextEncoding, 0, 1);
printf("%d: %s -> %s\n", n, in, out);
in= "tésté"; // ISO-8859-15
n= convertChars(in, strlen(in), uxTextEncoding, out, sizeof(out), uxPathEncoding, 0, 1);
printf("%d: %s -> %s\n", n, in, out); // default composition -- should yield "tésté"
n= convertChars(in, strlen(in), uxTextEncoding, out, sizeof(out), uxPathEncoding, 1, 1);
printf("%d: %s -> %s\n", n, in, out); // canonical decomposition -- should yield "teÌsteÌ"
}
return 0;
}
/*
cc -Wall -DCONV_TEST -g -o main sqUnixCharConv.c -framework CoreFoundation # MacOSX
cc -Wall -DCONV_TEST -g -o main sqUnixCharConv.c # glibc >= 2.2
cc -Wall -DCONV_TEST -g -o main sqUnixCharConv.c -liconv # others
*/
#endif /* defined(CONV_TEST) */
--- NEW FILE: sqUnixCharConv.h ---
/* sqUnixCharConv.h -- conversion between character encodings
*
* Author: Ian...@IN...
*
* Copyright (C) 1996-2002 Ian Piumarta and other authors/contributors
* as listed elsewhere in this file.
* All rights reserved.
*
* You are NOT ALLOWED to distribute modified versions of this file
* under its original name. If you want to modify it and then make
* your modifications available publicly, rename the file first.
*
* This file is part of Unix Squeak.
*
* This file is distributed in the hope that it will be useful, but WITHOUT
* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
* FITNESS FOR A PARTICULAR PURPOSE.
*
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
* this distribution, subject to the following additional restrictions:
*
* 1. The origin of this software must not be misrepresented; you must not
* claim that you wrote the original software. If you use this software
* in a product, an acknowledgment to the original author(s) (and any
* other contributors mentioned herein) in the product documentation
* would be appreciated but is not required.
*
* 2. You must not distribute (or make publicly available by any
* means) a modified copy of this file unless you first rename it.
*
* 3. This notice must not be removed or altered in any source distribution.
*
* Using (or modifying this file for use) in any context other than Squeak
* changes these copyright conditions. Read the file `COPYING' in the
* directory `platforms/unix/doc' before proceeding with any such use.
*
* Last edited: 2003-03-03 03:52:52 by piumarta on emilia.inria.fr
*/
#ifndef __sqUnixCharConv_h
#define __sqUnixCharConv_h
extern void *sqTextEncoding;
extern void *uxTextEncoding;
extern void *uxPathEncoding;
extern void *uxUTF8Encoding;
extern void *uxXWinEncoding;
extern void setEncoding(void **encoding, char *name);
extern int convertChars(char *from, int fromLen, void *fromCode,
char *to, int toLen, void *toCode,
int norm, int term);
extern int sq2uxText(char *from, int fromLen, char *to, int toLen, int term);
extern int ux2sqText(char *from, int fromLen, char *to, int toLen, int term);
extern int sq2uxPath(char *from, int fromLen, char *to, int toLen, int term);
extern int ux2sqPath(char *from, int fromLen, char *to, int toLen, int term);
extern int sq2uxUTF8(char *from, int fromLen, char *to, int toLen, int term);
extern int ux2sqUTF8(char *from, int fromLen, char *to, int toLen, int term);
#endif /* __sqUnixCharConv_h */
--- NEW FILE: sqUnixEvent.c ---
/* sqUnixEvent.c -- support for window system events.
*
* Copyright (C) 1996-2002 Ian Piumarta and other authors/contributors
* as listed elsewhere in this file.
* All rights reserved.
*
* You are NOT ALLOWED to distribute modified versions of this file
* under its original name. If you want to modify it and then make
* your modifications available publicly, rename the file first.
*
* This file is part of Unix Squeak.
*
* This file is distributed in the hope that it will be useful, but WITHOUT
* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
* FITNESS FOR A PARTICULAR PURPOSE.
*
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
* this distribution, subject to the following additional restrictions:
*
* 1. The origin of this software must not be misrepresented; you must not
* claim that you wrote the original software. If you use this software
* in a product, an acknowledgment to the original author(s) (and any
* other contributors mentioned herein) in the product documentation
* would be appreciated but is not required.
*
* 2. You must not distribute (or make publicly available by any
* means) a modified copy of this file unless you first rename it.
*
* 3. This notice must not be removed or altered in any source distribution.
*
* Using (or modifying this file for use) in any context other than Squeak
* changes these copyright conditions. Read the file `COPYING' in the
* directory `platforms/unix/doc' before proceeding with any such use.
*/
/* Author: Ian Piumarta <ian...@in...>
*
* Last edited: 2003-02-11 04:53:56 by piumarta on emilia.inria.fr
*
* NOTE: this file is included by the window support files that need it.
*/
#define IEB_SIZE 64 /* must be power of 2 */
typedef struct
{
int x, y;
} SqPoint;
SqPoint mousePosition= { 0, 0 }; /* position at last motion event */
int swapBtn= 0; /* 1 to swap yellow and blue buttons */
sqInputEvent inputEventBuffer[IEB_SIZE];
int iebIn= 0; /* next IEB location to write */
int iebOut= 0; /* next IEB location to read */
#define iebEmptyP() (iebIn == iebOut)
#define iebAdvance(P) (P= ((P + 1) & (IEB_SIZE - 1)))
int buttonState= 0; /* mouse button state or 0 if not pressed */
int modifierState= 0; /* modifier key state or 0 if none pressed */
#if defined(DEBUG_EVENTS)
#include <ctype.h>
static void printKey(int key)
{
printf(" `%c' (%d = 0x%x)", (isgraph(key) ? key : ' '), key, key);
}
static void printButtons(int buttons)
{
if (buttons & RedButtonBit) printf(" red");
if (buttons & YellowButtonBit) printf(" yellow");
if (buttons & BlueButtonBit) printf(" blue");
}
static void printModifiers(int midofiers)
{
if (midofiers & ShiftKeyBit) printf(" Shift");
if (midofiers & CtrlKeyBit) printf(" Control");
if (midofiers & CommandKeyBit) printf(" Command");
if (midofiers & OptionKeyBit) printf(" Option");
}
#endif
static sqInputEvent *allocateInputEvent(int eventType)
{
sqInputEvent *evt= &inputEventBuffer[iebIn];
iebAdvance(iebIn);
if (iebEmptyP())
{
/* overrun: discard oldest event */
iebAdvance(iebOut);
}
evt->type= eventType;
evt->timeStamp= ioMSecs();
return evt;
}
#define allocateMouseEvent() ( \
(sqMouseEvent *)allocateInputEvent(EventTypeMouse) \
)
#define allocateKeyboardEvent() ( \
(sqKeyboardEvent *)allocateInputEvent(EventTypeKeyboard) \
)
#define allocateDragEvent() ( \
(sqDragDropFilesEvent *)allocateInputEvent(EventTypeDragDropFiles) \
)
static int getButtonState(void)
{
/* red button honours the modifiers:
* red+ctrl = yellow button
* red+command = blue button
*/
int buttons= buttonState;
int modifiers= modifierState;
if ((buttons == RedButtonBit) && modifiers)
{
int yellow= swapBtn ? BlueButtonBit : YellowButtonBit;
int blue= swapBtn ? YellowButtonBit : BlueButtonBit;
switch (modifiers)
{
case CtrlKeyBit: buttons= yellow; modifiers &= ~CtrlKeyBit; break;
case CommandKeyBit: buttons= blue; modifiers &= ~CommandKeyBit; break;
}
}
#ifdef DEBUG_EVENTS
printf("BUTTONS");
printModifiers(modifiers);
printButtons(buttons);
printf("\n");
#endif
return buttons | (modifiers << 3);
}
static void signalInputEvent(void)
{
#ifdef DEBUG_EVENTS
printf("signalInputEvent\n");
#endif
if (inputEventSemaIndex > 0)
signalSemaphoreWithIndex(inputEventSemaIndex);
}
static void recordMouseEvent(void)
{
int state= getButtonState();
sqMouseEvent *evt= allocateMouseEvent();
evt->x= mousePosition.x;
evt->y= mousePosition.y;
evt->buttons= (state & 0x7);
evt->modifiers= (state >> 3);
evt->reserved1=
evt->reserved2= 0;
signalInputEvent();
#ifdef DEBUG_EVENTS
printf("EVENT: mouse (%d,%d)", mousePosition.x, mousePosition.y);
printModifiers(state >> 3);
printButtons(state & 7);
printf("\n");
#endif
}
static void recordKeyboardEvent(int keyCode, int pressCode, int modifiers)
{
sqKeyboardEvent *evt= allocateKeyboardEvent();
evt->charCode= keyCode;
evt->pressCode= pressCode;
evt->modifiers= modifiers;
evt->reserved1=
evt->reserved2=
evt->reserved3= 0;
signalInputEvent();
#ifdef DEBUG_EVENTS
printf("EVENT: key");
switch (pressCode)
{
case EventKeyDown: printf(" down "); break;
case EventKeyChar: printf(" char "); break;
case EventKeyUp: printf(" up "); break;
default: printf(" ***UNKNOWN***"); break;
}
printModifiers(modifiers);
printKey(keyCode);
printf("\n");
#endif
}
static void recordDragEvent(int dragType, int numFiles)
{
int state= getButtonState();
sqDragDropFilesEvent *evt= allocateDragEvent();
evt->dragType= dragType;
evt->x= mousePosition.x;
evt->y= mousePosition.y;
evt->modifiers= (state >> 3);
evt->numFiles= numFiles;
evt->reserved1= 0;
signalInputEvent();
#ifdef DEBUG_EVENTS
printf("EVENT: drag (%d,%d)", mousePosition.x, mousePosition.y);
printModifiers(state >> 3);
printButtons(state & 7);
printf("\n");
#endif
}
/* retrieve the next input event from the queue */
static int display_ioGetNextEvent(sqInputEvent *evt)
{
if (iebEmptyP())
ioProcessEvents();
if (iebEmptyP())
return false;
*evt= inputEventBuffer[iebOut];
iebAdvance(iebOut);
return true;
}
/*** the following are deprecated and should really go away. for now
we keep them for backwards compatibility with ancient images ***/
#define KEYBUF_SIZE 64
static int keyBuf[KEYBUF_SIZE]; /* circular buffer */
static int keyBufGet= 0; /* index of next item of keyBuf to read */
static int keyBufPut= 0; /* index of next item of keyBuf to write */
static int keyBufOverflows= 0; /* number of characters dropped */
static void recordKeystroke(int keyCode) /* DEPRECATED */
{
if (inputEventSemaIndex == 0)
{
int keystate= keyCode | (modifierState << 8);
# ifdef DEBUG_EVENTS
printf("RECORD keystroke");
printModifiers(modifierState);
printKey(keyCode);
printf(" = %d 0x%x\n", keystate, keystate);
# endif
if (keystate == getInterruptKeycode())
{
setInterruptPending(true);
setInterruptCheckCounter(0);
}
else
{
keyBuf[keyBufPut]= keystate;
keyBufPut= (keyBufPut + 1) % KEYBUF_SIZE;
if (keyBufGet == keyBufPut)
{
/* buffer overflow; drop the last character */
keyBufGet= (keyBufGet + 1) % KEYBUF_SIZE;
keyBufOverflows++;
}
}
}
}
static int display_ioPeekKeystroke(void) /* DEPRECATED */
{
int keystate;
ioProcessEvents(); /* process all pending events */
if (keyBufGet == keyBufPut)
return -1; /* keystroke buffer is empty */
keystate= keyBuf[keyBufGet];
return keystate;
}
static int display_ioGetKeystroke(void) /* DEPRECATED */
{
int keystate;
ioProcessEvents(); /* process all pending events */
if (keyBufGet == keyBufPut)
return -1; /* keystroke buffer is empty */
keystate= keyBuf[keyBufGet];
keyBufGet= (keyBufGet + 1) % KEYBUF_SIZE;
return keystate;
}
static int display_ioGetButtonState(void)
{
ioProcessEvents(); /* process all pending events */
return getButtonState();
}
static int display_ioMousePoint(void)
{
ioProcessEvents(); /* process all pending events */
/* x is high 16 bits; y is low 16 bits */
return (mousePosition.x << 16) | (mousePosition.y);
}
--- NEW FILE: sqUnixGL.h ---
extern void *ioGLcreateView(int x, int y, int w, int h, int flags);
extern void *ioGLcreateContext(void *drawable);
extern int ioGLsetCurrentContext(void *ctx);
extern int ioGLdestroyContext(void *ctx);
extern int ioGLdestroyView(void *drawable);
extern int ioGLflushBuffer(void *drawable, void *ctx);
--- NEW FILE: sqUnixGlobals.h ---
#ifndef __sqUnixGlobals_h
#define __sqUnixGlobals_h
#if 1 /* use global structure */
extern int getFullScreenFlag(void);
extern void setFullScreenFlag(int i);
extern int getInterruptCheckCounter(void);
extern void setInterruptCheckCounter(int i);
extern int getInterruptKeycode(void);
extern void setInterruptKeycode(int i);
extern int getInterruptPending(void);
extern void setInterruptPending(int i);
extern int getSavedWindowSize(void);
extern void setSavedWindowSize(int i);
#else /* ! global structure */
extern int fullScreenFlag;
extern int interruptCheckCounter;
extern int interruptKeycode;
extern int interruptPending;
extern int savedWindowSize;
# define getFullScreenFlag() (fullScreenFlag)
# define setFullScreenFlag(I) (fullScreenFlag= (I))
# define getInterruptCheckCounter() (interruptCheckCounter)
# define setInterruptCheckCounter(I) (interruptCheckCounter= (I))
# define getInterruptKeycode() (interruptKeycode)
# define setInterruptKeycode(I) (interruptKeycode= (I))
# define getInterruptPending() (interruptPending)
# define setInterruptPending(I) (interruptPending= (I))
# define getSavedWindowSize() (savedWindowSize)
# define setSavedWindowSize(I) (savedWindowSize= (I))
#endif /* !global structure */
#endif /* __sqUnixGlobals_h */
--- NEW FILE: sqUnixMain.c ---
/* sqUnixMain.c -- support for Unix.
*
* Copyright (C) 1996-2002 Ian Piumarta and other authors/contributors
* as listed elsewhere in this file.
* All rights reserved.
*
* You are NOT ALLOWED to distribute modified versions of this file
* under its original name. If you want to modify it and then make
* your modifications available publicly, rename the file first.
*
* This file is part of Unix Squeak.
*
* This file is distributed in the hope that it will be useful, but WITHOUT
* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
* FITNESS FOR A PARTICULAR PURPOSE.
*
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
* this distribution, subject to the following additional restrictions:
[...998 lines suppressed...]
exit(1);
}
#endif
/* run Squeak */
interpret();
/* we need these, even if not referenced from main executable */
(void)sq2uxPath;
(void)ux2sqPath;
return 0;
}
int ioExit(void)
{
dpy->winExit();
exit(0);
}
--- NEW FILE: sqUnixMain.h ---
#ifndef __sqUnixMain_h
#define __sqUnixMain_h
extern char shortImageName[];
extern int inputEventSemaIndex;
extern char vmPath[];
extern char **argVec;
extern int fullScreenFlag;
extern int textEncodingUTF8;
extern void imgInit(void);
#endif /* __sqUnixMain_h */
--- NEW FILE: sqUnixWindow.h ---
Index: Makefile.in
===================================================================
RCS file: /cvsroot/squeak/squeak/platforms/unix/vm/Makefile.in,v
retrieving revision 1.1
retrieving revision 1.2
diff -C2 -d -r1.1 -r1.2
*** Makefile.in 12 May 2003 07:26:29 -0000 1.1
--- Makefile.in 13 May 2003 22:19:01 -0000 1.2
***************
*** 5,8 ****
--- 5,12 ----
# All rights reserved.
#
+ # You are NOT ALLOWED to distribute modified versions of this file
+ # under its original name. If you want to modify it and then make
+ # your modifications available publicly, rename the file first.
+ #
# This file is part of Unix Squeak.
#
***************
*** 13,17 ****
# You may use and/or distribute this file ONLY as part of Squeak, under
# the terms of the Squeak License as described in `LICENSE' in the base of
! # this distribution, subject to the following restrictions:
#
# 1. The origin of this software must not be misrepresented; you must not
--- 17,21 ----
# You may use and/or distribute this file ONLY as part of Squeak, under
# the terms of the Squeak License as described in `LICENSE' in the base of
! # this distribution, subject to the following additional restrictions:
#
# 1. The origin of this software must not be misrepresented; you must not
***************
*** 21,25 ****
# would be appreciated but is not required.
#
! # 2. This notice must not be removed or altered in any source distribution.
#
# Using (or modifying this file for use) in any context other than Squeak
--- 25,32 ----
# would be appreciated but is not required.
#
! # 2. You must not distribute (or make publicly available by any
! # means) a modified copy of this file unless you first rename it.
! #
! # 3. This notice must not be removed or altered in any source distribution.
#
# Using (or modifying this file for use) in any context other than Squeak
***************
*** 27,37 ****
# directory `platforms/unix/doc' before proceeding with any such use.
#
- # You are not allowed to distribute a modified version of this file
- # under its original name without explicit permission to do so. If
- # you change it, rename it.
- #
# Author: ian...@in...
#
! # Last edited: 2002-12-01 10:20:57 by piumarta on calvin.inria.fr
[make_cfg]
--- 34,40 ----
# directory `platforms/unix/doc' before proceeding with any such use.
#
# Author: ian...@in...
#
! # Last edited: 2003-03-01 19:19:04 by piumarta on emilia.inria.fr
[make_cfg]
***************
*** 39,46 ****
TARGET = vm$a
! OBJS = $(INTERP)$o sqNamedPrims$o sqVirtualMachine$o \
! aio$o osExports$o sqUnixExternalPrims$o sqUnixMozilla$o sqXWindow$o
! XINCLUDES = [includes] -I$(topdir)/platforms/Cross/plugins/FilePlugin
$(TARGET) : $(OBJS) Makefile
--- 42,52 ----
TARGET = vm$a
! OBJS = $(INTERP)$o sqNamedPrims$o sqVirtualMachine$o aio$o debug$o osExports$o \
! sqUnixExternalPrims$o sqUnixMemory$o sqUnixCharConv$o sqUnixMain$o
! XINCLUDES = [includes] \
! -I$(topdir)/platforms/Cross/plugins/FilePlugin \
! -I$(topdir)/platforms/unix/plugins/B3DAcceleratorPlugin \
! $(X_INCLUDES)
$(TARGET) : $(OBJS) Makefile
Index: aio.c
===================================================================
RCS file: /cvsroot/squeak/squeak/platforms/unix/vm/aio.c,v
retrieving revision 1.1
retrieving revision 1.2
diff -C2 -d -r1.1 -r1.2
*** aio.c 12 May 2003 07:26:29 -0000 1.1
--- aio.c 13 May 2003 22:19:01 -0000 1.2
***************
*** 5,8 ****
--- 5,12 ----
* All rights reserved.
*
+ * You are NOT ALLOWED to distribute modified versions of this file
+ * under its original name. If you want to modify it and then make
+ * your modifications available publicly, rename the file first.
+ *
* This file is part of Unix Squeak.
*
***************
*** 13,17 ****
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
! * this distribution, subject to the following restrictions:
*
* 1. The origin of this software must not be misrepresented; you must not
--- 17,21 ----
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
! * this distribution, subject to the following additional restrictions:
*
* 1. The origin of this software must not be misrepresented; you must not
***************
*** 21,38 ****
* would be appreciated but is not required.
*
! * 2. This notice must not be removed or altered in any source distribution.
*
* Using (or modifying this file for use) in any context other than Squeak
* changes these copyright conditions. Read the file `COPYING' in the
* directory `platforms/unix/doc' before proceeding with any such use.
- *
- * You are not allowed to distribute a modified version of this file
- * under its original name without explicit permission to do so. If
- * you change it, rename it.
*/
/* Author: Ian...@in...
*
! * Last edited: 2003-02-06 16:36:13 by piumarta on emilia.local.
*/
--- 25,41 ----
* would be appreciated but is not required.
*
! * 2. You must not distribute (or make publicly available by any
! * means) a modified copy of this file unless you first rename it.
! *
! * 3. This notice must not be removed or altered in any source distribution.
*
* Using (or modifying this file for use) in any context other than Squeak
* changes these copyright conditions. Read the file `COPYING' in the
* directory `platforms/unix/doc' before proceeding with any such use.
*/
/* Author: Ian...@in...
*
! * Last edited: 2003-02-27 19:47:59 by piumarta on emilia.inria.fr
*/
***************
*** 96,101 ****
#undef DEBUG
! #ifdef DEBUG
# define FPRINTF(X) fprintf X
static char *ticks= "-\\|/";
--- 99,105 ----
#undef DEBUG
+ #undef DEBUG_TICKER
! #if defined(DEBUG) && defined(DEBUG_TICKER)
# define FPRINTF(X) fprintf X
static char *ticks= "-\\|/";
***************
*** 230,233 ****
--- 234,238 ----
# undef _DO
}
+ return 1;
}
}
Index: aio.h
===================================================================
RCS file: /cvsroot/squeak/squeak/platforms/unix/vm/aio.h,v
retrieving revision 1.1
retrieving revision 1.2
diff -C2 -d -r1.1 -r1.2
*** aio.h 12 May 2003 07:26:29 -0000 1.1
--- aio.h 13 May 2003 22:19:01 -0000 1.2
***************
*** 5,8 ****
--- 5,12 ----
* All rights reserved.
*
+ * You are NOT ALLOWED to distribute modified versions of this file
+ * under its original name. If you want to modify it and then make
+ * your modifications available publicly, rename the file first.
+ *
* This file is part of Unix Squeak.
*
***************
*** 13,17 ****
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
! * this distribution, subject to the following restrictions:
*
* 1. The origin of this software must not be misrepresented; you must not
--- 17,21 ----
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
! * this distribution, subject to the following additional restrictions:
*
* 1. The origin of this software must not be misrepresented; you must not
***************
*** 21,38 ****
* would be appreciated but is not required.
*
! * 2. This notice must not be removed or altered in any source distribution.
*
* Using (or modifying this file for use) in any context other than Squeak
* changes these copyright conditions. Read the file `COPYING' in the
* directory `platforms/unix/doc' before proceeding with any such use.
- *
- * You are not allowed to distribute a modified version of this file
- * under its original name without explicit permission to do so. If
- * you change it, rename it.
*/
/* author: ian...@in...
*
! * last edited: 2003-02-06 16:34:35 by piumarta on emilia.local.
*/
--- 25,41 ----
* would be appreciated but is not required.
*
! * 2. You must not distribute (or make publicly available by any
! * means) a modified copy of this file unless you first rename it.
! *
! * 3. This notice must not be removed or altered in any source distribution.
*
* Using (or modifying this file for use) in any context other than Squeak
* changes these copyright conditions. Read the file `COPYING' in the
* directory `platforms/unix/doc' before proceeding with any such use.
*/
/* author: ian...@in...
*
! * last edited: 2002-12-02 20:20:13 by piumarta on calvin.inria.fr
*/
Index: dlfcn-dyld.c
===================================================================
RCS file: /cvsroot/squeak/squeak/platforms/unix/vm/dlfcn-dyld.c,v
retrieving revision 1.1
retrieving revision 1.2
diff -C2 -d -r1.1 -r1.2
*** dlfcn-dyld.c 12 May 2003 07:26:29 -0000 1.1
--- dlfcn-dyld.c 13 May 2003 22:19:01 -0000 1.2
***************
*** 1,3 ****
! /* dlfcn-darwin.c -- provides dlopen() and friends as wrappers to Mach's dylib
*
* Author: Ian...@IN...
--- 1,3 ----
! /* dlfcn-dyld.c -- provides dlopen() and friends as wrappers around Mach dyld
*
* Author: Ian...@IN...
***************
*** 7,10 ****
--- 7,14 ----
* All rights reserved.
*
+ * You are NOT ALLOWED to distribute modified versions of this file
+ * under its original name. If you want to modify it and then make
+ * your modifications available publicly, rename the file first.
+ *
* This file is part of Unix Squeak.
*
***************
*** 15,19 ****
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
! * this distribution, subject to the following restrictions:
*
* 1. The origin of this software must not be misrepresented; you must not
--- 19,23 ----
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
! * this distribution, subject to the following additional restrictions:
*
* 1. The origin of this software must not be misrepresented; you must not
***************
*** 23,27 ****
* would be appreciated but is not required.
*
! * 2. This notice must not be removed or altered in any source distribution.
*
* Using (or modifying this file for use) in any context other than Squeak
--- 27,34 ----
* would be appreciated but is not required.
*
! * 2. You must not distribute (or make publicly available by any
! * means) a modified copy of this file unless you first rename it.
! *
! * 3. This notice must not be removed or altered in any source distribution.
*
* Using (or modifying this file for use) in any context other than Squeak
***************
*** 29,37 ****
* directory `platforms/unix/doc' before proceeding with any such use.
*
! * You are not allowed to distribute a modified version of this file
! * under its original name without explicit permission to do so. If
! * you change it, rename it.
! *
! * Last edited: 2002-12-01 10:28:43 by piumarta on calvin.inria.fr
*/
--- 36,40 ----
* directory `platforms/unix/doc' before proceeding with any such use.
*
! * Last edited: 2002-12-01 16:06:50 by piumarta on calvin.inria.fr
*/
***************
*** 99,103 ****
! void *dlsym(void *handle, const char *symbol)
{
char _symbol[256];
--- 102,106 ----
! static void *dlsym(void *handle, const char *symbol)
{
char _symbol[256];
***************
*** 150,154 ****
! int dlclose(void *handle)
{
if (( (MH_MAGIC == ((struct mach_header *)handle)->magic)) /* ppc */
--- 153,157 ----
! static int dlclose(void *handle)
{
if (( (MH_MAGIC == ((struct mach_header *)handle)->magic)) /* ppc */
Index: sqPlatformSpecific.h
===================================================================
RCS file: /cvsroot/squeak/squeak/platforms/unix/vm/sqPlatformSpecific.h,v
retrieving revision 1.8
retrieving revision 1.9
diff -C2 -d -r1.8 -r1.9
*** sqPlatformSpecific.h 12 May 2003 07:39:08 -0000 1.8
--- sqPlatformSpecific.h 13 May 2003 22:19:01 -0000 1.9
***************
*** 5,8 ****
--- 5,12 ----
* All rights reserved.
*
+ * You are NOT ALLOWED to distribute modified versions of this file
+ * under its original name. If you want to modify it and then make
+ * your modifications available publicly, rename the file first.
+ *
* This file is part of Unix Squeak.
*
***************
*** 13,17 ****
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
! * this distribution, subject to the following restrictions:
*
* 1. The origin of this software must not be misrepresented; you must not
--- 17,21 ----
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
! * this distribution, subject to the following additional restrictions:
*
* 1. The origin of this software must not be misrepresented; you must not
***************
*** 21,25 ****
* would be appreciated but is not required.
*
! * 2. This notice must not be removed or altered in any source distribution.
*
* Using (or modifying this file for use) in any context other than Squeak
--- 25,32 ----
* would be appreciated but is not required.
*
! * 2. You must not distribute (or make publicly available by any
! * means) a modified copy of this file unless you first rename it.
! *
! * 3. This notice must not be removed or altered in any source distribution.
*
* Using (or modifying this file for use) in any context other than Squeak
***************
*** 27,37 ****
* directory `platforms/unix/doc' before proceeding with any such use.
*
- * You are not allowed to distribute a modified version of this file
- * under its original name without explicit permission to do so. If
- * you change it, rename it.
- *
* Author: ian...@in...
*
! * Last edited: 2002-06-08 02:34:43 by piumarta on emilia.inria.fr
*/
--- 34,40 ----
* directory `platforms/unix/doc' before proceeding with any such use.
*
* Author: ian...@in...
*
! * Last edited: 2003-03-02 21:06:24 by piumarta on emilia.inria.fr
*/
***************
*** 42,46 ****
--- 45,71 ----
#undef ioLowResMSecs
+ #undef sqAllocateMemory
+ #undef sqGrowMemoryBy
+ #undef sqShrinkMemoryBy
+ #undef sqMemoryExtraBytesLeft
+
#include <sys/types.h>
typedef off_t squeakFileOffsetType;
+
+ #define SQ_STDIO_UTF8
+
+ /* intercept stdio functions that might need UTF-8 path conversion. */
+ /* (on HFS+ we also need to perform canonical decomposition on the UTF-8 encoding.) */
+
+ #if defined(SQ_STDIO_UTF8)
+ # undef fopen
+ # undef delete
+ # undef remove
+ extern FILE *sq_fopen(char *path, const char *mode);
+ extern int sq_remove(char *path);
+ extern int sq_rename(char *from, char *to);
+ # define fopen sq_fopen
+ # define remove sq_remove
+ # define rename sq_rename
+ #endif
Index: sqUnixExternalPrims.c
===================================================================
RCS file: /cvsroot/squeak/squeak/platforms/unix/vm/sqUnixExternalPrims.c,v
retrieving revision 1.3
retrieving revision 1.4
diff -C2 -d -r1.3 -r1.4
*** sqUnixExternalPrims.c 12 May 2003 07:39:09 -0000 1.3
--- sqUnixExternalPrims.c 13 May 2003 22:19:01 -0000 1.4
***************
*** 5,8 ****
--- 5,12 ----
* All rights reserved.
*
+ * You are NOT ALLOWED to distribute modified versions of this file
+ * under its original name. If you want to modify it and then make
+ * your modifications available publicly, rename the file first.
+ *
* This file is part of Unix Squeak.
*
***************
*** 13,17 ****
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
! * this distribution, subject to the following restrictions:
*
* 1. The origin of this software must not be misrepresented; you must not
--- 17,21 ----
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
! * this distribution, subject to the following additional restrictions:
*
* 1. The origin of this software must not be misrepresented; you must not
***************
*** 21,44 ****
* would be appreciated but is not required.
*
! * 2. This notice must not be removed or altered in any source distribution.
*
* Using (or modifying this file for use) in any context other than Squeak
* changes these copyright conditions. Read the file `COPYING' in the
* directory `platforms/unix/doc' before proceeding with any such use.
- *
- * You are not allowed to distribute a modified version of this file
- * under its original name without explicit permission to do so. If
- * you change it, rename it.
*/
/* Author: Ian...@IN...
*
! * Last edited: 2003-01-29 21:51:13 by piumarta on emilia.local.
*/
- #include "sq.h" /* sqUnixConfig.h */
-
#define DEBUG 0
#if DEBUG
# define dprintf(ARGS) fprintf ARGS
--- 25,47 ----
* would be appreciated but is not required.
*
! * 2. You must not distribute (or make publicly available by any
! * means) a modified copy of this file unless you first rename it.
! *
! * 3. This notice must not be removed or altered in any source distribution.
*
* Using (or modifying this file for use) in any context other than Squeak
* changes these copyright conditions. Read the file `COPYING' in the
* directory `platforms/unix/doc' before proceeding with any such use.
*/
/* Author: Ian...@IN...
*
! * Last edited: 2003-02-21 03:48:48 by piumarta on emilia.inria.fr
*/
#define DEBUG 0
+ #include "sq.h" /* sqUnixConfig.h */
+
#if DEBUG
# define dprintf(ARGS) fprintf ARGS
***************
*** 47,51 ****
#endif
! #if defined(HAVE_DYLD)
# include "dlfcn-dyld.c"
#endif
--- 50,54 ----
#endif
! #if !defined(HAVE_LIBDL) && defined(HAVE_DYLD)
# include "dlfcn-dyld.c"
#endif
***************
*** 124,130 ****
char libName[NAME_MAX + 32]; /* headroom for prefix/suffix */
struct stat buf;
- int err;
sprintf(libName, "%s%s%s%s", dirName, *prefix, moduleName, *suffix);
! if (((err= stat(libName, &buf)) == 0) && (S_ISDIR(buf.st_mode)))
dprintf((stderr, "ignoring directory: %s\n", libName));
else
--- 127,134 ----
char libName[NAME_MAX + 32]; /* headroom for prefix/suffix */
struct stat buf;
sprintf(libName, "%s%s%s%s", dirName, *prefix, moduleName, *suffix);
! if (stat(libName, &buf))
! dprintf((stderr, "not found: %s\n", libName));
! else if (S_ISDIR(buf.st_mode))
dprintf((stderr, "ignoring directory: %s\n", libName));
else
***************
*** 133,143 ****
handle= dlopen(libName, RTLD_NOW | RTLD_GLOBAL);
if (handle == 0)
! {
! if (err == 0)
! fprintf(stderr, "ioLoadModule(%s):\n %s\n", libName, dlerror());
! }
else
{
! dprintf((stderr, "loaded: %s\n", libName));
return handle;
}
--- 137,144 ----
handle= dlopen(libName, RTLD_NOW | RTLD_GLOBAL);
if (handle == 0)
! fprintf(stderr, "ioLoadModule(%s):\n %s\n", libName, dlerror());
else
{
! printf("squeak: loaded plugin `%s'\n", libName);
return handle;
}
***************
*** 219,238 ****
}
- /* these are ordered such that a knowledgeable user can override a
- "system" library with one in the CWD */
-
if (( handle= tryLoading( "./", pluginName))
- /* this is the standard location for the plugins */
|| (handle= tryLoading(VM_LIBDIR"/", pluginName))
- /* this is the default case: when LD_LIBRARY_PATH is not
- it searches /etc/ld.so.cache, /lib and /usr/lib */
|| (handle= tryLoading( "", pluginName))
- /* try SQUEAK_PLUGIN_PATH and LD_LIBRARY_PATH if set */
|| (handle= tryLoadingPath("SQUEAK_PLUGIN_PATH", pluginName))
|| (handle= tryLoadingPath("LD_LIBRARY_PATH", pluginName)))
return (int)handle;
-
- dprintf(("ioLoadModule: could not load: %s\n", pluginName));
return 0;
}
--- 220,268 ----
}
if (( handle= tryLoading( "./", pluginName))
|| (handle= tryLoading(VM_LIBDIR"/", pluginName))
|| (handle= tryLoading( "", pluginName))
|| (handle= tryLoadingPath("SQUEAK_PLUGIN_PATH", pluginName))
|| (handle= tryLoadingPath("LD_LIBRARY_PATH", pluginName)))
return (int)handle;
+ #if defined(DARWIN)
+ // look in the bundle contents dir
+ {
+ static char *contents= 0;
+ extern char vmPath[];
+ if (!contents)
+ {
+ char *delim;
+ contents= strdup(vmPath);
+ if ((delim= strrchr(contents, '/')))
+ delim[1]= '\0';
+ }
+ if ((handle= tryLoading(contents, pluginName)))
+ return (int)handle;
+ }
+ // the following is needed so that, for example, the FFI can pick up
+ // things like <cdecl: 'xyz' module: 'CoreServices'>
+ {
+ static char *frameworks[]=
+ {
+ "/System/Library/Frameworks",
+ "/System/Library/Frameworks/CoreServices.framework/Frameworks",
+ "/System/Library/Frameworks/ApplicationServices.framework/Frameworks",
+ "/System/Library/Frameworks/Carbon.framework/Frameworks",
+ 0
+ };
+ char **framework= 0;
+ for (framework= frameworks; *framework; ++framework)
+ {
+ char path[NAME_MAX];
+ sprintf(path, "%s/%s.framework/", *framework, pluginName);
+ if ((handle= tryLoading(path, pluginName)))
+ return (int)handle;
+ }
+ }
+ #endif
+
+ fprintf(stderr, "squeak: could not load plugin `%s'\n", pluginName);
return 0;
}
***************
*** 250,257 ****
if (fn == 0)
! dprintf((stderr, "ioFindExternalFunctionIn(%s, %d):\n %s\n",
! lookupName, moduleHandle, dlerror()));
! else
! dprintf((stderr, " => %d (0x%x)\n", (int)fn, (int)fn));
return (int)fn;
--- 280,285 ----
if (fn == 0)
! fprintf(stderr, "ioFindExternalFunctionIn(%s, %d):\n %s\n",
! lookupName, moduleHandle, dlerror());
return (int)fn;
***************
*** 262,266 ****
/* Free the module with the associated handle. Answer 0 on error (do
* NOT fail the primitive!).
! */
int ioFreeModule(int moduleHandle)
{
--- 290,294 ----
/* Free the module with the associated handle. Answer 0 on error (do
* NOT fail the primitive!).
! */
int ioFreeModule(int moduleHandle)
{
|