Count in octal
You are encouraged to solve this task according to the task description, using any language you may know.
- Task
Produce a sequential count in octal, starting at zero, and using an increment of a one for each consecutive number.
Each number should appear on a single line, and the program should count until terminated, or until the maximum value of the numeric type in use is reached.
- Related task
- Integer sequence is a similar task without the use of octal numbers.
0815
}:l:> Start loop, enqueue Z (initially 0).
}:o: Treat the queue as a stack and
<:8:= accumulate the octal digits
/=>&~ of the current number.
^:o:
<:0:- Get a sentinel negative 1.
&>@ Enqueue it between the digits and the current number.
{ Dequeue the first octal digit.
}:p:
~%={+ Rotate each octal digit into place and print it.
^:p:
<:a:~$ Output a newline.
<:1:x{+ Dequeue the current number and increment it.
^:l:
360 Assembly
The program uses one ASSIST macro (XPRNT) to keep the code as short as possible.
* Octal 04/07/2016
OCTAL CSECT
USING OCTAL,R13 base register
B 72(R15) skip savearea
DC 17F'0' savearea
STM R14,R12,12(R13) prolog
ST R13,4(R15) "
ST R15,8(R13) "
LR R13,R15 "
LA R6,0 i=0
LOOPI LR R2,R6 x=i
LA R9,10 j=10
LA R4,PG+23 @pg
LOOP LR R3,R2 save x
SLL R2,29 shift left 32-3
SRL R2,29 shift right 32-3
CVD R2,DW convert octal(j) to pack decimal
OI DW+7,X'0F' prepare unpack
UNPK 0(1,R4),DW packed decimal to zoned printable
LR R2,R3 restore x
SRL R2,3 shift right 3
BCTR R4,0 @pg=@pg-1
BCT R9,LOOP j=j-1
CVD R2,DW binary to pack decimal
OI DW+7,X'0F' prepare unpack
UNPK 0(1,R4),DW packed decimal to zoned printable
CVD R6,DW convert i to pack decimal
MVC ZN12,EM12 load mask
ED ZN12,DW+2 packed decimal (PL6) to char (CL12)
MVC PG(12),ZN12 output i
XPRNT PG,80 print buffer
C R6,=F'2147483647' if i>2**31-1 (integer max)
BE ELOOPI then exit loop on i
LA R6,1(R6) i=i+1
B LOOPI loop on i
ELOOPI L R13,4(0,R13) epilog
LM R14,R12,12(R13) "
XR R15,R15 "
BR R14 exit
LTORG
PG DC CL80' ' buffer
DW DS 0D,PL8 15num
ZN12 DS CL12
EM12 DC X'40',9X'20',X'2120' mask CL12 11num
YREGS
END OCTAL
- Output:
0 00000000000 1 00000000001 2 00000000002 3 00000000003 4 00000000004 5 00000000005 6 00000000006 7 00000000007 8 00000000010 9 00000000011 10 00000000012 10 00000000012 11 00000000013 ... 2147483640 17777777770 2147483641 17777777771 2147483642 17777777772 2147483643 17777777773 2147483644 17777777774 2147483645 17777777775 2147483646 17777777776 2147483647 17777777777
6502 Assembly
Easy6502 can only output using a limited video memory or a hexdump. However the output is correct up to 2 octal digits.
define SRC_LO $00
define SRC_HI $01
define DEST_LO $02
define DEST_HI $03
define temp $04 ;temp storage used by foo
;some prep work since easy6502 doesn't allow you to define arbitrary bytes before runtime.
SET_TABLE:
TXA
STA $1000,X
INX
BNE SET_TABLE
;stores the identity table at memory address $1000-$10FF
CLEAR_TABLE:
LDA #0
STA $1200,X
INX
BNE CLEAR_TABLE
;fills the range $1200-$12FF with zeroes.
LDA #$10
STA SRC_HI
LDA #$00
STA SRC_LO
;store memory address $1000 in zero page
LDA #$12
STA DEST_HI
LDA #$00
STA DEST_LO
;store memory address $1200 in zero page
loop:
LDA (SRC_LO),y ;load accumulator from memory address $1000+y
JSR foo ;convert accumulator to octal
STA (DEST_LO),y ;store accumulator in memory address $1200+y
INY
CPY #$40
BCC loop
BRK
foo:
sta temp ;store input temporarily
asl ;bit shift, this places the top bit of the right nibble in the bottom of the left nibble.
pha ;back this value up
lda temp
and #$07 ;take the original input and remove everything except the bottom 3 bits.
sta temp ;store it for later. What used to be stored here is no longer needed.
pla ;get the pushed value back.
and #$F0 ;clear the bottom 4 bits.
ora temp ;put the bottom 3 bits of the original input back.
and #$7F ;clear bit 7.
rts
- Output:
1200: 00 01 02 03 04 05 06 07 10 11 12 13 14 15 16 17 1210: 20 21 22 23 24 25 26 27 30 31 32 33 34 35 36 37 1220: 40 41 42 43 44 45 46 47 50 51 52 53 54 55 56 57 1230: 60 61 62 63 64 65 66 67 70 71 72 73 74 75 76 77
8080 Assembly
This assumes the CP/M operating system. The count will terminate after the largest unsigned 16-bit value is reached.
;-------------------------------------------------------
; useful equates
;-------------------------------------------------------
bdos equ 5 ; CP/M BDOS entry
conout equ 2 ; BDOS console output function
cr equ 13 ; ASCII carriage return
lf equ 10 ; ASCII line feed
;------------------------------------------------------
; main code begins here
;------------------------------------------------------
org 100h ; start of tpa under CP/M
lxi h,0 ; save CP/M's stack
dad sp
shld oldstk
lxi sp,stack ; set our own stack
lxi h,1 ; start counting at 1
count: call putoct
call crlf
inx h
mov a,h ; check for overflow (hl = 0)
ora l
jnz count
;
; all finished. clean up and exit.
;
lhld oldstk ; get CP/M's stack back
sphl ; restore it
ret ; exit to command prompt
;------------------------------------------------------
; Octal output routine
; entry: hl = number to output on console in octal
; this is a recursive routine and uses 6 bytes of stack
; space for each digit
;------------------------------------------------------
putoct: push b
push d
push h
mvi b,3 ; hl = hl >> 3
div2: call shlr
dcr b
jnz div2
mov a,l ; test if hl = 0
ora h
cnz putoct ; recursive call
pop h ; get unshifted hl back
push h
mov a,l ; get low byte
ani 7 ; a = a mod 8
adi '0' ; make printable
call putchr
pop h
pop d
pop b
ret
;-------------------------------------------------------
; logical right shift of 16-bit value in HL by one bit
;-------------------------------------------------------
shlr: ora a ; clear carry
mov a,h ; begin with most significant byte
rar ; bit 0 goes into carry
mov h,a ; put shifted byte back
mov a,l ; get least significant byte
rar ; bit 0 of MSB has shifted in
mov l,a
ret
;------------------------------------------------------
; output CRLF to console
;------------------------------------------------------
crlf: mvi a,cr
call putchr
mvi a,lf
call putchr
ret
;------------------------------------------------------
; Console output routine
; print character in A register to console
; preserves BC, DE, and HL
;------------------------------------------------------
putchr: push h
push d
push b
mov e,a ; character to E for CP/M
mvi c,conout
call bdos
pop b
pop d
pop h
ret
;-------------------------------------------------------
; data area
;-------------------------------------------------------
oldstk: dw 1
stack equ $+128 ; 64 level stack
;
end
- Output:
Showing the last 10 lines of the output.
1777766 1777767 1777770 1777771 1777772 1777773 1777774 1777775 1777776 1777777
AArch64 Assembly
/* ARM assembly AARCH64 Raspberry PI 3B */
/* program countOctal64.s */
/*******************************************/
/* Constantes file */
/*******************************************/
/* for this file see task include a file in language AArch64 assembly*/
.include "../includeConstantesARM64.inc"
/*********************************/
/* Initialized data */
/*********************************/
.data
sMessResult: .ascii "Count : "
sMessValeur: .fill 11, 1, ' ' // size => 11
szCarriageReturn: .asciz "\n"
/*********************************/
/* UnInitialized data */
/*********************************/
.bss
/*********************************/
/* code section */
/*********************************/
.text
.global main
main: // entry of program
mov x20,0 // loop indice
1: // begin loop
mov x0,x20
ldr x1,qAdrsMessValeur
bl conversion8 // call conversion octal
ldr x0,qAdrsMessResult
bl affichageMess // display message
add x20,x20,1
cmp x20,64
ble 1b
100: // standard end of the program
mov x0,0 // return code
mov x8,EXIT // request to exit program
svc 0 // perform the system call
qAdrsMessValeur: .quad sMessValeur
qAdrszCarriageReturn: .quad szCarriageReturn
qAdrsMessResult: .quad sMessResult
/******************************************************************/
/* Converting a register to octal */
/******************************************************************/
/* x0 contains value and x1 address area */
/* x0 return size of result (no zero final in area) */
/* area size => 11 bytes */
.equ LGZONECAL, 10
conversion8:
stp x1,lr,[sp,-16]! // save registers
mov x3,x1
mov x2,LGZONECAL
1: // start loop
mov x1,x0
lsr x0,x0,3 // / by 8
lsl x4,x0,3
sub x1,x1,x4 // compute remainder x1 - (x0 * 8)
add x1,x1,48 // digit
strb w1,[x3,x2] // store digit on area
cmp x0,0 // stop if quotient = 0
sub x4,x2,1
csel x2,x4,x2,ne
bne 1b // and loop
// and move digit from left of area
mov x4,0
2:
ldrb w1,[x3,x2]
strb w1,[x3,x4]
add x2,x2,1
add x4,x4,1
cmp x2,LGZONECAL
ble 2b
// and move spaces in end on area
mov x0,x4 // result length
mov x1,' ' // space
3:
strb w1,[x3,x4] // store space in area
add x4,x4,1 // next position
cmp x4,LGZONECAL
ble 3b // loop if x4 <= area size
100:
ldp x1,lr,[sp],16 // restaur 2 registers
ret // return to address lr x30
/********************************************************/
/* File Include fonctions */
/********************************************************/
/* for this file see task include a file in language AArch64 assembly */
.include "../includeARM64.inc"
Action!
PROC PrintOctal(CARD v)
CHAR ARRAY a(6)
BYTE i=[0]
DO
a(i)=(v&7)+'0
i==+1
v=v RSH 3
UNTIL v=0
OD
DO
i==-1
Put(a(i))
UNTIL i=0
OD
RETURN
PROC Main()
CARD i=[0]
DO
PrintF("decimal=%U octal=",i)
PrintOctal(i) PutE()
i==+1
UNTIL i=0
OD
RETURN
- Output:
Screenshot from Atari 8-bit computer
decimal=0 octal=0 decimal=1 octal=1 decimal=2 octal=2 decimal=3 octal=3 decimal=4 octal=4 ... decimal=3818 octal=7352 decimal=3819 octal=7353 decimal=3820 octal=7354 decimal=3821 octal=7355 decimal=3822 octal=7356 ...
Ada
with Ada.Text_IO;
procedure Octal is
package IIO is new Ada.Text_IO.Integer_IO(Integer);
begin
for I in 0 .. Integer'Last loop
IIO.Put(I, Base => 8);
Ada.Text_IO.New_Line;
end loop;
end Octal;
First few lines of Output:
8#0# 8#1# 8#2# 8#3# 8#4# 8#5# 8#6# 8#7# 8#10# 8#11# 8#12# 8#13# 8#14# 8#15# 8#16# 8#17# 8#20#
Aime
integer o;
o = 0;
do {
o_xinteger(8, o);
o_byte('\n');
o += 1;
} while (0 < o);
ALGOL 68
#!/usr/local/bin/a68g --script #
INT oct width = (bits width-1) OVER 3 + 1;
main:
(
FOR i TO 17 # max int # DO
printf(($"8r"8r n(oct width)dl$, BIN i))
OD
)
Output:
8r00000000001 8r00000000002 8r00000000003 8r00000000004 8r00000000005 8r00000000006 8r00000000007 8r00000000010 8r00000000011 8r00000000012 8r00000000013 8r00000000014 8r00000000015 8r00000000016 8r00000000017 8r00000000020 8r00000000021
ALGOL-M
begin
% display n on console in octal format %
procedure putoct(n);
integer n;
begin
integer digit, n8;
string(1) array octdig[0:7];
octdig[0] := "0"; octdig[1] := "1"; octdig[2] := "2";
octdig[3] := "3"; octdig[4] := "4"; octdig[5] := "5";
octdig[6] := "6"; octdig[7] := "7";
n8 := n / 8;
if n8 <> 0 then putoct(n8); % recursive call %
digit := n - (n / 8) * 8; % n mod 8 %
writeon(octdig[digit]);
end;
integer i, maxint;
i := 1;
maxint := 16383;
comment
Excercise the procedure by counting up in octal as
far as possible. In doing so, we have to take some
care, because integer variables are set to 1 on
overflow, and if that happens, the loop will simply
start over, and the program will run forever;
while i < maxint do % we need to stop one shy %
begin
write("");
putoct(i);
i := i + 1;
end;
% display the final value %
write("");
putoct(maxint);
end
- Output:
First and last 10 lines of output
1 2 3 4 5 6 7 10 11 12 ... 37766 37767 37770 37771 37772 37773 37774 37775 37776 37777
ALGOL W
Algol W has built-in hexadecimal and decimal output, this implements octal output.
begin
string(12) r;
string(8) octDigits;
integer number;
octDigits := "01234567";
number := -1;
while number < MAXINTEGER do begin
integer v, cPos;
number := number + 1;
v := number;
% build a string of octal digits in r, representing number %
% Algol W uses 32 bit integers, so r should be big enough %
% the most significant digit is on the right %
cPos := 0;
while begin
r( cPos // 1 ) := octDigits( v rem 8 // 1 );
v := v div 8;
( v > 0 )
end do begin
cPos := cPos + 1
end while_v_gt_0;
% show most significant digit on a newline %
write( r( cPos // 1 ) );
% continue the line with the remaining digits (if any) %
for c := cPos - 1 step -1 until 0 do writeon( r( c // 1 ) )
end while_r_lt_MAXINTEGER
end.
- Output:
0 1 2 3 4 5 6 7 10 11 12 ...
Amazing Hopper
#include <basico.h>
algoritmo
x=0, tope=11
decimales '0'
iterar grupo ( ++x,#( x< tope ),\
x,":",justificar derecha ( 5, x ---mostrar como octal--- ),\
NL, imprimir, cuando( #(x==10)){ \
"...\n...\n",x=4294967284, tope=4294967295} )
terminar
- Output:
0: 0 1: 1 2: 2 3: 3 4: 4 5: 5 6: 6 7: 7 8: 10 9: 11 10: 12 ... ... 4294967285: 37777777765 4294967286: 37777777766 4294967287: 37777777767 4294967288: 37777777770 4294967289: 37777777771 4294967290: 37777777772 4294967291: 37777777773 4294967292: 37777777774 4294967293: 37777777775 4294967294: 37777777776
APL
Works with Dyalog APL. 100,000 is just an arbitrarily large number I chose.
10⊥¨8∘⊥⍣¯1¨⍳100000
ARM Assembly
/* ARM assembly Raspberry PI */
/* program countoctal.s */
/************************************/
/* Constantes */
/************************************/
.equ STDOUT, 1 @ Linux output console
.equ EXIT, 1 @ Linux syscall
.equ WRITE, 4 @ Linux syscall
/*********************************/
/* Initialized data */
/*********************************/
.data
sMessResult: .ascii "Count : "
sMessValeur: .fill 11, 1, ' ' @ size => 11
szCarriageReturn: .asciz "\n"
/*********************************/
/* UnInitialized data */
/*********************************/
.bss
/*********************************/
/* code section */
/*********************************/
.text
.global main
main: @ entry of program
mov r4,#0 @ loop indice
1: @ begin loop
mov r0,r4
ldr r1,iAdrsMessValeur
bl conversion8 @ call conversion octal
ldr r0,iAdrsMessResult
bl affichageMess @ display message
add r4,#1
cmp r4,#64
ble 1b
100: @ standard end of the program
mov r0, #0 @ return code
mov r7, #EXIT @ request to exit program
svc #0 @ perform the system call
iAdrsMessValeur: .int sMessValeur
iAdrszCarriageReturn: .int szCarriageReturn
iAdrsMessResult: .int sMessResult
/******************************************************************/
/* display text with size calculation */
/******************************************************************/
/* r0 contains the address of the message */
affichageMess:
push {r0,r1,r2,r7,lr} @ save registres
mov r2,#0 @ counter length
1: @ loop length calculation
ldrb r1,[r0,r2] @ read octet start position + index
cmp r1,#0 @ if 0 its over
addne r2,r2,#1 @ else add 1 in the length
bne 1b @ and loop
@ so here r2 contains the length of the message
mov r1,r0 @ address message in r1
mov r0,#STDOUT @ code to write to the standard output Linux
mov r7, #WRITE @ code call system "write"
svc #0 @ call systeme
pop {r0,r1,r2,r7,lr} @ restaur des 2 registres */
bx lr @ return
/******************************************************************/
/* Converting a register to octal */
/******************************************************************/
/* r0 contains value and r1 address area */
/* r0 return size of result (no zero final in area) */
/* area size => 11 bytes */
.equ LGZONECAL, 10
conversion8:
push {r1-r4,lr} @ save registers
mov r3,r1
mov r2,#LGZONECAL
1: @ start loop
mov r1,r0
lsr r0,#3 @ / by 8
sub r1,r0,lsl #3 @ compute remainder r1 - (r0 * 8)
add r1,#48 @ digit
strb r1,[r3,r2] @ store digit on area
cmp r0,#0 @ stop if quotient = 0
subne r2,#1 @ else previous position
bne 1b @ and loop
@ and move digit from left of area
mov r4,#0
2:
ldrb r1,[r3,r2]
strb r1,[r3,r4]
add r2,#1
add r4,#1
cmp r2,#LGZONECAL
ble 2b
@ and move spaces in end on area
mov r0,r4 @ result length
mov r1,#' ' @ space
3:
strb r1,[r3,r4] @ store space in area
add r4,#1 @ next position
cmp r4,#LGZONECAL
ble 3b @ loop if r4 <= area size
100:
pop {r1-r4,lr} @ restaur registres
bx lr @return
Arturo
loop 1..40 'i ->
print ["number in base 10:" pad to :string i 2
"number in octal:" pad as.octal i 2]
- Output:
number in base 10: 1 number in octal: 1 number in base 10: 2 number in octal: 2 number in base 10: 3 number in octal: 3 number in base 10: 4 number in octal: 4 number in base 10: 5 number in octal: 5 number in base 10: 6 number in octal: 6 number in base 10: 7 number in octal: 7 number in base 10: 8 number in octal: 10 number in base 10: 9 number in octal: 11 number in base 10: 10 number in octal: 12 number in base 10: 11 number in octal: 13 number in base 10: 12 number in octal: 14 number in base 10: 13 number in octal: 15 number in base 10: 14 number in octal: 16 number in base 10: 15 number in octal: 17 number in base 10: 16 number in octal: 20 number in base 10: 17 number in octal: 21 number in base 10: 18 number in octal: 22 number in base 10: 19 number in octal: 23 number in base 10: 20 number in octal: 24 number in base 10: 21 number in octal: 25 number in base 10: 22 number in octal: 26 number in base 10: 23 number in octal: 27 number in base 10: 24 number in octal: 30 number in base 10: 25 number in octal: 31 number in base 10: 26 number in octal: 32 number in base 10: 27 number in octal: 33 number in base 10: 28 number in octal: 34 number in base 10: 29 number in octal: 35 number in base 10: 30 number in octal: 36 number in base 10: 31 number in octal: 37 number in base 10: 32 number in octal: 40 number in base 10: 33 number in octal: 41 number in base 10: 34 number in octal: 42 number in base 10: 35 number in octal: 43 number in base 10: 36 number in octal: 44 number in base 10: 37 number in octal: 45 number in base 10: 38 number in octal: 46 number in base 10: 39 number in octal: 47 number in base 10: 40 number in octal: 50
AutoHotkey
DllCall("AllocConsole")
Octal(int){
While int
out := Mod(int, 8) . out, int := int//8
return out
}
Loop
{
FileAppend, % Octal(A_Index) "`n", CONOUT$
Sleep 200
}
AWK
The awk extraction and reporting language uses the underlying C library to provide support for the printf command. This enables us to use that function to output the counter value as octal:
BEGIN {
for (l = 0; l <= 2147483647; l++) {
printf("%o\n", l);
}
}
BASIC
Some BASICs provide a built-in function to convert a number to octal, typically called OCT$
.
DIM n AS LONG
FOR n = 0 TO &h7FFFFFFF
PRINT OCT$(n)
NEXT
However, many do not. For those BASICs, we need to write our own function.
WHILE ("" = INKEY$)
PRINT Octal$(n)
n = n + 1
WEND
END
FUNCTION Octal$(what)
outp$ = ""
w = what
WHILE ABS(w) > 0
o = w AND 7
w = INT(w / 8)
outp$ = STR$(o) + outp$
WEND
Octal$ = outp$
END FUNCTION
See also: BBC BASIC, Liberty BASIC, PureBasic, Run BASIC
Applesoft BASIC
10 N$ = "0"
100 O$ = N$
110 PRINT O$
120 N$ = ""
130 C = 1
140 FOR I = LEN(O$) TO 1 STEP -1
150 N = VAL(MID$(O$, I, 1)) + C
160 C = N >= 8
170 N$ = STR$(N - C * 8) + N$
180 NEXT I
190 IF C THEN N$ = "1" + N$
200 GOTO 100
BASIC256
valor = 0
do
print ToOctal(valor)
valor += 1
until valor = 0
end
Chipmunk Basic
10 rem Count in ocatal
20 while ("" = inkey$ )
30 print octal$(n)
40 n = n+1
50 wend
60 end
200 function octal$(what)
210 outp$ = ""
220 w = what
230 while abs(w) > 0
240 o = w and 7
250 w = int(w/8)
260 outp$ = str$(o)+outp$
270 wend
280 octal$ = outp$
290 end function
Commodore BASIC
This example calculates the octal equivalent of the number and returns the octal equivalent in the form of a string.
Eventually, the number will reach 1,000,000,000 (one billion decimal) at which point the computer will express the value of n
in exponential format, i.e. 1e+09
and will thus loose precision and stop counting.
Commodore BASIC has a little quirk where numeric values converted to a string also include a leading space for the possible negative sign; this is why the STR$
function is wrapped in a RIGHT$
function.
10 n=0
20 gosub 70
30 print oc$
40 n=n+1
50 get a$:if a$<>"q" then goto 20
60 end
70 oc$="":t=n
80 q=int(t/8)
90 r=t-(q*8)
100 oc$=left$(str$(n),1)+right$(str$(r),1)+oc$
110 if q<>0 then t=q:goto 80
120 return
- Output:
0 1 2 3 4 5 6 7 10 11 12 13 14 15 17 20 21 22 23 User stopped count. ready. █
Sinclair ZX81 BASIC
The octal number is stored and manipulated as a string, meaning that even with only 1k of RAM the program shouldn't stop until the number gets to a couple of hundred digits long. I have not left it running long enough to find out exactly when it does run out of memory. The SCROLL
statement is necessary: the ZX81 halts when the screen is full unless it is positively told to scroll instead.
10 LET N$="0"
20 SCROLL
30 PRINT N$
40 LET L=LEN N$
50 LET N=VAL N$(L)+1
60 IF N=8 THEN GOTO 90
70 LET N$(L)=STR$ N
80 GOTO 20
90 LET N$(L)="0"
100 IF L=1 THEN GOTO 130
110 LET L=L-1
120 GOTO 50
130 LET N$="1"+N$
140 GOTO 20
uBasic/4tH
This routine allows for any base (up to 36) and also caters for negative numbers.
x = 1
Do
Print Show(FUNC(_FNtobase(x, 8)))
While Set (x, x+1)
Loop
End
_FNtobase
Param (2) ' convert A@ to string in base B@
Local (2) ' digit C@ and string D@
' initialize, save sign
d@ := "" : Push a@ < 0 : a@ = Abs(a@)
Do
c@ = a@ % b@ : a@ = a@ / b@ ' extract digit and append
d@ = Join (Char (Ord("0") + c@ + (7 * (c@ > 9))), d@)
While a@ > 0 ' something left to convert?
Loop
If Pop() Then d@ = Join ("-", d@) ' apply sign if required
Return (d@)
Batch File
@echo off
:: {CTRL + C} to exit the batch file
:: Send incrementing decimal values to the :to_Oct function
set loop=0
:loop1
call:to_Oct %loop%
set /a loop+=1
goto loop1
:: Convert the decimal values parsed [%1] to octal and output them on a new line
:to_Oct
set todivide=%1
set "fulloct="
:loop2
set tomod=%todivide%
set /a appendmod=%tomod% %% 8
set fulloct=%appendmod%%fulloct%
if %todivide% lss 8 (
echo %fulloct%
exit /b
)
set /a todivide/=8
goto loop2
- Output:
0 1 2 3 4 5 6 7 10 ...
BBC BASIC
Terminate by pressing ESCape.
N% = 0
REPEAT
PRINT FN_tobase(N%, 8, 0)
N% += 1
UNTIL FALSE
END
REM Convert N% to string in base B% with minimum M% digits:
DEF FN_tobase(N%, B%, M%)
LOCAL D%, A$
REPEAT
D% = N% MOD B%
N% DIV= B%
IF D%<0 D% += B% : N% -= 1
A$ = CHR$(48 + D% - 7*(D%>9)) + A$
M% -= 1
UNTIL (N%=FALSE OR N%=TRUE) AND M%<=0
=A$
bc
obase = 8 /* Output base is octal. */
for (num = 0; 1; num++) num /* Loop forever, printing counter. */
The loop never stops at a maximum value, because bc uses arbitrary-precision integers.
BCPL
This will count up from 0 until the limit of the machine word.
get "libhdr"
let start() be
$( let x = 0
$( writeo(x)
wrch('*N')
x := x + 1
$) repeatuntil x = 0
$)
Befunge
This is almost identical to the Binary digits sample, except for the change of base and the source coming from a loop rather than a single input.
:0\55+\:8%68>*#<+#8\#68#%/#8:_$>:#,_$1+:0`!#@_
BQN
_while_
and Oct
are snippets from BQNcrate. A more array-oriented approach is ⥊↕n⥊8
, which produces all n
-digit octal numbers instead of counting.
_while_←{𝔽⍟𝔾∘𝔽_𝕣_𝔾∘𝔽⍟𝔾𝕩}
Oct←8{⌽𝕗|⌊∘÷⟜𝕗⍟(↕1+·⌊𝕗⋆⁼1⌈⊢)}
{•Show Oct 𝕩, 𝕩+1} _while_ 1 0
Bracmat
Stops when the user presses Ctrl-C or when the stack overflows. The solution is not elegant, and so is octal counting.
( oct
=
. !arg:<8
& (!arg:~<0|ERROR)
| str$(oct$(div$(!arg.8)) mod$(!arg.8))
)
& -1:?n
& whl'(1+!n:?n&out$(!n oct$!n));
Brainf***
+[ Start with n=1 to kick off the loop
[>>++++++++<< Set up {n 0 8} for divmod magic
[->+>- Then
[>+>>]> do
[+[-<+>]>+>>] the
<<<<<<] magic
>>>+ Increment n % 8 so that 0s don't break things
>] Move into n / 8 and divmod that unless it's 0
-< Set up sentinel ‑1 then move into the first octal digit
[++++++++ ++++++++ ++++++++ Add 47 to get it to ASCII
++++++++ ++++++++ +++++++. and print it
[<]<] Get to a 0; the cell to the left is the next octal digit
>>[<+>-] Tape is {0 n}; make it {n 0}
>[>+] Get to the ‑1
<[[-]<] Zero the tape for the next iteration
++++++++++. Print a newline
[-]<+] Zero it then increment n and go again
C
#include <stdio.h>
int main()
{
unsigned int i = 0;
do { printf("%o\n", i++); } while(i);
return 0;
}
C#
using System;
class Program
{
static void Main()
{
var number = 0;
do
{
Console.WriteLine(Convert.ToString(number, 8));
} while (++number > 0);
}
}
C++
This prevents an infinite loop by counting until the counter overflows and produces a 0 again. This could also be done with a for or while loop, but you'd have to print 0 (or the last number) outside the loop.
#include <iostream>
int main()
{
unsigned i = 0;
do
{
std::cout << std::oct << i << std::endl;
++i;
} while(i != 0);
return 0;
}
Clojure
(doseq [i (range)] (println (format "%o" i)))
COBOL
>>SOURCE FREE
IDENTIFICATION DIVISION.
PROGRAM-ID. count-in-octal.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
REPOSITORY.
FUNCTION dec-to-oct
.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 i PIC 9(18).
PROCEDURE DIVISION.
PERFORM VARYING i FROM 1 BY 1 UNTIL i = 0
DISPLAY FUNCTION dec-to-oct(i)
END-PERFORM
.
END PROGRAM count-in-octal.
IDENTIFICATION DIVISION.
FUNCTION-ID. dec-to-oct.
DATA DIVISION.
LOCAL-STORAGE SECTION.
01 rem PIC 9.
01 dec PIC 9(18).
LINKAGE SECTION.
01 dec-arg PIC 9(18).
01 oct PIC 9(18).
PROCEDURE DIVISION USING dec-arg RETURNING oct.
MOVE dec-arg TO dec *> Copy is made to avoid modifying reference arg.
PERFORM WITH TEST AFTER UNTIL dec = 0
MOVE FUNCTION REM(dec, 8) TO rem
STRING rem, oct DELIMITED BY SPACES INTO oct
DIVIDE 8 INTO dec
END-PERFORM
.
END FUNCTION dec-to-oct.
CoffeeScript
n = 0
while true
console.log n.toString(8)
n += 1
Common Lisp
(loop for i from 0 do (format t "~o~%" i))
Component Pascal
BlackBox Component Builder
MODULE CountOctal;
IMPORT StdLog,Strings;
PROCEDURE Do*;
VAR
i: INTEGER;
resp: ARRAY 32 OF CHAR;
BEGIN
FOR i := 0 TO 1000 DO
Strings.IntToStringForm(i,8,12,' ',TRUE,resp);
StdLog.String(resp);StdLog.Ln
END
END Do;
END CountOctal.
Execute: ^Q CountOctal.Do
Output:
0%8 1%8 2%8 3%8 4%8 5%8 6%8 7%8 10%8 11%8 12%8 13%8 14%8 15%8 16%8 17%8 20%8 21%8 22%8
Cowgol
include "cowgol.coh";
typedef N is uint16;
sub print_octal(n: N) is
var buf: uint8[12];
var p := &buf[11];
[p] := 0;
loop
p := @prev p;
[p] := '0' + (n as uint8 & 7);
n := n >> 3;
if n == 0 then break; end if;
end loop;
print(p);
end sub;
var n: N := 0;
loop
print_octal(n);
print_nl();
n := n + 1;
if n == 0 then break; end if;
end loop;
Crystal
# version 0.21.1
# using unsigned 8 bit integer, range 0 to 255
(0_u8..255_u8).each { |i| puts i.to_s(8) }
- Output:
0 1 2 3 4 5 6 7 10 11 12 ... 374 375 376 377
D
void main() {
import std.stdio;
ubyte i;
do writefln("%o", i++);
while(i);
}
Dc
Named Macro
A simple infinite loop and octal output will do.
8o0[p1+lpx]dspx
Anonymous Macro
Needs r
(swap TOS and NOS):
8 o 0 [ r p 1 + r dx ] dx
Pushing/poping TOS to a named stack can be used instead of swaping:
8 o 0 [ S@ p 1 + L@ dx ] dx
DCL
$ i = 0
$ loop:
$ write sys$output f$fao( "!OL", i )
$ i = i + 1
$ goto loop
- Output:
00000000000 00000000001 00000000002 ... 17777777777 20000000000 20000000001 ... 37777777777 00000000000 00000000001 ...
Delphi
program CountingInOctal;
{$APPTYPE CONSOLE}
uses SysUtils;
function DecToOct(aValue: Integer): string;
var
lRemainder: Integer;
begin
Result := '';
repeat
lRemainder := aValue mod 8;
Result := IntToStr(lRemainder) + Result;
aValue := aValue div 8;
until aValue = 0;
end;
var
i: Integer;
begin
for i := 0 to 20 do
WriteLn(DecToOct(i));
end.
EasyLang
func$ oct v .
while v > 0
r$ = v mod 8 & r$
v = v div 8
.
if r$ = ""
r$ = 0
.
return r$
.
for i = 0 to 10
print oct i
.
print "."
print "."
max = pow 2 53
i = max - 10
repeat
print oct i
until i = max
i += 1
.
EDSAC order code
Uses 17-bit integers, maximum 2^16 - 1 (177777 octal). It would take the original EDSAC 18 or 19 hours to exhaust these, so there is not much point in extending to 35-bit integers.
[Count in octal, for Rosetta Code.
EDSAC program, Initial Orders 2.]
[Subroutine to print 17-bit non-negative integer in octal,
with suppression of leading zeros.
Input: 0F = number (not preserved)
Workspace: 0D, 4F, 5F]
T64K GK [load at location 64]
A3F T28@ [plant return link as usual]
T4D [clear whole of 4D including sandwich bit]
A2F [load 0...010 binary (permanently in 2F)]
T4F [(1) marker bit (2) flag to test for leading 0]
AF [load number]
R2F [shift 3 right]
A4D [add marker bit]
TD [store number and marker in 0D]
H29@ [mask to isolate 3-bit octal digit]
[Loop to print digits]
[10] T5F [clear acc]
C1F [top 5 bits of acc = octal digit]
U5F [to 5F for printing]
S4F [subtract flag to test for leading 0]
G18@ [skip printing if so]
O5F [print digit]
T5F [clear acc]
T4F [flag = 0, so future 0's are not skipped]
[18] T5F [clear acc]
AD [load number + marker bit, as shifted]
L2F [shift left 3 more]
TD [store back]
AF [has marker reached sign bit yet?]
E10@ [loop back if not]
[Last digit separately, in case input = 0]
T5F [clear acc]
C1F T5F O5F
[28] ZF [(planted) jump back to caller]
[29] UF [mask, 001110...0 binary]
[Main routine]
T96K GK [load at location 96]
[Constants]
[0] PD [1]
[1] #F [set figures mode]
[2] @F [carriage return]
[3] &F [line feed]
[4] K4096F [null char]
[Variable]
[5] PF [number to be printed]
[Enter with acc = 0]
[6] O1@ [set teleprinter to figures]
[7] U5@ [update number, initially 0]
TF [also to 0F for printing]
[9] A9@ G64F [call print soubroutine]
O2@ O3@ [print CR, LF]
A5@ A@ [load number, add 1]
E7@ [loop until number overflows and becomes negative]
O4@ [done; print null to flush teleprinter buffer]
ZF [halt the machine]
E6Z [define entry point]
PF [acc = 0 on entry]
[end]
- Output:
0 1 2 3 4 5 6 7 10 [...] 177775 177776 177777
Elixir
Stream.iterate(0,&(&1+1)) |> Enum.each(&IO.puts Integer.to_string(&1,8))
or
Stream.unfold(0, fn n ->
IO.puts Integer.to_string(n,8)
{n,n+1}
end) |> Stream.run
or
f = fn ff,i -> :io.fwrite "~.8b~n", [i]; ff.(ff, i+1) end
f.(f, 0)
Emacs Lisp
Displays in the message area interactively, or to standard output under -batch
.
(dotimes (i most-positive-fixnum) ;; starting from 0
(message "%o" i))
Erlang
The fun is copied from Integer sequence#Erlang. I changed the display format.
F = fun(FF, I) -> io:fwrite("~.8B~n", [I]), FF(FF, I + 1) end.
Use like this:
F( F, 0 ).
Euphoria
integer i
i = 0
while 1 do
printf(1,"%o\n",i)
i += 1
end while
Output:
... 6326 6327 6330 6331 6332 6333 6334 6335 6336 6337
F#
let rec countInOctal num : unit =
printfn "%o" num
countInOctal (num + 1)
countInOctal 1
Factor
USING: kernel math prettyprint ;
0 [ dup .o 1 + t ] loop
Forth
Using INTS from Integer sequence#Forth
: octal ( -- ) 8 base ! ; \ where unavailable
octal ints
Fortran
program Octal
implicit none
integer, parameter :: i64 = selected_int_kind(18)
integer(i64) :: n = 0
! Will stop when n overflows from
! 9223372036854775807 to -92233720368547758078 (1000000000000000000000 octal)
do while(n >= 0)
write(*, "(o0)") n
n = n + 1
end do
end program
FreeBASIC
' FB 1.05.0 Win64
Dim ub As UByte = 0 ' only has a range of 0 to 255
Do
Print Oct(ub, 3)
ub += 1
Loop Until ub = 0 ' wraps around to 0 when reaches 256
Print
Print "Press any key to quit"
Sleep
Frink
i = 0
while true
{
println[i -> octal]
i = i + 1
}
Futhark
Futhark cannot print. Instead we produce an array of integers that look like octal numbers when printed in decimal.
fun octal(x: int): int =
loop ((out,mult,x) = (0,1,x)) = while x > 0 do
let digit = x % 8
let out = out + digit * mult
in (out, mult * 10, x / 8)
in out
fun main(n: int): [n]int =
map octal (iota n)
FutureBasic
window 1, @"Count in Octal"
defstr word
dim as short i
text ,,,,, 50
print @"dec",@"oct"
for i = 0 to 25
print i,oct(i)
next
HandleEvents
Output:
dec oct 0 00 1 01 2 02 3 03 4 04 5 05 6 06 7 07 8 10 9 11 10 12 11 13 12 14 13 15 14 16 15 17 16 20 17 21 18 22 19 23 20 24 21 25 22 26 23 27 24 30 25 31
Go
package main
import (
"fmt"
"math"
)
func main() {
for i := int8(0); ; i++ {
fmt.Printf("%o\n", i)
if i == math.MaxInt8 {
break
}
}
}
Output:
0 1 2 3 4 5 6 7 10 11 12 ... 175 176 177
Note that to use a different integer type, code must be changed in two places. Go has no way to query a type for its maximum value. Example:
func main() {
for i := uint16(0); ; i++ { // type specified here
fmt.Printf("%o\n", i)
if i == math.MaxUint16 { // maximum value for type specified here
break
}
}
}
Output:
... 177775 177776 177777
Note also that if floating point types are used for the counter, loss of precision will prevent the program from from ever reaching the maximum value. If you stretch interpretation of the task wording "maximum value" to mean "maximum value of contiguous integers" then the following will work:
import "fmt"
func main() {
for i := 0.; ; {
fmt.Printf("%o\n", int64(i))
/* uncomment to produce example output
if i == 3 {
i = float64(1<<53 - 4) // skip to near the end
fmt.Println("...")
} */
next := i + 1
if next == i {
break
}
i = next
}
}
Output, with skip uncommented:
0 1 2 3 ... 377777777777777775 377777777777777776 377777777777777777 400000000000000000
Big integers have no maximum value, but the Go runtime will panic when memory allocation fails. The deferred recover here allows the program to terminate silently should the program run until this happens.
import (
"big"
"fmt"
)
func main() {
defer func() {
recover()
}()
one := big.NewInt(1)
for i := big.NewInt(0); ; i.Add(i, one) {
fmt.Printf("%o\n", i)
}
}
Output:
0 1 2 3 4 5 6 7 10 11 12 13 14 ...
Groovy
Size-limited solution:
println 'decimal octal'
for (def i = 0; i <= Integer.MAX_VALUE; i++) {
printf ('%7d %#5o\n', i, i)
}
Unbounded solution:
println 'decimal octal'
for (def i = 0g; true; i += 1g) {
printf ('%7d %#5o\n', i, i)
}
Output:
decimal octal 0 00 1 01 2 02 3 03 4 04 5 05 6 06 7 07 8 010 9 011 10 012 11 013 12 014 13 015 14 016 15 017 16 020 17 021 ...
Haskell
import Numeric (showOct)
main :: IO ()
main =
mapM_
(putStrLn . flip showOct "")
[1 .. maxBound :: Int]
Icon and Unicon
link convert # To get exbase10 method
procedure main()
limit := 8r37777777777
every write(exbase10(seq(0)\limit, 8))
end
J
Solution:
disp=. ([ echo) 1 ": 8&#.inv
(1 + disp)^:_]0x
The full result is not displayable, by design. This could be considered a bug, but is an essential part of this task. Here's how it starts:
(1 + disp)^:_]0x
0
1
2
3
4
5
6
7
10
11
...
The important part of this code is 8&#.inv which converts numbers from internal representation to a sequence of base 8 digits. (We then convert this sequence to characters - this gives us the octal values we want to display.)
So then we define disp as a word which displays its argument in octal and returns its argument as its result (unchanged).
Finally, the ^:_
clause tells J to repeat this function forever, with (1 + disp)
adding 1 to the result each time it is displayed (or at least that clause tells J to keep repeating that operation until it gives the same value back twice in a row - which won't happen - or to stop when the machine stops - like if the power is turned off - or if J is shut down - or...).
We use arbitrary precision numbers, not because there's any likelihood that fixed width numbers would ever overflow, but to emphasize that this thing is going to have to be shut down by some mechanism outside the program.
That said... note that what we are doing here is counting using an internal representation and converting that to octal for display. If we instead wanted to add 1 to a value provided to us in octal and provide the result in octal, we might instead use >:
(add 1) and wrap it in &.(8&#.)
(convert argument from octal and use inverse on result) with a list of digits representing our octal number. For example:
>:&.(8&#.)7 6
7 7
>:&.(8&#.)7 7
1 0 0
>:&.(8&#.)1 0 0
1 0 1
Jakt
fn main() {
for i in (0..) {
println("{:o}", i)
}
}
Janet
(loop [i :range [0 math/int-max]]
(printf "%o" i))
Java
void printCount() {
for (int value = 0; value <= 20; value++) {
/* the 'o' specifier will print the octal integer */
System.out.printf("%o%n", value);
}
}
0 1 2 3 4 5 6 7 10 11 12 13 14 15 16 17 20 21 22 23 24
An alternate implementation
public class Count{
public static void main(String[] args){
for(int i = 0;i >= 0;i++){
System.out.println(Integer.toOctalString(i)); //optionally use "Integer.toString(i, 8)"
}
}
}
JavaScript
for (var n = 0; n < 1e14; n++) { // arbitrary limit that's not too big
document.writeln(n.toString(8)); // not sure what's the best way to output it in JavaScript
}
Joy
DEFINE
digit == "01234567" of;
oct == "\n" [pop 7 >] [[8 div digit] dip cons] while swap digit swons.
0 [0 >=] [dup oct putchars succ] while pop.
jq
Here we use JSON strings of octal digits to represent octal numbers, and therefore there is no language-defined upper bound for the problem. We are careful therefore to select an algorithm that will continue indefinitely so long as there are sufficient physical resources. This is done by framing the problem so that we can use jq's `recurse(_)`.
# generate octals as strings, beginning with "0"
def octals:
# input and output: array of octal digits in reverse order
def octal_add1:
[foreach (.[], null) as $d ({carry: 1};
if $d then ($d + .carry ) as $r
| if $r > 7
then {carry: 1, emit: ($r - 8)}
else {carry: 0, emit: $r }
end
elif (.carry == 0) then .emit = null
else .emit = .carry
end;
select(.emit).emit)];
[0] | recurse(octal_add1) | reverse | join("");
octals
To print the octal strings without quotation marks, invoke jq with the -r command-line option.
Julia
for i in one(Int64):typemax(Int64)
print(oct(i), " ")
sleep(0.1)
end
I slowed the loop down with a sleep
to make it possible to see the result without being swamped.
- Output:
1 2 3 4 5 6 7 10 11 12 13 14 15 16 17 20 21 22 23 24 25 26 27 30 31 32 33 34 35 36 ^C
Klingphix
include ..\Utilitys.tlhy
:octal "" >ps [dup 7 band tostr ps> chain >ps 8 / int] [dup abs 0 >] while ps> tonum bor ;
( 0 10 ) sequence @octal map pstack
" " input
- Output:
((0, 1, 2, 3, 4, 5, 6, 7, 10, 11, 12))
Kotlin
// version 1.1
// counts up to 177 octal i.e. 127 decimal
fun main(args: Array<String>) {
(0..Byte.MAX_VALUE).forEach { println("%03o".format(it)) }
}
- Output:
First ten lines:
000 001 002 003 004 005 006 007 010 011
LabVIEW
LabVIEW contains a Number to Octal String function. The following image shows the front panel and block diagram.
Lang
$i = 0
while($i >= 0) {
fn.println(fn.toTextBase($i, 8))
$i += 1
}
Lang5
'%4o '__number_format set
0 do dup 1 compress . "\n" . 1 + loop
langur
We use an arbitrary limit for this.
We use the :8x interpolation modifier to create a string in base 8 (may use base 2 to 36).
val limit = 70
for i of limit {
writeln "10x{{i}} == 8x{{i:8x}}"
}
- Output:
10x0 == 8x0 10x1 == 8x1 10x2 == 8x2 10x3 == 8x3 10x4 == 8x4 10x5 == 8x5 10x6 == 8x6 10x7 == 8x7 10x8 == 8x10 10x9 == 8x11 10x10 == 8x12 10x11 == 8x13 10x12 == 8x14 10x13 == 8x15 10x14 == 8x16 10x15 == 8x17 10x16 == 8x20 10x17 == 8x21 10x18 == 8x22 10x19 == 8x23 10x20 == 8x24 10x21 == 8x25 10x22 == 8x26 10x23 == 8x27 10x24 == 8x30 10x25 == 8x31 10x26 == 8x32 10x27 == 8x33 10x28 == 8x34 10x29 == 8x35 10x30 == 8x36 10x31 == 8x37 10x32 == 8x40 10x33 == 8x41 10x34 == 8x42 10x35 == 8x43 10x36 == 8x44 10x37 == 8x45 10x38 == 8x46 10x39 == 8x47 10x40 == 8x50 10x41 == 8x51 10x42 == 8x52 10x43 == 8x53 10x44 == 8x54 10x45 == 8x55 10x46 == 8x56 10x47 == 8x57 10x48 == 8x60 10x49 == 8x61 10x50 == 8x62 10x51 == 8x63 10x52 == 8x64 ... 10x69982 == 8x210536 10x69983 == 8x210537 10x69984 == 8x210540 10x69985 == 8x210541 10x69986 == 8x210542 10x69987 == 8x210543 10x69988 == 8x210544 10x69989 == 8x210545 10x69990 == 8x210546 10x69991 == 8x210547 10x69992 == 8x210550 10x69993 == 8x210551 10x69994 == 8x210552 10x69995 == 8x210553 10x69996 == 8x210554 10x69997 == 8x210555 10x69998 == 8x210556 10x69999 == 8x210557 10x70000 == 8x210560
LFE
(: lists foreach
(lambda (x)
(: io format '"~p~n" (list (: erlang integer_to_list x 8))))
(: lists seq 0 2000))
Liberty BASIC
Terminate these ( essentially, practically) infinite loops by hitting <CTRL<BRK>
'the method used here uses the base-conversion from RC Non-decimal radices/Convert
'to terminate hit <CTRL<BRK>
global alphanum$
alphanum$ ="01234567"
i =0
while 1
print toBase$( 8, i)
i =i +1
wend
end
function toBase$( base, number) ' Convert decimal variable to number string.
maxIntegerBitSize =len( str$( number))
toBase$ =""
for i =10 to 1 step -1
remainder =number mod base
toBase$ =mid$( alphanum$, remainder +1, 1) +toBase$
number =int( number /base)
if number <1 then exit for
next i
toBase$ =right$( " " +toBase$, 10)
end function
As suggested in LOGO, it is easy to work on a string representation too.
op$ = "00000000000000000000"
L =len( op$)
while 1
started =0
for i =1 to L
m$ =mid$( op$, i, 1)
if started =0 and m$ ="0" then print " "; else print m$;: started =1
next i
print
for i =L to 1 step -1
p$ =mid$( op$, i, 1)
if p$ =" " then v =0 else v =val( p$)
incDigit = v +carry
if i =L then incDigit =incDigit +1
if incDigit >=8 then
replDigit =incDigit -8
carry =1
else
replDigit =incDigit
carry =0
end if
op$ =left$( op$, i -1) +chr$( 48 +replDigit) +right$( op$, L -i)
next i
wend
end
Or use a recursive listing of permutations with the exception that the first digit is not 0 (unless listing single-digit numbers). For each digit-place, list numbers with 0-7 in the next digit-place.
i = 0
while 1
call CountOctal 0, i, i > 0
i = i + 1
wend
sub CountOctal value, depth, startValue
value = value * 10
for i = startValue to 7
if depth > 0 then
call CountOctal value + i, depth - 1, 0
else
print value + i
end if
next i
end sub
Logo
No built-in octal-formatting, so it's probably more efficient to just manually increment a string than to increment a number and then convert the whole thing to octal every time we print. This also lets us keep counting as long as we have room for the string.
to increment_octal :n
ifelse [empty? :n] [
output 1
] [
local "last
make "last last :n
local "butlast
make "butlast butlast :n
make "last sum :last 1
ifelse [:last < 8] [
output word :butlast :last
] [
output word (increment_octal :butlast) 0
]
]
end
make "oct 0
while ["true] [
print :oct
make "oct increment_octal :oct
]
LOLCODE
LOLCODE has no conception of octal numbers, but we can use string concatenation (SMOOSH) and basic arithmetic to accomplish the task.
HAI 1.3
HOW IZ I octal YR num
I HAS A digit, I HAS A oct ITZ ""
IM IN YR octalizer
digit R MOD OF num AN 8
oct R SMOOSH digit oct MKAY
num R QUOSHUNT OF num AN 8
NOT num, O RLY?
YA RLY, FOUND YR oct
OIC
IM OUTTA YR octalizer
IF U SAY SO
IM IN YR printer UPPIN YR num
VISIBLE I IZ octal YR num MKAY
IM OUTTA YR printer
KTHXBYE
Lua
for l=1,2147483647 do
print(string.format("%o",l))
end
M2000 Interpreter
Module CountInOctal {
class OctalDigitsCounter {
private:
dim m() as byte
public:
Last as boolean
Value {
string s1
integer i
for i=len(.m()) to 1
s1=s1+.m(i)
next
=s1
}
Set (s as OctalDigitsCounter) {
.m()=s.m()
.Last<=false
}
Operator "++" {
integer z=0, i=1, h=len(.m()), L=h+1
if valid(.last) else error "problem"
while i<L
if .m(i)>=7% then z++:.m(i)=0:i++ else L=i:.m(i)++
end while
if z=H then .last<=true
}
class:
Module OctalDigitsCounter(Digits as long) {
if Digits<1 then Error "Wrong number for Digits"
dim .m(1 to Digits)
}
}
// set digits to number of character width of console
k=OctalDigitsCounter(width)
// or set to 3 digits
Rem : k=OctalDigitsCounter(3)
// you can press Esc to stop it
escape off
refresh 100 // to synchronize the scrolling, so we always see the numbers not the empty line
while not k.last
print part $(0), k // print without new line, $(0) used for non proportional character printing
refresh // so we do a refresh here before the scrolling which do the next print statement
print
k++
if keypress(27) then exit
end while
print
escape on
print "done"
}
CountInOctal
M4
define(`forever',
`ifelse($#,0,``$0'',
`pushdef(`$1',$2)$4`'popdef(`$1')$0(`$1',eval($2+$3),$3,`$4')')')dnl
forever(`y',0,1, `eval(y,8)
')
Maple
octcount := proc (n)
seq(printf("%a \n", convert(i, octal)), i = 1 .. n);
end proc;
MACRO-10
title OCTAL - Count in octal.
subttl PDP-10 assembly (MACRO-10 on TOPS-20). KJX 2022.
search monsym,macsym
comment \
If you want to see the overflow happening without waiting for
too long, change "movei b,1" to "move b,[377777,,777770]".
\
a=:1 ;Names for accumulators.
b=:2
c=:3
define crlf <tmsg <
>> ;Macro to print newline.
start:: reset% ;Initialize process.
movei b,1 ;B is the counter.
movei c,^d8 ;Octal output (nout%).
do.
movei a,.priou ;Use standard-output (nout%).
nout% ;Print number in B.
jrst [ tmsg <Output error.> ; NOUT can fail, print err-msg
jrst endprg ] ; and stop in that case.
crlf ;Print newline.
aos b ;Add one to B.
jfcl 10,[ tmsg <Arithmetic Overflow (AROV).> ;Handle overflow.
jrst endprg ]
loop. ;Do again.
enddo.
endprg: haltf% ;Halt program.
jrst start ;Allow continue-command.
end start
Mathematica /Wolfram Language
x=0;
While[True,Print[BaseForm[x,8];x++]
MATLAB / Octave
n = 0;
while (1)
dec2base(n,8)
n = n+1;
end;
Or use printf:
n = 0;
while (1)
printf('%o\n',n);
n = n+1;
end;
If a predefined sequence should be displayed, one can use
seq = 1:100;
dec2base(seq,8)
or
printf('%o\n',seq);
Mercury
:- module count_in_octal.
:- interface.
:- import_module io.
:- pred main(io::di, io::uo) is det.
:- implementation.
:- import_module int, list, string.
main(!IO) :-
count_in_octal(0, !IO).
:- pred count_in_octal(int::in, io::di, io::uo) is det.
count_in_octal(N, !IO) :-
io.format("%o\n", [i(N)], !IO),
count_in_octal(N + 1, !IO).
min
min has no support for octal or base conversion (it is a minimalistic language, after all) so we need to do that ourselves.
(
(dup 0 ==) (pop () 0 shorten)
(((8 mod) (8 div)) cleave) 'cons linrec
reverse 'print! foreach newline
) :octal
0 (dup octal succ)
9.223e18 int times ; close to max int value
MiniScript
toOctal = function(n)
result = ""
while n != 0
octet = n % 8
n = floor(n / 8)
result = octet + result
end while
return result
end function
maxnum = 10 ^ 15 - 1
i = 0
while i < maxnum
i += 1
print i + " = " + toOctal(i)
end while
МК-61/52
ИП0 П1 1 0 / [x] П1 Вx {x} 1
0 * 7 - x=0 21 ИП1 x#0 28 БП
02 ИП0 1 + П0 С/П БП 00 ИП0 lg
[x] 1 + 10^x П0 С/П БП 00
Modula-2
MODULE octal;
IMPORT InOut;
VAR num : CARDINAL;
BEGIN
num := 0;
REPEAT
InOut.WriteOct (num, 12); InOut.WriteLn;
INC (num)
UNTIL num = 0
END octal.
Nanoquery
Even though all integers are arbitrary precision, the maximum value that can be represented as octal using the format function is 2^64 - 1. Once this value is reached, the program terminates.
i = 0
while i < 2^64
println format("%o", i)
i += 1
end
NetRexx
/* NetRexx */
options replace format comments java crossref symbols binary
import java.math.BigInteger
-- allow an option to change the output radix.
parse arg radix .
if radix.length() == 0 then radix = 8
k_ = BigInteger
k_ = BigInteger.ZERO
loop forever
say k_.toString(int radix)
k_ = k_.add(BigInteger.ONE)
end
NewLISP
; file: ocount.lsp
; url: http://rosettacode.org/wiki/Count_in_octal
; author: oofoe 2012-01-29
; Although NewLISP itself uses a 64-bit integer representation, the
; format function relies on underlying C library's printf function,
; which can only handle a 32-bit octal number on this implementation.
(for (i 0 (pow 2 32)) (println (format "%o" i)))
(exit)
Sample output:
0 1 2 3 4 5 6 7 10 11 12 ...
Nim
import strutils
for i in 0 ..< int.high:
echo toOct(i, 16)
Nu
for n in 0.. { $n | (fmt).octal | print }
Oberon-2
MODULE CountInOctal;
IMPORT
NPCT:Tools,
Out := NPCT:Console;
VAR
i: INTEGER;
BEGIN
FOR i := 0 TO MAX(INTEGER) DO;
Out.String(Tools.IntToOct(i));Out.Ln
END
END CountInOctal.
- Output:
00000000000 00000000001 00000000002 00000000003 00000000004 00000000005 00000000006 00000000007 00000000010 00000000011 00000000012 00000000013 00000000014 00000000015 00000000016 00000000017 00000000020 00000000021 ... 00000077757 00000077760 00000077761 00000077762 00000077763 00000077764 00000077765 00000077766 00000077767 00000077770 00000077771 00000077772 00000077773 00000077774 00000077775 00000077776 00000077777
OCaml
let () =
for i = 0 to max_int do
Printf.printf "%o\n" i
done
- Output:
0 1 2 3 4 5 6 7 10 11 12 ... 7777777775 7777777776 7777777777
PARI/GP
Both versions will count essentially forever; the universe will succumb to proton decay long before the counter rolls over even in the 32-bit version.
Manual:
oct(n)=n=binary(n);if(#n%3,n=concat([[0,0],[0]][#n%3],n));forstep(i=1,#n,3,print1(4*n[i]+2*n[i+1]+n[i+2]));print;
n=0;while(1,oct(n);n++)
Automatic:
n=0;while(1,printf("%o\n",n);n++)
Pascal
See Delphi or
old string incrementer for Turbo Pascal transformed, same as in http://rosettacode.org/wiki/Count_in_octal#Logo, about 100x times faster than Dephi-Version, with the abilty to used preformated strings leading zeroes. Added a Bit fiddling Version IntToOctString, nearly as fast.
program StrAdd;
{$Mode Delphi}
{$Optimization ON}
uses
sysutils;//IntToStr
const
maxCntOct = (SizeOf(NativeUint)*8+(3-1)) DIV 3;
procedure IntToOctString(i: NativeUint;var res:Ansistring);
var
p : array[0..maxCntOct] of byte;
c,cnt: LongInt;
begin
cnt := maxCntOct;
repeat
c := i AND 7;
p[cnt] := (c+Ord('0'));
dec(cnt);
i := i shr 3;
until (i = 0);
i := cnt+1;
cnt := maxCntOct-cnt;
//most time consuming with Ansistring
//call fpc_ansistr_unique
setlength(res,cnt);
move(p[i],res[1],cnt);
end;
procedure IncStr(var s:String;base:NativeInt);
var
le,c,dg:nativeInt;
begin
le := length(s);
IF le = 0 then
Begin
s := '1';
EXIT;
end;
repeat
dg := ord(s[le])-ord('0') +1;
c := ord(dg>=base);
dg := dg-(base AND (-c));
s[le] := chr(dg+ord('0'));
dec(le);
until (c = 0) or (le<=0);
if (c = 1) then
begin
le := length(s);
setlength(s,le+1);
move(s[1],s[2],le);
s[1] := '1';
end;
end;
const
MAX = 8*8*8*8*8*8*8*8*8;//8^9
var
sOct,
s : AnsiString;
i : nativeInt;
T1,T0: TDateTime;
Begin
sOct := '';
For i := 1 to 16 do
Begin
IncStr(sOct,8);
writeln(i:10,sOct:10);
end;
writeln;
For i := 1 to 16 do
Begin
IntToOctString(i,s);
writeln(i:10,s:10);
end;
sOct := '';
T0 := time;
For i := 1 to MAX do
IncStr(sOct,8);
T0 := (time-T0)*86400;
writeln(sOct);
T1 := time;
For i := 1 to MAX do
IntToOctString(i,s);
T1 := (time-T1)*86400;
writeln(s);
writeln;
writeln(MAX);
writeln('IncStr ',T0:8:3);
writeln('IntToOctString ',T1:8:3);
end.
- Output:
1 1 2 2 3 3 4 4 5 5 6 6 7 7 8 10 9 11 10 12 11 13 12 14 13 15 14 16 15 17 16 20 1 1 2 2 3 3 4 4 5 5 6 6 7 7 8 10 9 11 10 12 11 13 12 14 13 15 14 16 15 17 16 20 1000000000 1000000000 134217728 IncStr 0.944 secs IntToOctString 2.218 secs
A recursive approach
program OctalCount;
{$mode objfpc}{$H+}
var
i : integer;
// display n in octal on console
procedure PutOctal(n : integer);
var
digit, n3 : integer;
begin
n3 := n shr 3;
if n3 <> 0 then PutOctal(n3);
digit := n and 7;
write(digit);
end;
// count in octal until integer overflow
begin
i := 1;
while i > 0 do
begin
PutOctal(i);
writeln;
i := i + 1;
end;
readln;
end.
- Output:
Showing last 10 lines of output
17777777766 17777777767 17777777770 17777777771 17777777772 17777777773 17777777774 17777777775 17777777776 17777777777
PascalABC.NET
##
for var i:=0 to 20 do
Println(Convert.ToString(i,8));
- Output:
0 1 2 3 4 5 6 7 10 11 12 13 14 15 16 17 20 21 22 23 24
Perl
Since task says "system register", I take it to mean "no larger than machine native integer limit":
use POSIX;
printf "%o\n", $_ for (0 .. POSIX::UINT_MAX);
Otherwise:
use bigint;
my $i = 0;
printf "%o\n", $i++ while 1
The above count in binary or decimal and convert to octal. This actually counts in octal. It will run forever or until the universe ends, whichever comes first.
#!/usr/bin/perl
$_ = 0;
s/([^7])?(7*)$/ $1 + 1 . $2 =~ tr!7!0!r /e while print "$_\n";
Phix
without javascript_semantics integer i = 0 constant ESC = #1B while not find(get_key(),{ESC,'q','Q'}) do printf(1,"%o\n",i) i += 1 end while
See Integer_sequence#Phix for something that will run in a browser, obviously use "%o" instead of "%d" to make it display octal numbers, or more accurately in that case, mpz_get_str(i,8).
PHP
<?php
for ($n = 0; is_int($n); $n++) {
echo decoct($n), "\n";
}
?>
Picat
Ways to convert to octal numbers:
to_oct_string(N)
to_radix_string(N,8)
printf("%o\n",N)
go =>
gen(N),
println(to_oct_string(N)),
fail.
gen(I) :-
gen(0, I).
gen(I, I).
gen(I, J) :-
I2 is I + 1,
gen(I2, J).
- Output:
0 1 2 3 4 5 6 7 10 11 ... 17615737040105402212262317777777776 17615737040105402212262317777777777 17615737040105402212262320000000000 17615737040105402212262320000000001 17615737040105402212262320000000002 <Ctrl-C>
PicoLisp
(for (N 0 T (inc N))
(prinl (oct N)) )
Pike
int i=1;
while(true)
write("0%o\n", i++);
- Output:
01 02 ...
PL/I
Version 1:
/* Do the actual counting in octal. */
count: procedure options (main);
declare v(5) fixed(1) static initial ((5)0);
declare (i, k) fixed;
do k = 1 to 999;
call inc;
put skip edit ( (v(i) do i = 1 to 5) ) (f(1));
end;
inc: proc;
declare (carry, i) fixed binary;
carry = 1;
do i = 5 to 1 by -1;
v(i) = v(i) + carry;
if v(i) > 7 then
do; v(i) = v(i) - 8; if i = 1 then stop; carry = 1; end;
else
carry = 0;
end;
end inc;
end count;
Version 2:
count: procedure options (main); /* 12 Jan. 2014 */
declare (i, j) fixed binary;
do i = 0 upthru 2147483647;
do j = 30 to 0 by -3;
put edit (iand(isrl(i, j), 7) ) (f(1));
end;
put skip;
end;
end count;
- Output:
(End of) Output of version 1 00000001173 00000001174 00000001175 00000001176 00000001177 00000001200 00000001201 00000001202 00000001203 00000001204 00000001205 00000001206 00000001207 00000001210 00000001211 00000001212 00000001213 00000001214 00000001215 00000001216
PL/I-80
If you only need to count, and aren't bothered by leading zeroes in the output, this will do the trick simply and with a minimum of fuss.
octal_count:
procedure options (main);
dcl i fixed;
i = 1;
do while (i ^= 0);
put skip edit (unspec(i)) (b3);
i = i + 1;
end;
end octal_count;
- Output:
First and last 10 numbers of output
000001 000002 000003 000004 000005 000006 000007 000010 000011 000012 ... 177766 177767 177770 177771 177772 177773 177774 177775 177776 177777
But a general purpose function to return the octal representation of an integer value as a string (similar to the OCT$ function in many BASICs) may prove more useful.
octal_count:
procedure options (main);
dcl i fixed;
i = 1;
do while (i ^= 0);
put skip list (octal(i));
i = i + 1;
end;
stop;
octal:
procedure (n) returns (char(6) varying);
dcl
(n, m) fixed,
s char(6) varying;
/* n is passed by reference, so make a local copy */
m = n;
s = '';
do while (m > 0);
s = ascii(mod(m,8) + rank('0')) || s;
m = m / 8;
end;
return (s);
end octal;
end octal_count;
- Output:
First and last 10 numbers of output
1 2 3 4 5 6 7 10 11 12 ... 77766 77767 77770 77771 77772 77773 77774 77775 77776 77777
PL/M
100H: /* PRINT INTEGERS IN OCTAL */
BDOS: PROCEDURE( FN, ARG ); /* CP/M BDOS SYSTEM CALL */
DECLARE FN BYTE, ARG ADDRESS;
GOTO 5;
END BDOS;
PR$CHAR: PROCEDURE( C ); DECLARE C BYTE; CALL BDOS( 2, C ); END;
PR$NL: PROCEDURE; CALL PR$CHAR( 0DH ); CALL PR$CHAR( 0AH ); END;
PR$OCTAL: PROCEDURE( N );
DECLARE N ADDRESS;
DECLARE V ADDRESS, O$STR( 7 ) BYTE, W BYTE;
V = N;
O$STR( W := 0 ) = '0' + ( V AND 7 );
DO WHILE( ( V := SHR( V, 3 ) ) > 0 );
O$STR( W := W + 1 ) = '0' + ( V AND 7 );
END;
W = W + 1;
DO WHILE( W <> 0 );
CALL PR$CHAR( O$STR( W := W - 1 ) );
END;
END PR$OCTAL;
DECLARE N ADDRESS;
N = 0;
CALL PR$OCTAL( N );
CALL PR$NL;
DO WHILE( ( N := N + 1 ) > 0 ); /* AFTER 65535 N WILL WRAP 'ROUND TO 0 */
CALL PR$OCTAL( N );
CALL PR$NL;
END;
EOF
PowerShell
[int64]$i = 0
While ( $True )
{
[Convert]::ToString( ++$i, 8 )
}
Prolog
Rather than just printing out a list of octal numbers, this code will generate a sequence. octal/1 can also be used to tell if a number is a valid octal number or not. octalize will keep producing and printing octal number, there is no limit.
o(O) :- member(O, [0,1,2,3,4,5,6,7]).
octal([O]) :- o(O).
octal([A|B]) :-
octal(O),
o(T),
append(O, [T], [A|B]),
dif(A, 0).
octalize :-
forall(
octal(X),
(maplist(write, X), nl)
).
PureBasic
Procedure.s octal(n.q)
Static Dim digits(20)
Protected i, j, result.s
For i = 0 To 20
digits(i) = n % 8
n / 8
If n < 1
For j = i To 0 Step -1
result + Str(digits(j))
Next
Break
EndIf
Next
ProcedureReturn result
EndProcedure
Define n.q
If OpenConsole()
While n >= 0
PrintN(octal(n))
n + 1
Wend
Print(#CRLF$ + #CRLF$ + "Press ENTER to exit"): Input()
CloseConsole()
EndIf
Sample output:
0 1 2 3 4 5 6 7 10 11 12 ... 777777777777777777767 777777777777777777770 777777777777777777771 777777777777777777772 777777777777777777773 777777777777777777774 777777777777777777775 777777777777777777776 777777777777777777777
Python
Python2
import sys
for n in xrange(sys.maxint):
print oct(n)
Python3
# Python3 count_in_oct.py by Xing216
import sys
for n in range(sys.maxsize):
print(oct(n))
QB64
Dim As Integer iNum, Icount
Dim sMax As String
sMax = ""
Do While Val(sMax) <= 0 Or Val(sMax) > 32767
Input "Please type a value from 1 to 32767 ", sMax
Loop
iNum = Val(sMax)
For Icount = 0 To iNum Step 1
Print Oct$(Icount)
Next
End
REM also QBasic example runs under QB64
Quackery
8 base put
0 [ dup echo cr 1+ again ]
Racket
#lang racket
(for ([i (in-naturals)])
(displayln (number->string i 8)))
(Racket has bignums, so this loop will never end.)
Raku
(formerly Perl 6)
say .base(8) for ^Inf;
- Output:
0
Here we arbitrarily show as many lines of output as there are lines in the program. :-)
REXX
If this REXX program wouldn't be stopped, it would count forever.
The technique used is to convert the decimal number to binary, and separate the binary digits in groups of three, and then convert those binary groups (numbers) to decimal.
/*REXX program counts in octal until the number exceeds the number of program statements*/
/*┌────────────────────────────────────────────────────────────────────┐
│ Count all the protons (and electrons!) in the universe. │
│ │
│ According to Sir Arthur Eddington in 1938 at his Tamer Lecture at │
│ Trinity College (Cambridge), he postulated that there are exactly │
│ │
│ 136 ∙ 2^256 │
│ │
│ protons in the universe, and the same number of electrons, which │
│ is equal to around 1.57477e+79. │
│ │
│ [Although, a modern estimate is around 10^80.] │
└────────────────────────────────────────────────────────────────────┘*/
numeric digits 100000 /*handle almost any sized big numbers. */
numIn= right('number in', 20) /*used for indentation of the output. */
w= length( sourceline() ) /*used for formatting width of numbers.*/
do #=0 to 136 * (2**256) /*Sir Eddington, here we come ! */
!= x2b( d2x(#) )
_= right(!, 3 * (length(_) % 3 + 1), 0)
o=
do k=1 to length(_) by 3
o= o'0'substr(_, k, 3)
end /*k*/
say numIn 'base ten = ' right(#,w) numIn "octal = " right( b2x(o) + 0, w + w)
if #>sourceline() then leave /*stop if # of protons > pgm statements*/
end /*#*/
/*stick a fork in it, we're all done. */
- output:
number in base ten = 0 number in octal = 0 number in base ten = 1 number in octal = 1 number in base ten = 2 number in octal = 2 number in base ten = 3 number in octal = 3 number in base ten = 4 number in octal = 4 number in base ten = 5 number in octal = 5 number in base ten = 6 number in octal = 6 number in base ten = 7 number in octal = 7 number in base ten = 8 number in octal = 10 number in base ten = 9 number in octal = 11 number in base ten = 10 number in octal = 12 number in base ten = 11 number in octal = 13 number in base ten = 12 number in octal = 14 number in base ten = 13 number in octal = 15 number in base ten = 14 number in octal = 16 number in base ten = 15 number in octal = 17 number in base ten = 16 number in octal = 20 number in base ten = 17 number in octal = 21 number in base ten = 18 number in octal = 22 number in base ten = 19 number in octal = 23 number in base ten = 20 number in octal = 24 number in base ten = 21 number in octal = 25 number in base ten = 22 number in octal = 26 number in base ten = 23 number in octal = 27 number in base ten = 24 number in octal = 30 number in base ten = 25 number in octal = 31 number in base ten = 26 number in octal = 32 number in base ten = 27 number in octal = 33 number in base ten = 28 number in octal = 34 number in base ten = 29 number in octal = 35 number in base ten = 30 number in octal = 36 number in base ten = 31 number in octal = 37 number in base ten = 32 number in octal = 40 number in base ten = 33 number in octal = 41
Ring
size = 30
for n = 1 to size
see octal(n) + nl
next
func octal m
output = ""
w = m
while fabs(w) > 0
oct = w & 7
w = floor(w / 8)
output = string(oct) + output
end
return output
RPL
This will run an octal counter at the top of the screen from 1 to n, n being entered as an argument.
≪ OCT CLLCD 1 SWAP FOR j j R→B 1 DISP 0.2 WAIT NEXT CLMF ≫ 'CLOCT' STO
Ruby
n = 0
loop do
puts "%o" % n
n += 1
end
# or
for n in (0..)
puts n.to_s(8)
end
# or
0.upto(1/0.0) do |n|
printf "%o\n", n
end
# version 2.1 later
0.step do |n|
puts format("%o", n)
end
Run BASIC
input "Begin number:";b
input " End number:";e
for i = b to e
print i;" ";toBase$(8,i)
next i
end
function toBase$(base,base10)
for i = 10 to 1 step -1
toBase$ = str$(base10 mod base) +toBase$
base10 = int(base10 / base)
if base10 < 1 then exit for
next i
end function
Rust
fn main() {
for i in 0..std::usize::MAX {
println!("{:o}", i);
}
}
Salmon
Salmon has built-in unlimited-precision integer arithmetic, so these examples will all continue printing octal values indefinitely, limited only by the amount of memory available (it requires O(log(n)) bits to store an integer n, so if your computer has 1 GB of memory, it will count to a number with on the order of octal digits).
iterate (i; [0...+oo])
printf("%o%\n", i);;
or
for (i; 0; true)
printf("%o%\n", i);;
or
variable i := 0;
while (true)
{
printf("%o%\n", i);
++i;
};
S-BASIC
Although many BASICs have a built-in OCT$ function, S-BASIC does not, so we have to supply our own
rem - return p mod q
function mod(p, q = integer) = integer
end = p - q * (p / q)
rem - return octal representation of n
function oct$(n = integer) = string
var s = string
s = ""
while n > 0 do
begin
s = chr(mod(n,8) + '0') + s
n = n / 8
end
end = s
rem - count in octal until overflow
var i = integer
i = 1
while i > 0 do
begin
print oct$(i)
i = i + 1
end
end
- Output:
Showing first and last 10 lines of output
1 2 3 4 5 6 7 10 11 12 ... 77766 77767 77770 77771 77772 77773 77774 77775 77776 77777
Scala
Stream from 0 foreach (i => println(i.toOctalString))
Scheme
(do ((i 0 (+ i 1))) (#f) (display (number->string i 8)) (newline))
Scratch
sed
This program expects one line (consisting of a non-negative octal integer) as start value:
:l
p
s/^7*$/0&/
h
y/01234567/12345670/
x
G
s/.7*\n.*\([^0]\)/\1/
bl
- Output:
$ echo 0 | sed -f count_oct.sed | head 0 1 2 3 4 5 6 7 10 11
Seed7
This example uses the radix operator to write a number in octal.
$ include "seed7_05.s7i";
const proc: main is func
local
var integer: i is 0;
begin
repeat
writeln(i radix 8);
incr(i);
until FALSE;
end func;
Sidef
var i = 0;
loop { say i++.as_oct }
Simula
BEGIN
PROCEDURE OUTOCT(N); INTEGER N;
BEGIN
PROCEDURE OCT(N); INTEGER N;
BEGIN
IF N > 0 THEN BEGIN
OCT(N//8);
OUTCHAR(CHAR(RANK('0')+MOD(N,8)));
END;
END OCT;
IF N < 0 THEN BEGIN OUTCHAR('-'); OUTOCT(-N); END
ELSE IF N = 0 THEN OUTCHAR('0')
ELSE OCT(N);
END OUTOCT;
INTEGER I;
WHILE I < MAXINT DO BEGIN
OUTINT(I,0);
OUTTEXT(" => ");
OUTOCT(I);
OUTIMAGE;
I := I+1;
END;
END.
Smalltalk
0 to:Integer infinity do:[:n |
n printOn:Stdout radix:8.
Stdout cr.
]
- Output:
1 2 3 4 5 6 7 10 11 12 13 14 15 16 17 20 21 ...
Sparkling
for (var i = 0; true; i++) {
printf("%o\n", i);
}
Standard ML
local
fun count n = (print (Int.fmt StringCvt.OCT n ^ "\n"); count (n+1))
in
val _ = count 0
end
Swift
import Foundation
func octalSuccessor(value: String) -> String {
if value.isEmpty {
return "1"
} else {
let i = value.startIndex, j = value.endIndex.predecessor()
switch (value[j]) {
case "0": return value[i..<j] + "1"
case "1": return value[i..<j] + "2"
case "2": return value[i..<j] + "3"
case "3": return value[i..<j] + "4"
case "4": return value[i..<j] + "5"
case "5": return value[i..<j] + "6"
case "6": return value[i..<j] + "7"
case "7": return octalSuccessor(value[i..<j]) + "0"
default:
NSException(name:"InvalidDigit", reason: "InvalidOctalDigit", userInfo: nil).raise();
return ""
}
}
}
var n = "0"
while strtoul(n, nil, 8) < UInt.max {
println(n)
n = octalSuccessor(n)
}
- Output:
The first few lines. anyway:
0 1 2 3 4 5 6 7 10 11 12 13 14 15 16 17 20 21 22 23
Tcl
package require Tcl 8.5; # arbitrary precision integers; we can count until we run out of memory!
while 1 {
puts [format "%llo" [incr counter]]
}
UNIX Shell
We use the bc calculator to increment our octal counter:
#!/bin/sh
num=0
while true; do
echo $num
num=`echo "obase=8;ibase=8;$num+1"|bc`
done
Using printf
Increment a decimal counter and use printf(1)
to print it in octal. Our loop stops when the counter overflows to negative.
#!/bin/sh
num=0
while test 0 -le $num; do
printf '%o\n' $num
num=`expr $num + 1`
done
Various recent shells have a bultin $(( ... ))
for arithmetic rather than running expr
, in which case
num=0
while test 0 -le $num; do
printf '%o\n' $num
num=$((num + 1))
done
VBA
With i defined as an Integer, the loop will count to 77777 (32767 decimal). Error handling added to terminate nicely on integer overflow.
Sub CountOctal()
Dim i As Integer
i = 0
On Error GoTo OctEnd
Do
Debug.Print Oct(i)
i = i + 1
Loop
OctEnd:
Debug.Print "Integer overflow - count terminated"
End Sub
VBScript
For i = 0 To 20
WScript.StdOut.WriteLine Oct(i)
Next
Vim Script
let counter = 0
while counter >= 0
echon printf("%o\n", counter)
let counter += 1
endwhile
V (Vlang)
import math
fn main() {
for i := i8(0); ; i++ {
println("${i:o}")
if i == math.max_i8 {
break
}
}
}
- Output:
0 1 2 ... 173 174 175 176 177
VTL-2
Stops at 65535, the largest integer supported by VTL-2.
1000 N=0
1010 #=2000
1020 ?=""
1030 #=N=65535*9999
1040 N=N+1
1050 #=1010
2000 R=!
2010 O=N
2020 D=1
2030 O=O/8
2040 :D)=%
2050 D=D+1
2060 #=O>1*2030
2070 E=D-1
2080 $=48+:E)
2090 E=E-1
2100 #=E>1*2080
2110 #=R
- Output:
0 1 2 3 4 5 6 7 10 11 12 ... 177775 177776 177777
Whitespace
This program prints octal numbers until the internal representation of the current integer overflows to -1; it will never do so on some interpreters.
It was generated from the following pseudo-Assembly.
push 0
; Increment indefinitely.
0:
push -1 ; Sentinel value so the printer knows when to stop.
copy 1
call 1
push 10
ochr
push 1
add
jump 0
; Get the octal digits on the stack in reverse order.
1:
dup
push 8
mod
swap
push 8
div
push 0
copy 1
sub
jn 1
pop
; Print them.
2:
dup
jn 3 ; Stop at the sentinel.
onum
jump 2
3:
pop
ret
Wren
import "./fmt" for Conv
var i = 0
while (true) {
System.print(Conv.oct(i))
i = i + 1
}
- Output:
0 1 2 3 4 5 6 7 10 11 12 13 14 15 16 17 20 21 22 23 24 ^C
XPL0
XPL0 doesn't have built-in routines to handle octal; instead it uses hex.
include c:\cxpl\codes; \intrinsic code declarations
proc OctOut(N); \Output N in octal
int N;
int R;
[R:= N&7;
N:= N>>3;
if N then OctOut(N);
ChOut(0, R+^0);
];
int I;
[I:= 0;
repeat OctOut(I); CrLf(0);
I:= I+1;
until KeyHit or I=0;
]
Example output:
0 1 2 3 4 5 6 7 10 11 12 13 14 15 16 17 20 21
zig
const std = @import("std");
const fmt = std.fmt;
const warn = std.debug.warn;
pub fn main() void {
var i: u8 = 0;
var buf: [3]u8 = undefined;
while (i < 255) : (i += 1) {
_ = fmt.formatIntBuf(buf[0..], i, 8, false, 0); // buffer, value, base, uppercase, width
warn("{}\n", buf);
}
}
Z80 Assembly
The Sega Master System's screen isn't big enough to show each number on its own line and have all the numbers be visible at the same time, so this program shows 8 per line. Hardware-specific code for loading system font, setting up video display processor, printing, etc. are omitted. Z80 Assembly doesn't have built-in support for displaying octal (or any value in any base for that matter) so it has to be done with a custom routine.
Outputs octal values 0 through 77 (decimal 0 to 63, or hexadecimal 0x00 to 0x3F.)
xor a ;LD A,0
ld b,&40 ;how many numbers to print.
loop_showOctal:
push af
push af
call ShowOctal
ld a,' '
call PrintChar ;put a blank space after the value
pop af
;;;;;;;;;;;;;;;;;;;;; this code starts a new line after every 8th output.
ld a,b
and &07
dec a
call z,NewLine
;;;;;;;;;;;;;;;;;;;;;;
pop af
inc a ;next number
djnz loop_showOctal
jp $ ;end program
ShowOctal:
push bc
ld c,a
add a
push af
ld a,7
and c
ld c,a
pop af
and &F0
or c
and &7F
pop bc
jp ShowHex
ShowHex: ;this isn't directly below ShowOctal, it's somewhere else entirely.
;thanks to Keith of Chibiakumas for this routine!
push af
and %11110000
ifdef gbz80
swap a ;game boy can use this, but Zilog Z80 cannot.
else
rrca
rrca
rrca
rrca
endif
call PrintHexChar
pop af
and %00001111
;execution flows into the subroutine below, effectively calling it for us without having to actually do so.
PrintHexChar:
or a ;Clear Carry Flag
daa
add a,&F0
adc a,&40 ;this sequence of instructions converts hexadecimal values to ASCII.
jp PrintChar ;hardware-specific routine, omitted. Thanks to Keith of Chibiakumas for this one!
- Output:
00 01 02 03 04 05 06 07 10 11 12 13 14 15 16 17 20 21 22 23 24 25 26 27 30 31 32 33 34 35 36 37 40 41 42 43 44 45 46 47 50 51 52 53 54 55 56 57 60 61 62 63 64 65 66 67 70 71 72 73 74 75 76 77
zkl
foreach n in ([0..]){println("%.8B".fmt(n))}
- Output:
0 1 2 3 4 5 6 7 10 11 12
ZX Spectrum Basic
10 PRINT "DEC. OCT."
20 FOR i=0 TO 20
30 LET o$="": LET n=i
40 LET o$=STR$ FN m(n,8)+o$
50 LET n=INT (n/8)
60 IF n>0 THEN GO TO 40
70 PRINT i;TAB 3;" = ";o$
80 NEXT i
90 STOP
100 DEF FN m(a,b)=a-INT (a/b)*b
- Programming Tasks
- Basic language learning
- Radices
- Iteration
- 0815
- 360 Assembly
- 6502 Assembly
- 8080 Assembly
- AArch64 Assembly
- Action!
- Ada
- Aime
- ALGOL 68
- ALGOL-M
- ALGOL W
- Amazing Hopper
- APL
- ARM Assembly
- Arturo
- AutoHotkey
- AWK
- BASIC
- Applesoft BASIC
- BASIC256
- Chipmunk Basic
- Commodore BASIC
- Sinclair ZX81 BASIC
- UBasic/4tH
- Batch File
- BBC BASIC
- Bc
- BCPL
- Befunge
- BQN
- Bracmat
- Brainf***
- C
- C sharp
- C++
- Clojure
- COBOL
- CoffeeScript
- Common Lisp
- Component Pascal
- Cowgol
- Crystal
- D
- Dc
- DCL
- Delphi
- EasyLang
- EDSAC order code
- Elixir
- Emacs Lisp
- Erlang
- Euphoria
- F Sharp
- Factor
- Forth
- Fortran
- FreeBASIC
- Frink
- Futhark
- FutureBasic
- Go
- Groovy
- Haskell
- Icon
- Unicon
- J
- Jakt
- Janet
- Java
- JavaScript
- Joy
- Jq
- Julia
- Klingphix
- Kotlin
- LabVIEW
- Lang
- Lang5
- Langur
- LFE
- Liberty BASIC
- Logo
- LOLCODE
- Lua
- M2000 Interpreter
- M4
- Maple
- MACRO-10
- Mathematica
- Wolfram Language
- MATLAB
- Octave
- Mercury
- Min
- MiniScript
- МК-61/52
- Modula-2
- Nanoquery
- NetRexx
- NewLISP
- Nim
- Nu
- Oberon-2
- OCaml
- PARI/GP
- Pascal
- PascalABC.NET
- Perl
- Phix
- PHP
- Picat
- PicoLisp
- Pike
- PL/I
- PL/I-80
- PL/M
- PowerShell
- Prolog
- PureBasic
- Python
- QB64
- Quackery
- Racket
- Raku
- REXX
- Ring
- RPL
- Ruby
- Run BASIC
- Rust
- Salmon
- S-BASIC
- Scala
- Scheme
- Scratch
- Sed
- Seed7
- Sidef
- Simula
- Smalltalk
- Sparkling
- Standard ML
- Swift
- Tcl
- UNIX Shell
- VBA
- VBScript
- Vim Script
- V (Vlang)
- VTL-2
- Whitespace
- Wren
- Wren-fmt
- XPL0
- Zig
- Z80 Assembly
- Zkl
- ZX Spectrum Basic
- Pages with too many expensive parser function calls