Random Number Generator Back to the Win32 Shootout
Back to dada's perl lab

[The Original Shootout]   [NEWS]   [FAQ]   [Methodology]   [Platform Details]   [Acknowledgements]   [Scorecard]  
All Source For Random Number Generator
random.awka
# $Id: random.gawk,v 1.6 2001/05/25 03:11:25 doug Exp $
# http://www.bagley.org/~doug/shootout/

function gen_random(max) { return( (max * (LAST = (LAST * IA + IC) % IM)) / IM ); }

BEGIN {
    IM = 139968;
    IA = 3877;
    IC = 29573;
    LAST = 42;

    n = (ARGV[1] < 1) ? 1 : ARGV[1];
    n--
    while (n--) {
    gen_random(100);
    }
    printf("%.9f\n", gen_random(100));
    exit;
}
random.bcc
/* -*- mode: c -*-
 * $Id: random.gcc,v 1.14 2001/05/08 01:36:50 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 */

#include <math.h>
#include <stdio.h>
#include <stdlib.h>

#define IM 139968
#define IA 3877
#define IC 29573

double
gen_random(double max) {
    static long last = 42;
    
    last = (last * IA + IC) % IM;
    return( max * last / IM );
}

int
main(int argc, char *argv[]) {
    int N = ((argc == 2) ? atoi(argv[1]) : 1);
    double result = 0;
    
    while (N--) {
    result = gen_random(100.0);
    }
    printf("%.9f\n", result);
    return(0);
}
random.bigforth
\ -*- mode: forth -*-
\ $Id: random.bigforth,v 1.1 2001/06/20 23:23:29 doug Exp $
\ http://www.bagley.org/~doug/shootout/
\ based on code from Marcel Hendrix

\needs float  import float  float also

\ read NUM from last command line argument
0. argc @ 1- arg >number 2drop drop constant NUM

 139968     CONSTANT IM 
   3877     CONSTANT IA
  29573     CONSTANT IC
IM S>D D>F 
1e FSWAP F/ FCONSTANT FIM 
     42     VALUE seed

: format-float  ff$ type ;

: IM_mod  
    S" DUP $001DF757 UM* NIP  $FFFFFFC0 AND  2187 *  - " 
    EVALUATE ; IMMEDIATE

: gen_random  
    S" seed IA *  IC +  IM_mod  DUP TO seed 0 D>F " EVALUATE
     S" FIM F* F* " EVALUATE ; IMMEDIATE

: MAIN 
    NUM
    10 SET-PRECISION
    0e  BEGIN  ?DUP  
        WHILE  1- FDROP 100e0 gen_random  
        REPEAT
    format-float cr ;

MAIN 
bye
random.csharp
// $Id: random.csharp,v 1.0 2002/02/14 13:42:00 dada Exp $
// http://dada.perl.it/shootout/

using System;

class App {

    public static int IM = 139968;
    public static int IA = 3877;
    public static int IC = 29573;
    public static long last = 42;


    public static double gen_random(double max) {        
        last = (last * IA + IC) % IM;
        return( max * last / IM );
    }

    public static int Main(String[] args) {
        int n;
        double result = 0;

        n = System.Convert.ToInt32(args[0]);
        if(n < 1) n = 1;

        while (n-->0) {
            result = gen_random(100.0);
        }
        Console.WriteLine(result.ToString("F9"));

        return(0);
    }
}
random.cygperl
#!/usr/local/bin/perl 
# $Id: random.perl,v 1.13 2001/05/08 01:51:39 doug Exp $
# http://www.bagley.org/~doug/shootout/

use strict;

use constant IM => 139968;
use constant IA => 3877;
use constant IC => 29573;

my $LAST = 42;
sub gen_random { ($_[0] * ($LAST = ($LAST * IA + IC) % IM)) / IM }

my $result = 0;
my $N = $ARGV[0] || 1;
while ($N--) {
    $result = &gen_random(100);
}
printf "%.9f\n", $result;
random.delphi
program random;


const
  IM = 139968;
  IA =   3877;
  IC =  29573;

var
  LAST: integer;

function gen_random(n: integer): double;
begin
  LAST := (LAST * IA + IC) mod IM;
  result := n * LAST / IM;
end;

var NUM, code, i: integer;
begin
  NUM :=1;
  if ParamCount=1 then
    Val(ParamStr(1),NUM,code);

  LAST := 42;
  for i:= 1 to NUM-1 do
    gen_random(100);
  WriteLn(gen_random(100):10:9);
end.

