Digit fifth powers

From Rosetta Code
Digit fifth powers is a draft programming task. It is not yet considered ready to be promoted as a complete task, for reasons that should be found in its talk page.
Task


Task desciption is taken from Project Euler (https://projecteuler.net/problem=30)
Find the sum of all the numbers that can be written as the sum of fifth powers of their digits.

Even though 15 = 1, it is not expressed as a sum (a sum being the summation of a list of two or more numbers), and is therefore not included.

11l

F fifth_power_digit_sum(n)
   R sum(String(n).map(c -> Int(c) ^ 5))

print(sum((2..999999).filter(i -> i == fifth_power_digit_sum(i))))
Output:
443839

8080 Assembly

putch:	equ	2 		; CP/M syscall to print a character
puts:	equ	9		; CP/M syscall to print a string
	org	100h
	;	Find the sum of the 5-powers of the digits
	;	of the current number
sum5:	mvi	b,6		; There are 6 digits
	lxi 	h,dps		; Set the accumulator to zero
	call 	dgzero 
	lxi	d,cur		; Load the start of the current number
addpow:	ldax	d 		; Get current digit
	mov	c,a		; Multiply by 6 (width of table)
	add	a
	add 	c
	add	a
	mvi 	h,0		; HL = index of table entry
	mov	l,a
	push	d		; Keep pointer to current digit
	lxi	d,pow5		; Add start address of pow5 table
	dad	d 
	xchg			; Let [DE] = n^5
	lxi 	h,dps		; Get accumulator
	call	dgadd		; Add the current power to it
	pop	d		; Restore pointer to current digit
	inx	d
	dcr 	b		; If we're not done yet, do the next digit
	jnz 	addpow 
	lxi	d,cur 		; Is the result the same as the current number?
	call	dgcmp
	jnz	next		; If not, try the next number
	lxi 	h,total		; But if so, it needs to be added to the total
	call	dgadd
	xchg			; As well as printed 
	call	dgout
next:	lxi 	h,cur		; Increment the current number
	call	dginc
	lxi	d,max		; Have we reached the end yet?
	call	dgcmp
	jnz	sum5		; If not, keep going
	lxi	d,stot
	mvi	c,puts
	call	5
	lxi	h,total
	jmp	dgout
	;;;;;;; Program data ;;;;;;;
	;	Table of powers of 5, stored as digits in low-endian order
pow5:	db	0,0,0,0,0,0	; 0 ^ 5
	db	1,0,0,0,0,0	; 1 ^ 5
	db	2,3,0,0,0,0	; 2 ^ 5
	db	3,4,2,0,0,0	; 3 ^ 5
	db	4,2,0,1,0,0	; 4 ^ 5
	db	5,2,1,3,0,0	; 5 ^ 5
	db	6,7,7,7,0,0	; 6 ^ 5
	db	7,0,8,6,1,0	; 7 ^ 5
	db	8,6,7,2,3,0	; 8 ^ 5
	db	9,4,0,9,5,0	; 9 ^ 5
	; 	End of the search space (9^5 * 6)
max:	db	4,9,2,4,5,3
	;	Variables
total:	db	0,0,0,0,0,0	; Total of all matching numbers
dps:	db	0,0,0,0,0,0	; Current sum of 5-powers of digits
cur:	db	2,0,0,0,0,0	; Current number to test (start at 2)
	;	Strings
nl:	db	13,10,'$'	; Newline
stot:	db	'Total: $'
	;;;;;;; Math routines ;;;;;;
	;	Zero out [HL]
dgzero:	push	b		; Keep BC and HL
	push 	h 
	xra	a
	mvi	b,6
dgzl:	mov	m,a
	inx	h
	dcr	b
	jnz	dgzl
	pop 	h		; Restore HL and BC
	pop 	b 	
	ret 
	;	Increment [HL]
dginc:	push 	h 		; Keep HL
dgincl:	inr	m		; Increment current digit
	mov	a,m		; Load it into the accumulator
	sui	10		; Subtract 10 from it
	jc	dginco		; If there is no carry, we're done
	mov	m,a		; Otherewise, write it back 
	inx	h		; And go increment the next digit
	jmp	dgincl
dginco:	pop 	h		; Restore HL
	ret	
	; 	Print the number in [HL]
dgout:	push 	b		; Keep all registers
	push 	d
	push 	h
	lxi	b,6		; Move to the last digit
	dad	b
dzero:	dcr	c		; Skip leading zeroes
	jm	restor 		; Don't bother handling 0 case
	dcx	h		; Go back
	mov	a,m		; Get digit
	ana	a
	jz	dzero		; Keep going until we find a nonzero digit
dgprn:	adi	'0'		; Write the digit
	mov	e,a
	push	b		; CP/M syscall destroys registers
	push 	h
	mvi	c,putch
	call 	5 
	pop 	h
	pop 	b
	dcx 	h
	mov	a,m
	dcr	c
	jp	dgprn
	mvi	c,puts		; Finally, print a newline
	lxi	d,nl
	call	5
restor:	pop 	h		; And restore the registers
	pop 	d
	pop 	b
	ret
	;	Compare [DE] to [HL]
dgcmp:	push 	b		; Keep the registers
	push 	d
	push 	h 
	mvi	b,6
dgcmpl:	ldax	d		; Get [DE]
	cmp	m		; Compare to [HL]
	jnz	restor		; If unequal, this is the result
	inx	d		; Otherwise, compare next pair
	inx	h
	dcr 	b
	jnz	dgcmpl
	jmp	restor
	;	Add [DE] to [HL]
dgadd:	push	b
	push 	d
	push 	h
	lxi	b,600h 		; B = counter, C = carry
dgaddl:	ldax	d		; Get digit from [DE]
	add	m 		; Add digit from [HL]
	add	c		; Carry the one
	cpi	10		; Is the result 10 or higher?
	mvi 	c,0		; Assume there will be no carry
	jc	dgwr		; If not, handle next digit
	sui	10		; But if so, subtract 10,
	inr	c 		; And set the carry flag for the next digit
dgwr:	mov	m,a		; Store the resulting digit in [HL]
	inx	d		; Move the pointers
	inx	h
	dcr	b		; Any more digits?
	jnz	dgaddl
	jmp	restor
Output:
4150
4151
54748
92727
93084
194979
Total: 443839

Ada

with Ada.Text_Io;

procedure Digit_Fifth_Powers is

   subtype Number is Natural range 000_002 .. 999_999;

   function Sum_5 (N : Natural) return Natural
   is
      Pow_5 : constant array (0 .. 9) of Natural :=
        (0 => 0**5, 1 => 1**5, 2 => 2**5, 3 => 3**5, 4 => 4**5,
         5 => 5**5, 6 => 6**5, 7 => 7**5, 8 => 8**5, 9 => 9**5);
   begin
      return (if N = 0
              then 0
              else Pow_5 (N mod 10) + Sum_5 (N / 10));
   End Sum_5;

   use Ada.Text_Io;
   Sum : Natural := 0;
begin
   for N in Number loop
      if N = Sum_5 (N) then
         Sum := Sum + N;
         Put_Line (Number'Image (N));
      end if;
   end loop;
   Put ("Sum: ");
   Put_Line (Natural'Image (Sum));
end Digit_Fifth_Powers;
Output:
 4150
 4151
 54748
 92727
 93084
 194979
Sum:  443839

ALGOL 68

As noted by the Julia sample, we need only consider up to 6 digit numbers.
Also note, the digit fifth power sum is independent of the order of the digits.

BEGIN
    []INT fifth = []INT( 0, 1, 2^5, 3^5, 4^5, 5^5, 6^5, 7^5, 8^5, 9^5 )[ AT 0 ];
    # as observed by the Julia sample, 9^5 * 7 has only 6 digits whereas 9^5 * 6 has 6 digits #
    # so only up to 6 digit numbers need be considered #
    # also, the digit fifth power sum is independent ofg the order of the digits # 
    [ 1 : 100 ]INT sums; FOR i TO UPB sums DO sums[ i ] := 0 OD;
    [ 0 :   9 ]INT used; FOR i FROM 0 TO 9 DO used[ i ] := 0 OD;
    INT s count := 0;
    FOR d1 FROM 0 TO 9 DO
        INT s1 = fifth[ d1 ];
        used[ d1 ] +:= 1;
        FOR d2 FROM d1 TO 9 DO
            INT s2 = fifth[ d2 ] + s1;
            used[ d2 ] +:= 1;
            FOR d3 FROM d2 TO 9 DO
                INT s3 = fifth[ d3 ] + s2;
                used[ d3 ] +:= 1;
                FOR d4 FROM d3 TO 9 DO
                    INT s4 = fifth[ d4 ] + s3;
                    used[ d4 ] +:= 1;
                    FOR d5 FROM d4 TO 9 DO
                        INT s5 = fifth[ d5 ] + s4;
                        used[ d5 ] +:= 1;
                        FOR d6 FROM d5 TO 9 DO
                            INT s6 = fifth[ d6 ] + s5;
                            used[ d6 ] +:= 1;
                            # s6 is the sum of the fifth powers of the digits #
                            # check it it is composed of the digits d1 - d6   #
                            [ 0 : 9 ]INT check; FOR i FROM 0 TO 9 DO check[ i ] := 0 OD;
                            INT v := s6;
                            FOR i TO 6 DO
                                check[ v MOD 10 ] +:= 1;
                                v OVERAB 10
                            OD;
                            BOOL same := TRUE;
                            FOR i FROM 0 TO 9 WHILE ( same := used[ i ] = check[ i ] ) DO SKIP OD;
                            IF same THEN
                                # found a number that is the sum of the fifth powers of its digits #
                                sums[ s count +:= 1 ] := s6
                            FI;
                            used[ d6 ] -:= 1
                        OD # d6 # ;
                        used[ d5 ] -:= 1
                    OD # d5 # ;
                    used[ d4 ] -:= 1
                OD # d4 # ;
                used[ d3 ] -:= 1
            OD # d3 # ;
            used[ d2 ] -:= 1
        OD # d2 # ;
        used[ d1 ] -:= 1
    OD # d1 # ;
    # sum and print the sums - ignore 0 and 1 #
    INT total := 0;
    print( ( "Numbers that are the sums of the fifth powers of their digits: " ) );
    FOR i TO s count DO
        IF sums[ i ] > 1 THEN
            print( ( " ", whole( sums[ i ], 0 ) ) );
            total +:= sums[ i ]
        FI
    OD;
    print( ( newline ) );
    print( ( "Total: ", whole( total, 0 ), newline ) )
END
Output:
Numbers that are the sums of the fifth powers of their digits:  4150 4151 93084 92727 54748 194979
Total: 443839

APL

Works with: Dyalog APL
+/((/⍨)(⊢=(+/5*¨∘))¨)1↓⍳6×9*5
Output:
443839

AppleScript

Simple solution:

on join(lst, delim)
    set astid to AppleScript's text item delimiters
    set AppleScript's text item delimiters to delim
    set txt to lst as text
    set AppleScript's text item delimiters to astid
    return txt
end join

on digit5thPowers()
    set sums to {}
    set total to 0
    repeat with n from (2 ^ 5) to ((9 ^ 5) * 6)
        set temp to n
        set sum to (temp mod 10) ^ 5
        repeat while (temp > 9)
            set temp to temp div 10
            set sum to sum + (temp mod 10) ^ 5
        end repeat
        if (sum = n) then
            set end of sums to n
            set total to total + n
        end if
    end repeat
    return join(sums, " + ") & " = " & total
end digit5thPowers

digit5thPowers()
Output:
"4150 + 4151 + 54748 + 92727 + 93084 + 194979 = 443839"

Faster alternative (about 55 times as fast) using the "start with the digits" approach suggested by other contributors. Its iterative structure requires prior knowledge that six digits will be needed.

on join(lst, delim)
    set astid to AppleScript's text item delimiters
    set AppleScript's text item delimiters to delim
    set txt to lst as text
    set AppleScript's text item delimiters to astid
    return txt
end join

on digit5thPowers()
    set hits to {}
    set total to 0
    repeat with d1 from 1 to 9
        set s1 to (d1 ^ 5)
        repeat with d2 from 1 to d1
            set s2 to s1 + (d2 ^ 5)
            repeat with d3 from 0 to d2
                set s3 to s2 + (d3 ^ 5)
                repeat with d4 from 0 to d3
                    set s4 to s3 + (d4 ^ 5)
                    repeat with d5 from 0 to d4
                        set s5 to s4 + (d5 ^ 5)
                        repeat with d6 from 0 to d5
                            set sum to s5 + (d6 ^ 5) as integer
                            set temp to sum
                            set d to temp mod 10
                            set digits to {d1, d2, d3, d4, d5, d6}
                            repeat while (digits contains {d})
                                repeat with i from 1 to 6
                                    if (digits's item i = d) then
                                        set digits's item i to missing value
                                        exit repeat
                                    end if
                                end repeat
                                set temp to temp div 10
                                set d to temp mod 10
                            end repeat
                            if (((count digits each integer) = 0) and (sum > (2 ^ 5))) then
                                set end of hits to sum
                                set total to total + sum
                            end if
                        end repeat
                    end repeat
                end repeat
            end repeat
        end repeat
    end repeat
    return join(hits, " + ") & " = " & total
end digit5thPowers

digit5thPowers()
Output:
"4150 + 4151 + 54748 + 92727 + 93084 + 194979 = 443839"

Recursive version of the above. This takes the power as a parameter and is believed to be good for powers between 3 and 13. (No matches found when the power is 12.)

on join(lst, delim)
    set astid to AppleScript's text item delimiters
    set AppleScript's text item delimiters to delim
    set txt to lst as text
    set AppleScript's text item delimiters to astid
    return txt
end join

on digitNthPowers(pwr)
    if ((pwr < 2) or (pwr > 13)) then return missing value -- Clear non-starter or too high for AppleScript.
    -- Trusting the theory in the Julia solution, work out how many digits are needed.
    set digits to {missing value}
    set digitCount to 1
    repeat until ((9 ^ pwr) * digitCount < (10 ^ digitCount))
        set digitCount to digitCount + 1
        set end of digits to missing value
    end repeat
    set hits to {}
    set total to 0
    
    script o
        on dnp(slot, dmin, dmax, sum)
            -- Recursive handler. Inherits the variables set before this script object.
            -- slot: current slot in digits.
            -- dmin, dmax: range of digit values to try in it.
            -- sum: sum of 5th powers at the calling level.
            repeat with d from dmin to dmax
                set digits's item slot to d
                if (slot < digitCount) then
                    dnp(slot + 1, 0, d, sum + d ^ pwr)
                else
                    copy digits to checklist
                    set sum to (sum + (d ^ pwr)) div 1
                    set temp to sum
                    set d to temp mod 10
                    repeat while (checklist contains {d})
                        repeat with i from 1 to digitCount
                            if (checklist's item i = d) then
                                set checklist's item i to missing value
                                exit repeat
                            end if
                        end repeat
                        set temp to temp div 10
                        set d to temp mod 10
                    end repeat
                    if (((count checklist each integer) = 0) and (sum > (2 ^ pwr))) then
                        set end of hits to sum
                        set total to total + sum
                    end if
                end if
            end repeat
        end dnp
    end script
    o's dnp(1, 1, 9, 0.0)
    
    if (hits = {}) then return missing value
    return join(hits, " + ") & " = " & total
end digitNthPowers

join({digitNthPowers(4), digitNthPowers(5), digitNthPowers(13)}, linefeed)
Output:
"1634 + 8208 + 9474 = 19316
4150 + 4151 + 54748 + 92727 + 93084 + 194979 = 443839
5.64240140138E+11 = 5.64240140138E+11"

Arturo

fifthDigitSum?: function [n]->
    n = sum map digits n 'd -> d^5

print dec sum select 1..1000000 => fifthDigitSum?
Output:
443839

AWK

# syntax: GAWK -f DIGIT_FIFTH_POWERS.AWK
BEGIN {
    for (p=3; p<=6; p++) {
      limit = 9^p*p
      sum = 0
      for (i=2; i<=limit; i++) {
        if (i == main(i)) {
          printf("%6d\n",i)
          sum += i
        }
      }
      printf("%6d power %d sum\n\n",sum,p)
    }
    exit(0)
}
function main(n,  i,total) {
    for (i=1; i<=length(n); i++) {
      total += substr(n,i,1) ^ p
    }
    return(total)
}
Output:
   153
   370
   371
   407
  1301 power 3 sum

  1634
  8208
  9474
 19316 power 4 sum

  4150
  4151
 54748
 92727
 93084
194979
443839 power 5 sum

548834
548834 power 6 sum

BASIC

FreeBASIC

function dig5( n as uinteger ) as uinteger
    dim as string ns = str(n)
    dim as uinteger ret = 0
    for i as ubyte = 1 to len(ns)
        ret += val(mid(ns,i,1))^5
    next i
    return ret
end function

dim as uinteger i, sum = 0

for i = 2 to 999999
    if i = dig5(i) then 
        print i
        sum += i
    end if
next i

print "Their sum is ", sum
Output:

4150 4151 54748 92727 93084 194979

Their sum is 443839

GW-BASIC

10 SUM! = 0
20 FOR I! = 2 TO 999999!
30 GOSUB 80
40 IF R! = I! THEN SUM! = SUM! + I! : PRINT I!
50 NEXT I!
60 PRINT "Total = ",SUM
70 END
80 N$ = STR$(I)
90 R! = 0
100 FOR J = 1 TO LEN(N$)
110 D = VAL(MID$(N$,J,1))
120 R! = R! + D*D*D*D*D
130 NEXT J
140 RETURN
Output:

4150 4151 54748 92727 93084 194979

Total = 443839

QB64

CONST LIMIT& = 9 ^ 5 * 6 ' we don't need to search higher than this in base 10
DIM AS LONG num, sum, digitSum
DIM digit AS _BYTE
DIM FifthPowers(9) AS _UNSIGNED INTEGER

FOR i% = LBOUND(FifthPowers) TO UBOUND(FifthPowers)
    FifthPowers(i%) = i% ^ 5
NEXT i%

FOR i& = 2 TO LIMIT&
    num& = i&
    digitSum& = 0
    WHILE num& > 0
        digit%% = num& MOD 10
        digitSum& = digitSum& + FifthPowers(digit%%)
        num& = INT(num& / 10)
    WEND
    IF digitSum& = i& THEN
        PRINT digitSum&
        sum& = sum& + digitSum&
    END IF
NEXT i&

PRINT "The sum is"; sum
Output:
 4150
 4151
 54748
 92727
 93084
 194979
The sum is 443839

BQN

Sum5  { 0:0; (𝕊⌊𝕩÷10) + (10|𝕩)5 }

+´(⊢=Sum5)¨/ 2↓↕6×95
Output:
443839

C

#include<stdio.h>
#include<stdlib.h>
#include<math.h>

int sum5( int n ) {
    if(n<10) return pow(n,5);
    return pow(n%10,5) + sum5(n/10);
}

int main(void) {
    int i, sum = 0;
    for(i=2;i<=999999;i++) {
        if(i==sum5(i)) {
            printf( "%d\n", i );
            sum+=i;
        }
    }
    printf( "Total is %d\n", sum );
    return 0;
}
Output:
4150

4151 54748 92727 93084 194979

Total is 443839

C++

Fast version. Checks numbers up to 399,999, which is above the requirement of 6 * 95 and well below the overkill value of 999,999.

#include <iostream>
#include <cmath>
#include <chrono>

using namespace std;
using namespace chrono;

int main() {
  auto st = high_resolution_clock::now();
  const uint i5 = 100000, i4 = 10000, i3 = 1000, i2 = 100, i1 = 10;
  uint p4[] = { 0, 1, 32, 243 }, nums[10], p5[10], t = 0, 
    m5, m4, m3, m2, m1, m0; m5 = m4 = m3 = m2 = m1 = m0 = 0;
  for (uint i = 0; i < 10; i++) p5[i] = pow(nums[i] = i, 5);
  for (auto i : p4) { auto im =      m5, ip =      i; m4 = 0;
  for (auto j : p5) { auto jm = im + m4, jp = ip + j; m3 = 0;
  for (auto k : p5) { auto km = jm + m3, kp = jp + k; m2 = 0;
  for (auto l : p5) { auto lm = km + m2, lp = kp + l; m1 = 0;
  for (auto m : p5) { auto mm = lm + m1, mp = lp + m; m0 = 0;
  for (auto n : p5) { auto nm = mm + m0++;
    if (nm == mp + n && nm > 1) t += nm;
  } m1 += i1; } m2 += i2; } m3 += i3; } m4 += i4; } m5 += i5; }
  auto et = high_resolution_clock::now();
  std::cout << t << " " <<
    duration_cast<nanoseconds>(et - st).count() / 1000.0 << " μs";
}
Output @ Tio.run:
443839 250.514 μs

CLU

sum5 = proc (n: int) returns (int)
    sum: int := 0
    while n > 0 do
        sum := sum + (n//10) ** 5
        n := n/10
    end
    return(sum)
end sum5

start_up = proc ()
    po: stream := stream$primary_output()
    total: int := 0
    for i: int in int$from_to(2, 6*9**5) do
        if sum5(i)=i then
            total := total + i
            stream$putright(po, int$unparse(i), 6) 
            stream$putc(po, '\n')
        end
    end
    stream$putl(po, "------ +")
    stream$putright(po, int$unparse(total), 6)
    stream$putc(po, '\n')
end start_up
Output:
  4150
  4151
 54748
 92727
 93084
194979
------ +
443839

COBOL

       IDENTIFICATION DIVISION.
       PROGRAM-ID. DIGIT-FIFTH-POWER.

       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 VARIABLES.
          03 CANDIDATE          PIC 9(6).
          03 MAXIMUM            PIC 9(6).
          03 DIGITS             PIC 9 OCCURS 6 TIMES,
                                REDEFINES CANDIDATE.
          03 DIGIT              PIC 9.
          03 POWER-SUM          PIC 9(6).
          03 TOTAL              PIC 9(6).

       01 OUT-FORMAT.
          03 OUT-NUM            PIC Z(5)9.

       PROCEDURE DIVISION.
       BEGIN.
           MOVE ZERO TO TOTAL.
           COMPUTE MAXIMUM = 9 ** 5 * 6.
           PERFORM TEST-NUMBER
               VARYING CANDIDATE FROM 2 BY 1
               UNTIL CANDIDATE IS GREATER THAN MAXIMUM.
           DISPLAY '------ +'.
           DISPLAY TOTAL.
           STOP RUN.

       TEST-NUMBER.
           MOVE ZERO TO POWER-SUM.
           PERFORM ADD-DIGIT-POWER
               VARYING DIGIT FROM 1 BY 1
               UNTIL DIGIT IS GREATER THAN 6.
           IF POWER-SUM IS EQUAL TO CANDIDATE,
               MOVE CANDIDATE TO OUT-NUM,
               DISPLAY OUT-NUM,
               ADD CANDIDATE TO TOTAL.
       
       ADD-DIGIT-POWER.
           COMPUTE POWER-SUM = POWER-SUM + DIGITS(DIGIT) ** 5.
Output:
  4150
  4151
 54748
 92727
 93084
194979
------ +
443839

Comal

0010 FUNC sum5(n) CLOSED
0020   sum:=0
0030   WHILE n>0 DO sum:+(n MOD 10)^5;n:=n DIV 10
0040   RETURN sum
0050 ENDFUNC sum5
0060 //
0070 max:=9^5*6
0080 total:=0
0090 FOR i:=2 TO max DO
0100   IF i=sum5(i) THEN
0110     PRINT USING "######":i
0120     total:+i
0130   ENDIF
0140 ENDFOR i
0150 PRINT "------ +"
0160 PRINT USING "######":total
0170 END
Output:
  4150
  4151
 54748
 92727
 93084
194979
------ +
443839

Cowgol

include "cowgol.coh";

sub pow5(n: uint32): (p: uint32) is
    p := n*n * n*n * n;
end sub;

sub sum5(n: uint32): (r: uint32) is
    r := 0;
    while n != 0 loop
        r := r + pow5(n % 10);
        n := n / 10;
    end loop;
end sub;

var total: uint32 := 0;
var n: uint32 := 2;
var max: uint32 := pow5(9) * 6;

while n <= max loop
    if n == sum5(n) then
        total := total + n;
        print_i32(n);
        print_nl();
    end if;
    n := n + 1;
end loop;

print("Total: ");
print_i32(total);
print_nl();
Output:
4150
4151
54748
92727
93084
194979
Total: 443839

Factor

Thanks to to the Julia entry for the tip about the upper bound of the search.

USING: kernel math math.functions math.ranges math.text.utils
math.vectors prettyprint sequences ;

2 9 5 ^ 6 * [a,b] [ dup 1 digit-groups 5 v^n sum = ] filter sum .
Output:
443839

Fermat

Func Sumfp(n) = if n<10 then Return(n^5) else Return((n|10)^5 + Sumfp(n\10)) fi.;
sum:=0;
for i=2 to 999999 do if i=Sumfp(i) then sum:=sum+i; !!i fi od;
!!('The sum was ', sum );
Output:

4150 4151 54748 92727 93084 194979

The sum was 443839

Delphi

Works with: Delphi version 6.0

Optimized for speed - runs in 60 ms on a Ryzen 7.

const Power5: array [0..9] of integer = (0,1,32,243,1024,3125,7776,16807,32768,59049);

function SumFifthPower(N: integer): integer;
var S: string;
var I: integer;
begin
S:=IntToStr(N);
Result:=0;
for I:=1 to Length(S) do
  Result:=Result+Power5[byte(S[I])-$30];
end;

procedure ShowFiftPowerDigits(Memo: TMemo);
var I,Sum: integer;
begin
Sum:=0;
for I:=2 to 354424 do
	begin
	if I = SumFifthPower(I) then
		begin
		Memo.Lines.Add(Format('%8.0n',[I*1.0]));
		Sum:=Sum+I;
		end;
	end;
Memo.Lines.Add('========');
Memo.Lines.Add(Format('%8.0n',[Sum*1.0]));
end;
Output:
   4,150
   4,151
  54,748
  92,727
  93,084
 194,979
========
 443,839

FOCAL

01.10 S M=9^5*6
01.20 S T=0
01.30 F C=2,M;D 3
01.40 T "TOTAL",T,!
01.50 Q

02.10 S X=C
02.20 S S=0
02.30 S Y=FITR(X/10)
02.40 S S=S+(X-Y*10)^5
02.50 S X=Y
02.60 I (-X)2.3

03.10 D 2
03.20 I (C-S)3.5,3.3,3.5
03.30 T %6,C,!
03.40 S T=T+C
03.50 R
Output:
=   4150
=   4151
=  54748
=  92727
=  93084
= 194979
TOTAL= 443839

Go

Translation of: Wren
Library: Go-rcu
package main

import (
    "fmt"
    "rcu"
)

func main() {
    // cache 5th powers of digits
    dp5 := [10]int{0, 1}
    for i := 2; i < 10; i++ {
        ii := i * i
        dp5[i] = ii * ii * i
    }
    fmt.Println("The sum of all numbers that can be written as the sum of the 5th powers of their digits is:")
    limit := dp5[9] * 6
    sum := 0
    for i := 2; i <= limit; i++ {
        digits := rcu.Digits(i, 10)
        totalDp := 0
        for _, d := range digits {
            totalDp += dp5[d]
        }
        if totalDp == i {
            if sum > 0 {
                fmt.Printf(" + %d", i)
            } else {
                fmt.Print(i)
            }
            sum += i
        }
    }
    fmt.Printf(" = %d\n", sum)
}
Output:
The sum of all numbers that can be written as the sum of the 5th powers of their digits is:
4150 + 4151 + 54748 + 92727 + 93084 + 194979 = 443839

J

(([=[:+/10&#.^:_1^5:)"0+/@#])2}.i.6*9^5
Output:
443839

jq

Adapted from Julia

Works with: jq

Works with gojq, the Go implementation of jq

Preliminaries

# To take advantage of gojq's arbitrary-precision integer arithmetic:
def power($b): . as $in | reduce range(0;$b) as $i (1; . * $in);

def sum(s): reduce s as $x (0; .+$x);

# Output: a stream of integers
def digits: tostring | explode[] | [.] | implode | tonumber;

The Task

# Output: an array of i^5 for i in 0 .. 9 inclusive
def dp5: [range(0;10) | power(5)];

def task:
  dp5 as $dp5
  | ($dp5[9] * 6) as $limit
  | sum( range(2; $limit + 1)
         | sum( digits | $dp5[.] ) as $s
         | select(. == $s) ) ;

"The sum of all numbers that can be written as the sum of the 5th powers of their digits is:", task
Output:
The sum of all numbers that can be written as the sum of the 5th powers of their digits is:
443839


Julia

In base 10, the largest digit is 9. If n is the number of digits, as n increases, 9^5 * n < 10^n. So we do not have to look beyond 9^5 * 6 since 9^5 * 6 < 1,000,000.

println("Numbers > 1 that can be written as the sum of fifth powers of their digits:")
arr = [i for i in 2 : 9^5 * 6 if mapreduce(x -> x^5, +, digits(i)) == i]
println(join(arr, " + "), " = ", sum(arr))
Output:
Numbers > 1 that can be written as the sum of fifth powers of their digits:
4150 + 4151 + 54748 + 92727 + 93084 + 194979 = 443839

MAD

            NORMAL MODE IS INTEGER
            
            INTERNAL FUNCTION(X)
            ENTRY TO POW5.
            FUNCTION RETURN X * X * X * X * X
            END OF FUNCTION
            
            INTERNAL FUNCTION(N)
            ENTRY TO SUM5.
            CUR = N
            SUM = 0
LOOP        WHENEVER CUR.G.0
                NEXT = CUR / 10
                SUM = SUM + POW5.(CUR - NEXT*10)
                CUR = NEXT
                TRANSFER TO LOOP
            END OF CONDITIONAL
            FUNCTION RETURN SUM
            END OF FUNCTION
            
            LIMIT = POW5.(9) * 6
            TOTAL = 0
            THROUGH TEST, FOR I = 2, 1, I.GE.LIMIT
            WHENEVER SUM5.(I).E.I
                TOTAL = TOTAL + I
                PRINT FORMAT NUM, I
            END OF CONDITIONAL
TEST        CONTINUE

            PRINT FORMAT TOT, TOTAL
            VECTOR VALUES NUM = $S7,I6*$
            VECTOR VALUES TOT = $7HTOTAL: ,I6*$
            END OF PROGRAM
Output:
         4150
         4151
        54748
        92727
        93084
       194979
TOTAL: 443839

Mathematica/Wolfram Language

ClearAll[FifthPowerSumQ]
FifthPowerSumQ[n_Integer] := Total[IntegerDigits[n]^5] == n
sol = Select[Range[2, 10000000], FifthPowerSumQ]
Total[sol]
Output:
{4150, 4151, 54748, 92727, 93084, 194979}
443839

PARI/GP

sumfp(n)=if(n<10,n^5,(n%10)^5+sumfp(n\10));
s=0;
for(i=2,999999,if(i==sumfp(i),s=s+i;print(i)));
print("Total: ",s);
Output:
4150

4151 54748 92727 93084 194979

Total: 443839

Pascal

slightly modified Own_digits_power_sum checks decimals up to power 19.

program PowerOwnDigits2;
{$IFDEF FPC}
  {$R+,O+}
  {$MODE DELPHI}{$OPTIMIZATION ON,ALL}{$COPERATORS ON}
{$ELSE}
  {$APPTYPE CONSOLE}
{$ENDIF}
uses
  SysUtils,StrUtils;
const
  CPU_hz = 1000*1000*1000;
const
  MAXBASE = 10;
  MaxDgtVal = MAXBASE - 1;
  MaxDgtCount = 19;
type
  tDgtCnt = 0..MaxDgtCount;
  tValues = 0..MaxDgtVal;
  tUsedDigits = array[tValues] of Int8;
  tpUsedDigits = ^tUsedDigits;

  tPower = array[tValues] of Uint64;
var
  PowerDgt:  tPower;
  gblUD   : tUsedDigits;
  CombIdx : array of Int8;
  Numbers : array of Uint64;
  rec_cnt : NativeInt;

 function GetCPU_Time: Uint64;
  type
    TCpu = record
              HiCpu,
              LoCpu : Dword;
           end;
  var
    Cput : TCpu;
  begin
  {$ASMMODE INTEL}
    asm
    RDTSC;
    MOV Dword Ptr [CpuT.LoCpu],EAX;  MOV Dword Ptr [CpuT.HiCpu],EDX
    end;
    with Cput do  result := Uint64(HiCPU) shl 32 + LoCpu;
  end;

  function InitCombIdx(ElemCount: Byte): pbyte;
  begin
    setlength(CombIdx, ElemCount + 1);
    Fillchar(CombIdx[0], sizeOf(CombIdx[0]) * (ElemCount + 1), #0);
    Result := @CombIdx[0];
    Fillchar(gblUD[0], sizeOf(tUsedDigits), #0);
    gblUD[0]:= 1;
  end;

  function Init(ElemCount:byte;Expo:byte):pByte;
  var
    pP1 : pUint64;
    p: Uint64;
    i,j: Int32;
  begin
    pP1 := @PowerDgt[0];
    for i in tValues do
    Begin
      p := 1;
      for j := 1 to Expo do
        p *= i;
      pP1[i] := p;
    end;
    result := InitCombIdx(ElemCount);
    gblUD[0]:= 1;
  end;

  function GetPowerSum(minpot:nativeInt;digits:pbyte;var UD :tUsedDigits):NativeInt;
  var
    res,r  : Uint64;
    dgt :Int32;
  begin
    dgt := minpot;
    res := 0;
    repeat
      dgt -=1;
      res += PowerDgt[digits[dgt]];
    until dgt=0;
    result := 0;
    //convert res into digits
    repeat
      r := res DIV MAXBASE;
      result+=1;
      dgt := res-r*MAXBASE;
      //substract from used digits
      UD[dgt] -= 1;
      res := r;
    until r = 0;
  end;

  procedure calcNum(minPot:Int32;digits:pbyte);
  var
    UD :tUsedDigits;
    res: Uint64;
    i: nativeInt;
  begin
    UD := gblUD;
    i:= GetPowerSum(minpot,digits,UD);
    if i = minPot then
    Begin
      //don't check 0
      i := 1;
      repeat
        If UD[i] <> 0 then
          Break;
        i +=1;
      until i > MaxDgtVal;

      if i > MaxDgtVal then
      begin
        res := 0;
        for i := minpot-1 downto 0 do
          res += PowerDgt[digits[i]];
        setlength(Numbers, Length(Numbers) + 1);
        Numbers[high(Numbers)] := res;
      end;
    end;
  end;

  function NextCombWithRep(pComb: pByte;pUD :tpUsedDigits;MaxVal, ElemCount: UInt32): boolean;
  var
    i,dgt: NativeInt;
  begin
    i := -1;
    repeat
      i += 1;
      dgt := pComb[i];
      if dgt < MaxVal then
        break;
      dec(pUD^[dgt]);
    until i >= ElemCount;
    Result := i >= ElemCount;

    if i = 0 then
    begin
      dec(pUD^[dgt]);
      dgt +=1;
      pComb[i] := dgt;
      inc(pUD^[dgt]);
    end
    else
    begin
      dec(pUD^[dgt]);
      dgt +=1;
      pUD^[dgt]:=i+1;
      repeat
        pComb[i] := dgt;
        i -= 1;
      until i < 0;
    end;
  end;

var
  digits : pByte;
  T0,T1 : UInt64;
  tmp : Uint64;
  Pot,dgtCnt,i, j : Int32;

begin
  T0 := GetCPU_Time;
  For pot := 2 to MaxDgtCount do
  begin
    Write('Exponent : ',Pot,' used ');
    T1 := GetCPU_Time;
    digits := Init(MaxDgtCount,pot);
    rec_cnt := 0;
    // i > 0
    For dgtCnt := 2 to pot+1 do
    Begin
      digits := InitCombIdx(Pot);
      repeat
        calcnum(dgtCnt,digits);
        inc(rec_cnt);
      until NextCombWithRep(digits,@gblUD,MaxDgtVal,dgtCnt);
    end;
    writeln(rec_cnt,' recursions in ',(GetCPU_Time-T1)/CPU_hz:0:6,' GigaCyles');
    If length(numbers) > 0 then
    Begin
      //sort
      for i := 0 to High(Numbers) - 1 do
        for j := i + 1 to High(Numbers) do
          if Numbers[j] < Numbers[i] then
          begin
            tmp := Numbers[i];
            Numbers[i] := Numbers[j];
            Numbers[j] := tmp;
          end;

      tmp := 0;
      for i := 0 to High(Numbers)-1 do
      begin
        write(Numb2USA(IntToStr(Numbers[i])),' + ');
        tmp +=Numbers[i];
      end;
      write(Numb2USA(IntToStr(Numbers[High(Numbers)])),' = ');
      tmp +=Numbers[High(Numbers)];
      writeln('sum to ',Numb2USA(IntToStr(tmp)));
    end;
    writeln;
    setlength(Numbers,0);
  end;
  T0 := GetCPU_Time-T0;
  Writeln('Max Uint64 ',Numb2USA(IntToStr(High(Uint64))));
  writeln('Total runtime : ',T0/CPU_hz:0:6,' GigaCyles');
  {$IFDEF WINDOWS}
  readln;
  {$ENDIF}
  setlength(CombIdx,0);
end.
Output @ Tio.run:
TIO.RUN User time: 12.905 s //Total runtime : 29.470650 GigaCyles estimated ~2,28 Ghz
Exponent : 2 used 275 recursions in 0.000030 GigaCyles

Exponent : 3 used 990 recursions in 0.000161 GigaCyles
153 + 370 + 371 + 407 = sum to 1,301

Exponent : 4 used 2992 recursions in 0.000367 GigaCyles
1,634 + 8,208 + 9,474 = sum to 19,316

Exponent : 5 used 7997 recursions in 0.001193 GigaCyles // /2.28 -> 523 µs
4,150 + 4,151 + 54,748 + 92,727 + 93,084 + 194,979 = sum to 443,839

Exponent : 6 used 19437 recursions in 0.003013 GigaCyles
548,834 = sum to 548,834

Exponent : 7 used 43747 recursions in 0.007827 GigaCyles
1,741,725 + 4,210,818 + 9,800,817 + 9,926,315 + 14,459,929 = sum to 40,139,604

Exponent : 8 used 92367 recursions in 0.017619 GigaCyles
24,678,050 + 24,678,051 + 88,593,477 = sum to 137,949,578

Exponent : 9 used 184745 recursions in 0.037308 GigaCyles
146,511,208 + 472,335,975 + 534,494,836 + 912,985,153 = sum to 2,066,327,172

Exponent : 10 used 352705 recursions in 0.090797 GigaCyles
4,679,307,774 = sum to 4,679,307,774

Exponent : 11 used 646635 recursions in 0.207819 GigaCyles
32,164,049,650 + 32,164,049,651 + 40,028,394,225 + 42,678,290,603 + 44,708,635,679 + 49,388,550,606 + 82,693,916,578 + 94,204,591,914 = sum to 418,030,478,906

Exponent : 12 used 1144055 recursions in 0.295691 GigaCyles

Exponent : 13 used 1961245 recursions in 0.532789 GigaCyles
564,240,140,138 = sum to 564,240,140,138

Exponent : 14 used 3268749 recursions in 0.937579 GigaCyles
28,116,440,335,967 = sum to 28,116,440,335,967

Exponent : 15 used 5311724 recursions in 1.623457 GigaCyles

Exponent : 16 used 8436274 recursions in 2.680338 GigaCyles
4,338,281,769,391,370 + 4,338,281,769,391,371 = sum to 8,676,563,538,782,741

Exponent : 17 used 13123099 recursions in 4.432118 GigaCyles
233,411,150,132,317 + 21,897,142,587,612,075 + 35,641,594,208,964,132 + 35,875,699,062,250,035 = sum to 93,647,847,008,958,559

Exponent : 18 used 20029999 recursions in 7.169892 GigaCyles

Exponent : 19 used 30045004 recursions in 11.431518 GigaCyles
1,517,841,543,307,505,039 + 3,289,582,984,443,187,032 + 4,498,128,791,164,624,869 + 4,929,273,885,928,088,826 = sum to 14,234,827,204,843,405,766

Max Uint64 18,446,744,073,709,551,615
Total runtime : 29.470650 GigaCyles

Perl

use strict;
use warnings;
use feature 'say';
use List::Util 'sum';

for my $power (3..6) {
    my @matches;
    for my $n (2 .. 9**$power * $power) {
        push @matches, $n if $n == sum map { $_**$power } split '', $n;
    }
    say "\nSum of powers of n**$power: " . join(' + ', @matches) . ' = ' . sum @matches;
}
Output:
Sum of powers of n**3: 153 + 370 + 371 + 407 = 1301
Sum of powers of n**4: 1634 + 8208 + 9474 = 19316
Sum of powers of n**5: 4150 + 4151 + 54748 + 92727 + 93084 + 194979 = 443839
Sum of powers of n**6: 548834 = 548834

Phix

with javascript_semantics
function sum5(integer n)
    return iff(n<10?power(n,5):power(remainder(n,10),5) + sum5(floor(n/10)))
end function
 
integer total = 0
sequence res = {}
for i=2 to power(9,5)*6 do
    if i=sum5(i) then
        res = append(res,sprint(i))
        total += i
    end if
end for
printf(1,"%s = %d\n",{join(res," + "),total})
Output:
4150 + 4151 + 54748 + 92727 + 93084 + 194979 = 443839

PicoLisp

(de sum5th (N)
   (sum 
      '((D) (** (format D) 5))
      (chop N)))

(setq solutions
   (cdr  # exclude 1
      (make
         (for N `(* 6 (** 9 5))
            (when (= N (sum5th N))
               (link N))))))

(prinl "The numbers that can be written as the sum of the 5th power of their digits are:" )
(prin "     ") (println solutions)
(prinl "Their sum is " (apply + solutions))
(bye)
Output:
The numbers that can be written as the sum of the 5th power of their digits are:
     (4150 4151 54748 92727 93084 194979)
Their sum is 443839

PILOT

C :max=9*(9*(9*(9*(9*6))))
  :sum=0
  :n=2
*number
C :dps=0
  :cur=n
*digit
C :next=cur/10
  :d=cur-(next*10)
  :dps=dps+d*(d*(d*(d*#d)))
  :cur=next
J (cur>0):*digit
T (dps=n):#n
C (dps=n):sum=sum+n
  :n=n+1
J (n<max):*number
T :Total: #sum
E :
Output:
4150
4151
54748
92727
93084
194979
Total: 443839

PL/M

100H:
/* BDOS ROUTINES */
BDOS: PROCEDURE (F,A); DECLARE F BYTE, A ADDRESS; GO TO 5; END BDOS;
EXIT: PROCEDURE; CALL BDOS(0,0); END EXIT;
PUT$CHAR: PROCEDURE (C); DECLARE C BYTE; CALL BDOS(2,C); END PUT$CHAR;
PRINT: PROCEDURE (S); DECLARE S ADDRESS; CALL BDOS(9,S); END PRINT;
NEW$LINE: PROCEDURE; CALL PRINT(.(13,10,'$')); END NEW$LINE;

/* THE NATIVE INTEGER TYPES ARE NOT BIG ENOUGH, SO WE NEED TO 
   MAKE OUR OWN */
DECLARE DGT$SIZE LITERALLY '6';
MAKE$DEC: PROCEDURE (N, BUF) ADDRESS;
    DECLARE (N, BUF) ADDRESS, (I, D BASED BUF) BYTE;
    DO I=0 TO DGT$SIZE-1;
        D(I) = N MOD 10;
        N = N/10;
    END;
    RETURN BUF;
END MAKE$DEC;

ADD: PROCEDURE (ACC, ADDEND) ADDRESS;
    DECLARE (ACC, ADDEND) ADDRESS;
    DECLARE (I, C, A BASED ACC, D BASED ADDEND) BYTE;
    C = 0;
    DO I=0 TO DGT$SIZE-1;
        A(I) = A(I) + D(I) + C;
        IF A(I) < 10 THEN
            C = 0;
        ELSE DO;
            A(I) = A(I) - 10;
            C = 1;
        END;
    END;
    RETURN ACC;
END ADD;

INCR: PROCEDURE (N);
    DECLARE N ADDRESS, (I, D BASED N) BYTE;
    DO I=0 TO DGT$SIZE-1;
        IF (D(I) := D(I) + 1) < 10 THEN
            RETURN;
        ELSE
            D(I) = 0;
    END;
END INCR;

EQUAL: PROCEDURE (A, B) BYTE;
    DECLARE (A, B) ADDRESS, (DA BASED A, DB BASED B, I) BYTE; 
    DO I=0 TO DGT$SIZE-1;
        IF DA(I) <> DB(I) THEN RETURN 0;
    END;
    RETURN 0FFH;
END EQUAL;

PRINT$NUM: PROCEDURE (N);
    DECLARE N ADDRESS, (I, D BASED N) BYTE;
    I = DGT$SIZE-1;
    DO WHILE I <> -1 AND D(I) = 0;
        I = I-1;
    END;
    
    DO WHILE I <> -1;
        CALL PUT$CHAR('0' + D(I));
        I = I-1;
    END;
END PRINT$NUM;

/* GENERATE A TABLE OF DIGIT POWERS BEFOREHAND */
DECLARE NATIVE$POWER$5 (10) ADDRESS INITIAL 
    (0, 1, 32, 243, 1024, 3125, 7776, 16807, 32768, 59049);
DECLARE POWER$5 (10) ADDRESS;
DECLARE POWER$BUF (60) BYTE;
DECLARE P BYTE;
DO P=0 TO 9;
    POWER$5(P) = MAKE$DEC(NATIVE$POWER$5(P), .POWER$BUF(DGT$SIZE * P));
END;

/* DIGITS OF SEARCH LIMIT (9**5 * 6) IN LOW ENDIAN ORDER */
DECLARE MAX (DGT$SIZE) BYTE INITIAL (4,9,2,4,5,3);

/* SUM THE 5-POWERS OF THE DIGITS OF N */
SUM$5: PROCEDURE (N, BUF) ADDRESS;
    DECLARE (N, BUF) ADDRESS, (I, D BASED N) BYTE;
    
    BUF = MAKE$DEC(0, BUF);
    DO I=0 TO DGT$SIZE-1;
        BUF = ADD(BUF, POWER$5(D(I)));
    END;
    RETURN BUF;
END SUM$5;

DECLARE CUR (DGT$SIZE) BYTE INITIAL (2,0,0,0,0,0);
DECLARE TOTAL$BUF (DGT$SIZE) BYTE;
DECLARE TOTAL ADDRESS;
TOTAL = MAKE$DEC(0, .TOTAL$BUF);

/* TEST EACH NUMBER */
DO WHILE NOT EQUAL(.CUR, .MAX);
    IF EQUAL(SUM5(.CUR, .MEMORY), .CUR) THEN DO;
        TOTAL = ADD(TOTAL, .CUR);
        CALL PRINT$NUM(.CUR);
        CALL NEWLINE;
    END;
    CALL INCR(.CUR);
END;

CALL PRINT(.'TOTAL: $');
CALL PRINT$NUM(TOTAL);
CALL NEWLINE;
CALL EXIT;
EOF
Output:
4150
4151
54748
92727
93084
194979
TOTAL: 443839

Python

Comparing conventional vs. faster.

from time import time

# conventional
st = time()
print(sum([n for n in range(2, 6*9**5) if sum(int(i)**5 for i in str(n)) == n]), "  ", (time() - st) * 1000, "ms")

# faster
st = time()
nums = list(range(10))
nu = list(range(((6 * 9**5) // 100000) + 1))
numbers = []
p5 = []
for i in nums: p5.append(i**5)
for i in nu:
    im = i * 100000
    ip = p5[i]
    for j in nums:
        jm = im + 10000 * j
        jp = ip + p5[j]
        for k in nums:
            km = jm + 1000 * k
            kp = jp + p5[k]
            for l in nums:
                lm = km + 100 * l
                lp = kp + p5[l]
                for m in nums:
                    mm = lm + 10 * m
                    mp = lp + p5[m]
                    for n in nums:
                        nm = mm + n
                        np = mp + p5[n]
                        if np == nm:
                            if nm > 1: numbers.append(nm)
print(sum(numbers), "  ", (time() - st) * 1000, "ms", end = "")
Output @ Tio.run:
443839    195.04594802856445 ms
443839    22.282838821411133 ms
Around eight times faster.


Quackery

Credit to the Julia example for deducing that 9^5*6 is an upper bound.

The 1 - at the end is to deduct the precluded solution, 1.

  [ [] swap
    [ 10 /mod
      rot join swap
      dup 0 = until ]
    drop ]              is digits ( n --> [ )

  0
  9 5 ** 6 * times
    [ i^ 0 over digits
      witheach [ 5 ** + ]
      = if [ i^ + ] ]
  1 - echo
Output:
443839

Raku

print q:to/EXPANATION/;
Sum of all integers (except 1 for some mysterious reason ¯\_(ツ)_/¯),
for which the individual digits to the nth power sum to itself.
EXPANATION

sub super($i) { $i.trans('0123456789' => '⁰¹²³⁴⁵⁶⁷⁸⁹') }

for 3..8 -> $power {
    print "\nSum of powers of n{super $power}: ";
    my $threshold = 9**$power * $power;
    put .join(' + '), ' = ', .sum with cache
    (2..$threshold).hyper.map: {
        state %p = ^10 .map: { $_ => $_ ** $power };
        $_ if %p{.comb}.sum == $_
    }
}
Output:
Sum of all integers (except 1 for some mysterious reason ¯\_(ツ)_/¯),
for which the individual digits to the nth power sum to itself.

Sum of powers of n³: 153 + 370 + 371 + 407 = 1301

Sum of powers of n⁴: 1634 + 8208 + 9474 = 19316

Sum of powers of n⁵: 4150 + 4151 + 54748 + 92727 + 93084 + 194979 = 443839

Sum of powers of n⁶: 548834 = 548834

Sum of powers of n⁷: 1741725 + 4210818 + 9800817 + 9926315 + 14459929 = 40139604

Sum of powers of n⁸: 24678050 + 24678051 + 88593477 = 137949578

REXX

/* numbers that are equal to the sum of their digits raised to the power 5 */

maximum = 9**5 * 6
total = 0
out = ''
do i = 2 to maximum 
    if sum5(i) = i then do
        if out \= '' then out = out || ' + '
        out = out || i
        total = total + i
    end
end
say out || ' = ' || total 
exit

sum5: procedure 
    arg num
    result = 0
    do i = 1 to length(num)
        result = result + substr(num, i, 1) ** 5
    end
    return result
Output:
4150 + 4151 + 54748 + 92727 + 93084 + 194979 = 443839

Ring

Conventional

? "working..."
 
sumEnd = 0
sumList = ""

pow5 = []
for i = 1 to 9
    add(pow5, pow(i, 5))
next

limitStart = 2
limitEnd = 6 * pow5[9]

for n = limitStart to limitEnd
    sum = 0
    m = n
    while m > 0
        d = m % 10
        if d > 0 sum += pow5[d] ok
        m = unsigned(m, 10, "/")
    end
    if sum = n
       sumList += "" + n + " + "
       sumEnd += n
    ok
next
 
? "The sum of all the numbers that can be written as the sum of fifth powers of their digits:"
? substr(sumList, 1, len(sumList) - 2) + "= " + sumEnd
? "done..."
Output:
working...
The sum of all the numbers that can be written as the sum of fifth powers of their digits:
4150 + 4151 + 54748 + 92727 + 93084 + 194979 = 443839
done...

Faster

Around six times faster than the conventional version.

st = clock()
lst9 = 1:10 lst3 = 1:4
p5 = [] m5 = [] m4 = [] m3 = [] m2 = [] m1 = []
for i in lst9
  add(p5, pow(i - 1, 5)) add(m1, (i - 1) * 10) add(m2, m1[i] * 10)
  add(m3, m2[i] * 10) add(m4, m3[i] * 10) add(m5, m4[i] * 10)
next

s = 0 t = ""
for i in lst3 ip = p5[i] im = m5[i]
  for j in lst9 jp = ip + p5[j] jm = im + m4[j]
    for k in lst9 kp = jp + p5[k] km = jm + m3[k]
      for l in lst9 lp = kp + p5[l] lm = km + m2[l]
        for m in lst9 mp = lp + p5[m] mm = lm + m1[m]
          for n in lst9 np = mp + p5[n] nm = mm + n - 1
            if nm = np and nm > 1
              if t != "" t += " + " ok
              s += nm t += nm
            ok
next next next next next next
et = clock()
put t + " = " + s + "  " + (et - st) / clockspersecond() + " sec"
Output @ Tio.run:
4150 + 4151 + 54748 + 92727 + 93084 + 194979 = 443839  4.90 sec

RPL

Brute force approach

The code below could have worked... if the time dog of the RPL emulator did not interrupt the execution after a few minutes.

≪ 2 999999 FOR n
     n →STR DUP SIZE 0 1 ROT FOR j
        OVER j DUP SUB STR→ 5 ^ + 
     NEXT 
     IF n ≠ THEN DROP END 
  NEXT

Smarter approach

Works with: Halcyon Calc version 4.2.7

So as not to wake the time dog, the execution has been broken into several parts and the algorithm has been improved:

  1. the program does not generate all the compliant numbers, but only provides the next value of the sequence, given the first ones
  2. since 9^5 = 59094, we do not need to check if the sum of the powered digits matches for numbers with a 9 and less than 59094
  3. on the other side, 6 * 7^5 = 100842, which means that 6-digit numbers above this value must have at least an 8 or a 9 in their digits to comply
  4. as 6 * 9^5 = 354424, there can't be any compliant 6-digit number above this value
≪ DUP SIZE 0 1 ROT FOR j
     OVER j DUP SUB STR→ 5 ^ +
  NEXT
  SWAP DROP
  IF DUP2 == THEN 1 SF ROT + SWAP ELSE DROP END
≫  
'Chk5p' STO  

≪ DROP 
  IF DUP SIZE THEN DUP LIST→ →ARRY RNRM 1 + ELSE 2 END
  1 CF DO 
     DUP →STR 
     IF OVER 59094 ≤ 
     THEN IF DUP "9" POS NOT THEN Chk5p ELSE DROP END 
     ELSE IF OVER 100842 ≥
          THEN IF DUP "9" POS OVER "8" POS OR THEN Chk5p ELSE DROP END 
          ELSE Chk5p 
          END 
     END 
     1 + 
  UNTIL 1 FS? DUP 354424 == OR END 
  DROP DUP LIST→ →ARRY CNRM 
≫
'NXT5P' STO
{} 0 NXT5P
NXT5P
NXT5P
NXT5P
NXT5P
NXT5P
Output:
2: { 194979 93084 92727 54748 4151 4150 }
1: 443839

Ruby

Translation of Julia.

arr = (2..9**5*6).select{|n| n.digits.sum{|d| d**5} == n }
puts "#{arr.join(" + ")} = #{arr.sum}"
Output:
4150 + 4151 + 54748 + 92727 + 93084 + 194979 = 443839

Seed7

$ include "seed7_05.s7i";

const proc: main is func
  local
    var integer: i is 0;
    var integer: n is 0;
    var integer: sum is 0;
    var integer: digitsum is 0;
  begin
    for i range 2 to 9 ** 5 * 6 do
      n := i;
      while n > 0 do
        digitsum +:= (n mod 10) ** 5;
        n := n div 10;
      end while;
      if digitsum = i then
        sum +:= i;
      end if;
      digitsum := 0;
    end for;
    writeln(sum);
  end func;
Output:
443839

Sidef

func digit_nth_powers(n, base=10) {

    var D = @(^base)
    var P = D.map {|d| d**n }
    var A = []
    var m = (base-1)**n

    for(var (k, t) = (1, 1); k*m >= t; (++k, t*=base)) {
        D.combinations_with_repetition(k, {|*c|
            var v = c.sum {|d| P[d] }
            A.push(v) if (v.digits(base).sort == c)
        })
    }

    A.sort.grep { _ > 1 }
}

for n in (3..8) {
    var a = digit_nth_powers(n)
    say "Sum of #{n}-th powers of their digits: #{a.join(' + ')} = #{a.sum}"
}
Output:
Sum of 3-th powers of their digits: 153 + 370 + 371 + 407 = 1301
Sum of 4-th powers of their digits: 1634 + 8208 + 9474 = 19316
Sum of 5-th powers of their digits: 4150 + 4151 + 54748 + 92727 + 93084 + 194979 = 443839
Sum of 6-th powers of their digits: 548834 = 548834
Sum of 7-th powers of their digits: 1741725 + 4210818 + 9800817 + 9926315 + 14459929 = 40139604
Sum of 8-th powers of their digits: 24678050 + 24678051 + 88593477 = 137949578

Wren

Library: Wren-math

Using the Julia entry's logic to arrive at an upper bound:

import "./math" for Int

// cache 5th powers of digits
var dp5 = (0..9).map { |d| d.pow(5) }.toList

System.print("The sum of all numbers that can be written as the sum of the 5th powers of their digits is:")
var limit = dp5[9] * 6
var sum = 0
for (i in 2..limit) {
    var digits = Int.digits(i)
    var totalDp = digits.reduce(0) { |acc, d| acc + dp5[d] }
    if (totalDp == i) {
        System.write((sum > 0) ? " + %(i)" : i)
        sum = sum + i
    }
}
System.print(" = %(sum)")
Output:
The sum of all numbers that can be written as the sum of the 5th powers of their digits is:
4150 + 4151 + 54748 + 92727 + 93084 + 194979 = 443839

XPL0

Since 1 is not actually a sum, it should not be included. Thus the answer should be 443839.

\upper bound: 6*9^5 = 354294
\7*9^5 is still only a 6-digit number, so 6 digits are sufficient

int     A, B, C, D, E, F,       \digits, A=LSD
        A5, B5, C5, D5, E5, F5, \digits to 5th power
        A0, B0, C0, D0, E0, F0, \digits multiplied by their decimal place
        N,              \number that can be written as the sum of its 5th pwrs
        S;              \sum of all numbers

[S:= 0;

for A:= 0, 9 do                 \for all digits
  [A5:= A*A*A*A*A;
  A0:= A;
  for B:= 0, 9 do
    [B5:= B*B*B*B*B;
    B0:= B*10;
    for C:= 0, 9 do
      [C5:= C*C*C*C*C;
      C0:= C*100;
      for D:= 0, 9 do
        [D5:= D*D*D*D*D;
        D0:= D*1000;
        for E:= 0, 9 do
          [E5:= E*E*E*E*E;
          E0:= E*10000;
          for F:= 0, 3 do
            [F5:= F*F*F*F*F;
            F0:= F*100000;
                [N:= F0 + E0 + D0 + C0 + B0 + A0;
                if N = A5 + B5 + C5 + D5 + E5 + F5 then
                        [S:= S + N;
                        IntOut(0, N);
                        CrLf(0);
                        ];
                ];
            ];
          ];
        ];
      ];
    ];
  ];
CrLf(0);
IntOut(0, S);
CrLf(0);
]
Output:
0
4150
1
4151
93084
92727
54748
194979

443840

Zig

const std = @import("std");

fn sum5(n: u32) u32 {
    var i = n;
    var r: u32 = 0;
    while (i != 0) : (i /= 10)
       r += std.math.pow(u32, i%10, 5);
    return r;
}

pub fn main() !void {
    const stdout = std.io.getStdOut().writer();
    const max = std.math.pow(u32,9,5) * 6;
    
    var n: u32 = 2;
    var total: u32 = 0;
    while (n <= max) : (n += 1) {
        if (sum5(n) == n) {
            try stdout.print("{d:6}\n", .{n});
            total += n;
        }
    }

    try stdout.print("Total: {d:6}\n", .{total});
}
Output:
  4150
  4151
 54748
 92727
 93084
194979
Total: 443839