Unix.st
author claus
Fri, 25 Feb 1994 14:00:53 +0100
changeset 56 be0ed17e6f85
parent 51 9b7ae5e18f3e
child 63 1f0cdefb013f
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1988 by Claus Gittinger
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

Object subclass:#OperatingSystem
       instanceVariableNames:''
       classVariableNames:''
       poolDictionaries:''
       category:'System-Support'
!

OperatingSystem comment:'

COPYRIGHT (c) 1988 by Claus Gittinger
             All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Attic/Unix.st,v 1.11 1994-02-05 12:27:58 claus Exp $

written 1988 by claus
'!

%{

#ifdef transputer
# define unlink(f)      ((remove(f) == 0) ? 0 : -1)
#else
# include <signal.h>

# ifdef SYSV
#  include <sys/types.h>
#  include <sys/param.h>
#  include <sys/times.h>
#  if ! defined(sco3_2)
#   include <unistd.h>
#  endif
#  if defined(isc3_2) || defined(sco3_2)
#   include <sys/time.h>
#  endif
#  if !defined(isc3_2)
#   if defined(PCS) && defined(mips)
#    include "/usr/include/bsd/sys/time.h"
#    include "/usr/include/sys/time.h"
#   else
#    include <time.h>
#   endif
#  endif
#  if defined(isc3_2)
#   include <sys/bsdtypes.h>
#  endif
#  ifdef FAST_TIMER
#   include <ft.h>
    static int timer_fd = -1;
#  endif
# else /* not SYSV */
#  include <sys/time.h>
#  include <sys/types.h>
# endif
# include <pwd.h>
# include <grp.h>

# include <sys/stat.h>
# include <errno.h>

# ifndef S_IXUSR
#  define S_IXUSR S_IEXEC
#  define S_IXGRP (S_IEXEC>>3)
#  define S_IXOTH (S_IEXEC>>6)
# endif

#endif

/*
 * on some systems errno is a macro ... check for it here
 */
#ifndef errno
 extern errno;
#endif

#include <stdio.h>
#include <fcntl.h>

/*
 * some (old) systems do not define this ...
 */
#ifndef R_OK
# define R_OK    4       /* Test for Read permission */ 
# define W_OK    2       /* Test for Write permission */
# define X_OK    1       /* Test for eXecute permission */
# define F_OK    0       /* Test for existence of File */
#endif
%}

!OperatingSystem class methodsFor:'documentation'!

documentation
"
this class gives access to some operating system services;
some of it is very specific for unix. 

"
! !

!OperatingSystem class methodsFor:'misc'!

exit
    "shutdown smalltalk immediately"

%{  /* NOCONTEXT */
    mainExit(0);
%}
    "OperatingSystem exit - dont evaluate this"
!

exit:exitCode
    "shutdown smalltalk immediately returning an exit-code"

%{  /* NOCONTEXT */
    if (! _isSmallInteger(exitCode))
        exit(1);
    mainExit(_intVal(exitCode));
%}
    "OperatingSystem exit:1 - dont evaluate this"
! !

!OperatingSystem class methodsFor:'os queries'!

getEnvironment:aString
    "get an environment string"

%{  /* NOCONTEXT */

    char *env;

    if (_isString(aString)) {
        env =  (char *)getenv(_stringVal(aString));
        if (env) {
            RETURN ( _MKSTRING(env COMMA_CON) );
        }
    }
%}
.
    ^ nil

    "OperatingSystem getEnvironment:'LANG'"
!

getProcessId
    "return the processId"

%{  /* NOCONTEXT */

    int pid = 0;
#ifndef transputer
    pid = getpid();
#endif
    RETURN ( _MKSMALLINT(pid) );
%}
    "OperatingSystem getProcessId"
!

getCPUType
    "return a string giving the type of machine we're running on"

    |cpu|
    
    cpu := 'unknown'.

%{  /* NOCONTEXT */
#ifdef vax
    cpu = _MKSTRING("vax" COMMA_CON);
#endif
#ifdef mips
    cpu = _MKSTRING("mips" COMMA_CON);
#endif
#ifdef i386
    cpu = _MKSTRING("i386" COMMA_CON);
#endif
#ifdef ns32k
    cpu = _MKSTRING("ns32k" COMMA_CON);
#endif
#ifdef mc68k
    cpu = _MKSTRING("mc68k" COMMA_CON);
#endif
#ifdef sparc
    cpu = _MKSTRING("sparc" COMMA_CON);
#endif
#if defined(hppa)
    cpu = _MKSTRING("hppa" COMMA_CON);
#endif
#ifdef rs6000
    cpu = _MKSTRING("rs6000" COMMA_CON);
#endif
#ifdef alpha
    cpu = _MKSTRING("alpha" COMMA_CON);
#endif
#ifdef transputer
    cpu = _MKSTRING("transputer" COMMA_CON);
#endif
%}
.
    ^ cpu

    "OperatingSystem getCPUType"
!

getOSType
    "return a string giving the type of os we're running on"

    |os|

    os := 'unknown'.

%{  /* NOCONTEXT */
#ifdef MSDOS
  os = _MKSTRING("msdos" COMMA_CON);
#endif

#ifdef sinix
  os = _MKSTRING("sinix" COMMA_CON);
#endif

#ifdef ultrix
  os = _MKSTRING("ultrix" COMMA_CON);
#endif

#ifdef sco
  os = _MKSTRING("sco" COMMA_CON);
#endif

#ifdef hpux
  os = _MKSTRING("hpux" COMMA_CON);
#endif

#ifdef LINUX
  os = _MKSTRING("linux" COMMA_CON);
#endif

#ifdef BSD
# ifdef MACH
  os = _MKSTRING("mach" COMMA_CON);
# endif

# ifdef sunos
  os = _MKSTRING("sunos" COMMA_CON);
# endif

# ifdef IRIS
  os = _MKSTRING("irix" COMMA_CON);
# endif

  if (os == nil) os = _MKSTRING("bsd" COMMA_CON);
#endif

#ifdef SYSV
# ifdef SYSV3
  os = _MKSTRING("sys5.3" COMMA_CON);
# else
#  ifdef SYSV4
    os = _MKSTRING("sys5.4" COMMA_CON);
#  else
    os = _MKSTRING("sys5" COMMA_CON);
#  endif
# endif
#endif
%}
.
    ^ os

    "OperatingSystem getOSType"
!

getSystemType
    "return a string giving the type of system we're running on"

    |sys|

    sys := 'unknown'.