random.elastic
// $Id: random.elastic,v 1.0 2002/05/09 15:36:00 dada Exp $
package random;

import basic;
import sys;
import array;

local IM = 139968;
local IA = 3877;
local IC = 29573;

private function gen_random( n )
{
    static LAST = 42.0;
    LAST = (LAST * IA + IC) % IM;
    return(n * LAST / IM);
}

private n = 1;
private result = 0;
if(array.length(sys.args) > 0) {
    n = basic.int(sys.args[0]);
} else {
    n = 1;
}
while(n--) {
    result = gen_random(100.0);
}
basic.print(result);
random.erlang
%%% -*- mode: erlang -*-
%%% $Id: random.erlang,v 1.3 2001/05/18 07:39:45 doug Exp $
%%% http://www.bagley.org/~doug/shootout/

-module(random).
-export([main/1]).

main() -> main(['1']).
main([Arg]) ->
    N = list_to_integer(atom_to_list(Arg)),
    io:fwrite("~.9f\n", [rand(N, 42, 0.0, 100.0)]),
    halt(0).


-define(IM, 139968).
-define(IA, 3877).
-define(IC, 29573).


rand(0, _, Rand, _) -> Rand;
rand(N, Seed, Rand, Max) ->
    NewSeed = (Seed * ?IA + ?IC) rem ?IM,
    NewRand = Max * NewSeed / ?IM,
    rand(N-1, NewSeed, NewRand, Max).
random.fpascal
program random;
uses SysUtils;

const
    IM = 139968;
    IA =   3877;
    IC =  29573;

var 
    LAST, NUM, i : longint;
    result : real;

function gen_random(n : integer) : real;
begin    
    LAST := (LAST * IA + IC) mod IM;
    gen_random := n * LAST / IM;
end;

begin
    if ParamCount = 0 then
        NUM := 1
    else
        NUM := StrToInt(ParamStr(1));
    if NUM < 1 then NUM := 1;
    LAST := 42;
    for i:= 1 to NUM do
    begin
        result := gen_random(100);
    end;
    WriteLn( result:10:9 );
end.
random.gawk
# $Id: random.gawk,v 1.6 2001/05/25 03:11:25 doug Exp $
# http://www.bagley.org/~doug/shootout/

function gen_random(max) { return( (max * (LAST = (LAST * IA + IC) % IM)) / IM ); }

BEGIN {
    IM = 139968;
    IA = 3877;
    IC = 29573;
    LAST = 42;

    n = (ARGV[1] < 1) ? 1 : ARGV[1];
    n--
    while (n--) {
    gen_random(100);
    }
    printf("%.9f\n", gen_random(100));
    exit;
}
random.gcc
/* -*- mode: c -*-
 * $Id: random.gcc,v 1.14 2001/05/08 01:36:50 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 */

#include <math.h>
#include <stdio.h>
#include <stdlib.h>

#define IM 139968
#define IA 3877
#define IC 29573

double
gen_random(double max) {
    static long last = 42;
    
    last = (last * IA + IC) % IM;
    return( max * last / IM );
}

int
main(int argc, char *argv[]) {
    int N = ((argc == 2) ? atoi(argv[1]) : 1);
    double result = 0;
    
    while (N--) {
    result = gen_random(100.0);
    }
    printf("%.9f\n", result);
    return(0);
}
random.gforth
\ -*- mode: forth -*-
\ $Id: random.gforth,v 1.6 2001/06/25 14:20:38 doug Exp $
\ http://www.bagley.org/~doug/shootout/
\ from Jorge Acereda Maciá

0. argc @ 1- arg >number 2drop drop constant NUM

: FIM 1e 139968e f/ POSTPONE FLITERAL ; immediate
: IA 3877 POSTPONE LITERAL ; immediate
: IC 29573 POSTPONE LITERAL ; immediate
: IM 139968 POSTPONE LITERAL ; immediate
42 value seed


: format-float  
  f$ dup >r 0<
  IF    '0 emit
  ELSE  scratch r@ min type  r@ precision - zeros  THEN
  '. emit r@ negate zeros
  scratch r> 0 max /string 0 max -zeros type ;

: gen-random 
    s" seed IA * IC + IM mod dup to seed " evaluate
    s" 0 d>f f* FIM f* " evaluate ; immediate 

: main
    10 SET-PRECISION
    0e NUM 0 do fdrop 100e gen-random loop format-float cr ;

main bye
random.ghc
-- $Id: random.ghc,v 1.5 2001/05/18 07:10:55 doug Exp $
-- http://www.bagley.org/~doug/shootout/

