Count Lines/Words/Chars Back to the Win32 Shootout
Back to dada's perl lab

[The Original Shootout]   [NEWS]   [FAQ]   [Methodology]   [Platform Details]   [Acknowledgements]   [Scorecard]  
All Source For Count Lines/Words/Chars
wc.awka
# $Id: wc.gawk,v 1.3 2001/05/25 03:21:20 doug Exp $
# http://www.bagley.org/~doug/shootout/

# this program modified from:
#   http://cm.bell-labs.com/cm/cs/who/bwk/interps/pap.html
# Timing Trials, or, the Trials of Timing: Experiments with Scripting
# and User-Interface Languages</a> by Brian W. Kernighan and
# Christopher J. Van Wyk.

# this version is a little more efficient than the original via
# use of NR

BEGIN { delete ARGV }
{
    nc += length($0) + 1
    nw += NF
}
END { print NR, nw, nc }
wc.bcc
/* -*- mode: c -*-
 * $Id: wc.gcc,v 1.4 2001/05/24 20:55:35 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 *
 * this program is modified from:
 *   http://cm.bell-labs.com/cm/cs/who/bwk/interps/pap.html
 * Timing Trials, or, the Trials of Timing: Experiments with Scripting
 * and User-Interface Languages</a> by Brian W. Kernighan and
 * Christopher J. Van Wyk.
 *
 */

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

#define    IN    1    
#define    OUT    0    

int
main() {
    int i, c, nl, nw, nc, state, nread;
    char buf[4096];

    state = OUT;
    nl = nw = nc = 0;
    while ((nread = read(0, buf, sizeof(buf))) > 0) {
        nc += nread;
        for (i=0; i<nread; i++) {
            c = buf[i];
            if (c == '\n')
            ++nl;
            if (c == ' ' || c == '\r' || c == '\n' || c == '\t')
            state = OUT;
            else if (state == OUT) {
            state = IN;
            ++nw;
            }
        }
    }
    printf("%d %d %d\n", nl, nw, nc);
    return(0);
}
wc.bigforth
\ -*- mode: forth -*-
\ $Id: wc.bigforth,v 1.1 2001/06/24 22:27:35 doug Exp $
\ http://www.bagley.org/~doug/shootout/

variable  nn       0       nn !       \ number of newlines
variable  nw       0       nw !       \ number of words
variable  nc       0       nc !       \ number of chars
variable  in_word  0       in_word !  \ flag: "in word"

10  constant  nl_ch
9   constant  tab_ch
32  constant  space_ch

4096 constant MAXREAD
create buff MAXREAD allot

\ scan the buffer and count lines, words, chars
: scanbuff 
    dup nc +!                 \ update nc with amount of chars in buffer
    buff + buff           \ from start of buff to buff + n
    do
    i c@
    case
        nl_ch    of  0 in_word !  1 nn +!  endof
        tab_ch   of  0 in_word !  endof
        space_ch of  0 in_word !  endof
        \ otherwise:
        in_word @ 0=
        if
        1 in_word !
        1 nw +!
        then
    endcase
    loop ;

: wc 
    buff
    begin
        buff MAXREAD stdin read-file throw dup
    while
    scanbuff
    repeat ;

wc nn @ . nw @ . nc @ 1 u.r cr

bye \ th-th-that's all folks!
wc.csharp
// $Id: wc.csharp,v 1.0 2002/02/14 10:21:00 dada Exp $
// http://dada.perl.it/shootout/

using System;

class App {
    public static int Main(String[] args) {
        int nread;
        int i;
        char c;
        char[] buf = new char[4096];
        int nl = 0, nw = 0, nc = 0;
        bool state = false;
        while( (nread = Console.In.Read( buf, 0, 4096)) > 0 ) {
            nc += nread;
            for (i=0; i<nread; i++) {
                c = buf[i];
                if (c == '\n') ++nl;
                if (c == ' ' || c == '\n' || c == '\t') state = false;
                else if (state == false) {
                    state = true;
                    nw++;
                }
            }
        }
        Console.WriteLine(nl.ToString() + " " + nw.ToString() + " " + nc.ToString() + "\n");
        return(0);
    }
}
wc.cygperl
#!/usr/local/bin/perl
# $Id: wc.perl,v 1.2 2001/05/16 19:59:52 doug Exp $
# http://www.bagley.org/~doug/shootout/

# this program is modified from:
#   http://cm.bell-labs.com/cm/cs/who/bwk/interps/pap.html
# Timing Trials, or, the Trials of Timing: Experiments with Scripting
# and User-Interface Languages</a> by Brian W. Kernighan and
# Christopher J. Van Wyk.

use strict;

my($nl, $nw, $nc);

while(<STDIN>) {
    $nc += length;
    $nw += scalar(split);
    $nl += 1;
    # print "$nl $nw $nc\n";
}
print "$nl $nw $nc\n";
exit(0);
while (read(STDIN, $_, 4095)) {
    $_ .= <STDIN>;
    $nl += scalar(split(/\n/));
    $nc += length;
    $nw += scalar(split);
}
print "$nl $nw $nc\n";
wc.erlang
%%% -*- mode: erlang -*-
%%% $Id: wc.erlang,v 1.5 2001/06/26 05:09:25 doug Exp $
%%% http://www.bagley.org/~doug/shootout/

