Skip to content

Commit

Permalink
[project @ 2003-02-22 04:51:50 by sof]
Browse files Browse the repository at this point in the history
Clean up code&interfaces that deals with timers and asynchrony:

- Timer.{c,h} now defines the platform-independent interface
  to the timing services needed by the RTS. Itimer.{c,h} +
  win32/Ticker.{c,h} defines the OS-specific services that
  creates/destroys a timer.
- For win32 plats, drop the long-standing use of the 'multimedia'
  API timers and implement the ticking service ourselves. Simpler
  and more flexible.
- Select.c is now solely for platforms that use select() to handle
  non-blocking I/O & thread delays. win32/AwaitEvent.c provides
  the same API on the Win32 side.
- support threadDelay on win32 platforms via worker threads.

Not yet compiled up on non-win32 platforms; will do once checked in.
  • Loading branch information
sof committed Feb 22, 2003
1 parent d6b7d20 commit 557947d
Show file tree
Hide file tree
Showing 20 changed files with 373 additions and 226 deletions.
156 changes: 9 additions & 147 deletions ghc/rts/Itimer.c
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
* $Id: Itimer.c,v 1.31 2002/08/16 13:29:06 simonmar Exp $
* $Id: Itimer.c,v 1.32 2003/02/22 04:51:50 sof Exp $
*
* (c) The GHC Team, 1995-1999
*
Expand All @@ -17,12 +17,10 @@
* Hence, we use the old-fashioned @setitimer@ that just about everyone seems
* to support. So much for standards.
*/

/* This is not posix compliant. */
/* #include "PosixSource.h" */

#include "Rts.h"
#if !defined(mingw32_TARGET_OS) /* to the end */
#include "RtsFlags.h"
#include "Timer.h"
#include "Itimer.h"
#include "Proftimer.h"
#include "Schedule.h"
Expand All @@ -39,126 +37,10 @@
# endif
# endif

#if HAVE_WINDOWS_H
# include <windows.h>
#endif

#ifdef HAVE_SIGNAL_H
# include <signal.h>
#endif

static lnat total_ticks = 0;

/* ticks left before next pre-emptive context switch */
static int ticks_to_ctxt_switch = 0;

/* -----------------------------------------------------------------------------
Tick handler
We use the ticker for time profiling.
SMP note: this signal could be delivered to *any* thread. We have
to ensure that it doesn't matter which thread actually runs the
signal handler.
-------------------------------------------------------------------------- */

static
void
#if defined(mingw32_TARGET_OS) || (defined(cygwin32_TARGET_OS) && !defined(HAVE_SETITIMER))

CALLBACK
handle_tick(UINT uID STG_UNUSED, UINT uMsg STG_UNUSED, DWORD dwUser STG_UNUSED,
DWORD dw1 STG_UNUSED, DWORD d STG_UNUSED)
#else
handle_tick(int unused STG_UNUSED)
#endif
{
total_ticks++;

#ifdef PROFILING
handleProfTick();
#endif

if (RtsFlags.ConcFlags.ctxtSwitchTicks > 0) {
ticks_to_ctxt_switch--;
if (ticks_to_ctxt_switch <= 0) {
ticks_to_ctxt_switch = RtsFlags.ConcFlags.ctxtSwitchTicks;
context_switch = 1; /* schedule a context switch */
}
}
}


/*
* Handling timer events under cygwin32 is not done with signal/setitimer.
* Instead of the two steps of first registering a signal handler to handle
* \tr{SIGVTALRM} and then start generating them via @setitimer()@, we use
* the Multimedia API (MM) and its @timeSetEvent@. (Internally, the MM API
* creates a separate thread that will notify the main thread of timer
* expiry). -- SOF 7/96
*
* 11/98: if the cygwin DLL supports setitimer(), then use it instead.
*/

#if defined(mingw32_TARGET_OS) || (defined(cygwin32_TARGET_OS) && !defined(HAVE_SETITIMER))

static LPTIMECALLBACK vtalrm_cback;
static unsigned int vtalrm_id = 0;
static unsigned int period = -1;

int
startVirtTimer(nat ms)
{
/* On Win32 setups that don't have support for
setitimer(), we use the MultiMedia API's timer
support.
The delivery of ticks isn't free; the performance hit should be checked.
*/
unsigned int delay;
TIMECAPS tc;

vtalrm_cback = handle_tick;

if ( timeGetDevCaps(&tc, sizeof(TIMECAPS)) == TIMERR_NOERROR) {
period = tc.wPeriodMin;
delay = timeBeginPeriod(period);
if (delay == TIMERR_NOCANDO) { /* error of some sort. */
return -1;
}
} else {
return -1;
}

#ifdef PROFILING
initProfTimer();
#endif

vtalrm_id =
timeSetEvent(ms, /* event every `delay' milliseconds. */
1, /* precision is within 1 ms */
vtalrm_cback,
TIME_CALLBACK_FUNCTION, /* ordinary callback */
TIME_PERIODIC);

return 0;
}