module Main(main) where
import System(getArgs)
import Numeric(showFFloat)

main = do
         ~[n] <- getArgs
         putStrLn (showFFloat (Just 9) (randloop (read n::Int) 42 0.0 100.0) "")
     return 1

randloop :: Int -> Int -> Double -> Double -> Double
randloop 0 seed r max = r
randloop n seed r max = randloop (n-1) newseed newrand max
    where normalize x max = (fromIntegral x) * (max / imd)
          newseed         = (seed * ia + ic) `mod` im
          newrand         = normalize newseed max
      im              = 139968
      imd             = fromIntegral im
      ia              = 3877
          ic              = 29573
random.gnat
-- $Id: random.gnat,v 1.0 2003/06/11 12:05:00 dada Exp $
-- http://dada.perl.it/shootout/
-- Ada 95 code by C.C.

with System, Ada.Command_Line, Ada.Text_IO;

procedure Random is
   type Real is digits Positive'Max (15, System.Max_Digits);
   package Rio is new Ada.Text_IO.Float_IO (Num => Real);

   package Random_Real is
      function Gen_Random (Supr : Real) return Real;
      pragma Inline (Gen_Random);
   end Random_Real;

   package body Random_Real is
      IM          : constant Positive := 139968;
      IA          : constant Integer := 3877;
      IC          : constant Integer := 29573;
      Last        : Integer := 42;

      function Gen_Random (Supr : Real) return Real is
         pragma Suppress (Overflow_Check);
         pragma Suppress (Range_Check);
      begin
         Last := (Last * IA + IC) mod IM;
         return Supr * Real (Last) / Real (IM);
      end Gen_Random;
         --  Assume no overflow for "Natural ((IM - 1) * IA + IC)"
   end Random_Real;

   Result   : Real;
   N        : Natural := 0;
begin
   begin
      N := Natural'Value (Ada.Command_Line.Argument (1));
   exception
      when Constraint_Error => null;
   end;
   for Iter in 1 .. N loop
      Result := Random_Real.Gen_Random (Supr => 100.0);
   end loop;
   Rio.Put (Result, Fore => 0, Aft => 9, Exp => 0);
   Ada.Text_IO.New_Line;
end Random;

random.guile
#!/usr/local/bin/guile \
-e main -s
!#

;;; $Id: random.guile,v 1.9 2001/07/31 16:38:37 doug Exp $
;;; http://www.bagley.org/~doug/shootout/

(use-modules (ice-9 format))

(define IM   139968)
(define IA     3877)
(define IC    29573)

(define LAST 42)
(define (gen_random max)
  (set! LAST (modulo (+ (* LAST IA) IC) IM))
  (/ (* max LAST) IM))

(define (main args)
  (let ((n (or (and (= (length args) 2) (string->;number (cadr args))) 1)))
    (let loop ((iter n))
      (if (>; iter 1)
      (begin
        (gen_random 100.0)
        (loop (- iter 1)))))
    (display (format "~,9F\n" (gen_random 100.0)))))
random.ici
// $Id: random.ici,v 1.0 2003/01/03 11:48:00 dada Exp $
// http://dada.perl.it/shootout
//
// contributed by Tim Long

static IM = 139968;
static IA = 3877;
static IC = 29573;
static last = 42;

static
gen_random(max)
{
    return max * (last = (last * $IA + $IC) % $IM) / $IM;
}

n = argv[1] ? int(argv[1]) : 1;
while (n--)
    result = gen_random(100.0);
printf("%.9f\n", result);
random.icon
# -*- mode: icon -*-
# $Id: random.icon,v 1.2 2001/05/08 01:51:39 doug Exp $
# http://www.bagley.org/~doug/shootout/

$define IM 139968
$define IA 3877
$define IC 29573

procedure gen_random(max)
    static LAST; initial LAST := 42;
    repeat { suspend((max * (LAST := (LAST * IA + IC) % IM)) / IM) }
end

procedure main(argv)
    n := argv[1] | 1;
    every i := 2 to n do gen_random(100.0)
    # Icon has fixed number of output decimal points to 9, bogus!
    write(gen_random(100.0))
end

random.java
// $Id: random.java,v 1.10 2001/05/08 01:51:39 doug Exp $
// http://www.bagley.org/~doug/shootout/

import java.text.*;

public class random {

    public static final long IM = 139968;
    public static final long IA = 3877;
    public static final long IC = 29573;

