Legisign.org Logo

Raiding the Lost Average

This is an old hobby of mine: to write some silly thing in as many programming languages as possible.

Here we calculate averages. Not all of these are tested, and even when they are, they are not guaranteed to work on any particular platform or with any particular dialect.

I have tried to preserve each language’s distinctive “flavour”, even when it means that the programs won’t be used the same way. Most of the code samples still read standard input (or the keyboard input, whichever is more appropriate) and spit out the result on screen. Some, especially the ones coded in a “functional” language, just define functions to be used in whatever manner is the most appropriate to the language.

A note about syntax colouring: I use the following attributes:

Of course, exactly the same principles are not applicable from language to language. For instance, BEGIN and END might be labeled as ‘predefined’ in AWK, but as they are used as specific values in matching, I decided to treat them as such. In LISP-like languages, the real distinction is between functions, special forms, macros and such, but I’ve decided that ‘keywords’ are specific important words (often macros) and the rest are ‘predefined’ if they cannot be redefined by the user in the same namespace.

See also Raiding the Lost Lottery Line.

ABC

ABC was designed for the same purpose as Pascal and BASIC in their turns: to be an easy-to-learn language with which it would be very difficult to fall into bad programming habits. BASIC failed, and since there is no comment statement in ABC as far as I know, I hardly think you could call ABC victorious either. Anyway, this was the predecessor of Python.

As you can see, number 0 stands for end of input. That means 0 cannot be included in the list of values you want to get the average of; but in an interpreting environment this is the easiest way round. No serious piece of programming this one.

PUT 1 IN number
WHILE number <> 0:
    WRITE "Give a number, 0 to quit: "
    READ number EG 0
    PUT sum + number IN sum
    PUT n + 1 IN n
PUT n - 1 IN n
PUT sum / n IN average
WRITE "Average =", average
Ada

Ada is a high-level procedural language much like C and Pascal. It’s been developed by and for the US government, and sometimes it’s been called the world’s first “paranoid” programming language as it puts much emphasis on data protection.

This example is totally untested and I’m actually quite sure it’s still not 100% correct.

-- Calculating average in Ada

with Ada.Text_IO;
use Ada.Text_IO;

n : INTEGER := 0;
number : FLOAT := 1.0;
sum : FLOAT := 0.0;

procedure CalcAverage is
begin
    while number != 0.0 loop
        Ada.Text_IO.Put(Give a number, or 0 to quit: ");
        Ada.Text_IO.Get(number);
        n := n + 1;
        sum := sum + number;
    end loop;
    n := n - 1;
    average := sum / n;
    Ada.Text_IO.Putline("Average = ", average);
end CalcAverage;
Algol

Algol is the ancestor of all modern procedural languages like Pascal or C (and the latter’s numerous children). As far as I know, there’s no functional Algol implementation for Linux so whatever I write I cannot test. Nevertheless I consider an Algol example quite essential for this page.

So, I admit having stolen the following code snippet from elsewhere. I only changed the initial comment. There’s no input or output, because Algol never defined standard I/O but left that to the implementation details.

Algol had advanced structures such as the ternary if…then…else in the assignment to Data[i]) below) that were not brought over to the later languages for a long time.

// Calculating average in Algol

begin
    integer n;
    Read Int(n);

    begin
        real array data[1:n];
        real sum, avg;
        integer i;
        sum := 0;

        for i := 1 step 1 until n do
            begin real val;
                Read Real(val);
                data[i] := if val < 0 then -val else val
            end;

        for i := 1 step 1 until n do
            sum := sum + data[i];
        avg := sum / n;
        Print Real(avg)
    end
end
AWK

AWK is a text-scanning, not a general-purpose programming language. Since AWK programs always have an implicit input loop, there is no need to write an input routine: we just have to make sure the data obtained is valid.

Previously, I had here a version that only expected one number per input line—I said we shouldn’t bother about anything more refined. Well, now I’ve refined it. In effect, this script can slurp in any text file and ultimately produce an average of all the numbers found inside it, negative ones included, unlike before.

# Calculating average in AWK

/-?[0-9]+.?[0-9]*/ {
    for (p = 1; p <= NF; p ++)
        if ($p ~ /^-?[0-9]+.?[0-9]*$/) {
            sum += $p
            n ++
        }
}

