Find limit of recursion

From Rosetta Code
Task
Find limit of recursion
You are encouraged to solve this task according to the task description, using any language you may know.
Find limit of recursion is part of Short Circuit's Console Program Basics selection.
Task

Find the limit of recursion.

6502 Assembly

The 6502's hardware stack isn't like other processors. First, it is fixed at the $0100-$01FF address range. The stack pointer is an 8-bit value, and assumes that the stack is always between $0100-$01FF. If the stack were to reach $01, and another JSR is executed, the stack would underflow to $FE, and the bottom of the stack would get clobbered. Since each JSR pushes a 2-byte return address onto the stack, the hardware limit of recursion is 128 calls.

Reading the current stack pointer is unreliable, as there is no requirement that the stack be "aligned" in any way. Unlike the 8086 and Z80, which require all pushes/pops to be exactly two bytes, the 6502's stack will likely contain both 1 byte registers and 2 byte return addresses. It's much easier to use a stack canary. Pick a value that is unlikely to be used in your program.

;beginning of your program
lda #$BE
sta $0100
lda #$EF
sta $0101

ldx #$ff
txs      ;stack pointer is set to $FF


;later...

lda $0100 ;if this no longer equals $BE the stack has overflowed
cmp #$BE
bne StackHasOverflowed

8080 Assembly

The 8080 was the first Intel processor to support a stack in RAM. (Its predecessor, the 8008, had an on-die call stack that was limited to 7 levels.) This means it was the first one on which recursive calls could be somewhat practical. It also set the convention that the machine stack grows downward into memory (i.e., the topmost item on the stack is one word below the second one, etc.), which is still true on modern Intel processors.

However, it has no support for any kind of memory protection. If the stack grows too large, it will simply overwrite other data or code, and the program will crash. This means it is up to the programmer to take care that this does not happen. Below are two ways of finding out the maximum recursion limit without crashing the program. (Note that they will give slightly different answers on the same system, as one program is slightly bigger than the other, leaving a little less room for the stack.)

Using a stack guard

One way of doing this is by using a stack guard (also known as a stack sentinel). The technique is to store a word of data just beyond the last byte of memory that the program wants to use. When you do a recursive call, you first check if it is still intact. If it isn't, the next call will overwrite something important, so in that case, the stack is full. This way, a stack overflow can be caught at run-time, at the cost of some overhead per call.

	org	100h
	lxi	b,0		; BC holds the amount of calls
	call	recur		; Call the recursive routine
	;;;	BC now holds the maximum amount of recursive calls one
	;;;	can make, and the stack is back to the beginning.
	;;;	Print the value in BC to the console. The stack is freed by ret
	;;;	so push and pop can be used.
	;;;	Make number into ASCII string
	lxi	h,num
	push	h
	mov	h,b
	mov	l,c
	lxi	b,-10
dgt:	lxi	d,-1
clcdgt:	inx	d
	dad	b
	jc	clcdgt
	mov	a,l
	adi	10+'0'
	xthl
	dcx	h
	mov	m,a
	xthl
	xchg
	mov	a,h
	ora	l
	jnz	dgt
	;;;	Use CP/M routine to print the string
	pop	d
	mvi	c,9
	call 	5
	rst	0
	;;;	Recursive routine
recur:	inx	b		; Count the call
	lxi	d,-GUARD	; See if the guard is intact (stack not full)
	lhld	guard		; (subtract the original value from the
	dad	d		; current one)
	mov	a,h		; If so, the answer should be zero
	ora	l
	cz	recur		; If it is, do another recursive call
	ret			; Return
	;;;	Placeholder for numeric output
	db	'00000'
num:	db	'$'
	;;;	The program doesn't need any memory after this location,
	;;;	so all memory beyond here is free for use by the stack.
	;;;	If the guard is overwritten, the stack has overflowed.
GUARD:	equ	$+2		; Make sure it is not a valid return address
guard:	dw	GUARD
Output:
27034

(Value will differ depending on system, CP/M version, memory size, etc.)


Calculating the value

If all you need to know is how much room there is beforehand, it's possible to just calculate the value. The 8080 processor decides where the stack is depending on the SP (stack pointer) register, which always points to the location of the topmost stack item (or, if the stack is considered 'empty', it is just outside the stack).

Therefore, if you take the address of the highest byte of memory that your program is actually using, and subtract this from SP, you get the amount of free stack memory, in bytes. Because a stack item is two bytes (addresses are 16 bits), if you then divide it by 2, you get the maximum amount of calls you can make before the stack is full (and would overwrite your program).

	org	100h
	lxi	h,-top	; Subtract highest used location from stack pointer
	dad	sp	
	xra	a	; This gives bytes, but a call takes two bytes;
	ora	h	; so HL should be divided by two to give the actual
	rar		; number.
	mov	h,a
	mov	a,l
	rar
	mov	l,a
	;;;	The number of free stack words is now in HL, output it
	lxi	d,num
	push	d
	lxi	b,-10
dgt:	lxi	d,-1
clcdgt:	inx	d
	dad	b
	jc	clcdgt
	mov	a,l
	adi	10+'0'
	xthl
	dcx	h
	mov	m,a
	xthl
	xchg
	mov	a,h
	ora	l
	jnz	dgt
	;;;	Use CP/M routine to print the string
	pop	d
	mvi	c,9
	call 	5
	rst	0
	;;;	Placeholder for numeric output
	db	'00000'
num:	db	'$'	
	;;;	The program does not need any memory beyond this point.
	;;;	This means anything from this place up to SP is free for the
	;;;	stack.
top:	equ	$
Output:
27039

(Value will differ depending on system, CP/M version, memory size, etc.)

ACL2

(defun recursion-limit (x)
   (if (zp x)
       0
       (prog2$ (cw "~x0~%" x)
               (1+ (recursion-limit (1+ x))))))
Output:
(trimmed)
87195
87196
87197
87198
87199
87200
87201

***********************************************
************ ABORTING from raw Lisp ***********
Error:  Stack overflow on value stack.
***********************************************

Ada

with Ada.Text_IO;  use Ada.Text_IO;

procedure Test_Recursion_Depth is
   function Recursion (Depth : Positive) return Positive is
   begin
      return Recursion (Depth + 1);
   exception
      when Storage_Error =>
         return Depth;
   end Recursion;