    public static void main(String args[]) {
    int N = Integer.parseInt(args[0]);
    NumberFormat nf = NumberFormat.getInstance();
    nf.setMaximumFractionDigits(9);
    nf.setMinimumFractionDigits(9);
    nf.setGroupingUsed(false);
    double result = 0;
    while (N-- > 0) {
        result = gen_random(100);
    }
    System.out.println(nf.format(result));
    }

    public static long last = 42;
    public static double gen_random(double max) {
    return( max * (last = (last * IA + IC) % IM) / IM );
    }
}
random.jscript
// -*- mode: java -*-
// $Id: random.njs,v 1.4 2001/08/02 20:27:40 doug Exp $
// http://www.bagley.org/~doug/shootout/
// by David Hedbor <david@hedbor.org>

var IM = 139968;
var IA = 3877;
var IC = 29573;
var last = 42;

function gen_random(max) { return(max * (last = (last * IA + IC) % IM) / IM); }

var n, result = 0;
ARGS = WScript.Arguments;
if(ARGS.length > 0) {
    n = parseInt(ARGS.Item(0), "10");
    if (n < 1) n = 1;
} else {
    n = 1;
}
n--;
while (n--) {
    gen_random(100.0);
}

WScript.Echo(gen_random(100.0).toFixed(9));


random.lcc
/* -*- mode: c -*-
 * $Id: random.gcc,v 1.14 2001/05/08 01:36:50 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 */

#include <math.h>
#include <stdio.h>
#include <stdlib.h>

#define IM 139968
#define IA 3877
#define IC 29573

double
gen_random(double max) {
    static long last = 42;
    
    last = (last * IA + IC) % IM;
    return( max * last / IM );
}

int
main(int argc, char *argv[]) {
    int N = ((argc == 2) ? atoi(argv[1]) : 1);
    double result = 0;
    
    while (N--) {
    result = gen_random(100.0);
    }
    printf("%.9f\n", result);
    return(0);
}
random.lua
-- $Id: random.lua,v 1.12 2001/05/08 01:36:50 doug Exp $
-- http://www.bagley.org/~doug/shootout/
-- implemented by: Roberto Ierusalimschy

local IM = 139968
local IA = 3877
local IC = 29573

LAST = 42
function gen_random(max)
    LAST = mod((LAST * %IA + %IC), %IM)
    return( (max * LAST) / %IM )
end

local N = tonumber((arg and arg[1])) or 1
local result = 0
for i=N, 1, -1 do
    result = gen_random(100)
end
write(format("%.9f\n", result))
random.lua5
-- $Id: random.lua,v 1.12 2001/05/08 01:36:50 doug Exp $
-- http://www.bagley.org/~doug/shootout/
-- contributed by Roberto Ierusalimschy

local IM = 139968
local IA = 3877
local IC = 29573

local LAST = 42
local function gen_random(max)
    LAST = math.mod((LAST * IA + IC), IM)
    return( (max * LAST) / IM )
end

local N = tonumber((arg and arg[1])) or 1
local result = 0
for i=1, N do
    result = gen_random(100)
end
io.write(string.format("%.9f\n", result))

random.mawk
# $Id: random.mawk,v 1.6 2001/05/25 03:11:25 doug Exp $
# http://www.bagley.org/~doug/shootout/

function gen_random(max) { return( (max * (LAST = (LAST * IA + IC) % IM)) / IM ); }

BEGIN {
    IM = 139968;
    IA = 3877;
    IC = 29573;
    LAST = 42;

    n = (ARGV[1] < 1) ? 1 : ARGV[1];
    n--
    while (n--) {
    gen_random(100);
    }
    printf("%.9f\n", gen_random(100));
    exit;
}
random.mercury
% ---------------------------------------------------------------------------- %
% random.m
% Ralph Becket <rbeck@microsoft.com>
% Tue Jan  9 14:18:19 GMT 2001
% vim: ts=4 sw=4 et tw=0 wm=0 ff=unix
% ---------------------------------------------------------------------------- %

:- module mytest.

:- interface.

:- import_module io.



:- pred main(io__state, io__state).
:- mode main(di, uo) is det.



:- implementation.



:- import_module float, int, list, string, require.


main -->
    io__command_line_arguments(ArgV),
    (   { ArgV = [],        N = 1 }
    ;   { ArgV = [Arg],     N = string__det_to_int(Arg) }
    ;   { ArgV = [_,_|_],   error("usage: random [N]") }
    ),
    io__format("%.9f\n", [f(nth_random_no(N, seed))]).