%{  /* NOCONTEXT */
#ifdef MSDOS
  sys = _MKSTRING("msdos" COMMA_CON);
#endif

#ifdef sinix
  sys = _MKSTRING("sinix" COMMA_CON);
#endif

#ifdef ultrix
  sys = _MKSTRING("ultrix" COMMA_CON);
#endif

#ifdef sco
  sys = _MKSTRING("sco" COMMA_CON);
#endif

#ifdef sunos
  sys = _MKSTRING("sunos" COMMA_CON);
#endif

#ifdef solaris
  sys = _MKSTRING("solaris" COMMA_CON);
#endif

#ifdef NEXT
  sys = _MKSTRING("next" COMMA_CON);
#endif

#ifdef IRIS
  sys = _MKSTRING("iris" COMMA_CON);
#endif

#ifdef LINUX
  sys = _MKSTRING("linux" COMMA_CON);
#endif

#ifdef hpux
  sys = _MKSTRING("hpux" COMMA_CON);
#endif

#ifdef BSD
# ifdef MACH
  if (sys == nil) sys = _MKSTRING("mach" COMMA_CON);
# endif
  if (sys == nil) sys = _MKSTRING("bsd" COMMA_CON);
#endif

#ifdef SYSV
# ifdef SYSV3
  if (sys == nil) sys = _MKSTRING("sys5.3" COMMA_CON);
# else
#  ifdef SYSV4
    if (sys == nil) sys = _MKSTRING("sys5.4" COMMA_CON);
#  else
    if (sys == nil) sys = _MKSTRING("sys5" COMMA_CON);
#  endif
# endif
#endif
%}
.
    ^ sys

    "OperatingSystem getSystemType"
!

getHostName
    "return the hostname we are running on - if there is
     a HOST environment variable, we are much faster here ..."

    |name p|

    name := self getEnvironment:'HOST'.
    name isNil ifTrue:[
        "since fork might be slow on some machines, give a warning ..."
        'please set the HOST shell variable for faster startup' printNewline.

        p := PipeStream readingFrom:'hostname'.
        p notNil ifTrue:[
            name := p nextLine.
            p close
        ]
    ].
    name isNil ifTrue:[
        'cannot find out hostname' printNewline.
    ].
    ^name
!

isBSDlike
    "return true, if the OS we're running on is a real unix."

%{  /* NOCONTEXT */

#ifdef BSD
    RETURN ( true );
#endif
#ifdef SYSV4
    RETURN ( true );
#endif
%}
.
    ^ false
!

maxFileNameLength
    "return the max number of characters in a filename."

%{  /* NOCONTEXT */
#if defined(BSD) || defined(SYSV4) || defined(LONGFILENAMES)
    RETURN ( _MKSMALLINT(255) );
#else
# ifdef SYSV
    RETURN ( _MKSMALLINT(14) );
# endif
# ifdef MSDOS
    RETURN ( _MKSMALLINT(9) );
# endif
#endif
%}
.
    ^ 14
!

supportsIOInterrupts
    "return true, if the OS supports IO availability interrupts 
     (i.e. SIGPOLL/SIGIO).

     Currently, this mechanism does not work at all ..."

%{  /* NOCONTEXT */
#ifdef NOTDEF

#if defined(SIGPOLL) || defined(SIGIO)
# if defined(F_GETFL) && defined(F_SETFL)
#  if defined(FASYNC)
/*
 * mhmh they seem to NOT work on NS2.1
 */
#   if !defined(NEXT)
    RETURN (true);
#   endif
#  endif
# endif
#endif

#endif
%}
.
    ^ false
!

supportsNonBlockingIO
    "return true, if the OS supports nonblocking IO"

%{  /* NOCONTEXT */
#if defined(F_GETFL) && defined(F_SETFL)
# if defined(FNDELAY)
    RETURN (true);
# endif
#endif
%}
.
    ^ false
!

supportsSelect
    "return true, if the OS supports selecting on multiple
     filedescriptors via select."

%{  /* NOCONTEXT */
#if defined(sco)
    /*
     * sco has a broken select - always waiting 1 second
     */
    RETURN(false);
#endif
%}
.
    ^ true
! !

!OperatingSystem class methodsFor:'users & groups'!

getLoginName
    "return a string with the users name"

%{  /* NOCONTEXT */

    char *name = "you";
#ifndef transputer
    name = (char *)getlogin();
    if (! name || (name[0] == 0)) {
        name = (char *)getenv("LOGNAME");
    }
#endif
    RETURN ( _MKSTRING(name COMMA_CON) );
%}
    "OperatingSystem getLogin"
!

getUserNameFromID:aNumber
    "return the user-name-string for a given numeric user-id"

%{  /* NOCONTEXT */

#ifndef transputer
    struct passwd *p;

    if (_isSmallInteger(aNumber)) {
        p = getpwuid(_intVal(aNumber));
        if (p) {
            RETURN ( _MKSTRING(p->pw_name COMMA_CON) );
        }
    }
#endif
%}
.
    ^ '???'

    "OperatingSystem getUserNameFromID:0"
!

getGroupNameFromID:aNumber
    "return the group-name-string for a given numeric group-id"

%{  /* NOCONTEXT */

#ifndef transputer
    struct group *g;

    if (_isSmallInteger(aNumber)) {
        g = getgrgid(_intVal(aNumber));
        if (g) {
            RETURN ( _MKSTRING(g->gr_name COMMA_CON) );
        }
    }
#endif
%}
.
    ^ '???'

    "OperatingSystem getGroupNameFromID:0"
!

getHomeDirectory
    "return the name of the users home directory"

    ^ OperatingSystem getEnvironment:'HOME'

    "OperatingSystem getHomeDirectory"
! !

!OperatingSystem class methodsFor:'error messages'!

lastErrorString
    "return a message string describing the last error"

    ^ self errorTextForNumber:ErrorNumber
!

