Handle a signal

From Rosetta Code
Task
Handle a signal
You are encouraged to solve this task according to the task description, using any language you may know.

Most general purpose operating systems provide interrupt facilities, sometimes called signals. Unhandled signals generally terminate a program in a disorderly manner. Signal handlers are created so that the program behaves in a well-defined manner upon receipt of a signal.


Task

Provide a program that displays a single integer on each line of output at the rate of one integer in each half second.

Upon receipt of the SigInt signal (often created by the user typing ctrl-C) the program will cease printing integers to its output, print the number of seconds the program has run, and then the program will terminate.

Ada

Signal Handler

Ada signal handlers must be defined at the library level. The following package defines a simple signal handler for the SigInt signal. <lang ada>with Ada.Interrupts; use Ada.Interrupts; with Ada.Interrupts.Names; use Ada.Interrupts.Names;

package Sigint_Handler is

     protected Handler is
     entry Wait;
     procedure Handle;
     pragma Interrupt_Handler(Handle);
     pragma Attach_Handler(Handle, Sigint);
     private
     Call_Count : Natural := 0;
  end Handler;

end Sigint_Handler;</lang> <lang ada>package body Sigint_Handler is

  -------------
  -- Handler --
  -------------
  protected body Handler is
     ----------
     -- Wait --
     ----------
     entry Wait when Call_Count > 0 is
     begin
        Call_Count := Call_Count - 1;
     end Wait;
     ------------
     -- Handle --
     ------------
     procedure Handle is
     begin
        Call_Count := Call_Count + 1;
     end Handle;
  end Handler;

end Sigint_Handler;</lang> A signal may be received at any time in a program. Ada signal handling requires a task to suspend on an entry call for the handler which is executed only when the signal has been received. The following program uses the interrupt handler defined above to deal with receipt of SigInt. <lang ada>with Ada.Calendar; use Ada.Calendar; with Ada.Text_Io; use Ada.Text_Io; with Sigint_Handler; use Sigint_Handler;

