* Towers of Hanoi 08/09/2015 HANOITOW CSECT USING HANOITOW,R12 r12 : base register LR R12,R15 establish base register ST R14,SAVE14 save r14 BEGIN LH R2,=H'4' n <=== L R3,=C'123 ' stating position BAL R14,MOVE r1=move(m,n) RETURN L R14,SAVE14 restore r14 BR R14 return to caller SAVE14 DS F static save r14 PG DC CL44'xxxxxxxxxxxx Move disc from pole X to pole Y' NN DC F'0' POLEX DS F current poles POLEN DS F new poles * .... recursive subroutine move(n, poles) [r2,r3] MOVE LR R10,R11 save stackptr (r11) in r10 temp LA R1,STACKLEN amount of storage required GETMAIN RU,LV=(R1) allocate storage for stack USING STACKDS,R11 make storage addressable LR R11,R1 establish stack addressability ST R14,SAVE14M save previous r14 ST R10,SAVE11M save previous r11 LR R1,R5 restore saved argument r5 BEGINM STM R2,R3,STACK push arguments to stack ST R3,POLEX CH R2,=H'1' if n<>1 BNE RECURSE then goto recurse L R1,NN LA R1,1(R1) nn=nn+1 ST R1,NN XDECO R1,PG nn MVC PG+33(1),POLEX+0 from MVC PG+43(1),POLEX+1 to XPRNT PG,44 print "move disk from to" B RETURNM RECURSE L R2,N n BCTR R2,0 n=n-1 MVC POLEN+0(1),POLES+0 from MVC POLEN+1(1),POLES+2 via MVC POLEN+2(1),POLES+1 to L R3,POLEN new poles BAL R14,MOVE call move(n-1,from,via,to) LA R2,1 n=1 MVC POLEN,POLES L R3,POLEN new poles BAL R14,MOVE call move(1,from,to,via) L R2,N n BCTR R2,0 n=n-1 MVC POLEN+0(1),POLES+2 via MVC POLEN+1(1),POLES+1 to MVC POLEN+2(1),POLES+0 from L R3,POLEN new poles BAL R14,MOVE call move(n-1,via,to,from) RETURNM LM R2,R3,STACK pull arguments from stack LR R1,R11 current stack L R14,SAVE14M restore r14 L R11,SAVE11M restore r11 LA R0,STACKLEN amount of storage to free FREEMAIN A=(R1),LV=(R0) free allocated storage BR R14 return to caller LTORG DROP R12 base no longer needed STACKDS DSECT dynamic area SAVE14M DS F saved r14 SAVE11M DS F saved r11 STACK DS 0F stack N DS F r2 n POLES DS F r3 poles STACKLEN EQU *-STACKDS YREGS END HANOITOW 5 var, disks var sa var sb var sc : save sc ! sb ! sa ! disks ! ; : get sa @ sb @ sc @ ; : get2 get swap ; : hanoi save disks @ not if ;; then disks @ get disks @ n:1- get2 hanoi save cr " move a ring from " . sa @ . " to " . sb @ . disks @ n:1- get2 rot hanoi ; " Tower of Hanoi, with " . disks @ . " rings: " . disks @ 1 2 3 hanoi cr bye public function move(n:int, from:int, to:int, via:int):void { if (n > 0) { move(n - 1, from, via, to); trace("Move disk from pole " + from + " to pole " + to); move(n - 1, via, to, from); } } with Ada.Text_Io; use Ada.Text_Io; procedure Towers is type Pegs is (Left, Center, Right); procedure Hanoi (Ndisks : Natural; Start_Peg : Pegs := Left; End_Peg : Pegs := Right; Via_Peg : Pegs := Center) is begin if Ndisks > 0 then Hanoi(Ndisks - 1, Start_Peg, Via_Peg, End_Peg); Put_Line("Move disk" & Natural'Image(Ndisks) & " from " & Pegs'Image(Start_Peg) & " to " & Pegs'Image(End_Peg)); Hanoi(Ndisks - 1, Via_Peg, End_Peg, Start_Peg); end if; end Hanoi; begin Hanoi(4); end Towers; move := proc(n::number, src::number, dst::number, via::number) is if n > 0 then move(n - 1, src, via, dst) print(src & ' to ' & dst) move(n - 1, via, dst, src) fi end move(4, 1, 2, 3) PROC move = (INT n, from, to, via) VOID: IF n > 0 THEN move(n - 1, from, via, to); printf(($"Move disk from pole "g" to pole "gl$, from, to)); move(n - 1, via, to, from) FI ; main: ( move(4, 1,2,3) ) begin procedure move ( integer value n, from, to, via ) ; if n > 0 then begin move( n - 1, from, via, to ); write( i_w := 1, s_w := 0, "Move disk from peg: ", from, " to peg: ", to ); move( n - 1, via, to, from ) end move ; move( 4, 1, 2, 3 ) end. PROC move(n, from, to, via) IF n > 0 move(n-1, from, via, to) WriteF('Move disk from pole \d to pole \d\n', from, to) move(n-1, via, to, from) ENDIF ENDPROC PROC main() move(4, 1,2,3) ENDPROC global moves --this is so the handler 'hanoi' can see the 'moves' variable set moves to "" hanoi(4, "peg A", "peg C", "peg B") on hanoi(ndisks, fromPeg, toPeg, withPeg) if ndisks is greater than 0 then hanoi(ndisks - 1, fromPeg, withPeg, toPeg) set moves to moves & "Move disk " & ndisks & " from " & fromPeg & " to " & toPeg & return hanoi(ndisks - 1, withPeg, toPeg, fromPeg) end if return moves end hanoi on run map(arrows, hanoi(3, "left", "right", "mid")) -- {"left -> right", "left -> mid", "right -> mid", -- "left -> right", "mid -> left", "mid -> right", "left -> right"} end run -- n -> s -> s -> s -> [(s, s)] on hanoi(n, a, b, c) if n > 0 then hanoi(n - 1, a, c, b) & {{a, b}} & hanoi(n - 1, c, b, a) else {} end if end hanoi -- DISPLAY FUNCTION -- (a, a) -> String on arrows(x) item 1 of x & " -> " & item 2 of x end arrows -- LIBRARY FUNCTION -- map :: (a -> b) -> [a] -> [b] on map(f, xs) script mf property lambda : f end script set lng to length of xs set lst to {} repeat with i from 1 to lng set end of lst to mf's lambda(item i of xs, i, xs) end repeat return lst end map move(n, from, to, via) ;n = # of disks, from = start pole, to = end pole, via = remaining pole { if (n = 1) { msgbox , Move disk from pole %from% to pole %to% } else { move(n-1, from, via, to) move(1, from, to, via) move(n-1, via, to, from) } } move(64, 1, 3, 2) Func move($n, $from, $to, $via) If ($n = 1) Then ConsoleWrite(StringFormat("Move disk from pole "&$from&" To pole "&$to&"\n")) Else move($n - 1, $from, $via, $to) move(1, $from, $to, $via) move($n - 1, $via, $to, $from) EndIf EndFunc move(4, 1,2,3) $ awk 'func hanoi(n,f,t,v){if(n>0){hanoi(n-1,f,v,t);print(f,"->",t);hanoi(n-1,v,t,f)}} BEGIN{hanoi(4,"left","middle","right")}' SUB move (n AS Integer, fromPeg AS Integer, toPeg AS Integer, viaPeg AS Integer) IF n>0 THEN move n-1, fromPeg, viaPeg, toPeg PRINT "Move disk from "; fromPeg; " to "; toPeg move n-1, viaPeg, toPeg, fromPeg END IF END SUB move 4,1,2,3 10 DIM N(1024), F(1024), T(1024), V(1024): REM STACK PER PARAMETER 20 SP = 0: REM STACK POINTER 30 N(SP) = 4: REM START WITH 4 DISCS 40 F(SP) = 1: REM ON PEG 1 50 T(SP) = 2: REM MOVE TO PEG 2 60 V(SP) = 3: REM VIA PEG 3 70 GOSUB 100 80 END 90 REM MOVE SUBROUTINE 100 IF N(SP) = 0 THEN RETURN 110 OS = SP: REMEMBER STACK POINTER 120 SP = SP + 1: REM INCREMENT STACK POINTER 130 N(SP) = N(OS) - 1: REM MOVE N-1 DISCS 140 F(SP) = F(OS) : REM FROM START PEG 150 T(SP) = V(OS) : REM TO VIA PEG 160 V(SP) = T(OS) : REM VIA TO PEG 170 GOSUB 100 180 OS = SP - 1: REM OS WILL HAVE CHANGED 190 PRINT "MOVE DISC FROM"; F(OS); "TO"; T(OS) 200 N(SP) = N(OS) - 1: REM MOVE N-1 DISCS 210 F(SP) = V(OS) : REM FROM VIA PEG 220 T(SP) = T(OS) : REM TO DEST PEG 230 V(SP) = F(OS) : REM VIA FROM PEG 240 GOSUB 100 250 SP = SP - 1 : REM RESTORE STACK POINTER FOR CALLER 260 RETURN call move(4,1,2,3) print "Towers of Hanoi puzzle completed!" end subroutine move (n, fromPeg, toPeg, viaPeg) if n>0 then call move(n-1, fromPeg, viaPeg, toPeg) print "Move disk from "+fromPeg+" to "+toPeg call move(n-1, viaPeg, toPeg, fromPeg) end if end subroutine @echo off setlocal enabledelayedexpansion %==The main thing==% %==First param - Number of disks==% %==Second param - Start pole==% %==Third param - End pole==% %==Fourth param - Helper pole==% call :move 4 START END HELPER echo. pause exit /b 0 %==The "function"==% :move setlocal set n=%1 set from=%2 set to=%3 set via=%4 if %n% gtr 0 ( set /a x=!n!-1 call :move !x! %from% %via% %to% echo Move top disk from pole %from% to pole %to%. call :move !x! %via% %to% %from% ) exit /b 0 DIM Disc$(13),Size%(3) FOR disc% = 1 TO 13 Disc$(disc%) = STRING$(disc%," ")+STR$disc%+STRING$(disc%," ") IF disc%>=10 Disc$(disc%) = MID$(Disc$(disc%),2) Disc$(disc%) = CHR$17+CHR$(128+disc%-(disc%>7))+Disc$(disc%)+CHR$17+CHR$128 NEXT disc% MODE 3 OFF ndiscs% = 13 FOR n% = ndiscs% TO 1 STEP -1 PROCput(n%,1) NEXT INPUT TAB(0,0) "Press Enter to start" dummy$ PRINT TAB(0,0) SPC(20); PROChanoi(ndiscs%,1,2,3) VDU 30 END DEF PROChanoi(a%,b%,c%,d%) IF a%=0 ENDPROC PROChanoi(a%-1,b%,d%,c%) PROCtake(a%,b%) PROCput(a%,c%) PROChanoi(a%-1,d%,c%,b%) ENDPROC DEF PROCput(disc%,peg%) PRINTTAB(13+26*(peg%-1)-disc%,20-Size%(peg%))Disc$(disc%); Size%(peg%) = Size%(peg%)+1 ENDPROC DEF PROCtake(disc%,peg%) Size%(peg%) = Size%(peg%)-1 PRINTTAB(13+26*(peg%-1)-disc%,20-Size%(peg%))STRING$(2*disc%+1," "); ENDPROC ( ( move = n from to via . !arg:(?n,?from,?to,?via) & ( !n:>0 & move$(!n+-1,!from,!via,!to) & out$("Move disk from pole " !from " to pole " !to) & move$(!n+-1,!via,!to,!from) | ) ) & move$(4,1,2,3) ); [ This implementation is recursive and uses a stack, consisting of frames that are 8 bytes long. The layout is as follows: Byte Description 0 recursion flag (the program stops if the flag is zero) 1 the step which is currently executed 4 means a call to move(a, c, b, n - 1) 3 means a call to move(a, b, c, 1) 2 means a call to move(b, a, c, n - 1) 1 prints the source and dest pile 2 flag to check whether the current step has already been done or if it still must be executed 3 the step which will be executed in the next loop 4 the source pile 5 the helper pile 6 the destination pile 7 the number of disks to move The first stack frame (0 0 0 0 0 0 0 0) is used to abort the recursion. ] >>>>>>>> These are the parameters for the program (1 4 1 0 'a 'b 'c 5) +>++++>+>> >>>>++++++++[<++++++++++++>-]< [<<<+>+>+>-]<<<+>++>+++>+++++> <<<<<<<< [> while (recurse) [- if (step gt 0) >[-]+< todo = 1 [- if (step gt 1) [- if (step gt 2) [- if (step gt 3) >>+++<< next = 3 >-< todo = 0 >>>>>>[>+>+<<-]>[<+>-]> n dup - [[-] if (sub(n 1) gt 0) <+>>>++++> push (1 0 0 4) copy and push a <<<<<<<<[>>>>>>>>+>+ <<<<<<<<<-]>>>>>>>> >[<<<<<<<<<+>>>>>>>>>-]< > copy and push c <<<<<<<[>>>>>>>+>+ <<<<<<<<-]>>>>>>> >[<<<<<<<<+>>>>>>>>-]< > copy and push b <<<<<<<<<[>>>>>>>>>+>+ <<<<<<<<<<-]>>>>>>>>> >[<<<<<<<<<<+>>>>>>>>>>-]< > copy n and push sub(n 1) <<<<<<<<[>>>>>>>>+>+ <<<<<<<<<-]>>>>>>>> >[<<<<<<<<<+>>>>>>>>>-]< - >> ] <<<<<<<< ] >[-< if ((step gt 2) and todo) >>++<< next = 2 >>>>>>> +>>>+> push 1 0 0 1 a b c 1 <<<<<<<<[>>>>>>>>+>+ <<<<<<<<<-]>>>>>>>> >[<<<<<<<<<+>>>>>>>>>-]< > a <<<<<<<<[>>>>>>>>+>+ <<<<<<<<<-]>>>>>>>> >[<<<<<<<<<+>>>>>>>>>-]< > b <<<<<<<<[>>>>>>>>+>+ <<<<<<<<<-]>>>>>>>> >[<<<<<<<<<+>>>>>>>>>-]< > c + >> >]< ] >[-< if ((step gt 1) and todo) >>>>>>[>+>+<<-]>[<+>-]> n dup - [[-] if (n sub 1 gt 0) <+>>>++++> push (1 0 0 4) copy and push b <<<<<<<[>>>>>>>+ <<<<<<<-]>>>>>>> >[<<<<<<<<+>>>>>>>>-]< > copy and push a <<<<<<<<<[>>>>>>>>>+ <<<<<<<<<-]>>>>>>>>> >[<<<<<<<<<<+>>>>>>>>>>-]< > copy and push c <<<<<<<<[>>>>>>>>+ <<<<<<<<-]>>>>>>>> >[<<<<<<<<<+>>>>>>>>>-]< > copy n and push sub(n 1) <<<<<<<<[>>>>>>>>+>+ <<<<<<<<<-]>>>>>>>> >[<<<<<<<<<+>>>>>>>>>-]< - >> ] <<<<<<<< >]< ] >[-< if ((step gt 0) and todo) >>>>>>> >++++[<++++++++>-]< >>++++++++[<+++++++++>-]<++++ >>++++++++[<++++++++++++>-]<+++++ >>+++++++++[<++++++++++++>-]<+++ <<< >.+++++++>.++.--.<<. >>-.+++++.----.<<. >>>.<---.+++.>+++.+.+.<.<<. >.>--.+++++.---.++++. -------.+++.<<. >>>++.-------.-.<<<. >+.>>+++++++.---.-----.<<<. <<<<.>>>>. >>----.>++++++++.<+++++.<<. >.>>.---.-----.<<<. <<.>>++++++++++++++. >>>[-]<[-]<[-]<[-] +++++++++++++.---.[-] <<<<<<< >]< >>[<<+>>-]<< step = next ] return with clear stack frame <[-]>[-]>[-]>[-]>[-]>[-]>[-]>[-]<<<<<< <<<<<<<< >>[<<+>>-]<< step = next < ] #include void move(int n, int from, int to, int via) { if (n > 0) { move(n - 1, from, via, to); printf("Move disk from pole %d to pole %d\n", from, to); move(n - 1, via, to, from); } } int main() { move(4, 1,2,3); return 0; } #include #include #include typedef struct { int *x, n; } tower; tower *new_tower(int cap) { tower *t = calloc(1, sizeof(tower) + sizeof(int) * cap); t->x = (int*)(t + 1); return t; } tower *t[3]; int height; void text(int y, int i, int d, const char *s) { printf("\033[%d;%dH", height - y + 1, (height + 1) * (2 * i + 1) - d); while (d--) printf("%s", s); } void add_disk(int i, int d) { t[i]->x[t[i]->n++] = d; text(t[i]->n, i, d, "=="); usleep(100000); fflush(stdout); } int remove_disk(int i) { int d = t[i]->x[--t[i]->n]; text(t[i]->n + 1, i, d, " "); return d; } void move(int n, int from, int to, int via) { if (!n) return; move(n - 1, from, via, to); add_disk(to, remove_disk(from)); move(n - 1, via, to, from); } int main(int c, char *v[]) { puts("\033[H\033[J"); if (c <= 1 || (height = atoi(v[1])) <= 0) height = 8; for (c = 0; c < 3; c++) t[c] = new_tower(height); for (c = height; c; c--) add_disk(0, c); move(height, 0, 2, 1); text(1, 0, 1, "\n"); return 0; } public void move(int n, int from, int to, int via) { if (n == 1) { System.Console.WriteLine("Move disk from pole " + from + " to pole " + to); } else { move(n - 1, from, via, to); move(1, from, to, via); move(n - 1, via, to, from); } } void move(int n, int from, int to, int via) { if (n == 1) { std::cout << "Move disk from pole " << from << " to pole " << to << std::endl; } else { move(n - 1, from, via, to); move(1, from, to, via); move(n - 1, via, to, from); } } (defn towers-of-hanoi [n from to via] (if (= n 1) (println (format "Move from %s to %s" from to)) (do (towers-of-hanoi (dec n) from via to) (println (format "Move from %s to %s" from to)) (recur (dec n) via to from)))) >>SOURCE FREE IDENTIFICATION DIVISION. PROGRAM-ID. towers-of-hanoi. PROCEDURE DIVISION. CALL "move-disk" USING 4, 1, 2, 3 . END PROGRAM towers-of-hanoi. IDENTIFICATION DIVISION. PROGRAM-ID. move-disk RECURSIVE. DATA DIVISION. LINKAGE SECTION. 01 n PIC 9 USAGE COMP. 01 from-pole PIC 9 USAGE COMP. 01 to-pole PIC 9 USAGE COMP. 01 via-pole PIC 9 USAGE COMP. PROCEDURE DIVISION USING n, from-pole, to-pole, via-pole. IF n > 0 SUBTRACT 1 FROM n CALL "move-disk" USING CONTENT n, from-pole, via-pole, to-pole DISPLAY "Move disk from pole " from-pole " to pole " to-pole CALL "move-disk" USING CONTENT n, via-pole, to-pole, from-pole END-IF . END PROGRAM move-disk. hanoi = (ndisks, start_peg=1, end_peg=3) -> if ndisks staging_peg = 1 + 2 + 3 - start_peg - end_peg hanoi(ndisks-1, start_peg, staging_peg) console.log "Move disk #{ndisks} from peg #{start_peg} to #{end_peg}" hanoi(ndisks-1, staging_peg, end_peg) hanoi(4) (defun move (n from to via) (cond ((= n 1) (format t "Move from ~A to ~A.~%" from to)) (t (move (- n 1) from via to) (format t "Move from ~A to ~A.~%" from to) (move (- n 1) via to from)))) import std.stdio; void hanoi(in int n, in char from, in char to, in char via) { if (n > 0) { hanoi(n - 1, from, via, to); writefln("Move disk %d from %s to %s", n, from, to); hanoi(n - 1, via, to, from); } } void main() { hanoi(3, 'L', 'M', 'R'); } // Code found and then improved by Glenn C. Rhoads, // then some more by M. Kolar (2000). void main(in string[] args) { import core.stdc.stdio, std.conv, std.typetuple; immutable size_t n = (args.length > 1) ? args[1].to!size_t : 3; size_t[3] p = [(1 << n) - 1, 0, 0]; // Show the start configuration of the pegs. '|'.putchar; foreach_reverse (immutable i; 1 .. n + 1) printf(" %d", i); "\n|\n|".puts; foreach (immutable size_t x; 1 .. (1 << n)) { { immutable size_t i1 = x & (x - 1); immutable size_t fr = (i1 + i1 / 3) & 3; immutable size_t i2 = (x | (x - 1)) + 1; immutable size_t to = (i2 + i2 / 3) & 3; size_t j = 1; for (size_t w = x; !(w & 1); w >>= 1, j <<= 1) {} // Now j is not the number of the disk to move, // it contains the single bit to be moved: p[fr] &= ~j; p[to] |= j; } // Show the current configuration of pegs. foreach (immutable size_t k; TypeTuple!(0, 1, 2)) { "\n|".printf; size_t j = 1 << n; foreach_reverse (immutable size_t w; 1 .. n + 1) { j >>= 1; if (j & p[k]) printf(" %zd", w); } } '\n'.putchar; } } main() { moveit(from,to) { print("move ${from} ---> ${to}"); } hanoi(height,toPole,fromPole,usePole) { if (height>0) { hanoi(height-1,usePole,fromPole,toPole); moveit(fromPole,toPole); hanoi(height-1,toPole,usePole,fromPole); } } hanoi(3,3,1,2); } main() { String say(String from, String to) => "$from ---> $to"; hanoi(int height, int toPole, int fromPole, int usePole) { if (height > 0) { hanoi(height - 1, usePole, fromPole, toPole); print(say(fromPole.toString(), toPole.toString())); hanoi(height - 1, toPole, usePole, fromPole); } } hanoi(3, 3, 1, 2); } [ # move(from, to) n # print from [ --> ]n # print " --> " p # print to\n sw # p doesn't pop, so get rid of the value ]sm [ # init(n) sw # tuck n away temporarily 9 # sentinel as bottom of stack lw # bring n back 1 # "from" tower's label 3 # "to" tower's label 0 # processed marker ]si [ # Move() lt # push to lf # push from lmx # call move(from, to) ]sM [ # code block ln # push n lf # push from lt # push to 1 # push processed marker 1 ln # push n 1 # push 1 - # n - 1 lf # push from ll # push left 0 # push processed marker 0 ]sd [ # code block ln # push n 1 # push 1 - # n - 1 ll # push left lt # push to 0 # push processed marker 0 ]se [ # code block ln 1 =M ln 1 !=d ]sx [ # code block lMx lex ]sy [ # quit() q # exit the program ]sq [ # run() d 9 =q # if stack empty, quit() sp # processed st # to sf # from sn # n 6 # lf # - # lt # - # 6 - from - to sl # lp 0 =x # lp 0 !=y # lrx # loop ]sr 5lix # init(n) lrx # run() def move(out, n, fromPeg, toPeg, viaPeg) { if (n.aboveZero()) { move(out, n.previous(), fromPeg, viaPeg, toPeg) out.println(`Move disk $n from $fromPeg to $toPeg.`) move(out, n.previous(), viaPeg, toPeg, fromPeg) } } move(stdout, 4, def left {}, def right {}, def middle {}) class APPLICATION create make feature {NONE} -- Initialization make do move (4, "A", "B", "C") end feature -- Towers of Hanoi move (n: INTEGER; frm, to, via: STRING) require n > 0 do if n = 1 then print ("Move disk from pole " + frm + " to pole " + to + "%N") else move (n - 1, frm, via, to) move (1, frm, to, via) move (n - 1, via, to, frm) end end end open monad io :::IO //Functional approach hanoi 0 _ _ _ = [] hanoi n a b c = hanoi (n - 1) a c b ++ [(a,b)] ++ hanoi (n - 1) c b a hanoiIO n = mapM_ f $ hanoi n 1 2 3 where f (x,y) = putStrLn $ "Move " ++ show x ++ " to " ++ show y //Imperative approach using IO monad hanoiM n = hanoiM' n 1 2 3 where hanoiM' 0 _ _ _ = return () hanoiM' n a b c = do hanoiM' (n - 1) a c b putStrLn $ "Move " ++ show a ++ " to " ++ show b hanoiM' (n - 1) c b a defmodule RC do def hanoi(n) when 0 io:format("Move from ~p to ~p~n", [F, T]); move(N, F, T, V) -> move(N-1, F, V, T), move(1 , F, T, V), move(N-1, V, T, F). !----------------------------------------------------------- ! HANOI.R : solve tower of Hanoi puzzle using a recursive ! modified algorithm. !----------------------------------------------------------- PROGRAM HANOI !$INTEGER !VAR I,J,MOSSE,NUMBER PROCEDURE PRINTMOVE LOCAL SOURCE$,DEST$ MOSSE=MOSSE+1 CASE I OF 1-> SOURCE$="Left" END -> 2-> SOURCE$="Center" END -> 3-> SOURCE$="Right" END -> END CASE CASE J OF 1-> DEST$="Left" END -> 2-> DEST$="Center" END -> 3-> DEST$="Right" END -> END CASE PRINT("I move a disk from ";SOURCE$;" to ";DEST$) END PROCEDURE PROCEDURE MOVE IF NUMBER<>0 THEN NUMBER=NUMBER-1 J=6-I-J MOVE J=6-I-J PRINTMOVE I=6-I-J MOVE I=6-I-J NUMBER=NUMBER+1 END IF END PROCEDURE BEGIN MAXNUM=12 MOSSE=0 PRINT(CHR$(12);TAB(25);"--- TOWERS OF HANOI ---") REPEAT PRINT("Number of disks ";) INPUT(NUMBER) UNTIL NUMBER>1 AND NUMBER<=MAXNUM PRINT PRINT("For ";NUMBER;"disks the total number of moves is";2^NUMBER-1) I=1 ! number of source pole J=3 ! number of destination pole MOVE END PROGRAM #light let rec hanoi num start finish = match num with | 0 -> [ ] | _ -> let temp = (6 - start - finish) (hanoi (num-1) start temp) @ [ start, finish ] @ (hanoi (num-1) temp finish) [] let main args = (hanoi 4 1 2) |> List.iter (fun pair -> match pair with | a, b -> printf "Move disc from %A to %A\n" a b) 0 ["Move disk from "$!\" to "$!\" "]p: { to from } [n;0>[n;1-n: @\ h;! @\ p;! \@ h;! \@ n;1+n:]?]h: { via to from } 4n:["right"]["middle"]["left"]h;!%%% USING: formatting kernel locals math ; IN: rosettacode.hanoi : move ( from to -- ) "%d->%d\n" printf ; :: hanoi ( n from to other -- ) n 0 > [ n 1 - from other to hanoi from to move n 1 - other to from hanoi ] when ; CREATE peg1 ," left " CREATE peg2 ," middle " CREATE peg3 ," right " : .$ COUNT TYPE ; : MOVE-DISK LOCALS| via to from n | n 1 = IF CR ." Move disk from " from .$ ." to " to .$ ELSE n 1- from via to RECURSE 1 from to via RECURSE n 1- via to from RECURSE THEN ; : left ." left" ; : right ." right" ; : middle ." middle" ; : move-disk ( v t f n -- v t f ) dup 0= if drop exit then 1- >R rot swap R@ ( t v f n-1 ) recurse rot swap 2dup cr ." Move disk from " execute ." to " execute swap rot R> ( f t v n-1 ) recurse swap rot ; : hanoi ( n -- ) 1 max >R ['] right ['] middle ['] left R> move-disk drop drop drop ; PROGRAM TOWER CALL Move(4, 1, 2, 3) CONTAINS RECURSIVE SUBROUTINE Move(ndisks, from, to, via) INTEGER, INTENT (IN) :: ndisks, from, to, via IF (ndisks == 1) THEN WRITE(*, "(A,I1,A,I1)") "Move disk from pole ", from, " to pole ", to ELSE CALL Move(ndisks-1, from, via, to) CALL Move(1, from, to, via) CALL Move(ndisks-1, via, to, from) END IF END SUBROUTINE Move END PROGRAM TOWER Hanoi := function(n) local move; move := function(n, a, b, c) # from, through, to if n = 1 then Print(a, " -> ", c, "\n"); else move(n - 1, a, c, b); move(1, a, b, c); move(n - 1, b, a, c); fi; end; move(n, "A", "B", "C"); end; include "ConsoleWindow" void local fn move( n as long, fromPeg as long, toPeg as long, viaPeg as long ) if n > 0 fn move( n-1, fromPeg, viaPeg, toPeg ) print "Move disk from "; fromPeg; " to "; toPeg fn move( n-1, viaPeg, toPeg, fromPeg ) end if end fn fn move( 4, 1, 2, 3 ) print print "Towers of Hanoi puzzle solved." end package main import "fmt" // a towers of hanoi solver just has one method, play type solver interface { play(int) } func main() { var t solver // declare variable of solver type t = new(towers) // type towers must satisfy solver interface t.play(4) } // towers is example of type satisfying solver interface type towers struct { // an empty struct. some other solver might fill this with some // data representation, maybe for algorithm validation, or maybe for // visualization. } // play is sole method required to implement solver type func (t *towers) play(n int) { // drive recursive solution, per task description t.moveN(n, 1, 2, 3) } // recursive algorithm func (t *towers) moveN(n, from, to, via int) { if n > 0 { t.moveN(n-1, from, via, to) t.move1(from, to) t.moveN(n-1, via, to, from) } } // example function prints actions to screen. // enhance with validation or visualization as needed. func (t *towers) move1(from, to int) { fmt.Println("move disk from rod", from, "to rod", to) } package main import "fmt" func main() { move(3, "A", "B", "C") } func move(n uint64, a, b, c string) { if n > 0 { move(n-1, a, c, b) fmt.Println("Move disk from " + a + " to " + c) move(n-1, b, a, c) } } def tail = { list, n -> def m = list.size(); list[([m - n, 0].max()).. } def check = { it -> } def moveRing = { from, to -> to << from.pop(); report(); check(to) } def moveStack moveStack = { from, to, using = STACK.values().find { !(it.is(from) || it.is(to)) } -> if (!from) return def n = from.size() moveStack(tail(from, n-1), using, to) moveRing(from, to) moveStack(tail(using, n-1), to, from) } enum Ring { S('°'), M('o'), L('O'), XL('( )'); private sym private Ring(sym) { this.sym=sym } String toString() { sym } } report = { STACK.each { k, v -> println "${k}: ${v}" }; println() } check = { to -> assert to == ([] + to).sort().reverse() } Ring.values().reverseEach { STACK.A << it } report() check(STACK.A) moveStack(STACK.A, STACK.C) hanoi :: Integer -> a -> a -> a -> [(a, a)] hanoi 0 _ _ _ = [] hanoi n a b c = hanoi (n-1) a c b ++ [(a,b)] ++ hanoi (n-1) c b a hanoiIO n = mapM_ f $ hanoi n 1 2 3 where f (x,y) = putStrLn $ "Move " ++ show x ++ " to " ++ show y hanoiM :: Integer -> IO () hanoiM n = hanoiM' n 1 2 3 where hanoiM' 0 _ _ _ = return () hanoiM' n a b c = do hanoiM' (n-1) a c b putStrLn $ "Move " ++ show a ++ " to " ++ show b hanoiM' (n-1) c b a procedure main(arglist) hanoi(arglist[1]) | stop("Usage: hanoi n\n\rWhere n is the number of disks to move.") end #procedure hanoi(n:integer, needle1:1, needle2:2) # unicon shorthand for icon code 1,2,3 below procedure hanoi(n, needle1, needle2) #: solve towers of hanoi by moving n disks from needle 1 to needle2 via other local other n := integer(0 < n) | runerr(n,101) # 1 ensure integer (this also ensures it's positive too) /needle1 := 1 # 2 default /needle2 := 2 # 3 default if n = 1 then write("Move disk from ", needle1, " to ", needle2) else { other := 6 - needle1 - needle2 # clever but somewhat un-iconish way to find other hanoi(n-1, needle1, other) write("Move disk from ", needle1, " to ", needle2) hanoi(n-1, other, needle2) } return end Hanoi is a room. A post is a kind of supporter. A post is always fixed in place. The left post, the middle post, and the right post are posts in Hanoi. A disk is a kind of supporter. The red disk is a disk on the left post. The orange disk is a disk on the red disk. The yellow disk is a disk on the orange disk. The green disk is a disk on the yellow disk. Definition: a disk is topmost if nothing is on it. When play begins: move 4 disks from the left post to the right post via the middle post. To move (N - number) disk/disks from (FP - post) to (TP - post) via (VP - post): if N > 0: move N - 1 disks from FP to VP via TP; say "Moving a disk from [FP] to [TP]..."; let D be a random topmost disk enclosed by FP; if a topmost disk (called TD) is enclosed by TP, now D is on TD; otherwise now D is on TP; move N - 1 disks from VP to TP via FP. hanoi := method(n, from, to, via, if (n == 1) then ( writeln("Move from ", from, " to ", to) ) else ( hanoi(n - 1, from, via, to ) hanoi(1 , from, to , via ) hanoi(n - 1, via , to , from) ) ) = method(n, f, u, t, if(n < 2, "#{f} --> #{t}" println, H(n - 1, f, t, u) "#{f} --> #{t}" println H(n - 1, u, f, t) ) ) hanoi = method(n, H(n, 1, 2, 3) ) H =: i.@,&2 ` (({&0 2 1,0 2,{&1 0 2)@$:@<:) @. * NB. tacit using anonymous recursion H1=: monad define NB. explicit equivalent of H if. y do. ({&0 2 1 , 0 2 , {&1 0 2) H1 y-1 else. i.0 2 end. ) hanoi=: monad define moves=. H y disks=. $~` ((],[,]) $:@<:) @.* y ('move disk ';' from peg ';' to peg ');@,."1 ":&.>disks,.1+moves ) public void move(int n, int from, int to, int via) { if (n == 1) { System.out.println("Move disk from pole " + from + " to pole " + to); } else { move(n - 1, from, via, to); move(1, from, to, via); move(n - 1, via, to, from); } } function move(n, a, b, c) { if (n > 0) { move(n-1, a, c, b); console.log("Move disk from " + a + " to " + c); move(n-1, b, a, c); } } move(4, "A", "B", "C"); (function () { // hanoi :: n -> s -> s -> s -> [[s, s]] function hanoi(n, a, b, c) { return n ? hanoi(n - 1, a, c, b).concat( [[a, b]] ).concat(hanoi(n - 1, c, b, a)) : []; } return hanoi(3, 'left', 'right', 'mid') .map(function (d) { return d[0] + ' -> ' + d[1]; }); })(); DEFINE hanoi == [[rolldown] infra] dip [ [ [null] [pop pop] ] [ [dup2 [[rotate] infra] dip pred] [ [dup rest put] dip [[swap] infra] dip pred ] [] ] ] condnestrec. # n is the number of disks to move from From to To def move(n; From; To; Via): if n > 0 then # move all but the largest at From to Via (according to the rules): move(n-1; From; Via; To), # ... so the largest disk at From is now free to move to its final destination: "Move disk from \(From) to \(To)", # Move the remaining disks at Via to To: move(n-1; Via; To; From) else empty end; h:{[n;a;b;c]if[n>0;_f[n-1;a;c;b];`0:,//$($n,":",$a,"->",$b,"\n");_f[n-1;c;b;a]]} h[4;1;2;3] #!/usr/bin/lasso9 define towermove( disks::integer, a,b,c ) => { if(#disks > 0) => { towermove(#disks - 1, #a, #c, #b ) stdoutnl("Move disk from " + #a + " to " + #c) towermove(#disks - 1, #b, #a, #c ) } } towermove((integer($argv -> second || 3)), "A", "B", "C") source$ ="A" via$ ="B" target$ ="C" call hanoi 4, source$, target$, via$ ' ie call procedure to move legally 4 disks from peg A to peg C via peg B wait sub hanoi numDisks, source$, target$, via$ if numDisks =0 then exit sub else call hanoi numDisks -1, source$, via$, target$ print " Move disk "; numDisks; " from peg "; source$; " to peg "; target$ call hanoi numDisks -1, via$, target$, source$ end if end sub end to move :n :from :to :via if :n = 0 [stop] move :n-1 :from :via :to (print [Move disk from] :from [to] :to) move :n-1 :via :to :from end move 4 "left "middle "right :- object(hanoi). :- public(run/1). :- mode(run(+integer), one). :- info(run/1, [ comment is 'Solves the towers of Hanoi problem for the specified number of disks.', argnames is ['Disks']]). run(Disks) :- move(Disks, left, middle, right). move(1, Left, _, Right):- !, report(Left, Right). move(Disks, Left, Aux, Right):- Disks2 is Disks - 1, move(Disks2, Left, Right, Aux), report(Left, Right), move(Disks2, Aux, Left, Right). report(Pole1, Pole2):- write('Move a disk from '), writeq(Pole1), write(' to '), writeq(Pole2), write('.'), nl. :- end_object. HAI HOW DUZ I HANOI YR N AN YR SRC AN YR DST AN YR VIA BTW VISIBLE SMOOSH "HANOI N=" N " SRC=" SRC " DST=" DST " VIA=" VIA MKAY BOTH SAEM N AN 0, O RLY? YA RLY BTW VISIBLE "Done." GTFO NO WAI I HAS A LOWER ITZ DIFF OF N AN 1 HANOI DST VIA SRC LOWER VISIBLE SMOOSH "Move disc " N " from " SRC ... " to " DST MKAY HANOI SRC DST VIA LOWER OIC IF U SAY SO HANOI 2 3 1 4 BTW requires reversed arguments? KTHXBYE function move(n, src, dst, via) if n > 0 then move(n - 1, src, via, dst) print(src, 'to', dst) move(n - 1, via, dst, src) end end move(4, 1, 2, 3) Hanoi[0, from_, to_, via_] := Null Hanoi[n_Integer, from_, to_, via_] := (Hanoi[n-1, from, via, to]; Print["Move disk from pole ", from, " to ", to, "."]; Hanoi[n-1, via, from, to]) function towerOfHanoi(n,A,C,B) if (n~=0) towerOfHanoi(n-1,A,B,C); disp(sprintf('Move plate %d from tower %d to tower %d',[n A C])); towerOfHanoi(n-1,B,C,A); end end MODULE Hanoi EXPORTS Main; FROM IO IMPORT Put; FROM Fmt IMPORT Int; PROCEDURE doHanoi(n, from, to, using: INTEGER) = BEGIN IF n > 0 THEN doHanoi(n - 1, from, using, to); Put("move " & Int(from) & " --> " & Int(to) & "\n"); doHanoi(n - 1, using, to, from); END; END doHanoi; BEGIN doHanoi(4, 1, 2, 3); END Hanoi. def move(n, fromPeg, toPeg, viaPeg): if (n > 0): move(n.previous(), fromPeg, viaPeg, toPeg) traceln(`Move disk $n from $fromPeg to $toPeg`) move(n.previous(), viaPeg, toPeg, fromPeg) move(3, "left", "right", "middle")