errorTextForNumber:errNr
    "return a message string from a unix errorNumber 
     (as returned by a system call). Should be replaced by
     a resource lookup."

    |msg messages|

    (Language == #german) ifTrue:[
        messages := #('keine superuser Berechtigung'
                      'ungueltiger Datei- oder VerzeichnisName'
                      nil "'ungueltige Prozessnummer'  "
                      nil "'unterbrochener systemcall' "
                      'E/A Fehler'
                      nil "'Geraet existiert nicht' "
                      'zu viele Argumente'
                      'nicht ausfuehrbar'
                      nil "'falscher FileDescriptor'"
                      nil "'kein Kindprozess'       "
                      'zu viele Prozesse oder zu wenig Speicher'
                      'zu wenig Speicher'
                      'keine ZugriffsBerechtigung'
                      nil "'falsche Adresse'        "
                      nil "'kein Blockgeraet'       "
                      nil "'Platte noch im Zugriff' "
                      'Datei existiert bereits'
                      nil "'Link ueber Plattengrenzen hinweg' "
                      'Geraet existiert nicht'
                      'ist kein Verzeichnis'
                      'ist ein Verzeichnis'
                      nil "'ungueltiges Argument' "
                      'zu viele Dateien offen'
                      'zu viele Dateien offen'
                      nil "'kein Terminalgeraet'  "
                      'Datei wird gerade ausgefuehrt'
                      'Datei zu gross'
                      'Platte ist voll'
                      'ungueltige Positionierung'
                      'Platte ist schreibgeschuetzt'
                      'zu viele Links'
                      'Pipe unterbrochen'
                      'argument nicht im gueltigen Bereich'
                      'Ergebnis nicht im gueltigen Bereich')
    ] ifFalse:[
        messages := #('Not super-user'
                      'No such file or directory'
                      nil "'No such process'   "
                      nil "'interrupted system call' "
                      'I/O error'
                      nil "'No such device or address' "
                      'Arg list too long'
                      'Exec format error'
                      nil "'Bad file number'"
                      nil "'No children'       "
                      'No more processes'
                      'Not enough core'
                      'Permission denied'
                      nil "'Bad address'        "
                      nil "'Block device required'       "
                      nil "'Mount device busy' "
                      'File exists'
                      nil "'Cross-device link' "
                      'No such device'
                      'Not a directory'
                      'Is a directory'
                      nil 'Invalid argument'
                      'File table overflow'
                      'Too many open files'
                      nil "'Not a typewriter' "
                      'Text file busy'
                      'File too large'
                      'No space left on device'
                      'Illegal seek'
                      'Read only file system'
                      'Too many links'
                      'Broken pipe'
                      'Math arg out of domain of func'
                      'Math result not representable')
    ].

    (errNr between:1 and:messages size) ifTrue:[
        msg := messages at:errNr
    ].
    msg isNil ifTrue:[
        ^ ('ErrorNr: ' , errNr printString)
    ].
    ^ msg
! !

!OperatingSystem class methodsFor:'interrupts'!

blockInterrupts
    "needed, for proper semaphore handling"
%{
    BLOCKINTERRUPTS();
%}
!

unblockInterrupts
    "needed, for proper semaphore handling"
%{
    UNBLOCKINTERRUPTS();
%}
!

enableUserInterrupts
    "enable userInterrupt (^C) handling;
     after enabling, ^C will send the message 'userInterrupt'
     to the UserInterruptHandler object."

%{  /* NOCONTEXT */
    extern void userInterrupt();

    signal(SIGINT, userInterrupt);
    /* signal(SIGQUIT, userInterrupt); */
%}
!

enableFpExceptionInterrupts
    "enable floating point exception interrupts (if the
     architecture supports it).
     after enabling, fpu-exceptions will send the message 
     'fpuExceptionInterrupt' to the FPUExceptionInterruptHandler object."

%{  /* NOCONTEXT */
    extern void fpExceptionInterrupt();

    signal(SIGFPE, fpExceptionInterrupt);
%}
!

enableSignalInterrupts
    "enable signal exception interrupts (trap, buserror & segm. violation).
     after enabling, these exceptions will send the message 
     'signalInterrupt' to the SignalInterruptHandler object."

%{  /* NOCONTEXT */
    extern void signalPIPEInterrupt();
    extern void signalBUSInterrupt();
    extern void signalSEGVInterrupt();

    signal(SIGPIPE, signalPIPEInterrupt);
#ifdef SIGBUS
    signal(SIGBUS,  signalBUSInterrupt);
#endif
    signal(SIGSEGV, signalSEGVInterrupt);
%}
!

enableIOInterruptsOn:fd
    "turn on IO interrupts for a filedescriptor"

%{  /* NOCONTEXT */

    int ret, flags;
    extern void ioInterrupt();

#if defined(F_GETFL) && defined(F_SETFL)
# if defined(FASYNC)
    if (_isSmallInteger(fd)) {
#  ifdef SIGPOLL
        signal(SIGPOLL, ioInterrupt);
#  endif
#  ifdef SIGIO
        signal(SIGIO,  ioInterrupt);
#  endif
        flags = fcntl(_intVal(fd), F_GETFL, 0);
        ret = fcntl(_intVal(fd), F_SETFL, flags | FASYNC);
        if (ret >= 0) ret = flags;
        RETURN ( _MKSMALLINT(ret) );
    }
# endif
#endif
#ifdef SIGURG
        signal(SIGURG,  ioInterrupt);
#endif
%}
.
    self primitiveFailed
!

disableIOInterruptsOn:fd
    "turn off IO interrupts for a filedescriptor"

%{  /* NOCONTEXT */

    int ret, flags;

#if defined(F_GETFL) && defined(F_SETFL)
# if defined(FASYNC)
    if (_isSmallInteger(fd)) {
        flags = fcntl(_intVal(fd), F_GETFL, 0);
        ret = fcntl(_intVal(fd), F_SETFL, flags & ~FASYNC);
        if (ret >= 0) ret = flags;
        RETURN ( _MKSMALLINT(ret) );
    }
# endif
#endif
%}
.
    self primitiveFailed
!

enableChildSignalInterrupts
    "enable childSignal interrupts 
     (SIGCHLD, if the architecture supports it).
     after enabling, these signals will send the message 
     'childSignalInterrupt' to the ChildSignalInterruptHandler object."

%{  /* NOCONTEXT */
    extern void signalChildInterrupt();

#ifdef SIGCHLD
    signal(SIGCHLD, signalChildInterrupt);
    RETURN(true);
#else
# ifdef SIGCLD
    signal(SIGCLD, signalChildInterrupt);
    RETURN(true);
# endif
#endif
%}
.
    ^ false
!

startSpyTimer
    "trigger a spyInterrupt, to be signalled after some (short) time.
     This is used by MessageTally for profiling."