:- func nth_random_no(int, int) = float.

nth_random_no(I, S0) = ( if I > 1 then nth_random_no(I - 1, S) else R ) :-
    gen_random(100.0, R, S0, S).



:- pred gen_random(float, float, int, int).
:- mode gen_random(in, out, in, out) is det.

gen_random(Max, R, S0, S) :-
    S = (S0 * ia + ic) `rem` im,
    R = Max * float(S) / float(im).

:- func im = int.   im = 139968.
:- func ia = int.   ia =   3877.
:- func ic = int.   ic =  29573.
:- func seed = int. seed =   42.
random.mingw32
/* -*- mode: c -*-
 * $Id: random.gcc,v 1.14 2001/05/08 01:36:50 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 */

#include <math.h>
#include <stdio.h>
#include <stdlib.h>

#define IM 139968
#define IA 3877
#define IC 29573

double
gen_random(double max) {
    static long last = 42;
    
    last = (last * IA + IC) % IM;
    return( max * last / IM );
}

int
main(int argc, char *argv[]) {
    int N = ((argc == 2) ? atoi(argv[1]) : 1);
    double result = 0;
    
    while (N--) {
    result = gen_random(100.0);
    }
    printf("%.9f\n", result);
    return(0);
}
random.modula2
(* The Great Win32 Language Shootout http://dada.perl.it/shootout/

   contributed by Isaac Gouy (Modula2 novice)

   To build: xc =m random
   To run:   random 900000
*)

MODULE Random;
<* procinline + *>
<* ioverflow - *>
<* alignment="8" *>


(* Prefer unqualified procedures *)
FROM LanguageShootout IMPORT N;

FROM STextIO IMPORT WriteLn;
FROM SLongIO IMPORT WriteFixed;


CONST
   IM = 139968;
   IA = 3877;
   IC = 29573;

VAR
   n, last: INTEGER;
   result: LONGREAL;

PROCEDURE Gen_Random(max: LONGREAL): LONGREAL;
BEGIN
   last := (last*IA + IC) REM IM;
   RETURN max * LFLOAT(last) / LFLOAT(IM);
END Gen_Random;


BEGIN
   n := N();
   last := 42;

   WHILE n > 0 DO
      DEC(n);
      result := Gen_Random(100.0);
   END;  	

   WriteFixed(result,9,1); WriteLn;
END Random.
random.modula3

MODULE Main;
IMPORT Fmt, Scan, Params, Wr, Stdio;

CONST 
    IM = 139968;
    IA = 3877;
    IC = 29573;

PROCEDURE gen_random(n: REAL): REAL =
BEGIN
    last := (last * IA + IC) MOD IM;
    RETURN n * FLOAT(last) / FLOAT(IM);
END gen_random;

VAR last: INTEGER := 42;

VAR 
    n: INTEGER;
    i: INTEGER;
    result: REAL;
BEGIN
    IF Params.Count > 0 THEN
        n := Scan.Int(Params.Get(1));
    ELSE
        n := 1;
    END;
    FOR i := 1 TO n DO
        result := gen_random(100.0);
    END;
    Wr.PutText (Stdio.stdout, Fmt.Real(result, prec:=9));
    Wr.Close (Stdio.stdout);
END Main.
random.nice
/* The Great Win32 Language Shootout http://dada.perl.it/shootout/ 
   contributed by Isaac Gouy (Nice novice)

To compile:	
   nicec --sourcepath=.. -d=. -a random.jar random

To run:
   java -jar random.jar 900000
*/


import java.text.*;

import ackermann; // reuse toSingleInt


void main(String[] args){
   var n = toSingleInt(args);
   double result = 0.0;

   while (n-- > 0) result = gen_random(100.0);

   println(floatFormat(9).format(result));
}


let int IM = 139968;
let int IA = 3877;
let int IC = 29573;
var int seed = 42;


double gen_random(double max) {        
   seed = (seed * IA + IC) % IM;
   return( max * seed / IM );
}


NumberFormat floatFormat(int digits){
   NumberFormat f = NumberFormat.getInstance();
   f.setGroupingUsed(false);
   f.setMaximumFractionDigits(digits);
   f.setMinimumFractionDigits(digits);
   return f;
} 
random.ocaml
(*
 * $Id: random.ocaml,v 1.10 2001/07/26 01:33:45 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 * with help from Markus Mottl
 *)

let im = 139968
let ia = 3877
let ic = 29573
let last_ref = ref 42