-module(wc).
-export([main/0, main/1]).

% TBD - this program should not assume lines are less than 10000 characters long

main() -> main(['1']).
main(Args) ->
    Port = open_port({fd, 0, 1}, [eof, {line, 10000}]),
    wc(Port, 0, 0, 0),
    halt(0).

wc(Port, NL, NW, NC) ->
    receive
    {Port, {_, {_, Line}}} ->
        wc(Port, NL + 1, NW + cw(Line, out, 0), NC + length(Line) + 1);
    {Port, eof} ->
        io:format("~w ~w ~w~n", [NL, NW, NC])
    end.

% count words in a line (list)
cw([],        _, Count) -> Count;
cw([$\ |T],   _, Count) -> cw(T, out, Count);
cw([$\t|T],   _, Count) -> cw(T, out, Count);
cw([_|T],   out, Count) -> cw(T, in, 1 + Count);
cw([_|T],    in, Count) -> cw(T, in, Count).
wc.fpascal
program wc;


uses SysUtils;

var
    nl, nw, nc: longint;
    Buf: array[1..4096] of byte;
    NumRead: Integer;

    A: Integer;
    Tmp: String;
    TmpPos : Byte;
    Ch: String;
    InWord: Boolean;
begin
    nl := 0;
    nc := 0;
    nw := 0;
    InWord := False;
    NumRead := FileRead(StdInputHandle, Buf, 4096);
    While NumRead > 0 Do
    begin
        Inc(nc, NumRead);
        For A := 1 To NumRead Do
        begin
            if Buf[A] = 10 Then Inc(nl);
            if Buf[A] = 13 Then Dec(nc);
            if (Buf[A] = 32) Or (Buf[A] = 10) Or (Buf[A] = 13) Or (Buf[A] = 9) Then 
                InWord := False
            else
            begin
                If InWord = False Then
                begin
                    Inc(nw);
                    InWord := True;
                end;
            end;
        end;
        NumRead := FileRead(StdInputHandle, Buf, 4096);
    end;
    WriteLn(IntToStr(nl) + ' ' + IntToStr(nw) + ' ' + IntToStr(nc));
end.
wc.gawk
# $Id: wc.gawk,v 1.3 2001/05/25 03:21:20 doug Exp $
# http://www.bagley.org/~doug/shootout/

# this program modified from:
#   http://cm.bell-labs.com/cm/cs/who/bwk/interps/pap.html
# Timing Trials, or, the Trials of Timing: Experiments with Scripting
# and User-Interface Languages</a> by Brian W. Kernighan and
# Christopher J. Van Wyk.

# this version is a little more efficient than the original via
# use of NR

BEGIN { delete ARGV }
{
    nc += length($0) + 1
    nw += NF
}
END { print NR, nw, nc }
wc.gcc
/* -*- mode: c -*-
 * $Id: wc.gcc,v 1.4 2001/05/24 20:55:35 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 *
 * this program is modified from:
 *   http://cm.bell-labs.com/cm/cs/who/bwk/interps/pap.html
 * Timing Trials, or, the Trials of Timing: Experiments with Scripting
 * and User-Interface Languages</a> by Brian W. Kernighan and
 * Christopher J. Van Wyk.
 *
 */

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

#define    IN    1    
#define    OUT    0    

int
main() {
    int i, c, nl, nw, nc, state, nread;
    char buf[4096];

    state = OUT;
    nl = nw = nc = 0;
    while ((nread = read(0, buf, sizeof(buf))) > 0) {
    nc += nread;
    for (i=0; i<nread; i++) {
        c = buf[i];
        if (c == '\n')
        ++nl;
        if (c == ' ' || c == '\n' || c == '\t')
        state = OUT;
        else if (state == OUT) {
        state = IN;
        ++nw;
        }
    }
    }
    printf("%d %d %d\n", nl, nw, nc);
    return(0);
}
wc.gforth
\ -*- mode: forth -*-
\ $Id: wc.gforth,v 1.2 2001/06/13 15:33:05 doug Exp $
\ http://www.bagley.org/~doug/shootout/

variable  nn       0       nn !       \ number of newlines
variable  nw       0       nw !       \ number of words
variable  nc       0       nc !       \ number of chars
variable  in_word  0       in_word !  \ flag: "in word"

10  constant  nl_ch
9   constant  tab_ch
32  constant  space_ch

4096 constant MAXREAD
create buff MAXREAD allot

\ scan the buffer and count lines, words, chars
: scanbuff 
    dup nc +!                 \ update nc with amount of chars in buffer
    buff + buff           \ from start of buff to buff + n
    do
    i c@
    case
        nl_ch    of  0 in_word !  1 nn +!  endof
        tab_ch   of  0 in_word !  endof
        space_ch of  0 in_word !  endof
        \ otherwise:
        in_word @ 0=
        if
        1 in_word !
        1 nw +!
        endif
    endcase
    loop ;

: wc 
    buff
    begin
        buff MAXREAD stdin read-file throw dup
    while
    scanbuff
    repeat ;

wc nn @ . nw @ . nc @ 1 u.r cr

bye \ th-th-that's all folks!
wc.ghc
-- $Id: wc.ghc,v 1.2 2001/05/24 14:05:53 doug Exp $
-- http://www.bagley.org/~doug/shootout/
-- from Brian Gregor