END {
    average = sum / n
    printf("Average = %f\n", average)
}
BASIC

Here I tried to approximate the feeling of very primitive BASIC: no advanced loop control, just a GOTO clause forcing the control to move to a given line number—the so-called “spaghetti BASIC”. Later BASICs got very close to, say, Pascal.

There were a few commonly used abbreviations in later BASICs, too. For instance, PRINT was typed ? to save a couple of bytes of precious memory, and GOTO was redundant after THEN for the same reason. END clause is optional when there was no need to end the run prematurely.

0 again stands for the end-of-input, as in the ABC code.

100 REM Calculating average in BASIC
110 REM
120 PRINT "Give a number, 0 to quit: ";
130 INPUT F
140 S=S+F
150 N=N+1
160 IF F<>0 THEN GOTO 120
170 N=N-1
180 A=S/N
190 PRINT "Average ="; A
200 END
C

Nothing remarkable here except the eyesore syntax, at least when compared to Pascal or Python.

Read until standard input is exhausted, then calculate the average. There’s no checking of invalid input, but that’s almost like a C tradition (see the Unix Hater’s Handbook!).

/* Calculating average in C */

#include <stdio.h>

void main(void)
{
    double number, sum = 0.0, average;
    int n;

    for (n = 0; scanf("%lf", &number) == 1; sum += number, n ++)
        ;
    average = sum / n;
    printf("Average = %lf\n", average);
}
C++

This is hardly any different from C except in minor points. In a program of this size, there is no gain in utilizing the object-orientedness of the language.

C++ standards have changed lately, so I have had to modify the following a bit; nowadays it’s obligatory to specify namespaces, but I have absolutely no idea why one first should declare iostream but then happily use std as the namespace prefix—it’s just weird.

// Calculating the average in C++

#include <iostream>

int main(void)
{
    double number, sum = 0.0, average;
    int n = 0;

    for (; std::cin >> number; sum += number, n ++)
        ;
    average = sum / n;
    std::cout << "Average = " << average << std::endl;
    return 0;
}
COBOL

As in my samples in other languages, I have tried to find the “true” COBOL here, which means going back in time a bit.

0 stands for end of input. Cf. ABC.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. CALC-AVERAGE.
      *
      * Calculating average in COBOL
      *
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
           NUMBER     PIC 999999.999 VALUE 0.
           SUM        PIC 9999999.9999 VALUE 0.
           N          PIC 99 VALUE 0.
           AVERAGE    PIC ZZZZZZ9.9ZZZ VALUE 0.
       PROCEDURE DIVISION.
       MAIN SECTION.
           PERFORM SUM-FIGURES UNTIL FIGURE EQUALS TO 0.
           DIVIDE SUM BY N GIVING AVERAGE.
           DISPLAY 'Average =', AVERAGE.
       MAIN-EX.
           EXIT.
           STOP RUN.
       SUM-FIGURES SECTION.
           DISPLAY 'Give a number, 0 to quit: '.
           ACCEPT NUMBER.
           ADD NUMBER TO SUM.
           ADD 1 TO N.
       SUM-FIGURES-EX.
           EXIT.
D

D is a newer language in the C-derived or “lots of braces” family. It has also borrowed lots of features from here and there.

// Calculating average in D

import std.stdio;
import std.format;

void main()
{
    ulong n = 0;
    double number, sum = 0, average;

    foreach (char[] line; stdin.byLine()) {
        ++ n;
        formattedRead(line, "%f", &number);
        sum += number;
    }
    average = sum / n;
    writeln("Average = ", average);
}
Erlang

Erlang is a newer functional language that was conceived by Ericsson Corporation for robust handling of telecom switches. The idea behind the following closely resembles other functional languages such as Haskell or Ocaml. One nice thing about these languages is the lack of almost all boilerplate code, i.e. code that mostly declares that ‘this is a program’, ‘now I’m going to write my program’, ‘here are the facts of the program’.

%% Calculating average in Erlang

-module(avg).
-export([sum/1, avg/1]).

sum([]) ->
    0;
sum([First|Rest]) ->
    sum(First, Rest).

sum(Tally, []) ->
    Tally;
