GENWiki

Premier IT Outsourcing and Support Services within the UK

User Tools

Site Tools


archive:holiday:merry.jok

Table of Contents

Article 254 of comp.sources.misc: Path: puukko!santra!tut!enea!mcvax!uunet!husc6!ukma!tut.cis.ohio-state.edu!mandrill!hal!ncoast!allbery From: rsk@mace.cc.purdue.edu (Rich Kulawiec) Newsgroups: comp.sources.misc Subject: v03i076: Just for fun (something which once appeared on the net) Message-ID: 8807101545.AA21634@mace.cc.purdue.edu Date: 10 Jul 88 15:45:48 GMT Sender: allbery@ncoast.UUCP Reply-To: rsk@mace.cc.purdue.edu (Rich Kulawiec) Lines: 2008 Approved: allbery@ncoast.UUCP

Posting-number: Volume 3, Issue 76 Submitted-by: "Rich Kulawiec" rsk@mace.cc.purdue.edu Archive-name: xmases

[Only half a year late… ;-) ++bsa]

I found this while doing some housecleaning in my account, and thought it was marginally interesting enough to send along to you.

—Rsk

From: ded@aplvax.UUCP Newsgroups: net.misc Subject: Merry Christmas Programs Organization: JHU/Applied Physics Lab, Laurel, MD

Well, here it is: the long awaited list of "Merry Christmas" programs. If you are a crawled-out-from-under-a-rock sort of person and don't know what's going on here, then you should read the following sentence: I don't know what's going on here either. For some reason, I wanted to collect a group of programs which print the phrase "Merry Christmas" 15 times. If you can figure out why I wanted to do this, please let me know.

Thanks alot to all the nice folks who inundated me with mail. Some of the submissions made extremely clever use of editors and utility languages (I'm particularly fond of the UNIX shell script by Ben Hyde). A few errors probably crept in due to transmission errors and my editing, and for that I apologize (because you're probably gonna be swamped by a horde of prepubescent fault finders).

Several of you requested that I (1) send you personal copies of the results, (2) send you only the more interesting examples, or (3) send you a report contrasting and comparing the various syntaxes. I lost all your names.

If you sent me a submission and it wasn't included, then it either duplicated a previous entry or never arrived. I deleted many comments to save space. In retrospect, that was probably a mistake.

  1. -Don Davis

/* 6502 assembly */

START LDX #$0F LOOP1 LDY #$10 LOOP2 LDA MCDATA,Y

JSR $FDF0	(CHAROUT or something like that)
DEY
BPL LOOP2
DEX
BPL LOOP1
RTS

MCDATA ASC "

		~ Kenn Frankel
		...!sdcsvax!sdccs6!ix192

/* Ada version */

with text_io; use text_io;
program print_merry_christmas is
begin
	for i in 1..15 loop
		put("Merry Christmas"); new_line;
	end loop;
end print_merry_Christmas;

I tested the program using the SuperSoft/Maranatha Ada compiler.

  1. - Dave Norris

/* Ada */

/* This program is merely an ordinary loop. It was developed by */ /* Rob Pearce of JHU/APL. Oh yes; Rob is English. */

  1   with text_io; use text_io;
  2
  3   procedure number_a is
  4
  5     i_max:constant integer:=15;
  6     type i_type is range 1..i_max;
  7
  8     package i_type_io is new integer_io(num=>i_type);
  9
 10   begin  -- number_a
 11     for i in i_type loop
 12       i_type_io.put(item=>i,
 13                     width=>2);
 14       put("  " &
 15           "God save the Queen");
 16       new_line;
 17     end loop;
 18   end number_a;

/* Ada */

