Sum digits of an integer

From Rosetta Code
Task
Sum digits of an integer
You are encouraged to solve this task according to the task description, using any language you may know.
Task

Take a   Natural Number   in a given base and return the sum of its digits:

  •   110         sums to   1
  •   123410   sums to   10
  •   fe16       sums to   29
  •   f0e16     sums to   29



11l

Translation of: Nim
F sum_digits(=n, base)
   V r = 0
   L n > 0
      r += n % base
      n I/= base
   R r

print(sum_digits(1, 10))
print(sum_digits(1234, 10))
print(sum_digits(F'E, 16))
print(sum_digits(0F'0E, 16))
Output:
1
10
29
29

360 Assembly

Translation of: REXX

The program uses two ASSIST macro (XDECO,XPRNT) to keep the code as short as possible.

*        Sum digits of an integer  08/07/2016
SUMDIGIN CSECT
         USING  SUMDIGIN,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            " addressability
         LA     R11,NUMBERS        @numbers
         LA     R8,1               k=1
LOOPK    CH     R8,=H'4'           do k=1 to hbound(numbers)
         BH     ELOOPK             "
         SR     R10,R10              sum=0
         LA     R7,1                 j=1
LOOPJ    CH     R7,=H'8'             do j=1 to length(number)
         BH     ELOOPJ               "
         LR     R4,R11                 @number
         BCTR   R4,0                   -1
         AR     R4,R7                  +j
         MVC    D,0(R4)                d=substr(number,j,1)
         SR     R9,R9                  ii=0
         SR     R6,R6                  i=0
LOOPI    CH     R6,=H'15'              do i=0 to 15
         BH     ELOOPI                 "
         LA     R4,DIGITS                @digits
         AR     R4,R6                    i
         MVC    C,0(R4)                  c=substr(digits,i+1,1)
         CLC    D,C                      if d=c
         BNE    NOTEQ                    then
         LR     R9,R6                      ii=i
         B      ELOOPI                     leave i
NOTEQ    LA     R6,1(R6)                 i=i+1
         B      LOOPI                  end do i
ELOOPI   AR     R10,R9                 sum=sum+ii
         LA     R7,1(R7)               j=j+1
         B      LOOPJ                end do j
ELOOPJ   MVC    PG(8),0(R11)         number
         XDECO  R10,XDEC             edit sum
         MVC    PG+8(8),XDEC+4       output sum
         XPRNT  PG,L'PG              print buffer
         LA     R11,8(R11)           @number=@number+8
         LA     R8,1(R8)             k=k+1
         B      LOOPK              end do k
ELOOPK   L      R13,4(0,R13)       epilog 
         LM     R14,R12,12(R13)    " restore
         XR     R15,R15            " rc=0
         BR     R14                exit
DIGITS   DC     CL16'0123456789ABCDEF'
NUMBERS  DC     CL8'1',CL8'1234',CL8'FE',CL8'F0E'
C        DS     CL1
D        DS     CL1
PG       DC     CL16' '            buffer
XDEC     DS     CL12               temp
         YREGS
         END    SUMDIGIN
Output:
1              1
1234          10
FE            29
F0E           29

8086 Assembly

	cpu	8086
	org	100h
section	.text
	jmp	demo
	;;;	Sum of digits of AX in base BX.
	;;;	Returns: AX = result
	;;;	CX, DX destroyed.
digsum:	xor	cx,cx		; Result
.loop:	xor	dx,dx		; Divide AX by BX
	div	bx		; Quotient in AX, modulus in DX
	add	cx,dx		; Add digit to sum
	test	ax,ax		; Is the quotient now zero?
	jnz	.loop		; If not, keep going
	mov	ax,cx		; Otherwise, return
	ret
	;;;	Print the value of AX in decimal using DOS.	
	;;;	(Note the similarity.)
pr_ax:	mov	bx,num		; Number buffer pointer
	mov	cx,10		; Divisor
.loop:	xor	dx,dx		; Get digit
	div	cx
	add	dl,'0'		; Make ASCII digit
	dec	bx		; Store in buffer
	mov	[bx],dl
	test	ax,ax		; More digits?
	jnz	.loop		; If so, keep going
	mov	dx,bx		; Begin of number in DX
	mov	ah,9		; MS-DOS syscall 9 prints $-terminated string
	int	21h
	ret
	;;;	Run the function on the given examples
demo:	mov	si,tests	; Pointer to example array
.loop:	lodsw			; Get base
	test	ax,ax		; If 0, we're done
	jz	.done
	xchg	bx,ax
	lodsw			; Get number
	call	digsum		; Calculate sum of digits
	call	pr_ax		; Print sum of digits
	jmp	.loop		; Get next pair
.done:	ret
section	.data
	db	'*****'		; Placeholder for numeric output
num:	db	13,10,'$'
tests:	dw	10, 1		; Examples
	dw	10, 1234
	dw	16, 0FEh
	dw	16, 0F0Eh
	dw	0		; End marker
Output:
1
10
29
29

Action!

CARD FUNC SumDigits(CARD num,base)
  CARD res,a

  res=0
  WHILE num#0
  DO
    res==+num MOD base
    num=num/base
  OD
RETURN(res)

PROC Main()
  CARD ARRAY data=[
      1 10  1234 10  $FE 16  $F0E 16
      $FF 2  0 2  2186 3  2187 3]
  BYTE i
  CARD num,base,res

  FOR i=0 TO 15 STEP 2
  DO
    num=data(i)
    base=data(i+1)
    res=SumDigits(num,base)
    PrintF("num=%U base=%U sum=%U%E",num,base,res)
  OD
RETURN
Output:

Screenshot from Atari 8-bit computer

num=1 base=10 sum=1
num=1234 base=10 sum=10
num=254 base=16 sum=29
num=3854 base=16 sum=29
num=255 base=2 sum=8
num=0 base=2 sum=0
num=2186 base=3 sum=14
num=2187 base=3 sum=1

Ada

Numeric constants in Ada are either decimal or written as B#Digits#. Here B is the base, written as a decimal number, and Digits is a base-B number. E.g., 30, 10#30# 2#11110#, and 16#1E# are the same number -- either written in decimal, binary or hexadecimal notation.

with Ada.Integer_Text_IO;

procedure Sum_Digits is
   -- sums the digits of an integer (in whatever base)
   -- outputs the sum (in base 10)

   function Sum_Of_Digits(N: Natural; Base: Natural := 10) return Natural is
      Sum: Natural := 0;
      Val: Natural := N;
   begin
      while Val > 0 loop
         Sum := Sum + (Val mod Base);
         Val := Val / Base;
      end loop;
      return Sum;
   end Sum_Of_Digits;

   use Ada.Integer_Text_IO;

begin -- main procedure Sum_Digits
   Put(Sum_OF_Digits(1));            --   1
   Put(Sum_OF_Digits(12345));        --  15
   Put(Sum_OF_Digits(123045));       --  15
   Put(Sum_OF_Digits(123045,  50));  -- 104
   Put(Sum_OF_Digits(16#fe#,  10));  --  11
   Put(Sum_OF_Digits(16#fe#,  16));  --  29
   Put(Sum_OF_Digits(16#f0e#, 16));  --  29
end Sum_Digits;
Output:
          1         15         15        104         11         29         29

ALGOL 68

Works with: ALGOL 68G version Any - tested with release 2.8.win32
# operator to return the sum of the digits of an integer value in the #
# specified base                                                      #
PRIO SUMDIGITS = 1;
OP   SUMDIGITS = ( INT value, INT base )INT:
     IF base < 2
     THEN
         # invalid base #
         print( ( "Base for digit sum must be at least 2", newline ) );
         stop
     ELSE
         # the base is OK #
         INT    result := 0;
         INT    rest   := ABS value;

         WHILE rest /= 0
         DO
             result PLUSAB ( rest MOD base );
             rest   OVERAB base
         OD;

         result
     FI; # SUMDIGITS #

# additional operator so we can sum the digits of values expressed in #
# other than base 10, e.g. 16ra is a hex lteral with value 10         #
# (Algol 68 allows bases 2, 4, 8 and 16 for non-base 10 literals)     #
# however as such literals are BITS values, not INTs, we need this    #
# second operator                                                     #
OP   SUMDIGITS = ( BITS value, INT base )INT: ABS value SUMDIGITS base;

main:(

    # test the SUMDIGITS operator #

    print( ( "value\base base digit-sum", newline ) );
    print( ( "      1\10   10 ", whole(      1 SUMDIGITS 10, -9 ), newline ) );
    print( ( "   1234\10   10 ", whole(   1234 SUMDIGITS 10, -9 ), newline ) );
    print( ( "     fe\16   16 ", whole(  16rfe SUMDIGITS 16, -9 ), newline ) );
    print( ( "    f0e\16   16 ", whole( 16rf0e SUMDIGITS 16, -9 ), newline ) );

    # of course, we don't have to express the number in the base we sum #
    # the digits in...                                                  #
    print( ( "     73\10   71 ", whole(     73 SUMDIGITS 71, -9 ), newline ) )

)
Output:
value\base base digit-sum
      1\10   10         1
   1234\10   10        10
     fe\16   16        29
    f0e\16   16        29
     73\10   71         3


AppleScript

----------------- SUM DIGITS OF AN INTEGER -----------------

-- baseDigitSum :: Int -> Int -> Int
on baseDigitSum(base)
    script
        on |λ|(n)
            script go
                on |λ|(x)
                    if 0 < x then
                        Just({x mod base, x div base})
                    else
                        Nothing()
                    end if
                end |λ|
            end script
            sum(unfoldl(go, n))
        end |λ|
    end script
end baseDigitSum


--------------------------- TEST ---------------------------
on run
    {ap(map(baseDigitSum, {2, 8, 10, 16}), {255}), ¬
        ap(map(baseDigitSum, {10}), {1, 1234}), ¬
        ap(map(baseDigitSum, {16}), map(readHex, {"0xfe", "0xf0e"}))}
    
    --> {{8, 17, 12, 30}, {1, 10}, {29, 29}}
end run


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

-- Just :: a -> Maybe a
on Just(x)
    -- Constructor for an inhabited Maybe (option type) value.
    -- Wrapper containing the result of a computation.
    {type:"Maybe", Nothing:false, Just:x}
end Just


-- Nothing :: Maybe a
on Nothing()
    -- Constructor for an empty Maybe (option type) value.
    -- Empty wrapper returned where a computation is not possible.
    {type:"Maybe", Nothing:true}
end Nothing


-- Each member of a list of functions applied to
-- each of a list of arguments, deriving a list of new values
-- ap (<*>) :: [(a -> b)] -> [a] -> [b]
on ap(fs, xs)
    set lst to {}
    repeat with f in fs
        tell mReturn(contents of f)
            repeat with x in xs
                set end of lst to |λ|(contents of x)
            end repeat
        end tell
    end repeat
    return lst
end ap


-- elemIndex :: Eq a => a -> [a] -> Maybe Int
on elemIndex(x, xs)
    set lng to length of xs
    repeat with i from 1 to lng
        if x = (item i of xs) then return Just(i - 1)
    end repeat
    return Nothing()
end elemIndex


-- foldl :: (a -> b -> a) -> a -> [b] -> a
on foldl(f, startValue, xs)
    tell mReturn(f)
        set v to startValue
        set lng to length of xs
        repeat with i from 1 to lng
            set v to |λ|(v, item i of xs, i, xs)
        end repeat
        return v
    end tell
end foldl


-- foldr :: (a -> b -> b) -> b -> [a] -> b
on foldr(f, startValue, xs)
    tell mReturn(f)
        set v to startValue
        set lng to length of xs
        repeat with i from lng to 1 by -1
            set v to |λ|(item i of xs, v, i, xs)
        end repeat
        return v
    end tell
end foldr


-- identity :: a -> a
on identity(x)
    -- The argument unchanged.
    x
end identity


-- map :: (a -> b) -> [a] -> [b]
on map(f, xs)
    -- The list obtained by applying f
    -- to each element of xs.
    tell mReturn(f)
        set lng to length of xs
        set lst to {}
        repeat with i from 1 to lng
            set end of lst to |λ|(item i of xs, i, xs)
        end repeat
        return lst
    end tell
end map


-- maybe :: b -> (a -> b) -> Maybe a -> b
on maybe(v, f, mb)
    -- Either the default value v (if mb is Nothing),
    -- or the application of the function f to the 
    -- contents of the Just value in mb.
    if Nothing of mb then
        v
    else
        tell mReturn(f) to |λ|(Just of mb)
    end if
end maybe


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


-- readHex :: String -> Int
on readHex(s)
    -- The integer value of the given hexadecimal string.
    set ds to "0123456789ABCDEF"
    script go
        on |λ|(c, a)
            set {v, e} to a
            set i to maybe(0, my identity, elemIndex(c, ds))
            {v + (i * e), 16 * e}
        end |λ|
    end script
    item 1 of foldr(go, {0, 1}, characters of s)
end readHex


-- sum :: [Num] -> Num
on sum(xs)
    script add
        on |λ|(a, b)
            a + b
        end |λ|
    end script
    
    foldl(add, 0, xs)
end sum


-- > unfoldl (\b -> if b == 0 then Nothing else Just (b, b-1)) 10
-- > [1,2,3,4,5,6,7,8,9,10]
-- unfoldl :: (b -> Maybe (b, a)) -> b -> [a]
on unfoldl(f, v)
    set xr to {v, v} -- (value, remainder)
    set xs to {}
    tell mReturn(f)
        repeat -- Function applied to remainder.
            set mb to |λ|(item 2 of xr)
            if Nothing of mb then
                exit repeat
            else -- New (value, remainder) tuple,
                set xr to Just of mb
                -- and value appended to output list.
                set xs to ({item 1 of xr} & xs)
            end if
        end repeat
    end tell
    return xs
end unfoldl
Output:
{{8, 17, 12, 30}, {1, 10}, {29, 29}}

APL

sd+/¯1
Output:
      10 sd 12345
15
      16 sd 254
29

ArnoldC

LISTEN TO ME VERY CAREFULLY sumDigits
I NEED YOUR CLOTHES YOUR BOOTS AND YOUR MOTORCYCLE n
I NEED YOUR CLOTHES YOUR BOOTS AND YOUR MOTORCYCLE base
GIVE THESE PEOPLE AIR
HEY CHRISTMAS TREE sum
YOU SET US UP @I LIED
STICK AROUND n
HEY CHRISTMAS TREE digit
YOU SET US UP @I LIED
GET TO THE CHOPPER digit
HERE IS MY INVITATION n
I LET HIM GO base
ENOUGH TALK
GET TO THE CHOPPER sum
HERE IS MY INVITATION sum
GET UP digit
ENOUGH TALK
GET TO THE CHOPPER n
HERE IS MY INVITATION n
HE HAD TO SPLIT base
ENOUGH TALK
CHILL
I'LL BE BACK sum
HASTA LA VISTA, BABY

IT'S SHOWTIME
HEY CHRISTMAS TREE sum
YOU SET US UP @I LIED
GET YOUR A** TO MARS sum
DO IT NOW sumDigits 12345 10
TALK TO THE HAND "sumDigits 12345 10 ="
TALK TO THE HAND sum
GET YOUR A** TO MARS sum
DO IT NOW sumDigits 254 16
TALK TO THE HAND "sumDigits 254 16 ="
TALK TO THE HAND sum
YOU HAVE BEEN TERMINATED
Output:
sumDigits 12345 10 =
15
sumDigits 254 16 =
29

Arturo

Translation of: Nim
sumDigits: function [n base][
	result: 0
	while [n>0][
		result: result + n%base
		n: n/base
    ]
	return result
]
 
print sumDigits 1 10
print sumDigits 12345 10
print sumDigits 123045 10
print sumDigits from.hex "0xfe" 16
print sumDigits from.hex "0xf0e" 16
Output:
1
15
15
29
29

ATS

(* ****** ****** *)
//
// How to compile:
// patscc -DATS_MEMALLOC_LIBC -o SumDigits SumDigits.dats
//
(* ****** ****** *)
//
#include
"share/atspre_staload.hats"
//
(* ****** ****** *)

extern
fun{a:t@ype}
SumDigits(n: a, base: int): a

implement
{a}(*tmp*)
SumDigits(n, base) = let
//
val base = gnumber_int(base)
//
fun
loop (n: a, res: a): a =
  if gisgtz_val<a> (n)
    then loop (gdiv_val<a>(n, base), gadd_val<a>(res, gmod_val<a>(n, base)))
    else res
//
in
  loop (n, gnumber_int(0))
end // end of [SumDigits]

(* ****** ****** *)

val SumDigits_int = SumDigits<int>

(* ****** ****** *)

implement
main0 () =
{
//
val n = 1
val () = println! ("SumDigits(1, 10) = ", SumDigits_int(n, 10))
val n = 12345
val () = println! ("SumDigits(12345, 10) = ", SumDigits_int(n, 10))
val n = 123045
val () = println! ("SumDigits(123045, 10) = ", SumDigits_int(n, 10))
val n = 0xfe
val () = println! ("SumDigits(0xfe, 16) = ", SumDigits_int(n, 16))
val n = 0xf0e
val () = println! ("SumDigits(0xf0e, 16) = ", SumDigits_int(n, 16))
//
} (* end of [main0] *)
Output:
SumDigits(1, 10) = 1
SumDigits(12345, 10) = 15
SumDigits(123045, 10) = 15
SumDigits(0xfe, 16) = 29
SumDigits(0xf0e, 16) = 29

AutoHotkey

Translated from the C version.

MsgBox % sprintf("%d %d %d %d %d`n"
	,SumDigits(1, 10)
	,SumDigits(12345, 10)
	,SumDigits(123045, 10)
	,SumDigits(0xfe, 16)
	,SumDigits(0xf0e, 16) )

SumDigits(n,base) {
	sum := 0
	while (n)
	{
		sum += Mod(n,base)
		n /= base
	}
	return sum
}

sprintf(s,fmt*) {
	for each, f in fmt
		StringReplace,s,s,`%d, % f
	return s
}
Output:
1 15 15 29 29

AWK

MAWK only support base 10 numeric constants, so a conversion function is necessary.

Will sum digits in numbers from base 2 to base 16.

The output is in decimal. Output in other bases would require a function to do the conversion because MAWK's printf() does not support bases other than 10.

Other versions of AWK may not have these limitations.

#!/usr/bin/awk -f

BEGIN {
    print sumDigits("1")
    print sumDigits("12")
    print sumDigits("fe")
    print sumDigits("f0e")
}

function sumDigits(num,    nDigs, digits, sum, d, dig, val, sum) {
    nDigs = split(num, digits, "")
    sum = 0
    for (d = 1; d <= nDigs; d++) {
        dig = digits[d]
        val = digToDec(dig)
        sum += val
    }
    return sum
}

function digToDec(dig) {
    return index("0123456789abcdef", tolower(dig)) - 1
}
Output:
 1
 3
 29
 29

BASIC

Works with: QBasic
Works with: PowerBASIC
Works with: FreeBASIC
Translation of: Visual Basic

Note that in order for this to work with the Windows versions of PowerBASIC, the test code (the block at the end containing the PRINT lines) needs to be inside FUNCTION PBMAIN.

FUNCTION sumDigits(num AS STRING, bas AS LONG) AS LONG
    'can handle up to base 36
    DIM outp AS LONG
    DIM validNums AS STRING, tmp AS LONG, x AS LONG, lennum AS LONG, L0 AS LONG
    'ensure num contains only valid characters
    validNums = LEFT$("0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ", bas)
    lennum = LEN(num)
    FOR L0 = lennum TO 1 STEP -1
        x = INSTR(validNums, UCASE$(MID$(num, L0, 1))) - 1
        IF -1 = x THEN EXIT FUNCTION
        tmp = tmp + (x * (bas ^ (lennum - L0)))
    NEXT
    WHILE tmp
        outp = outp + (tmp MOD bas)
        tmp = tmp \ bas
    WEND
    sumDigits = outp
END FUNCTION

PRINT sumDigits(LTRIM$(STR$(1)), 10)
PRINT sumDigits(LTRIM$(STR$(1234)), 10)
PRINT sumDigits(LTRIM$(STR$(&HFE)), 16)
PRINT sumDigits(LTRIM$(STR$(&HF0E)), 16)
PRINT sumDigits("2", 2)
Output:
 1
 10
 11
 20
 0

See also: BBC BASIC, Run BASIC, Visual Basic

Applesoft BASIC

10 BASE = 10
20 N$ = "1" : GOSUB 100 : PRINT N
30 N$ = "1234" : GOSUB 100 : PRINT N
40 BASE = 16
50 N$ = "FE" : GOSUB 100 : PRINT N
60 N$ = "F0E" : GOSUB 100 : PRINT N
90 END

100 REM SUM DIGITS OF N$, BASE
110 IF BASE = 1 THEN N = LEN(N$) : RETURN
120 IF BASE < 2 THEN BASE = 10
130 N = 0 : V$ = LEFT$("0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ", BASE)
140 FOR I = 1 TO LEN(N$) : C$ = MID$(N$, I, 1)
150     FOR J = 1 TO LEN(V$)
160         IF C$ <> MID$(V$, J, 1) THEN NEXT J : N = SQR(-1) : STOP
170     N = N + J - 1
180 NEXT I
190 RETURN

BASIC256

function SumDigits(number, nBase)
    if number < 0 then number = -number
    if nBase < 2 then nBase = 2
    sum = 0
    while number > 0
	sum += number mod nBase
	number /= nBase
    end while
    return sum
end function

print "The sums of the digits are:"
print
print "1    base 10 : "; SumDigits(1, 10)
print "1234 base 10 : "; SumDigits(1234, 10)
print "fe   base 16 : "; SumDigits(0xfe, 16)
print "f0e  base 16 : "; SumDigits(0xf0e, 16)
end

BBC BASIC

This solution deliberately avoids MOD and DIV so it is not restricted to 32-bit integers.

      *FLOAT64
      PRINT "Digit sum of 1 (base 10) is "; FNdigitsum(1, 10)
      PRINT "Digit sum of 12345 (base 10) is "; FNdigitsum(12345, 10)
      PRINT "Digit sum of 9876543210 (base 10) is "; FNdigitsum(9876543210, 10)
      PRINT "Digit sum of FE (base 16) is "; ~FNdigitsum(&FE, 16) " (base 16)"
      PRINT "Digit sum of F0E (base 16) is "; ~FNdigitsum(&F0E, 16) " (base 16)"
      END
      
      DEF FNdigitsum(n, b)
      LOCAL q, s
      WHILE n <> 0
        q = INT(n / b)
        s += n - q * b
        n = q
      ENDWHILE
      = s
Output:
Digit sum of 1 (base 10) is 1
Digit sum of 12345 (base 10) is 15
Digit sum of 9876543210 (base 10) is 45
Digit sum of FE (base 16) is 1D (base 16)
Digit sum of F0E (base 16) is 1D (base 16)

Chipmunk Basic

Works with: Chipmunk Basic version 3.6.4
Translation of: BASIC256
10 rem Sum digits of an integer
20 cls
30 print "The sums of the digits are:"
40 print
50 gosub 100 : print "1    base 10 : " sumdigits(1,10)
60 gosub 100 : print "1234 base 10 : ";sumdigits(1234,10)
70 gosub 100 : print "fe   base 16 : " sumdigits(254,16)
80 gosub 100 : print "f0e  base 16 : ";sumdigits(3854,16)
90 end
100 sub sumdigits(number,nbase)
110  if number < 0 then number = -number
120  if nbase < 2 then nbase = 2
130  sum = 0
140  while number > 0
150   sum = sum+(number-int(number/nbase)*nbase)
160   number = int(number/nbase)
170  wend
180  sumdigits = sum
190 return
(define dsum (lambda (x base) 
                 (let ((number (if (string? x) (string->number x base) x))) 
                 (if (= (string-length (number->string number)) 1) number 
                     (+ (mod number base) (dsum (div number base) base))))))
> (dsum  123 10)
6
> (dsum  "fe" 16)
29
> (dsum  "f0e" 16)
29
> (dsum  1234 10)
10

Craft Basic

define number = 0, base = 0, sum = 0

input "number: ", number
input "base: ", base

if number < 0 then

	let number = number * -1

endif

if base < 2 then

	let base = 2

endif

do

	if number > 0 then

		let sum = sum + number % base
		let number = int(number / base)

	endif

loop number > 0

print "sum of digits in base ", base, ": ", sum

end
Output:

number: 1234567 base: 10 sum of digits in base 10: 28

FreeBASIC

Translation of: PureBasic
' FB 1.05.0 Win64

Function SumDigits(number As Integer, nBase As Integer) As Integer
  If number < 0 Then number = -number  ' convert negative numbers to positive
  If nBase < 2 Then nBase = 2   ' nBase can't be less than 2
  Dim As Integer sum = 0
  While number > 0
    sum += number Mod nBase
    number \= nBase
  Wend
  Return sum
End Function
 
Print "The sums of the digits are:"
Print
Print "1    base 10 :"; SumDigits(1, 10)
Print "1234 base 10 :"; SumDigits(1234, 10)
Print "fe   base 16 :"; SumDigits(&Hfe, 16)
Print "f0e  base 16 :"; SumDigits(&Hf0e, 16) 
Print
Print "Press any key to quit the program"
Sleep
Output:
The sums of the digits are:

1    base 10 : 1
1234 base 10 : 10
fe   base 16 : 29
f0e  base 16 : 29

Gambas

Public Sub Main()
  
  Print "The sums of the digits are:\n" 
  Print "1    base 10 : "; SumDigits(1, 10) 
  Print "1234 base 10 : "; SumDigits(1234, 10) 
  Print "fe   base 16 : "; SumDigits(&Hfe, 16) 
  Print "f0e  base 16 : "; SumDigits(&Hf0e, 16) 

End

Function SumDigits(number As Integer, nBase As Integer) As Integer 

  If number < 0 Then number = -number  ' convert negative numbers to positive
  If nBase < 2 Then nBase = 2   ' nBase can't be less than 2
  Dim sum As Integer = 0 
  While number > 0 
    sum += number Mod nBase 
    number \= nBase 
  Wend 
  Return sum 

End Function
Output:
Same as FreeBASIC entry.

GW-BASIC

Works with: Applesoft BASIC
Works with: Chipmunk Basic
Works with: PC-BASIC version any
Works with: QBasic
Translation of: Applesoft BASIC
10 REM Sum digits of an integer
20 CLS : REM  20 HOME for Applesoft BASIC
30 BASE = 10
40 N$ = "1" : GOSUB 100 : PRINT "1    base 10 : " N
50 N$ = "1234" : GOSUB 100 : PRINT "1234 base 10 : " N
60 BASE = 16
70 N$ = "FE" : GOSUB 100 : PRINT "FE   base 16 : " N
80 N$ = "F0E" : GOSUB 100 : PRINT "F0E  base 16 : " N
90 END
100 REM SUM DIGITS OF N$, BASE
110 IF BASE = 1 THEN N = LEN(N$) : RETURN
120 IF BASE < 2 THEN BASE = 10
130 N = 0 : V$ = LEFT$("0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ", BASE)
140 FOR I = 1 TO LEN(N$) : C$ = MID$(N$, I, 1)
150   FOR J = 1 TO LEN(V$)
160     IF C$ <> MID$(V$, J, 1) THEN NEXT J : N = SQR(-1) : STOP
170   N = N + J - 1
180 NEXT I
190 RETURN

Minimal BASIC

Translation of: Tiny BASIC

Only base ten is supported. Minimal BASIC does not support operations on strings (except assignment to variables).

10 REM Sum digits of an integer
20 PRINT "Enter a number";
30 INPUT N
40 LET N = ABS(N)
50 LET S = 0
60 IF N = 0 THEN 100
70 LET S = S+N-10*INT(N/10)
80 LET N = INT(N/10)
90 GOTO 60
100 PRINT "Its digit sum:"; S
110 END

MSX Basic

Works with: MSX BASIC version any
10 CLS
20 PRINT "The sums of the digits are:" : PRINT
30 B = 10
40 N$ = "1" : GOSUB 100 : PRINT "1    base 10 :" N
50 N$ = "1234" : GOSUB 100 : PRINT "1234 base 10 :" N
60 B = 16
70 N$ = "FE" : GOSUB 100 : PRINT "FE   base 16 :" N
80 N$ = "F0E" : GOSUB 100 : PRINT "F0E  base 16 :" N
90 END
100 REM SUM DIGITS OF N$, B
110 IF B = 1 THEN N = LEN(N$) : RETURN
120 IF B < 2 THEN B = 10
130 N = 0 
140 V$ = LEFT$("0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ", B)
150 FOR I = 1 TO LEN(N$) 
160   C$ = MID$(N$, I, 1)
170   FOR J = 1 TO LEN(V$)
180     IF C$ <> MID$(V$, J, 1) THEN NEXT J : N = SQR(-1) : STOP
190   N = N + J - 1
200 NEXT I
210 RETURN
Output:
Similar to FreeBASIC entry.

Palo Alto Tiny BASIC

Translation of: Tiny BASIC

Only base ten is supported. Palo Alto Tiny BASIC does not support operations on strings.

10 REM SUM DIGITS OF AN INTEGER
20 INPUT "ENTER A NUMBER"N
30 LET N=ABS(N),U=0
40 IF N=0 GOTO 80
50 LET U=U+N-N/10*10
60 LET N=N/10
70 GOTO 40
80 PRINT "ITS DIGIT SUM:",U
90 STOP
Output:
ENTER A NUMBER:-12321
ITS DIGIT SUM:      9

PureBasic

EnableExplicit

Procedure.i SumDigits(Number.q, Base)
  If Number < 0 : Number = -Number : EndIf; convert negative numbers to positive
  If Base < 2 : Base = 2 : EndIf ; base can't be less than 2
  Protected sum = 0
  While Number > 0
    sum + Number % Base
    Number / Base
  Wend
  ProcedureReturn sum
EndProcedure
  
If OpenConsole()
  PrintN("The sums of the digits are:")
  PrintN("")
  PrintN("1    base 10 : " + SumDigits(1, 10))
  PrintN("1234 base 10 : " + SumDigits(1234, 10))
  PrintN("fe   base 16 : " + SumDigits($fe, 16))
  PrintN("f0e  base 16 : " + SumDigits($f0e, 16)) 
  PrintN("")
  PrintN("Press any key to close the console")
  Repeat: Delay(10) : Until Inkey() <> ""
  CloseConsole()
EndIf
Output:
The sums of the digits are:

1    base 10 : 1
1234 base 10 : 10
fe   base 16 : 29
f0e  base 16 : 29

QBasic

Works with: QBasic version 1.1
Works with: QuickBasic version 4.5
FUNCTION SumDigits (number, nBase)
    IF number < 0 THEN number = -number
    IF nBase < 2 THEN nBase = 2
    sum = 0

    DO WHILE number > 0
       sum = sum + (number MOD nBase)
       number = number \ nBase
    LOOP

    SumDigits = sum
END FUNCTION

PRINT "The sums of the digits are:"
PRINT
PRINT "1    base 10 :"; SumDigits(1, 10)
PRINT "1234 base 10 :"; SumDigits(1234, 10)
PRINT "fe   base 16 :"; SumDigits(&HFE, 16)
PRINT "f0e  base 16 :"; SumDigits(&HF0E, 16)
END

QuickBASIC

Works with: QBasic
Works with: QB64
Works with: VB-DOS
DECLARE FUNCTION SumDigits% (Num AS INTEGER, NBase AS INTEGER)

CLS
PRINT "1 base 10 ->"; SumDigits%(1, 10)
PRINT "1234 base 10 ->"; SumDigits%(1234, 10)
PRINT "FE base 16 ->"; SumDigits%(&HFE, 16); " (Hex -> "; HEX$(SumDigits%(&HFE, 16)); ")"
PRINT "F0E base 16 ->"; SumDigits%(&HF0E, 16); " (Hex -> "; HEX$(SumDigits%(&HF0E, 16)); ")"

FUNCTION SumDigits% (Num AS INTEGER, NBase AS INTEGER)
  ' Var
  DIM iSum AS INTEGER

  Num = ABS(Num)  ' Should be a positive number
  IF NBase < 2 THEN NBase = 10  ' Default decimal
  DO WHILE Num > 0
    iSum = iSum + (Num MOD NBase)
    Num = Num \ NBase
  LOOP
  SumDigits% = iSum
END FUNCTION
Output:
1 base 10 -> 1
1234 base 10 -> 10
FE base 16 -> 11
F0E base 16 -> 20

Run BASIC

Translation of: BASIC256
function SumDigits(number, nBase)
    if number < 0 then number = -1 * number ' convert negative numbers to positive
    if nBase < 2 then nBase = 2             ' nBase can//t be less than 2
    sum = 0
    while number > 0
        sum = sum + (number mod nBase)
        number = int(number / nBase)
    wend
    SumDigits = sum
end function

print "The sums of the digits are:\n"
print "1    base 10 : "; SumDigits(1, 10)
print "1234 base 10 : "; SumDigits(1234, 10)
print "fe   base 16 : "; SumDigits(hexdec("FE"), 16)
print "f0e  base 16 : "; SumDigits(hexdec("F0E"), 16)

==={{header|TI-83 BASIC}}===
<syntaxhighlight lang="ti-83b">"01234567890ABCDEFGHIJKLMNOPQRSTUVWXYZ"→Str1
Disp "SUM DIGITS OF INT"
Disp "-----------------"
Disp "ENTER NUMBER"
Input Str2
Disp "ENTER BASE"
Input B
0→R
length(Str2)→L
For(I,1,L,1)
sub(Str2,I,1)→Str3
inString(Str1,Str3)-1→S
If S≥B or S=-1:Then
Disp "ERROR:"
Disp Str3
Disp "NOT IN BASE"
Disp B
Stop
End
R+S→R
End
Disp R

Tiny BASIC

Only base ten is supported because the only data type is signed 16-bit int.

    PRINT "Enter a number."
    INPUT N
    IF N < 0 THEN LET N = -N
    LET S = 0
10  IF N = 0 THEN GOTO 20
    LET S = S + N - 10*(N/10)
    LET N = N / 10
    GOTO 10
20  PRINT "Its digit sum is ",S,"."
    END
Output:
Enter a number.
-11212
Its digit sum is 7.

True BASIC

FUNCTION SumDigits(number, nBase)
    IF number < 0 THEN LET number = -number
    IF nBase < 2 THEN  LET nBase = 2
    LET sum = 0

    DO WHILE number > 0
       LET sum = sum + REMAINDER(number, nBase)
       LET number = INT(number / nBase)
    LOOP

    LET SumDigits = sum
END FUNCTION

PRINT "The sums of the digits are:"
PRINT
PRINT "1    base 10 :"; SumDigits(1, 10)
PRINT "1234 base 10 :"; SumDigits(1234, 10)
PRINT "fe   base 16 :"; SumDigits(254, 16)        !0xfe
PRINT "f0e  base 16 :"; SumDigits(3854, 16)       !0xf0e
END

Visual Basic

This version checks that only valid digits for the indicated base are passed in, exiting otherwise.

Function sumDigits(num As Variant, base As Long) As Long
    'can handle up to base 36
    Dim outp As Long
    Dim validNums As String, tmp As Variant, x As Long, lennum As Long
    'ensure num contains only valid characters
    validNums = Left$("0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ", base)
    lennum = Len(num)
    For L0 = lennum To 1 Step -1
        x = InStr(validNums, Mid$(num, L0, 1)) - 1
        If -1 = x Then Exit Function
        tmp = tmp + (x * (base ^ (lennum - L0)))
    Next
    While tmp
        outp = outp + (tmp Mod base)
        tmp = tmp \ base
    Wend
    sumDigits = outp
End Function

Sub tester()
    Debug.Print sumDigits(1, 10)
    Debug.Print sumDigits(1234, 10)
    Debug.Print sumDigits(&HFE, 16)
    Debug.Print sumDigits(&HF0E, 16)
    Debug.Print sumDigits("2", 2)
End Sub
Output:

(in the debug window)

 1
 10
 11
 20
 0

XBasic

Works with: Windows XBasic
PROGRAM  "Sum digits of an integer"
VERSION  "0.0000"

DECLARE FUNCTION  Entry ()
DECLARE FUNCTION SumDigits (number, nBase)

FUNCTION  Entry ()
	PRINT "The sums of the digits are:"
	PRINT
	PRINT "1    base 10 : "; SumDigits(1, 10)
	PRINT "1234 base 10 : "; SumDigits(1234, 10)
	PRINT "fe   base 16 : "; SumDigits(0xfe, 16)
	PRINT "f0e  base 16 : "; SumDigits(0xf0e, 16)
END FUNCTION

FUNCTION SumDigits (number, nBase)
	IF number < 0 THEN number = -number
	IF nBase < 2 THEN nBase = 2
	sum = 0
	DO WHILE number > 0
	    sum = sum + (number MOD nBase)
	    number = number / nBase
	LOOP
	RETURN sum
END FUNCTION
END PROGRAM

Yabasic

sub SumDigits(number, nBase)
    if number < 0 then number = -number : fi
    if nBase < 2 then nBase = 2 : fi
    sum = 0
    while number > 0
        sum = sum + mod(number, nBase)
        number = int(number / nBase)
    wend
    return sum
end sub

print "The sums of the digits are:\n"
print "1    base 10 : ", SumDigits(1, 10)
print "1234 base 10 : ", SumDigits(1234, 10)
print "fe   base 16 : ", SumDigits(0xfe, 16)
print "f0e  base 16 : ", SumDigits(0xf0e, 16) 
end

bc

define s(n) {
    auto i, o, s
    
    o = scale
    scale = 0

    for (i = n; i > 0; i /= ibase) {
        s += i % ibase
    }
    
    scale = o
    return(s)
}

ibase = 10
s(1)
s(1234)
ibase = 16
s(FE)
s(F0E)
Output:
1
10
29
29

BCPL

get "libhdr"

let digitsum(n, base) =
    n=0 -> 0,
    n rem base + digitsum(n/base, base)

let start() be 
$(  writef("%N*N", digitsum(1, 10))      // prints 1
    writef("%N*N", digitsum(1234, 10))   // prints 10
    writef("%N*N", digitsum(#1234, 8))   // also prints 10
    writef("%N*N", digitsum(#XFE, 16))   // prints 29
    writef("%N*N", digitsum(#XF0E, 16))  // also prints 29
$)
Output:
1
10
10
29
29

Befunge

This solution reads the number and base as integers from stdin (in base 10). There doesn't seem any point in accepting input in other bases, because it would then have to be processed as a string and the base would be irrelevant, defeating the point of this exercise.

" :rebmuN">:#,_&0v
|_,#!>#:<"Base: "<
<>10g+\00g/:v:p00&
v^\p01<%g00:_55+\>
>" :muS">:#,_$\.,@
Output:
Number: 1234
Base: 10
Sum: 10

BQN

Recursive function which sums the digits of the left argument.

Default base(right argument) is 10.

SumDigits  {
  𝕊 𝕩: 10 𝕊 𝕩;
  𝕨 𝕊 0: 0;
  (𝕨|𝕩)+𝕨𝕊⌊𝕩÷𝕨
}

•Show SumDigits 1
•Show SumDigits 1234
•Show 16 SumDigits 254
1
10
29

Try It!

C

#include <stdio.h>

int SumDigits(unsigned long long n, const int base) {
    int sum = 0;
    for (; n; n /= base)
    	sum += n % base;
    return sum;
}
 
int main() {
    printf("%d %d %d %d %d\n",
        SumDigits(1, 10),
        SumDigits(12345, 10),
        SumDigits(123045, 10),
        SumDigits(0xfe, 16),
        SumDigits(0xf0e, 16) );
    return 0;
}
Output:
1 15 15 29 29

C#

namespace RosettaCode.SumDigitsOfAnInteger
{
    using System;
    using System.Collections.Generic;
    using System.Linq;

    internal static class Program
    {
        /// <summary>
        ///     Enumerates the digits of a number in a given base.
        /// </summary>
        /// <param name="number"> The number. </param>
        /// <param name="base"> The base. </param>
        /// <returns> The digits of the number in the given base. </returns>
        /// <remarks>
        ///     The digits are enumerated from least to most significant.
        /// </remarks>
        private static IEnumerable<int> Digits(this int number, int @base = 10)
        {
            while (number != 0)
            {
                int digit;
                number = Math.DivRem(number, @base, out digit);
                yield return digit;
            }
        }

        /// <summary>
        ///     Sums the digits of a number in a given base.
        /// </summary>
        /// <param name="number"> The number. </param>
        /// <param name="base"> The base. </param>
        /// <returns> The sum of the digits of the number in the given base. </returns>
        private static int SumOfDigits(this int number, int @base = 10)
        {
            return number.Digits(@base).Sum();
        }

        /// <summary>
        ///     Demonstrates <see cref="SumOfDigits" />.
        /// </summary>
        private static void Main()
        {
            foreach (var example in
                new[]
                {
                    new {Number = 1, Base = 10},
                    new {Number = 12345, Base = 10},
                    new {Number = 123045, Base = 10},
                    new {Number = 0xfe, Base = 0x10},
                    new {Number = 0xf0e, Base = 0x10}
                })
            {
                Console.WriteLine(example.Number.SumOfDigits(example.Base));
            }
        }
    }
}
Output:
1
15
15
29
29

C++

#include <iostream>
#include <cmath>
int SumDigits(const unsigned long long int digits, const int BASE = 10) {
    int sum = 0;
    unsigned long long int x = digits;
    for (int i = log(digits)/log(BASE); i>0; i--){
        const double z = std::pow(BASE,i);
	  const unsigned long long int t = x/z;
	  sum += t;
	  x -= t*z;
    }
    return x+sum;
}

int main() {
        std::cout << SumDigits(1) << ' '
                  << SumDigits(12345) << ' '
                  << SumDigits(123045) << ' '
                  << SumDigits(0xfe, 16) << ' '
                  << SumDigits(0xf0e, 16) << std::endl;
        return 0;
}
Output:
1 15 15 29 29

Template metaprogramming version

Tested with g++-4.6.3 (Ubuntu).

// Template Metaprogramming version by Martin Ettl
#include <iostream>
#include <cmath>

typedef unsigned long long int T;
template <typename T, T i> void For(T &sum, T &x, const T &BASE)
{
    const double z(std::pow(BASE,i));
    const T t = x/z;
    sum += t;
    x -= t*z; 
    For<T, i-1>(sum,x,BASE);
}
template <> void For<T,0>(T &, T &, const T &){}

template <typename T, T digits, int BASE> T SumDigits()
 {
    T sum(0);
    T x(digits);
    const T end(log(digits)/log(BASE));
    For<T,end>(sum,x,BASE);
    return x+sum;
}

int main() 
{
        std::cout << SumDigits<T, 1     , 10>()  << ' '
                  << SumDigits<T, 12345 , 10>()  << ' '
                  << SumDigits<T, 123045, 10>()  << ' '
                  << SumDigits<T, 0xfe  , 16>()  << ' '
                  << SumDigits<T, 0xf0e , 16>()  << std::endl;
        return 0;
}
Output:
1 15 15 29 29

Chez Scheme

(define dsum (lambda (x base) 
                 (let ((number (if (string? x) (string->number x base) x))) 
                 (if (= (string-length (number->string number)) 1) number 
                     (+ (mod number base) (dsum (div number base) base))))))
> (dsum  123 10)
6
> (dsum  "fe" 16)
29
> (dsum  "f0e" 16)
29
> (dsum  1234 10)
10

Clojure

(defn sum-digits [n base] 
  (let [number (if-not (string? n) (Long/toString n base) n)]
    (reduce + (map #(Long/valueOf (str %) base) number))))
Output:
user=> (sum-digits 1 10)
1
user=> (sum-digits 1234 10)
10
user=> (sum-digits "fe" 16)
29
user=> (sum-digits "f0e" 16)
29
user=> (sum-digits 254 16)
29
user=> (sum-digits 3854 16)
29
user=> (sum-digits 16rfe 16)
29
user=> (sum-digits 16rf0e 16)
29
user=> (sum-digits "clojure" 32)
147

CLU

% Find the digits of a number in a given base
digits = iter (n, base: int) yields (int)
    while n>0 do
        yield(n // base)
        n := n / base
    end
end digits

% Sum the digits of a number in a given base
digitsum = proc (n, base: int) returns (int)
    sum: int := 0
    for digit: int in digits(n, base) do
        sum := sum + digit
    end
    return(sum)
end digitsum

start_up = proc ()
    po: stream := stream$primary_output()
    
    stream$putl(po, int$unparse(digitsum(1, 10)))    
    stream$putl(po, int$unparse(digitsum(1234, 10))) 
    stream$putl(po, int$unparse(digitsum(254, 16)))   % 0xFE = 254
    stream$putl(po, int$unparse(digitsum(3854, 16)))  % 0xF0E = 3854
end start_up
Output:
1
10
29
29

Common Lisp

(defun sum-digits (number base)
  (loop for n = number then q
        for (q r) = (multiple-value-list (truncate n base))
        sum r until (zerop q)))

Example:

(loop for (number base) in '((1 10) (1234 10) (#xfe 16) (#xf0e 16))
      do (format t "(~a)_~a = ~a~%" number base (sum-digits number base)))
Output:
(1)_10 = 1
(1234)_10 = 10
(254)_16 = 29
(3854)_16 = 29

Cowgol

include "cowgol.coh";

sub digitSum(n: uint32, base: uint32): (r: uint32) is
    r := 0;
    while n > 0 loop
        r := r + n % base;
        n := n / base;
    end loop;
end sub;

print_i32(digitSum(1, 10)); # prints 1
print_nl();
print_i32(digitSum(1234, 10)); # prints 10
print_nl();
print_i32(digitSum(0xFE, 16)); # prints 29
print_nl();
print_i32(digitSum(0xF0E, 16)); # prints 29
print_nl();
Output:
1
10
29
29

Crystal

class String
  def sum_digits(base : Int) : Int32
  	self.chars.reduce(0) { |acc, c|
  		value = c.to_i(base)
  		acc += value
  	}
  end
end

puts("1".sum_digits 10)
puts("1234".sum_digits 10)
puts("fe".sum_digits 16)
puts("f0e".sum_digits 16)
Output:
1
10
29
29

D

import std.stdio, std.bigint;

uint sumDigits(T)(T n, in uint base=10) pure nothrow
in {
    assert(base > 1);
} body {
    typeof(return) total = 0;
    for ( ; n; n /= base)
        total += n % base;
    return total;
}

void main() {
    1.sumDigits.writeln;
    1_234.sumDigits.writeln;
    sumDigits(0xfe, 16).writeln;
    sumDigits(0xf0e, 16).writeln;
    1_234.BigInt.sumDigits.writeln;
}
Output:
1
10
29
29
10

Dart

Translation of: FreeBASIC
import 'dart:math';

num sumDigits(var number, var nBase) {
  if (number < 0) number = -number; // convert negative numbers to positive
  if (nBase < 2) nBase = 2;         // nBase can't be less than 2
  num sum = 0;
  while (number > 0) {
    sum += number % nBase;
    number ~/= nBase;
  }
  return sum;
}

void main() {
  print('The sums of the digits are:\n');
  print('1    base 10 : ${sumDigits(1, 10)}');
  print('1234 base 10 : ${sumDigits(1234, 10)}');
  print('fe   base 16 : ${sumDigits(0xfe, 16)}');
  print('f0e  base 16 : ${sumDigits(0xf0e, 16)}');
}
Output:
Same as FreeBASIC entry.

Dc

[ I ~ S! d 0!=S L! + ] sS

1 lS x p
1234 lS x p
16 i
FE lS x p
F0E lS x p
Output:
1
10
29
29

Dyalect

Translation of: C#
func digits(num, bas = 10) {
    while num != 0 {
        let (n, digit) = (num / bas, num % bas)
        num = n
        yield digit
    }
}

func Iterator.Sum(acc = 0) {
    for x in this {
        acc += x
    }
    return acc
}

func sumOfDigits(num, bas = 10) => digits(num, bas).Sum()

for e in [ 
    (num: 1, bas: 10),
    (num: 12345, bas: 10),
    (num: 123045, bas:10),
    (num: 0xfe, bas: 16),
    (num: 0xf0e, bas: 16)
    ] {
    print(sumOfDigits(e.num, e.bas))
}
Output:
1
15
15
29
29

Delphi

See Pascal.

Draco

proc nonrec digitsum(word n; byte base) byte:
    byte sum;
    sum := 0;
    while n>0 do
        sum := sum + n % base;
        n := n / base
    od;
    sum
corp

proc nonrec main() void:
    writeln(digitsum(1, 10));
    writeln(digitsum(1234, 10));
    writeln(digitsum(0xFE, 16));
    writeln(digitsum(0xF0E, 16))
corp
Output:
1
10
29
29

EasyLang

func sumdig s$ .
   for c$ in strchars s$
      h = strcode c$ - 48
      if h >= 10
         h -= 39
      .
      r += h
   .
   return r
.
print sumdig "1"
print sumdig "1234"
print sumdig "fe"
print sumdig "f0e"

EDSAC order code

Numbers on the simulated input tape have to be in decimal (not a serious restriction, as pointed out in the Befunge solution). The EDSAC subroutine library didn't include a routine for integer division, so we have to write our own. In the test values, decimal 2003579 represents base-36 16xyz from Kotlin.

[Sum of digits of a number in a given base - Rosetta Code
 EDSAC program (Initial Orders 2)]

      [Arrange the storage]
          T45K P56F       [H parameter: library subroutine R4 to read integer]
          T46K P80F       [N parameter: subroutine to print 35-bit positive integer]
          T47K P180F      [M parameter: main routine]
          T48K P120F      [& (Delta) parameter: subroutine for integer division]
          T51K P157F      [G parameter: subroutine to find sum of digits]

[Library subroutine M3, runs at load time and is then overwritten.
 Prints header; here, last character sets teleprinter to figures.]
          PF GK IF AF RD LF UF OF E@ A6F G@ E8F EZ PF
      *!!!!NUMBER!!!!!!!BASE!!!SUM!OF!DIGITS@&#..PZ

[============== G parameter: Subroutine find sum of digits ==============
 Input:  4D = non-negative number (not preserved)
         6D = base (not preserved)
 Output: 0D = sum of digits
 Workspace: 8D (in called subroutine), 10D, 12D]
          E25K TG GK
          A3F T22@        [plant return link as usual]
          A6D T10D        [store base in 10D]
          T12D            [sum of digits in 12D, initialize to 0]
          A4D             [acc := number]
          E17@            [jump into middle of loop]
       [Start of loop. Next dividend is already in 4D.]
    [7]   TF              [clear acc]
          A10D T6D        [pass base as divisor]
   [10]   A10@ G&         [call division subroutine]
          A4D A12D T12D   [remainder is next digit; add to result]
          A6D U4D         [quotient becomes next dividend]
   [17]   S10D            [is dividend >= base?]
          E7@             [if so, loop back to do division]
       [Here if dividend < base. Means that dividend = top digit.]
          A10D            [restore digit after test]
          A12D            [add to sum of digits]
          TD              [return sum of digits in 0D]
   [22]   ZF              [(planted) jump back to caller]

[====================== M parameter: Main routine ======================]
          E25K TM GK  
[Load at even addess; put 35-bit values first]
    [0]   PF PF           [number]
    [2]   PF PF           [base]
    [4]   PF              [negative data count]
    [5]   !F              [space]
    [6]   @F              [carriage return]
    [7]   &F              [line feed]
    [8]   K4096F          [null character]
[Enter with acc = 0]
    [9]   A9@ GH          [call subroutine R4, sets 0D := count of (n,k) pairs]
          SF              [acc := count negated; it's assumed that count < 2^16]
          E48@            [exit if count = 0]
          LD              [shift count into address field]
   [14]   T4@             [update negative loop counter]
   [15]   A15@ GH         [call library subroutine R4, 0D := number]
          AD T#@          [store number]
   [19]   A19@ GH         [call library subroutine R4, 0D := base]
          AD T2#@         [store base]
          A#@ TD          [pass number to print subroutine]
   [25]   A25@ GN O5@     [print number, plus space]
          A2#@ TD         [pass base to print subroutine]
   [30]   A30@ GN O5@ O5@ O5@ [print base, plus spaces]
          A#@ T4D         [pass number to sum-of-digits subroutine]
          A2#@ T6D        [same for base]
   [39]   A39@ GG         [call subroutine, 0D := sum of digits]
   [41]   A41@ GN O6@ O7@ [print sum of digits, plus CR,LF]
          A4@ A2F         [increment negative counter]
          G14@            [loop back if still negative]
   [48]   O8@             [done; print null to flush printer buffer]
          ZF              [halt the machine]

[The next 3 lines put the entry address into location 50,
 so that it can be accessed via the X parameter (see end of program).]
          T50K
          P9@
          T9Z

[================== H parameter: Library subroutine R4 ==================
 Input of one signed integer, returned in 0D.
 22 locations.]
          E25K TH GK
   GKA3FT21@T4DH6@E11@P5DJFT6FVDL4FA4DTDI4FA4FS5@G7@S5@G20@SDTDT6FEF

[============================= N parameter ==============================
 Library subroutine P7, prints long strictly positive integer in 0D.
 10 characters, right justified, padded left with spaces.
 Even address; 35 storage locations; working position 4D.]
          E25K TN
    GKA3FT26@H28#@NDYFLDT4DS27@TFH8@S8@T1FV4DAFG31@SFLDUFOFFFSFL4F
    T4DA1FA27@G11@XFT28#ZPFT27ZP1024FP610D@524D!FO30@SFL8FE22@

[========================== & (Delta) parameter ==========================]
[The following subroutine is not in the EDSAC library.
 Division subroutine for positive 35-bit integers,
   returning quotient and remainder.
 Input:  dividend at 4D, divisor at 6D
 Output: remainder at 4D, quotient at 6D.
 37 locations; working locations 0D, 8D.]
          E25K T&
    GKA3FT35@A6DU8DTDA4DRDSDG13@T36@ADLDE4@T36@T6DA4DSDG23@
    T4DA6DYFYFT6DT36@A8DSDE35@T36@ADRDTDA6DLDT6DE15@EFPF

[==========================================================================]
[On the original EDSAC, the following (without the whitespace and comments)]
[might have been input on a separate tape.]
          E25K TX GK
          EZ              [define entry point]
          PF              [acc = 0 on entry]
[Count of (n,k) pairs, then the pairs, to be read by library subroutine R4.]
[Note that sign comes *after* value.]
10+1+10+1234+10+254+16+3854+16+2186+3+2187+3+123045+50+2003579+36+
123456789+1000+1234567890+100000+
Output:
    NUMBER       BASE   SUM OF DIGITS
         1         10            1
      1234         10           10
       254         16           29
      3854         16           29
      2186          3           14
      2187          3            1
    123045         50          104
   2003579         36          109
 123456789       1000         1368
1234567890     100000        80235

Elixir

defmodule RC do
  def sumDigits(n, base\\10)
  def sumDigits(n, base) when is_integer(n) do
    Integer.digits(n, base) |> Enum.sum
  end
  def sumDigits(n, base) when is_binary(n) do
    String.codepoints(n) |> Enum.map(&String.to_integer(&1, base)) |> Enum.sum
  end
end

Enum.each([{1, 10}, {1234, 10}, {0xfe, 16}, {0xf0e, 16}], fn {n,base} ->
  IO.puts "#{Integer.to_string(n,base)}(#{base}) sums to #{ RC.sumDigits(n,base) }"
end)
IO.puts ""
Enum.each([{"1", 10}, {"1234", 10}, {"fe", 16}, {"f0e", 16}], fn {n,base} ->
  IO.puts "#{n}(#{base}) sums to #{ RC.sumDigits(n,base) }"
end)
Output:
1(10) sums to 1
1234(10) sums to 10
FE(16) sums to 29
F0E(16) sums to 29

1(10) sums to 1
1234(10) sums to 10
fe(16) sums to 29
f0e(16) sums to 29

Emacs Lisp

(defun digit-sum (n)
  (apply #'+ (mapcar (lambda (c) (- c ?0)) (string-to-list "123"))))

(digit-sum 1234) ;=> 10

Erlang

-module(sum_digits).
-export([sum_digits/2, sum_digits/1]).

sum_digits(N) ->
    sum_digits(N,10).

sum_digits(N,B) ->
    sum_digits(N,B,0).

sum_digits(0,_,Acc) ->
    Acc;
sum_digits(N,B,Acc) when N < B ->
    Acc+N;
sum_digits(N,B,Acc) ->
    sum_digits(N div B, B, Acc + (N rem B)).

Example usage:

2> sum_digits:sum_digits(1).
1
3> sum_digits:sum_digits(1234).
10
4> sum_digits:sum_digits(16#fe,16).
29
5> sum_digits:sum_digits(16#f0e,16).
29

Excel

LAMBDA

We can define digit sums for integer strings in bases up to base 36 by binding the names digitSum, digitValue to the following lambda expressions in the Name Manager of the Excel WorkBook:

(See LAMBDA: The ultimate Excel worksheet function)

digitSum
=LAMBDA(s,
    FOLDROW(
        LAMBDA(a,
            LAMBDA(c,
                a + digitValue(c)
            )
        )
    )(0)(
        CHARSROW(s)
    )
)


digitValue
=LAMBDA(c,
    LET(
        ic, UNICODE(MID(c, 1, 1)),

        IF(AND(47 < ic, 58 > ic),
            ic - 48,
            IF(AND(64 < ic, 91 > ic),
                10 + (ic - 65),
                IF(AND(96 < ic, 123 > ic),
                    10 + (ic - 97),
                    0
                )
            )
        )
    )
)

and also assuming the following generic bindings in the Name Manager for the WorkBook:

CHARSROW
=LAMBDA(s,
    MID(s,
        SEQUENCE(1, LEN(s), 1, 1),
        1
    )
)


FOLDROW
=LAMBDA(op,
    LAMBDA(a,
        LAMBDA(xs,
            LET(
                b, op(a)(HEADROW(xs)),

                IF(1 < COLUMNS(xs),
                    FOLDROW(op)(b)(
                        TAILROW(xs)
                    ),
                    b
                )
            )
        )
    )
)


HEADROW
=LAMBDA(xs,
    LET(REM, "The first item of each row in xs",

        INDEX(
            xs,
            SEQUENCE(ROWS(xs)),
            SEQUENCE(1, 1)
        )
    )
)


TAILROW
=LAMBDA(xs,
    LET(REM,"The tail of each row in the grid",
        n, COLUMNS(xs) - 1,

        IF(0 < n,
            INDEX(
                xs,
                SEQUENCE(ROWS(xs), 1, 1, 1),
                SEQUENCE(1, n, 2, 1)
            ),
            NA()
        )
    )
)
Output:
fx =digitSum(A2)
A B
1 Digit strings Sum of digit values
2 00 0
3 1 1
4 1234 10
5 fe6 35
6 f0e 29
7 ff 30
8 gg 32
9 ze7ro 107
10 zero 100

Ezhil

# இது ஒரு எழில் தமிழ் நிரலாக்க மொழி உதாரணம்

# sum of digits of a number
# எண்ணிக்கையிலான இலக்கங்களின் தொகை

நிரல்பாகம் எண்_கூட்டல்( எண் )
  தொகை = 0
  @( எண் > 0 ) வரை
     d = எண்%10;
     பதிப்பி "digit = ",d
     எண் = (எண்-d)/10;
     தொகை  = தொகை  + d
  முடி
  பின்கொடு தொகை 
முடி


பதிப்பி எண்_கூட்டல்( 1289)#20
பதிப்பி எண்_கூட்டல்( 123456789)# 45

F#

open System

let digsum b n =
    let rec loop acc = function
        | n when n > 0 ->
            let m, r = Math.DivRem(n, b)
            loop (acc + r) m
        | _ -> acc
    loop 0 n

[<EntryPoint>]
let main argv =
    let rec show = function 
        | n :: b :: r -> printf " %d" (digsum b n); show r
        | _ -> ()

    show [1; 10; 1234; 10; 0xFE; 16; 0xF0E; 16]     // ->  1 10 29 29
    0

or Generically

In order to complete the Digital root task I require a function which can handle numbers larger than 32 bit integers.

//Sum Digits of An Integer - Nigel Galloway: January 31st., 2015
//This code will work with any integer type
let inline sumDigits N BASE =
  let rec sum(g, n) = if n < BASE then n+g else sum(g+n%BASE, n/BASE)
  sum(LanguagePrimitives.GenericZero<_>,N)
Output:
> sumDigits 254 2;;
val it : int = 7
> sumDigits 254 10;;
val it : int = 11
> sumDigits 254 16;;
val it : int = 29
> sumDigits 254 23;;
val it : int = 12

so let's try it with a big integer

> sumDigits 123456789123456789123456789123456789123456789I 10I;;
val it : System.Numerics.BigInteger = 225 {IsEven = false;
                                           IsOne = false;
                                           IsPowerOfTwo = false;
                                           IsZero = false;
                                           Sign = 1;}

Factor

: sum-digits ( base n -- sum ) 0 swap [ dup zero? ] [ pick /mod swapd + swap ] until drop nip ;

{ 10 10 16 16 } { 1 1234 0xfe 0xf0e } [ sum-digits ] 2each
Output:
--- Data stack:
1
10
29
29

Forth

This is an easy task for Forth, that has built in support for radices up to 36. You set the radix by storing the value in variable BASE.

: sum_int 0 begin over while swap base @ /mod swap rot + repeat nip ;

 2 base ! 11110 sum_int decimal  . cr
10 base ! 12345 sum_int decimal  . cr
16 base ! f0e   sum_int decimal  . cr

Fortran

Please find GNU/linux compilation instructions along with the sample output within the comments at the start of this FORTRAN 2008 source. Thank you. Review of this page shows a solution to this task with the number input as text. The solution is the sum of index positions in an ordered list of digit characters. (awk). Other solutions ignore the representations of the input, encode digits using the base, then sum the encoding. Both methods appear in this implementation.

!-*- mode: compilation; default-directory: "/tmp/" -*-
!Compilation started at Fri Jun  7 21:00:12
!
!a=./f && make $a && $a
!gfortran -std=f2008 -Wall -fopenmp -ffree-form -fall-intrinsics -fimplicit-none f.f08 -o f
!f.f08:57.29:
!
!  subroutine process1(fmt,s,b)
!                             1
!Warning: Unused dummy argument 'b' at (1)
!digit sum       n
!        1 1
!       10 1234
!       29 fe
!       29 f0e
! sum of digits of n expressed in base is...
!      n   base    sum
!      1     10      1
!   1234     10     10
!    254     16     29
!   3854     16     29
!
!Compilation finished at Fri Jun  7 21:00:12

module base_mod
  private :: reverse
contains
  subroutine reverse(a)
    integer, dimension(:), intent(inout) :: a
    integer :: i, j, t
    do i=1,size(a)/2
       j = size(a) - i + 1
       t = a(i)
       a(i) = a(j)
       a(j) = t
    end do
  end subroutine reverse  

  function antibase(b, n) result(a)
    integer, intent(in) :: b,n
    integer, dimension(32) :: a
    integer :: m, i
    a = 0
    m = n
    i = 1
    do while (m .ne. 0)
       a(i) = mod(m, b)
       m = m/b
       i = i+1
    end do
    call reverse(a)
  end function antibase
end module base_mod

program digit_sum
  use base_mod
  call still
  call confused
contains
  subroutine still
    character(len=6),parameter :: fmt = '(i9,a)'
    print'(a9,a8)','digit sum','n'
    call process1(fmt,'1',10)
    call process1(fmt,'1234',10)
    call process1(fmt,'fe',16)
    call process1(fmt,'f0e',16)
  end subroutine still

  subroutine process1(fmt,s,b)
    character(len=*), intent(in) :: fmt, s
    integer, intent(in), optional :: b
    integer :: i
    print fmt,sum((/(index('123456789abcdef',s(i:i)),i=1,len(s))/)),' '//s
  end subroutine process1

  subroutine confused
    character(len=5),parameter :: fmt = '(3i7)'
    print*,'sum of digits of n expressed in base is...'
    print'(3a7)','n','base','sum'
    call process0(10,1,fmt)
    call process0(10,1234,fmt)
    call process0(16,254,fmt)
    call process0(16,3854,fmt)
  end subroutine confused

  subroutine process0(b,n,fmt)
    integer, intent(in) :: b, n
    character(len=*), intent(in) :: fmt
    print fmt,n,b,sum(antibase(b, n))
  end subroutine process0
end program digit_sum

Frink

In Frink numbers can be specifed to an arbitrary base from 2 to 36 as number\\base. The function integerDigits[n, base] lists the digits of n in the base base.

sumDigits[n, base=10] := sum[integerDigits[n, base]]

The sample problems can be written as:

sumDigits[1]
sumDigits[1234]
sumDigits[fe\\16]
sumDigits[f03\\16]

Fōrmulæ

Fōrmulæ programs are not textual, visualization/edition of programs is done showing/manipulating structures but not text. Moreover, there can be multiple visual representations of the same program. Even though it is possible to have textual representation —i.e. XML, JSON— they are intended for storage and transfer purposes more than visualization and edition.

Programs in Fōrmulæ are created/edited online in its website.

In this page you can see and run the program(s) related to this task and their results. You can also change either the programs or the parameters they are called with, for experimentation, but remember that these programs were created with the main purpose of showing a clear solution of the task, and they generally lack any kind of validation.

Solution

Test cases

Go

Handling numbers up to 2^64-1 and bases from 2 to 36 is pretty easy, larger values can be handled using the math/big package (but it's still limited to base<=36).

// File digit.go

package digit

import (
	"math/big"
	"strconv"
)

func SumString(n string, base int) (int, error) {
	i, ok := new(big.Int).SetString(n, base)
	if !ok {
		return 0, strconv.ErrSyntax
	}
	if i.Sign() < 0 {
		return 0, strconv.ErrRange
	}
	if i.BitLen() <= 64 {
		return Sum(i.Uint64(), base), nil
	}
	return SumBig(i, base), nil
}

func Sum(i uint64, base int) (sum int) {
	b64 := uint64(base)
	for ; i > 0; i /= b64 {
		sum += int(i % b64)
	}
	return
}

func SumBig(n *big.Int, base int) (sum int) {
	i := new(big.Int).Set(n)
	b := new(big.Int).SetUint64(uint64(base))
	r := new(big.Int)
	for i.BitLen() > 0 {
		i.DivMod(i, b, r)
		sum += int(r.Uint64())
	}
	return
}
// File digit_test.go

package digit

import "testing"

type testCase struct {
	n    string
	base int
	dSum int
}

var testData = []testCase{
	{"1", 10, 1},
	{"1234", 10, 10},
	{"fe", 16, 29},
	{"f0e", 16, 29},
	{"18446744073709551615", 10, 87},
	{"abcdefghijklmnopqrstuvwzuz0123456789", 36, 628},
}

func TestSumString(t *testing.T) {
	for _, tc := range testData {
		ds, err := SumString(tc.n, tc.base)
		if err != nil {
			t.Error("test case", tc, err)
			continue
		}
		if ds != tc.dSum {
			t.Error("test case", tc, "got", ds, "expected", tc.dSum)
		}
	}
}

func TestErrors(t *testing.T) {
	for _, tc := range []struct {
		n    string
		base int
	}{
		{"1234", 37},
		{"0", 1},
		{"1234", 4},
		{"-123", 10},
	} {
		_, err := SumString(tc.n, tc.base)
		if err == nil {
			t.Error("expected error for", tc)
		}
		t.Log("got expected error:", err)
	}
}


Golfscript

{base {+}*}:sd;

Test (apply sd for each array [number radix]) :

Output:
[[1 10] [1234 10] [254 16] [3854 16]] {~sd p}%
1
10
29
29

Groovy

Solution:

def digitsum = { number, radix = 10 ->
    Integer.toString(number, radix).collect { Integer.parseInt(it, radix) }.sum()
}

Test:

[[30, 2], [30, 10], [1, 10], [12345, 10], [123405, 10], [0xfe, 16], [0xf0e, 16]].each {
    println """
    Decimal value:     ${it[0]}
    Radix:             ${it[1]}
    Radix value:       ${Integer.toString(it[0], it[1])}
    Decimal Digit Sum: ${digitsum(it[0], it[1])}
    Radix Digit Sum:   ${Integer.toString(digitsum(it[0], it[1]), it[1])}
    """
}
Output:
    Decimal value:     30
    Radix:             2
    Radix value:       11110
    Decimal Digit Sum: 4
    Radix Digit Sum:   100
    

    Decimal value:     30
    Radix:             10
    Radix value:       30
    Decimal Digit Sum: 3
    Radix Digit Sum:   3
    

    Decimal value:     1
    Radix:             10
    Radix value:       1
    Decimal Digit Sum: 1
    Radix Digit Sum:   1
    

    Decimal value:     12345
    Radix:             10
    Radix value:       12345
    Decimal Digit Sum: 15
    Radix Digit Sum:   15
    

    Decimal value:     123405
    Radix:             10
    Radix value:       123405
    Decimal Digit Sum: 15
    Radix Digit Sum:   15
    

    Decimal value:     254
    Radix:             16
    Radix value:       fe
    Decimal Digit Sum: 29
    Radix Digit Sum:   1d
    

    Decimal value:     3854
    Radix:             16
    Radix value:       f0e
    Decimal Digit Sum: 29
    Radix Digit Sum:   1d

Haskell

digsum
  :: Integral a
  => a -> a -> a
digsum base = f 0
  where
    f a 0 = a
    f a n = f (a + r) q
      where
        (q, r) = n `quotRem` base

main :: IO ()
main = print $ digsum 16 255 -- "FF": 15 + 15 = 30
Output:
30

In terms of unfoldr:

import Data.List (unfoldr)
import Data.Tuple (swap)

----------------- SUM DIGITS OF AN INTEGER ---------------

baseDigitSum :: Int -> Int -> Int
baseDigitSum base = sum . unfoldr go
  where
    go x
      | 0 < x = (Just . swap) $ quotRem x base
      | otherwise = Nothing

-------------------------- TESTS -------------------------
main :: IO ()
main =
  mapM_
    print
    [ baseDigitSum <$> [2, 8, 10, 16] <*> [255],
      baseDigitSum <$> [10] <*> [1, 1234],
      baseDigitSum <$> [16] <*> [0xfe, 0xf0e]
    ]
Output:
[8,17,12,30]
[1,10]
[29,29]


Or, we could write sum . fmap digitToInt, or the equivalent but more efficient fusion of it to a single fold: foldr ((+) . digitToInt) 0

import Data.Char (digitToInt, intToDigit, isHexDigit)
import Data.List (transpose)
import Numeric (readInt, showIntAtBase)

------------------ SUM OF INTEGER DIGITS -----------------

digitSum :: String -> Int
digitSum = foldr ((+) . digitToInt) 0

intDigitSum :: Int -> Int -> Int
intDigitSum base =
  digitSum
    . flip (showIntAtBase base intToDigit) []


-------------------------- TESTS -------------------------
main :: IO ()
main =
  mapM_ putStrLn $
    unwords
      <$> transpose
        ( ( fmap
              =<< flip justifyRight ' '
                . succ
                . maximum
                . fmap length
          )
            <$> transpose
              ( [ "Base",
                  "Digits",
                  "Value",
                  "digit string -> sum",
                  "integer value -> sum"
                ] :
                ( ( \(s, b) ->
                      let v = readBase b s
                       in [ show b, -- base
                            show s, -- digits
                            show v, -- value
                            -- sum from digit string
                            show (digitSum s),
                            -- sum from base and value
                            show (intDigitSum b v)
                          ]
                  )
                    <$> [ ("1", 10),
                          ("1234", 10),
                          ("fe", 16),
                          ("f0e", 16)
                        ]
                )
              )
        )
  where
    justifyRight n c = (drop . length) <*> (replicate n c <>)
    readBase b s = n
      where
        [(n, _)] = readInt b isHexDigit digitToInt s
Output:
 Base  Digits  Value  digit string -> sum  integer value -> sum
   10     "1"      1                    1                     1
   10  "1234"   1234                   10                    10
   16    "fe"    254                   29                    29
   16   "f0e"   3854                   29                    29

Icon and Unicon

This solution works in both languages. This solution assumes the input number is expressed in the indicated base. This assumption differs from that made in some of the other solutions.

procedure main(a)
    write(dsum(a[1]|1234,a[2]|10))
end

procedure dsum(n,b)
    n := integer((\b|10)||"r"||n)
    sum := 0
    while sum +:= (0 < n) % b do n /:= b
    return sum
end

Sample runs:

->sdi 1
1
->sdi 1234
10
->sdi fe 16
29
->sdi f0e 16
29
->sdi ff 16
30
->sdi 255 16
12
->sdi fffff 16
75
->sdi 254 16
11
->

J

digsum=: 10&$: : (+/@(#.inv))

Example use:

   digsum 1234
10
   10 digsum 254
11
   16 digsum 254
29

Illustration of mechanics:

   10 #. 1 2 3 4
1234
  10 #.inv 1234
1 2 3 4
  10 +/ 1 2 3 4
10
  10 +/@(#.inv) 1234
10

So #.inv gives us the digits, +/ gives us the sum, and @ glues them together with +/ being a "post processor" for #.inv or, as we say in the expression: (#.inv). We need the parenthesis or inv will try to look up the inverse of +/@#. and that's not well defined.

The rest of it is about using 10 as the default left argument when no left argument is defined. A J verb has a monadic definition (for use with one argument) and a dyadic definition (for use with two arguments) and : derives a new verb where the monadic definition is used from the verb on the left and the dyadic definition is used from the verb on the right. $: is a self reference to the top-level defined verb.

Full examples:

   digsum 1
1
   digsum 1234
10
   16 digsum 16bfe
29
   16 digsum 16bf0e
29

Note that J implements numeric types -- J tries to ensure that the semantics of numbers match their mathematical properties. So it doesn't matter how we originally obtained a number.

   200+54
254
   254
254
   2.54e2
254
   16bfe
254
   254b10 , 1r254b0.1  NB. 10 in base 254 , 0.1 in base 1/254
254 254

Java

import java.math.BigInteger;
public class SumDigits {
    public static int sumDigits(long num) {
	return sumDigits(num, 10);
    }
    public static int sumDigits(long num, int base) {
	String s = Long.toString(num, base);
	int result = 0;
	for (int i = 0; i < s.length(); i++)
	    result += Character.digit(s.charAt(i), base);
	return result;
    }
    public static int sumDigits(BigInteger num) {
	return sumDigits(num, 10);
    }
    public static int sumDigits(BigInteger num, int base) {
	String s = num.toString(base);
	int result = 0;
	for (int i = 0; i < s.length(); i++)
	    result += Character.digit(s.charAt(i), base);
	return result;
    }

    public static void main(String[] args) {
	System.out.println(sumDigits(1));
	System.out.println(sumDigits(12345));
	System.out.println(sumDigits(123045));
	System.out.println(sumDigits(0xfe, 16));
	System.out.println(sumDigits(0xf0e, 16));
	System.out.println(sumDigits(new BigInteger("12345678901234567890")));
    }
}
Output:
1
15
15
29
29
90

JavaScript

Imperative

function sumDigits(n) {
	n += ''
	for (var s=0, i=0, e=n.length; i<e; i+=1) s+=parseInt(n.charAt(i),36)
	return s
}
for (var n of [1, 12345, 0xfe, 'fe', 'f0e', '999ABCXYZ']) document.write(n, ' sum to ', sumDigits(n), '<br>')
Output:
1 sum to 1
12345 sum to 15
254 sum to 11
fe sum to 29
f0e sum to 29
999ABCXYZ sum to 162

Functional

ES5

(function () {
    'use strict';

    // digitsSummed :: (Int | String) -> Int
    function digitsSummed(number) {
    
        // 10 digits + 26 alphabetics
        // give us glyphs for up to base 36
        var intMaxBase = 36;
    
        return number
            .toString()
            .split('')
            .reduce(function (a, digit) { 
                return a + parseInt(digit, intMaxBase);
            }, 0);
    }

    // TEST

    return [1, 12345, 0xfe, 'fe', 'f0e', '999ABCXYZ']
        .map(function (x) {
            return x + ' -> ' + digitsSummed(x);
        })
        .join('\n');

})();
1 -> 1
12345 -> 15
254 -> 11
fe -> 29
f0e -> 29
999ABCXYZ -> 162

ES6

(() => {
    "use strict";

    // -------------- INTEGER DIGITS SUMMED --------------

    // digitsSummed :: (Int | String) -> Int
    const digitsSummed = number => {

        // 10 digits + 26 alphabetics
        // give us glyphs for up to base 36
        const intMaxBase = 36;

        return `${number}`
            .split("")
            .reduce(
                (sofar, digit) => sofar + parseInt(
                    digit, intMaxBase
                ),
                0
            );
    };

    // ---------------------- TEST -----------------------
    return [1, 12345, 0xfe, "fe", "f0e", "999ABCXYZ"]
        .map((x) => `${x} -> ${digitsSummed(x)}`)
        .join("\n");
})();
Output:
1 -> 1
12345 -> 15
254 -> 11
fe -> 29
f0e -> 29
999ABCXYZ -> 162

Joy

DEFINE digitsum ==
  [swap string] [dup [strtol] dip] [] ifte
  [<] [pop] [dup rollup div rotate] [+] linrec.

1 10 digitsum.
1234 10 digitsum.
"fe" 16 digitsum.
"f0e" 16 digitsum.
Output:
1
10
29
29

jq

The following pipeline will have the desired effect if numbers and/or strings are presented as input:

tostring | explode | map(tonumber - 48) | add

For example:

$ jq -M 'tostring | explode | map(tonumber - 48) | add'
123
6
"123"
6

Julia

Using the built-in digits function:

sumdigits(n, base=10) = sum(digits(n, base))

Kotlin

// version 1.1.0

const val digits = "0123456789abcdefghijklmnopqrstuvwxyz"

fun sumDigits(ns: String, base: Int): Int {
    val n = ns.toLowerCase().trim()
    if (base !in 2..36) throw IllegalArgumentException("Base must be between 2 and 36")
    if (n.isEmpty())    throw IllegalArgumentException("Number string can't be blank or empty")
    var sum = 0
    for (digit in n) {
        val index = digits.indexOf(digit)
        if (index == -1 || index >= base) throw IllegalArgumentException("Number string contains an invalid digit")
        sum += index
    }
    return sum
}

fun main(args: Array<String>) {
    val numbers = mapOf("1" to 10, "1234" to 10, "fe" to 16, "f0e" to 16, "1010" to 2, "777" to 8, "16xyz" to 36)
    println("The sum of digits is:")
    for ((number, base) in numbers) println("$number\tbase $base\t-> ${sumDigits(number, base)}")
}
Output:
The sum of digits is:
1       base 10 -> 1
1234    base 10 -> 10
fe      base 16 -> 29
f0e     base 16 -> 29
1010    base 2  -> 2
777     base 8  -> 21
16xyz   base 36 -> 109

Lambdatalk

Following Javascript, with 10 digits + 26 alphabetics giving us glyphs for up to base 36

{def sum_digits
 {lambda {:n}
  {if {W.empty? {W.rest :n}}
   then {parseInt {W.first :n} 36}
   else {+ {parseInt {W.first :n} 36} {sum_digits {W.rest :n}}}}}}
-> sum_digits

 
{S.map {lambda {:i} {div}:i sum to {sum_digits :i}}
       1 12345 0xfe fe f0e 999ABCXYZ}
-> 
1 sum to 1 
12345 sum to 15 
0xfe sum to 62 
fe sum to 29 
f0e sum to 29 
999ABCXYZ sum to 162

Lasso

define br => '<br />\n'

define sumdigits(int, base = 10) => {
	fail_if(#base < 2, -1, 'Base need to be at least 2')
	local(
		out		= integer,
		divmod
	)
	while(#int) => {
		 #divmod = #int -> div(#base)
		 #int = #divmod -> first
		 #out += #divmod -> second
	}
	return #out
}

sumdigits(1)
br
sumdigits(12345)
br
sumdigits(123045)
br
sumdigits(0xfe, 16)
br
sumdigits(0xf0e, 16)
Output:
1
15
15
29
29

Lingo

on sum_digits (n, base)
  sum = 0
  repeat while n
    m = n / base
    sum = sum + n - m * base
    n = m
  end repeat
  return sum
end
put sum_digits(1, 10)
-- 1
put sum_digits(1234, 10)
-- 10
put sum_digits(254, 16) -- 0xfe
-- 29
put sum_digits(3854, 16) -- 0xf0e
-- 29

LiveCode

function sumDigits n, base
    local numb
    if base is empty then put 10 into base
    repeat for each char d in n
        add baseConvert(d,base,10) to numb
    end repeat
    return numb
end sumDigits

Example

put sumdigits(1,10) & comma & \
    sumdigits(1234,10) & comma & \
    sumdigits(fe,16) & comma & \
    sumdigits(f0e,16)

Output

1,10,29,29

make "digits "0123456789abcdefghijklmnopqrstuvwxyz

to digitvalue :digit
   output difference find [equal? :digit item ? :digits] iseq 1 count :digits 1
end

to sumdigits :number [:base 10]
  output reduce "sum map.se "digitvalue :number
end

foreach [1 1234 fe f0e] [print (se ? "-> sumdigits ?)]
Output:
1 -> 1
1234 -> 10
fe -> 29
f0e -> 29

Lua

function sum_digits(n, base)
    sum = 0
    while n > 0.5 do
        m = math.floor(n / base)
        digit = n - m * base
        sum = sum + digit
        n = m
    end
    return sum
end

print(sum_digits(1, 10))
print(sum_digits(1234, 10))
print(sum_digits(0xfe, 16))
print(sum_digits(0xf0e, 16))
Output:
1
10
29
29

M2000 Interpreter

module SumDigitisOfAnInteger {
	z="0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ"
	sumdigits=lambda z (m as string) ->{
		integer ret, i
		m=ucase$(m)
		if len(m)=0 then =ret:exit
		for i=1 to len(m):ret+=instr(z, mid$(m,i,1))-1:next
		=ret
	}
	CheckBase=lambda z (m as string, base as integer)->{
		if len(m)=0 then Error "not valid input"
		if base<2 or base>len(z) then Error "not valid input"
		integer ret=1
		m=ucase$(m)
		for i=1 to len(m)
			ret*=instr(z, mid$(m,i,1))<=base
			if ret=0 then exit for
		next
		=ret<>0
	}
	string n
	integer b
	stack new {
		data "1", 10
		data "1234", 10
		data ""+0xfe, 10
		data "fe", 16
		data "f0e", 16
		while not empty
			read n, b
			Print n+" (base:"+b+") sums to "+sumdigits(n)
		end while
	}
	Input "number, base :", n, b
	if CheckBase(n, b) then
		Print "sums to "+sumdigits(n)
	else
		Print n;" isn't a number of base "+b
	end if
}
SumDigitisOfAnInteger
Output:
1 (base:10) sums to 1
1234 (base:10) sums to 10
254 (base:10) sums to 11
fe (base:16) sums to 29
f0e (base:16) sums to 29
number, base :12345671234567, 8
sums to 56


Maple

sumDigits := proc( num )
	local digits, number_to_string, i;
	number_to_string := convert( num, string );
	digits := [ seq( convert( h, decimal, hex ), h in seq( parse( i ) , i in number_to_string ) ) ];
	return add( digits ); 
end proc:
sumDigits( 1234 );
sumDigits( "fe" );
Output:
10
29

Mathematica/Wolfram Language

Total[IntegerDigits[1234]]
Total[IntegerDigits[16^^FE, 16]]
Output:
10
29

Miranda

main :: [sys_message]
main = [Stdout (lay (map fmt tests))]
       where tests     = [(1,10), (1234,10), (0xfe,16), (0xf0e,16)]
             fmt (d,b) = (shownum d) ++ "_" ++ (shownum b) ++ " -> " ++
                         (shownum (digitsum b d))

digitsum :: num->num->num
digitsum base 0 = 0
digitsum base n = n mod base + digitsum base (n div base)
Output:
1_10 -> 1
1234_10 -> 10
254_16 -> 29
3854_16 -> 29

МК-61/52

П0	<->	П1	Сx	П2	ИП1	^	ИП0	/	[x]
П3	ИП0	*	-	ИП2	+	П2	ИП3	П1	x=0
05	ИП2	С/П

ML

Function with first argument valid base, second argument number

local
 open IntInf
in
 fun summDigits  base = ( fn 0 => 0 | n => n mod base + summDigits base (n div base ) )
end;

summDigits 10 1 ;
summDigits 10 1234 ;
summDigits 16 0xfe ;
summDigits 16 0xf0e ;
summDigits 4332489243570890023480923 0x8092eeac80923984098234098efad2109ce341000c3f0912527130  ;

output

val it = 1: IntInf.int
val it = 10: IntInf.int
val it = 29: IntInf.int
val it = 29: IntInf.int
val it = 4745468831557628080368936: IntInf.int

mLite

Left in the to_radix even though not used in the solution.

exception :radix_out_of_range and :unknown_digit;

fun to_radix (0, radix, result) = implode result
           | (n, radix > 36, result) = raise :radix_out_of_range
           | (n rem radix > 10, radix, result) =
               to_radix (n div radix, radix,
                         chr (n rem radix + ord #"a" - 10) :: result)
           | (n, radix, result) =
               to_radix (n div radix, radix,
                         chr (n rem radix + ord #"0") :: result)
           | (n, radix) = to_radix (n, radix, [])
;
fun from_radix (s, radix) =
      let val digits = explode "0123456789abcdefghijklmnopqrstuvwxyz";
          val len_digits = len digits;
          fun index (_, n >= radix, c) = raise :unknown_digit
                  | (h :: t, n, c = h) = n
                  | (_ :: t, n, c) = index (t, n + 1, c)
                  | c = index (digits, 0, c)
          and conv ([], radix, power, n) = n
                 | (h :: t, radix, power, n) =
                     conv (t, radix, power * radix, index h * power + n)
                 | (s, radix) = conv (rev ` explode s, radix, 1, 0)
          in
            conv (s, radix)
          end

;
fun sumdig
		([], base, n) = n
	|	(h :: t, base, n) = sumdig (t, base, from_radix (implode [h], base) + n)
	|	(s, base) = sumdig (explode s, base, 0)

;
fun shosum (s, b) = (print "sum of digits of "; print s; print " (base "; print b; print ") = "; println ` sumdig (s, b))
;

shosum ("10fg",17);
shosum ("deadbeef",16);
shosum ("1101010101010101010101010101010101010101010101010101010101010101010101010101010101010101",2);
shosum ("thequickbrownfoxjumpsoverthelazydog",36);

Output

sum of digits of 10fg (base 17) = 32
sum of digits of deadbeef (base 16) = 104
sum of digits of 1101010101010101010101010101010101010101010101010101010101010101010101010101010101010101 (base 2) = 45
sum of digits of thequickbrownfoxjumpsoverthelazydog (base 36) = 788

Modula-2

Translation of: Pascal
Works with: ADW Modula-2 version any (Compile with the linker option Console Application).
MODULE SumOFDigits;
FROM STextIO IMPORT
  WriteString, WriteLn;
FROM SWholeIO IMPORT
  WriteInt;
FROM Conversions IMPORT
  StrBaseToLong;

PROCEDURE SumOfDigitBase(N: LONGCARD; Base: CARDINAL): CARDINAL;
VAR
  Tmp, LBase: LONGCARD;
  Digit, Sum : CARDINAL;
BEGIN
  Digit := 0;
  Sum   := 0;
  LBase := Base;
  WHILE N > 0 DO
    Tmp := N / LBase;
    Digit := N - LBase * Tmp;
    N := Tmp;
    INC(Sum, Digit);
  END;
  RETURN Sum;
END SumOfDigitBase;

VAR
  Num: LONGCARD;

BEGIN
  WriteString('   1 sums to '); 
  WriteInt(SumOfDigitBase(1, 10), 1); 
  WriteLn;
  WriteString('1234 sums to '); 
  WriteInt(SumOfDigitBase(1234, 10), 1); 
  WriteLn;
  IF StrBaseToLong('FE', 16, Num) THEN
    WriteString(' $FE sums to '); 
    WriteInt(SumOfDigitBase(Num, 16), 1); 
    WriteLn;
  END;
  IF StrBaseToLong('F0E', 16, Num) THEN
    WriteString('$F0E sums to '); 
    WriteInt(SumOfDigitBase(Num, 16), 1); 
    WriteLn;
  END;
  WriteString('MAX(LONGCARD) (in dec) sums to '); 
  WriteInt(SumOfDigitBase(MAX(LONGCARD), 10), 1); 
  WriteLn;
END SumOFDigits.
Output:
   1 sums to 1
1234 sums to 10
 $FE sums to 29
$F0E sums to 29
MAX(LONGCARD) (in dec) sums to 87

NetRexx

Strings

Processes data as text from the command line. Provides a representative sample if no input is supplied:

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

parse arg input
inputs = ['1234', '01234', '0xfe', '0xf0e', '0', '00', '0,2' '1', '070', '77, 8' '0xf0e, 10', '070, 16', '0xf0e, 36', '000999ABCXYZ, 36', 'ff, 16', 'f, 10', 'z, 37'] -- test data
if input.length() > 0 then inputs = [input] -- replace test data with user input
loop i_ = 0 to inputs.length - 1
  in = inputs[i_]
  parse in val . ',' base .
  dSum = sumDigits(val, base)
  say 'Sum of digits for integer "'val'" for a given base of "'base'":' dSum'\-'
  -- Carry the exercise to it's logical conclusion and sum the results to give a single digit in range 0-9
  loop while dSum.length() > 1 & dSum.datatype('n')
    dSum = sumDigits(dSum, 10)
    say ',' dSum'\-'
    end
  say
  end i_

-- Sum digits of an integer
method sumDigits(val = Rexx, base = Rexx '') public static returns Rexx

  rVal = 0
  parse normalizeValue(val, base) val base .
  loop label digs for val.length()
    -- loop to extract digits from input and sum them
    parse val dv +1 val
    do
      rVal = rVal + Integer.valueOf(dv.toString(), base).intValue()
    catch ex = NumberFormatException
      rVal = 'NumberFormatException:' ex.getMessage()
      leave digs
    end
    end digs
  return rVal

-- Clean up the input, normalize the data and determine which base to use
method normalizeValue(inV = Rexx, base = Rexx '') private static returns Rexx
  inV = inV.strip('l')
  base = base.strip()
  parse inV xpref +2 . -
         =0 opref +1 . -
         =0 . '0x' xval . ',' . -
         =0 . '0'  oval . ',' . -
         =0 dval .

  select
    when xpref = '0x' & base.length() = 0 then do
      -- value starts with '0x' and no base supplied.  Assign hex as base
      inval = xval
      base = 16
      end
    when opref = '0'  & base.length() = 0 then do
      -- value starts with '0' and no base supplied.  Assign octal as base
      inval = oval
      base = 8
      end
    otherwise do
      inval = dval
      end
    end
  if base.length() = 0 then base = 10 -- base not set.  Assign decimal as base
  if inval.length() <= 0 then inval = 0 -- boundary condition.  Invalid input or a single zero
  rVal = inval base

  return rVal
Output:
Sum of digits for integer "1234" for a given base of "": 10, 1
Sum of digits for integer "01234" for a given base of "": 10, 1
Sum of digits for integer "0xfe" for a given base of "": 29, 11, 2
Sum of digits for integer "0xf0e" for a given base of "": 29, 11, 2
Sum of digits for integer "0" for a given base of "": 0
Sum of digits for integer "00" for a given base of "": 0
Sum of digits for integer "0" for a given base of "2": 0
Sum of digits for integer "070" for a given base of "": 7
Sum of digits for integer "77" for a given base of "8": 14, 5
Sum of digits for integer "070" for a given base of "16": 7
Sum of digits for integer "0xf0e" for a given base of "36": 62, 8
Sum of digits for integer "000999ABCXYZ" for a given base of "36": 162, 9
Sum of digits for integer "ff" for a given base of "16": 30, 3
Sum of digits for integer "f" for a given base of "10": NumberFormatException: For input string: "f"
Sum of digits for integer "z" for a given base of "37": NumberFormatException: radix 37 greater than Character.MAX_RADIX

Type int

Processes sample data as int arrays:

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

inputs = [[int 1234, 10], [octal('01234'), 8], [0xfe, 16], [0xf0e,16], [8b0, 2], [16b10101100, 2], [octal('077'), 8]] -- test data
loop i_ = 0 to inputs.length - 1
  in = inputs[i_, 0]
  ib = inputs[i_, 1]
  dSum = sumDigits(in, ib)
  say 'Sum of digits for integer "'Integer.toString(in, ib)'" for a given base of "'ib'":' dSum'\-'
  -- Carry the exercise to it's logical conclusion and sum the results to give a single digit in range 0-9
  loop while dSum.length() > 1 & dSum.datatype('n')
    dSum = sumDigits(dSum, 10)
    say ',' dSum'\-'
    end
  say
  end i_

-- Sum digits of an integer
method sumDigits(val = int, base = int 10) public static returns Rexx
  rVal = Rexx 0
  sVal = Rexx(Integer.toString(val, base))
  loop label digs for sVal.length()
    -- loop to extract digits from input and sum them
    parse sVal dv +1 sVal
    do
      rVal = rVal + Integer.valueOf(dv.toString(), base).intValue()
    catch ex = NumberFormatException
      rVal = 'NumberFormatException:' ex.getMessage()
      leave digs
    end
    end digs
  return rVal

-- if there's a way to insert octal constants into an int in NetRexx I don't remember it
method octal(oVal = String) private constant returns int signals NumberFormatException
  iVal = Integer.valueOf(oVal, 8).intValue()
  return iVal
Output:
Sum of digits for integer "1234" for a given base of "10": 10, 1
Sum of digits for integer "1234" for a given base of "8": 10, 1
Sum of digits for integer "fe" for a given base of "16": 29, 11, 2
Sum of digits for integer "f0e" for a given base of "16": 29, 11, 2
Sum of digits for integer "0" for a given base of "2": 0
Sum of digits for integer "10101100" for a given base of "2": 4
Sum of digits for integer "77" for a given base of "8": 14, 5

Never

func sum_digits(n : int, base : int) -> int {
    var sum = 0;
    
    do
    {
        sum = sum + n % base;
        n = n / base
    }
    while (n != 0);
    
    sum
}

func main() -> int {
    print(sum_digits(1, 10));
    print(sum_digits(12345, 10));
    print(sum_digits(123045, 10));
    print(sum_digits(0xfe, 16));
    print(sum_digits(0Xf0e, 16));
    
    0
}
Output:
1
15
15
29
29

Nim

proc sumdigits(n, base: Natural): Natural =
  var n = n
  while n > 0:
    result += n mod base
    n = n div base

echo sumDigits(1, 10)
echo sumDigits(12345, 10)
echo sumDigits(123045, 10)
echo sumDigits(0xfe, 16)
echo sumDigits(0xf0e, 16)
Output:
1
15
15
29
29

Oberon-2

MODULE SumDigits;
IMPORT Out;
PROCEDURE Sum(n: LONGINT;base: INTEGER): LONGINT;
VAR
	sum: LONGINT;
BEGIN
	sum := 0;
	WHILE (n > 0) DO
		INC(sum,(n MOD base));
		n := n DIV base
	END;
	RETURN sum
END Sum;
BEGIN
	Out.String("1     : ");Out.LongInt(Sum(1,10),10);Out.Ln;
	Out.String("1234  : ");Out.LongInt(Sum(1234,10),10);Out.Ln;
	Out.String("0FEH  : ");Out.LongInt(Sum(0FEH,16),10);Out.Ln;
	Out.String("OF0EH : ");Out.LongInt(Sum(0F0EH,16),10);Out.Ln
END SumDigits.
Output:
1     :          1
1234  :         10
0FEH  :         29
OF0EH :         29

Objeck

class SumDigits {
  function : Main(args : String[]) ~ Nil {
    SumDigit(1)->PrintLine();
    SumDigit(12345)->PrintLine();
    SumDigit(0xfe, 16)->PrintLine();
    SumDigit(0xf0e, 16)->PrintLine();
  }

  function : SumDigit(value : Int, base : Int := 10) ~ Int {
    sum := 0;
    do {
      sum += value % base;
      value /= base;
    }
    while(value <> 0);
    return sum;
  }
}
Output:
1
15
29
29

OCaml

let sum_digits ~digits ~base =
  let rec aux sum x =
    if x <= 0 then sum else
    aux (sum + x mod base) (x / base)
  in
  aux 0 digits
 
let () =
  Printf.printf "%d %d %d %d %d\n"
    (sum_digits 1 10)
    (sum_digits 12345 10)
    (sum_digits 123045 10)
    (sum_digits 0xfe 16)
    (sum_digits 0xf0e 16)
Output:
1 15 15 29 29

Oforth

: sumDigits(n, base)  0 while( n ) [ n base /mod ->n + ] ;

Usage :

sumDigits(1, 10) println
sumDigits(1234, 10) println
sumDigits(0xfe, 16) println
sumDigits(0xf0e, 16) println
Output:
1
10
29
29

Ol

(define (sum n base)
   (if (zero? n)
      n
      (+ (mod n base) (sum (div n base) base))))

(print (sum 1 10))
; ==> 1

(print (sum 1234 10))
; ==> 10

(print (sum #xfe 16))
; ==> 29

(print (sum #xf0e 16))
; ==> 29

PARI/GP

dsum(n,base)=my(s); while(n, s += n%base; n \= base); s

Also the built-in sumdigits can be used for base 10.

Pascal

Program SumOFDigits;

function SumOfDigitBase(n:UInt64;base:LongWord): LongWord;
var
  tmp: Uint64;
  digit,sum : LongWord;
Begin
  digit := 0;
  sum   := 0;
  While n > 0 do
  Begin
    tmp := n div base;
    digit := n-base*tmp;
    n := tmp;
    inc(sum,digit);
  end;
  SumOfDigitBase := sum;  
end;
Begin
  writeln('   1 sums to ', SumOfDigitBase(1,10)); 
  writeln('1234 sums to ', SumOfDigitBase(1234,10));  
  writeln(' $FE sums to ', SumOfDigitBase($FE,16)); 
  writeln('$FOE sums to ', SumOfDigitBase($F0E,16));   
  
  writeln('18446744073709551615 sums to ', SumOfDigitBase(High(Uint64),10));  

end.
output
   1 sums to 1
1234 sums to 10
 $FE sums to 29
$FOE sums to 29
18446744073709551615 sums to 87

Perl

#!/usr/bin/perl
use strict;
use warnings;

my %letval = map { $_ => $_ } 0 .. 9;
$letval{$_} = ord($_) - ord('a') + 10 for 'a' .. 'z';
$letval{$_} = ord($_) - ord('A') + 10 for 'A' .. 'Z';

sub sumdigits {
  my $number = shift;
  my $sum = 0;
  $sum += $letval{$_} for (split //, $number);
  $sum;
}

print "$_ sums to " . sumdigits($_) . "\n"
  for (qw/1 1234 1020304 fe f0e DEADBEEF/);
Output:
1 sums to 1
1234 sums to 10
1020304 sums to 10
fe sums to 29
f0e sums to 29
DEADBEEF sums to 104

The ntheory module also does this, for a solution similar to Raku, with identical output.

Library: ntheory
use ntheory "sumdigits";
say sumdigits($_,36) for (qw/1 1234 1020304 fe f0e DEADBEEF/);

Phix

Library: Phix/basics
function sum_digits(integer n, integer base)
integer res = 0
    while n do
        res += remainder(n,base)
        n = floor(n/base)
    end while
    return res
end function
 
?sum_digits(1,10)
?sum_digits(1234,10)
?sum_digits(#FE,16)
?sum_digits(#F0E,16)
Output:
1
10
29
29

PHP

<?php
function sumDigits($num, $base = 10) {
    $s = base_convert($num, 10, $base);
    foreach (str_split($s) as $c)
        $result += intval($c, $base);
    return $result;
}
echo sumDigits(1), "\n";
echo sumDigits(12345), "\n";
echo sumDigits(123045), "\n";
echo sumDigits(0xfe, 16), "\n";
echo sumDigits(0xf0e, 16), "\n";
?>
Output:
1
15
15
29
29

Picat

go =>

  println(1=sum_digits(1)),
  println(1234=sum_digits(1234)),

  println('"1234"'=sum_digits("1234")),
  println(1234=sum_digits(1234)),

  println('"fe(16)"'=sum_digits("fe", 16)), % -> 29
  println('"f0e(16)"'=sum_digits("f0e", 16)), % -> 29
  println('"FOE(16)"'=sum_digits("F0E", 16)), % -> 29
  println('123(16)'=sum_digits(123, 16)), % -> 6
  println('"123"(16)'=sum_digits("123", 16)), % -> 6

  println('"1110010101"(2)'=sum_digits("1110010101", 2)),
  
  println('"picat"(36)'=sum_digits("picat", 36)),

  Alpha = "0123456789abcdefghijklmnopqrstuvwxyz",
  Rand = [Alpha[1+random2() mod Alpha.length] : _ in 1..40],
  println(rand=Rand),
  println(rand_sum_digits=sum_digits(Rand, 36)),

  println("\nTesting exceptions"),
  catch(println(sum_digits(Rand, 10)), E, println(exception=E)), % bad_base
  catch(println(sum_digits("picat_is_fun!", 36)), E2, println(exeption=E2)), % bad_digit
  catch(println(sum_digits("11100101", 1)),E3,println(exception=E3)), % bad base
  catch(println(sum_digits("hi", 100)), E4, println(exception=E4)), % bad base

  % Output base
  println("\nOutput base"),
  println('"fe(16,10)"'=sum_digits("fe", 16,10)), % -> 29
  println('"fe(16,16)"'=sum_digits("fe", 16,16)), % -> 1d
  println('"f0e(16,16)"'=sum_digits("f0e", 16,16)), % -> 1d
  println('"1110010101"(2,2)'=sum_digits("1110010101", 2,2)), % -> 110
  println('"rosetta(36,36)"'=sum_digits("rosetta", 36,36)), % 4h
  nl.

% base 10
sum_digits(N) = sum([D.to_integer() : D in N.to_string()]), integer(N) => true.
sum_digits(N) = sum([D.to_integer() : D in N]), string(N) => true.

% base Base
sum_digits(N,Base) = sum_digits(N.to_string(), Base), integer(N) => true.
sum_digits(N,Base) = sum_digits(N,Base,10), string(N) => true.
sum_digits(N,Base,OutputBase) = Sum, string(N) =>
  N := to_lowercase(N),
  Alpha = "0123456789abcdefghijklmnopqrstuvwxyz",
  Map = new_map([A=I : {A,I} in zip(Alpha,0..length(Alpha)-1)]),
  M = [Map.get(I,-1) : I in N],
  if max(M) >= Base ; Base < 2; Base > Alpha.length then
    throw $bad_base('N'=N,base=Base)
  elseif min(M) == -1 then
    throw $bad_digits('N'=N,bad=[D : D in N, not Map.has_key(D) ])
  else
    if OutputBase != 10 then
      Sum = dec_to_base(sum(M),OutputBase)
    else 
      Sum = sum(M)
    end
  end.

dec_to_base(N, Base) = [Alpha[D+1] : D in reverse(Res)] =>
  Alpha = "0123456789abcdefghijklmnopqrstuvwxyz",
  Res = [],
  while (N > 0) 
    R := N mod Base,
    N := N div Base,
    Res := Res ++ [R]
  end.

base_to_dec(N, Base) = base_to_dec(N.to_string(), Base), integer(N) => true.
base_to_dec(N, Base) = Res =>
  println($base_to_dec(N, Base)),
  Alpha = "0123456789abcdefghijklmnopqrstuvwxyz",
  Map = new_map([A=I : {A,I} in zip(Alpha,0..length(Alpha)-1)]),
  Len = N.length,
  Res = sum([Map.get(D)*Base**(Len-I) : {D,I} in zip(N,1..N.length)]).
Output:
1 = 1
1234 = 10
"1234" = 10
1234 = 10
"fe(16)" = 29
"f0e(16)" = 29
"FOE(16)" = 29
123(16) = 6
"123"(16) = 6
"1110010101"(2) = 6
"picat"(36) = 94
rand = ic5hprdfzrcs2h9hqko8dedirtk3fd6fs1sd7sxd
rand_sum_digits = 694

Testing exceptions
exception = bad_base(N = ic5hprdfzrcs2h9hqko8dedirtk3fd6fs1sd7sxd,base = 10)
exeption = bad_digits(N = picat_is_fun!,bad = __!)
exception = bad_base(N = 11100101,base = 1)
exception = bad_base(N = hi,base = 100)

Output base
"fe(16,10)" = 29
"fe(16,16)" = 1d
"f0e(16,16)" = 1d
"1110010101"(2,2) = 110
"rosetta(36,36)" = 4h


PicoLisp

(de sumDigits (N Base)
   (or
      (=0 N)
      (+ (% N Base) (sumDigits (/ N Base) Base)) ) )

Test:

: (sumDigits 1 10)
-> 1

: (sumDigits 1234 10)
-> 10

: (sumDigits (hex "fe") 16)
-> 29

: (sumDigits (hex "f0e") 16)
-> 29

PL/I

sum_digits: procedure options (main);   /* 4/9/2012 */
   declare ch character (1);
   declare (k, sd) fixed;

   on endfile (sysin) begin; put skip data (sd); stop; end;
   sd = 0;
   do forever;
      get edit (ch) (a(1)); put edit (ch) (a);
      k = index('abcdef', ch);
      if k > 0 then /* we have a base above 10 */
         sd = sd + 9 + k;
      else
         sd = sd + ch;
   end;
end sum_digits;

results:

5c7e
SD=      38;
10111000001
SD=       5;

PL/M

100H:
BDOS: PROCEDURE (F,A); DECLARE F BYTE, A ADDRESS; GO TO 5; END BDOS;
EXIT: PROCEDURE; GO TO 0; END EXIT;
PRINT: PROCEDURE (S); DECLARE S ADDRESS; CALL BDOS(9,S); END PRINT;

PRINT$NUM: PROCEDURE (N);
    DECLARE S (8) BYTE INITIAL ('.....',13,10,'$');
    DECLARE (N, P) ADDRESS, C BASED P BYTE;
    P = .S(5);
DIGIT:
    P = P-1;
    C = N MOD 10 + '0';
    IF (N := N/10) > 0 THEN GO TO DIGIT;
    CALL PRINT(P);
END PRINT$NUM;

DIGIT$SUM: PROCEDURE (N, BASE) BYTE;
    DECLARE N ADDRESS, (BASE, SUM) BYTE;
    SUM = 0;
    DO WHILE N > 0;
        SUM = SUM + N MOD BASE;
        N = N / BASE;
    END;
    RETURN SUM;
END DIGIT$SUM;

CALL PRINT$NUM(DIGIT$SUM(    1, 10));
CALL PRINT$NUM(DIGIT$SUM( 1234, 10));
CALL PRINT$NUM(DIGIT$SUM( 0FEH, 16));
CALL PRINT$NUM(DIGIT$SUM(0F0EH, 16));
CALL EXIT;
EOF
Output:
1
10
29
29

PowerShell

function Get-DigitalSum ([string] $number, $base = 10)
{
    if ($number.ToCharArray().Length -le 1) { [Convert]::ToInt32($number, $base) }
    else 
    {
        $result = 0
        foreach ($character in $number.ToCharArray())
        {
            $digit = [Convert]::ToInt32(([string]$character), $base)
            $result += $digit
        }
        return $result
    }
}
Output:
PS C:\> Get-DigitalSum 1
1

PS C:\> Get-DigitalSum 1234
10

PS C:\> Get-DigitalSum fe 16
29

PS C:\> Get-DigitalSum f0e 16
29

Alternative Implementation

function Get-DigitalSum ([string] $number, $base = 10)
{
    Invoke-Expression (($number.ToCharArray() | ForEach-Object {[string][convert]::ToInt16($_, $base)}) -join "+")
}
Output:
PS C:\> Get-DigitalSum 1
1

PS C:\> Get-DigitalSum 1234
10

PS C:\> Get-DigitalSum fe 16
29

PS C:\> Get-DigitalSum f0e 16
29

Prolog

Works with: SWI Prolog
digit_sum(N, Base, Sum):-
    digit_sum(N, Base, Sum, 0).

digit_sum(N, Base, Sum, S1):-
    N < Base,
    !,
    Sum is S1 + N.
digit_sum(N, Base, Sum, S1):-
    divmod(N, Base, M, Digit),
    S2 is S1 + Digit,
    digit_sum(M, Base, Sum, S2).

test_digit_sum(N, Base):-
    digit_sum(N, Base, Sum),
    writef('Sum of digits of %w in base %w is %w.\n', [N, Base, Sum]).

main:-
    test_digit_sum(1, 10),
    test_digit_sum(1234, 10),
    test_digit_sum(0xfe, 16),
    test_digit_sum(0xf0e, 16).
Output:
Sum of digits of 1 in base 10 is 1.
Sum of digits of 1234 in base 10 is 10.
Sum of digits of 254 in base 16 is 29.
Sum of digits of 3854 in base 16 is 29.

Python

from numpy import base_repr

def sumDigits(num, base=10):
    return sum(int(x, base) for x in list(base_repr(num, base)))

or

def sumDigits(num, base=10):
    if base < 2:
        print("Error: base must be at least 2")
        return
    num, sum = abs(num), 0
    while num >= base:
        num, rem = divmod(num, base)
        sum += rem
    return sum + num

print(sumDigits(1))
print(sumDigits(12345))
print(sumDigits(-123045))
print(sumDigits(0xfe, 16))
print(sumDigits(0xf0e, 16))
Output:
1
15
15
29
29

The following does no error checking and requires non-base 10 numbers passed as string arguments:

def sumDigits(num, base=10):
    return sum(int(x, base) for x in str(num))

print(sumDigits(1))
print(sumDigits(12345))
print(sumDigits(123045))
print(sumDigits('fe', 16))
print(sumDigits("f0e", 16))

Each digit is base converted as it's summed.


Or, as a composition of re-usable abstractions:

'''Sum digits of an integer'''

from functools import reduce


# digitSum :: Int -> Int -> Int
def digitSum(base):
    '''The sum of the digits of a
       natural number in a given base.
    '''
    return lambda n: reduce(
        lambda a, x: a + digitToInt(x),
        showIntAtBase(base)(digitChar)(n)(''),
        0
    )


# --------------------------TEST---------------------------
# main :: IO ()
def main():
    '''Digit sums of numbers in bases 10 and 16:'''

    print(
        fTable(main.__doc__)(
            lambda nb: showIntAtBase(nb[0])(
                digitChar
            )(nb[1])(' in base ') + str(nb[0])
        )(repr)(
            uncurry(digitSum)
        )([(10, 1), (10, 10), (16, 0xfe), (16, 0xf0e)])
    )


# -------------------------DISPLAY-------------------------

# fTable :: String -> (a -> String) ->
# (b -> String) -> (a -> b) -> [a] -> String
def fTable(s):
    '''Heading -> x display function -> fx display function ->
       f -> xs -> tabular string.
    '''
    def go(xShow, fxShow, f, xs):
        ys = [xShow(x) for x in xs]
        w = max(map(len, ys))
        return s + '\n' + '\n'.join(map(
            lambda x, y: y.rjust(w, ' ') + ' -> ' + fxShow(f(x)),
            xs, ys
        ))
    return lambda xShow: lambda fxShow: lambda f: lambda xs: go(
        xShow, fxShow, f, xs
    )


# -------------------------GENERIC-------------------------

# digitChar :: Int to Char
def digitChar(n):
    '''A digit char for integers drawn from [0..15]'''
    return ' ' if 0 > n or 15 < n else '0123456789abcdef'[n]


# digitToInt :: Char -> Int
def digitToInt(c):
    '''The integer value of any digit character
       drawn from the 0-9, A-F or a-f ranges.
    '''
    oc = ord(c)
    if 48 > oc or 102 < oc:
        return None
    else:
        dec = oc - 48   # ord('0')
        hexu = oc - 65  # ord('A')
        hexl = oc - 97  # ord('a')
    return dec if 9 >= dec else (
        10 + hexu if 0 <= hexu <= 5 else (
            10 + hexl if 0 <= hexl <= 5 else None
        )
    )


# showIntAtBase :: Int -> (Int -> String) -> Int -> String -> String
def showIntAtBase(base):
    '''String representation of an integer in a given base,
       using a supplied function for the string representation
       of digits.
    '''
    def wrap(toChr, n, rs):
        def go(nd, r):
            n, d = nd
            r_ = toChr(d) + r
            return go(divmod(n, base), r_) if 0 != n else r_
        return 'unsupported base' if 1 >= base else (
            'negative number' if 0 > n else (
                go(divmod(n, base), rs))
        )
    return lambda toChr: lambda n: lambda rs: (
        wrap(toChr, n, rs)
    )


# uncurry :: (a -> b -> c) -> ((a, b) -> c)
def uncurry(f):
    '''A function over a tuple,
       derived from a curried function.
    '''
    return lambda tpl: f(tpl[0])(tpl[1])


# MAIN ---
if __name__ == '__main__':
    main()
Output:
Digit sums of numbers in bases 10 and 16:
  1 in base 10 -> 1
 10 in base 10 -> 1
 fe in base 16 -> 29
f0e in base 16 -> 29

Quackery

Translation of: Forth
  [ temp put 0
    [ over while 
      swap temp share /mod 
      rot + again ]
    nip temp release ]     is digitsum ( n n --> n )               
   
        1 10 digitsum echo sp
     1234 10 digitsum echo sp
   hex FE 16 digitsum echo sp
  hex F0E 16 digitsum echo
Output:
1 10 29 29

R

Translation of: Python
change.base <- function(n, base)
{
  ret <- integer(as.integer(logb(x=n, base=base))+1L)
  
  for (i in 1:length(ret))
  {
    ret[i] <- n %% base
    n <- n %/% base
    
  }
  
  return(ret)
}

sum.digits <- function(n, base=10)
{
  if (base < 2)
    stop("base must be at least 2")
  
  return(sum(change.base(n=n, base=base)))
}

sum.digits(1)
sum.digits(12345)
sum.digits(123045)
sum.digits(0xfe, 16)
sum.digits(0xf0e, 16)

Racket

#lang racket
(define (sum-of-digits n base (sum 0))
  (if (= n 0)
      sum
      (sum-of-digits (quotient n base)
                     base
                     (+ (remainder n base) sum))))

(for-each
 (lambda (number-base-pair)
   (define number (car number-base-pair))
   (define base (cadr number-base-pair))
   (displayln (format "(~a)_~a = ~a" number base (sum-of-digits number base))))
 '((1 10) (1234 10) (#xfe 16) (#xf0e 16)))



;  outputs:
;    (1)_10 = 1
;    (1234)_10 = 10
;    (254)_16 = 29
;    (3854)_16 = 29

Raku

(formerly Perl 6) This will handle input numbers in any base from 2 to 36. The results are in base 10.

say Σ $_ for <1 1234 1020304 fe f0e DEADBEEF>;

sub Σ { [+] $^n.comb.map: { :36($_) } }
Output:
1
10
10
29
29
104

REXX

version 1

/* REXX ************************************************************** 
* 04.12.2012 Walter Pachl                                               
**********************************************************************/ 
digits='0123456789ABCDEF'                                               
Do i=1 To length(digits)                                                
  d=substr(digits,i,1)                                                  
  value.d=i-1                                                           
  End                                                                   
Call test '1'                                                           
Call test '1234'                                                        
Call test 'FE'                                                          
Call test 'F0E'                                                         
Exit                                                                    
test:                                                                   
  Parse Arg number                                                      
  res=right(number,4)                                                   
  dsum=0                                                                
  Do While number<>''                                                   
    Parse Var number d +1 number                                        
    dsum=dsum+value.d                                                   
    End                                                                 
  Say res '->' right(dsum,2)                                            
  Return
Output:
   1 ->  1
1234 -> 10
  FE -> 29
 F0E -> 29

version 2

This REXX version allows:

  •   leading signs   (+ -)
  •   decimal points
  •   leading and/or trailing whitespace
  •   numerals may be in mixed case
  •   numbers may include commas   (,)
  •   numbers may be expressed up to base 36
  •   numbers may be any length (size)
/*REXX program  sums  the  decimal digits  of natural numbers in any base up to base 36.*/
parse arg z                                      /*obtain optional argument from the CL.*/
if z='' | z=","  then z= '1 1234 fe f0e +F0E -666.00 11111112222222333333344444449'
        do j=1  for words(z);     _=word(z, j)   /*obtain a number from the list.       */
        say right(sumDigs(_), 9)    ' is the sum of the digits for the number '    _
        end   /*j*/
exit                                             /*stick a fork in it,  we're all done. */
/*──────────────────────────────────────────────────────────────────────────────────────*/
sumDigs: procedure;  arg x;  @=123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ;  $=0
                        do k=1  to length(x);   $=$ + pos( substr(x, k, 1), @);  end /*k*/
         return $

output   when using the default input:

        1  is the sum of the digits for the number  1
       10  is the sum of the digits for the number  1234
       29  is the sum of the digits for the number  fe
       29  is the sum of the digits for the number  f0e
       29  is the sum of the digits for the number  +F0E
       18  is the sum of the digits for the number  -666.00
       79  is the sum of the digits for the number  11111112222222333333344444449

version 3

This REXX version is an optimized version limited to base ten integers only   (for fast decomposing of a decimal number's numerals).

The function makes use of REXX's   parse   statement

/*REXX program  sums  the  decimal digits  of  integers  expressed in base ten.         */
parse arg z                                      /*obtain optional argument from the CL.*/
if z='' | z=","  then z=copies(7, 108)           /*let's generate a pretty huge integer.*/
numeric digits 1 + max( length(z) )              /*enable use of gigantic numbers.      */

     do j=1  for words(z);    _=abs(word(z, j))  /*ignore any leading sign,  if present.*/
     say sumDigs(_)      ' is the sum of the digits for the number '    _
     end   /*j*/
exit                                             /*stick a fork in it,  we're all done. */
/*──────────────────────────────────────────────────────────────────────────────────────*/
sumDigs: procedure;  parse arg N 1 $ 2 ?         /*use first decimal digit for the sum. */
                             do  while ?\=='';  parse var ? _ 2 ?;  $=$+_;  end  /*while*/
         return $

output   when using the default input:

756  is the sum of the digits for the number  777777777777777777777777777777777777777777777777777777777777777777777777777777777777777777777777777777777777

Ring

see "sum digits of 1 = " + sumDigits(1) + nl
see "sum digits of 1234 = " + sumDigits(1234) + nl

func sumDigits n
     sum = 0
     while n > 0.5 
           m = floor(n / 10)
           digit = n - m * 10
           sum = sum + digit
           n = m
     end
     return sum

RPL

RPL can natively handle numbers in bases 2,8,10 or 16, but displays them according to the current base mode. For example, when you type #256d, it will be immediately turned into #100h if HEX mode is active. As there is no way to force the base mode to the base used for input, switching to string handling looks like a reasonable approach for code clarity and size. A side effect is that it can proceed with numbers in any base between 2 and 36.

Works with: Halcyon Calc version 4.2.7
≪ →STR → digits 
   ≪ 0 
     1 digits SIZE FOR j 
       digits j DUP SUB NUM 
       IF DUP 48 ≥ OVER 57 ≤ AND 
       THEN 48 - 
       ELSE IF DUP 65 ≥ OVER 90 ≤ AND 
            THEN 55 - 
            ELSE NOT 
       END END 
     + NEXT
≫ ≫ '∑DIGITS' STO
1 ∑DIGITS
1234 ∑DIGITS
#FEh ∑DIGITS
#F0Eh ∑DIGITS
Output:
 4: 1
 3: 10
 2: 29
 1: 29

Ruby

def sum_digits(num, base = 10) = num.digits(base).sum

Rust

Using an Iterator

This solution creates an iterator which yields the digits of a given number using a given base and then utilizes the `sum` method which is implemented automatically on iterators.

struct DigitIter(usize, usize);

impl Iterator for DigitIter {
    type Item = usize;
    fn next(&mut self) -> Option<Self::Item> {
        if self.0 == 0 {
            None
        } else {
            let ret = self.0 % self.1;
            self.0 /= self.1;
            Some(ret)
        }
    }
}

fn main() {
    println!("{}", DigitIter(1234,10).sum::<usize>());
}

Scala

def sumDigits(x:BigInt, base:Int=10):BigInt=sumDigits(x.toString(base), base)
def sumDigits(x:String, base:Int):BigInt = x map(_.asDigit) sum

Test:

sumDigits(0)                                // => 0
sumDigits(0, 2)                             // => 0
sumDigits(0, 16)                            // => 0
sumDigits("00", 2)                          // => 0
sumDigits("00", 10)                         // => 0
sumDigits("00", 16)                         // => 0
sumDigits(1234)                             // => 10
sumDigits(0xfe)                             // => 11
sumDigits(0xfe, 16)                         // => 29
sumDigits(0xf0e, 16)                        // => 29
sumDigits(077)                              // => 9
sumDigits(077, 8)                           // => 14
sumDigits("077", 8)                         // => 14
sumDigits("077", 10)                        // => 14
sumDigits("077", 16)                        // => 14
sumDigits("0xf0e", 36)                      // => 62
sumDigits("000999ABCXYZ", 36)               // => 162
sumDigits(BigInt("12345678901234567890"))   // => 90
sumDigits("12345678901234567890", 10)       // => 90

Scheme

This requires taking an input number (which may be input in any supported base), and a required target base to represent the number (as numbers entered in a given base do not preserve that base internally, and we may want to use unsupported bases).

The output is the sum of the digits in the target base, displayed in base 10.

(import (scheme base)
        (scheme write))

;; convert number to a list of digits, in desired base
(define (number->list n base) 
  (let loop ((res '())
             (num n))
    (if (< num base) 
      (cons num res)
      (loop (cons (remainder num base) res)
            (quotient num base)))))

;; return the sum of digits of n in given base
(define (sum-digits n base)
  (apply + (number->list n base)))

;; test cases: 
;; -- this displays each number in its original, given-base, for comparison
;; -- target-base is the base in which to consider each number represented, for summing the digits
(define (test-case n given-base target-base)
  (display (string-append (number->string n given-base)
                          " base "
                          (number->string given-base)
                          " has decimal value "
                          (number->string n)
                          " => sum of digits in base "
                          (number->string target-base)
                          " is "
                          (number->string (sum-digits n target-base))))
  (newline))

(test-case 1 10 10)
(test-case 1234 10 10)
(test-case #o1234 8 10)
(test-case #xFE 16 16)
(test-case #xFE 16 10)
(test-case #xF0E 16 16)
(test-case #b1101010101010101010101010101010101 2 2)
(test-case #b1101010101010101010101010101010101 2 10)
(test-case #b1101010101010101010101010101010101 2 1000)
Output:

The final sum is always in base 10:

1 base 10 has decimal value 1 => sum of digits in base 10 is 1
1234 base 10 has decimal value 1234 => sum of digits in base 10 is 10
1234 base 8 has decimal value 668 => sum of digits in base 10 is 20
fe base 16 has decimal value 254 => sum of digits in base 16 is 29
fe base 16 has decimal value 254 => sum of digits in base 10 is 11
f0e base 16 has decimal value 3854 => sum of digits in base 16 is 29
1101010101010101010101010101010101 base 2 has decimal value 14316557653 => sum of digits in base 2 is 18
1101010101010101010101010101010101 base 2 has decimal value 14316557653 => sum of digits in base 10 is 46
1101010101010101010101010101010101 base 2 has decimal value 14316557653 => sum of digits in base 1000 is 1540

Seed7

$ include "seed7_05.s7i";

const func integer: sumDigits (in var integer: num, in integer: base) is func
  result
     var integer: sum is 0;
  begin
    while num > 0 do
      sum +:= num rem base;
      num := num div base;
    end while;
  end func;

const proc: main is func
  begin
    writeln(sumDigits(1,      10));
    writeln(sumDigits(12345,  10));
    writeln(sumDigits(123045, 10));
    writeln(sumDigits(123045, 50));
    writeln(sumDigits(16#fe,  10));
    writeln(sumDigits(16#fe,  16));
    writeln(sumDigits(16#f0e, 16));
  end func;
Output:
1
15
15
104
11
29
29

Sidef

Translation of: Raku
func Σ(String str, base=36) {
    str.chars.map{ Num(_, base) }.sum
}

<1 1234 1020304 fe f0e DEADBEEF>.each { |n|
    say "Σ(#{n}) = #{Σ(n)}"
}
Output:
Σ(1) = 1
Σ(1234) = 10
Σ(1020304) = 10
Σ(fe) = 29
Σ(f0e) = 29
Σ(DEADBEEF) = 104

SQL

Works with: ORACLE 19c

This is not a particularly efficient solution, but it gets the job done.

/*
This code is an implementation of "Sum digits of an integer" in SQL ORACLE 19c 
p_in_str -- input string
*/
with
  function sum_digits(p_in_str in varchar2) return varchar2 is
  v_in_str varchar(32767) := translate(p_in_str,'*-+','*');
  v_sum integer;
begin
  --
  if regexp_count(v_in_str,'[0-9A-F]',1,'i')=length(v_in_str) then -- base 16
    execute immediate 'select sum('||regexp_replace(v_in_str,'(\w)','to_number(''\1'',''X'')+')||'0) from dual' into v_sum;
    --   
  elsif regexp_count(v_in_str,'[0-9]',1,'i')=length(v_in_str) then -- base 10 
    execute immediate 'select sum('||regexp_replace(v_in_str,'(\d)','\1+')||'0) from dual' into v_sum;
    --
  else
    return 'Sum of digits for integer "'||p_in_str||'" not defined';
    --  
  end if;
  -- 
  return 'Sum of digits for integer "'||p_in_str||'" = '||v_sum;
end;

--Test
select sum_digits('') as res from dual
union all 
select sum_digits('000') as res from dual
union all 
select sum_digits('-010') as res from dual
union all
select sum_digits('+010') as res from dual
union all 
select sum_digits('120034') as res from dual
union all 
select sum_digits('FE') as res from dual
union all 
select sum_digits('f0e') as res from dual
union all
select sum_digits('öst12') as res from dual;
Output:
Sum of digits for integer "" not defined
Sum of digits for integer "000" = 0
Sum of digits for integer "-010" = 1
Sum of digits for integer "+010" = 1
Sum of digits for integer "120034" = 10
Sum of digits for integer "FE" = 29
Sum of digits for integer "f0e" = 29
Sum of digits for integer "öst12" not defined

Standard ML

fun sumDigits (0, _) = 0
  | sumDigits (n, base) = n mod base + sumDigits (n div base, base)

val testInput = [(1, 10), (1234, 10), (0xfe, 16), (0xf0e, 16)]
val () = print (String.concatWith " " (map (Int.toString o sumDigits) testInput) ^ "\n")

Stata

function sumdigits(s) {
	a = ascii(strupper(s)):-48
	return(sum(a:-(a:>9)*7))
}

sumdigits("1")
  1

sumdigits("1234")
  10

sumdigits("fe")
  29

sumdigits("f0e")
  29

sumdigits(inbase(16, 254, 10))
  29

Swift

Works with: Swift version 4.0
extension String: Error {
    func sumDigits(withBase base: Int) throws -> Int {
        func characterToInt(_ base: Int) -> (Character) -> Int? {
            return { char in
                return Int(String(char), radix: base)
            }
        }
        
        return try self.map(characterToInt(base))
            .flatMap {
                guard $0 != nil else { throw "Invalid input" }
                return $0
            }
            .reduce(0, +)
    }
}

print(try! "1".sumDigits(withBase: 10))
print(try! "1234".sumDigits(withBase: 10))
print(try! "fe".sumDigits(withBase: 16))
print(try! "f0e".sumDigits(withBase: 16))
Output:
1
10
29
29

Tcl

Supporting arbitrary bases makes this primarily a string operation.

proc sumDigits {num {base 10}} {
    set total 0
    foreach d [split $num ""] {
	if {[string is alpha $d]} {
	    set d [expr {[scan [string tolower $d] %c] - 87}]
	} elseif {![string is digit $d]} {
	    error "bad digit: $d"
	}
	if {$d >= $base} {
	    error "bad digit: $d"
	}
	incr total $d
    }
    return $total
}

Demonstrating:

puts [sumDigits 1]
puts [sumDigits 12345]
puts [sumDigits 123045]
puts [sumDigits fe 16]
puts [sumDigits f0e 16]
puts [sumDigits 000999ABCXYZ 36]
Output:
1
15
15
29
29
162

Transd

#lang transd

MainModule : {
    v10: [1, 1234, 10000000],
    vvar: ["fe:16", "f0e:16", "2022:3", "Transd:30"],

    sumDigits: (λ s String() 
        (with snum (substr s 0 ":") 
              base (first (substr s after: ":") "10") n 0
        (textout "sum of " :left width: 10 (+ snum ":" base " : " ))
        (tsd (split snum "") :reduce
            using: (λ s String() (+= n (to-Int (+ s ":" base))))) (lout n))
    ),

    _start: (lambda 
        (tsd v10 reduce: ["(to-String col1)"] 
                 using: (λ s String() (sumDigits s)))
        (tsd vvar reduce: ["(sumDigits col1)"] )
    )
}
Output:
sum of 1:10 :        1
sum of 1234:10 :     10
sum of 10000000:10 : 1
sum of fe:16 :       29
sum of f0e:16 :      29
sum of 2022:3 :      6
sum of Transd:30 :   130

TypeScript

Translation of: Pascal
// Sum digits of an integer

function sumOfDigitBase(n: number, bas: number): number {
  var digit = 0, sum = 0;
  while (n > 0)
  {
    var tmp = Math.floor(n / bas);
    digit = n - bas * tmp;
    n = tmp;
    sum += digit;
  }
  return sum;
}
 
console.log(`    1 sums to ${sumOfDigitBase(1, 10)}`); 
console.log(` 1234 sums to ${sumOfDigitBase(1234, 10)}`); 
console.log(` 0xfe sums to ${sumOfDigitBase(0xfe, 16)}`); 
console.log(`0xf0e sums to ${sumOfDigitBase(0xf0e, 16)}`); 
maxint = Number.MAX_SAFE_INTEGER;
console.log(`${maxint} (Number.MAX_SAFE_INTEGER) sums to ${sumOfDigitBase(maxint, 10)}`);
Output:
    1 sums to 1
 1234 sums to 10
 0xfe sums to 29
0xf0e sums to 29
9007199254740991 (Number.MAX_SAFE_INTEGER) sums to 76

Ursa

The function:

def sumDigits (string val, int base)
	decl int ret
	for (decl int i) (< i (size val)) (inc i)
		set ret (+ ret (int val<i> base))
	end for
	return ret
end sumDigits

Calling the function: (This could be done on a single line, but it's split up for clarity.)

out (sumDigits "1" 10) endl console
out (sumDigits "1234" 10) endl console
out (sumDigits "fe" 16) endl console
out (sumDigits "f0e" 16) endl console
Output:
1
10
29
29

Uxntal

@sum-digits ( num* base* -: sum* )
    #0000 STH2
    &loop
        OVR2 OVR2 DIV2k MUL2 SUB2
        STH2r ADD2 STH2
        DIV2k ORAk ?{ POP2 POP2 POP2 STH2r JMP2r }
        SWP2 ROT2 POP2 !&loop

V (Vlang)

const digits = [[1, 10], [1234, 10], [0xfe, 16], [0xf0e, 16]]

fn main() {
	for val in digits {println(sum_digits(val[0], val[1]))}
}

fn sum_digits(num int, base int) int {
	mut sum, mut temp := 0, num
	for temp > 0 {
		sum += temp % base
		temp /= base
	}
	return sum
}
Output:
1
10
29
29

Wren

Library: Wren-fmt
import "./fmt" for Fmt, Conv

var sumDigits = Fn.new { |n, b|
    var sum = 0
    while (n > 0) {
        sum = sum + n%b
        n = (n/b).truncate
    }
    return sum
}

var tests = [ [1, 10], [1234, 10], [0xfe, 16], [0xf0e, 16], [1411, 8], [111, 3] ]
System.print("The sum of the digits is:")
for (test in tests) {
    var n = test[0]
    var b = test[1]
    var sum = sumDigits.call(n, b)
    Fmt.print("$-5s in base $2d = $2d", Conv.itoa(n, b), b, sum)
}
Output:
The sum of the digits is:
1     in base 10 =  1
1234  in base 10 = 10
fe    in base 16 = 29
f0e   in base 16 = 29
2603  in base  8 = 11
11010 in base  3 =  3

XPL0

code    ChOut=8, CrLf=9, IntOut=11;

func    SumDigits(N, Base);
int     N, Base, Sum;
[Sum:= 0;
repeat  N:= N/Base;
        Sum:= Sum + rem(0);
until   N=0;
return Sum;
];

[IntOut(0, SumDigits(1,      10));  ChOut(0, ^ );
 IntOut(0, SumDigits(12345,  10));  ChOut(0, ^ );
 IntOut(0, SumDigits(123045, 10));  ChOut(0, ^ );
 IntOut(0, SumDigits($FE,    10));  ChOut(0, ^ );
 IntOut(0, SumDigits($FE,    16));  ChOut(0, ^ );
 IntOut(0, SumDigits($F0E,   16));  CrLf(0);
]
Output:
1 15 15 11 29 29

zkl

fcn sum(n,b=10){ 
   if(b==10) n.split().sum(0);  // digits to list
   else      n.toString(b).split("").apply("toInt",b).sum(0);
}

If not base 10, convert the int into a string (in the proper base, ie 0xfe-->"fe"), blow it apart into a list of digits/characters, convert each character back into a int (from the base, ie ("c"/16-->12) and add them up.

Output:
sum(1,10);     //--> 1
sum(1234,10);  //--> 10
sum(0xfe,16);  //--> 29
sum(0xf0e,16); //--> 29
sum(0b1101,2); //--> 3