let gen_random max =
  let new_last = (!last_ref * ia + ic) mod im in
  last_ref := new_last;
  max *. float_of_int new_last /. float im

let _ =
  let n =
    try int_of_string Sys.argv.(1)
    with Invalid_argument _ -> 1 in
  let rec loop i =
    let r = gen_random 100.0 in
    if i > 1 then loop (i-1) else r in
  Printf.printf "%.9f\n" (loop n)

random.ocamlb
(*
 * $Id: random.ocaml,v 1.10 2001/07/26 01:33:45 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 * with help from Markus Mottl
 *)

let im = 139968
let ia = 3877
let ic = 29573
let last_ref = ref 42

let gen_random max =
  let new_last = (!last_ref * ia + ic) mod im in
  last_ref := new_last;
  max *. float_of_int new_last /. float im

let _ =
  let n =
    try int_of_string Sys.argv.(1)
    with Invalid_argument _ -> 1 in
  let rec loop i =
    let r = gen_random 100.0 in
    if i > 1 then loop (i-1) else r in
  Printf.printf "%.9f\n" (loop n)

random.oz
%%% $Id: random.oz,v 1.0 2002/03/12 10:08:00 dada Exp $
%%% http://dada.perl.it/shootout/
functor
import System Application
define
fun {RandLoop N SEED R MAX}
    case N 
    of 0 then R
    else 
        local IA IC IM NEWSEED NEWRAND in
            IM = 139968
            IA =   3877
            IC =  29573
            NEWSEED = (SEED * IA + IC) mod IM
            NEWRAND = MAX * {Int.toFloat NEWSEED}/{Int.toFloat IM}
            {RandLoop N-1 NEWSEED NEWRAND MAX}
        end
    end
end
in 
    local A NUM I in
        [A] = {Application.getArgs plain}
        NUM = {String.toInt A}
        {System.printInfo {RandLoop NUM 42 0 100.0}}
    end
    {Application.exit 0}
end
random.parrot
# $Id: random.parrot,v 1.0 2002/08/19 17:18:00 dada Exp $
# http://dada.perl.it/shootout/

.constant IM 139968
.constant IMf 139968.0
.constant IA 3877
.constant IC 29573
.constant LAST I10

    set .LAST, 42
    
    set I1, P0[1]
    
while:
    set N0, 100
    bsr gen_random
    dec I1
    if I1, while
    print N0
    end

gen_random:
    
    #last = (last * IA + IC) % IM;
    #return( max * last / IM );

    mul I11, .LAST, .IA
    add I11, .IC
    cmod .LAST, I11, .IM
    set N10, .LAST
    mul N11, N0, N10
    div N0, N11, .IMf
    ret 

random.perl
#!/usr/local/bin/perl 
# $Id: random.perl,v 1.13 2001/05/08 01:51:39 doug Exp $
# http://www.bagley.org/~doug/shootout/

use strict;

use constant IM => 139968;
use constant IA => 3877;
use constant IC => 29573;

my $LAST = 42;
sub gen_random { ($_[0] * ($LAST = ($LAST * IA + IC) % IM)) / IM }

my $result = 0;
my $N = $ARGV[0] || 1;
while ($N--) {
    $result = &gen_random(100);
}
printf "%.9f\n", $result;
random.php
<?php
/*
 $Id: random.php,v 1.4 2001/05/16 05:30:59 doug Exp $
 http://www.bagley.org/~doug/shootout/
*/
define("IM", 139968);
define("IA", 3877);
define("IC", 29573);

$LAST = 42;
function gen_random ($max) {
    global $LAST;
    return( ($max * ($LAST = ($LAST * IA + IC) % IM)) / IM );
}

$result = 0;
$N = ($argc == 2) ? $argv[1] : 1;
while ($N--) {
    $result = gen_random(100);
}

printf("%.9f\n", $result);
?>
random.pike
#!/usr/local/bin/pike// -*- mode: pike -*-
// $Id: random.pike,v 1.13 2001/05/08 06:35:56 doug Exp $
// http://www.bagley.org/~doug/shootout/

int IM = 139968;
int IA = 3877;
int IC = 29573;

int last = 42;

float
gen_random(float max) { return(max * (last = (last * IA + IC) % IM) / IM); }

int
main(int argc, array(string) argv) {
    float result = 0;
    int N = (int)argv[-1] || 1;
    while (N--) {
    result = gen_random(100.0);
    }
    write("%.9f\n", result);
    return(0);
}

random.pliant
# $Id: random.pliant,v 1.0 2002/02/07 15:19:00 dada Exp $
# http://dada.perl.it/shootout/