%{  /* NOCONTEXT */

    extern void spyInterrupt();
#if defined(ITIMER_VIRTUAL)
    struct itimerval dt;

    dt.it_interval.tv_sec = 0;
    dt.it_interval.tv_usec = 0;
    dt.it_value.tv_sec = 0;
    dt.it_value.tv_usec = 1000;   /* 1000 Hz */
    setitimer(ITIMER_VIRTUAL, &dt, 0);
#ifndef SYSV4
# if defined(BSD) || defined(HAS_SIGSETMASK)
    sigsetmask(0);
#  endif
# endif

# ifdef SIGVTALRM
    signal(SIGVTALRM, spyInterrupt);
# else
    signal(SIGALRM, spyInterrupt);
# endif

    RETURN (true);
#endif
%}
.
    ^ false
!

stopSpyTimer
    "stop spy timing"

%{  /* NOCONTEXT */

#if defined(ITIMER_VIRTUAL)
    struct itimerval dt;

    dt.it_interval.tv_sec = 0;
    dt.it_interval.tv_usec = 0;
    dt.it_value.tv_sec = 0;
    dt.it_value.tv_usec = 0;
    setitimer(ITIMER_VIRTUAL, &dt, 0);
    RETURN (true);
#endif
%}
.
    ^ false
!

enableTimer:millis
    "trigger a timerInterrupt, to be signalled after some time."

%{  /* NOCONTEXT */

    extern void timerInterrupt();
#if defined(ITIMER_REAL)
    struct itimerval dt;

    dt.it_interval.tv_sec = 0;
    dt.it_interval.tv_usec = 0;
    dt.it_value.tv_sec = _intVal(millis) / 1000;
    dt.it_value.tv_usec = (_intVal(millis) % 1000) * 1000;  
    setitimer(ITIMER_REAL, &dt, 0);
#ifndef SYSV4
# if defined(BSD) || defined(HAS_SIGSETMASK)
    sigsetmask(0);
#  endif
# endif
    signal(SIGALRM, timerInterrupt);

    RETURN (true);
#endif
%}
.
    ^ false
!

disableTimer
    "disable timer interrupt"

%{  /* NOCONTEXT */

#if defined(ITIMER_REAL)
    struct itimerval dt;

    dt.it_interval.tv_sec = 0;
    dt.it_interval.tv_usec = 0;
    dt.it_value.tv_sec = 0;
    dt.it_value.tv_usec = 0;
    setitimer(ITIMER_REAL, &dt, 0);
    RETURN (true);
#endif
%}
.
    ^ false
! !

!OperatingSystem class methodsFor:'time and date'!

getTimeLow
    "return low 16 bits of current time. 
     Obsolete: Dont use this method, use getTimeParts below.
     This method will not always return the correct time 
     if used together with getTimeHi.
     (a wrap between the two getTimeXXX calls could occur)"

%{  /* NOCONTEXT */

    RETURN ( _MKSMALLINT(time(0) & 0xFFFF) );
%}
.
    self primitiveFailed

    "OperatingSystem getTimeLow"
!

getTimeHi
    "return hi 16 bits of current time. 
     Obsolete: Dont use this method, use getTimeParts below. 
     This method will NOT always return the correct time
     if used together with getTimeHi.
     (a wrap between the two getTimeXXX calls could occur)"

%{  /* NOCONTEXT */

    RETURN ( _MKSMALLINT((time(0) >> 16) & 0xFFFF) );
%}
.
    self primitiveFailed

    "OperatingSystem getTimeHi"
!

getTimeInto:aBlock
    "evaluate the argument aBlock, passing the time-parts of
     the current time as arguments."

    |low hi|
%{ 
    int now;

    now = time(0);
    hi  = _MKSMALLINT((now >> 16) & 0xFFFF);
    low = _MKSMALLINT(now & 0xFFFF);
%}
.
    aBlock value:low value:hi

    "OperatingSystem getTimeTimeInto:[:low :hi | low printNewline. hi printNewline]"
!

getTime
    "return current Time (in seconds since 1970).
     This might return a LargeInteger some time."

    ^ self getTimeHi * 16r10000 + self getTimeLow

    "OperatingSystem getTime"
!

computeDatePartsOf:timeLow and:timeHi for:aBlock
    "compute year, month and day from the time-parts timeLow and
     timeHi and evaluate the argument, a 3-arg block with these.
     This method was added to avoid LargeInteger arithmetic; the time-parts
     are those returned by getTimeLow and getTimeHi."

    |year month day|

    ((timeLow isMemberOf:SmallInteger) and:[timeHi isMemberOf:SmallInteger])
    ifFalse:[
        ^ self primitiveFailed
    ].
%{
    struct tm *tmPtr;
    long t;

    t = (_intVal(timeHi) << 16) | _intVal(timeLow);
    tmPtr = localtime(&t);
    year = _MKSMALLINT(tmPtr->tm_year + 1900);
    month = _MKSMALLINT(tmPtr->tm_mon + 1);
    day = _MKSMALLINT(tmPtr->tm_mday);
%}
.
    aBlock value:year value:month value:day
!

computeTimePartsOf:timeLow and:timeHi for:aBlock
    "compute hours, minutes and seconds from the time-parts timeLow and
     timeHi and evaluate the argument, a 3-arg block with these."

    |hours minutes seconds|

    ((timeLow isMemberOf:SmallInteger) and:[timeHi isMemberOf:SmallInteger])
    ifFalse:[
        ^ self primitiveFailed
    ].
%{
    struct tm *tmPtr;
    long t;

    t = (_intVal(timeHi) << 16) | _intVal(timeLow);
    tmPtr = localtime(&t);
    hours = _MKSMALLINT(tmPtr->tm_hour);
    minutes = _MKSMALLINT(tmPtr->tm_min);
    seconds = _MKSMALLINT(tmPtr->tm_sec);
%}
.
    aBlock value:hours value:minutes value:seconds
!

getMillisecondTime
    "since range is limited to 0..1ffffff and value is wrapping around
     at 1fffffff, this can only be used for relative time deltas.
     Use methods below to compare and add time deltas (should move to Time)"

%{  /* NOCONTEXT */

    long t;
#ifdef SYSV
# ifdef HZ
    /* sys5 time */
    long ticks;
    struct tms tb;

    ticks = times(&tb);
    t = (ticks * 1000) / HZ;
# endif
#else
    /* bsd time */
    struct timeval tb;
    struct timezone tzb;

    gettimeofday(&tb, &tzb);
    t = tb.tv_sec*1000 + tb.tv_usec/1000;
#endif
    RETURN ( _MKSMALLINT(t & 0x0FFFFFFF) );
%}
.
    self error:'time not available'