module Main where

-- compile with:  ghc -O -o wc -package lang wc.hs

import IO
import IOExts
import PackedString

main = do
         -- set buffer to 4k
         hSetBuffering stdin (BlockBuffering (Just 4096))
         -- these are mutable variables
         nL <- newIORef 0
         nW <- newIORef 0
     nC <- newIORef 0
         (nl,nw,nc) <- countAll nL nW nC
     putStrLn ((show nl)++" "++(show nw)++" "++(show nc))

countAll :: IORef Int -> IORef Int -> IORef Int -> IO (Int,Int,Int)
countAll nL nW nC = do 
         end <- hIsEOF stdin
         nl <- readIORef nL
        nw <- readIORef nW
         nc <- readIORef nC
         if (not end) 
            then (do  
              inStr <- hGetLine stdin
              -- using a packed string is a small speed win
              let str = packString inStr
              -- using IORefs makes it easy to force strict
              -- evaluation - how to easily do this without
              -- IORefs?
              writeIORef nL $! (nl + 1)
              writeIORef nW $! (nw + (length (wordsPS str)))
              writeIORef nC $! (nc + 1 + (lengthPS str))
              countAll nL nW nC)
            else  return (nl,nw,nc)
wc.gnat
-- $Id: wc.gnat,v 1.0 2003/06/11 12:11:00 dada Exp $
-- http://dada.perl.it/shootout/
-- Ada 95 code by C.C.

-- Annotated Ada Reference Manual ISO/IEC 8652:1995: http://www.ada-auth.org/

with Interfaces.C, System, Ada.Strings.Fixed, Ada.Text_IO;

procedure Wc is
   package IC renames Interfaces.C;
   function L_Trim (Source : String; Side : Ada.Strings.Trim_End :=
               Ada.Strings.Left) return String renames Ada.Strings.Fixed.Trim;

   package Io is
      type File_Descriptor is new IC.int;       --  STDIN=0, STDOUT=1, STDERR=2
      type Setmode_Flag is new IC.int;
      STDIN       : constant File_Descriptor := 0;
      O_BINARY    : constant Setmode_Flag := 16#8000#;

      function C_Setmode (
               FD       : File_Descriptor;
               Mode     : Setmode_Flag)
            return IC.int;

      function C_Sysread (
               FD       : File_Descriptor;
               Buf      : System.Address;
               NByte    : IC.int)
            return IC.int;
   private
      pragma Import (C, C_Setmode, "_setmode");          --  Microsoft Windows
      pragma Import (C, C_Sysread, "_read");
   end Io;

   Buffer      : String (1 .. 4 * 1024);
   NL, NW, NC  : Natural := 0;
   Inside_Word : Boolean := False;
   C           : Character;
   Last, R     : Integer;