module "/pliant/language/context.pli"

gvar Int IM := 139968
gvar Int IA :=   3877
gvar Int IC :=  29573

gvar Int LAST := 42

function gen_random n -> r
  arg Int n ; arg Float r
  LAST := (LAST * IA + IC) % IM
  r := (n * LAST) / IM
  return r

gvar Float result 

gvar Str s_n := cast ((pliant_script_args translate Address 1) map CStr) Str
if (s_n parse (gvar Int n))
  while n > 0
    result := gen_random(100)
    n := n - 1
  console (string result "fixed 9") eol
else
  console "usage: random.pli <number>" eol
random.poplisp
;;; -*- mode: lisp -*-
;;; $Id: random.poplisp,v 1.0 2002/05/08 17:32:00 dada Exp $

(defconstant IM     139968)
(defconstant IA       3877)
(defconstant IC     29573)

(defvar LAST 42)

(declaim (inline gen_random))
(defun gen_random (max)
  (declare (type (signed-byte 32) IM IA IC LAST))
  (declare (double-float max))
  (setq LAST (mod (+ (the fixnum (* LAST IA)) IC) IM))
  (/ (* max LAST) IM))

  (let ((n (parse-integer (or (car pop11::poparglist) "1"))))
    (loop for i fixnum from 1 below n do
      (gen_random 100.0d0))
    (format t "~,9K~%" (gen_random 100.0d0)))
random.python
#!/usr/local/bin/python
# $Id: random.python,v 1.17 2001/07/31 16:38:37 doug Exp $
# http://www.bagley.org/~doug/shootout/
# with help from Brent Burley

import sys

IM = 139968
IA = 3877
IC = 29573

LAST = 42
def gen_random(max):
    global LAST
    LAST = (LAST * IA + IC) % IM
    return( (max * LAST) / IM )

def main():
    N = int(sys.argv[1])
    if N < 1:
        N = 1
    gr = gen_random
    for i in xrange(1,N):
        gr(100.0)
    print "%.9f" % gr(100.0)

main()

random.rexx
NUMERIC DIGITS 10

vIM=139968
vIA=3877
vIC=29573

LAST=42

parse arg n
If n < 1 Then Do
    n = 1
End

Do i = 1 TO N
    result = gen_random(100)
End

SAY result

EXIT

gen_random:
    PROCEDURE EXPOSE LAST vIM vIA vIC
    PARSE ARG n
    LAST = (LAST * vIA + vIC) // vIM
    return n * LAST / vIM

random.ruby
#!/usr/local/bin/ruby
# -*- mode: ruby -*-
# $Id: random.ruby,v 1.13 2001/05/08 06:35:57 doug Exp $
# http://www.bagley.org/~doug/shootout/

IM = 139968
IA = 3877
IC = 29573

$last = 42.0
def gen_random (max) (max * ($last = ($last * IA + IC) % IM)) / IM end

N = Integer(ARGV.shift || 1)
result = 0
N.times do
    result = gen_random(100.0)
end
printf "%.9f\n", result
random.se
-- -*- mode: eiffel -*-
-- $Id: random.se,v 1.3 2001/05/23 18:30:39 doug Exp $
-- http://www.bagley.org/~doug/shootout/

-- <LOC-OFF>
indexing
   description: "This class is the entry point for the random number generation test" 
   author : Steve Thompson
   email  : "Steve_Thompson@prodigy.net"
   date   : February 18, 2001
   compile: "compile -clean -case_insensitive -boost -no_split -O3 main.e -o main"
   run    : "main 900000"
-- <LOC-ON>

class RANDOM
   
creation make
   
feature -- Creation
   
   make is
      local
     random: RANDOMNUMBER
     n: INTEGER
     answer: DOUBLE
     index: INTEGER
      do
     if argument_count = 0 then 
        n := 1
     else
        n := argument(1).to_integer
     end
     from 
        index := n
        !!random.make 
     until index = 0 loop
        answer := random.next(100.0)
        index := index - 1
     end
     io.put_string(answer.to_string_format(9))
     io.put_new_line
      end
   
end
random.slang
% $Id: random.slang,v 1.0 2003/01/03 13:41:00 dada Exp $
% http://dada.perl.it/shootout/
%
% contributed by John E. Davis

variable IM = 139968;
variable IA = 3877;
variable IC = 29573;
variable LAST = 42;

define gen_random(max)
{
    LAST = (LAST * IA + IC) mod IM;
    (max * LAST) / IM;
}