!

millisecondTimeDeltaBetween:msTime1 and:msTime2
    "subtract two millisecond times (such as returned getMillisecondTime).
     The returned value is msTime1 - msTime2 where a wrap occurs at:16r0FFFFFFF."

    (msTime1 > msTime2) ifTrue:[
        ^ msTime1 - msTime2
    ].
    ^ msTime1 + 16r10000000 - msTime2
!

millisecondTime:msTime1 isAfter:msTime2
    "return true if msTime1 is after msTime2, false if not.
     handling wrap at 16r0FFFFFFF. The two arguments are
     millisecond times (such as returned getMillisecondTime)."

    (msTime1 > msTime2) ifTrue:[
        ((msTime1 - msTime2) > 16r08000000) ifTrue:[
            ^ false
        ].
        ^ true
    ].
    ((msTime2 - msTime1) > 16r08000000) ifTrue:[
        ^ true
    ].
    ^ false
!

millisecondTimeAdd:msTime1 and:msTime2
    "add two millisecond times (such as returned getMillisecondTime).
     The returned value is msTime1 + msTime2 where a wrap occurs at:16r0FFFFFFF."

    |sum|

    sum := msTime1 + msTime2.
    (sum > 16r0FFFFFFF) ifTrue:[^ sum - 16r10000000].
    (sum < 0) ifTrue:[^ sum + 16r10000000].
    ^ sum
!

millisecondDelay:millis
    "delay execution for millis milliseconds."

    self selectOn:nil withTimeOut:millis

    "OperatingSystem millisecondDelay:2000"
!

sleep:numberOfSeconds
    "cease any action for some time. 
     Not really useful since not even low-prio processes and interrupt
     handling will run during the sleep - use millisecondDelay:."

%{  /* NOCONTEXT */

    if (_isSmallInteger(numberOfSeconds)) {
        sleep(_intVal(numberOfSeconds));
        RETURN ( self );
    }
%}
.
    self primitiveFailed
! !

!OperatingSystem class methodsFor:'waiting for events'!

setBlocking:aBoolean on:fd
    "set/clear the blocking attribute - if set (which is the default)
     a read on the fileDescriptor will block until data is available.
     If cleared, a read operation will immediately return with a value of
     nil."

%{  /* NOCONTEXT */

    int ret, flags;
    int savInt;

#if defined(F_GETFL) && defined(F_SETFL)
# if defined(FNDELAY)
    if (_isSmallInteger(fd)) {
        flags = fcntl(_intVal(fd), F_GETFL, 0);
        if (aBoolean == true) {
            ret = fcntl(_intVal(fd), F_SETFL, flags & ~FNDELAY);
        } else {
            ret = fcntl(_intVal(fd), F_SETFL, flags | FNDELAY);
        }
        if (ret >= 0) ret = flags;
        RETURN ( _MKSMALLINT(ret) );
    }
# endif
#endif
%}
.
    self primitiveFailed
!

readCheck:fd
    "return true, if data is available on a filedescriptor"

    (self selectOnAnyReadable:(Array with:fd)
                     writable:nil
                        error:nil
                  withTimeOut:0) == fd
        ifTrue:[^ true].
    ^ false
!

writeCheck:fd
    "return true, if filedescriptor can be written without blocking"

    (self selectOnAnyReadable:nil
                     writable:(Array with:fd)
                        error:nil
                  withTimeOut:0) == fd
        ifTrue:[^ true].
    ^ false
!

selectOn:fd withTimeOut:millis
    "wait for aFileDesriptor to become ready; timeout after t milliseconds.
     Return true, if i/o ok, false if timed-out or interrupted.
     With 0 as timeout argument, this can be used to check for availability
     of read-data.
     Experimental."

    ^ self selectOnAnyReadable:(Array with:fd)
                      writable:(Array with:fd)
                         error:nil
                   withTimeOut:millis
!

selectOn:fd1 and:fd2 withTimeOut:millis
    "wait for any fd to become ready; timeout after t milliseconds.
     Return fd if i/o ok, nil if timed-out or interrupted.
     Experimental."

    ^ self selectOnAnyReadable:(Array with:fd1 with:fd2)
                      writable:(Array with:fd1 with:fd2)
                         error:nil
                   withTimeOut:millis
!

selectOnAnyReadable:fdArray withTimeOut:millis
    "wait for any fd in fdArray (an Array of integers) to become ready for reading;
     timeout after t milliseconds. An empty set will always wait.
     Return first ready fd if i/o ok, nil if timed-out or interrupted.
     Experimental."

    ^ self selectOnAnyReadable:fdArray 
                      writable:nil 
                         error:nil
                   withTimeOut:millis
!

selectOnAny:fdArray withTimeOut:millis
    "wait for any fd in fdArray (an Array of integers) to become ready;
     timeout after t milliseconds. An empty set will always wait.
     Return first ready fd if i/o ok, nil if timed-out or interrupted.
     Experimental."

    ^ self selectOnAnyReadable:fdArray
                      writable:fdArray
                         error:nil
                   withTimeOut:millis
! 

selectOnAnyReadable:readFdArray writable:writeFdArray error:errorFdArray withTimeOut:millis
    "wait for any fd in readFdArray (an Array of integers) to become ready for reading,
     writeFdArray to become ready for writing.
     timeout after t milliseconds. Empty sets will always wait.
     Return first ready fd if i/o ok, nil if timed-out or interrupted.
     Experimental."

    |rcount wcount ecount|

    (readFdArray notNil and:[readFdArray class ~~ Array]) ifTrue:[
        ^ self error:'argument must be nil or an Array'
    ].
    (writeFdArray notNil and:[writeFdArray class ~~ Array]) ifTrue:[
        ^ self error:'argument must be nil or an Array'
    ].
    (errorFdArray notNil and:[errorFdArray class ~~ Array]) ifTrue:[
        ^ self error:'argument must be nil or an Array'
    ].
    rcount := readFdArray size.
    wcount := writeFdArray size.
    ecount := errorFdArray size.