int
stopVirtTimer()
{
/* Shutdown the MM timer */
if ( vtalrm_id != 0 ) {
timeKillEvent(vtalrm_id);
}
if (period > 0) {
timeEndPeriod(period);
}

return 0;
}

#else
static
int
install_vtalrm_handler(void)
Expand All @@ -174,7 +56,7 @@ install_vtalrm_handler(void)
}

int
startVirtTimer(nat ms)
startTicker(nat ms)
{
# ifndef HAVE_SETITIMER
/* fprintf(stderr, "No virtual timer on this system\n"); */
Expand All @@ -186,10 +68,6 @@ startVirtTimer(nat ms)

timestamp = getourtimeofday();

#ifdef PROFILING
initProfTimer();
#endif

it.it_value.tv_sec = ms / 1000;
it.it_value.tv_usec = 1000 * (ms - (1000 * it.it_value.tv_sec));
it.it_interval = it.it_value;
Expand All @@ -198,7 +76,7 @@ startVirtTimer(nat ms)
}

int
stopVirtTimer()
stopTicker()
{
# ifndef HAVE_SETITIMER
/* fprintf(stderr, "No virtual timer on this system\n"); */
Expand All @@ -213,23 +91,17 @@ stopVirtTimer()
# endif
}

#endif /* !{mingw,cygwin32}_TARGET_OS */

# if 0
/* This is a potential POSIX version */
int
startVirtTimer(nat ms)
startTicker(nat ms)
{
struct sigevent se;
struct itimerspec it;
timer_t tid;

timestamp = getourtimeofday();

#ifdef PROFILING
initProfTimer();
#endif

se.sigev_notify = SIGEV_SIGNAL;
se.sigev_signo = SIGVTALRM;
se.sigev_value.sival_int = SIGVTALRM;
Expand All @@ -243,7 +115,7 @@ startVirtTimer(nat ms)
}

int
stopVirtTimer()
stopTicker()
{
struct sigevent se;
struct itimerspec it;
Expand All @@ -262,11 +134,8 @@ stopVirtTimer()
it.it_interval = it.it_value;
return timer_settime(tid, TIMER_RELTIME, &it, NULL);
}

# endif

#if defined(mingw32_TARGET_OS) || (defined(cygwin32_TARGET_OS) && !defined(HAVE_SETITIMER))
#else
void
block_vtalrm_signal(void)
{
Expand All @@ -288,12 +157,10 @@ unblock_vtalrm_signal(void)

(void) sigprocmask(SIG_UNBLOCK, &signals, NULL);
}
#endif

/* gettimeofday() takes around 1us on our 500MHz PIII. Since we're
* only calling it 50 times/s, it shouldn't have any great impact.
*/
#if !defined(mingw32_TARGET_OS)
unsigned int
getourtimeofday(void)
{
Expand All @@ -302,10 +169,5 @@ getourtimeofday(void)
return (tv.tv_sec * TICK_FREQUENCY +
tv.tv_usec * TICK_FREQUENCY / 1000000);
}
#else
unsigned int
getourtimeofday(void)
{
return ((unsigned int)GetTickCount() * TICK_FREQUENCY) / 1000;
}
#endif

#endif /* !mingw32_TARGET_OS */
22 changes: 9 additions & 13 deletions ghc/rts/Itimer.h
@@ -1,22 +1,18 @@
/* -----------------------------------------------------------------------------
* $Id: Itimer.h,v 1.10 2001/11/27 01:51:23 sof Exp $
* $Id: Itimer.h,v 1.11 2003/02/22 04:51:51 sof Exp $
*
* (c) The GHC Team 1998-2001
*
* Interval timer for profiling and pre-emptive scheduling.
*
* ---------------------------------------------------------------------------*/
#ifndef __ITIMER_H__
#define __ITIMER_H__

# define TICK_FREQUENCY 50 /* ticks per second */
# define TICK_MILLISECS (1000/TICK_FREQUENCY) /* ms per tick */
extern int startTicker( nat ms );
extern int stopTicker ( void );

/* Context switch timing constants. Context switches happen after a
* whole number of ticks, the default being every tick.
*/
#define CS_MIN_MILLISECS TICK_MILLISECS /* milliseconds per slice */