– This program counts to 15, but does so via three "concurrently – executing" tasks. The output has been modified to be a single – character instead of the full "Merry Christmas" message. The – first task prints, sequentially, 0..4. The second prints, in – turn, 5..9; and the third sequentially prints A..E. – – If we had used the full "Merry Christmas" line, then the three – concurrent tasks would have (almost certainly) interleaved their – respective character strings, and one would have not been able to – read any of the messages! – – The program was developed by Rob Pearce of JHU/APL, and was run – on a validated Ada system, the NY University, Ada/ED. The machine – was a VAX-11/750 under typical loading. (Note the times; they're – about the same on an empty machine, too!) The listing has been – edited to remove the "uninteresting" lines and the #$^& control – characters. – Mars Gralia – 11/11/8

NYU ANSI-Ada/ED 1.1(11-Apr-83) FRI 11 NOV 83 09:27:31 PAGE 1

  1   with text_io; use text_io;
  2
  3   procedure number_f is
  4
  5     task A;
  6     task B;
  7     task C;
  8
  9
 10     task body A is
 11
 12     begin  -- A
 13       for ch in character range '0'..'4' loop
 14         put(ch);
 15       end loop;
 16     end A;
 17
 18
 19     task body B is
 20
 21     begin  -- B
 22       for ch in character range '5'..'9' loop
 23         put(ch);
 24       end loop;
 25     end B;
 26
 27
 28     task body C is
 29
 30     begin  -- C
 31       for ch in character range 'A'..'E' loop
 32         put(ch);
 33       end loop;
 34     end C;
 35
 36
 37   begin  -- number_f
 38     null;
 39   end number_f;
No translation errors detected
Translation time: 69 seconds

NYU ANSI-Ada/ED 1.1(11-Apr-83) FRI 11 NOV 83 10:34:05 PAGE 1

Binding time: 3.3 seconds
Begin Ada execution

5A06B127C38D94E

Execution complete
Execution time: 51 seconds
I-code statements executed: 97

/* Algol-60 */

begin comment Algol-60 version. "Print" is system defined; integer i;

for i := 1 step 1 until 15 do Print("Merry Christmas")

end

        		--  chip elliott     ...decvax!dartvax!chip

/* Algol-68 */

BEGIN
TO 15
	DO
	print(("Merry Christmas",newline))
	OD
END
  -- Andrew Klossner   (decvax!tektronix!tekecs!andrew)  [UUCP]
		       (andrew.tektronix@rand-relay)     [ARPA]

/* APL */ \/ PROG ; S _ __ [1] ! ! ← (15, pS) p S ← 'Merry Christmas' \/

Here's an APL version. Since APL uses more than the ASCII character set, I had to fake it some. The triangle is the greek character 'del' (an upside-down delta), the first symbol on line [1] is a 'quad', a rectangular block, the '←' is a left arrow, and the lower-case 'p' is the greek character 'rho'. Have fun.

				^-^ Bruce ^-^

/* APL */

15 15 rho 'Merry Christmas'

(rho is the greek letter of that name, the reshape operator in APL)

That may not count, since it's more like an expression than a program, but it will do what you asked for. I guess you could make it a program if you wanted, as follows:

del merry
[1] 15 15 rho 'Merry Christmas'
del

(del is a little upside-down triangle)

				Joe Ziegler
				...ihnp4!pegasus!lzmi!ziegler

/* APL */

  Here is an APL Merry Christmas. Since APL uses a different chracter set,

I will use the following identifiers for non-ascii chracters:

  RHO - greek letter rho
  BOX - the rectangle or window character
  ASGN - the back-arrow assignment character
  TRI - upside-down triangle

TRI merry ; mesg BOX ASGN (15,RHO mesg)RHO mesg ASGN "Merry Christmas" TRI

  1. –From some unknown person on the other side of uucp

/* AWK */

awk 'BEGIN {for (i=1;i<=15;i++) print "Merry Xmas"}' /dev/null
		From: seismo!mcvax!steven (Steven Pemberton)

/* AWK */ (note that it wants some standard input):

BEGIN { for (i = 0; i < 15; i++) {

printf "Merry Christmas\n"
}   

}

		From: David Chase <rbbb@rice>
              

/* B */ (not the predecessor of "C", by the way).

  HOW'TO MERRY'CHRISTMAS:
FOR i IN {1..15}:
    WRITE 'Merry Christmas' /

The string quote in B is used like the underscore in "C". HOW'TO introduces a procedure declaration. Indentation is used for grouping statements. The slash is used in WRITE-commands to indicate a newline. Actually, this definition should be followed by a call:

  MERRY'CHRISTMAS

You could also write the body of the procedure instead of the call, and then would have no need for the definition ("B" has no clear notion of what a program is; usually it's a group of procedures and functions living together in a workspace).

– Guido van Rossum, "B Group", Centre for Mathematics and Computer Science, (CWI, formerly MC), Amsterdam {philabs,decvax}!mcvax!guido

/* Applesoft BASIC */

10 FOR I = 1 TO 10 : PRINT "MERRY CHRISTMAS" : NEXT I

  1. –From some unknown person on the other side of uucp

/* Basic-Plus (DEC Basic on RSTS/E) */

	10	! Merry Christmas program &
		! Written by David Kaufman for Usenet survey

	20 For I = 1 to 15 \ &
		Print "Merry Christmas" \ &
		Next I

	30 End 	! Optional, but helps reloading command

	Merry Christmas!
		David Kaufman
		...decvax!yale-comix!kaufman

/* BASIC */

1000 i=0 1010 if i=15 then goto 1050 1020 print 'Merry Christmas' 1030 i = i+1 1040 goto 1010 1050 end

					That's All
					Dave Wargo
					UCSD

/* bc */

bc«! for(i=19^83;i⇐19^83+14;i++) "Merry Christmas " !

  1. -unknown hacker

/* BCPL */

      // Cambridge IBM implementation
      get "libhdr"
      let start(parm) be $(
          selectoutput(findoutput("sysprint"))
          for i := 1 to 15 do writef("Merry Christmas*N")
      $)  
				These languages courtesy of:
				    Pavel Curtis, Cornell
				    Mike Caplinger, Rice

/* BCPL */

GET "libhdr"

LET start() BE

FOR index = 1 TO 15 DO writes("Merry Christmas*n")
		From: jd@ukc.UUCP
		Organization: Computing Lab. Kent University, England

/* Bliss-11 */

module Christmas = begin \Main\

external MsgScan; local i;

incr i from 1 to 15 do

MsgScan( uplit asciz "Merry Christmas%C" );

end \Main\ eludom

			From: leiby

/* C */

main() {

int i;
for (i=0; i<15; i++)
	printf("Merry Christmas\n");

}

					by Don Davis

/* CDC 6000-type assembly */

      IDENT   MERRY
      ENTRY   MERRY
      SYSCOM  B1

OUTPUT FILEB OBUF,101B,FET=8 OBUF BSS 101B

COUNT DATA 14

MERRY SB1 1

MERRY1 WRITEC OUTPUT,(=C*MERRY CHRISTMAS*)

      SA1     COUNT
      SX6     X1-1
      SA6     COUNT
      NZ      X1,MERRY1
      WRITER  OUTPUT,R
      ENDRUN
      END     MERRY

Jeff Lee CSNet: Jeff @ GATech ARPA: Jeff.GATech @ CSNet-Relay uucp: …!{sb1,allegra,ut-ngp}!gatech!jeff …!duke!mcnc!msdc!gatech!jeff

/* CGOL */ ( an extensible language that translates into MACLISP)

for i in 1 to 15 do print "Merry Christmas"<ESC>

The value of this expression is nil, if you really want a list of them,

for i in 1 to 15 collect "Merry Christmas"<ESC>
			Garret Swart

/* CLI */ To print Merry Christmas 15 times under Data General's CLI's (command line interpreters):

RDOS, RTOS, DOS:	MESSAGE Merry Christmas(,,,,,,,,,,,,,,,)
AOS, AOS/VS:		write Merry Christmas(,,,,,,,,,,,,,,,)

(for your information, the parenthesis indicate that the command will be executed multiple times, with possible subsitutions, so "write a(b,c) d" would write two lines: "abd" and "acd". Since nothing is substituted, the same command is executed 15 times. BTW, write can be abreviated to "wr", "wri", …)

			Michael Meissner
			Data General Corporation
			...{allegra, decvax!ittvax, rocky2}!datagen!mrm

/* CLU */

start_up = proc ()

  po: stream := stream$primary_output ()
  for i: int in int$from_to (1, 15) do
      stream$putl (po, "Merry Christmas")
end
  end start_up
			Happy Hacking!
			Russell Finn
			{decvax, eagle, mit-eddie}!mit-vax!russ
			RUSS%MIT-VAX@MIT-ML

/* CLU */ (Liskov, August 1977 CACM)

start_up = proc ()

 for i: int in int$from_to(1, 15) do
    stream$putl(stream$primary_output(), "Merry Christmas")
 end

end start_up

		Original-From:     J. Dean Brock <brock@unc>

/* COBOL */

     IDENTIFICATION DIVISION. 
     PROGRAM-ID. XMASPRINT.
     ENVIRONMENT DIVISION.
     CONFIGURATION SECTION.
     SOURCE-COMPUTER. UNIVAC-1110.
     OBJECT-COMPUTER. UNIVAC-1110.
     DATA DIVISION.
     PROCEDURE DIVISION.  
     0000-MAIN.
         PERFORM 10-PRINT 15 TIMES.
         STOP RUN.
     10-PRINT.  DISPLAY 'Merry Christmas' UPON PRINTER.
	From: seismo!decvax!sdcsvax!ittvax!dcdwest!noscvax!kemp

/* Cprolog */

/* Write Merry Christmas 15 times in 4.1bsd Cprolog * To execute, get into prolog, then issue the commands: * |?- ['xmas.p']. * |?- xmas. */

xmas :- name(Text,"Merry Christmas") , writeline(Text,15). writeline(_,0). writeline(Text,N) :- write(Text) , nl , M is N - 1 , writeline(Text,M).

	From: seismo!decvax!microsof!ubc-vision!mprvaxa!tbray
              

/* dBASEII */

store 0 to number
do while number < 15
	? "Merry Christmas"
	store 1+number to number
enddo
release number
			From: seismo!philabs!sbcs!BNL!jeffy
				--Jeff M.

/* dBASE II */

SET TALK OFF STORE 0 TO counter DO WHILE counter < 15

  @ counter, 0 SAY "Merry Christmas"
  STORE counter + 1 TO counter

ENDDO RETURN

			From: mike@uokvax.UUCP

/* 'csh' command version */

repeat 15 echo Merry Christmas

		Original-From:     Bruce Israel <israel@umcp-cs>

/* DCL (VAX/VMS shell) */

              
      $ i = 1
      $ loop:
      $ if i.gt.15 then goto done
      $ write sys$output "Merry Christmas"
      $ i = i + 1
      $ goto loop
      $ done:
      $ exit
              
      From: David Chase <rbbb@rice>

/* DCL */ And (as I noticed that Un*x shell scripts were on your list, and in the interest of equal time) here it is in DCL (Digital Command Language, a CLI which runs on many DEC machines – I cut my teeth on VAX/VMS):

$ i = 1 $ loop: $ write sys$output "Merry Christmas" $ i = i + 1 $ if i .le. 15 then goto loop $ exit

			Happy Hacking!
			Russell Finn
			{decvax, eagle, mit-eddie}!mit-vax!russ
			RUSS%MIT-VAX@MIT-ML

/* DDL */

Here is a Merry Christmas program written in DDL. Yes DDL, the Dungeon Definition Language from UCLA. I have included a makefile in case you have never seen this stuff before.

* xmas.ddl * VAR count; (count) = 1; Greetings = ( WHILE ( $lt @count 15 ) : ( $setg count ( $plus 1 @count )) ( $say "Merry Christmas\n") ) ($spec 3 0 0 0 0); START = ($sdem Greetings); * makefile *

xmas:

/usr/src/games/ddl/ddlcomp tiny < tiny.ddl > ddlcomp.out

To run it type the following

`/usr/games/lib/ddlrun xmas'
  1. Joel

/* ed */

ed - /etc/passwd<<!
1,15g/./s/.*/Merry Christmas/p
q
!
	From: seismo!mcvax!steven (Steven Pemberton)

/* ed */ (UNIX 'standard' line editor):

      a   
      Merry Christmas
      .   
      t.  
      t.  
      t.  
      t.  
      t.  
      t.  
      t.  
      t.  
      t.  
      t.  
      t.  
      t.  
      t.  
      t.  
      t.  
      1,$p
				These languages courtesy of:
				    Pavel Curtis, Cornell
				    Mike Caplinger, Rice

/* Concurrent-Euclid */


var xmas :

  module
  include '%IO'
  initially
imports (var IO)
begin
    var i : ShortInt := 0
    loop
	IO.PutString ('Merry Christmas$N$E')
	i := i + 1
	exit when i = 15
    end loop
end

end module {xmas}


Stephen Perelgut Computer Systems Research Group University of Toronto

    Usenet:	{linus, ihnp4, allegra, decvax, floyd}!utcsrgv!perelgut

/* Concurrent Euclid */

var MerryChristmas :

  module
  include '%IO'
  initially
imports (var IO)
begin
    var i: SignedInt := 15
    loop
	IO.PutString('Merry Christmas$N$E')
	i := i - 1
	exit when i = 0
    end loop
end

end module

			From utcsrgv!utai!rayan 

/* EYE */

Since you said "the more obscure the better", here is the program written in EYE, a language which was implemented by Kuck & Associates, Inc. of Champaign, Illinois as an implementation language for writing a large piece of software.

program yule_tidings is

constant number_of_times_to_print_merry_christmas : integer = 15;

begin( yule_tidings )

for i:integer = 1 to number_of_times_to_print_merry_christmas
loop( print_merry_christmas )
	put( 'Merry Christmas' | );
	endloop( print_merry_christmas );
end( yule_tidings );
				Jim Davies
				{pur-ee parsec}!uiucdcs!uiuccsb!davies

/* FRED */ (a text editor)

u15 jm Merry Christmas

			From: decvax!watmath!ljdickey

/* Forth */

(Forth) 15 0 DO ."Merry Christmas" CR LOOP

				Adam Reed
				AT&T Information Systems
				ihnp4!hogpc!pegasus!lzmi!adam

/* Forth */

: greetings cr 0 do ." Merry Christmas" cr loop ;

15 greetings

			Dave Seaman
			..!pur-ee!pucc-k:ags

/* Fortran? */

If you want an obscure solution, try the following Fortran on a VAX. It works on BSD4.1, BSD4.1c and System V.

integer table(12)
data table/248514560, -552542885, 4847, -83763968
   1, 323331, 1542717440, 1260, 1292108988
   2, 2037543525, 1919435552, 1836348265, 684897/
call out(table)
end
subroutine out(code)
external code
call code
return
end

Griff Smith AT&T Bell Laboratories, Murray Hill Phone: (201) 582-7736 Internet: ggs@ulysses.uucp UUCP: ulysses!ggs

/* Fortran 77 */

    program yule
    parameter (nwish = 15)

c

    do 1 i = 1,nwish
  1   print*,'Merry Christmas'

c

    end
				Jim Davies
				{pur-ee parsec}!uiucdcs!uiuccsb!davies

/* FP */ (Backus' Functional Programming Language): (Using the syntax of Scott Baden's UNIX implementation)

      ; MC prints the string 'Merry Christmas' 15 times when applied
      ;                       to any argument and returns T.
      {MC     %T @ out @ &%"Merry Christmas\n" @ iota @ %15}
				These languages courtesy of:
				    Pavel Curtis, Cornell
				    Mike Caplinger, Rice

/* GPSS */

SIMULATE
GENERATE	1
TERMINATE	1
START		15,,1
REPORT
TEXT		MERRY CHRISTMAS
END
  1. –From some unknown person on the other side of uucp

/* IBM 370 assembly */

How about this one (IBM 370 assembler running VM/VPS - a local hack at Boston University):

xmas csect

        stm     r14,r12,12(r13)
        lr      r12,r15
        using   xmas,r12
        st      r13,savearea+4
        la      r13,savearea

* * Initialize counter *

xmasloop ds 0h

        la      r2,15                   Print it 15 times
        qio     rb=xmasrb               Print "Merry Christmas"
        bct     r2,xmasloop
        l       r13,4(,r13)             Restore registers
        lm      r14,r12,12(r13)
        br      r14                     Return to OS

xmasrb qiorb ddname=sysprint,bufad=xmasmsg,lrecl=l'xmasmsg xmasmsg dc c' Merry Christmas' Don't forget carriage control

        end     xmas

If that isn't obscure, I don't know what is.

  1. –Sender: reg@ima!vaxine.UUCP

/* Icon */

  # write "Merry Christmas" 15 times on standard output
  procedure main()
    every 1 to 15 do write("Merry Christmas")
  end

"1 to 15" is a generator which produces the sequence 1..15; "every X do Y" evaluates Y for each value of X; write() writes a line of text.

				Randy Hudson
				decvax!cca!ima!inmet!rgh

/* Icon (Version 5) */

procedure main()

  every write(|"Merry Christmas") \ 15

end

The more canonical solution is:

procedure main()

  every 1 to 15 do
      write("Merry Christmas")

end

but obviously isn't as devious.

  1. –Bill Mitchell

/* Imp80 */

%begin

%integer index
%for index = 1, 1, 15 %cycle
	Print String("Merry Christmas")
	New Line
%repeat

%end %of %program

			From: jd@ukc.UUCP
	Organization: Computing Lab. Kent University, England

/* The Kent Recursive Calculator */

there you are, here is the merry christmas program in my favourite 
language, krc (The Kent Recursive Calculator),
a teaching and research applicative language used at the University of
Kent, Canterbury, UK.
the syntax is annexed and requests for the full formal description
of the language (syntax+semantics) will be considered.
the program is:
print 0 = []
print n = "Merry Christmas":nl:print (n-1)
and the command to run it (in the interpreter) is
print 15!
silvio lemos meira
computing lab
university of kent at canterbury
...vax135!ukc!srlm
SYNTAX...

(note: space is limited, but the syntax is available upon request;

just send me a stamped, self-addressed antelope -- Don Davis)

/* LISP */

 (do ((i 0 (add1 i)))
     ((eq i 15))
     (msg "Merry Christmas" N))
			Dave Seaman
			..!pur-ee!pucc-k:ags

/* Scheme or Maclisp or Franz Lisp */ ; (do 1))

  ((= i 15))
  (princ "Merry Christmas")
  (terpri)   ;new line

)

        		--  chip elliott     ...decvax!dartvax!chip

/* MTS Lisp */

(repeat '( print '"Merry Christmas") 15)    # MTS Lisp.
               Bruce Wilcox, Intermetrics Inc.

/* LSRHS Logo */ (from the Usenix82 tape):

to greet :n 10 if :n >1 then greet (:n - 1) 20 print [Merry Christmas] end greet 15

	From: seismo!decvax!trw-unix!trwspp!urban (Mike Urban)

/* Logo */

      repeat 15 [print "Merry\ Christmas]
				These languages courtesy of:
				    Pavel Curtis, Cornell
				    Mike Caplinger, Rice

/* LSE */

Here's a language you probably have never heard of… LSE (Langue Symbolique d'Instruction, or Symbolic Language of Instruction). I used it on some ancient machine in France (of French make) and it is roughly parallel to BASIC translated to French. It sure isn't my favorite, but it's interesting…

10 pour i = 1 jusqua 15 faire 20 20 afficher "Merry Christmas"

			Philippe Lacroute
			..decvax!sun!cochon

/* m4 */

define(`merry',`ifelse(eval($1),eval(0),,Merry Christmas `merry'(eval($1-1)))')dnl merry(15)dnl

				Joseph L. Wood, III
				AT&T Information Systems
				Laboratories, Holmdel
				(201) 834-3759
				ariel!jlw

/* MACSYMA */

      doit() := for i:1 thru 15 do print("Merry Christmas")$
				These languages courtesy of:
				    Pavel Curtis, Cornell
				    Mike Caplinger, Rice

/* make */

If you use the following as the description file for 'make', it will satisfy your requirement. Make can be considered a language interpreter, so what the heck.

———————- cut ——- here ———————————– .SILENT:

foo_._bar_ : # some name unlikely to already exist

echo merry christmas
echo merry christmas
echo merry christmas
echo merry christmas
echo merry christmas
echo merry christmas
echo merry christmas
echo merry christmas
echo merry christmas
echo merry christmas
echo merry christmas
echo merry christmas
echo merry christmas
echo merry christmas
echo merry christmas
  1. –From some unknown person on the other side of uucp

/* A Maryland Text Editor procedure */


let a=0 next:test a<15 escape dis 'Merry Christmas' let a=a+1 jump next

From: seismo!decvax!sdcsvax!ittvax!dcdwest!noscvax!kemp

/* Mesa 5.0 */

– Here it is in Mesa 5.0; good luck trying to find an Alto or a D-machine – on which to run it.

DIRECTORY

      IODefs: FROM "iodefs" USING [WriteLine];

MerryChristmas: PROGRAM IMPORTS IODefs =

      BEGIN
      i: INTEGER; -- loop index
      FOR i IN [0..15) DO -- print the message 15 times
              WriteLine["Merry Christmas"]; -- this is the message, and the
                                            -- procedure WriteLine[] provides
                                            -- the carriage return
              ENDLOOP; -- go back and do it again
      END. -- all done
  1. - Patrick Olmstead
  1. - …ucbvax!menlo70!sytek!olmstead
  2. - …decvax!sytek!olmstead (when decvax answers the phone)

/* MIX */

* * THIS PROGRAM WILL PRINT "MERRY CHRISTMAS" 15 TIMES * LP EQU 18 CARD PUNCH DEVICE * MSG ALF MERR DON'T FORGET THE BLANK SPACE FOR CCTL

         ALF  Y CHR
         ALF  ISTMA
         ALF  S
         ORIG *+20

* START EQU *

         ENT1 0		INITIALIZE COUNTER

* LOOP EQU *

         OUT  MSG(LP)		WRITE IT OUT
         JBUS *(LP)		WAIT ON I/O
         INC1 1		R1 := R1 + 1
         CMP1 =15=		IF (R1 = 15)
         JE   DONE		   THEN DONE
         JMP  LOOP		   ELSE DO IT AGAIN

* DONE EQU *

         HLT			AND A HAPPY NEW YEAR
         END  START

– Theodore Hope School of ICS, Georgia Tech, Atlanta GA CSNet: Hope @ GaTech ARPA: Hope.GaTech @ CSNet-Relay uucp: …!{akgua,allegra,rlgvax,sb1,unmvax,ut-ngp,ut-sally}!gatech!Hope

/* MLisp */ (Gosling's Emacs editor extension language):

      (provide-prefix-argument 15 (insert-string "Merry Christmas\n"))
				These languages courtesy of:
				    Pavel Curtis, Cornell
				    Mike Caplinger, Rice

/* Modula-2 */

Module cheers; ODULEcheers; FROM InOut IMPORT WriteLn, WriteString; VAR

i	:CARDINAL;

BEGIN

FOR i := 1 TO 15 DO
  WriteString('Merry Christmas');
  WriteLn;
END;	(*FOR I*)

END cheers.

		From: seismo!decvax!decwrl!amd70!fortune!dsd!mush

/* MTS editor */

* And here is a weird one written in the MTS editor * * the @verify@-lnum says to print the new line without linenumber * '*' refers the current line number. *

insert "merry christmas" @verify@-lnum copy * to * copies=14 @verify@-lnum

  1. –From: seismo!cmcl2!floyd!ihnp4!alberta!stephen

/* Mystery Language */ (Author did not include name and I don't recognize it)

MODULE Greetings; FROM Terminal IMPORT WriteString, WriteLn;

VAR i: CARDINAL;

BEGIN

FOR i:=1 TO 15 DO
  WriteString("Merry Christmas");
  WriteLn;
END; (*for*)

END Greetings.

	From: seismo!decvax!decwrl!amd70!dual!proper!opje

/* Newspeak */

(defproc merry-xmas () (values)

(do ((i 1 (1+ i)))
    (print "Merry Christmas")
    (exit-do-if (= i 15))))
 
	From: John Foderaro (on an h19-u) <ucbvax!ucbkim:jkf>

/* nroff */

.nr i 15+1 1 .de MC .if \\n-i \{ .tl Merry Christmas . MC \} .. .MC

		R. Drew Davis  pyuxbb!drew

/* OOPC */ (an object-oriented preprocessor for C):

main() {

int i;
for (i=0; i<15; i++)
	printf("Merry Christmas\n");

}

If it looks a lot like C, that's because it is. The object-oriented features are only used when you're dealing with objects (you can use C wherever you want).

Karl Freburger
decvax!ittvax!freb

/* OPS5 */

; A program to print Merry Christmas 15 times, in OPS5. ; OPS5 is a simple AI/expert systems language for writing ; production systems in. (literalize counter value) ; Analogous to a record declaration.

			; The program:    A single production.

(p print-one-merry-christmas ; if

(counter ^value {<c> > 0})		;	counter.value > 0
-->					; then
(write (crlf) Merry Christmas)		;      write("Merry christmas");
(modify 1 ^value (compute <c> - 1)))	;      counter.value -:= 1;

(make counter ^value 15) ; Create a counter with value=15 (watch 0) ; No tracing. (run) ; Go for it.

; Ben Hyde, Intermetrics Inc.

/* Pascal */

program yuletidings (output); const

numberofwishes = 15;

var

i : integer;

begin

for i := 1 to numberofwishes do
	writeln('Merry Christmas');
end.
				Jim Davies
				{pur-ee parsec}!uiucdcs!uiuccsb!davies

/* PDP-11 assembler */ (under RT-11)

.TITLE	MERRY XMAS
.IDENT	/R M/
.NLIST	BEX
.DSABL	GBL
.ENABL	LC
.MACLL	.PRINT, .EXIT

MERRY::

MOV	#15.,R4			;set up the print count
.PRINT	#MSG1			;print the message
SOB	R4,MERRY		;loop until finished
.EXIT				;return to RT-11

MSG1: .ASCIZ /Merry Christmas !!!/

.EVEN
.END	MERRY
			From: seismo!utah-cs!pwa-b!miorelli

/* PDP-11 assembler */ (under UNIX)

	mov	$15.,r4
1:
	mov	$1,r0
	sys	write; 2f; 3f-2f
	bcs	1f
	sob	r4,1b
	clr	r0
1:
	sys	exit
.data
2:	<Merry Christmas\n\0>
3:

Jim McKie Mathematisch Centrum, Amsterdam ….mcvax!jim

/* PL/I version. ANS PL/I, subset G. */

merry: proc options(main);

dcl i fixed binary;

do i = 1 to 15;

   put skip edit('Merry Christmas') (a);

end;

end merry;

       		--  chip elliott     ...decvax!dartvax!chip

/* PL/1 */

START: PROC OPTIONS(MAIN); DCL I FIXED BINARY(15); /* LONG FORM; SAME AS DCL I; */ DO I = 1 TO 15;

PUT EDIT ("Merry Christmas");

END; END START;

													julie	
			seismo!philabs!jah

/* PL/1 */

yule: proc options(main);

%numwish = '15';

do i = 1,numwish;

 put skip list('Merry Christmas');
 end;

end yule;

				Jim Davies
				{pur-ee parsec}!uiucdcs!uiuccsb!davies

/* Pr1me assembly */

       SEG
       RLIT
       SUBR   PRINT
       LINK

PRINT ECB START

       DYNM   COUNT
       PROC

START LDA =15

       STA    COUNT

START1 LDA COUNT

       BEQ    DONE
       S1A
       STA    COUNT
       CALL   TNOU
       AP     =C'Merry Christmas',S
       AP     =15,SL
       JMP    START1

DONE PRTN

       END

Jeff Lee CSNet: Jeff @ GATech ARPA: Jeff.GATech @ CSNet-Relay uucp: …!{sb1,allegra,ut-ngp}!gatech!jeff …!duke!mcnc!msdc!gatech!jeff

/* Prolog */

hello(0) :- !.
hello(N) :- M is N - 1, print("Merry Christmas"), hello(M), !.
hello(15)!

(I'm just learning prolog, so my apologies if the style is wrong.)

						Aloke Prabhakar
						prabhaka@BERKELEY
						ucbvax!prabhaka

/* Prolog */

wmc:- countmc(15). countmc(0). countmc(Count):- write('Merry Christmas'), nl, Ncnt is Count-1, countmc(Ncnt).

  1. -Peter Borgwardt, U. of Minnesota

borgward.umn-cs@rand-relay

/* REVE */ (Equational-programming/term-rewriting system):

(Has no I/O. This will look like

          merry_christmas(merry_christmas(...))

Also, to avoid having to specify 15 as the fifteenth successor of zero, we define addition and multiplication.)

      (x + 0)     == x
      (x + s(y))  == (s(x) + y)
      (x * 0)     == 0
      (x * s(y))  == (x + (x * y))
      mc(s(0))    == merry_christmas
      mc(s(s(x))) == merry_christmas(mc(s(x)))
      
      mc( (s(s(s(0))) * s(s(s(s(s(0)))))) )
				These languages courtesy of:
				    Pavel Curtis, Cornell
				    Mike Caplinger, Rice

/* *roff */

Well, the most natural choice for Merry Christmas is of course:

V/N/T/DIT/roff.

This will print it on the standard output, It will give you an extra blank line, sorry about that.

.fp 1 MC
.pl 1
.nf
.nr l 0 +1
.de mm
.if \\n+l=15 .rm mm
Merry Christmas
.mm
..
.mm

The font MC is of course your local ``Merry Christmas font''; all the characters are built from christmas trees. If you don't want the extra newline you can use the error output:

.de mm
.if \\nk=14 .ab Merry Christmas
.nr k +1
.tm Merry Christmas
.mm
..
.mm

Of course, you loose the nice look of the MC font.

There are of course about a dozen other ways to use troff for this.

  1. - jaap akkerhuis (mcvax!jaap)

/* QC */

/* * This program is written in the language QC (quick & clean), a * descendant of QD (quick & dirty). Both languages were written by * Chris Grey for 370/ systems runing MTS (a user-friendly operating * system). */ proc main(): int I; extern printf;

for I from 1 upto 15 do
      printf("Merry Christmas")
od

corp

  1. –From: seismo!cmcl2!floyd!ihnp4!alberta!stephen

/* sed script */

echo 'Mery Chistma' | sed '

s/\(..\)\(.\)\(....\)\(.\)\(.\)\(...\)/\1\2\2\3\2\4\5\6\5/
h;G;G
s/$/\

/

s/.*/&&&&&/

'

		From: seismo!decvax!ucbvax!reed!phillips

/* SETL */ (Doesn't use any of the interesting features of the language):

      definef main();
          (1 <= forall i <= 15) print('Merry Christmas');
      end main;.
				These languages courtesy of:
				    Pavel Curtis, Cornell
				    Mike Caplinger, Rice

/* XEROX sigma-7 assembler */ (running under CP-V)

SYSTEM SIG7
SYSTEM BPM
REF M:LO

BUFR TEXT 'MERRY CHRISTMAS' START LI,4 15

M:WRITE M:LO,(BUF,BUFR),(SIZE,15)
BDR,4 START+1
M:EXIT
END START

or, you can avoid loading the BPM macro's by doing your own FPT

SYSTEM SIG7
REF M:LO

BUFR TEXT 'MERRY CHRISTMAS' FPT GEN,8,24 X'11',M:LO

GEN,4,28 3,X'10'
DATA BUFR
DATA 15

START LI,4 15

CAL1,1 FPT
BDR,4 START
CAL1,9 1
END START
				Bob McQueer
				druxt!mcq

/* Smalltalk-80 */

output <- WriteStream on: (String new: 10).
1 to 15 do: [
	output nextPutAll: 'Merry Christmas'.
	output cr
].
output contents.

Select this from the screen and hit 'printIt', and out comes the message.

		From: seismo!decvax!ittvax!freb

/* Smalltalk-80 */

      merryChristmas: aStream
          "Prints 'Merry Christmas' on aStream 15 times."
          
          15 timesRepeat:
              [aStream
                  nextPutAll: 'Merry Christmas';
                  cr
              ]
				These languages courtesy of:
				    Pavel Curtis, Cornell
				    Mike Caplinger, Rice

/* Snobol-3 */ (Snobol-4?? What's that? We use Snobol-3 here.)

* S.D.S. TSS SNOBOL-3

        N = 1

LOOP LOUT = 'MERRY CHRISTMAS'

        N = .LT(N,15) N + 1                        /S(LOOP)F(.EXIT)
		From: seismo!rochester!rocksvax!sunybcs!colonel

/* Snobol 4 */

* Snobol 4 version. Not very elegant! * i = 1

a: output = 'Merry Christmas'

 i = i + 1
 le(i,15)    :s(a)
	          --  chip elliott     ...decvax!dartvax!chip

/* SPEED editor */

To print Merry Christmas 15 times using the SPEED editor from Data General (SPEED is a TECO-like editor, $ will represent an escape character, ^D will represent a control-D):

15<iMerry Christmas $>$#t$#k$h^D

			Michael Meissner
			Data General Corporation
			...{allegra, decvax!ittvax, rocky2}!datagen!mrm

/* SPL/3000 */

$Control Uslinit Begin

Byte Array

 Msg (0:14) := "Merry Christmas";

Integer

 I;

Intrinsic

 Print, Terminate;

For I := 1 UNTIL 15 Do

 Print (Msg, -15, 0);        << 15 bytes, no CCTL >>

Terminate;

End.

From: seismo!harpo!ihnp4!clyde!akgua!emory!gatech!hope

/* Stage 2 */

#$#$0 (+-*/) END# $F0# # $# $10$F7# Merry Christmas$F15# $F8# ## 15 END

  1. –Written and Contributed by Tom Almy, Tektronix, Inc.

/* Stoic */ 15 0 DO "Merry Christmas&15&" MSG LOOP

  1. –Written and Contributed by Tom Almy, Tektronix, Inc.

/* TECO */

15<^AMerry Christmas

(where '$' is an Escape, and ^A is a control-A)

  1. –Written and Contributed by Tom Almy, Tektronix, Inc.

/* TECO */ (Text Editor COrrector)

15<^AMerry Christmas

note: ^A is a Control A

    $ is an escape character

And a Happy New Year,

			Rob Spray
			Software Designer
			US Mail:  Computer*Thought Corporation
				  1721 West Plano Parkway, Suite 125
				  Plano TX 75075
			BellTel:  214-424-3511
			ARPAnet:  ROB.CT@RAND-RELAY
			uucp:     ... decvax!cornell!ctvax!rob

/* TECO */

:IGMerry Christmas

$ !* Put string in Q-register G !

15<:GG>$$		!* 15 Times, print it out !

The dollar signs represent ESCapes.

			Merry Christmas!
				David Kaufman
				...decvax!yale-comix!kaufman

/* TeX */ (Knuth's text formatting language, assuming presence of Plain.TeX macros):

      \def\mc#1{\ifnum #1>0 Merry Christmas\par
                {\count0=#1\advance\count0 by-1\mc\count0}\fi}
      \mc{15}
				These languages courtesy of:
				    Pavel Curtis, Cornell
				    Mike Caplinger, Rice

/* TRAC */

#(ds,Merry-Christmas,(#(eq,arg,0,,(#(PS,Merry Christmas( ))#(Merry-Christmas,#(su,arg,1))))))' #(ss,Merry-Christmas,arg)' #(Merry-Christmas,15)'

Note: "TRAC" is a trademark of Rockford Research, Inc.

  1. –Written and Contributed by Tom Almy, Tektronix, Inc.

/* TRAC */

      #(ds,merry,(#(eq,count,0,,((Merry Christmas
      )#(cl,merry,#(su,count,1))))))'
      #(ss,merry,count)'
      #(cl,merry,15)'

The TRAC language is a text- and macro-processing language reminiscent of LISP. The first command defines a function, the second marks "count" as a dummy argument, the third calls the function. The printing is done by the command interpreter.

Andy Behrens

                 decvax!dartvax!andyb

/* TROFF */

      .de MC
      .nf
      .if \\$1>0 \{\
      Merry Christmas
      .nr x \\$1
      .nr x -1
      .MC \\nx \}
      ..
      .MC 15
				These languages courtesy of:
				    Pavel Curtis, Cornell
				    Mike Caplinger, Rice

/* Turing */


for : 1 .. 15

  put "Merry Christmas"

end for


Stephen Perelgut Computer Systems Research Group University of Toronto

    Usenet:	{linus, ihnp4, allegra, decvax, floyd}!utcsrgv!perelgut

/* UL */

Here's one you probably wouldn't expect to get. It is Model204 User Language (UL is a query/programming language for the M204 database system that runs on IBM mainframes).

BEGIN %A IF FIXED DP 0 1. FOR %A FROM 1 TO 15

 PRINT 'MERRY CHRISTMAS'

2. END

That's it!

			Mickey Levine
			decvax!cca!mickey

/* UNIX shell script */

echo "Merry Christmas" | sed -e 's/./Merry Christmas%/g' | tr % '\012'

	                 Ben Hyde Intermetrics Inc.

/* Unix shell script (Bourne) */

COUNT=0 while test $COUNT -lt 15 do

echo "Merry Christmas."
COUNT=`expr $COUNT + 1`

done

		Ta!
		Dave Ihnat
		ihuxx!ignatz

/* VALGOL */

I didn't look closely, but I didn't see a submission in VALGOL. Here is an attempt, but I can't vouch for its correctness, since I don't know any valley girls. After all, I live in Washington, not California, and we're a little behind the times up here.

Like, gag me with a Merry Christmas! No Way! Merry Christmas! Like, so totally Merry Christmas! Barf me out with a Merry Christmas! So gross! Merry Christmas!

I realize this is only five times, not fifteen, but you can multiprocess in VALGOL. Just get three valley girls and execute the above on each one.

		From: seismo!cornell!uw-beaver!ssc-vax!fluke!witters

/* VAX MACRO */ (VMS flavour…snicker)

; text: .ascii "Merry Christmas" ; output text

.byte	13,10			; carriage control
tlen 	= . - text		; text length

tty: .ascid "TT:" ; logical name of current terminal chan: .blkw 1 ; storage for IO channel number

.entry xmas,^M<r10>
$ASSIGN_S	devnam=tty,chan=chan		;get channel to terminal
movl		#1,r10				;initialize loop

loop: $QIOW_S chan=chan,func=#IO$_WRITELBLK,- ;dump the message

		P1=text,P2=#tlen
aobleq		#15,r10,loop			;15 times
ret
.end xmas
	From: seismo!decvax!microsof!ubc-vision!mprvaxa!tbray

/* Xerox Data Systems Metasymbol Assembler */

       system       sig9
       system       bpm
       csect        1

message text 'Merry Christmas'

       ref          m:lo

start equ,0 $

       li,7         15

loop equ,0 $

       m:write      m:lo,(buf,message),(size,15)
       bdr,7        loop
       m:exit      
       end          start

Jon Bertoni

/* XPL version. (Defined in book "A Compiler Generator".) */

dcl i fixed;

do i = 1 to 15;

   output = 'Merry Christmas';

end;

  1. - chip elliott …decvax!dartvax!chip

				Don Davis
				JHU/APL
			...decvax!harpo!seismo!umcp-cs!aplvax!ded
			...rlgvax!cvl!umcp-cs!aplvax!ded

Article 257 of comp.sources.misc: Path: puukko!santra!tut!enea!mcvax!uunet!lll-winken!lll-lcc!ames!necntc!ncoast!allbery From: peter@sugar.UUCP (Peter da Silva) Newsgroups: comp.sources.misc Subject: v03i080: Re: v03i076: Just for fun (something which once appeared on the net) Message-ID: 8807130507.AA26710@uunet.UU.NET Date: 13 Jul 88 05:07:49 GMT Sender: allbery@ncoast.UUCP Reply-To: peter@sugar.UUCP (Peter da Silva) Lines: 34 Approved: allbery@ncoast.UUCP

Posting-number: Volume 3, Issue 80 Submitted-by: "Peter da Silva" peter@sugar.UUCP Archive-name: more-xmas

[Introducing the major motion picture: THE CHRISTMAS THAT WOULDN'T DIE! Now showing at theaters near you!!! ;-) ++bsa]

Ratfor (from the book, with the DEC F4P Fortran):

do(i=1,15) type *, 'Merry Christmas'
end

Ratforth (AKA Fifth, a language I hacked up to make Forth less ugly):

define christmas { 
	do(15,0) { 
		type(count("Merry Christmas"));
		CR;
	}
}

This produces, by the way:

: christmas 15 0 do " Merry Christmas" count type CR ;

AREXX:

/* Say Merry Christmas 15 times */
do i=1 to 15
	say 'Merry Christmas'
	end i

— – `-_-' Peter (have you hugged your wolf today?) da Silva. – U Mail to …!uunet!sugar!peter, flames to alt.dev.null. – "Running OS/2 on a '386 is like pulling your camper with an Indy car"



1)
i 0 (+ i 1
/data/webs/external/dokuwiki/data/pages/archive/holiday/merry.jok.txt · Last modified: 2000/01/16 15:33 by 127.0.0.1

Donate Powered by PHP Valid HTML5 Valid CSS Driven by DokuWiki