%{
    fd_set rset, wset, eset;
    int t, f, maxF, i, lX, bX;
    struct timeval wt;
    OBJ fd, retFd;

    if (_isSmallInteger(millis)) {
        FD_ZERO(&rset);
        FD_ZERO(&wset);
        FD_ZERO(&eset);

        maxF = -1;
        for (i=0; i<_intVal(rcount);i++) {
            fd = _ArrayInstPtr(readFdArray)->a_element[i];
            if (fd != nil) {
                f = _intVal(fd);
                if ((f >= 0) && (f < FD_SETSIZE)) {
                    FD_SET(f, &rset);
                    if (f > maxF) maxF = f;
                }
            }
        }
        for (i=0; i<_intVal(wcount);i++) {
            fd = _ArrayInstPtr(writeFdArray)->a_element[i];
            if (fd != nil) {
                f = _intVal(fd);
                if ((f >= 0) && (f < FD_SETSIZE)) {
                    FD_SET(f, &wset);       
                    if (f > maxF) maxF = f;
                }
            }
        }
        for (i=0; i<_intVal(ecount);i++) {
            fd = _ArrayInstPtr(errorFdArray)->a_element[i];
            if (fd != nil) {
                f = _intVal(fd);
                if ((f >= 0) && (f < FD_SETSIZE)) {
                    FD_SET(f, &eset);       
                    if (f > maxF) maxF = f;
                }
            }
        }
        t = _intVal(millis);
        wt.tv_sec = t / 1000;
        wt.tv_usec = (t % 1000) * 1000;

        if (select(maxF+1, &rset, &wset, &eset, &wt)) {
            for (i=0; i <= maxF; i++) {
                if (FD_ISSET(i, &rset)
                 || FD_ISSET(i, &wset)
                 || FD_ISSET(i, &eset)) {
                    RETURN ( _MKSMALLINT(i) );
                }
            }
        }
        RETURN ( nil );
    }
%}
.
    self primitiveFailed
! !

!OperatingSystem class methodsFor:'executing commands'!

fork
    "fork a new process"

%{  /* NOCONTEXT */

    int pid;

    pid = fork();
    RETURN ( _MKSMALLINT(pid) );
%}
.
    self primitiveFailed
!

exec:aPath withArguments:argArray
    "execute the unix command specified by the argument, aPath, with
     arguments in argArray.
     If successful, this method does not return and smalltalk is gone.
     If not sucessfull, false is returned. Normal use is with fork."

%{
    char *argv[64];
    int nargs, i;
    OBJ arg;

    if (_isString(aPath) && _isArray(argArray)) {
        nargs = _arraySize(argArray);
        for (i=0; i < nargs; i++) {
            arg = _ArrayInstPtr(argArray)->a_element[i];
            if (_isString(arg)) {
                argv[i] = (char *) _stringVal(arg);
            }
        }
        argv[i] = NULL;
        execv(_stringVal(aPath), argv);
        /* should not be reached */
        RETURN ( false );
    }
%}
.
    self primitiveFailed
!

executeCommand:aCommandString
    "execute the unix command specified by the argument, aCommandString.
     Return true if successful, false otherwise. Smalltalk is suspended,
     while the command is executing."

%{  /* NOCONTEXT */

    int status;
    extern OBJ ErrorNumber;

    if (_isString(aCommandString)) {
        status = system((char *) _stringVal(aCommandString));
        if (status == 0) {
            RETURN ( true );
        }
        ErrorNumber = _MKSMALLINT(errno);
        RETURN ( false );
    }
%}
.
    self primitiveFailed

    "OperatingSystem executeCommand:'pwd'"
    "OperatingSystem executeCommand:'ls -l'"
    "OperatingSystem executeCommand:'invalidCommand'"
! !

!OperatingSystem class methodsFor:'file access'!

getCharacter
    "read a character from keyboard - this is a blocking low-level
     read provided for debugger and fatal conditions. Use Stdin or
     (even better) the event mechanisms provided."

%{  /* NOCONTEXT */

    RETURN ( _MKSMALLINT(getchar()) );
%}
!

fileSeparator
    "return the character used to separate names in a path.
     This character differs for MSDOS and other systems,
     (but those are currently not supported)"

    ^ $/
!

baseNameOf:aPathString
    "return the baseName of the argument, aPathString
     - thats the file/directory name without leading parent-dirs
     (i.e. OperatingSystem baseNameOf:'/usr/lib/st/file' -> 'file'
       and OperatingSystem baseNameOf:'/usr/lib' -> lib).
     This method does not check if the path is valid 
     (i.e. if these directories really exist)."

    |prev index sep|

    sep := self fileSeparator.
    ((aPathString size == 1) and:[(aPathString at:1) == sep]) ifTrue:[
        ^ aPathString
    ].
    prev := 1.
    [true] whileTrue:[
        index := aPathString indexOf:sep startingAt:prev.
        index == 0 ifTrue:[
            ^ aPathString copyFrom:prev
        ].
        prev := index + 1
    ]

    "OperatingSystem baseNameOf:'/fee/foo/bar'"
    "OperatingSystem baseNameOf:'foo/bar'"
    "OperatingSystem baseNameOf:'../../foo/bar'"
!