sum(Tally, [First|Rest]) ->
    sum(Tally + First, Rest).

avg([]) ->
    0;
avg(L) ->
    sum(L) / length(L).
Forth

As becomes the Forth ideology, this is a one-liner. Adherents in other languages may want to use indentations and such to point out the structure. The input-output ideology tries to be as much “Forthish” as possible: there is neither input nor output here. The “word” created in the sample expects to find its input in the stack when it is called, and the answer is left in the stack when done.

What happens? First we get the depth of the stack, i.e., the number of items in it. The value goes to the top of the stack, where we duplicate it since we’ll be needing it twice. One of these values is put in the “return stack” with >r where it will be safe for a while. Now we go to a loop from 1 to depth which we still have on the stack ready to be used. The body of the loop is between the do and loop: we sum all the values we find in the stack (the depth value was already eaten up by do). Finally we get the saved value from the return stack with r>. Now there are only two values left in the stack: the sum and the depth, so we divide the former with the latter, leaving the result on the stack.

(Wow, that takes so much longer in English!)

\ Calculating average in Forth ( n1 n2 … -- n )
: avg depth dup >r 1 do + loop r> / ;
Fortran

Fortran is the oldest programming languages still in use: it’s been used continuously since the 1950s. This sample is old-fashioned Fortran, not the current kind, but not so old-fashioned that we should use the predefined variable names (i etc. for integers, f etc. for floats and so on).

c    Calculating average in Fortran
     program average
     real f, s, a
     integer n
     s=0
     n=0
10   write (*,*) 'Give a number, 0 to quit:'
     read (*,*) f
     s=s+f
     n=n+1
     if (f.eq.0) goto 10
     n=n-1
     a=s/n
     write (*,*) 'Average =', a
     stop
     end
Go

Google’s Go is one more “dot com era” language to the C-derived family. Unlike C (mostly) but like D, it can be used both interpreted and compiled. Note that variables can go undeclared (like “sum” in this example), if you use Pascal-like “:=” to initialize them. Normally variables are set to a value with “=”, as in C.

// Calculating average in Go

package main

import (
        "fmt"
        "strconv"
)

func main() {
        var line string
        var number float64

        sum := 0.0
        n := 0
        for {
                _, err := fmt.Scan(&line)
                if err != nil {
                        break
                }
                number, err = strconv.ParseFloat(line, 64)
                if err == nil {
                        sum += number
                        n ++
                }
        }
        average := sum / float64(n)
        fmt.Println("Average =", average)
}
Haskell

Haskell is a purely-functional programming language. If anything it’s to be loved for its clearness and lack of boilerplate code.

The example given doesn’t have any I/O: it only specifies the function to be called when calculating the average of a list of numbers.

-- Calculating average in Haskell

avg :: Fractional a => [a] -> a
avg [] = 0
avg ns = sum ns / fromIntegral (length ns)
Icon

Icon can be notoriously cryptic when used by real gurus. It has ingenious control structures that do not return a value but signal failure or success, which makes it very easy to hide value-checking inside ordinary statements.

In my sample here, there is no need to write an explicit end-of-loop test in the while clause, since read() fails when no more input is available, and that makes while fail (and end) too.

# Calculating average in Icon

procedure main()
    sum := n := 0
    while sum +:= read() do n +:= 1
    write("Average = ", average := sum / n)
end
J

J is a successor to APL, one of the oddest programming languages ever designed (at least for serious purposes). Visually the two languages don’t look much like each other because J tries to not repeat the “mistake” of APL: using an obscure character set that needs to be independently implemented. Instead, plain ASCII characters are used. On the other hand, conceptually J is quite close to APL.