int startVirtTimer( nat ms );
int stopVirtTimer ( void );
void block_vtalrm_signal ( void );
void unblock_vtalrm_signal ( void );
unsigned int getourtimeofday ( void );
extern void block_vtalrm_signal ( void );
extern void unblock_vtalrm_signal ( void );
extern unsigned int getourtimeofday ( void );
#endif /* __ITIMER_H__ */
4 changes: 1 addition & 3 deletions ghc/rts/LdvProfile.c
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
* $Id: LdvProfile.c,v 1.4 2003/01/30 10:06:35 simonmar Exp $
* $Id: LdvProfile.c,v 1.5 2003/02/22 04:51:51 sof Exp $
*
* (c) The GHC Team, 2001
* Author: Sungwoo Park
Expand All @@ -14,8 +14,6 @@
#include "Rts.h"
#include "LdvProfile.h"
#include "RtsFlags.h"
#include "Itimer.h"
#include "Proftimer.h"
#include "Profiling.h"
#include "Stats.h"
#include "Storage.h"
Expand Down
25 changes: 21 additions & 4 deletions ghc/rts/PrimOps.hc
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
* $Id: PrimOps.hc,v 1.104 2003/02/21 05:34:15 sof Exp $
* $Id: PrimOps.hc,v 1.105 2003/02/22 04:51:51 sof Exp $
*
* (c) The GHC Team, 1998-2002
*
Expand All @@ -19,8 +19,11 @@
#include "BlockAlloc.h" /* tmp */
#include "StablePriv.h"
#include "StgRun.h"
#include "Itimer.h"
#include "Timer.h" /* TICK_MILLISECS */
#include "Prelude.h"
#ifndef mingw32_TARGET_OS
#include "Itimer.h" /* getourtimeofday() */
#endif

#ifdef HAVE_SYS_TYPES_H
# include <sys/types.h>
Expand Down Expand Up @@ -1602,15 +1605,29 @@ FN_(waitWritezh_fast)

FN_(delayzh_fast)
{
#ifdef mingw32_TARGET_OS
StgAsyncIOResult* ares;
unsigned int reqID;
#else
StgTSO *t, *prev;
nat target;
#endif
FB_
/* args: R1.i */
ASSERT(CurrentTSO->why_blocked == NotBlocked);
CurrentTSO->why_blocked = BlockedOnDelay;

ACQUIRE_LOCK(&sched_mutex);

#ifdef mingw32_TARGET_OS
/* could probably allocate this on the heap instead */
ares = (StgAsyncIOResult*)RET_STGCALL2(P_,stgMallocBytes,sizeof(StgAsyncIOResult), "asyncWritezh_fast");
reqID = RET_STGCALL1(W_,addDelayRequest,R1.i);
ares->reqID = reqID;
ares->len = 0;
ares->errCode = 0;
CurrentTSO->block_info.async_result = ares;
APPEND_TO_BLOCKED_QUEUE(CurrentTSO);
#else
target = (R1.i / (TICK_MILLISECS*1000)) + getourtimeofday();
CurrentTSO->block_info.target = target;

Expand All @@ -1628,7 +1645,7 @@ FN_(delayzh_fast)
} else {
prev->link = CurrentTSO;
}

#endif
RELEASE_LOCK(&sched_mutex);
JMP_(stg_block_noregs);
FE_
Expand Down
4 changes: 2 additions & 2 deletions ghc/rts/Profiling.c
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
* $Id: Profiling.c,v 1.35 2002/12/19 18:02:13 panne Exp $
* $Id: Profiling.c,v 1.36 2003/02/22 04:51:52 sof Exp $
*
* (c) The GHC Team, 1998-2000
*
Expand All @@ -16,7 +16,7 @@
#include "Profiling.h"
#include "Storage.h"
#include "Proftimer.h"
#include "Itimer.h"
#include "Timer.h"
#include "ProfHeap.h"
#include "Arena.h"
#include "RetainerProfile.h"
Expand Down
4 changes: 2 additions & 2 deletions ghc/rts/Proftimer.c
@@ -1,5 +1,5 @@
/* -----------------------------------------------------------------------------
* $Id: Proftimer.c,v 1.11 2002/12/11 15:36:47 simonmar Exp $
* $Id: Proftimer.c,v 1.12 2003/02/22 04:51:52 sof Exp $
*
* (c) The GHC Team, 1998-1999
*
Expand All @@ -15,7 +15,7 @@

#include "Rts.h"
#include "Profiling.h"
#include "Itimer.h"
#include "Timer.h"
#include "Proftimer.h"
#include "RtsFlags.h"

Expand Down

0 comments on commit 557947d

Please sign in to comment.