directoryNameOf:aPathString
    "return the directoryName of the argument, aPath
     - thats the name of the directory where aPath is
     (i.e. OperatingSystem directoryNameOf:'/usr/lib/st/file' -> '/usr/lib/st'
       and OperatingSystem directoryNameOf:'/usr/lib' -> /usr').
     This method does not check if the path is valid (i.e. if these directories
     really exist)."

    |last index sep sepString|

    sep := self fileSeparator.
    sepString := sep asString.
    (aPathString = sepString) ifTrue:[
        ^ aPathString
    ].
    (aPathString startsWith:sepString) ifFalse:[
        (aPathString endsWith:sepString) ifTrue:[
            ^ aPathString copyFrom:1 to:(aPathString size - 1)
        ].
    ].
    last := 1.
    [true] whileTrue:[
        index := aPathString indexOf:sep startingAt:(last + 1).
        index == 0 ifTrue:[
            (last == 1) ifTrue:[^ sepString].
            ^ aPathString copyFrom:1 to:(last - 1)
        ].
        last := index.
    ]

    "OperatingSystem directoryNameOf:'/fee/foo/bar'"
    "OperatingSystem directoryNameOf:'foo/bar'"
    "OperatingSystem directoryNameOf:'../../foo/bar'"
!

isValidPath:aPathName
    "return true, if 'aPathName' is a valid path name
     (i.e. the file or directory exists)"

%{  /* NOCONTEXT */

    struct stat buf;
    int ret;
    extern errno;

    if (_isString(aPathName)) {
        do {
            ret = stat((char *) _stringVal(aPathName), &buf);
        } while (ret < 0 && errno == EINTR);
        RETURN ( ret ? false : true );
    }
%}
.
    self primitiveFailed
!

isDirectory:aPathName
    "return true, if 'aPathName' is a valid directory path name.
     (i.e. exists and is a directory)"

%{  /* NOCONTEXT */

    struct stat buf;
    int ret;
    extern errno;

    if (_isString(aPathName)) {
        do {
            ret = stat((char *) _stringVal(aPathName), &buf);
        } while (ret < 0 && errno == EINTR);
        if ((ret < 0) || ((buf.st_mode & S_IFMT) != S_IFDIR)) {
            RETURN ( false );
        }
        RETURN ( true );
    }
%}
.
    self primitiveFailed
!

isReadable:aPathName
    "return true, if the file/dir 'aPathName' is readable."

%{  /* NOCONTEXT */

    extern OBJ ErrorNumber;

    if (_isString(aPathName)) {
        if (access(_stringVal(aPathName), R_OK) == 0) {
            RETURN ( true );
        }
        ErrorNumber = _MKSMALLINT(errno);
        RETURN ( false );
    }
%}
.
    self primitiveFailed
!

isWritable:aPathName
    "return true, if the given file is writable"

%{  /* NOCONTEXT */

    extern OBJ ErrorNumber;

    if (_isString(aPathName)) {
        if (access(_stringVal(aPathName), W_OK) == 0) {
            RETURN ( true );
        }
        ErrorNumber = _MKSMALLINT(errno);
        RETURN ( false );
    }
%}
.
    self primitiveFailed
!

isExecutable:aPathName
    "return true, if the given file is executable"

%{  /* NOCONTEXT */

    extern OBJ ErrorNumber;

    if (_isString(aPathName)) {
        if (access(_stringVal(aPathName), X_OK) == 0) {
            RETURN ( true );
        }
        ErrorNumber = _MKSMALLINT(errno);
        RETURN ( false );
    }
%}
.
    self primitiveFailed
!

infoOf:aPathName
    "return an dictionary filled with info for the file 'aPathName';
     info is: (type->t mode->n uid->u gid->g size->s id->ino).
     return nil if such a file does not exist. A dictionary is returned,
     since we might need to add more info in the future without affecting
     existing applications."

    |info type mode uid gid size id atimeLow atimeHi mtimeLow mtimeHi|

    "{ Symbol: directory }"
    "{ Symbol: regular }"
    "{ Symbol: characterSpecial }"
    "{ Symbol: blockSpecial }"
    "{ Symbol: fifo }"
    "{ Symbol: socket }"
    "{ Symbol: symbolicLink }"
    "{ Symbol: unknown }"

%{
    struct stat buf;
    int ret;
    extern errno;

    if (_isString(aPathName)) {
        do {
            ret = stat((char *) _stringVal(aPathName), &buf);
        } while (ret < 0 && errno == EINTR);
        if (ret < 0) {
            ErrorNumber = _MKSMALLINT(errno);
            RETURN ( nil );
        }
        switch (buf.st_mode & S_IFMT) {
            case S_IFDIR:
                type = _directory;
                break;
            case S_IFCHR:
                type = _characterSpecial;
                break;
            case S_IFBLK:
                type = _blockSpecial;
                break;
            case S_IFREG:
                type = _regular;
                break;
#ifdef S_IFLNK
            case S_IFLNK:
                type = _symbolicLink;
                break;
#endif
#ifdef S_IFSOCK
            case S_IFSOCK:
                type = _socket;
                break;
#endif
#ifdef S_IFIFO
            case S_IFIFO:
                type = _fifo;
                break;
#endif
            default:
                type = _unknown;
                break;
        }
        mode = _MKSMALLINT(buf.st_mode & 0777);
        uid = _MKSMALLINT(buf.st_uid);
        gid = _MKSMALLINT(buf.st_gid);
        size = _MKSMALLINT(buf.st_size);
        id = _MKSMALLINT(buf.st_ino);
        atimeLow = _MKSMALLINT(buf.st_atime & 0xFFFF);
        atimeHi = _MKSMALLINT((buf.st_atime >> 16) & 0xFFFF);
        mtimeLow = _MKSMALLINT(buf.st_mtime & 0xFFFF);
        mtimeHi = _MKSMALLINT((buf.st_mtime >> 16) & 0xFFFF);
    }
%}
.
    mode notNil ifTrue:[
        info := IdentityDictionary new.
        info at:#type put:type.
        info at:#mode put:mode.
        info at:#uid put:uid.
        info at:#gid put:gid.
        info at:#size put:size.
        info at:#id put:id.
        info at:#accessTime       put:(Time fromUnixTimeLow:atimeLow and:atimeHi).
        info at:#modificationTime put:(Time fromUnixTimeLow:mtimeLow and:mtimeHi).
        ^ info
   ].
   self primitiveFailed

   "OperatingSystem infoOf:'/'"
   "(OperatingSystem infoOf:'/') at:#uid"
!

accessModeOf:aPathName
    "return a number representing access rights rwxrwxrwx for owner,
     group and others. return nil if such a file does not exist."

    "
     this could have been implemented as:
        (self infoOf:aPathName) at:#mode
     but for huge directory searches the code below is faster
    "

%{  /* NOCONTEXT */

    struct stat buf;
    int ret;
    extern errno;

    if (_isString(aPathName)) {
        do {
            ret = stat((char *) _stringVal(aPathName), &buf);
        } while (ret < 0 && errno == EINTR);
        if (ret < 0) {
            ErrorNumber = _MKSMALLINT(errno);
            RETURN ( nil );
        }
        RETURN ( _MKSMALLINT(buf.st_mode & 0777) );
    }
%}
.
   self primitiveFailed

   "(OperatingSystem accessModeOf:'/') printStringRadix:8"
!

changeAccessModeOf:aPathName to:modeBits
    "change the access rights rwxrwxrwx for owner,
     group and others of aPathName. return true if changed, false
     if such a file does not exist or change was not allowd."

%{  /* NOCONTEXT */

    if (_isString(aPathName) && _isSmallInteger(modeBits)) {
        RETURN ( (chmod((char *) _stringVal(aPathName), _intVal(modeBits) ) < 0) ?
                                false : true );
    }
%}
.
   self primitiveFailed
!

timeOfLastChange:aPathName
    "return the time, when the file was last changed"

    |timeLow timeHi|
%{
    struct stat buf;
    int ret;
    extern errno;
    time_t mtime;

    if (_isString(aPathName)) {
        do {
            ret = stat((char *) _stringVal(aPathName), &buf);
        } while (ret < 0 && errno == EINTR);
        if (ret >= 0) {
            timeLow = _MKSMALLINT(buf.st_mtime & 0xFFFF);
            timeHi = _MKSMALLINT((buf.st_mtime >> 16) & 0xFFFF);
        }
        ErrorNumber = _MKSMALLINT(errno);
    }
%}
.
    timeLow notNil ifTrue:[^ Time fromUnixTimeLow:timeLow and:timeHi].
    self primitiveFailed

    "OperatingSystem timeOfLastChange:'/'"
!

timeOfLastAccess:aPathName
    "return the time, when the file was last accessed"

    |timeLow timeHi|
%{
    struct stat buf;
    time_t mtime;
    int ret;
    extern errno;

    if (_isString(aPathName)) {
        do {
            ret = stat((char *) _stringVal(aPathName), &buf);
        } while (ret < 0 && errno == EINTR);
        if (ret >= 0) {
            timeLow = _MKSMALLINT(buf.st_atime & 0xFFFF);
            timeHi = _MKSMALLINT((buf.st_atime >> 16) & 0xFFFF);
        }
        ErrorNumber = _MKSMALLINT(errno);
    }
%}
.
    timeLow notNil ifTrue:[^ Time fromUnixTimeLow:timeLow and:timeHi].
    self primitiveFailed

    "OperatingSystem timeOfLastAccess:'/'"
!

idOf:aPathName
    "return the fileNumber (i.e. inode number) of a file"

    "
     this could have been implemented as:
        (self infoOf:aPathName) at:#id 
     but for huge directory searches the code below is faster
    "

%{  /* NOCONTEXT */

    struct stat buf;
    int ret;
    extern errno;

    if (_isString(aPathName)) {
        do {
            ret = stat((char *) _stringVal(aPathName), &buf);
        } while (ret < 0 && errno == EINTR);
        if (ret >= 0) {
            RETURN (_MKSMALLINT(buf.st_ino));
        }
        ErrorNumber = _MKSMALLINT(errno);
    }
%}
.
    self primitiveFailed

    "OperatingSystem idOf:'/'"
!

typeOf:aPathName
    "return the type of a file as a symbol"

    "
     this could have been implemented as:
        (self infoOf:aPathName) at:#type 
     but for huge directory searches the code below is faster
    "

%{  /* NOCONTEXT */

    struct stat buf;
    int ret;
    extern errno;

    if (_isString(aPathName)) {
        do {
            ret = stat((char *) _stringVal(aPathName), &buf);
        } while (ret < 0 && errno == EINTR);
        if (ret < 0) {
            ErrorNumber = _MKSMALLINT(errno);
            RETURN ( nil );
        }
        switch (buf.st_mode & S_IFMT) {
            case S_IFDIR:
                RETURN ( _directory );
            case S_IFCHR:
                RETURN ( _characterSpecial );
            case S_IFBLK:
                RETURN ( _blockSpecial );
            case S_IFREG:
                RETURN ( _regular );
#ifdef S_IFLNK
            case S_IFLNK:
                RETURN ( _symbolicLink );
#endif
#ifdef S_IFSOCK
            case S_IFSOCK:
                RETURN ( _socket );
#endif
#ifdef S_IFIFO
            case S_IFIFO:
                RETURN ( _fifo );
#endif
            default:
                RETURN ( _unknown );
        }
    }
%}
.
    self primitiveFailed

    "OperatingSystem typeOf:'/'"
!

createDirectory:newPathName
    "create a new directory with name 'newPathName'.
     Return true if successful, false if failed."

    "since createDirectory is not used too often,
     you'll forgive me using mkdir ..."

    ^ self executeCommand:('mkdir ' , newPathName)

    "OperatingSystem createDirectory:'foo'"
!

recursiveCreateDirectory:dirName
    "create a directory - with all parent dirs if needed.
     Return true if successful, false otherwise. If false
     is returned, a partial created tree may be left,
     which is not cleaned-up here."

    self createDirectory:dirName.
    (self isDirectory:dirName) ifFalse:[
        (self recursiveCreateDirectory:(self directoryNameOf:dirName)) ifFalse:[^ false].
        ^ self createDirectory:dirName
    ].
    ^ (self isDirectory:dirName)

    "OperatingSystem recursiveCreateDirectory:'foo/bar/baz'"
!

removeFile:fullPathName
    "remove the file named 'fullPathName'; return true if successful"

%{  /* NOCONTEXT */

    if (_isString(fullPathName)) {
        RETURN ( (unlink((char *) _stringVal(fullPathName)) >= 0) ? true : false );
    }
%}
.
    self primitiveFailed
!

removeDirectory:fullPathName
    "remove the directory named 'fullPathName'.
     Return true if successful, false if directory is not empty or no permission"

%{  /* NOCONTEXT */

    if (_isString(fullPathName)) {
        RETURN ( (rmdir((char *) _stringVal(fullPathName)) >= 0) ? true : false );
    }
%}
.
    self primitiveFailed
!

recursiveRemoveDirectory:fullPathName
    "remove the directory named 'fullPathName' and all contained files/directories.
     Return true if successful."

    ^ self executeCommand:('rm -rf ' , fullPathName)
!

link:oldPath to:newPath
    "link the file 'oldPath' to 'newPath'. The link will be a hard link.
     Return true if successful, false if not."

%{  /* NOCONTEXT */

    if (_isString(oldPath) && _isString(newPath)) {
        RETURN ( (link((char *) _stringVal(oldPath), (char *) _stringVal(newPath)) >= 0) ?
                                true : false );
    }
%}
.
    self primitiveFailed

    "OperatingSystem link:'foo' to:'bar'"
!

rename:oldPath to:newPath
    "rename the file 'oldPath' to 'newPath'. 
     Return true if sucessfull, false if not"

%{  /* NOCONTEXT */

    if (_isString(oldPath) && _isString(newPath)) {
#if defined(BSD)
        if (rename((char *) _stringVal(oldPath), (char *) _stringVal(newPath)) >= 0) {
            RETURN ( true );
        }
#else
        if (link((char *) _stringVal(oldPath), (char *) _stringVal(newPath)) >= 0) {
            if (unlink((char *) _stringVal(oldPath)) >= 0) {
                RETURN ( true );
            }
            unlink((char *) _stringVal(newPath));
        }
#endif
        RETURN ( false );
    }
%}
.
    self primitiveFailed

    "OperatingSystem rename:'foo' to:'bar'"
! !