Briefly, this declares that avg is now defined (=:) to be the folding sum (+/) of a vector divided (%) by its length (#). Comments are usually at the end of the code lines, and the start with NB.

avg =: +/ % # NB. Calculating average in J
JavaScript

This one expects to be called from somewhere, as befits JavaScript’s Web ideology.

// Calculating average in JavaScript
function calcAverage(l)
{
    for (i = 0; i < calcAverage.arguments.length; i ++, sum += calcAverage.arguments[i])
        ;
    average = sum / calcAverage.arguments.length;
    document.write('Average =', average);
}
Julia

Julia is a relatively new language which only very recently reached version 1.0. Julia is specialized in high-performance technical computation, meaning that it’s designed to be fast in computation and oriented in number crunching.

Julia has had many design changes already. As far as I recall, there used to be a builtin mean() function for averages, but now there isn’t. Likewise, stdin used to be STDIN, and so on.

# Calculating average in Julia

function average(nums)
    sum(nums) / length(nums)
end

nums = [parse(Float64, num) for num in readlines(stdin)]
println!("Average = ", average(nums))
KiXtart

A hideous language this one, just one bit better than the extremely nasty MS-DOS batch “language”.

; Calculating average in KiXtart

$number = 1
$sum = 0
$n = 0

WHILE "$number"
    "Give a number, 0 to quit:"
    GET $number
    $sum = $sum + $number
    $n = $n + 1
LOOP

$n = $n - 1
$average = $sum / $n
"Average =" $average
Lisp

“Lots of Idiotic Silly Parentheses”? The syntax is a bit rough for us humans, but still, the ideology in Lisp is quite sound.

I had here previously a version that used eval, but Teemu Likonen proposed the following, more Lisp-like version that uses apply. (One could also use reduce in this particular case, as the purpose is to reduce a list of numbers to a single value, their sum.)

; Calculating average in Common Lisp

(defun average (&rest numbers)
  (/ (apply #'+ numbers) (length numbers)))
Ocaml

The following is way overdone, of course: no one would actually calculate averages this way but would use ready-made library functions. Defining the length function, in particular, is totally unwarranted because there already is one. This sample is given more as a demonstration of how you could define it were it missing.

Note that there are distinct keywords for defining non-recursive (let) and recursive functions (let rec), as well as distinct versions of the arithmetic infix sum operator for integers (+) and floats (+.).

(* Calculating average in Ocaml *)

let rec length ns =
    match ns with
      []          -> 0
      | n :: ns'  -> 1 + length ns'

let rec sum ns =
    match ns with
      []          -> 0.
      | n :: ns'  -> n +. sum ns'

let average ns =
    match ns with
      []          -> 0.
      | ns'       -> sum ns' /. float_of_int (length ns')
Pascal

The syntax of Pascal is as lucid as you could hope for. For short tasks as in here, the lucidity tends to give an additional length to the code, but Pascal-adherents worship readability above all. (The same is true of Python.)

{ Calculating average in Pascal }

program CalcAverage(input, output);

var number, sum, average : double;
    n : integer;

begin
    number := 1.0;
    sum := 0.0;
    n := 0;

    while number <> 0 do begin
        write ('Give a number, 0 to quit: ');
        read (number);
        sum := sum + number;
        n := n + 1
    end;
    average := sum / n;
    writeln ('Average =', average)
end.

Here’s a second version that’s been tested and is known to work with Free Pascal. It reads standard input until EOF and thus can use zeros as input values.

{ Calculating average in Free Pascal }

program CalcAverage;

uses sysutils;

var stdin : text;
    number, sum, average : double;
    line : string;
    n : integer;

begin
    sum := 0.0;
    n := 0;

    assign(stdin, '');
    reset(stdin);
    while not eof(stdin) do begin
        readln(stdin, line);
        if TryStrToFloat(line, number) then begin
            sum := sum + number;
            n := n + 1
        end
    end;
    close(stdin);
    average := sum / n;
    writeln('Average =', average)
end.
Perl

Perl is one of the languages with which you can write absolutely unreadable code if so you wish (cf. AWK, Icon). The sample here is an eyesore for all Pascal-lovers, but still pretty easy to number out.

# Calculating average in Perl

for (; <>; $sum += $_, $n ++) {}
$average = $sum / $n;
print "Average = $average\n";
Pilot

This example is totally untested, since I don’t have an interpreter for Pilot (though I once even ported one to OS/2!). It’s a silly little language; I wonder whoever thought that language of this kind would be suitable for the educational environment?!

The syntax is extremely crude and simplistic. It can be directly read once you grasp that the one-letter commands are just abbreviations of common English verbs: A for accept, C for compute, J for jump, and T for type.

R:Calculating average in Pilot
*INPUT
T:Give a number, or 0 to quit:
A:#F
C:#S=#S+#F
C:#N=#N+1
J(#F<>0):*INPUT
C:#N=#N-1
C:#A=#S/#N
T:Average = #A
PL/I

This one is a real milestone on the bumpy road of programming language history. PL/I paved the road for languages like Pascal and C with its neat procedural syntax.

            /* Calculating average in PL/I */

AVERAGE:    PROCEDURE OPTIONS (MAIN);

            DECLARE (NUMBER, SUM, AVERAGE) FIXED BIN(15);
            DECLARE (N) FIXED BIN(7);

            NUMBER = 1;
            SUM = 0;
            N = 0;

            DO WHILE (NUMBER <> 0);
                PUT SKIP DATA "Give a number, 0 to quit: ";
                GET NUMBER;
                SUM = SUM + NUMBER;
                N = N + 1;
            END DO;

            PUT SKIP DATA "Average =", AVERAGE
END AVERAGE;
Python

Python may be the easiest language for humans to read: it is very close to being pseudocode you might write anyway.

Reading standard input until end-of-file can be done in many ways. One way would be to create an infinite loop with while True: and use an exception to get out of it. The following tries to be more verbose and tell the human reader exactly that’s what we are doing, but that necessitates importing the sys module in order to have a name for standard input.

# Calculating average in Python #1

import sys

sum = 0.0
for n, line in enumerate(sys.stdin):
    sum += float(line)
average = sum / (n + 1)
print(f'Average = {average}')

The next example uses list comprehension to process the data from the standard input. It requires enough memory to hold the whole file and more, but that will be a problem only with very large files.

First, sys.stdin.readlines() reads the standard I/O until EOF and returns everything in a list of strings. Next, list comprehension is used to create a copy of the (temporary) input buffer where each element is cast into floats. This list is assigned the name nums; and the rest is easy.

# Calculating average in Python #2

import sys

nums = [float(num) for num in sys.stdin.readlines()]
average = sum(nums) / len(nums)
print(f'Average = {average}\n')
R

It’s kind of meaningless to have this sample here, because as a statistical language R obviously has a built-in way for acquiring descriptive statistics like averages. numbers is here a vector that could be supplied by hand (say, via the c() function) or, more usually, be read from a data file.

average <- mean(numbers)
Racket

Racket is derived from Scheme which in turn is a dialect of Lisp. Racket can run Scheme programs but it also supports many different programming styles; you can actually switch from one Racket style to another just by adding a different #lang directive in the beginning of the source file.

This example shows “typed Racket” which basically means coding in Haskell style.

#lang typed/racket
;;; Calculating average in (typed) Racket

(: average (Number * -> Number))
(define (average . ns)
  (if (null? ns)
      0
      (/ (apply + ns) (length ns))))
REXX

REXX is a nice well-behaved little scripting language that’s been designed to be easily embeddable in applications. I used it a lot back in OS/2. The sample should be self-explanatory for all with any familiarity with procedural languages.

/* Calculating average in REXX */

sum = 0.0
n = 0
do loop until number = 0
    pull number
    sum = sum + number
    n = n + 1
end do
n = n - 1
average = sum / n
say "Average =" average
Ruby

Ruby is very much in the same category as Perl and Python, a script language suitable for small as well as for larger tasks as well, not being particularly slow in its typical tasks even while being “interpreted” (actually, bytecode-compiled), thus not requiring lengthy compile process when editing is in order. Unlike Perl and Python, it’s fully object-oriented, and thus it’s been called “Smalltalk to the masses”.

Syntactically Ruby is closer to Perl than Python, but it does not inherit the uglyness: variable names do not need to be preceded by silly characters (those which in Perl tell the type of the variable), statements do not need the trailing semicolons, and so on.

Some people see Ruby as the “successor” to Perl—that still remains to be seen, I guess.

# Calculating average in Ruby

sum = 0.0
n = 0
ARGF.each do |line|
    sum += line.to_f
    n += 1
end
average = sum / n
print "Average = #{average}"
Rust

Rust is designed to be a systems programming language that is as fast and, if needed, as low-level as C but safer and less error-prone. It looks very much like C but is actually more akin to the ML family of languages; for example, variables are immutable by default.

// Calculating average in Rust

use std::io;
use std::io::BufRead;

fn main() {
    let mut sum = 0.0;
    let mut n = 0;

    for num in io::stdin().lock().lines() {
        let num: f64 = num.unwrap().trim().parse().expect("NaN");
        sum += num;
        n += 1;
    }
    let avg = sum / n as f64;
    println!("Keskiarvo = {}", avg);
}
Scala

Scala is a newer language which tries to bring functional programming concepts into general purpose computing. It executes in the Java Virtual Machine (JVM). Programs can in general be quite effortlessly converted from Java to Scala, if not vice versa, because when using idiomatic functional Scala style the programs might be harder to translate to an imperative language. It is also possible to write in Scala almost as if in Java, although almost always Scala programs are still more compact and more to the point.

object Average {
    def main(args: Array[String]) {
        val numbers = for (num <- args) yield try { num.toDouble } catch { case _ => 0.0 }
        println("Average = " + (numbers.reduceLeft(_+_) / numbers.length))
    }
}
Scheme

Scheme is the other major old and venerable variant of Lisp (the other one is Common Lisp; newer variants like Clojure exist too). Unlike the variants that retain the name “Lisp”, Scheme strives both for syntactic simplicity and syntactic extensibility. It is still widely used in education, although Java and Python may have somewhat taken its place in that regard lately.

The following examples are identical: the second one just uses a syntactic convention with which one lambda can be expressed implicitly.

;;; Calculating average in Scheme #1

(define average
  (lambda (numbers)
    (/ (apply + numbers) (length numbers))))
;;; Calculating average in Scheme #2

(define (average . numbers)
  (/ (apply + numbers) (length numbers)))
sh

The following should work in most relatively recent UNIX shells that follow the POSIX or original Bourne shell syntax; this includes ash, bash, ksh, zsh and so on.

#!/bin/sh
# Calculating average in sh (bash, ksh, zsh…)

sum=0
n=0
while read number; do
    if [ x$number != x ]; then
        sum=$(( $sum + $number ))
        n=$(( $n + 1 ))
    fi
done
average=$(( $sum / $n ))
echo Average = $average
Tcl

Speaking of silly languages… Still, Tcl is pretty straigtforward once you get accustomed to the cumbersome notation used when, for example, setting values to variables.

Tcl is often (solely?) used because of its quite usable Tk GUI toolkit, so often in fact that you see the name “Tcl/Tk” mentioned much more often than plain Tcl.

(For years and years, the following code used to be syntactically incorrect. I knew of that but couldn’t run it anywhere to get it right. Now it seems to work at least on my Linux box.)

# Calculating average in Tcl

set number 1
set sum 0
set n 0

while { $number != 0 } {
    puts "Give a number or 0 to quit:"
    gets stdin number
    set sum [ expr $sum + $number ]
    incr n
}
set n [ expr $n - 1 ]
set average [ expr $sum / $n ]
puts stdout "Average = $average"
Zsh

The Z Shell or zsh is one of the most advanced descendants of the original Bourne shell (sh). There’s actually little that’s zsh-specific in the following sample: the emulate builtin to ensure certain defaults in case this is run as a function, declaring the parameter types as floats or integers, and the (( … )) notation for calculations.

#!/usr/bin/zsh
# Calculating average in ZSH

emulate -L zsh
setopt extended_glob

integer n
float sum number average

sum=0
n=0
while read number; do
    [[ $number == -#<->##.#<->## ]] && (( sum+=number, ++n ))
done
(( average=sum/n ))
print Average = $average
4DOS

Perhaps not a fully-fledged programming language, this one…; JP Software’s 4DOS was (and is, now as freeware) an alternative to the extremely cude MS-DOS command interpreter, command.com. It has reincarnated as 4OS2 for OS/2, 4NT for Windows NT, and Take Command for various Windows GUIs, all of which inherit the same syntax.

@echo off
rem Calculating average in 4DOS batch language

setlocal
set sum=0
set n=0
do while %number ne 0
    echo Give a number, or 0 to quit:
    input %%number
    set sum=%@eval[%sum + %number]
    set n=%@eval[%n + 1]
enddo
set n=%@eval[%n - 1]
set average=%@eval[%sum / %n]
echo Average = %average
endlocal