$mode uni
// Usage: fallsong n for "American" verison starting at n bottles.
// takesong n for "British" version
// eM n - general utility which returns english version of n.
// Note: Definition of billion, trillion, etc. follow American usage.
// Limits: Some counting and reporting problems caused by comparison
// tolerance and floating-point numbers above one trillion.
// Absolute limit: Approximately 9.9998354e65, at which point
// floating-point representation becomes unreliable.
ewd1:=("zero";"one";"two";"three";"four";"five";"six";"seven";"eight";"nine";
"ten";"eleven";"twelve";"thirteen";"fourteen";"fifteen";"sixteen";
"seventeen";"eighteen";"nineteen")
ewd10:=("";"";"twenty";"thirty";"forty";"fifty";"sixty";"seventy";
"eighty";"ninety"); ewdh:=" hundred"; ewdc:=" and ";
epow:=("";" thousand")," ",~("m";"b";"tr";"quadr";"quint";"sext";"sept";
"oct";"non";"dec";"undec";"duodec";"tredec";"quattuordec";"quindec";
"sexdec";"septendec";"octodec";"novemdec";"vigint"),~<"illion"
eH n:{if(20<=n){(t;xx):=0 10 M.>n;(t I.>ewd10),if(0=xx)""else "-",xx I.>ewd1}
else n I.> ewd1}
eT n:{if(100<=n){(h;x):=0 100 M.>n;(h I.>ewd1),ewdh,if(0=x)""else ewdc,eH x}
else eH n}
eM n:{z:="";(i:=#epow)do{
(n;x):=0 1000 M.>n;
if(0!=x)z:=,(((100>x)&(i=0)&0!=n)/"and "),(eT M.-x),(i I.>epow),
((0!=#z)/", "),z;
if(0=n):=z};z}
cap str:{n:=`int|1 S.+str;if((97<=n)&122>=n)str[0]:=`char|n- 32;str}
nb n:(if(0!=n)(cap eM n)else "No more"),((- 1=n)S.-" bottles")," of beer"
ootb n:if(1!=n)"one of those bottles"else"that bottle"
fate{b;n}:{if(b)".\nIf ",(ootb n)," should happen to fall,\n" else
".\nTake ",((1=n)I.>("one";"it"))," down; pass it around,\n"}
b stanza n:{w:=" on the wall.";
(nb n),w,"\n",(nb n),(b fate n),(nb n- 1),w,"\n"}
fallsong n:{(i:=n)do S.- 1 stanza n-i;}
takesong n:{(i:=n)do S.- 0 stanza n-i;}
REPORT z_99_bottles_of_beer.
*&---------------------------------------------------------------------*
*& Author: Dominik Ritter *
*& Sprache: ABAP-Objects *
*& Version: SAP R/3 4.6c
*&---------------------------------------------------------------------*
CLASS shelf DEFINITION.
PUBLIC SECTION.
METHODS: constructor IMPORTING value(bottles) TYPE i,
take_bottles IMPORTING value(n) TYPE i,
bottles_left EXPORTING value(bottles) TYPE i.
PROTECTED SECTION.
DATA: no_bottles TYPE i.
ENDCLASS.
CLASS shelf IMPLEMENTATION.
METHOD constructor.
no_bottles = bottles.
ENDMETHOD.
METHOD take_bottles.
no_bottles = no_bottles - n.
ENDMETHOD.
METHOD bottles_left.
bottles = no_bottles.
ENDMETHOD.
ENDCLASS.
DATA: beer TYPE REF TO shelf.
DATA: bottlesonshelf TYPE i.
START-OF-SELECTION.
CREATE OBJECT: beer EXPORTING bottles = 99.
CALL METHOD beer->bottles_left IMPORTING bottles = bottlesonshelf.
WHILE bottlesonshelf GT 1.
WRITE:/(2) bottlesonshelf, ' bottles of beer on the wall, '.
WRITE:/(2) bottlesonshelf, ' bottles of beer.'.
WRITE:/ 'Take one down, pass it around, '.
CALL METHOD beer->take_bottles EXPORTING n = 1.
CALL METHOD beer->bottles_left IMPORTING bottles = bottlesonshelf.
WRITE:/(2) bottlesonshelf, ' bottles of beer on the wall.'.
SKIP.
ENDWHILE.
WRITE:/ '1 bottle of beer on the wall,'.
WRITE:/ '1 bottle of beer.'.
WRITE:/ 'Take one down, pass it around, '.
WRITE:/ 'no more bottles of beer on the wall.'.
REPORT z_99_bottles_of_beer.
*&---------------------------------------------------------------------*
*& Author: Dominik Ritter *
*&---------------------------------------------------------------------*
DATA: nobottles TYPE i.
START-OF-SELECTION.
nobottles = 99.
WHILE nobottles GT 1.
WRITE:/(2) nobottles, ' bottles of beer on the wall, '.
WRITE:/(2) nobottles, ' bottles of beer.'.
WRITE:/ 'Take one down, pass it around, '.
nobottles = nobottles - 1.
WRITE:/(2) nobottles, ' bottles of beer on the wall.'.
SKIP.
ENDWHILE.
WRITE:/ '1 bottle of beer on the wall,'.
WRITE:/ '1 bottle of beer.'.
WRITE:/ 'Take one down, pass it around, '.
WRITE:/ 'no more bottles of beer on the wall.'.
<a href=http://www.cwi.nl/cwi/projects/abc.html>ABC</a> was developed
at CWI in the Netherlands.
PUT "by Whitey (whitey@netcom.com) - 10/13/96" IN author
HOW TO RETURN verse n:
SELECT:
n = 0:
PUT "no more bottles of beer" IN s
n = 1:
PUT "1 bottle of beer" IN s
ELSE:
PUT "`n` bottles of beer" IN s
RETURN s
HOW TO DRINK:
PUT 99 IN num
WHILE num > 0:
WRITE verse num, " on the wall, ", verse num, "," /
WRITE "take one down, pass it around," /
PUT num - 1 IN num
WRITE verse num, " on the wall." /
DRINK
\ Abundance version of 99 bottles of beer RG 2.0/1.0 97/03/08
<<<DEFINE 1 99 SMALL All-Bottles DEFINE>>>
<<< Bottles ( count -- ) DUP WRITE
CASE 0 OF DROP " No more bottles " ENDOF
1 OF DROP " 1 bottle " ENDOF
OTHERS OF . " bottles " ENDOF ENDCASE >>>
<<< Sing
WRITE
<<<RFOR All-Bottles
I Bottles " of beer on the wall, "
I Bottles " of beer" NL
" Take one down and pass it around," NL
I 1- Bottles " of beer on the wall." 2 NLS
RFOR>>> >>>
// "99 bottles of beer" in ActionScript
// by David Fichtmueller ( david@fichtmueller.de )
b = 99;
for (i=1; i<=99; i++) {
txt = txt+b+" bottle(s) of beer on the wall. "+b+" bottle(s) of beer. Take
one down, pass it around, ";
b = b-1;
txt = txt+b+" bottle(s) of beer on the wall. ";
}
stop ();
-- Just for amusement, here's a multi-tasking version.
-- Ten customers enter bar to sing and drink. Bartender serializes
-- access to 'take one down' to avoid fights
-- contributed by tmoran@bix.com
with Text_IO;
procedure Bar is
Out_Of_Beer : Exception;
protected Bartender is
function Count return Integer;
procedure Take_One_Down;
private
Remaining : Integer range 0 .. 99 := 99;
end Bartender;
protected body Bartender is
function Count return Integer is
begin return Remaining; end Count;
procedure Take_One_Down is
begin
if Remaining = 0 then raise Out_Of_Beer;
else Remaining := Remaining - 1;
end if;
end Take_One_Down;
end Bartender;
type Names is (Charles, Ada, John, Grace, Donald,
Edsger, Niklaus, Seymour, Fred, Harlan);
task type Customers is
entry Enter_Bar(Who : in Names);
end Customers;
Customer_List : array(Names) of Customers;
task body Customers is
Me : Names;
procedure Sing_And_Drink(Singer_ID : in String) is
procedure Sing(S : in String) renames Text_IO.Put_Line;
begin
loop
declare
Bottle_Part : constant String
:= Integer'image(Bartender.Count) & " bottles of beer";
begin
Sing(Bottle_Part & " on the wall" & Singer_ID);
Sing(Bottle_Part & Singer_ID);
end;
Sing(" Take one down and pass it arround" & Singer_ID);
Bartender.Take_One_Down;
delay 10.0; -- allow ten seconds to gulp one down
end loop;
exception
when Out_Of_Beer => Sing("no more beer!" & Singer_ID);
end Sing_And_Drink;
begin -- customer task
accept Enter_Bar(Who : in Names) do
Me := Who;
end Enter_Bar;
Sing_And_Drink(" - " & Names'image(Me));
end Customers;
begin -- operating bar
for Person in Customer_List'range loop
Customer_List(Person).Enter_Bar(Person);
delay 2.0; -- allow two seconds between customers entering bar
end loop;
end Bar;
/* Ada version of 99 Bottles of Beer */
with TEXT_IO; use TEXT_IO;
procedure BOTTLES is
package INT_IO is new INTEGER_IO (INTEGER);
use INT_IO;
COUNT : INTEGER := 99;
begin
while COUNT > 0 loop
PUT (COUNT,WIDTH=>0); PUT_LINE (" bottles of beer on the wall,");
PUT (COUNT,WIDTH=>0); PUT_LINE (" bottles of beer.");
PUT_LINE ("Take one down and pass it around.");
COUNT := COUNT - 1;
if COUNT = 0 then
PUT_LINE("No bottles of beer on the wall!");
else
PUT (COUNT,WIDTH=>0); PUT_LINE (" bottles of beer on the wall.");
end if;
NEW_LINE;
end loop;
end BOTTLES;
ADL is Adventure Definition Language
{ This version of beer.adl is the normal procedural one which has }
{ no user interaction, and only prints out the song. Quite boring, }
{ really. Ross Cunniff, 1997 cunniff@fc.hp.com }
START =
LOCAL i, s;
($setg i 99)
(WHILE ($gt @i 0) DO
(IF ($gt @i 1) THEN
($say ($str @i) " bottles of beer on the wall.\n")
($say ($str @i) " bottles of beer.\n")
ELSE
($say "1 bottle of beer on the wall.\n")
($say "1 bottle of beer.\n")
)
($say "You take one down, pass it around.\n")
($setg i ($minus @i 1))
(IF ($gt @i 1) THEN
($say ($str @i) " bottles of beer on the wall.\n\n")
ELSEIF ($eq @i 1) THEN
($say "1 bottle of beer on the wall.\n\n")
ELSE
($say "No more bottles of beer on the wall.\n")
)
)
($spec 3)
;
bottles := 99;
OPENWINDOW('##1# bottles of beer on the wall \'+
'##1# bottles of beer on the wall');
UPDATEWINDOW(1,bottles);
REPEAT
OPENWINDOW('Take one down, pass it around');
OPENWINDOW('##1# bottles of beer on the wall \'+
'##1# bottles of beer on the wall');
bottles := bottles -1;
UPDATEWINDOW(1,bottles);
UNTIL bottles = 1;
OPENWINDOW('1 bottle of beer on the wall \'+
'no more bottles of beer on the wall');
CLOSEWINDOW();
-- "99 Bottles of Beer" ALAN (v2.x) version
-- Stephen Griffiths, 1999
-- ALAN is a text adventure authoring system
-- webpage at http://www.welcome.to/alan-if
LOCATION Wall NAME '99' Bottles 'of' Beer
HAS Bottles 99.
END LOCATION.
EVENT Sing
"$p"
SAY Bottles OF Wall.
"bottle"
IF Bottles OF Wall > 1 THEN
"$$s"
END IF.
"of beer on the wall,"
"$n"
SAY Bottles OF Wall.
"bottle"
IF Bottles OF Wall > 1 THEN
"$$s"
END IF.
"of beer."
"$nTake"
IF Bottles OF Wall > 1 THEN
"one"
ELSE
"it"
END IF.
"down, pass it around,"
DECREASE Bottles OF Wall.
IF Bottles OF Wall > 0 THEN
"$n"
SAY Bottles OF Wall.
"bottle"
IF Bottles OF Wall > 1 THEN
"$$s"
END IF.
"of beer on the wall."
SCHEDULE Sing AFTER 0.
ELSE
"$nNo bottles of beer on the wall,"
"$nNo bottles of beer."
QUIT.
END IF.
END EVENT.
START AT Wall.
SCHEDULE Sing AFTER 0.
% Algol (60), Unisys MCP (descendant of Burroughs B6700) variant.
%
% January 21, 2003 by Tom Herbertson
% http://members.cox.net/herbertsont/
%
% Run with ;VALUE = <number> to specify initial quantity NEQ 99
% Run with ;SW1 for American ("happen to fall") version
% Run with ;SW2 to spell out numbers
% Send results to printer by running with ;FILE TERM(PRINTER)
% or to disk with ;FILE TERM(DISK,PROTECTION=SAVE,TITLE=<file name>)
% Enter ?HI to quit early
BEGIN
FILE TERM(KIND=REMOTE,MYUSE=OUT);
EBCDIC ARRAY OUTLINE[0:71];
TRANSLATETABLE LOWERTOUPPER
("abcdefghijklmnopqrstuvwxyz" TO "ABCDEFGHIJKLMNOPQRSTUVWXYZ");
EBCDIC VALUE ARRAY
TENS
(" "," ",
"twenty ","thirty ","forty ","fifty ",
"sixty ","seventy ","eighty ","ninety "),
UNDER_TWENTY
("zero ","one ","two ","three ",
"four ","five ","six ","seven ",
"eight ","nine ","ten ","eleven ",
"twelve ","thirteen ","fourteen ","fifteen ",
"sixteen ","seventeen ","eighteen ","nineteen ");
PROCEDURE BOTTLECOUNT(I,P,SPELLING);
VALUE I, SPELLING;
INTEGER I; POINTER P; BOOLEAN SPELLING;
BEGIN
POINTER FIRST_LETTER;
INTEGER T, U;
IF I EQL 0 THEN
REPLACE P:P BY "No more"
ELSE
BEGIN
IF SPELLING AND I LEQ 99 THEN
BEGIN
T := I DIV 10;
U := I MOD 10;
FIRST_LETTER := P;
IF T GEQ 2 THEN
BEGIN
REPLACE P:P BY TENS [T*12] UNTIL = " "; % each entry is 12 chars
IF U NEQ 0 THEN
REPLACE P:P BY "-";
END
ELSE
IF T = 1 THEN
U:=*+10; % bring back the teens
IF U NEQ 0 THEN
REPLACE P:P BY UNDER_TWENTY [U*12] UNTIL = " "; % like TENS
REPLACE FIRST_LETTER BY FIRST_LETTER FOR 1 WITH LOWERTOUPPER;
END TURNING NUMBER INTO WORDS
ELSE
REPLACE P:P BY I FOR * DIGITS
END;
REPLACE P:P BY " bottles" FOR 7 + REAL(I NEQ 1), " ";
END;
DEFINE FORM = REPLACE OP:OP BY # ;
POINTER OP;
BOOLEAN REMOTE_OUTPUT, EARLYEXIT;
INTERRUPT HI;
BEGIN
EARLYEXIT := TRUE;
END;
PROCEDURE SPOUT;
BEGIN
WRITE(TERM,72,OUTLINE);
REPLACE (OP:=OUTLINE) BY " " FOR 72;
END;
BOOLEAN FALL, SPELL;
REAL TV;
INTEGER BOTTLES;
DEFINE MANTISSAF = [38:39] #, % Determines max single-precision integer
ALL1 = REAL (NOT FALSE) #,
MAXINT = ALL1.MANTISSAF #;
REPLACE (OP:=OUTLINE) BY " " FOR 72;
OPEN(TERM);
REMOTE_OUTPUT := (TERM.KIND EQL VALUE(REMOTE));
FALL := MYSELF.SW1;
SPELL := MYSELF.SW2;
IF (TV := MYSELF.TASKVALUE) GTR MAXINT THEN
BEGIN
FORM "Too many bottles, using ";
IF SPELL THEN
FORM "ninety-nine."
ELSE
FORM "99.";
SPOUT;
SPOUT; % blank line
BOTTLES := 99;
END
ELSE
IF (BOTTLES := TV) EQL 0 THEN
BOTTLES := 99;
IF BOTTLES > 99 AND SPELL THEN
BEGIN
FORM "I know the words only up to ninety-nine.";
SPOUT;
SPOUT; % blank line
END;
ATTACH HI TO MYSELF.EXCEPTIONEVENT;
FOR BOTTLES := BOTTLES STEP -1 UNTIL 1 DO
BEGIN
BOTTLECOUNT(BOTTLES,OP,SPELL);
FORM "of beer on the wall,";
SPOUT;
BOTTLECOUNT(BOTTLES,OP,SPELL);
FORM "of beer,";
SPOUT;
IF FALL THEN
BEGIN
FORM "If ";
IF BOTTLES = 1 THEN
FORM "that bottle "
ELSE
FORM "one of those bottles ";
FORM "should happen to fall,";
END
ELSE
BEGIN
FORM "Take ";
IF BOTTLES = 1 THEN
FORM "it "
ELSE
FORM "one ";
FORM "down and pass it around,";
END;
SPOUT;
BOTTLECOUNT(BOTTLES-1,OP,SPELL);
FORM "of beer on the wall.";
SPOUT;
IF BOTTLES GTR 1 THEN
BEGIN
SPOUT; % interstanza blank separator line
IF EARLYEXIT THEN
BEGIN
FORM "Closing time!";
SPOUT;
BOTTLES := 1; % stop loop
END
ELSE
IF REMOTE_OUTPUT THEN
WHEN (1); % one-second interval to allow terminal to catch up
% (and be responsive to EXCEPTIONEVENT (?HI))
END;
END OF BOTTLES LOOP;
END.
# 99 Bottles of Beer #
# by Otto Stolz <Otto.Stolz@Uni-Konstanz.de> #
( PROC width = (INT x) INT: (x>9 | 2 | 1)
; FOR i FROM 99 BY -1 TO 1
DO printf ( ( $ 2l n(width(i))d
, x "bottle" b("","s") x "of beer on the wall,"
, x n(width(i))d
, x "bottle" b("","s") x "of beer."
, l "Take one down, pass it around,"
, x n(width(i-1))d
, x "bottle" b("","s") x "of beer."
$
, i , i=1
, i , i=1
, i-1, i=2
) )
OD
)
program Bottles(input, output);
{ Alice Pascal version of 99 Bottles of beer (Bottles.ap) }
{ See http://www.templetons.com/brad/alice.html }
{ Philipp Winterberg, http://www.winterbergs.de }
var
b : Byte;
begin
b := 99;
repeat
writeln(b:2, ' bottle(s) of beer on the wall,');
writeln(b:2, ' bottle(s) of beer');
writeln('Take one down, pass it around,');
b := b - 1;
writeln(b:2, ' bottle(s) of beer on the wall.');
writeln('');
until b = 0;
end.
Amanda is a DOS version of Miranda.
/*
I made some changes to the miranda script by Tim Walls.
Changes by Gavin Spearhead (wieger1@noord.bart.nl)
*/
bottlesofbeer :: num -> [char]
bottlesofbeer n = "\nNo more bottles of beer on the wall, \n"
++ "no more bottles of beer.\n" , if n = 0
= "\nOne bottle of beer on the wall, one bottle of beer,\n"
++ "Take one down and pass it around"
++ (bottlesofbeer (n-1)) , if n = 1
= "\n" ++ itoa(n) ++ " bottles of beer on the wall, "
++ itoa(n)
++ " bottles of beer,\nTake one down and pass it around"
++ (bottlesofbeer (n-1)) , otherwise
/* AML (Arc Macro Language) version of 99 bottles of beer on the wall
/* Author prefers anonymity B-)
/*
&do number = 9 &to 1 &by -1
/* handle the one bottle cases
&if %number% = 1 &then
&set noun1 = bottle
&else
&set noun1 = bottles
&if %number% = 2 &then
&set noun2 = bottle
&else
&set noun2 = bottles
&type \%number% %noun1% of beer on the wall,
&type %number% %noun1% of beer,
&type Take one down, pass it around,
&type [calc %number% - 1] %noun2% of beer on the wall
&end
&return
-- AppleScript version of "99 Bottles of Beer"
-- by Kristopher Johnson kdj@mindspring.com
to createBottleString for aNumberOfBottles
if aNumberOfBottles is 0 then
return "No more bottles"
else if aNumberOfBottles is 1 then
return "1 more bottle"
else
return (aNumberOfBottles as string) & " bottles"
end if
end createBottleString
set lyrics to ""
repeat with numberOfBottles from 99 to 1 by -1
set bottleString to (createBottleString for numberOfBottles)
set lyrics to lyrics & bottleString & " of beer on the wall, " & bottleString & " of beer. " & return
set lyrics to lyrics & "Take one down and pass it around, " & return
set lyrics to lyrics & (createBottleString for (numberOfBottles - 1)) & " of beer on the wall. " & return
end repeat
set lyrics to lyrics & "No more bottles of beer on the wall, no more bottles of beer." & return
set lyrics to lyrics & "Go to the store and buy some more." & return
set lyrics to lyrics & "99 bottles of beer on the wall."
return lyrics
0 REM ************************
1 REM ** 99 BOTTLES OF BEER **
2 REM ** APPLESOFT VERSION **
3 REM ** BY LEE FASTENAU **
4 REM ************************
10 TEXT : HOME
20 FOR Z = 99 TO 1 STEP - 1
30 A = Z: GOSUB 1000
40 PRINT " ON THE WALL."
50 GOSUB 1000
60 PRINT "."
70 GOSUB 2000
80 A = Z - 1: GOSUB 1000
90 PRINT " ON THE WALL."
100 NEXT
110 END
1000 IF A < 1 THEN A$ = "NO MORE": GOTO 1020
1010 A$ = STR$ (A)
1020 A$ = A$ + " BOTTLE"
1030 IF A < > 1 THEN A$ = A$ + "S"
1040 A$ = A$ + " OF BEER"
1050 PRINT A$;
1060 RETURN
2000 A$ = "TAKE"
2010 IF A > 1 THEN A$ = A$ + " ONE": GOTO 2030
2020 A$ = A$ + " IT"
2030 A$ = A$ + " DOWN, PASS IT AROUND."
2040 PRINT A$
2050 RETURN
/************************************************/
/* AS-Version of 99 bottles of beer on the wall */
/* by Juergen Buechner http://www.jbuechner.de/ */
/* created 2002-09-10 06:17 in the morning */
/************************************************/
RTN BEER(§in,§out)
§out = CONCAT(CHAR(§in,'<&&&'),' bottle')
IF §in > 1
§out =CC(§out,'s')
IF END
§out = CC(§out,' of beer')
RTN END
/*
IN didummy
OUT *
WHEN §START
DEF Ünrz(N03)
DEF Ütebeer(A80)
DO Ünrz=100:1<-1>
CALL BEER(Ünrz,Ütebeer)
PRINT CC(Ütebeer,' on the wall,')
PRINT CC(Ütebeer,'.')
PRINT 'Take one down and pass it around,'
CALL BEER(Ünrz-1,Ütebeer)
PRINT CC(Ütebeer,' on the wall.')
NEXT
RUN
' ASHE version of 99 Bottles of beer (Bottles.txt)
' See http://www.grandriversoftware.com/products/ashe/index.shtml
' Philipp Winterberg, http://www.winterbergs.de
Number b = 99
While b > 0
Print b; " bottle(s) of beer on the wall,"
Print b; " bottle(s) of beer."
Print "Take one down, pass it around, "
b--
Print b; " bottle(s) of beer on the wall."
Print
Wend
rem ASIC version of 99 Bottles of beer (Bottles.asi)
rem See http://www.programmersheaven.com/search/Download.asp?FileID=15872
rem Philipp Winterberg, http://www.winterbergs.de
cls
b = 99
bottles:
print b;
print " bottle(s) of beer on the wall,"
print b;
print " bottle(s) of beer."
print "Take one down, pass it around,"
b = b - 1
print b;
print " bottle(s) of beer on the wall."
print
if B>0 then bottles:
end
Microsoft's Active Server Pages language (called VBScript), meant to be embedded in HTML documents.
<HTML>
<HEAD>
<TITLE>99 Bottles of Beer</TITLE>
</HEAD>
<BODY>
<!-- Microsoft ASP (Active Server Pages) listing by Vince Curley
(vincec@microsoft.com) -->
<%
n = 99
do
str = n & " bottle"
if n <> 1 then str = str & "s"
str = str & " of beer"
Response.Write str & " on the wall...<BR>"
Response.Write str & "!<BR>"
Response.Write "Take one down, pass it around...<BR>"
n = n - 1
if n > 0 then
str = n
else
str = "No "
end if
str = str & " bottle"
if n <> 1 then str = str & "s"
str = str & " of beer on the wall!<BR>"
Response.Write str
Response.Write "<BR>"
loop while n > 0
Response.Write "<FONT SIZE=7><STRONG>Buy more
beer!</STRONG></FONT>"
%>
</BODY>
</HTML>
;/ bottles on the wall in 8051 assembler
;/
;/ bill webster 2003
;/____________________________________________________________________________
; sfr definitions
SCON data 0x98
SBUF data 0x99
PCON data 0x87
TMOD data 0x89
TH1 data 0x8D
B data 0xF0
; bit definitions
TI bit 0x99
TR1 bit 0x8E
;/ start vector
;/____________________________________________________________________________
cseg at 0
jmp start
cseg at 0x30
;/ print number in r0 as decimal - limited to numbers in [0..99]
;/____________________________________________________________________________
putn:
mov a, r0
mov b, #10
div ab
jz units
call printDigit
units:
mov a, b
; fall through
;/ convert number in [0..9] to ascii digit & print
;/____________________________________________________________________________
printDigit:
add a, #'0'
; fall through
;/ character out
;/____________________________________________________________________________
putch:
jnb TI, putch
clr TI
mov SBUF, a
ret
;/ print string at dptr
;/____________________________________________________________________________
puts:
clr a
movc a, @a + dptr
jnz more
ret
more:
call putch
inc dptr
jmp puts
;/
;/____________________________________________________________________________
start:
; initialize serial port
orl TMOD, #0x20
setb TR1
mov SCON, #0x50
mov TH1, #0xFE
orl PCON, #0x80
setb TI
; bottles to begin with
mov r0, #99
verse:
call putn
mov dptr, #line1
call puts
call putn
mov dptr, #line2
call puts
dec r0
call putn
mov dptr, #line1
call puts
mov dptr, #eoln
call puts
cjne r0, #0, verse
jmp $
;/ string constants
;/____________________________________________________________________________
cr equ 0x0D
lf equ 0x0A
line1: db ' bottles of beer on the wall,'
eoln: db cr, lf, 0
line2: db ' bottles of beer,', cr, lf
db 'Take one down, pass it around,', cr, lf, 0
end
; 99 Bottles of Beer program in Intel 8086 assembly language.
; Assemble to a .COM file for MS-DOS.
;
; Author: Alan deLespinasse
; aldel@alum.mit.edu
; www.aldel.com
code segment
assume cs:code,ds:code
org 100h
start:
; Main loop
mov cx, 99 ; bottles to start with
loopstart:
call printcx ; print the number
mov dx,offset line1 ; print the rest of the first line
mov ah,9 ; MS-DOS print string routine
int 21h
call printcx ; print the number
mov dx,offset line2_3 ; rest of the 2nd and 3rd lines
mov ah,9
int 21h
dec cx ; take one down
call printcx ; print the number
mov dx,offset line4 ; print the rest of the fourth line
mov ah,9
int 21h
cmp cx, 0 ; Out of beer?
jne loopstart ; if not, continue
int 20h ; quit to MS-DOS
; subroutine to print CX register in decimal
printcx:
mov di, offset numbufferend ; fill the buffer in from the end
mov ax, cx ; put the number in AX so we can divide it
printcxloop:
mov dx, 0 ; high-order word of numerator - always 0
mov bx, 10
div bx ; divide DX:AX by 10. AX=quotient, DX=remainder
add dl,'0' ; convert remainder to an ASCII character
mov [ds:di],dl ; put it in the print buffer
cmp ax,0 ; Any more digits to compute?
je printcxend ; if not, end
dec di ; put the next digit before the current one
jmp printcxloop ; loop
printcxend:
mov dx,di ; print, starting at the last digit computed
mov ah,9
int 21h
ret
; Data
line1 db ' bottles of beer on the wall,',13,10,'$'
line2_3 db ' bottles of beer,',13,10,'Take one down, pass it around,',13,10,'$'
line4 db ' bottles of beer on the wall.',13,10,13,10,'$'
numbuffer db 0,0,0,0,0
numbufferend db 0,'$'
code ends
end start
BEER TITLE '99 BOTTLES OF BEER ON THE WALL'
*+--------------------------------------------------------------------+
*¦ ¦
*¦MODULE NAME :BEER ¦
*¦ ¦
*¦FUNCTION :DISPLAY 99 BOTTLES OF BEER ON THE WALL ON THE ¦
*¦ :SYSTEM CONSOLE. ¦
*¦ ¦
*¦ENVIRONMENT :Z900 SYSTEM (S/390) RUNNING ZOS. ¦
*¦ ¦
*+--------------------------------------------------------------------+
*--------------------------------------------------------------*
* PROGRAM ENTRY POINT. *
*--------------------------------------------------------------*
BEER CSECT
* *-----------------------------------------------------*
* * SAVE CALLER'S ENVIRONMENT. *
* *-----------------------------------------------------*
STM R14,R12,12(R13) SAVE CALLER'S REGS.
* *-----------------------------------------------------*
* * BUILD OUR EXECUTION ENVIRONMENT. *
* *-----------------------------------------------------*
LA R12,0(,R15) COPY OVER BASE REGISTER.
USING BEER,R12 ASSIGN BASE.
LA R3,RSA POINT TO OUR RSA.
ST R3,8(,R13) SAVE IN CALLER'S RSA.
ST R13,4(,R3) CHAIN CALLER'S TO OURS.
LR R13,R3 SET UP OUR RSA.
*--------------------------------------------------------------*
* NUMBER OF BEERS LOOP. *
*--------------------------------------------------------------*
LA R4,99 NUMBER OF BEERS.
BEERLOOP DS 0H
* *-----------------------------------------------------*
* * CREATE A PRINTABLE NUMBER FROM INTEGER. *
* *-----------------------------------------------------*
CVD R4,DWORD CONVERT FIXED TO DECIMAL.
MVI WORK,C' ' PLACE SEED.
MVC WORK+1(L'WORK-1),WORK PROPIGATE SEED.
MVC WORK(8),=X'4020202020202120'
LA R1,WORK+5 DEFAULT TO LAST BYTE.
EDMK WORK(8),DWORD+4 UNPACK NUMBER.
* *-----------------------------------------------------*
* * MODIFY MESSAGES WITH BEER NUMBER. *
* *-----------------------------------------------------*
MVC MSG1+4(2),0(R1) COPY OVER NUMBER OF BEERS.
MVC MSG2+4(2),0(R1) COPY OVER NUMBER OF BEERS.
MVC MSG4+4(2),0(R1) COPY OVER NUMBER OF BEERS.
* *-----------------------------------------------------*
* * ISSUE MESSAGE TO CONSOLE PRAISING THE NUMBER OF *
* * BEERS. *
* *-----------------------------------------------------*
WTO MF=(E,MSG1) ISSUE MESSAGE.
WTO MF=(E,MSG2) ISSUE MESSAGE.
WTO MF=(E,MSG3) ISSUE MESSAGE.
WTO MF=(E,MSG4) ISSUE MESSAGE.
* *-----------------------------------------------------*
* * DECRIMENT BEER COUNT AND LOOP UNTIL DONE. *
* *-----------------------------------------------------*
BCT R4,BEERLOOP LOOP AROUND.
*--------------------------------------------------------------*
* EXIT PROGRAM SUCCESSFULLY. *
*--------------------------------------------------------------*
EXIT DS 0H
L R13,4(,R13) POINT TO CALLER'S RSA.
LM R14,R12,12(R13) RESTORE CALLER'S REGISTERS.
XR R15,R15 ZERO RETURN CODE.
BR R14 RETURN TO CALLER.
*--------------------------------------------------------------*
* CONSTANTS AND LITERAL POOL. *
*--------------------------------------------------------------*
RSA DC 18A(0) REGISTER SAVE AREA.
DWORD DC D'0' DOUBLE WORD.
WORK DC XL256'00' WORK AREA.
MSG1 WTO 'XX BOTTLES(S) OF BEER ON THE WALL,',MF=L
MSG2 WTO 'XX BOTTLES(S) OF BEER.',MF=L
MSG3 WTO 'TAKE ONE DOWN, PASS IT AROUND,',MF=L
MSG4 WTO 'XX BOTTLE(S) OF BEER ON THE WALL.',MF=L
R0 EQU 0
R1 EQU 1
R2 EQU 2
R3 EQU 3
R4 EQU 4
R5 EQU 5
R6 EQU 6
R7 EQU 7
R8 EQU 8
R9 EQU 9
R10 EQU 10
R11 EQU 11
R12 EQU 12
R13 EQU 13
R14 EQU 14
R15 EQU 15
END ,
* 99 bottles of beer
* Assembler program for IBM System/370 (and up)
* (c) R. Heemskerk, systeemprogrammeur@zonnet.nl
* The program expects a sequential output dataset allocated to ddname OUTDD, FB80
BOTTLE99 CSECT
SAVE (14,12),,BOTTLE99
LR 12,15
USING BOTTLE99,12
LR 11,13
CNOP 0,4
BAL 13,START
DC 20A(0)
START ST 13,8(11)
ST 11,4(13)
OPEN (OUTFILE,(OUTPUT))
MVI EXTRA1,C's'
MVI EXTRA2,C's'
LA 4,99
LOOP CVD 4,DEC
MVC CNVNUM,MASK
ED CNVNUM,DECNUM
MVC OUTNUM1,CNVNUM+2
MVC OUTNUM2,CNVNUM+2
CL 4,=F'1'
BNE PUT
MVI EXTRA1,C' '
MVI EXTRA2,C' '
PUT PUT OUTFILE,OUTLINE1
PUT OUTFILE,OUTLINE2
BCT 4,LOOP
PUT OUTFILE,OUTLINE3
PUT OUTFILE,OUTLINE4
DONE CLOSE OUTFILE
EXIT L 13,4(13)
RETURN (14,12),RC=0
CNVNUM DS XL4
MASK DC X'40202120'
DEC DS 0D
DS XL6
DECNUM DS XL2
OUTLINE1 DC CL80' '
ORG OUTLINE1
OUTNUM1 DS CL2
DC C' bottle'
EXTRA1 DC C' '
DC C' of beer on the wall, '
OUTNUM2 DS CL2
DC C' bottle'
EXTRA2 DC C' '
DC C' of beer.'
ORG OUTLINE1+80
OUTLINE2 DC CL80'Take one down, pass it around.'
OUTLINE3 DC CL80'No more bottles of beer on the wall, no more bottleX
s of beer.'
OUTLINE4 DC CL80'Go to the store and buy some more.'
OUTFILE DCB DSORG=PS,DDNAME=OUTDD,MACRF=(PM)
LTORG
END
; 99 Bottles of Beer on the Wall in UDVM assembly.
;
; See the developing IETF SigComp specification under development
; in the ROHC working group for a language reference.
;
; By Adam Roach <adam at who.net>
at (64)
:registers pad(8)
:num_bottles pad(2)
:digit pad(1)
:digit_lsb pad(1)
:tens_ascii pad(1)
:ones_ascii pad(1)
:bottles_of_beer pad(16)
:on_the_wall pad(12)
:lf pad(1)
:take_one_down pad(30)
; Padding to make the strings come out an even length
pad(1)
; Executable code must start on a 64-byte boundary
align (64)
:start
; Initialize variables.
MULTILOAD (num_bottles, #, 99, 0, 14906,
8290,28532,29804,25971,8303,26144,25189,25970,8303,28192,29800,25888,
30561,27756,2676,24939,25888,28526,25888,25711,30574,11296,28769,29555,
8297,29728,24946,28533,28260,2560)
:loop
OUTPUT (tens_ascii, 31) ; "xx bottles of beer on the wall\n"
OUTPUT (tens_ascii, 18) ; "xx bottles of beer"
OUTPUT (lf, 31) ; "\ntake one down, pass it around\n"
SUBTRACT ($num_bottles, 1)
; Compute the ASCII digit for the tens position
LOAD (digit, $num_bottles)
DIVIDE ($digit, 10)
ADD ($digit, 48)
COPY (digit_lsb, 1, tens_ascii)
; Compute the ASCII digit for the digits position
LOAD (digit, $num_bottles)
REMAINDER ($digit, 10)
ADD ($digit, 48)
COPY (digit_lsb, 1, ones_ascii)
OUTPUT (tens_ascii, 31) ; "xx bottles of beer on the wall\n"
COMPARE ($num_bottles, 0, finish, finish, loop)
:finish
; Signal that we're complete, and store this code as state so
; that it can be referenced by a state identifier in the future.
set (code_length, end - start)
END-MESSAGE (0, 0, code_length, start, start, 6, 1)
:end
// 99 bottles written in AML (Aurora Macro Language) for the fantastic Aurora
// text editor. Although the latest version of the editor is still available
// for free download (Aurora Editor/32 v3.3 Beta 1) development is now defunct,
// and the author uncontactable.
//
// If you have experienced the beauty and power of this editor and want to
// support an open-source initiative, visit the biggest fan-site:
// http://www-personal.umich.edu/~knassen/aurora.html
//
// Author: Danny Lawler.
include bootpath "define.aml"
createbuf // Target buffer for text ops
for i = 99 downto 0 do
plural = if? i == 1 "" "s"
buff = if? i == 0 "No" i
addline buff + ' bottle' + plural + ' of beer on the wall,'
addline buff + ' bottle' + plural + ' of beer,'
plural = if? i-1 == 1 "" "s"
if not i then
addline 'First we weep, then we sleep.'
else
addline 'Take one down, pass it around,'
end
buff = if? (i-1 <= 0) "No" i-1
addline buff + ' bottle' + plural + ' of beer on the wall.'
addline
end
buff = ' * 99 Bottles of Beer * '
// Display output in popup menu
popup (getcurrbuf) buff length buff
destroybuf
'**************************************
'* Title: 99 Bottles of Beer *
'* Author: Steven Bugo *
'* Language: Avenue (ArcView GIS 3.x) *
'**************************************
msg = ""
bottles1 = "bottles"
bottles2 = "bottles"
noneleft = "No more bottles of beer on the wall!"
for each i in 99..1 by -1
if (i = 1) then
bottles1 = "bottle"
end
if (i = 2) then
bottles2 = "bottle"
end
msg = msg + i.AsString ++ bottles1 ++ "of beer on the wall," + NL
msg = msg + i.AsString ++ bottles1 ++ "of beer," + NL + "Take one down, pass it around," + NL
if (i = 1) then
msg = msg + noneleft
else
msg = msg + (i - 1).AsString ++ bottles2 + " of beer on the wall" + NL
+ NL
end
end
MsgBox.Report(msg, "99 Bottles of Beer")
#!/usr/bin/awk -f
# awk version of 99 bottles of beer
# by Whitey (whitey@netcom.com) - 06/05/95
BEGIN {
for(i = 99; i > 0; i--) {
print s = bottle(i), "on the wall,", s ","
print "take one down, pass it around,"
print bottle(i - 1), "on the wall."
}
}
function bottle(n) {
return sprintf("%s bottle%s of beer", n ? n : "no more", n - 1 ? "s" : "")
}
+--------------------------------------------------------+
| This is program "99 botels of beer on the wall" on AWL |
| of Simantic Siemens STEP7 (with simply output) |
| by Marzhuhin Alexandr aka Sly AlMRu@Beep.ru |
| more info about STEP7 www.ad.siemens.com |
+--------------------------------------------------------+
declare variebles:
---------------------
db2.dbw "Botels_of_Beer" dec 99
---------------------
address decl name type comments
0.0 in take_botel_of_beer bool Signal for take on botel
2.0 in Timer_Function timer timer function used for take-off delay
4.0 out Process_Message char Message XXX Botels of beer on the wall
6.0 out End_Message char No more beer :-(
in_out
temp
--------------------
AUTHOR Sly
FAMILY The Program 99 Botels of beer
NAME : 99 Botels of beer
VERSION : 1.0
FUNCTION_BLOCK FB20
VAR_INPUT
Botels_of_beer: INT;
END_VAR
BEGIN
CONTROL:=FALSE;
INDEX := 99;
Process_Message := "Botels of beer on the wall";
End_message := "No more beer :-(";
Botels_of_beer := 99;
FOR INDEX:= 1 TO ENDVALUE DO
Botels_of_beer := Botels_of_beer - 1;
IF Botels_of_beer >0000 THEN
CONTROL = TRUE
OUT := Botels_of_beer;
OUT := Process_Message;
END_IF
END_FOR;
OUT := End_Message;