begin
   Put_Line ("Recursion depth on this system is" & Integer'Image (Recursion (1)));
end Test_Recursion_Depth;

Note that unlike some solutions in other languages this one does not crash (though usefulness of this task is doubtful).

In Ada Storage_Error exception is propagated when there is no free memory to accomplish the requested action. In particular it is propagated upon stack overflow within the task where this occurs. Storage_Error can be handled without termination of the task. In the solution the function Recursion calls itself or else catches Storage_Error indicating stack overflow.

Note that this technique requires some care, because there must be enough stack space for the handler to work. In this case it works because the handler just return the current call depth. In real-life Storage_Error is usually fatal.

Output:
Recursion depth on this system is 524091

ALGOL 68

The depth of recursion in Algol 68 proper is unlimited. Particular implementations will reach a limit, if only through exhaustion of storage and/or address space and/or time before power failure. If not time limited, the depth reached depends very much on what the recursive routine needs to store on the stack, including local variables if any. The simplest recursive Algol68 program is:

PROC recurse = VOID : recurse; recurse

This one-liner running under Algol68 Genie and 64-bit Linux reaches a depth of 3535 with the shell's default stack size of 8Mbytes and 28672 when set to 64Mbytes, as shown by the following output. From this we can deduce that Genie does not implement tail recursion. The --trace option to a68g prints a stack trace when the program crashes; the first two commands indicate the format of the trace, the third counts the depth of recursion with the default stack size and the fourth shows the result of octupling the size of the stack.

Output:
pcl@anubis ~/a68/Rosetta $ a68g --trace Recurse.a68 | head
genie: frame stack 6144k, expression stack 2048k, heap 49152k, handles 8192k
      BEGIN MODE DOUBLE = LONG REAL, QUAD = LONG LONG REAL;
      -                                                    
1     PROC recurse = VOID : recurse; recurse
      -                                     
genie_unit
1     PROC recurse = VOID : recurse; recurse
                                     -      
genie_unit
1     PROC recurse = VOID : recurse; recurse
pcl@anubis ~/a68/Rosetta $ a68g --trace Recurse.a68 | tail
1     PROC recurse = VOID : recurse; recurse
                            -               
genie_unit
1     PROC recurse = VOID : recurse; recurse
                            -               
genie_unit
1     PROC recurse = VOID : recurse; recurse
                     1                      
a68g: runtime error: 1: stack overflow (detected in particular-program).
Genie finished in 0.19 seconds
pcl@anubis ~/a68/Rosetta $ a68g --trace Recurse.a68 |  grep recurse | wc
   3535   28280  159075
pcl@anubis ~/a68/Rosetta $ prlimit --stack=67108864 a68g --trace Recurse.a68 | grep recurse | wc
  28672  229376 1290240
pcl@anubis ~/a68/Rosetta $ 

AppleScript

Test 1

A basic test for Applescript, which has a notoriously shallow recursion stack.

-- recursionDepth :: () -> IO String
on recursionDepth()
    script go
        on |λ|(i)
            try
                |λ|(1 + i)
            on error
                "Recursion limit encountered at " & i
            end try
        end |λ|
    end script
    
    go's |λ|(0)
end recursionDepth

on run
    
    recursionDepth()
    
end run
Output:
"Recursion limit encountered at 502"

Test 2

We get a fractionally higher (and arguably purer) result by deriving the highest Church Numeral (Church-encoded integer) that can be represented using AppleScript:

-- HIGHEST CHURCH NUMERAL REPRESENTABLE IN APPLESCRIPT ?

-- (This should be a good proxy for recursion depth)

on run
    script unrepresentable
        on |λ|(x)
            try
                churchFromInt(x)
                return false
            on error
                return true
            end try
            x > 10
        end |λ|
    end script
    
    "The highest Church-encoded integer representable in Applescript is " & ¬
        (|until|(unrepresentable, my succ, 0) - 1)
end run

-- CHURCH NUMERALS ------------------------------------------------------

-- chZero :: (a -> a) -> a -> a
on chZero(f)
    script
        on |λ|(x)
            x
        end |λ|
    end script
end chZero

-- chSucc :: ((a -> a) -> a -> a) -> (a -> a) -> a -> a
on chSucc(n)
    script
        on |λ|(f)
            script
                property mf : mReturn(f)'s |λ|
                on |λ|(x)
                    mf(mReturn(n)'s |λ|(mf)'s |λ|(x))
                end |λ|
            end script
        end |λ|
    end script
end chSucc

-- churchFromInt :: Int -> (a -> a) -> a -> a
on churchFromInt(x)
    script go
        on |λ|(i)
            if 0 < i then
                chSucc(|λ|(i - 1))
            else
                chZero
            end if
        end |λ|
    end script
    go's |λ|(x)
end churchFromInt

-- intFromChurch :: ((Int -> Int) -> Int -> Int) -> Int
on intFromChurch(cn)
    mReturn(cn)'s |λ|(my succ)'s |λ|(0)
end intFromChurch


-- GENERIC FUNCTIONS ----------------------------------------

-- until :: (a -> Bool) -> (a -> a) -> a -> a
on |until|(p, f, x)
    set v to x
    set mp to mReturn(p)
    set mf to mReturn(f)
    repeat until mp's |λ|(v)
        set v to mf's |λ|(v)
    end repeat
end |until|

-- Lift 2nd class handler function into 1st class script wrapper 
-- mReturn :: First-class m => (a -> b) -> m (a -> b)
on mReturn(f)
    if class of f is script then
        f
    else
        script
            property |λ| : f
        end script
    end if
end mReturn

-- succ :: Enum a => a -> a
on succ(x)
    1 + x
end succ
Output:
"The highest Church-encoded integer representable in Applescript is 571"

Test 3

The recursion limit with a fixed-length stack depends not only on the size of the stack, but on how many local variables (including parameter variables) and return addresses (including those for 'try' statements) are stored at each level. Also, of course, on where you start counting, since recursion's unlikely to begin with an empty stack in real-life situations and you may or may not regard the top call to a recursive handler as part of the recursion.

The recursive handler in the first AppleScript test above is entered with the return addresses from the 'run' and 'recursionDepth' handlers (or pointers thereto) already on the stack along with pointers to the local 'go' value and the passed 'i'. Each successive call stacks the return addresses for the 'try' statement and the handler itself along with a new 'i'. The final result of 502 is the number of times the recursive handler successfully calls itself and is probably a reasonably indicative real-world figure.

Testing with no local variables and with an external 'try' statement, the maximum recursion depth possible appears to be 733. (732 if the code below's run as an applet instead of in an editor or from the system script menu.) So, depending on what a script actually does, the limit can be anything between <502 and 733. In practice, it's very difficult for well written AppleScript code to run out of stack.

global i

on recursion()
    set i to i + 1
    recursion()
end recursion

on run
    set i to -1
    try
        recursion()
    on error
        "Recursion limit encountered at " & i
        -- display dialog result -- Uncomment to see the result if running as an applet.
    end try
end run
Output:
"Recursion limit encountered at 733"

Arturo

recurse: function [x][
    print x
    recurse x+1
]

recurse 0
Output:
...
...
...
10912
10913
10914
[2]    67851 segmentation fault  arturo find\ limit\ of\ recursion.art

AutoHotkey

Recurse(0)

Recurse(x)
{
  TrayTip, Number, %x%
  Recurse(x+1)
}

Last visible number is 827.

AutoIt

;AutoIt Version: 3.2.10.0
$depth=0
recurse($depth)
Func recurse($depth)
   ConsoleWrite($depth&@CRLF)
   Return recurse($depth+1)
EndFunc

Last value of $depth is 5099 before error. Error: Recursion level has been exceeded - AutoIt will quit to prevent stack overflow.

AWK

# syntax: GAWK -f FIND_LIMIT_OF_RECURSION.AWK
#
# version             depth  messages
# ------------------  -----  --------
# GAWK 3.1.4           2892  none
# XML GAWK 3.1.4       3026  none
# GAWK 4.0          >999999
# MAWK 1.3.3           4976  A stack overflow was encountered at
#                            address 0x7c91224e.
# TAWK-DOS AWK 5.0c     357  stack overflow
# TAWK-WIN AWKW 5.0c   2477  awk stack overflow
# NAWK 20100523        4351  Segmentation fault (core dumped)
#
BEGIN {
    x()
    print("done")
}
function x() {
    print(++n)
    if (n > 999999) { return }
    x()
}

Axe

Warning: running this program will cause you to have to clear your RAM. You will lose any data stored in RAM.

In Axe 1.2.2 on a TI-84 Plus Silver Edition, the last line this prints before hanging is 12520. This should be independent of any arguments passed since they are not stored on the stack.

RECURSE(1)
Lbl RECURSE
.Optionally, limit the number of times the argument is printed
Disp r₁▶Dec,i
RECURSE(r₁+1)

BASIC

Applesoft BASIC

Each GOSUB consumes 6 bytes of stack space and when more than 25 levels have been reached and an ?OUT OF MEMORY ERROR message is displayed.

 100  PRINT "RECURSION DEPTH"
 110  PRINT D" ";
 120  LET D = D + 1
 130  GOSUB 110"RECURSION
Output:
RECURSION DEPTH
0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25
?OUT OF MEMORY ERROR IN 120

BaCon

Utterly dependent on the stack size and RAM available to the process.

' Recursion limit
FUNCTION recurse(i)
    PRINT i
    extraneous = recurse(i+1)
    RETURN 0
END FUNCTION

extraneous = recurse(0)
Output:
prompt$ ./recursion-limit
0
1
2
...
261881
261882
261883
Segmentation fault

BASIC256

function Recursion(i)
	print i
	ext = Recursion(i + 1)
	return False
end function

ext = Recursion(0)

Chipmunk Basic

Works with: Chipmunk Basic version 3.6.4
10 sub recursion(n)
20   print n
30   recursion(1 + n)
40 end sub
50 recursion(0)
60 end

FreeBASIC

sub sisyphus( n as ulongint )
    print n
    sisyphus( 1 + n )
end sub
sisyphus(0)
Output:
0
1
2
...
261785
261786
261787
Segmentation fault (core dumped)

Gambas

Public Sub Main()  
  
  Recursion(0)
  
End

Sub Recursion(n As Long) 

  Print n 
  Recursion(1 + n) 

End Sub

GW-BASIC

10 N#=0
20 N# = N# + 1
30 LOCATE 1,1:PRINT N#
40 GOSUB 20
Output:
33
Out of memory in 20.

Minimal BASIC

10 LET N = 0
20 LET N = N + 1
30 PRINT N
40 GOSUB 20
50 END
Output:
 257
40: error: stack overflow

MSX Basic

Works with: MSX BASIC version any

The GW BASIC solution works without any changes.>

QBasic

Works with: QBasic version 1.1
FUNCTION Recursion (i)
PRINT i
ext = Recursion(i + 1)
Recursion = 0
END FUNCTION

ext = Recursion(0)

Quite BASIC

10 LET N = 0
20 LET N = N + 1
30 PRINT N
40 GOSUB 20

Sinclair ZX81 BASIC

The only limit is the available memory.

10 LET D=0
20 GOSUB 30
30 PRINT AT 0,0;D
40 LET D=D+1
50 GOSUB 30
Output:

Run with 1k of RAM:

345

4/30

(The error code means "out of memory attempting to execute line 30".)

Tiny BASIC

10 LET N = -32767
20 LET M = 0
30 LET N = N + 1
40 IF N = 32767 THEN LET M = M + 1
50 IF N = 32767 THEN PRINT M," x 2^16"
60 IF N = 32767 THEN LET N = -N
70 GOSUB 30
Output:
1 x 2^16
2 x 2^16
3 x 2^16
4 x 2^16
5 x 2^16
...
1645 x 2^16
1646 x 2^16

I don't recommend actually running this; it will crash the computer.

True BASIC

Works with: BASIC256
Works with: QBasic
FUNCTION Recursion (i)
    PRINT i
    LET ext = Recursion(i + 1)
    LET Recursion = 0
END FUNCTION

LET ext = Recursion(0)
END

XBasic

Works with: Windows XBasic
PROGRAM  "Find limit of recursion"

DECLARE FUNCTION  Entry ()
DECLARE FUNCTION  Recursion(n)

FUNCTION  Entry ()
    Recursion (0)
END FUNCTION

FUNCTION  Recursion (i)
    PRINT i
    Recursion (1 + i)

END FUNCTION
END PROGRAM

Yabasic

sub Recursion(i)
print i
Recursion(i + 1)
end sub

Recursion(0)

ZX Spectrum Basic

On the ZX Spectrum recursion is limited only by stack space. The program eventually fails, because the stack is so full that there is no stack space left to make the addition at line 110:

10 LET d=0: REM depth
100 PRINT AT 1,1; "Recursion depth: ";d
110 LET d=d+1
120 GO SUB 100: REM recursion
130 RETURN: REM this is never reached
200 STOP
Output:
(from a 48k Spectrum)
 Recursion depth: 13792
 4 Out of memory, 110:1

Batch File

MUNG.CMD is a commandline tool written in DOS Batch language. It finds the limit of recursion possible using CMD /C.

@echo off
set /a c=c+1
echo [Depth %c%] Mung until no good
cmd /c mung.cmd
echo [Depth %c%] No good
set /a c=c-1

Result (abbreviated):

...
[Depth 259] Mung until no good
[Depth 260] Mung until no good
[Depth 261] Mung until no good
[Depth 261] No good
[Depth 260] No good
[Depth 259] No good
...

If one uses call rather than CMD/C, the call depth is much deeper but ends abruptly and can't be trapped.

@echo off
set /a c=c+1
echo [Depth %c%] Mung until no good
call mung.cmd
echo [Depth %c%] No good
set /a c=c-1

Result (abbreviated):

1240: Mung until no good
1241: Mung until no good
******  B A T C H   R E C U R S I O N  exceeds STACK limits ******
Recursion Count=1240, Stack Usage=90 percent
******       B A T C H   PROCESSING IS   A B O R T E D      ******

You also get the exact same results when calling mung internally, as below

@echo off
set c=0
:mung
set /a c=c+1
echo [Level %c%] Mung until no good
call :mung
set /a c=c-1
echo [Level %c%] No good

Setting a limit on the recursion depth can be done like this:

@echo off
set c=0
:mung
set /a c=%1+1
if %c%==10 goto :eof
echo [Level %c%] Mung until no good
call :mung %c%
set /a c=%1-1
echo [Level %c%] No good

BBC BASIC

      PROCrecurse(1)
      END
      
      DEF PROCrecurse(depth%)
      IF depth% MOD 100 = 0 PRINT TAB(0,0) depth%;
      PROCrecurse(depth% + 1)
      ENDPROC
Output:
from BBC BASIC for Windows with default value of HIMEM
     37400
No room

Befunge

In Befunge, the limit of recursion is essentially the depth of the stack. The program below calculates that limit by repeatedly pushing values until the stack overflows. After every iteration, it writes out the count of values pushed so far, so once the stack eventually does overflow, the last value output should tell you the depth that was reached.

Most interpreters allocate their stack on the global heap, so the size of the stack will depend on available memory, and on a modern system you're likely to run out of patience long before you run out of memory. That said, there have been some interpreters with a fixed stack depth - as low as 199 even - but that isn't a common implementation choice.

1>1#:+#.:_@

BQN

Tested with the CBQN REPL on Ubuntu Linux.

   {𝕊1+•Show 𝕩}0
0
1
.
.
.
4094
Error: Stack overflow
at {𝕊1+•Show 𝕩}0

Bracmat

rec=.out$!arg&rec$(!arg+1)

Observed recursion depths:

 Windows XP command prompt: 6588
 Linux: 18276

Bracmat crashes when it tries to exceed the maximum recursion depth.

C

#include <stdio.h>

void recurse(unsigned int i)
{
  printf("%d\n", i);
  recurse(i+1); // 523756
}

int main()
{
  recurse(0);
  return 0;
}

Segmentation fault occurs when i is 523756. (This was checked debugging with gdb rather than waiting the output: the printf line for the test was commented). It must be noted that the recursion limit depends on how many parameters are passed onto the stack. E.g. adding a fake double argument to recurse, the limit is reached at i == 261803. The limit depends on the stack size and usage in the function. Even if there are no arguments, the return address for a call to a subroutine is stored on the stack (at least on x86 and many more processors), so this is consumed even if we put arguments into registers.

The following code may have some effect unexpected by the unwary:

#include <stdio.h>

char * base;
void get_diff()
{
	char x;
	if (base - &x < 200)
		printf("%p %d\n", &x, base - &x);
}

void recur()
{
	get_diff();
	recur();
}

int main()
{
	char v = 32;
	printf("pos of v: %p\n", base = &v);
	recur();
	return 0;
}

With GCC 4.5, if compiled without -O2, it segfaults quickly; if gcc -O2, crash never happens, because the optimizer noticed the tail recursion in recur() and turned it into a loop!

C#

using System;
class RecursionLimit
{
  static void Main(string[] args)
  {
    Recur(0);
  }
 
  private static void Recur(int i) 
  {
    Console.WriteLine(i);
    Recur(i + 1);
  }
}

Through debugging, the highest I achieve is 14250.

Through execution (with Mono), another user has reached 697186.

C++

#include <iostream>
 
void recurse(unsigned int i)
{
  std::cout<<i<<"\n";
  recurse(i+1);
}
 
int main()
{
  recurse(0);
}

Clojure

=> (def *stack* 0)
=> ((fn overflow [] ((def *stack* (inc *stack*))(overflow))))
java.lang.StackOverflowError (NO_SOURCE_FILE:0)
=> *stack*
10498

COBOL

Works with: OpenCOBOL
identification division.
program-id. recurse.
data division.
working-storage section.
01 depth-counter	pic 9(3).
01  install-address   	usage is procedure-pointer.
01  install-flag      	pic x comp-x value 0.
01  status-code       	pic x(2) comp-5.
01  ind               	pic s9(9) comp-5.


linkage section.
01  err-msg           	pic x(325).

procedure division.
100-main.

	set install-address to entry "300-err".
	
	call "CBL_ERROR_PROC" using install-flag
		install-address
		returning status-code.

	if status-code not = 0
		display "ERROR INSTALLING ERROR PROC"
		stop run
        end-if

 	move 0 to depth-counter.
	display 'Mung until no good.'.
	perform 200-mung.
	display 'No good.'.
	stop run.

200-mung.
	add 1 to depth-counter.
	display depth-counter.
	perform 200-mung.
300-err.
	entry "300-err" using err-msg.
	perform varying ind from 1 by 1
		until (err-msg(ind:1) = x"00") or (ind = length of err-msg)
			continue
	end-perform

	display err-msg(1:ind).

*> room for a better-than-abrupt death here.
	
	exit program.
Compiled with
cobc -free -x -g recurse.cbl
gives, after a while,
...
249
250
251
252
253
Trapped: recurse.cob:38: Stack overflow, possible PERFORM depth exceeded
recurse.cob:50: libcob: Stack overflow, possible PERFORM depth exceeded

Without stack-checking turned on (achieved with -g in this case), it gives

...
249
250
251
252
253
254
255
256
257
Attempt to reference unallocated memory (Signal SIGSEGV)
Abnormal termination - File contents may be incorrect

which suggests that -g influences the functionality of CBL_ERROR_PROC

Thanks to Brian Tiffin for his demo code on opencobol.org's forum

A more 'canonical' way of doing it

from Richard Plinston on comp.lang.cobol

Works with: OpenCOBOL
       IDENTIFICATION DIVISION.
       PROGRAM-ID.          recurse RECURSIVE.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01  Starter          PIC S9(8) VALUE 1.
       PROCEDURE DIVISION.
       Program-Recurse.
           CALL "recurse-sub" USING Starter
           STOP RUN.

       IDENTIFICATION DIVISION.
       PROGRAM-ID.          recurse-sub.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       LINKAGE SECTION.
       01  Countr                      PIC S9(8).
       PROCEDURE DIVISION USING Countr.
       Program-Recursive.
           DISPLAY Countr
           ADD 1   TO Countr
           CALL "recurse-sub" USING Countr

           EXIT PROGRAM.
       END PROGRAM recurse-sub.
       END PROGRAM recurse.
Compiled with
cobc -x -g recurse.cbl
gives
...
+00000959
+00000960
+00000961
+00000962
+00000963
+00000964
recurse.cbl:19: Attempt to reference unallocated memory (Signal SIGSEGV)
Abnormal termination - File contents may be incorrect

CoffeeScript

recurse = ( depth = 0 ) ->
    try
        recurse depth + 1
    catch exception
        depth

console.log "Recursion depth on this system is #{ do recurse }"
Output:
Example on Node.js
    Recursion depth on this system is 9668

Common Lisp

(defun recurse () (recurse))
(trace recurse)
(recurse)
Output:
This test was done with clisp under cygwin
 3056. Trace: (RECURSE)
 3057. Trace: (RECURSE)
 3058. Trace: (RECURSE)
 3059. Trace: (RECURSE)
 
 *** - Lisp stack overflow. RESET

However, for an implementation of Lisp that supports proper tail recursion, this function will not cause a stack overflow, so this method will not work.

Crystal

def recurse(counter = 0)
    puts counter
    recurse(counter + 1)
end

recurse()
Output:
...
523656
Stack overflow (e.g., infinite or very deep recursion)

D

import std.c.stdio;

void recurse(in uint i=0) {
    printf("%u ", i);
    recurse(i + 1);
}

void main() {
    recurse();
}

With the DMD compiler, using default compilation arguments, the stack overflows at 51_002.

With DMD increasing the stack size using for example -L/STACK:1500000000 the stack overflows at 75_002_026.

Using -O compilation argument DMD performs tail call optimization, and the stack doesn't overflow.

Dc

Tail recursion is optimized into iteration by GNU dc, so I designed a not tail recursive function, summing all numbers up to n:

## f(n) = (n < 1) ? n : f(n-1) + n;
[q]sg
[dSn d1[>g 1- lfx]x Ln+]sf
[ [n=]Pdn []pP lfx [--> ]P p ]sh

65400 lhx
65600 lhx

With the standard Ubuntu stack size limit 8MB I get

Output:
$ time dc t1.dc 
n=65400
--> 2138612700
n=65600
Segmentation fault (core dumped)

real    0m0.337s
user    0m0.112s
sys     0m0.008s

With larger stack size limit I get linearly greater numbers: stack size / 128.

Delphi

Works with: Delphi version 2010 (and probably all other versions)
program Project2;
{$APPTYPE CONSOLE}
uses
  SysUtils;

function Recursive(Level : Integer) : Integer;
begin
  try
    Level := Level + 1;
    Result := Recursive(Level);
  except
    on E: EStackOverflow do
      Result := Level;
  end;
end;

begin
  Writeln('Recursion Level is ', Recursive(0));
  Writeln('Press any key to Exit');
  Readln;
end.
Output:
Recursion Level is 28781

DWScript

Recursion limit is a parameter of script execution, which can be specified independently from the stack size to limit execution complexity.

var level : Integer;

procedure Recursive;
begin
   Inc(level);
   try
      Recursive;
   except
   end;
end;

Recursive;

Println('Recursion Level is ' + IntToStr(level));

Déjà Vu

This example is untested. Please check that it's correct, debug it as necessary, and remove this message.


rec-fun n:
	!. n
	rec-fun ++ n

rec-fun 0

This continues until the memory is full, so I didn't wait for it to finish. Currently, it should to to almost 3 million levels of recursion on a machine with 1 GB free. Eliminating the n should give over 10 million levels on the same machine.

E

Outside of debugging access to other vats, E programs are (ideally) not allowed to observe recursion limits, because stack unwinding at an arbitrary point can break invariants of the code that was executing at the time. In particular, consider an attacker who estimates the stack size, nearly fills up the stack to that point, then invokes the victim — If the attacker is allowed to catch our hypothetical StackOverflowException from inside the victim, then there is a good chance of the victim then being in an inconsistent state, which the attacker can then make use of.

EasyLang

proc recurse i . .
   if i mod 10 = 0
      print i
   .
   recurse i + 1
.
recurse 1
.
.
9100
InternalError: too much recursion

Elixir

same as "Erlang"

Emacs Lisp

(defun my-recurse (n)
  (my-recurse (1+ n)))
(my-recurse 1)
=>
enters debugger at (my-recurse 595),
per the default max-lisp-eval-depth 600 in Emacs 24.1

Variable max-lisp-eval-depth[1] is the maximum depth of function calls and variable max-specpdl-size[2] is the maximum depth of nested let bindings. A function call is a let of the parameters, even if there's no parameters, and so counts towards max-specpdl-size as well as max-lisp-eval-depth.

The limits can be increased with setq etc globally, or let etc temporarily. Lisp code which knows it needs deep recursion might temporarily increase the limits. Eg. regexp-opt.el. The ultimate limit is memory or C stack.

Erlang

Erlang has no recursion limit. It is tail call optimised. If the recursive call is not a tail call it is limited by available RAM. Please add what to save on the stack and how much RAM to give to Erlang and I will test that limit.

F#

A tail-recursive function will run indefinitely without problems (the integer will overflow, though).

let rec recurse n = 
  recurse (n+1)

recurse 0

The non-tail recursive function of the following example crashed with a StackOverflowException after 39958 recursive calls:

let rec recurse n = 
   printfn "%d" n
   1 + recurse (n+1)

recurse 0 |> ignore

Factor

Factor is tail-call optimized, so the following example will run without issue. In fact, Factor's iterative combinators such as map, each, and times are written in terms of tail recursion.

: recurse ( n -- n ) 1 + recurse ;

0 recurse

The following non-tail recursive word caused a call stack overflow error after 65518 recursive calls in the listener.

SYMBOL: depth

: fn ( n -- n ) depth inc 1 + fn 1 + ;

[ 0 fn ] try
depth get "Recursion depth on this system is %d.\n" printf
Output:
Call stack overflow

Type :help for debugging help.
Recursion depth on this system is 65518.

Fermat

Func Sisyphus(n)=!!n;Sisyphus(n+1).
Sisyphus(0)
Output:
0
1
2
...
41815
41816
Segmentation fault (core dumped)

Forth

: munge ( n -- n' ) 1+ recurse ;

: test   0 ['] munge catch if ." Recursion limit at depth " . then ;

test   \ Default gforth: Recursion limit at depth 3817

Or you can just ask the system:

s" return-stack-cells" environment? ( 0 | potential-depth-of-return-stack -1 )

Full TCO is problematic, but a properly tail-recursive call is easy to add to any Forth. For example, in SwiftForth:

: recur; [ last 2 cells + literal ] @ +bal postpone again ; immediate

: test dup if 1+ recur; then drop ." I gave up finding a limit!" ;

1 test

Fortran

program recursion_depth

  implicit none

  call recurse (1)

contains

  recursive subroutine recurse (i)

    implicit none
    integer, intent (in) :: i

    write (*, '(i0)') i
    call recurse (i + 1)

  end subroutine recurse

end program recursion_depth
Output:
(snipped)
208914
208915
208916
208917
208918
208919
208920
208921
208922
208923
Segmentation fault (core dumped)

GAP

The limit is around 5000 :

f := function(n)
  return f(n+1);
end;

# Now loop until an error occurs
f(0);

# Error message :
#   Entering break read-eval-print loop ...
#   you can 'quit;' to quit to outer loop, or
#   you may 'return;' to continue

n;
# 4998

# quit "brk mode" and return to GAP
quit;

This is the default GAP recursion trap, see reference manual, section 7.10. It enters "brk mode" after multiples of 5000 recursions levels. On can change this interval :

SetRecursionTrapInterval(100000);
# No limit (may crash GAP if recursion is not controlled) :
SetRecursionTrapInterval(0);

gnuplot

# Put this in a file foo.gnuplot and run as
#     gnuplot foo.gnuplot

# probe by 1 up to 1000, then by 1% increases
if (! exists("try")) { try=0 }
try=(try<1000 ? try+1 : try*1.01)

recurse(n) = (n > 0 ? recurse(n-1) : 'ok')
print "try recurse ", try
print recurse(try)
reread

Gnuplot 4.6 has a builtin STACK_DEPTH limit of 250, giving

try recurse 251
"/tmp/foo.gnuplot", line 2760: recursion depth limit exceeded

Gnuplot 4.4 and earlier has no limit except the C stack, giving a segv or whatever eventually.

Go

Go features stacks that grow as needed making the effective recursion limits relatively large.

Pre-Go 1.2 this could be all of memory and the program would grow without bounds until the system swap space was exhausted and the program was killed (either by the a run-time panic after an allocation failure or by the operating system killing the process).

Go 1.2 set a limit to the maximum amount of memory that can be used by a single goroutine stack. The initial setting is 1 GB on 64-bit systems, 250 MB on 32-bit systems. The default can be changed by SetMaxStack in the runtime/debug package. It is documented as "useful mainly for limiting the damage done by goroutines that enter an infinite recursion."

package main

import (
	"flag"
	"fmt"
	"runtime/debug"
)

func main() {
	stack := flag.Int("stack", 0, "maximum per goroutine stack size or 0 for the default")
	flag.Parse()
	if *stack > 0 {
		debug.SetMaxStack(*stack)
	}
	r(1)
}

func r(l int) {
	if l%1000 == 0 {
		fmt.Println(l)
	}
	r(l + 1)
}

Run without arguments on a 64-bit system:

Output:
[…]
4471000
4472000
4473000
runtime: goroutine stack exceeds 1000000000-byte limit
fatal error: stack overflow

runtime stack:
runtime.throw(0x5413ae)
	/usr/local/go/src/pkg/runtime/panic.c:520 +0x69
runtime.newstack()
	/usr/local/go/src/pkg/runtime/stack.c:770 +0x486
runtime.morestack()
	/usr/local/go/src/pkg/runtime/asm_amd64.s:228 +0x61

goroutine 16 [stack growth]:
main.r(0x444442)
	[…]/rosetta/stack_size/stack.go:9 fp=0xc2680380c8 sp=0xc2680380c0
main.r(0x444441)
	[…]/rosetta/stack_size/stack.go:13 +0xc5 fp=0xc268038140 sp=0xc2680380c8
main.r(0x444440)
[…]
...additional frames elided...
created by _rt0_go
	/usr/local/go/src/pkg/runtime/asm_amd64.s:97 +0x120

goroutine 19 [finalizer wait]:
runtime.park(0x412a20, 0x542ce8, 0x5420a9)
	/usr/local/go/src/pkg/runtime/proc.c:1369 +0x89
runtime.parkunlock(0x542ce8, 0x5420a9)
	/usr/local/go/src/pkg/runtime/proc.c:1385 +0x3b
runfinq()
	/usr/local/go/src/pkg/runtime/mgc0.c:2644 +0xcf
runtime.goexit()
	/usr/local/go/src/pkg/runtime/proc.c:1445
exit status 2

Run with "-stack 262144000" (to simulate the documented 250 MB limit on a 32-bit system):

Output:
[…]
1117000
1118000
runtime: goroutine stack exceeds 262144000-byte limit
fatal error: stack overflow
[…]

On a 32-bit system an int is 32 bits so the maximum value to debug.SetMaxStack is 2147483647 (nearly 2 GB). On a 64-bit system an int is usually 64 bits so the maximum value will much larger, more than the available memory. Thus setting the maximum value will either exhaust all the system memory and swap (as with pre-Go 1.2) or will result in a allocation failure and run-time panic (e.g. 32-bit systems often have more memory and swap in total than the memory accessible to a single user program due to the limits of a 32 bit address space shared with the kernel).

Note, unlike with some other systems, increasing or changing this value only changes the allocation limit. The stack still starts out very small and only grows as needed, there is no large stack pre-allocation even when using a very high limit. Also note that this is per-goroutine, each goroutine can recurse independently and approach the limit.

The above code built pre-Go 1.2 (without the then non-existent debug.SetMaxStack call) and run on a 1 GB RAM machine with 2.5 GB swap filled available RAM quickly, at a recursion depth of about 10M. It took a several minutes to exhaust swap before exiting with this trace: (as you see, at a depth of over 25M.)

[…]
25611000
25612000
25613000
25614000
throw: out of memory (FixAlloc)

runtime.throw+0x43 /home/sonia/go/src/pkg/runtime/runtime.c:102
	runtime.throw(0x80e80c8, 0x1)
runtime.FixAlloc_Alloc+0x76 /home/sonia/go/src/pkg/runtime/mfixalloc.c:43
	runtime.FixAlloc_Alloc(0x80eb558, 0x2f)
runtime.stackalloc+0xfb /home/sonia/go/src/pkg/runtime/malloc.c:326
	runtime.stackalloc(0x1000, 0x8048c44)
runtime.newstack+0x140 /home/sonia/go/src/pkg/runtime/proc.c:768
	runtime.newstack()
runtime.morestack+0x4f /home/sonia/go/src/pkg/runtime/386/asm.s:220
	runtime.morestack()
----- morestack called from goroutine 1 -----
main.r+0x1a /home/sonia/t.go:9
	main.r(0x186d801, 0x0)
main.r+0x95 /home/sonia/t.go:13
	main.r(0x186d800, 0x0)
main.r+0x95 /home/sonia/t.go:13
	main.r(0x186d7ff, 0x0)
main.r+0x95 /home/sonia/t.go:13
	main.r(0x186d7fe, 0x0)
main.r+0x95 /home/sonia/t.go:13
	main.r(0x186d7fd, 0x0)

... (more of the same stack trace omitted)


----- goroutine created by -----
_rt0_386+0xc1 /home/sonia/go/src/pkg/runtime/386/asm.s:80

goroutine 1 [2]:
runtime.entersyscall+0x6f /home/sonia/go/src/pkg/runtime/proc.c:639
	runtime.entersyscall()
syscall.Syscall+0x53 /home/sonia/go/src/pkg/syscall/asm_linux_386.s:33
	syscall.Syscall()
syscall.Write+0x5c /home/sonia/go/src/pkg/syscall/zsyscall_linux_386.go:734
	syscall.Write(0x1, 0x977e4f18, 0x9, 0x40, 0x9, ...)
os.*File·write+0x39 /home/sonia/go/src/pkg/os/file_unix.go:115
	os.*File·write(0x0, 0x0, 0x9, 0x40, 0x9, ...)
os.*File·Write+0x98 /home/sonia/go/src/pkg/os/file.go:141
	os.*File·Write(0xbffe1980, 0x8, 0x9, 0x8048cbf, 0x186d6b4, ...)
----- goroutine created by -----
_rt0_386+0xc1 /home/sonia/go/src/pkg/runtime/386/asm.s:80

Gri

In Gri 2.12.23 the total depth of command calls is limited to an internal array size cmd_being_done_LEN which is 100. There's no protection or error check against exceeding this, so the following code segfaults shortly after 100,

`Recurse'
{
    show .depth.
    .depth. = {rpn .depth. 1 +}
    Recurse
}
.depth. = 1
Recurse

Groovy

Translation of: Java

Solution:

def recurse;
recurse = {
    try {
        recurse (it + 1)
    } catch (StackOverflowError e) {
        return it
    }
}

recurse(0)
Output:
387

Haskell

import Debug.Trace (trace)

recurse :: Int -> Int
recurse n = trace (show n) recurse (succ n)

main :: IO ()
main = print $ recurse 1

Or point-free:

import Debug.Trace (trace)
import Data.Function (fix)

recurse :: Int -> Int
recurse = fix ((<*> succ) . flip (trace . show))

main :: IO ()
main = print $ recurse 1


Or, more practically, testing up to a given depth:

import Debug.Trace (trace)

testToDepth :: Int -> Int -> Int
testToDepth max n
  | n >= max = max
  | otherwise = trace (show n) testToDepth max (succ n)

main :: IO ()
main = print $ testToDepth 1000000 1
Output:
...
999987
999988
999989
999990
999991
999992
999993
999994
999995
999996
999997
999998
999999
1000000

hexiscript

fun rec n
  println n
  rec (n + 1)
endfun

rec 1

HolyC

The point at which a stack overflow occurs varies depending upon how many parameters passed onto the stack. Running the code from within the editor on a fresh boot of TempleOS will cause a stack overflow when i is larger than ~8100.

U0 Recurse(U64 i) {
  Print("%d\n", i);
  Recurse(i + 1);
}

Recurse(0);

i

function test(counter) {
	print(counter)
	test(counter+1)
}

software {
	test(0)
}

Icon and Unicon

procedure main() 
envar := "MSTKSIZE"
write(&errout,"Program to test recursion depth - dependant on the environment variable ",envar," = ",\getenv(envar)|&null)
deepdive()
end

procedure deepdive()
static d
initial d := 0 
write( d +:= 1)
deepdive()
end

Note: The stack size environment variable defaults to about 50000 words. This terminates after approximately 3500 recursions (Windows). The interpreter should terminate with a 301 error, but currently this does not work.

Inform 7

Home is a room.

When play begins: recurse 0.

To recurse (N - number):
	say "[N].";
	recurse N + 1.

Using the interpreters built into Windows build 6F95, a stack overflow occurs after 6529 recursions on the Z-machine or 2030 recursions on Glulx.

J

Testing stack depth can be risky because the OS may shut down J in the limiting case. To portably test stack depth it's best to run jconsole and display a count as each stack frame is entered.

Note also that task assumes that all stack frames must be the same size, which is probably not the case.

(recur=: verb def 'recur smoutput N=:N+1')N=:0

This above gives a stack depth of 9998 on one machine.

Note also, that ^: can be used for induction, and does not have stack size limits, though it does require that the function involved is a mathematical function of known variables -- and this is not always the case (for example, Markov processes typically use non-functions or "functions of unknown variables").

Java

public class RecursionTest {
	
    private static void recurse(int i) {
        try {
	    recurse(i+1);
	} catch (StackOverflowError e) {
	    System.out.print("Recursion depth on this system is " + i + ".");
	}
    }
	
    public static void main(String[] args) {
        recurse(0);
    }
}
Output:
Recursion depth on this system is 10473.

Settings:

Default size of stack is 320 kB.. To extend the memory allocated for stack can be used switch -Xss with the memmory limits.
For example: java -cp . -Xss1m RecursionTest (set the stack size to 1 MB).

JavaScript

function recurse(depth)
{
 try
 {
  return recurse(depth + 1);
 }
 catch(ex)
 {
  return depth;
 }
}

var maxRecursion = recurse(1);
document.write("Recursion depth on this system is " + maxRecursion);
Output:
(Chrome)
Recursion depth on this system is 10473.
Output:
(Firefox 1.6.13)
Recursion depth on this system is 3000.
Output:
(IE6)
Recursion depth on this system is 2552.

jq

Recent versions of jq (after July 1, 2014, i.e. after version 1.4) include some "Tail Call Optimizations" (TCO). As a result, tail-recursive functions of arity 0 will run indefinitely in these later versions. The TCO optimizations also speed up other recursive functions.

Accordingly we present two test functions and show the results using jq 1.4 and using a version of jq with TCO optimizations.

Arity-0 Function

def zero_arity:
  if (. % 1000000 == 0) then . else empty end, ((.+1)| zero_arity);

1|zero_arity

Arity-1 Function

def with_arity(n):
  if (n % 1000 == 0) then n else empty end, with_arity(n+1);

with_arity(1)

Results using jq 1.4

# Arity 0 - without TCO:
...
23000000      # 1.62 GB
25000000
*** error: can't allocate region
user	0m54.558s
sys	0m2.773s

# Arity 1 - without TCO:
...
77000 # 23.4 MB
...
85000  # 23.7 MB
90000  # 25.4 MB
237000 # 47.4 MB (5h:08)
242000 # 50.0 MB (5h:14m)
# [job cancelled manually after over 5 hours]

Results using jq with TCO

The arity-0 test was stopped after the recursive function had been called 100,000,000 (10^8) times. The memory required did not grow beyond 360 KB (sic).

$ time jq -n -f Find_limit_of_recursions.jq
...
10000000 # 360 KB
...
100000000  # 360 KB
# [job cancelled to get a timing]
user	2m0.534s
sys	0m0.329s

The arity-1 test process was terminated simply because it had become too slow; at that point it had only consumed about 74.6K MB.

...
56000   #  9.9MB
...
95000   # 14.8 MB
98000   # 15.2 MB
99000   # 15.4 MB
100000  # 15.5 MB
127000  # 37.4 MB
142000  # 37.4 MB
254000  # 74.6 MB
287000  # 74.6 MB
406000  # 74.6 MB (8h:50m)
412000  # 74.6 MB (9h:05m)
# [job cancelled manually after over 9 hours]

Discussion

Even without the TCO optimizations, the effective limits for recursive jq functions are relatively high:

  1. the arity-0 function presented here proceeded normally beyond 25,000,000 (25 million) iterations;
  2. the arity-1 function is more effectively constrained by performance than by memory: the test process was manually terminated after 242,000 iterations.

With the TCO optimizations:

  1. the arity-0 function is not only unconstrained by memory but is fast and remains fast; it requires only 360 KB (that is KB).
  2. the arity-1 function is, once again, more effectively constrained by performance than by memory: the test process was terminated after 412,000 iterations simply because it had become too slow; at that point it had only consumed about 74.6 MB.

Julia

This solution includes two versions of the function for probing recursion depth. The Clean version is perhaps more idiomatic. However the Dirty version, by using a global variable for the depth counter and minimizing the complexity of the called code reaches a significantly greater depth of recursion.

Clean

function divedivedive(d::Int)
    try
        divedivedive(d+1)
    catch
        return d
    end
end

Dirty

function divedivedive()
    global depth
    depth += 1
    divedivedive()
end

Main

depth = divedivedive(0)
println("A clean dive reaches a depth of ", depth, ".")

depth = 0
try
    divedivedive()
end
println("A dirty dive reaches a depth of ", depth, ".")
Output:
A clean dive reaches a depth of 21807.
A dirty dive reaches a depth of 174454.

Kotlin

The result is a typical figure for Oracle's JVM 1.8.0_121 running on Ubuntu version 14.04, 64 bit using the default stack size.

One might have expected that the result would be the same (or only vary over a small range) for a given configuration but in fact the results are all over the place - running the program a number of times I obtained figures as high as 26400 and as low as 9099! I have no idea why.

// version 1.1.2

fun recurse(i: Int) {
    try {
        recurse(i + 1)
    }
    catch(e: StackOverflowError) {
        println("Limit of recursion is $i")
    }
}

fun main(args: Array<String>) = recurse(0)
Output:
10367

Liberty BASIC

Checks for the case of gosub & for proper subroutine.

'subroutine recursion limit- end up on 475000

call test 1

sub test n
    if n mod 1000 = 0 then locate 1,1: print n
    call test n+1
end sub
'gosub recursion limit- end up on 5767000
[test]
    n = n+1
    if n mod 1000 = 0 then locate 1,1: print n
gosub [test]

LIL

lil.c allows an optional build time value to set a limit on recursion:

/* Enable limiting recursive calls to lil_parse - this can be used to avoid call stack
 * overflows and is also useful when running through an automated fuzzer like AFL */
/*#define LIL_ENABLE_RECLIMIT 10000*/

Otherwise, it is a race to run out of stack:

Output:
Little Interpreted Language Interactive Shell
# func recur {n} {print $n; inc n; recur $n}
recur
# recur
1
2
...
37323
37324
Segmentation fault (core dumped)

That number will varying depending on system and state of system.

Like Scheme, Logo guarantees tail call elimination, so recursion is effectively unbounded. You can catch a user interrupt though to see how deep you could go.

make "depth 0

to recurse
  make "depth :depth + 1
  recurse
end

catch "ERROR [recurse]
  ; hit control-C after waiting a while
print error          ; 16 Stopping... recurse [make "depth :depth + 1]
(print [Depth reached:] :depth)   ; some arbitrarily large number

LSL

I ran this twice and got 1891 and 1890; probably varies with the number Avatars on a Sim and other variables I can't control.

Originally I had it without the OwnerSay in the recursive function. Generally, if LSL has a Runtime Error it just shouts on the DEBUG_CHANNEL and skips to the next statement (which would have returned to the next statement in state_entry() said the highest number it had achieved) but, it just shouted "Script run-time error. Object: Stack-Heap Collision" on debug and quit running.

To test it yourself; rez a box on the ground, and add the following as a New Script.

integer iLimit_of_Recursion = 0;
Find_Limit_of_Recursion(integer x) {
	llOwnerSay("x="+(string)x);
	iLimit_of_Recursion = x;
	Find_Limit_of_Recursion(x+1);
}
default {
	state_entry() {
		Find_Limit_of_Recursion(0);
		llOwnerSay("iLimit_of_Recursion="+(string)iLimit_of_Recursion);
	}
}
Output:
[2012/07/07 18:40]  Object: x=0
[2012/07/07 18:40]  Object: x=1
[2012/07/07 18:40]  Object: x=2
   ...   ...   ...   ...   ...
[2012/07/07 18:41]  Object: x=1888
[2012/07/07 18:41]  Object: x=1889
[2012/07/07 18:41]  Object: x=1890
[2012/07/07 18:41]  Object: Object [script:New Script] Script run-time error
[2012/07/07 18:41]  Object: Stack-Heap Collision

Lua

Lua (version 5.3) support proper tail call, if the recursion is proper tail call there is no limit. Otherwise, it is limited by stack size set by the implementation.

local c = 0
function Tail(proper)
  c = c + 1
  if proper then
    if c < 9999999 then return Tail(proper) else return c end
  else
    return 1/c+Tail(proper) -- make the recursive call must keep previous stack
  end  
end

local ok,check = pcall(Tail,true)
print(c, ok, check)
c=0
ok,check = pcall(Tail,false)
print(c, ok, check)
Output:
9999999	true	9999999
333325	false	D:\00EXE\share\lua\5.3\test.lua:57: stack overflow

M2000 Interpreter

Modules & Functions

Module checkit {
      Global z
      Function a {
            z++
            =a()
      }
      try {
            m=a()
      }
      Print z
      
      z<=0
      Function a {
            z++
            call a()
      }
      try {
            call a()
      }
      Print z
      
      z<=0
      Module m {
            z++
            Call m
      }
      try {
            call m
      }
      Print z
      
      z<=0
      \\ without Call a module can't call itself
      \\ but can call something global, and that global can call back
      Module Global m1 {
            z++
            m2
      }
      Module Global m2 {
            z++
            m1
      }
      try {
            call m1
      }
      Print z
}
Checkit

In Wine give these:

4030  
8473  (plus 2 because we have Checkit inside a Z so these are two calls)
8473 (the same as above)
11225 (the same as above)

Subroutines

A lot of languages have a subroutine as a function without return value. As we see before, M2000 has Modules (as procedures) and Functions as that can be called as procedures too. These "procedures" can use only globals and anything they make for them. So what is a subroutine in Μ2000?

Subroutines are part of modules/functions. They haven't execution object, and they have to use parent object. So this parent object has the return stack, and use heap for this. So we can set a limit with Recursion.Limit to say 500000.

So a subroutine is code with module's scope, with recursion and local definitions. Utilizing current stack we can get results, or we can use by reference parameters to get results too.

We have to use statement Local for local variables and arrays who shadows same name variables or arrays. Parent can be the module/function as the caller, or another subroutine, or the same, but all have the same parent, the module/function.


Module Checkit {
     \\ recursion for subs controled by a value
      \\ change limit get a list of numbers from 1 to limit
      Recursion.Limit 10
      function FindZ {
            z=1
            Try {
                  CallmeAgain(1)
            }
            =Abs(z)
            Sub CallmeAgain(x)
                  z--
                   CallmeAgain(x+1)
                  z++
            End Sub     
      }
      z=FindZ()
      Print "Calls:"; z
      NormalCall(1)
      Sub NormalCall(x)
            Print x
            z--
            if z>0 then NormalCall(x+1)
            z++
      End Sub
}
Checkit

Mathematica / Wolfram Language

The variable $RecursionLimit can be read for its current value or set to different values. eg

$RecursionLimit=10^6

Would set the recursion limit to one million.

MATLAB / Octave

The recursion limit can be 'get' and 'set' using the "get" and "set" keywords.

Sample Usage:

>> get(0,'RecursionLimit')

ans =

   500

>> set(0,'RecursionLimit',2500)
>> get(0,'RecursionLimit')

ans =

        2500

Maxima

f(p) := f(n: p + 1)$
f(0);
Maxima encountered a Lisp error:
 Error in PROGN [or a callee]: Bind stack overflow.
Automatically continuing.
To enable the Lisp debugger set *debugger-hook* to nil.

n;
406

МК-61/52

П2	ПП	05	ИП1	С/П
ИП0	ИП2	-	x<0	20	ИП0	1	+	П0	ПП	05
ИП1	1	+	П1	В/О

Modula-2

MODULE recur;

IMPORT InOut;

PROCEDURE recursion (a : CARDINAL);

BEGIN
  InOut.Write ('.');    (*  just count the dots....     *)
  recursion (a + 1)
END recursion;

BEGIN
  recursion (0)
END recur.

Producing this:

jan@Beryllium:~/modula/rosetta$ recur >testfile
Segmentation fault
jan@Beryllium:~/modula/rosetta$ ls -l
-rwxr-xr-x 1 jan users  20032 2011-05-20 00:26 recur*
-rw-r--r-- 1 jan users    194 2011-05-20 00:26 recur.mod
-rw-r--r-- 1 jan users 523264 2011-05-20 00:26 testfile
jan@Beryllium:~/modula/rosetta$ wc testfile
     0      1 523264 testfile

So the recursion depth is just over half a million.

MUMPS

RECURSE
 IF $DATA(DEPTH)=1 SET DEPTH=1+DEPTH
 IF $DATA(DEPTH)=0 SET DEPTH=1
 WRITE !,DEPTH_" levels down"
 DO RECURSE
 QUIT
End of the run ...
1918 levels down
1919 levels down
1920 levels down
 DO RECURSE
 ^
<FRAMESTACK>RECURSE+4^ROSETTA
USER 72d0>

Nanoquery

Translation of: Python
def recurse(counter)
        println counter
        counter += 1
        recurse(counter)
end

recurse(1)
Output:
1
2
3
...
456
457
458
%recursion depth exception: recursion too deep while calling function 'recurse'

Neko

/**
 Recursion limit, in Neko
*/

/* This version is effectively unlimited, (50 billion test before ctrl-c) */
sum = 0.0
counter = 0
tco = function(n) {
    sum += n
    counter += 1
    if n > 10000000 return n else tco(n + 1)
}

try $print("Tail call recursion: ", tco(0), " sum: ", sum, "\n")
catch with $print("tco counter: ", counter, " ", with, "\n")

/* Code after tail, these accumulate stack, will run out of space */
sum = 0.0
counter = 0
recurse = function(n) {
    sum += n
    counter += 1
    if n > 1000000 return n else recurse(n + 1)
    return sum
}

try $print("Recurse: ", recurse(0), " sum: ", sum, "\n")
catch with $print("recurse limit exception: ", counter, " ", with, "\n")
Output:
prompt$ nekoc recursion-limit.neko 
prompt$ neko recursion-limit.n     
Tail call recursion: 10000001 sum: 50000015000001
recurse limit exception: 52426 Stack Overflow

NetRexx

Like Java, NetRexx memory allocation is managed by the JVM under which it is run. The following sample presents runtime memory allocations then begins the recursion run.

/* NetRexx */
options replace format comments java crossref symbols binary

import java.lang.management.

memoryInfo()
digDeeper(0)

/**
 * Just keep digging
 * @param level depth gauge
 */
method digDeeper(level = int) private static binary
  do
    digDeeper(level + 1)
  catch ex = Error
    System.out.println('Recursion got' level 'levels deep on this system.')
    System.out.println('Recursion stopped by' ex.getClass.getName())
  end
  return

/**
 * Display some memory usage from the JVM
 * @see ManagementFactory
 * @see MemoryMXBean
 * @see MemoryUsage
 */
method memoryInfo() private static
  mxBean = ManagementFactory.getMemoryMXBean()   -- get the MemoryMXBean
  hmMemoryUsage = mxBean.getHeapMemoryUsage()    -- get the heap MemoryUsage object
  nmMemoryUsage = mxBean.getNonHeapMemoryUsage() -- get the non-heap MemoryUsage object
  say 'JVM Memory Information:'
  say '      Heap:' hmMemoryUsage.toString()
  say '  Non-Heap:' nmMemoryUsage.toString()
  say '-'.left(120, '-')
  say
  return
Output:
JVM Memory Information: 
      Heap: init = 0(0K) used = 2096040(2046K) committed = 85000192(83008K) max = 129957888(126912K) 
  Non-Heap: init = 24317952(23748K) used = 5375328(5249K) committed = 24317952(23748K) max = 136314880(133120K) 
------------------------------------------------------------------------------------------------------------------------ 
 
Recursion got 9673 levels deep on this system. 
Recursion stopped by java.lang.StackOverflowError 

Nim

proc recurse(i: int): int =
  echo i
  recurse(i+1)
echo recurse(0)

Compiled without optimizations (debug build), the program stops with the following message:

Error: call depth limit reached in a debug build (2000 function calls). You can change it with -d:nimCallDepthLimit=<int> but really try to avoid deep recursions instead.

Compiled with option -d:release (release build), it terminates with a segmentation error (on Linux) after more than 673000 calls. Switching with option --gc:arc to “arc” memory manager, it terminates after more than 209000 calls.

Compiled with option --d:danger (suppressing almost all checks), it terminates with a segmentation error after more than 785000 calls. Switching to “arc” memory manager, it terminates after more than 224000 calls.

Instead of waiting for the recursions you can compile with debuginfo activated and check with gdb:

nim c -d:release --debuginfo --lineDir:on recursionlimit.nim

OCaml

When the recursion is a "tail-recursion" there is no limit. Which is important because being a functional programming language, OCaml uses recursion to make loops.

If the recursion is not a tail one, the execution is stopped with the message "Stack overflow":

# let last = ref 0 ;;
val last : int ref = {contents = 0}
# let rec f i =
    last := i;
    i + (f (i+1))
  ;;
val f : int -> int = <fun>
# f 0 ;;
stack overflow during evaluation (looping recursion?).
# !last ;;
- : int = 262067

here we see that the function call stack size is 262067.

(* One can build a function from the idea above, catching the exception *)

let rec_limit () =
  let last = ref 0 in
  let rec f i =
    last := i;
    1 + f (i + 1)
  in
  try (f 0)
  with Stack_overflow -> !last
;;

rec_limit ();;
262064

(* Since with have eaten some stack with this function, the result is slightly lower.
But now it may be used inside any function to get the available stack space *)

Oforth

Limit found is 173510 on Windows system. Should be more on Linux system.

: limit  1+ dup . limit ;

0 limit

ooRexx

Using ooRexx for the program shown under Rexx:

 rexx pgm 1>x1 2>x2

 puts the numbers in x1 and the error messages in x2

...
2785
2786
8 *-*      call self
....
     8 *-*   call self
     3 *-* call self
Error 11 running C:\work.ooRexx\wc\main.4.1.1.release\Win32Rel\StreamClasses.orx line 366:  Control stack full
Error 11.1:  Insufficient control stack space; cannot continue execution

Oz

Translation of: Scheme

Oz supports an unbounded number of tail calls. So the following code can run forever with constant memory use (although the space used to represent Number will slowly increase):

declare
  proc {Recurse Number}
     {Show Number}
     {Recurse Number+1}
  end
in
  {Recurse 1}

With non-tail recursive functions, the number of recursions is only limited by the available memory.

PARI/GP

As per "Recursive functions" in the Pari/GP users's manual.

dive(n) = dive(n+1)
dive(0)

The limit is the underlying C language stack. Deep recursion is detected before the stack is completely exhausted (by checking RLIMIT_STACK) so a gp level error is thrown instead of a segfault.

Pascal

See Delphi

Perl

Maximum recursion depth is memory dependent.

my $x = 0;
recurse($x);

sub recurse ($x) {
   print ++$x,"\n";
   recurse($x);
}


1
2
...
...
10702178
10702179
Out of memory!

Phix

On 32-bit the limit is an impressive 31 million. I have seen this hit 43 million on 64-bit, but it then forced a hard reboot.
Those limits will obviously be significantly smaller for routines with more parameters, local variables, and temps.

atom t1 = time()+1
 
integer depth = 0
 
procedure recurse()
    if time()>t1 then
        ?depth
        t1 = time()+1
    end if
    depth += 1
    -- only 1 of these will ever get called, of course...
    recurse()
    recurse()
    recurse()
end procedure
 
recurse()
output   32 bit
C:\Program Files (x86)\Phix>p e01
8336837
16334140
20283032
21863323
22547975
22875708
23227196
23536921
24051004
24902668
25518908
26211370
26899260
27457596
27946743
28627343
29129830
29811260
31081002
31893231
32970812
33612604
34624828
34886703
Your program has run out of memory, one moment please
C:\Program Files (x86)\Phix\e01.exw:48 in procedure recurse()
memory allocation failure
... called from C:\Program Files (x86)\Phix\e01.exw:48 in procedure recurse()
... called from C:\Program Files (x86)\Phix\e01.exw:48 in procedure recurse()
... called from C:\Program Files (x86)\Phix\e01.exw:48 in procedure recurse()
... called from C:\Program Files (x86)\Phix\e01.exw:48 in procedure recurse()

Global & Local Variables

--> see C:\Program Files (x86)\Phix\ex.err
Press Enter...
C:\Program Files (x86)\Phix>

saner

The following much more safely merely tests it can reach 20,000,000, plus however far it gets in the last whole-second

atom t1 = time()+1
 
integer depth = 0, depth_blown = false
string btd = "building"
 
procedure recurse()
    if time()>t1 then
        printf(1,"depth: %d (%s)\n",{depth,btd})
        if depth>20_000_000 then
            depth_blown = true
            btd = "tearing down"
        end if
        t1 = time()+1
    end if
    if depth_blown then
        depth -= 1
    else
        depth += 1
        recurse()  -- (build, aka +1 with progress)
        recurse()  -- (tear down, -1 with progress)
    end if
end procedure
 
recurse()
Output:
depth: 8857573 (building)
depth: 17197111 (building)
depth: 25309477 (building)
depth: 20023696 (tearing down)
depth: 14825154 (tearing down)
depth: 9601027 (tearing down)
depth: 3725849 (tearing down)

Phixmonti

/# Rosetta Code problem: http://rosettacode.org/wiki/Find_limit_of_recursion
by Galileo, 10/2022 #/

def sec msec int enddef

sec var t

def recursion
    1 +
    sec t 1 + > if t 1 + var t dup print nl endif
    recursion
enddef

0 recursion
Output:
281007
431296
581394
730334
879369
1029498
1179530
1330012
1479943
1630421
1781000
1930959
2081595
2231553
2381764
2531888
2682392
2832907
2983242
3133677
3284111
3434178
3584534
3734997
3885133
4035703
4185613
4336355
4486693
4635764
4786107
4935949
5086156
5235687
5385416
5535747
5685633
5835858
5985753
6135743
6285747
6436123
6585421
6735203
6885286
7035236
7185132
7334455
7484643
7618401
7731876
7852957
7976679
8103526
8230876
8358600
8488773
8623796
8763058
8898198
9046186
9189766
9339550
9489755
9633985
9781880
9931149
10080277
10227093
10361576
10498033
10646428
10795650
10940499
11090442
11239675
11389776
11539185
11687704
11831276
11966704
12086836
Your program has run out of memory, one moment please



Global & Local Variables

*** Error detected ***
*** Stack content:
[12197563]
*** Location: .. Rosetta Code problem: http://rosettacode.org/wiki/Find_limit_of_recursion by Galileo, 10/2022 #/ def sec msec ..
=== Press any key to exit ===

PHP

<?php
function a() {
    static $i = 0;
    print ++$i . "\n";
    a();
}
a();
Output:
 1
 2
 3
 [...]
 597354
 597355
 597356
 597357
 597358
 
 Fatal error: Allowed memory size of 134217728 bytes exhausted (tried to allocate 261904 bytes) in [script-location.php] on line 5

PicoLisp

The 64-bit and the 32-bit version behave slightly different. While the 32-bit version imposes no limit on its own, and relies on the 'ulimit' setting of the caller, the 64-bit version segments the available stack (likewise depending on 'ulimit') and allows each (co)routine a maximal stack size as configured by 'stack'.

32-bit version

$ ulimit -s
8192
$ pil +
: (let N 0 (recur (N) (recurse (msg (inc N)))))
...
730395
730396
730397
Segmentation fault

64-bit version

$ ulimit -s
unlimited
$ pil +
: (stack)  # The default stack segment size is 64 MB
-> 64

: (co 'a (yield 7))  # Start a dummy coroutine
-> 7

: (let N 0 (recur (N) (recurse (println (inc N)))))
...
2475
2476
2477
Stack overflow
?

PL/I

recurs: proc options (main) reorder;
dcl sysprint file;
dcl mod      builtin;

dcl ri       fixed bin(31) init (0);

recursive: proc recursive;            
  ri += 1;
  if mod(ri, 1024) = 1 then
    put data(ri);

  call recursive();
end recursive;

call recursive();
end recurs;

Result (abbreviated):

...
RI=       4894721;
RI=       4895745;
RI=       4896769;
RI=       4897793;
RI=       4898817;

At this stage the program, running on z/OS with a REGION=0M on the EXEC statement (i.e. grab as much storage as you like), ABENDs with a USER COMPLETION CODE=4088 REASON CODE=000003EC

Obviously, if the procedure recursive would have contained local variables, the depth of recursion would be reached much earlier...

PowerShell

Works with: PowerShell version 2

When the overflow exception is thrown, the entire stack collapses. But anticipating this, we can leverage PowerShell features to get and process all of the results from before the exception. In PowerShell, when anything is written the the output stream WITHOUT the "Return" keyword, processing continues, so we can successfully return data from the function even if the function never successfully completes. The original calling line will also be terminated when the exception is thrown, but if instead of assigning it to a variable, we send the results to a pipeline, we can process the earlier results before handling the exception.

function TestDepth ( $N )
    {
    $N
    TestDepth ( $N + 1 )
    }
   
try
    {
    TestDepth 1 | ForEach { $Depth = $_ }
    }
catch
    {
    "Exception message: " + $_.Exception.Message
    }
"Last level before error: " + $Depth
Output:
Exception message: The script failed due to call depth overflow.
Last level before error: 4994

PureBasic

The recursion limit is primarily determined by the stack size. The stack size can be changed when compiling a program by specifying the new size using '/stack:NewSize' in the linker file.

Procedural

In addition to the stack size the recursion limit for procedures is further limited by the procedure's parameters and local variables which are also stored on the same stack.

Procedure Recur(n)
  PrintN(str(n))
  Recur(n+1)
EndProcedure

Recur(1)
Stack overflow after 86317 recursions on x86 Vista.

Classic

rec:
  PrintN(str(n))
  n+1
  Gosub rec
  Return
Stack overflow after 258931 recursions on x86 Vista.

Python

import sys
print(sys.getrecursionlimit())

To set it:

import sys
sys.setrecursionlimit(12345)

Or, we can test it:

def recurse(counter):
  print(counter)
  counter += 1
  recurse(counter)

Giving:

File "<stdin>", line 2, in recurse
RecursionError: maximum recursion depth exceeded while calling a Python object
996

Which we could change if we wanted to.

We can catch the RecursionError and keep going a bit further:

def recurseDeeper(counter):
    try:
        print(counter)
        recurseDeeper(counter + 1)
    except RecursionError:
        print("RecursionError at depth", counter)
        recurseDeeper(counter + 1)

Giving:

1045
Fatal Python error: Cannot recover from stack overflow.


Quackery

When the direct approach

0 [ 1+ dup echo cr recurse ]

was still churning out digits after 13,000,000 (Quackery does not optimise tail end recursion) I decided on an indirect approach, by asking the equivalent question, "What is the largest nest that Quackery can create?" as each item on the Quackery return stack occupies two items in a nest (i.e. dynamic array).

' [ 1 ]  [ dup size echo cr  dup join again ]

On the first trial the process died with a segmentation error after reaching 2^30 items, and on the second trial the computer became very unresponsive at the same point, but made it to 2^31 items before I force-quit it.

In conclusion, the answer to the question "What depth of recursion does Quackery support?", at least in the case of Quackery running under Python 3.8.1 on a mid 2011 iMac with a 2.5 GHz Intel Core i5 and 12 GB of RAM and MacOS 10.13.6, is "sufficient".

I would anticipate at least equivalent results running under PyPy3, as it has much better garbage collection. (Also, it runs Quackery 20 to 30 times faster than the default version of Python 3, so would crash significantly sooner.)


R

R's recursion is counted by the number of expressions to be evaluated, rather than the number of function calls.

#Get the limit
options("expressions")

#Set it
options(expressions = 10000)

#Test it
recurse <- function(x) 
{ 
  print(x)
  recurse(x+1)

}
recurse(0)

Racket

#lang racket
(define (recursion-limit)
  (with-handlers ((exn? (lambda (x) 0)))
    (add1 (recursion-limit))))

This should theoretically return the recursion limit, as the function can't be tail-optimized and there's an exception handler to return a number when an error is encountered. For this to work one has to give the Racket VM the maximum possible memory limit and wait.

Raku

(formerly Perl 6) Maximum recursion depth is memory dependent. Values in excess of 1 million are easily achieved.

Works with: Rakudo version 2015.12
my $x = 0;
recurse;

sub recurse () {
   ++$x;
   say $x if $x %% 1_000_000;   
   recurse;
}
Output:

When manually terminated memory use was on the order of 4Gb:

1000000
2000000
3000000
4000000
5000000
6000000
7000000
8000000
9000000
10000000
^C

Retro

When run, this will display the address stack depth until it reaches the max depth. Once the address stack is full, Retro will crash.

: try -6 5 out wait 5 in putn cr try ;

REXX

recursive procedure

On (IBM's) VM/CMS, the limit of recursion was built-into CMS to stop run-away EXEC programs (this
included EXEC[0], EXEC2, and REXX) being called recursively;   it was either 200 or 250 as I recall.

This limit was maybe changed later to allow the user to specify the limit.   My memory is really fuzzy
about these details, it was over thirty years ago.

/*REXX program finds the recursion limit:   a subroutine that repeatably calls itself.  */
parse version x;     say x;     say             /*display which REXX is being used.     */
#=0                                             /*initialize the numbers of invokes to 0*/
call self                                       /*invoke the  SELF  subroutine.         */
                                                /* [↓]  this will never be executed.    */
exit                                            /*stick a fork in it,  we're all done.  */
/*──────────────────────────────────────────────────────────────────────────────────────*/
self: procedure expose #                        /*declaring that  SELF  is a subroutine.*/
      #=#+1                                     /*bump number of times SELF is invoked. */
      say #                                     /*display the number of invocations.    */
      call self                                 /*invoke ourselves recursively.         */
output   when using Regina 3.6 under Windows/XP Pro:
REXX-Regina_3.6(MT) 5.00 31 Dec 2011
 .
 .
 .
164405
164406
164407
System resources exhausted

[Your mileage will vary.]

For BREXX 2.1.0,    it was     251   
For Regina 3.2,      "  "    3,641
For Regina 3.3,      "  "    4,234
For Regina 3.4,      "  "  945,144
For Regina 3.4P1,    "  "     "
For Regina 3.5,      "  "  164,560
For Regina 3.6,      "  "  164,407
For Regina 3.7,      "  "     "
For Regina 3.7RC1,   "  "     "
For Regina 3.8,      "  "     "
For Regina 3.8RC1,   "  "     "
For Regina 3.8.2,    "  "     "   
For Regina 3.9.0,    "  "  164,527
For Regina 3.9.1,    "  "     " 
For Regina 3.9.3,    "  "  164,398 

Note that the above recursion limit will be less and it's dependent upon how much virtual memory the program itself uses,
this would include REXX variables and their values, and the program source (as it's kept in virtual memory also),
and the size of the REXX.EXE and REXX.DLL programs, and any other programs executing in the Windows DOS (including
either the CMD.EXE or COMMAND.COM) shell).

output   when using Personal REXX under Windows/XP Pro:


The recursion level wasn't captured, but the last number shown was 240.

REXX/Personal 4.00 21 Mar 1992
 .
 .
 .
    10 +++ call self
    10 +++ call self
    10 +++ call self
     4 +++ call SELF 
Error 5 on line 10 of D:\SELF.REX: Machine resources exhausted
output   when using R4 REXX under Windows/XP Pro:
REXX-r4 4.00 29 Apr 2012
 .
 .
 .
505
506
507
An unexpected error occurred
output   when using ROO REXX under Windows/XP Pro:
REXX-roo 4.00 28 Jan 2007

 .
 .
 .
380
381
382
An unexpected error occurred

recursive subroutine

All REXXes were executed under Windows/XP Pro.

/*REXX program finds the recursion limit:   a subroutine that repeatably calls itself.  */
parse version x;     say x;     say             /*display which REXX is being used.     */
#=0                                             /*initialize the numbers of invokes to 0*/
call self                                       /*invoke the  SELF  subroutine.         */
                                                /* [↓]  this will never be executed.    */
exit                                            /*stick a fork in it,  we're all done.  */
/*──────────────────────────────────────────────────────────────────────────────────────*/
self:  #=#+1                                    /*bump number of times SELF is invoked. */
       say #                                    /*display the number of invocations.    */
       call self                                /*invoke ourselves recursively.         */
output   (paraphrased and edited)
For BREXX 2.1.0,    it was     251
For Regina 3.2,      "  "    4,234
For Regina 3.3,      "  "    3,641
For Regina 3.4,      "  "  945,144
For Regina 3.4P1,    "  "     "
For Regina 3.5,      "  "     "
For Regina 3.6,      "  "  828,441
For Regina 3.7,      "  "     " 
For Regina 3.7RC1,   "  "     "
For Regina 3.8,      "  "     "
For Regina 3.8RC1,   "  "     " 
For Regina 3.8.2,    "  "     "    
For Regina 3.9.0,    "  "  828,441
For Regina 3.9.1,    "  "     " 
For Regina 3.9.3,    "  "     "
For Personal REXX,  it was     240  (the same)
For R4,             it was     507  (the same)
For ROO,            it was     382  (the same)

Ring

recurse(0)

func recurse x
     see ""+ x + nl
     recurse(x+1)

Ruby

def recurse x
  puts x
  recurse(x+1)
end

recurse(0)
Output:
Produces a SystemStackError
.
.
.
6074
recurse.rb:3:in `recurse': stack level too deep (SystemStackError)
	from recurse.rb:3:in `recurse'
	from recurse.rb:6

when tracking Stack overflow exceptions ; returns 8732 on my computer :

def recurse n
  recurse(n+1)
rescue SystemStackError
  n
end

puts recurse(0)

Run BASIC

a = recurTest(1)
 
function recurTest(n)
if n mod 100000 then cls:print n
if n > 327000 then [ext]
   n = recurTest(n+1)
[ext]
end function
327000

Rust

fn recurse(n: i32) {
    println!("depth: {}", n);
    recurse(n + 1)
}

fn main() {
    recurse(0);
}
Output:
...
depth: 18433
depth: 18434
depth: 18435

thread '<main>' has overflowed its stack
An unknown error occurred

To learn more, run the command again with --verbose.

Sather

class MAIN is
  attr r:INT;
  recurse is
    r := r + 1;
    #OUT + r + "\n";
    recurse;
  end;
  main is
    r := 0;
    recurse;
  end;
end;

Segmentation fault is reached when r is 130560.

Scala

def recurseTest(i:Int):Unit={
   try{
      recurseTest(i+1)
   } catch { case e:java.lang.StackOverflowError => 
      println("Recursion depth on this system is " + i + ".")
   }
}
recurseTest(0)
Output:
depending on the current stack size
Recursion depth on this system is 4869.

If your function is tail-recursive the compiler transforms it into a loop.

def recurseTailRec(i:Int):Unit={
   if(i%100000==0) println("Recursion depth is " + i + ".")
   recurseTailRec(i+1)
}

Scheme

(define (recurse number)
  (begin (display number) (newline) (recurse (+ number 1))))

(recurse 1)

Implementations of Scheme are required to support an unbounded number of tail calls. Furthermore, implementations are encouraged, but not required, to support exact integers of practically unlimited size.

SenseTalk

put recurse(1)

function recurse n
    put n
    get the recurse of (n+1)
end recurse

Recursion limit error is reached at 40.

Sidef

Maximum recursion depth is memory dependent.

func recurse(n) {
   say n;
   recurse(n+1);
}

recurse(0);
Output:
0
1
2
...
...
357077
357078
357079

Smalltalk

In the Squeak dialect of Smalltalk:

Object subclass: #RecursionTest
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'RosettaCode'

Add the following method:

counter: aNumber
	^self counter: aNumber + 1

Call from the Workspace:

r := RecursionTest new.
r counter: 1.

After some time the following error pops up:

   Warning! Squeak is almost out of memory!
   Low space detection is now disabled. It will be restored when you close or proceed from this error notifier. Don't panic, but do proceed with caution.
   Here are some suggestions:
   If you suspect an infinite recursion (the same methods calling each other again and again), then close this debugger, and fix the problem.
   If you want this computation to finish, then make more space available (read on) and choose "proceed" in this debugger. Here are some ways to make more space available...
   * Close any windows that are not needed.
   * Get rid of some large objects (e.g., images).
   * Leave this window on the screen, choose "save as..." from the screen menu, quit, restart the Squeak VM with a larger memory allocation, then restart the image you just saved, and choose "proceed" in this window.
   If you want to investigate further, choose "debug" in this window.  Do not use the debugger "fullStack" command unless you are certain that the stack is not very deep. (Trying to show the full stack will definitely use up all remaining memory if the low-space problem is caused by an infinite recursion!).

Other dialects raise an exception:

counter := 0.
down := [ counter := counter + 1. down value ].
down on: RecursionError do:[
   'depth is ' print. counter printNL
].

Standard ML

fun recLimit () =
  1 + recLimit ()
  handle _ => 0

val () = print (Int.toString (recLimit ()) ^ "\n")

Swift

var n = 1

func recurse() {
    print(n)
    n += 1
    recurse()
}

recurse()

Tcl

proc recur i {
    puts "This is depth [incr i]"
    catch {recur $i}; # Trap error from going too deep
}
recur 0

The tail of the execution trace looks like this:

This is depth 995
This is depth 996
This is depth 997
This is depth 998
This is depth 999

Note that the maximum recursion depth is a tunable parameter, as is shown in this program:

# Increase the maximum depth
interp recursionlimit {} 1000000
proc recur i {
    if {[catch {recur [incr i]}]} {
        # If we failed to recurse, print how far we got
	puts "Got to depth $i"
    }
}
recur 0

For Tcl 8.5 on this platform, this prints:

Got to depth 6610

At which point it has exhausted the C stack, a trapped error. Tcl 8.6 uses a stackless execution engine, and can go very deep if required:

Got to depth 999999

TSE SAL

// library: program: run: recursion: limit <description>will stop at 3616</description> <version>1.0.0.0.3</version> <version control></version control> (filenamemacro=runprrli.s) [kn, ri, su, 25-12-2011 23:12:02]
PROC PROCProgramRunRecursionLimit( INTEGER I )
 Message( I )
 PROCProgramRunRecursionLimit( I + 1 )
END

PROC Main()
 PROCProgramRunRecursionLimit( 1 )
END

TXR

(set-sig-handler sig-segv
  (lambda (signal async-p) (throw 'out)))

(defvar *count* 0)

(defun recurse ()
  (inc *count*)
  (recurse))

(catch (recurse)
  (out () (put-line `caught segfault!\nreached depth: @{*count*}`)))
Output:
$ txr limit-of-recursion.tl
caught segfault!
reached depth: 10909

UNIX Shell

Works with: Bourne Again SHell
recurse()
{
  # since the example runs slowly, the following
  # if-elif avoid unuseful output; the elif was
  # added after a first run ended with a segmentation
  # fault after printing "10000"
  if [[ $(($1 % 5000)) -eq 0 ]]; then 
      echo $1;
  elif [[ $1 -gt 10000 ]]; then
      echo $1
  fi
  recurse $(($1 + 1))
}

recurse 0

The Bash reference manual says No limit is placed on the number of recursive calls, nonetheless a segmentation fault occurs at 13777 (Bash v3.2.19 on 32bit GNU/Linux)

Ursa

def recurse (int counter)
    try
        recurse (+ counter 1)
    catch recursionerror
        out "the limit of recursion was " counter endl console
    end try
end

recurse 1

Uxntal

Uxn has a known stack size of 256 bytes, which allows 128 function calls. However, assuming we don’t know this, we can find the stack size with a program anyway. In older versions of Uxn, it was possible to detect stack overflow with the System vector, which would make this task easier, but the current Uxn stacks are circular, with no overflow and underflow checks, which means that we have to get a bit more creative. Calling a recursive function enough times will cause the return stack pointer to wrap around and overwrite the first return address, which means execution will be trapped in the recursive function forever. By detecting when the function has run more times than expected, the recursion limit can be found.

|00 @System &vector $2 &expansion $2 &wst $1 &rst $1 &metadata $2 &r $2 &g $2 &b $2 &debug $1 &state $1
|10 @Console &vector $2 &read $1 &pad $4 &type $1 &write $1 &error $1

|00 @calls $1

|0100
    #01
    &loop
        DUP .calls STZ
        recurse
        INC !&loop

@recurse
    ( keep calling recurse until stack value is 00 )
    #01 SUB DUP #00 EQU ?&done

    recurse

    ( as we walk back up the stack, increment counter )
    &done INC

    ( if we go above the original call count, the stack was corrupted )
    DUP .calls LDZ GTH ?&fail
JMP2r

&fail
    ;msg1 print-str
    .calls LDZ print-hex
    ;msg2 print-str
    #80 .System/state DEO BRK

@print-str
    &loop
        LDAk .Console/write DEO
        INC2 LDAk ?&loop
    POP2
JMP2r

@print-hex
    DUP #04 SFT print-digit #0f AND print-digit
JMP2r

@print-digit
    DUP #09 GTH #27 MUL ADD #30 ADD .Console/write DEO
JMP2r

@msg1 "Stack 20 "overflow 20 "at 20 "# 00
@msg2 20 "calls. 0a00

Vala

void recur(uint64 v ) { 
  print (@"$v\n"); 
  recur( v + 1);
} 

void main() { 
  recur(0); 
}
Output:

trimmed output

0
1
2
...
25905
25906
25907

VBA

Option Explicit

Sub Main()
    Debug.Print "The limit is : " & Limite_Recursivite(0)
End Sub

Function Limite_Recursivite(Cpt As Long) As Long
    Cpt = Cpt + 1               'Count
    On Error Resume Next
    Limite_Recursivite Cpt      'recurse
    On Error GoTo 0
    Limite_Recursivite = Cpt    'return
End Function
Output:
The limit is : 6442

VBScript

Haven't figured out how to see the depth. And this depth is that of calling the O/S rather than calling within.

'mung.vbs
option explicit

dim c
if wscript.arguments.count = 1 then
	c = wscript.arguments(0)
	c = c + 1
else
	c = 0
end if
wscript.echo "[Depth",c & "] Mung until no good."
CreateObject("WScript.Shell").Run "cscript Mung.vbs " & c, 1, true
wscript.echo "[Depth",c & "] no good."

Okay, the internal limits version.

'mung.vbs
option explicit

sub mung(c)
	dim n
	n=c+1
	wscript.echo "[Level",n & "] Mung until no good"
	on error resume next
	mung n
	on error goto 0
	wscript.echo "[Level",n & "] no good"
end sub

mung 0
Output:
(abbrev.)
[Level 1719] Mung until no good
[Level 1720] Mung until no good
[Level 1721] Mung until no good
[Level 1722] Mung until no good
[Level 1722] no good
[Level 1721] no good
[Level 1720] no good
[Level 1719] no good

V (Vlang)

It'll be some number, depending on machine and environment.

// Find limit of recursion, in V (Vlang)
module main

// starts here, then call down until stacks become faulty
pub fn main() {
    recurse(0)
}

fn recurse(n int) {
    println(n)
    recurse(n+1)
}
Output:
prompt$ v run find-limit-of-recursion.v
...
174537
174538
prompt$ echo $?
11

Wren

I cannot find any published information on the maximum amount of memory that can be used by a fiber's stack - and hence the limit of recursion for a given function - but it appears to be 4 GB on a sufficiently large 64-bit system such as my own (32 GB) with no shell limit.

The final figure produced by the following script was 536,870,500 and multiplying by 8 (the number of bytes of storage required for the parameter 'n') gives 4,294,964,000 which is just 3,296 bytes short of 4 GB.

In Wren a fiber's stack starts small and is increased as required. It appears that the runtime makes no attempt to check for any limitation internally leaving the script to eventually segfault.

var F = Fn.new { |n|
    if (n%500 == 0) System.print(n)  // print progress after every 500 calls
    F.call(n + 1)
}
F.call(1)
Output:
...
536870000
536870500
Segmentation fault (core dumped)

x86 Assembly

Works with: nasm
   global main

   section .text

main
	xor	eax, eax
	call   	recurse
	ret

recurse
	add	eax, 1  
	call 	recurse
	ret

I've used gdb and the command print $eax to know when the segmentation fault occurred. The result was 2094783.

XPL0

On the Raspberry Pi this causes a Segmentation fault at the recursion levels shown in Output.

The stack size is about 8 MB. The original compiler pushes a single 4-byte value (the return address for Recurse) onto the stack.

The optimizing compiler pushes an additional 4-byte value (r11), which is the base address of variables local to Recurse. But since there aren't any local variables in this situation, the optimizing compiler isn't as optimal as it could be.

The MS-DOS version crashes at 12,224 levels. The allocated stack size is 16,384 bytes. But since each call pushes a 4-byte value, the actual limit should be a maximum of 4,096.

int Lev;
proc Recurse;
[if (Lev & $3FF) = 0 then
    [IntOut(0, Lev);  ChOut(0, ^ )];
Lev:= Lev+1;
Recurse;
];

[Lev:= 0;
Recurse;
]
Output:
2,096,128 for the original compiler (xplr)
1,047,552 for the optimizing compiler (xpl0)

Z80 Assembly

Unlike the 6502, the Z80 has a 16-bit stack pointer that is fully relocatable. Therefore, the limit of recursion technically depends on how much RAM you have. The definition of "limit for recursion" for this example is maximum number of instructions that have a push effect (including push, call, rst, etc.),before RAM that was not intended to be part of the stack area (i.e. the heap) becomes clobbered. For this task we'll assume that interrupts are disabled, and no hardware exists that would generate an NMI. (Both of those operations put return addresses on the stack and can do so at any time during our code execution so for simplicity we'll ignore them.

To give the maximum limit, we'll say that there is only one variable (we need one to store the stack pointer), and the entire address space of the CPU exists and is in RAM (i.e. 64k of RAM, including the beginning vector table, program code, and stack space, no address mirroring. Also we'll assume there is no "video memory" or anything not intended for a specific purpose.) A byte count of each line of code is also provided.

(For a more realistic example see this task's entry for 8080 Assembly.)

org &0000
LD SP,&FFFF ;3 bytes
loop:
or a ;1 byte, clears the carry flag
ld (&0024),sp ;4 bytes
ld hl,(&0024) ;3 bytes
push af ;1 byte
ld bc,(&0024) ;4 bytes
sbc hl,bc    ;4 bytes
jr z,loop    ;2 bytes
jr *         ;2 bytes
;address &0024 begins here
word 0       ;placeholder for stack pointer

This is the minimum amount of code I can come up with that can check for the limit. (Note that this code has no way to display the results of the test to the user, so on real hardware the limit of recursion is much less, but for an emulator this will suffice.) The concept here is relatively simple. Do the following in a loop:

  • Store the stack pointer into memory.
  • Load it into HL.
  • Push a value. This will cause the real stack pointer to decrement and the pushed value will be written to memory.
  • After the push, load from the same memory location into BC. If we haven't reached the limit of recursion, HL = BC.
  • The CP instruction only compares the accumulator to an 8 bit register, so to compare HL to BC we actually have to subtract them. If the result is zero, they were the same to begin with.
  • If they're different, then the act of pushing AF clobbered the stack pointer we backed up in step 1. This means recursion is at its limit, so quit looping and halt the CPU.

Zig

Translation of: C

Works with: 0.11.x, 0.12.0-dev.1381+61861ef39

For 0.10.x, replace @call(.some_call_modifier, ...) with @call(.{ .modifier = .some_call_modifier }, ...) in these examples.

Leave TRE to the compiler

In this version, Zig compiler is free to (not) optimize recursive function, so behaviour may change from one optimization mode to another, like it was with 2-nd example from C section.

const std = @import("std");

fn recurse(i: c_uint) void {
    std.debug.print("{d}\n", .{i});
    // We use wrapping addition operator here to mirror C behaviour.
    recurse(i +% 1);
    // Line above is equivalent to:
    // @call(.auto, recurse, .{i +% 1});
}

pub fn main() void {
    recurse(0);
    return;
}

Force-disable TRE

To force-disable "simple tail recursion elimination" (STRE) for all optimize modes, we can use "never_tail" field of enum "std.builtin.CallModifier". It works not as hint, but as a hard requirement, so if it's impossible to fulfill, compile error is outputted.

const std = @import("std");

fn recurse(i: c_uint) void {
    std.debug.print("{d}\n", .{i});
    // We use wrapping addition operator here to mirror C behaviour.
    @call(.never_tail, recurse, .{i +% 1});
}

pub fn main() void {
    recurse(0);
    return;
}

Segmentation fault occurs at different values of "i", depending on running platform, but on my platform (with stack size reported by ulimit as 16384) both C and Zig versions (compiled without optimizations output last value in approximately [523500, 524000] range.

gcc compiler with -O2 flag eliminated tail recursion, as mentioned in 2-nd example from C section, but in this Zig example recurse function is never turned into loop, even when enabling different optimization modes — we explicitly prohibited compiler from doing it in any optimize/build mode!

Force-enable TRE

Similarly, we can force-enable mentioned optimization in all optimize modes by using enum field "always_tail". It's (again) a hard requirement and will emit compile error if this requirement is impossible to complete.

const std = @import("std");

fn recurse(i: c_uint) void {
    std.debug.print("{d}\n", .{i});
    // We use wrapping addition operator here to mirror C behaviour.
    @call(.always_tail, recurse, .{i +% 1});
}

pub fn main() void {
    recurse(0);
    return;
}

On my machine, segmentation fault never occurs, instead resulting in infinite loop in all optimize modes (as intended).

zkl

fcn{self.fcn()}()
Output:
Stack trace for VM#1 ():
   Cmd.__fcn#1_2 addr:3  args(0) reg(0) R
   <repeats 2096 times>
   Cmd.__constructor addr:3  args(0) reg(0) R
   startup.__constructor addr:2242  args(0) reg(1) ER
   startup.__constructor addr:2178  args(0) reg(22) 
Exception thrown: AssertionError(That is one big stack, infinite recursion?)