define main()
{
   variable N = integer (__argv[1]);
   if (N < 1)
     N = 1;

   loop (N-1)
     () = gen_random (100.0);

   vmessage ("%.9f", gen_random(100.0));
}

main();
random.smlnj
(* -*- mode: sml -*-
 * $Id: random.smlnj,v 1.5 2001/07/09 00:25:28 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 *)

structure Test : sig
    val main : (string * string list) -> OS.Process.status
end = struct

val im : int = 139968;
val ia : int = 3877;
val ic : int = 29573;

fun randloop 0 seed rand max = rand
  | randloop n seed rand max = 
    let
    val newseed : int = (seed * ia + ic) mod im;
    val newrand : real = max * (Real.fromInt newseed) / (Real.fromInt im);
    in
        randloop (n-1) newseed newrand max
    end;


fun atoi s = case Int.fromString s of SOME num => num | NONE => 0;

fun main(name, args) = 
  let
    val arg = hd(args @ ["1"]);
    val num = atoi arg;
    val result = randloop num 42 0.0 100.0;
  in
      print (Real.fmt (StringCvt.FIX (SOME 9)) result); print "\n";
      OS.Process.success
  end
end

val _ = SMLofNJ.exportFn("random", Test.main);
random.tcl
#!/usr/local/bin/tclsh
# $Id: random.tcl,v 1.7 2001/05/08 01:36:50 doug Exp $
# http://www.bagley.org/~doug/shootout/
# from Miguel Sofer

trace variable params w make_main
proc make_main {args} {
    global params last
    set randBody [string map $params {
        expr {(100.0 * [set last [expr {($last * IA + IC) % IM}]]) / IM}
    }]
    set mainBody [string map [list randBody $randBody] {
     global argv last
     set N [lindex $argv 0]
     set result 0.0
     while {$N} {
         set result [randBody]
         incr N -1
     }
     puts [format "%.9f" $result]
    }]
    proc main {} $mainBody     
}

set params {IM 139968 IA 3877 IC 29573}
set last 42

main
random.vbscript
Const IM = 139968
Const IA =   3877
Const IC =  29573

LAST = 42

Function gen_random(n)
    LAST = (LAST * IA + IC) Mod IM
    gen_random = n * LAST / IM
End Function

result = 0
n = WScript.Arguments(0)
If n < 1 Then n = 1
For i = 1 To N
    result = gen_random(100)
Next

WScript.Echo FormatNumber(result, 9)
random.vc
/* -*- mode: c -*-
 * $Id: random.gcc,v 1.14 2001/05/08 01:36:50 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 */

#include <math.h>
#include <stdio.h>
#include <stdlib.h>

#define IM 139968
#define IA 3877
#define IC 29573

double
gen_random(double max) {
    static long last = 42;
    
    last = (last * IA + IC) % IM;
    return( max * last / IM );
}

int
main(int argc, char *argv[]) {
    int N = ((argc == 2) ? atoi(argv[1]) : 1);
    double result = 0;
    
    while (N--) {
    result = gen_random(100.0);
    }
    printf("%.9f\n", result);
    return(0);
}
random.vc++
// -*- mode: c++ -*-
// $Id: random.g++,v 1.4 2001/06/20 03:20:02 doug Exp $
// http://www.bagley.org/~doug/shootout/

#include <iostream>
#include <stdlib.h>
#include <math.h>

using namespace std;

#define IM 139968
#define IA 3877
#define IC 29573

double gen_random(double max) {
    static long last = 42;
    last = (last * IA + IC) % IM;
    return( max * last / IM );
}

int main(int argc, char *argv[]) {
    int N = ((argc == 2) ? atoi(argv[1]) : 1);
    double result = 0;
    
    while (N--) {
    result = gen_random(100.0);
    }
    cout.precision(10);
    cout << result << endl;
    return(0);
}

random.vpascal
program random;
uses SysUtils;

const
    IM = 139968;
    IA =   3877;
    IC =  29573;

var 
    LAST, NUM, i : integer;
    result : real;
    

function gen_random(n : integer) : real;
begin    
    LAST := (LAST * IA + IC) mod IM;
    gen_random := n * LAST / IM;
end;

begin
    if ParamCount = 0 then
        NUM := 1
    else
        NUM := StrToInt(ParamStr(1));
    if NUM < 1 then NUM := 1;
    LAST := 42;
    for i:= 1 to NUM do
    begin
        result := gen_random(100);
    end;
    WriteLn( result:10:9 );
end.