begin
   R := Integer (Io.C_Setmode (Io.STDIN, Io.O_BINARY));  --  Read CR,LF right
   loop
      Last := Integer (Io.C_Sysread (FD => Io.STDIN,
                  Buf => Buffer (1)'Address, NByte => Buffer'Length));
      exit when Last <= 0;
      NC := NC + Last;
      for K in Buffer'First .. Last loop
         C := Buffer (K);
         if C = ASCII.LF then
            NL := NL + 1;
         end if;
         if C = ' ' or C = ASCII.CR or C = ASCII.LF or C = ASCII.HT then
            Inside_Word := False;
         elsif not Inside_Word then
            Inside_Word := True;
            NW := NW + 1;
         end if;
      end loop;
   end loop;
   Ada.Text_IO.Put_Line (L_Trim (Natural'Image (NL)) & Natural'Image (NW) &
            Natural'Image (NC));
end Wc;
   --  The "Ada.Streams.Stream_IO.Read (File, Item, Last)" procedure can't
   --  read from STDIN: can't associate Standard Input with File parameter.
   --  GNAT's Interfaces.C_Streams.fread function isn't from ISO/IEC 8652:1995.

wc.guile
#!/usr/local/bin/guile -s
!#

;;; $Id: wc.guile,v 1.7 2001/08/20 00:29:13 doug Exp $
;;; http://www.bagley.org/~doug/shootout/
;;; from Dale P. Smith

(define (wc iport)
  (let ((chars 0) (words 0) (lines 0) (inword 0) (x #f))
    (let loop ()
      (set! x (read-char iport))
      (if (eof-object? x)
      (begin (display lines) (display " ") (display words)
         (display " ") (display chars) (newline))
      (begin
        (set! chars (+ 1 chars))
        (if (not (char-whitespace? x))
        (set! inword 1)
        (begin
          (set! words (+ words inword))
          (set! inword 0)
          (if (char=? x #\newline)
              (set! lines (+ 1 lines)))))
        (loop))))))

(wc (current-input-port))
wc.ici
// $Id: wc.ici,v 1.0 2003/01/03 12:08:00 dada Exp $
// http://dada.perl.it/shootout
//
// contributed by Tim Long

nl = nw = nc = 0;
while (l = getline())
{
    ++nl;
    nc += nels(l) + 1;
    nw += nels(smash(l, #\S+#, ""));
}
printf("%d %d %d\n", nl, nw, nc);
wc.icon
# -*- mode: icon -*-
# $Id: wc.icon,v 1.1 2001/05/15 06:21:02 doug Exp $
# http://www.bagley.org/~doug/shootout/

procedure main(argv)
    local nl, nw, nc, nonspaces
    nl := nw := nc := 0
    nonspaces := ~' \t'
    while line := read() do line ? {
    nl +:= 1
    nc +:= 1 + *line
    while tab(upto(nonspaces)) do {
        nw +:= 1
        tab(many(nonspaces))
    }
    }
    write(nl, " ", nw, " ", nc)
end
wc.java
// $Id: wc.java,v 1.2 2001/05/31 22:56:19 doug Exp $
// http://www.bagley.org/~doug/shootout/
// with help from Dirus@programmer.net

import java.io.*;
import java.util.*;
import java.text.*;

// this program modified from:
//   http://cm.bell-labs.com/cm/cs/who/bwk/interps/pap.html
// Timing Trials, or, the Trials of Timing: Experiments with Scripting
// and User-Interface Languages</a> by Brian W. Kernighan and
// Christopher J. Van Wyk.

public class wc {
    public static void main(String[] args) {
        int nl = 0, nw = 0, nc = 0;

        try {
            byte[] buff = new byte[4096];
            boolean inword = false;
            int length;

            while ((length = System.in.read(buff)) != -1) {
                nc += length;
                for(int i = 0; i < length; i++) {
                    char c = (char)buff[i];
                    if (c == '\n')
                        ++nl;
                    if (Character.isWhitespace(c))
                        inword = false;
                    else if (inword == false) {
                        ++nw;
                        inword = true;
                    }
                }
            }
        } catch (IOException e) {
            System.err.println(e);
            return;
        }
        System.out.println(Integer.toString(nl) + " " +
                           Integer.toString(nw) + " " +
                           Integer.toString(nc));
    }
}
wc.jscript
// -*- mode: java -*-
// $Id: wc.njs,v 1.1 2001/07/10 02:36:59 doug Exp $
// http://www.bagley.org/~doug/shootout/
// from David Hedbor
// modified by Aldo Calpini <dada@perl.it> for Win32

var nl = 0, nw = 0, nc = 0; // line, word and character counters

var buf, i;
var stdin = WScript.StdIn;
while(!stdin.AtEndOfStream) {
  buf = stdin.readLine();
  if(buf.length > 0) {
    nc += buf.length;
    var words = buf.split(/\s+/);
    nw += words.length;
  }
  nc += 1;
  nl += 1;
  // WScript.Echo(nl, nw, nc);  
} 

WScript.Echo(nl, nw, nc);
wc.lcc
/* -*- mode: c -*-
 * $Id: wc.gcc,v 1.4 2001/05/24 20:55:35 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 *
 * this program is modified from:
 *   http://cm.bell-labs.com/cm/cs/who/bwk/interps/pap.html
 * Timing Trials, or, the Trials of Timing: Experiments with Scripting
 * and User-Interface Languages</a> by Brian W. Kernighan and
 * Christopher J. Van Wyk.
 *
 */

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

#define    IN    1    
#define    OUT    0    

int
main() {
    int i, c, nl, nw, nc, state, nread;
    char buf[4096];

    state = OUT;
    nl = nw = nc = 0;
    while ((nread = read(0, buf, sizeof(buf))) > 0) {
    nc += nread;
    for (i=0; i<nread; i++) {
        c = buf[i];
        if (c == '\n')
        ++nl;
        if (c == ' ' || c == '\n' || c == '\t')
        state = OUT;
        else if (state == OUT) {
        state = IN;
        ++nw;
        }
    }
    }
    printf("%d %d %d\n", nl, nw, nc);
    return(0);
}
wc.lua
-- $Id: wc.lua,v 1.1 2001/05/14 16:33:47 doug Exp $
-- http://www.bagley.org/~doug/shootout/
-- from Roberto Ierusalimschy

BUFSIZE = 2^12

local cc,lc,wc = 0,0,0
while 1 do
    local lines, rest = read(BUFSIZE, "*l")
    if lines == nil then break end
    if rest then lines = lines..rest..'\n' end
    cc = cc+strlen(lines)
    local _,t = gsub(lines, "%S+", "")   -- count words in the line
    wc = wc+t
    _,t = gsub(lines, "\n", "\n")   -- count newlines in the line
    lc = lc+t
end

write(lc, " ", wc, " ", cc, "\n")
wc.lua5
-- $Id: wc.lua,v 1.1 2001/05/14 16:33:47 doug Exp $
-- http://www.bagley.org/~doug/shootout/
-- contributed by Roberto Ierusalimschy

local cc,lc,wc = 0,0,0
for line in io.lines() do
  cc = cc + string.len(line)  -- count chars in the line
  local _,t = string.gsub(line, "%S+", "")   -- count words in the line
  wc = wc+t
  lc = lc+1            -- count lines
end
cc = cc + lc   -- count the newlines as characters

io.write(lc, " ", wc, " ", cc, "\n")

wc.mawk
# $Id: wc.mawk,v 1.3 2001/05/25 03:21:51 doug Exp $
# http://www.bagley.org/~doug/shootout/

# this program modified from:
#   http://cm.bell-labs.com/cm/cs/who/bwk/interps/pap.html
# Timing Trials, or, the Trials of Timing: Experiments with Scripting
# and User-Interface Languages</a> by Brian W. Kernighan and
# Christopher J. Van Wyk.

# this version is a little more efficient than the original via
# use of NR

BEGIN { delete ARGV }
{
    nc += length($0) + 1
    nw += NF
}
END { print NR, nw, nc }
wc.mingw32
/* -*- mode: c -*-
 * $Id: wc.gcc,v 1.4 2001/05/24 20:55:35 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 *
 * this program is modified from:
 *   http://cm.bell-labs.com/cm/cs/who/bwk/interps/pap.html
 * Timing Trials, or, the Trials of Timing: Experiments with Scripting
 * and User-Interface Languages</a> by Brian W. Kernighan and
 * Christopher J. Van Wyk.
 *
 */

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

#define    IN    1    
#define    OUT    0    

int
main() {
    int i, c, nl, nw, nc, state, nread;
    char buf[4096];

    state = OUT;
    nl = nw = nc = 0;
    while ((nread = read(0, buf, sizeof(buf))) > 0) {
    nc += nread;
    for (i=0; i<nread; i++) {
        c = buf[i];
        if (c == '\n')
        ++nl;
        if (c == ' ' || c == '\n' || c == '\t')
        state = OUT;
        else if (state == OUT) {
        state = IN;
        ++nw;
        }
    }
    }
    printf("%d %d %d\n", nl, nw, nc);
    return(0);
}
wc.modula2
(* The Great Win32 Language Shootout http://dada.perl.it/shootout/

   contributed by Isaac Gouy (Modula2 novice)

   To build: xc =m wc
   To run:   wc < input.txt
*)

MODULE Wc;
<* m2extensions + *>

FROM SRawIO IMPORT Read;
FROM SIOResult IMPORT ReadResult, wrongFormat;
FROM SYSTEM IMPORT ADR, FILL;
FROM STextIO IMPORT WriteLn;
FROM SWholeIO IMPORT WriteCard;

CONST
   buffer_size = 4096;
   LF = CHR(10);
   CR = CHR(13);
   TAB = CHR(9);
   Space = CHR(32);
   Null = CHR(0);


TYPE Buffer_Type = ARRAY [1..buffer_size] OF CHAR;


PROCEDURE Fill(VAR buf: Buffer_Type);
   VAR i: INTEGER;
BEGIN
   (* Clear the buffer *)
   FILL( ADR(buf), Null, buffer_size );

   (* Raw read into the buffer *)
   Read(buf);

   IF ReadResult() = wrongFormat THEN
      (* ignore LF if it's followed by end of input *)
      i := LENGTH(buf);
      IF (i > 0) AND (buf[i] = LF) THEN
         buf[i] := Null;
      END;
   END;
END Fill;


VAR
   nc, nl, nw: CARDINAL;
   i, read_length: CARDINAL;
   buf: Buffer_Type;
   c: CHAR;
   insideWord: BOOLEAN;

BEGIN
   insideWord := FALSE;	
   REPEAT
      Fill(buf);

      read_length := LENGTH(buf);	
      INC(nc, read_length);	
      FOR i := 1 TO read_length DO
         c := buf[i];
         IF c = LF THEN INC(nl); END;	
         IF (c = Space) OR (c = LF) OR (c = TAB) OR (c = CR) THEN
            insideWord := FALSE;	
         ELSIF NOT insideWord THEN
            insideWord := TRUE;	
            INC(nw);
         END;
      END;
   UNTIL read_length<1;

   WriteCard(nl,1); WriteCard(nw,0); WriteCard(nc,0); WriteLn;
END Wc.
wc.nice
/* The Great Win32 Language Shootout http://dada.perl.it/shootout/ 
   contributed by Isaac Gouy (Nice novice)

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

To run:
   java -jar wc.jar < input.txt > out.txt
*/


import java.io.*;

void main(String[] args){
   let int newline = 0xA;
   let int space = 0x20;
   let int cr = 0xD;
   let int tab = 0x9;

   int value, nl = 0, nw = 0, nc = 0;
   try {
      boolean insideWord = false;
      BufferedReader r = new BufferedReader(new InputStreamReader(System.in));
      while ((value = r.read()) != -1){
         ++nc;
         if (value == newline) ++nl;
         if (value == space || value == cr || value == newline || value == tab) 
            insideWord = false;
         else if (!insideWord) {
            insideWord = true;
            ++nw;
         }
      }
   } catch (IOException e) { System.err.println(e); }

   print(nl); print(" "); print(nw); print(" "); println(nc);
}
wc.ocaml
(*
 * $Id: wc.ocaml,v 1.7 2001/05/25 22:33:22 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 * based on code by Cuihtlauac ALVARADO and Markus Mottl
 *)

let nl = ref 0
let nw = ref 0
let nc = ref 0
let max = 4096
let buf = String.create max

let readblock scanfun =
  let nread = input stdin buf 0 max in
  if nread = 0 then () else
  begin nc := !nc + nread; scanfun 0 nread end


let rec scan_out_of_word i n =
  if i < n then
    match buf.[i] with
    | '\n'     -> incr nl; scan_out_of_word (i+1) n
    | ' '|'\t' ->          scan_out_of_word (i+1) n
    | _        -> incr nw; scan_in_word (i+1) n
  else
    readblock scan_out_of_word

and scan_in_word i n =
  if i < n then
    match buf.[i] with
    | '\n'     -> incr nl; scan_out_of_word (i+1) n
    | ' '|'\t' ->          scan_out_of_word (i+1) n
    | _        ->          scan_in_word (i+1) n
  else
    readblock scan_in_word


let _ =
  scan_out_of_word 0 0;
  Printf.printf "%d %d %d\n" !nl !nw !nc
wc.ocamlb
(*
 * $Id: wc.ocaml,v 1.7 2001/05/25 22:33:22 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 * based on code by Cuihtlauac ALVARADO and Markus Mottl
 *)

let nl = ref 0
let nw = ref 0
let nc = ref 0
let max = 4096
let buf = String.create max

let readblock scanfun =
  let nread = input stdin buf 0 max in
  if nread = 0 then () else
  begin nc := !nc + nread; scanfun 0 nread end


let rec scan_out_of_word i n =
  if i < n then
    match buf.[i] with
    | '\n'     -> incr nl; scan_out_of_word (i+1) n
    | ' '|'\t' ->          scan_out_of_word (i+1) n
    | _        -> incr nw; scan_in_word (i+1) n
  else
    readblock scan_out_of_word

and scan_in_word i n =
  if i < n then
    match buf.[i] with
    | '\n'     -> incr nl; scan_out_of_word (i+1) n
    | ' '|'\t' ->          scan_out_of_word (i+1) n
    | _        ->          scan_in_word (i+1) n
  else
    readblock scan_in_word


let _ =
  scan_out_of_word 0 0;
  Printf.printf "%d %d %d\n" !nl !nw !nc
wc.perl
#!/usr/local/bin/perl
# $Id: wc.perl,v 1.2 2001/05/16 19:59:52 doug Exp $
# http://www.bagley.org/~doug/shootout/

# this program is modified from:
#   http://cm.bell-labs.com/cm/cs/who/bwk/interps/pap.html
# Timing Trials, or, the Trials of Timing: Experiments with Scripting
# and User-Interface Languages</a> by Brian W. Kernighan and
# Christopher J. Van Wyk.

use strict;

my($nl, $nw, $nc);

while(<STDIN>) {
    $nc += length;
    $nw += scalar(split);
    $nl += 1;
    # print "$nl $nw $nc\n";
}
print "$nl $nw $nc\n";
exit(0);
while (read(STDIN, $_, 4095)) {
    $_ .= <STDIN>;
    $nl += scalar(split(/\n/));
    $nc += length;
    $nw += scalar(split);
}
print "$nl $nw $nc\n";
wc.php
<?php
/*
 $Id: wc.php,v 1.4 2001/06/26 05:10:01 doug Exp $
 http://www.bagley.org/~doug/shootout/
 
 TBD - this program should not assume lines are less than 10000 characters long
*/

$fd = fopen("php://stdin", "r");
$nl = $nw = $nc = 0;
while (!feof ($fd)) {
    if ($line = fgets($fd, 10000)) {
    ++$nl;
    $nc += strlen($line);
    $nw += count(preg_split("/\s+/", $line, -1, PREG_SPLIT_NO_EMPTY));
    }
}
fclose($fd);
print "$nl $nw $nc\n";
?>
wc.pike
#!/usr/local/bin/pike// -*- mode: pike -*-
// $Id: wc.pike,v 1.4 2001/06/07 17:55:11 doug Exp $
// http://www.bagley.org/~doug/shootout/
// from Per Hedbor, optimized by David Hedbor

enum State { Outside, Inside };

void main() {
    int nl = 0, nw = 0, nc = 0; // line, word and character counters
    int sl; // Size of input

    State state = Outside; // Inside or outside word

    string buf;
    string rest="";
    array l;
    do {
    buf = replace(Stdio.stdin.read( 4196 ), "\t", " ");
    if(strlen(buf)) {
        nc += sizeof(buf);
        l = (rest+ buf) / "\n";
        nl += sizeof(l)-1;
        foreach(l[..sizeof(l)-2], rest) {
        nw += sizeof(rest / " " - ({""}));
        }
        if(sizeof(l)>1) {
        rest = l[-1];
        } //else rest="";
    } else {
        nw += sizeof(rest / " " - ({""}));
        break;
    }
    } while( 1 );
    write("%d %d %d\n", nl, nw, nc);
}
wc.pliant
# $Id: wc.pliant,v 1.0 2002/02/11 17:03:00 dada Exp $
# http://dada.perl.it/shootout/

module "/pliant/language/unsafe.pli"
module "/pliant/language/context.pli"
module "/pliant/language/stream.pli"
module "/pliant/language/os.pli"

gvar Str line := ""
gvar Address Buf
gvar Int ReadSize := 4096
gvar Int i
gvar Int nl := 0
gvar Int nw := 0
gvar Int nc := 0
gvar Char ch
gvar Int j
gvar CBool state := false
gvar CBool ok
gvar Int ReadCount
gvar Int s := os_GetStdHandle -10

Buf := memory_allocate ReadSize+1 null

ok := os_ReadFile s Buf ReadSize ReadCount null
while ok and ReadCount > 0
  line set Buf ReadCount false    
  nc := nc + (line len)
  i := 0
  while i<line:len
    ch := line:i
    if ch="[lf]"
      nl += 1
    if ch=" " or ch="[tab]" or ch="[lf]"
      state := false
    eif state = false
      nw += 1
      state := true
    i += 1

  ok := os_ReadFile s Buf ReadSize ReadCount null

console nl " " nw " " nc eol
wc.poplisp
;;; -*- mode: lisp -*-
;;; $Id: wc.cmucl,v 1.3 2001/06/05 13:19:24 doug Exp $
;;; http://www.bagley.org/~doug/shootout/
;;; from Bulent Murtezaoglu (with some code from Andrew McDowell)

(declaim (optimize (speed 3) (debug 0) (safety 0) (space 0) (compilation-speed 0)))
     
  (let* ((start 0)
     (current #\X)            ;junk char save me the locally
     (end 0)
     (nc 0)
     (buffer (make-string 4096)))
    (declare (type (simple-base-string 4096) buffer) (fixnum start end nc)
         (base-char current))
    (labels
    ((get-char ()
           (when (= start end)
             (setf start 0)
             (setf end (read-sequence buffer *standard-input*))
             (incf nc end)
             (when (zerop end)
               (return-from get-char nil)))
           (setf current (schar buffer start))
           (incf start)))
      (let ((nl 0)
        (nw 0)
        (inword nil))
    (declare (fixnum nl nw))
    (loop while (get-char) do
      (cond ((char= current #\newline)
         (incf nl)
         (setq inword nil))
        ((or (char= current #\space) (char= current #\tab))
         (setq inword nil))
        ((not inword) ;; only tested if we have a word constituent
         (incf nw) (setq inword t))))
    (format t "~A ~A ~A~%" nl nw nc))))
wc.python
#!/usr/local/bin/python
# $Id: wc.python,v 1.2 2001/05/15 03:11:19 doug Exp $
# http://www.bagley.org/~doug/shootout/

import sys

def main():
    nl = nw = nc = 0
    rl = sys.stdin.readlines
    lines = rl(4096)
    while lines:
        for line in lines:
            nl += 1
            nc += len(line)
            nw += len(line.split())
        lines = rl(4096)

    print "%d %d %d" % (nl, nw, nc)

main()
wc.rexx
nl = 0
nw = 0
nc = 0
DO UNTIL LINES() = 0
    PARSE LINEIN L
    nw = nw + WORDS(L)
    nc = nc + LENGTH(L) + 1
    nl = nl + 1
END
nc = nc - 1
nl = nl - 1
SAY nl nw nc
wc.ruby
#!/usr/local/bin/ruby
# -*- mode: ruby -*-
# $Id: wc.ruby,v 1.5 2001/06/26 05:07:54 doug Exp $
# http://www.bagley.org/~doug/shootout/
# with help from Paul Brannan

nl = nw = nc = 0
loop do
  data = (STDIN.read(4096) or break) << (STDIN.gets || "")
  nc += data.length
  nl += data.count("\n")
  ((data.strip! || data).tr!("\n", " ") || data).squeeze!
  nw += data.count(" ") + 1
end
puts "#{nl} #{nw} #{nc}"
wc.se
-- -*- mode: eiffel -*-
-- $Id: wc.se,v 1.1 2001/05/14 17:39:13 doug Exp $
-- http://www.bagley.org/~doug/shootout/

class WC

creation make

feature

   make is

      local
     nl, nw, nc, state: INTEGER;
     c: CHARACTER;
      do
     nl := 0
     nw := 0
     nc := 0
     state := 0
     from
        io.read_character
     until
        io.end_of_input
     loop
        c := io.last_character
        nc := nc + 1
        if c = '%N' then
           nl := nl + 1
        end
        if c = ' ' or c = '%N' or c = '%T' then
           state := 0
        else
           if state = 0 then
          state := 1
          nw := nw + 1
           end
        end
        io.read_character
     end
         std_output.put_integer(nl)
         std_output.put_character(' ')
         std_output.put_integer(nw)
         std_output.put_character(' ')
         std_output.put_integer(nc)
         std_output.put_character('%N')
      end
end
wc.slang
% $Id: wc.slang,v 1.0 2003/01/03 14:41:00 dada Exp $
% http://dada.perl.it/shootout/
%
% contributed by John E. Davis

define main()
{
   variable nl, nw, nc;
   
   nl = 0; nw = 0; nc = 0;
   
   foreach (stdin) using ("line")
     {
    variable line = ();
        nl++;
    nc += strlen (line);
    nw += length (strtok (line));
     }

   vmessage ("%d %d %d", nl, nw, nc);
}

main()
wc.smlnj
(* -*- mode: sml -*-
 * $Id: wc.smlnj,v 1.2 2001/07/09 00:25:29 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 * from Stephen Weeks
 *)


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

fun incr r = r := !r + 1
   
val nl = ref 0
val nw = ref 0
val nc = ref 0
val max = 4096
val buf = Word8Array.array (max, 0w0)
val sub = Word8Array.sub

fun readblock scanfun =
   let
      val nread = Posix.IO.readArr (Posix.FileSys.stdin,
                    {buf = buf, i =  0, sz = NONE})
   in
      if nread = 0
     then ()
      else (nc := !nc + nread;
        scanfun (0, nread))
   end

val c2b = Byte.charToByte
val newline = c2b #"\n"
val space = c2b #" "
val tab = c2b #"\t"

fun scan_out_of_word (i, n) =
   if i < n
      then
     let
        val c = sub (buf, i)
     in
        if c = newline
           then (incr nl; scan_out_of_word (i + 1, n))
        else if c = space orelse c = tab
            then scan_out_of_word (i + 1, n)
         else (incr nw; scan_in_word (i + 1, n))
     end
   else readblock scan_out_of_word

and scan_in_word (i, n) =
  if i < n then
     let
    val c = sub (buf, i)
     in
    if c = newline
       then (incr nl; scan_out_of_word (i + 1, n))
    else if c = space orelse c = tab
        then scan_out_of_word (i + 1, n)
         else scan_in_word (i + 1, n)
     end
  else readblock scan_in_word

fun printl [] = print "\n" | printl(h::t) = ( print h ; printl t )
   
fun main (name, args) =
  let
    val _ =
        (scan_out_of_word (0, 0);
    printl [Int.toString (!nl), " ", Int.toString (!nw), " ", Int.toString (!nc)])
  in
    OS.Process.success
  end
end

val _ = SMLofNJ.exportFn("wc", Test.main);
wc.tcl
#!/usr/local/bin/tclsh
# $Id: wc.tcl,v 1.5 2001/05/17 15:44:09 doug Exp $
# http://www.bagley.org/~doug/shootout/

# this program is modified from:
#   http://cm.bell-labs.com/cm/cs/who/bwk/interps/pap.html
# Timing Trials, or, the Trials of Timing: Experiments with Scripting
# and User-Interface Languages</a> by Brian W. Kernighan and
# Christopher J. Van Wyk.

# Modified by Miguel Sofer and Jeff Hobbs

proc main {} {
    set nl 0
    set nc 0
    set nw 0

    set map [list \" x \{ x \} x]
    while {1} {
    set data [read stdin 4096]
    if {![string length $data]} {break}
    if {[gets stdin extra] >= 0} {
        append data $extra
        incr nc
    }
    incr nc [string length $data]
    incr nw [llength [string map $map $data]]
    incr nl [llength [split $data "\n"]]
    }
    puts "$nl $nw $nc"
}

main
wc.vc
/* -*- mode: c -*-
 * $Id: wc.gcc,v 1.4 2001/05/24 20:55:35 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 *
 * this program is modified from:
 *   http://cm.bell-labs.com/cm/cs/who/bwk/interps/pap.html
 * Timing Trials, or, the Trials of Timing: Experiments with Scripting
 * and User-Interface Languages</a> by Brian W. Kernighan and
 * Christopher J. Van Wyk.
 *
 */

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

#define    IN    1    
#define    OUT    0    

int
main() {
    int i, c, nl, nw, nc, state, nread;
    char buf[4096];

    state = OUT;
    nl = nw = nc = 0;
    while ((nread = read(0, buf, sizeof(buf))) > 0) {
    nc += nread;
    for (i=0; i<nread; i++) {
        c = buf[i];
        if (c == '\n')
        ++nl;
        if (c == ' ' || c == '\n' || c == '\t')
        state = OUT;
        else if (state == OUT) {
        state = IN;
        ++nw;
        }
    }
    }
    printf("%d %d %d\n", nl, nw, nc);
    return(0);
}
wc.vc++
// -*- mode: c++ -*-
// $Id: wc.g++,v 1.4 2001/07/08 18:45:52 doug Exp $
// http://www.bagley.org/~doug/shootout/

#include <iostream>
#include <vector>

using namespace std;

enum {
    OUT,            
    IN                
};

int
main(int argc, char *argv[]) {
    char c;
    int nl, nw, nc, state;

    ios_base::sync_with_stdio(false);
    cin.tie(0);

    state = OUT;
    nl = nw = nc = 0;
    while (cin.get(c)) {
    ++nc;
    if (c == '\n')
        ++nl;
    if (c == ' ' || c == '\n' || c == '\t')
        state = OUT;
    else if (state == OUT) {
        state = IN;
        ++nw;
    }
    }
    cout << nl << " " << nw << " " << nc << endl;
}
wc.vpascal
program wc;

uses SysUtils, Windows;

var
    StdInputHandle: longint;
    
    nl, nw, nc: longint;
    Buf: array[1..4096] of byte;
    NumRead: Integer;

    A: Integer;
    Tmp: String;
    TmpPos : Byte;
    Ch: String;
    InWord: Boolean;
begin
    StdInputHandle := GetStdHandle(std_Input_Handle);
    nl := 0;
    nc := 0;
    nw := 0;
    InWord := False;
    NumRead := FileRead(StdInputHandle, Buf, 4096);
    While NumRead > 0 Do
    begin
        Inc(nc, NumRead);
        For A := 1 To NumRead Do
        begin
            if Buf[A] = 10 Then Inc(nl);
            if Buf[A] = 13 Then Dec(nc);
            if (Buf[A] = 32) Or (Buf[A] = 10) Or (Buf[A] = 13) Or (Buf[A] = 9) Then 
                InWord := False
            else
            begin
                If InWord = False Then
                begin
                    Inc(nw);
                    InWord := True;
                end;
            end;
        end;
        NumRead := FileRead(StdInputHandle, Buf, 4096);
    end;
    WriteLn(IntToStr(nl) + ' ' + IntToStr(nw) + ' ' + IntToStr(nc));
end.