procedure Signals is

  task Counter is
     entry Stop;
  end Counter;
  task body Counter is
     Current_Count : Natural := 0;
  begin
     loop
        select
           accept Stop;
           exit;
        or delay 0.5;
        end select;
        Current_Count := Current_Count + 1;
        Put_Line(Natural'Image(Current_Count));
     end loop;
  end Counter;
  task Sig_Handler;
  
  task body Sig_Handler is
     Start_Time : Time := Clock;
     Sig_Time : Time;
  begin
     Handler.Wait;
     Sig_Time := Clock;
     Counter.Stop;
     Put_Line("Program execution took" & Duration'Image(Sig_Time - Start_Time) & " seconds");
  end Sig_Handler;
     

begin

  null;
        

end Signals;</lang>

Output:
 1
 2
 3
 4
 5
 6
 7
 8
Program execution took 4.348057086 seconds

AutoHotkey

<lang AutoHotkey>Start:=A_TickCount counter=0 SetTimer, timer, 500 return

timer: Send % ++Counter "`n" return

^c:: SetTimer, timer, off SetFormat, float, 0.3 Send, % "Task took " (A_TickCount-Start)/1000 " Seconds" ExitApp return</lang>

Output:
1
2
3
4
5
6
Task took 3.526 Seconds

BaCon

<lang freebasic>' Handle signal SUB Finished

   SIGNAL SIG_DFL, SIGINT    : ' Restore SIGINT to default
   PRINT "Running for", TIMER / 1000.0, "seconds" FORMAT "%s %f %s\n"
   STOP SIGINT               : ' Send another terminating SIGINT

ENDSUB

SIGNAL Finished, SIGINT iter = 1 WHILE TRUE

   SLEEP 500
   PRINT iter
   iter = iter + 1

WEND</lang>

Output:
$ ./handle-signal
1
2
3
^CRunning for 1.766000 seconds

BBC BASIC

This program runs only in console mode; it must be compiled and then run as an EXE. <lang bbcbasic> REM!Exefile C:\bbcsigint.exe,encrypt,console

     INSTALL @lib$+"CALLBACK"
     CTRL_C_EVENT = 0
     
     SYS "GetStdHandle", -10 TO @hfile%(1)
     SYS "GetStdHandle", -11 TO @hfile%(2)
     *INPUT 13
     *OUTPUT 14
     ON ERROR PRINT REPORT$ : QUIT ERR
     
     CtrlC% = FALSE
     handler% = FN_callback(FNsigint(), 1)
     SYS FN_syscalls("SetConsoleCtrlHandler"), handler%, 1 TO !FN_systo(res%)
     IF res%=0 PRINT "Could not set SIGINT handler" : QUIT 1
     
     PRINT "Press Ctrl+C to test...."
     TIME = 0
     Time% = 50
     REPEAT
       WAIT 1
       IF TIME > Time% THEN
         PRINT Time%
         Time% += 50
       ENDIF
     UNTIL CtrlC%
     PRINT "Ctrl+C was pressed after "; TIME/100 " seconds."
     QUIT
     
     DEF FNsigint(T%)
     CASE T% OF
       WHEN CTRL_C_EVENT: CtrlC% = TRUE : = 1
     ENDCASE
     = 0</lang>
Output:
C:\>bbcsigint
Press Ctrl+C to test....
        50
       100
       150
       200
       250
Ctrl+C was pressed after 2.72 seconds.

C:\>

C

Library: POSIX

Standard C's sleep() only provides one-second resolution, so the POSIX usleep() function is used here. (POSIX is not needed for the actual signal handling part.) <lang C>#include <stdio.h>

  1. include <stdlib.h> // for exit()
  2. include <signal.h>
  3. include <time.h> // for clock()
  4. include <unistd.h> // for POSIX usleep()

volatile sig_atomic_t gotint = 0;

void handleSigint() {

   /*
    * Signal safety: It is not safe to call clock(), printf(),
    * or exit() inside a signal handler. Instead, we set a flag.
    */
   gotint = 1;

}

int main() {

   clock_t startTime = clock();
   signal(SIGINT, handleSigint);
   int i=0;
   for (;;) {
       if (gotint)
           break;
       usleep(500000);
       if (gotint)
           break;

printf("%d\n", ++i);

   }
   clock_t endTime = clock();
   double td = (endTime - startTime) / (double)CLOCKS_PER_SEC;
   printf("Program has run for %5.3f seconds\n", td);
   return 0;

}</lang>

Output:
1
2
3
Program has run for 1.953 seconds

C#

Signals in C# are called events, and are handled by attaching event handler functions to the event, which are called when the event is triggered.

<lang csharp>using System; //DateTime, Console, Environment classes class Program {

   static DateTime start;
   static void Main(string[] args)
   {
       start = DateTime.Now;
       //Add event handler for Ctrl+C command
       Console.CancelKeyPress += new ConsoleCancelEventHandler(Console_CancelKeyPress);
       int counter = 0;
       while (true)
       {
           Console.WriteLine(++counter);
           System.Threading.Thread.Sleep(500);
       }
   }
   static void Console_CancelKeyPress(object sender, ConsoleCancelEventArgs e)
   {
       var end = DateTime.Now;
       Console.WriteLine("This program ran for {0:000.000} seconds.", (end - start).TotalMilliseconds / 1000);
       Environment.Exit(0);
   }

}</lang>

Clojure

(= (- Java verbosity) Clojure)

<lang Clojure>(require 'clojure.repl)

(def start (System/nanoTime))

(defn shutdown [_]

 (println "Received INT after"
          (/ (- (System/nanoTime) start) 1e9)
          "seconds.")
 (System/exit 0))

(clojure.repl/set-break-handler! shutdown)

(doseq [i (range)]

 (prn i)
 (Thread/sleep 500))</lang>

COBOL

Works with GnuCOBOL 2.0 <lang cobol>

      identification division.
      program-id. signals.
      data division.
      working-storage section.
      01 signal-flag  pic 9 external.
         88 signalled value 1.
      01 half-seconds usage binary-long.
      01 start-time   usage binary-c-long.
      01 end-time     usage binary-c-long.
      01 handler      usage program-pointer.
      01 SIGINT       constant as 2.
      procedure division.
      call "gettimeofday" using start-time null
      set handler to entry "handle-sigint"
      call "signal" using by value SIGINT by value handler
      perform until exit
          if signalled then exit perform end-if
          call "CBL_OC_NANOSLEEP" using 500000000
          if signalled then exit perform end-if
          add 1 to half-seconds
          display half-seconds
      end-perform
      call "gettimeofday" using end-time null
      subtract start-time from end-time
      display "Program ran for " end-time " seconds"
      goback.
      end program signals.
      identification division.
      program-id. handle-sigint.
      data division.
      working-storage section.
      01 signal-flag  pic 9 external.
      linkage section.
      01 the-signal   usage binary-long.
      procedure division using by value the-signal returning omitted.
      move 1 to signal-flag
      goback.
      end program handle-sigint.

</lang>

Output:
prompt$ cobc -x -j signals.cob
+0000000001
+0000000002
+0000000003
+0000000004
+0000000005
^CProgram ran for +00000000000000000002 seconds
prompt$

Common Lisp

Each Common Lisp implementation will handle signals differently, although a multi-implementation approach can be done using cffi. The full list of signal number can be found on [1]. Tested on SBCL 1.2.7 and ECL 13.5.1. <lang lisp> (ql:quickload :cffi)

(defvar *SIGINT* 2)

(defmacro set-signal-handler (signo &body body)

 (let ((handler (gensym "HANDLER")))
   `(progn
      (cffi:defcallback ,handler :void ((signo :int))
        (declare (ignore signo))
        ,@body)
      (cffi:foreign-funcall "signal" :int ,signo :pointer (cffi:callback ,handler)))))

(defvar *initial* (get-internal-real-time))

(set-signal-handler *SIGINT*

 (format t "Ran for ~a seconds~&" (/ (- (get-internal-real-time) *initial*) internal-time-units-per-second))
 (quit))

(let ((i 0))

 (loop do
   (format t "~a~&" (incf i))
   (sleep 0.5)
 )

)

</lang>

Output:
1
2
3
4
5
6
7
8
9
10
Ran for 4901/1000 seconds

Forth

Works with: GNU Forth

Normally Gforth handles most signals (e.g., the user interrupt SIGINT, or the segmentation violation SIGSEGV) by translating it into a Forth THROW.

<lang forth>-28 constant SIGINT

numbers ( n -- n' )
 begin dup . cr  1+  500 ms again ;
main
 utime
 0 begin
   ['] numbers catch
   SIGINT =
 until drop
 utime d- dnegate
 <# # # # # # # [char] . hold #s #> type ."  seconds" ;

main bye</lang>

F#

<lang fsharp>open System

let rec loop n = Console.WriteLine( n:int )

                Threading.Thread.Sleep( 500 )
                loop (n + 1)

let main() =

  let start = DateTime.Now
  Console.CancelKeyPress.Add(
     fun _ -> let span = DateTime.Now - start
              printfn "Program has run for %.0f seconds" span.TotalSeconds
            )
  loop 1

main()</lang>

Go

<lang go>package main

import (

   "fmt"
   "os"
   "os/signal"
   "time"

)

func main() {

   start := time.Now()
   k := time.Tick(time.Second / 2)
   sc := make(chan os.Signal, 1)
   signal.Notify(sc, os.Interrupt)
   for n := 1; ; {
       // not busy waiting, this blocks until one of the two
       // channel operations is possible
       select {
       case <-k:
           fmt.Println(n)
           n++
       case <-sc:
           fmt.Printf("Ran for %f seconds.\n",
               time.Now().Sub(start).Seconds())
           return
       }
   }

}</lang>

Output:
1
2
3
^C
Ran for 1.804877 seconds.

Haskell

<lang haskell>import Prelude hiding (catch) import Control.Exception (catch, throwIO, AsyncException(UserInterrupt)) import Data.Time.Clock (getCurrentTime, diffUTCTime) import Control.Concurrent (threadDelay)

main = do t0 <- getCurrentTime

         catch (loop 0)
               (\e -> if e == UserInterrupt
                        then do t1 <- getCurrentTime
                                putStrLn ("\nTime: " ++ show (diffUTCTime t1 t0))
                        else throwIO e)

loop i = do print i

           threadDelay 500000 {- µs -}
           loop (i + 1)</lang>

HicEst

Subroutines "F2" to "F9" can be called any time by the F2...F9 keys or by a mouse click on the toolbar buttons "F2" to "F9". These buttons appear as soon as a SUBROUTINE "F2" to "F9" statement is compiled: <lang HicEst>seconds = TIME()

DO i = 1, 1E100  ! "forever"

 SYSTEM(WAIT = 500) ! milli seconds
 WRITE(Name) i

ENDDO

SUBROUTINE F2  ! call by either the F2 key, or by a toolbar-F2 click

  seconds = TIME() - seconds
  WRITE(Messagebox, Name) seconds
  ALARM(999)        ! quit immediately

END</lang>

Icon and Unicon

The following works in Unicon. I don't know if it works in Icon.

<lang unicon>global startTime

procedure main()

   startTime := &now
   trap("SIGINT", handler)
   every write(seq()) do delay(500)

end

procedure handler(s)

   stop("\n",&now-startTime," seconds")

end</lang>

Sample run:

->signal
1
2
3
4
^C
2 seconds
->

Java

Use of sun.misc.SignalHandler allows one to specify which signal to catch, though is unsupported and potentially not available in all JVMs

<lang java>import sun.misc.Signal; import sun.misc.SignalHandler;

public class ExampleSignalHandler {

   public static void main(String... args) throws InterruptedException {
       final long start = System.nanoTime();
       Signal.handle(new Signal("INT"), new SignalHandler() {
           public void handle(Signal sig) {
               System.out.format("\nProgram execution took %f seconds\n", (System.nanoTime() - start) / 1e9f);
               System.exit(0);
           }
       });
       int counter = 0;
       while(true) {
           System.out.println(counter++);
           Thread.sleep(500);
       }
   }

} </lang>

Or one can use a generic shutdown hook as follows, though a reference to the particular signal is not available.

<lang java>public class ExampleSignalHandler {

   public static void main(String... args) throws InterruptedException {
       final long start = System.nanoTime();
       Runtime.getRuntime().addShutdownHook(new Thread(new Runnable() {
           public void run() {
               System.out.format("\nProgram execution took %f seconds\n", (System.nanoTime() - start) / 1e9f);
           }
       }));
       int counter = 0;
       while(true) {
           System.out.println(counter++);
           Thread.sleep(500);
       }
   }

} </lang>

Output:
node hsignal.js
1
2
3
4
5
6
7
8
9
4.5 seconds elapsed

JavaScript

Based on NodeJS interpreter/engine <lang javascript>(function(){

   var count=0
       secs=0
   
   var i= setInterval( function (){
       count++
       secs+=0.5
       console.log(count)
   }, 500);
   
   process.on('SIGINT', function() {
       clearInterval(i)
       console.log(secs+' seconds elapsed');
       process.exit()
   });

})(); </lang>

Output:
node hsignal.js
1
2
3
4
5
6
7
8
9
4.5 seconds elapsed

Julia

<lang Julia> ccall(:jl_exit_on_sigint, Void, (Cint,), 0) tic() ticks = 0 try

   while true
       sleep(0.5)
       ticks += 1
       println(ticks)
   end

end println() toc() </lang> The tricky bit for this task is the ccall, which tells the main() running Julia to pass SIGINT on to Julia as an error. This call is not needed when running this code in Julia's REPL, which has the desired behavior by default.

Output:
1
2
3
4
5
6
7
8
9
^C
elapsed time: 4.689995572 seconds

Liberty BASIC

Liberty BASIC cannot react to a SigInt signal and truly kill itself. The best it can do is respond to Ctrl-C by exiting normally. <lang lb> nomainwin WindowHeight=DisplayHeight open "Handle a signal" for graphics as #1

  1. 1 "trapclose [quit]"
  2. 1 "down;setfocus;place 10 20"
  3. 1 "\Press CTRL + C to stop."
  4. 1 "when characterInput [keyPressed]"

start=time$("ms") timer 500, [doPrint] wait [quit] close #1:end

[doPrint]

 if sigInt then
   timer 0
   #1 "\Seconds elapsed: ";(time$("ms")-start)/1000
  else
   i=i+1
   if i mod 20 = 0 then #1 "cls;place 10 20"
   #1 "\";i
 end if
 wait

[keyPressed]

 if len(Inkey$)>1 then
   if left$(Inkey$,1)=chr$(8) then sigCtrl=1 else sigCtrl=0
 end if
 if sigCtrl=1 and Inkey$=chr$(3) then sigInt=1
 wait
</lang>

MATLAB

MATLAB versions 6.5 (R13) and newer can no longer catch CTRL+C with a try-catch block. The onCleanup() function was introduced in version 7.6 (R2008a), possibly specifically for this situation. However, the designated onCleanup() function will execute no matter how the function ends (task completion, CTRL+C, exception), and CTRL+C will still cause an exception to be thrown and displayed.

Works with: MATLAB version 7.6 (R2008a) and later

<lang MATLAB>function sigintHandle

   k = 1;
   tic
   catchObj = onCleanup(@toc);
   while true
       pause(0.5)
       fprintf('%d\n', k)
       k = k+1;
   end

end</lang>

Output:
>> sigintCleanup
1
2
3
4
5
6
Elapsed time is 3.348772 seconds.
??? Operation terminated by user during ==> sigintHandle at 6
Works with: MATLAB version 6.1 (R12.1) and earlier
This example is untested. Please check that it's correct, debug it as necessary, and remove this message.


<lang MATLAB>function sigintHandle

   k = 1;
   tic
   try
       while true
           pause(0.5)
           fprintf('%d\n', k)
           k = k+1;
       end
   catch me
       toc
       rethrow me
   end

end</lang>

NewLISP

<lang NewLISP>; Mac OSX, BSDs or Linux only, not Windows (setq start-time (now))

(signal 2 (lambda()

           (println
            (format "Program has run for %d seconds"
                    (- (apply date-value (now))
                       (apply date-value start-time))))
           (exit 0)))

(while (println (++ i))

 (sleep 500))</lang>

Nim

<lang nim>import times, os, strutils

let t = epochTime()

proc handler() {.noconv.} =

 echo "Program has run for ", formatFloat(epochTime() - t, precision = 0), " seconds."
 quit 0

setControlCHook(handler)

for n in 1 .. <int64.high:

 sleep 500
 echo n</lang>

Or if you prefer an exception to be thrown on SIGINT: <lang nim>import times, os, strutils

type EKeyboardInterrupt = object of Exception

proc handler() {.noconv.} =

 raise newException(EKeyboardInterrupt, "Keyboard Interrupt")

setControlCHook(handler)

let t = epochTime()

try:

 for n in 1 .. <int64.high:
   sleep 500
   echo n

except EKeyboardInterrupt:

 echo "Program has run for ", formatFloat(epochTime() - t, precision = 0), " seconds."</lang>

OCaml

OCaml's Unix.sleep doesn't handle non-integral arguments, so this program prints a number every second.

<lang ocaml>#load "unix.cma";; (* for sleep and gettimeofday; not needed for the signals stuff per se *)

let start = Unix.gettimeofday ();;

Sys.set_signal Sys.sigint

 (Sys.Signal_handle (fun _signum ->
                       Printf.printf "Ran for %f seconds.\n"
                         (Unix.gettimeofday () -. start);
                       exit 0));;

let rec loop n =

 Printf.printf "%d\n%!" n;
 Unix.sleep 1;
 loop (n + 1)

in

 loop 1;;</lang>

Perl

Perl's (in fact Unix's) sleep doesn't handle non-integral arguments correctly on some platforms, so this program uses the select syscall for timeout.

<lang perl>my $start = time;

$SIG{INT} = sub

  {print 'Ran for ', time - $start, " seconds.\n";
   exit;};

for (my $n = 0 ;; select(undef, undef, undef, .5))

  {print ++$n, "\n";}</lang>

This example does the required task: <lang perl>use 5.010; use AnyEvent; my $start = AE::time; my $exit = AE::cv; my $int = AE::signal 'INT', $exit; my $n; my $num = AE::timer 0, 0.5, sub { say $n++ }; $exit->recv; say " interrupted after ", AE::time - $start, " seconds";</lang>

Output:
0
1
2
3
4
5
6
7
8
9
10
^C interrupted after 5.23734092712402 seconds

Perl 6

We note with glee that the task does not require us to print consecutive integers, so we'll print Fibonacci numbers instead. :-) <lang perl6>signal(SIGINT).tap: {

   note "Took { now - INIT now } seconds.";
   exit;

}

for 0, 1, *+* ... * {

   sleep 0.5;
   .say;

}</lang>

Output:
0
1
1
2
3
5
8
13
21
34
55
89
^CTook 6.3437449 seconds.
Aborted

PHP

Translation of: Perl

<lang php><?php declare(ticks = 1);

$start = microtime(YES);

function mySigHandler() {

 global $start;
 $elapsed = microtime(YES) - $start;
 echo "Ran for $elapsed seconds.\n";
 exit();

}

pcntl_signal(SIGINT, 'mySigHandler');

for ($n = 0; ; usleep(500000)) // 0.5 seconds

  echo ++$n, "\n";

?></lang>

PicoLisp

Put the following into a file, set it to executable, and run it <lang PicoLisp>#!/usr/bin/picolisp /usr/lib/picolisp/lib.l

(push '*Bye '(println (*/ (usec) 1000000)) '(prinl))

(let Cnt 0

  (loop
     (println (inc 'Cnt))
     (wait 500) ) )</lang>

PL/I

<lang> handler: procedure options (main);

  declare i fixed binary (31);
  declare (start_time, finish_time) float (18);
  on attention begin;
     finish_time = secs();
     put skip list ('elapsed time =', finish_time - start_time, 'secs');
     stop;
  end;
  start_time = secs();
  do i = 1 by 1;
     delay (500);
     put skip list (i);
  end;

end handler; </lang>

PowerShell

<lang powershell> $Start_Time = (Get-date).second Write-Host "Type CTRL-C to Terminate..." $n = 1 Try {

   While($true)
   {
       Write-Host $n
       $n ++
       Start-Sleep -m 500
   }

} Finally {

   $End_Time = (Get-date).second
   $Time_Diff = $End_Time - $Start_Time
   Write-Host "Total time in seconds"$Time_Diff

} </lang>

Output:
PS F:\> . .\signal.ps1
Type CTRL-C to Terminate...
1
2
3
4
5
Total time in seconds 2

PureBasic

This code is for Windows only due to the usage of SetConsoleCtrlHandler() <lang PureBasic>CompilerIf #PB_Compiler_OS<>#PB_OS_Windows

 CompilerError "This code is Windows only"

CompilerEndIf

Global Quit, i, T0=ElapsedMilliseconds(), T1

Procedure CtrlC()

 T1=ElapsedMilliseconds()
 Quit=1
 While i: Delay(1): Wend 

EndProcedure

If OpenConsole()

 SetConsoleCtrlHandler_(@CtrlC(),#True)  
 While Not Quit
   PrintN(Str(i))
   i+1
   Delay(500)
 Wend
 PrintN("Program has run for "+StrF((T1-T0)/1000,3)+" seconds.")
 Print ("Press ENTER to exit."):Input(): i=0

EndIf</lang>

0
1
2
3
4
Program has run for 2.121 seconds.
Press ENTER to exit.

Python

Simple version <lang python>import time

def counter():

   n = 0
   t1 = time.time()
   while True:
       try:
           time.sleep(0.5)
           n += 1
           print n
       except KeyboardInterrupt, e:
           print 'Program has run for %5.3f seconds.' % (time.time() - t1)
           break

counter()</lang> The following example should work on all platforms. <lang python>import time

def intrptWIN():

  procDone = False
  n = 0
  while not procDone:
     try:
        time.sleep(0.5)
        n += 1
        print n
     except KeyboardInterrupt, e:
        procDone = True

t1 = time.time() intrptWIN() tdelt = time.time() - t1 print 'Program has run for %5.3f seconds.' % tdelt</lang>

There is a signal module in the standard distribution that accomodates the UNIX type signal mechanism. However the pause() mechanism is not implemented on Windows versions. <lang python>import signal, time, threading done = False n = 0

def counter():

  global n, timer
  n += 1
  print n
  timer = threading.Timer(0.5, counter)
  timer.start()

def sigIntHandler(signum, frame):

  global done
  timer.cancel()
  done = True

def intrptUNIX():

  global timer
  signal.signal(signal.SIGINT, sigIntHandler)
  timer = threading.Timer(0.5, counter)
  timer.start()
  while not done:
     signal.pause()

t1 = time.time() intrptUNIX() tdelt = time.time() - t1 print 'Program has run for %5.3f seconds.' % tdelt</lang>

How about this one? It should work on all platforms; and it does show how to install a signal handler: <lang python>import time, signal

class WeAreDoneException(Exception):

   pass

def sigIntHandler(signum, frame):

   signal.signal(signal.SIGINT, signal.SIG_DFL) # resets to default handler
   raise WeAreDoneException

t1 = time.time()

try:

   signal.signal(signal.SIGINT, sigIntHandler)
   n = 0
   while True:
       time.sleep(0.5)
       n += 1
       print n

except WeAreDoneException:

   pass

tdelt = time.time() - t1 print 'Program has run for %5.3f seconds.' % tdelt</lang>

Racket

<lang racket>

  1. lang racket

(define now current-milliseconds) (define start (now)) (with-handlers ([exn:break?

                (λ(x)
                  (define elapsed (/ (- (now) start) 1000.))
                  (displayln (~a "Total time: " elapsed)))])
 (for ([i (in-naturals)])
   (displayln i)
   (sleep 0.5)))

</lang>

Output:

<lang racket> 0 1 2 3 4 5 6 7 Total time: 3.965 </lang>

REXX

REXX has no   sleep   function that is built into the language.

Some operating systems that REXX runs under have a   SLEEP   or equivalent BIF.


But, there's more than one way to skin a cat.   (No offense to cat lovers.) <lang rexx>/*REXX program displays integers until a Ctrl─C is pressed, then shows the number of */ /*────────────────────────────────── seconds that have elapsed since start of execution.*/ call time 'Reset' /*reset the REXX elapsed timer. */ signal on halt /*HALT: signaled via a Ctrl─C in DOS.*/

  do j=1                                        /*start with  unity  and go ye forth.  */
  say right(j,20)                               /*display the integer right-justified. */
  t=time('E')                                   /*get the REXX elapsed time in seconds.*/
               do forever;   u=time('Elapsed')  /* "   "    "     "      "   "    "    */
               if u<t | u>t+.5  then iterate j  /* ◄═══ passed midnight or  ½  second. */
               end   /*forever*/
  end   /*j*/

halt: say 'program HALTed, it ran for' format(time("ELapsed"),,2) 'seconds.'

                                                /*stick a fork in it,  we're all done. */</lang>

output

                   1
                   2
                   3
                   4
                   5
                   6
                   7
                   8
                   9
                  10
                  11
                  12
                  13
                  14
                  15
                  16
                  17
                  18
                  19
                  20
                  21
                  22
^C                    ◄■■■■■■■■■■■■■ this where (and when) the user pressed the  Crtl-C  buttons.
program HALTed, it ran for 11.53 seconds.

Note: some REXX interpreters don't show the

^C

when   Ctrl-C   is pressed.

Ruby

<lang ruby>t1 = Time.now

catch :done do

 Signal.trap('INT') do
   Signal.trap('INT', 'DEFAULT') # reset to default
   throw :done
 end
 n = 0
 loop do
   sleep(0.5)
   n += 1
   puts n
 end

end

tdelt = Time.now - t1 puts 'Program has run for %5.3f seconds.' % tdelt</lang>

Scala

Library: Scala

<lang Scala>import sun.misc.Signal import sun.misc.SignalHandler

object SignalHandl extends App {

 val start = System.nanoTime()
 var counter = 0
 Signal.handle(new Signal("INT"), new SignalHandler() {
   def handle(sig: Signal) {
     println(f"\nProgram execution took ${(System.nanoTime() - start) / 1e9f}%f seconds\n")
     exit(0)
   }
 })
 while (true) {
   counter += 1
   println(counter)
   Thread.sleep(500)
 }

}</lang>

Sidef

<lang ruby>var start = Time.sec;   Sig.INT { |_|

   Sys.say("Ran for #{Time.sec - start} seconds.");
   Sys.exit;

}   { |i|

   Sys.say(i);
   Sys.sleep(0.5);

} * Math.inf;</lang>

Output:
1
2
3
4
^CRan for 2 seconds.

Smalltalk

Works with: Smalltalk/X

<lang smalltalk>|n|

n := 0. UserInterrupt

    catch:[
        [true] whileTrue:[
            n := n + 1.
            n printCR.
            Delay waitForSeconds: 0.5.
        ]
    ]</lang>

or: <lang smalltalk>[ ... do something... ] on: UserInterrupt do: [:exInfo | ...handler... ]</lang>

attaching an OS-signal (unix signal) to an exception or signal instance: <lang smalltalk>|mySignal| mySignal := Signal new mayProceed: false. OperatingSytem operatingSystemSignal: (OperatingSystem signalNamed:'SIGHUP') install: mySignal. [

  .. do something...

] on: mySignal do:[

  ... handle SIGHUP gracefully...

]</lang> As the runtime system already catches common unix signals and arranges for an OSError to be raised, user code normally does not need to care for this (except for those who want to change that very runtime system behavior ;-).

Swift

Translation of: C

<lang swift>import Foundation

let startTime = NSDate() var signalReceived: sig_atomic_t = 0

signal(SIGINT) { signal in signalReceived = 1 }

for var i = 0;; {

   if signalReceived == 1 { break }
   usleep(500_000)
   if signalReceived == 1 { break }
   print(++i)

}

let endTime = NSDate() print("Program has run for \(endTime.timeIntervalSinceDate(startTime)) seconds")

</lang>

Tcl

Core Tcl does not have signal handling. However the Expect and TclX extension packages do.

Using Expect: <lang tcl>package require Expect

proc sigint_handler {} {

   puts "elapsed time: [expr {[clock seconds] - $::start_time}] seconds"
   set ::looping false

}

trap sigint_handler SIGINT

set start_time [clock seconds] set n 0 set looping true while {$looping} {

   puts [incr n]
   after 500

}</lang>

Similarly, with TclX: <lang tcl>package require Tclx

proc sigint_handler {} {

   puts "elapsed time: [expr {[clock seconds] - $::start_time}] seconds"
   set ::looping false

}

signal trap sigint sigint_handler

set start_time [clock seconds] set n 0 set looping true while {$looping} {

   puts [incr n]
   after 500

}</lang>

With TclX, you don't have to trap signals, you can convert the signal into a catchable error: <lang tcl>package require Tclx

signal error sigint

set start_time [clock seconds] set n 0 proc infinite_loop {} {

   while 1 { 
       puts [incr n]
       after 500 
   } 

} if {[catch infinite_loop out] != 0} {

   lassign $::errorCode class name msg
   if {$class eq "POSIX" && $name eq "SIG" && $msg eq "SIGINT"} {
       puts "elapsed time: [expr {[clock seconds] - $start_time}] seconds"
   } else {
       puts "infinite loop interrupted, but not on SIGINT: $::errorInfo"
   }

}</lang>

With Tcl 8.6, that would be written as: <lang tcl>package require Tclx

signal error sigint

set start_time [clock seconds] proc infinite_loop {} {

   while 1 {
       puts [incr n]
       after 500
   }

} try {

   infinite_loop

} trap {POSIX SIG SIGINT} {} {

   puts "elapsed time: [expr {[clock seconds] - $start_time}] seconds"

}</lang>

Note also that from 8.5 onwards, Tcl also has other mechanisms for delivering interrupt-like things, such as interpreter resource limits which permit stopping an execution after a set amount of time and returning control to a supervisor module. However, this is not driven by user interrupts and is so only tangential to this task.

X86 Assembly

Works with: NASM version Linux


Now, I realize linking to C libraries is somewhat cheating. It is entirely possible to do this entirely in syscalls using sys_nanosleep/sys_write but that would require allot more work, definition of the timespec structure among other things. <lang asm> %define sys_signal 48 %define SIGINT 2 %define sys_time 13

extern usleep extern printf

section .text global _start

_sig_handler: mov ebx, end_time mov eax, sys_time int 0x80 mov eax, dword [start_time] mov ebx, dword [end_time] sub ebx, eax mov ax, 100 div ebx push ebx push p_time call printf push 0x1 mov eax, 1 push eax int 0x80 ret

_start: mov ebx, start_time mov eax, sys_time int 0x80 mov ecx, _sig_handler mov ebx, SIGINT mov eax, sys_signal int 0x80 xor edi, edi .looper: push 500000 call usleep push edi push p_cnt call printf inc edi jmp .looper

section .data p_time db "The program has run for %d seconds.",13,10,0 p_cnt db "%d",13,10,0

section .bss start_time resd 1 end_time resd 1 </lang>


TXR

<lang txr>(set-sig-handler sig-int

                (lambda (signum async-p)
                  (throwf 'error "caught signal ~s" signum)))

(let ((start-time (time)))

 (catch (each ((num (range 1)))
          (format t "~s\n" num)
          (usleep 500000))
   (error (msg)
          (let ((end-time (time)))
            (format t "\n\n~a after ~s seconds of execution\n"
                    msg (- end-time start-time))))))</lang>
Run:
$ txr handle-a-signal.tl
1
2
3
4
5
6
7
8
9
10
11
12
^C

caught signal 2 after 6 seconds of execution

range generates a range of integers as a lazy list, which is infinite if the endpoint argument is omitted. We walk this infinite list using each like any other list.

UNIX Shell

The timing will drift with this example (because we need to consider processing time on top of the wait), but the task demonstrates signal handling. For a more accurate timer, we need to implement a signalling process that signals the shell every half a second.

<lang bash>c="1"

  1. Trap signals for SIGQUIT (3), SIGABRT (6) and SIGTERM (15)

trap "echo -n 'We ran for ';echo -n `expr $c /2`; echo " seconds"; exit" 3 6 15 while [ "$c" -ne 0 ]; do # infinite loop

 # wait 0.5    # We need a helper program for the half second interval
 c=`expr $c + 1`

done</lang>

Works with: bash

Note that the following solution only works on systems that support a version of sleep that can handle non-integers. <lang bash>

  1. !/bin/bash

trap 'echo "Run for $((s/2)) seconds"; exit' 2 s=1

while true do

 echo $s
 sleep .5
 let s++

done </lang>

Output:
1
2
3
4
5
^CRun for 2 seconds
Works with: bash

Here is a version of the above which assumes that there is a controlling tty device. It exploits the POSIX standard timeout feature of the tty line discipline. Instead of executing a sleep operation, we execute a terminal read with a 5 tenths of a second timeout:

<lang bash>#!/bin/bash trap 'echo "Run for $((s/2)) seconds"; exit' 2 s=1

half_sec_sleep() {

 local save_tty=$(stty -g)
 stty -icanon time 5 min 0
 read
 stty $save_tty

}


while true do

 echo $s
 half_sec_sleep
 let s++

done</lang>

Works with: zsh

<lang bash>TRAPINT(){ print $n; exit } for (( n = 0; ; n++)) sleep 1</lang>

Visual FoxPro

<lang vfp>

  • !* In VFP, Ctrl+C is normally used to copy text to the clipboard.
  • !* Esc is used to stop execution.

CLEAR SET ESCAPE ON ON ESCAPE DO StopLoop CLEAR DLLS DECLARE Sleep IN WIN32API INTEGER nMilliSeconds lLoop = .T. n = 0 ? "Press Esc to Cancel..." t1 = INT(SECONDS()) DO WHILE lLoop n = n + 1 ? n Sleep(500) ENDDO ? "Elapsed time:", TRANSFORM(INT(SECONDS()) - t1) + " secs." CLEAR DLLS RETURN TO MASTER

PROCEDURE StopLoop lLoop = .F. ENDPROC </lang>

zkl

SigInt is the only signal zkl brings out. <lang zkl>var t=Time.Clock.time; try{ n:=0; while(1){(n+=1).println(); Atomic.sleep(0.5)} } catch{ println("ran for ",Time.Clock.time-t," seconds"); System.exit() }</lang>

Output:
1
2
3
4
5
6
^C
ran for 2 seconds