Exponentiation operator

From Rosetta Code
Task
Exponentiation operator
You are encouraged to solve this task according to the task description, using any language you may know.

Most programming languages have a built-in implementation of exponentiation.


Task

Re-implement integer exponentiation for both   intint   and   floatint   as both a procedure,   and an operator (if your language supports operator definition).

If the language supports operator (or procedure) overloading, then an overloaded form should be provided for both   intint   and   floatint   variants.


Related tasks



11l

Translation of: JavaScript
F my_pow(base, exp) -> Float
   I exp < 0
      R 1 / my_pow(base, -exp)
   I exp == 0
      R 1
   V ans = base
   L 0 .< exp - 1
      ans *= base
   R ans

print(‘2  ^ 3   = ’my_pow(2, 3))
print(‘1  ^ -10 = ’my_pow(1, -10))
print(‘-1 ^ -3  = ’my_pow(-1, -3))
print()
print(‘2.0 ^ -3 = ’my_pow(2.0, -3))
print(‘1.5 ^ 0  = ’my_pow(1.5, 0))
print(‘4.5 ^ 2  = ’my_pow(4.5, 2))
Output:
2  ^ 3   = 8
1  ^ -10 = 1
-1 ^ -3  = -1

2.0 ^ -3 = 0.125
1.5 ^ 0  = 1
4.5 ^ 2  = 20.25

68000 Assembly

68000 Assembly has no built-in exponentiation. The easiest form of this operator to implement is a 32-bit unsigned version.

ExponentUnsigned:
	;input: D0.W = BASE
	;	D1.W = EXPONENT
	;	OUTPUTS TO D0
	;	NO OVERFLOW PROTECTION - USE AT YOUR OWN RISK!
	;HIGH WORDS OF D0 AND D1 ARE CLEARED.
	;clobbers D1
	
	MOVE.L D2,-(SP)
		
		;using DBRAs lets us simultaneously subtract and compare
		DBRA D1,.test_if_one
		MOVEQ.L #1,D0		;executes only if D1 was 0 to start with
.test_if_one:		
		DBRA D1,.go
		bra .done		;executes only if D1 was 1 to start with
.go:
		;else, multiply D0 by its ORIGINAL self repeatedly.
		MOVE.L D0,D2
.loop:
		MULU D0,D2
		DBRA D1,.loop
		
		MOVE.L D2,D0
.done:
	MOVE.L (SP)+,D2
	RTS

Action!

INCLUDE "D2:REAL.ACT" ;from the Action! Tool Kit

INT FUNC PowerI(INT base,exp)
  INT res,i

  IF exp<0 THEN Break() FI

  res=1
  FOR i=1 TO exp
  DO
    res==*base
  OD
RETURN (res)

PROC PowerR(REAL POINTER base INT exp
            REAL POINTER res)
  INT i
  REAL tmp

  IF exp<0 THEN Break() FI

  IntToReal(1,res)
  FOR i=1 TO exp
  DO
    RealMult(res,base,tmp)
    RealAssign(tmp,res)
  OD
RETURN

PROC TestI(INT base,exp)
  INT res

  res=PowerI(base,exp)
  PrintF("%I^%I=%I%E",base,exp,res)
RETURN

PROC TestR(REAL POINTER base INT exp)
  REAL res

  PowerR(base,exp,res)
  PrintR(base) PrintF("^%I=",exp)
  PrintRE(res)
RETURN

PROC Main()
  REAL base

  Put(125) PutE() ;clear screen

  TestI(27,3)
  TestI(2,12)
  TestI(-3,9)
  TestI(1,1000)
  TestI(20000,0)
  
  ValR("3.141592654",base)
  TestR(base,10)
  ValR("-1.11",base)
  TestR(base,99)
  ValR("0.123456789",base)
  TestR(base,1)
  ValR("987654.321",base)
  TestR(base,0)
RETURN
Output:

Screenshot from Atari 8-bit computer

27^3=19683
2^12=4096
-3^9=-19683
1^1000=1
20000^0=1
3.14159265^10=93648.046
-1.11^99=-30688.4433
.123456789^1=.123456789
987654.321^0=1

Ada

First we declare the specifications of the two procedures and the two corresponding operators (written as functions with quoted operators as their names):

package Integer_Exponentiation is
   --  int^int
   procedure Exponentiate (Argument : in     Integer;
                           Exponent : in     Natural;
                           Result   :    out Integer);
   function "**" (Left  : Integer;
                  Right : Natural) return Integer;

   --  real^int
   procedure Exponentiate (Argument : in     Float;
                           Exponent : in     Integer;
                           Result   :    out Float);
   function "**" (Left  : Float;
                  Right : Integer) return Float;
end Integer_Exponentiation;

Now we can create a test program:

with Ada.Float_Text_IO, Ada.Integer_Text_IO, Ada.Text_IO;
with Integer_Exponentiation;

procedure Test_Integer_Exponentiation is
   use Ada.Float_Text_IO, Ada.Integer_Text_IO, Ada.Text_IO;
   use Integer_Exponentiation;
   R : Float;
   I : Integer;
begin
   Exponentiate (Argument => 2.5, Exponent => 3, Result => R);
   Put ("2.5 ^ 3 = ");
   Put (R, Fore => 2, Aft => 4, Exp => 0);
   New_Line;

   Exponentiate (Argument => -12, Exponent => 3, Result => I);
   Put ("-12 ^ 3 = ");
   Put (I, Width => 7);
   New_Line;
end Test_Integer_Exponentiation;

Finally we can implement the procedures and operations:

package body Integer_Exponentiation is
   --  int^int
   procedure Exponentiate (Argument : in     Integer;
                           Exponent : in     Natural;
                           Result   :    out Integer) is
   begin
      Result := 1;
      for Counter in 1 .. Exponent loop
         Result := Result * Argument;
      end loop;
   end Exponentiate;

   function "**" (Left  : Integer;
                  Right : Natural) return Integer is
      Result : Integer;
   begin
      Exponentiate (Argument => Left,
                    Exponent => Right,
                    Result   => Result);
      return Result;
   end "**";

   --  real^int
   procedure Exponentiate (Argument : in     Float;
                           Exponent : in     Integer;
                           Result   :    out Float) is
   begin
      Result := 1.0;
      if Exponent < 0 then
         for Counter in Exponent .. -1 loop
            Result := Result / Argument;
         end loop;
      else
         for Counter in 1 .. Exponent loop
            Result := Result * Argument;
         end loop;
      end if;
   end Exponentiate;

   function "**" (Left  : Float;
                  Right : Integer) return Float is
      Result : Float;
   begin
       Exponentiate (Argument => Left,
                    Exponent => Right,
                    Result   => Result);
      return Result;
   end "**";
end Integer_Exponentiation;

ALGOL 68

Works with: ALGOL 68 version Revision 1 - no extensions to language used
Works with: ALGOL 68G version Any - tested with release 1.18.0-9h.tiny
main:(
  INT two=2, thirty=30; # test constants #
  PROC VOID undefined;

# First implement exponentiation using a rather slow but sure FOR loop #
  PROC int pow = (INT base, exponent)INT: ( # PROC cannot be over loaded #
    IF exponent<0 THEN undefined FI;
    INT out:=( exponent=0 | 1 | base );
    FROM 2 TO exponent DO out*:=base OD;
    out
  );

  printf(($" One Gibi-unit is: int pow("g(0)","g(0)")="g(0)" - (cost: "g(0)
           " INT multiplications)"l$,two, thirty, int pow(two,thirty),thirty-1));

# implement exponentiation using a faster binary technique and WHILE LOOP #
  OP ** = (INT base, exponent)INT: (
    BITS binary exponent:=BIN exponent ; # do exponent arithmetic in binary #
    INT out := IF bits width ELEM binary exponent THEN base ELSE 1 FI;
    INT sq := IF exponent < 0 THEN undefined; ~ ELSE base FI;

    WHILE
      binary exponent := binary exponent SHR 1;
      binary exponent /= BIN 0
    DO
      sq *:= sq;
      IF bits width ELEM binary exponent THEN out *:= sq FI
    OD;
    out
  );

  printf(($" One Gibi-unit is: "g(0)"**"g(0)"="g(0)" - (cost: "g(0)
           " INT multiplications)"l$,two, thirty, two ** thirty,8));

  OP ** = (REAL in base, INT in exponent)REAL: ( # ** INT Operator can be overloaded #
    REAL base := ( in exponent<0 | 1/in base | in base);
    INT exponent := ABS in exponent;
    BITS binary exponent:=BIN exponent ; # do exponent arithmetic in binary #
    REAL out := IF bits width ELEM binary exponent THEN base ELSE 1 FI;
    REAL sq := base;

    WHILE
      binary exponent := binary exponent SHR 1;
      binary exponent /= BIN 0
    DO
      sq *:= sq;
      IF bits width ELEM binary exponent THEN out *:= sq FI
    OD;
    out
  );

  printf(($" One Gibi-unit is: "g(0,1)"**"g(0)"="g(0,1)" - (cost: "g(0)
           " REAL multiplications)"l$, 2.0, thirty, 2.0 ** thirty,8));

  OP ** = (REAL base, REAL exponent)REAL: ( # ** REAL Operator can be overloaded #
    exp(ln(base)*exponent)
  );

  printf(($" One Gibi-unit is: "g(0,1)"**"g(0,1)"="g(0,1)" - (cost: "
           "depends on precision)"l$, 2.0, 30.0, 2.0 ** 30.0))
)
Output:
One Gibi-unit is: int pow(2,30)=1073741824 - (cost: 29 INT multiplications)
One Gibi-unit is: 2**30=1073741824 - (cost: 8 INT multiplications)
One Gibi-unit is: 2.0**30=1073741824.0 - (cost: 8 REAL multiplications)
One Gibi-unit is: 2.0**30.0=1073741824.0 - (cost: depends on precision)

Recursive operator calls

Works with: ALGOL 68 version Revision 1 - no extensions to language used
Works with: ALGOL 68G version Any - tested with release 1.18.0-9h.tiny
main:(
  INT two=2, thirty=30; # test constants #
  PROC VOID undefined;
 
# First implement exponentiation using a rather slow but sure FOR loop #
  PROC int pow = (INT base, exponent)INT: ( # PROC cannot be over loaded #
    IF exponent<0 THEN undefined FI;
    INT out:=( exponent=0 | 1 | base );
    FROM 2 TO exponent DO out*:=base OD;
    out
  );
 
  printf(($" One Gibi-unit is: int pow("g(0)","g(0)")="g(0)" - (cost: "g(0)
           " INT multiplications)"l$,two, thirty, int pow(two,thirty),thirty-1));
 
# implement exponentiation using a faster binary technique and WHILE LOOP #
  OP ** = (INT base, exponent)INT:
    IF   base = 0 THEN 0 ELIF base = 1 THEN 1
    ELIF exponent = 0 THEN 1 ELIF exponent = 1 THEN base
    ELIF ODD exponent THEN
      (base*base) ** (exponent OVER 2) * base
    ELSE
      (base*base) ** (exponent OVER 2)
    FI;

  printf(($" One Gibi-unit is: "g(0)"**"g(0)"="g(0)" - (cost: "g(0)
           " INT multiplications)"l$,two, thirty, two ** thirty,8));
 
  OP ** = (REAL in base, INT in exponent)REAL: ( # ** INT Operator can be overloaded #
    REAL base := ( in exponent<0 | 1/in base | in base);
    INT exponent := ABS in exponent;
    IF   base = 0 THEN 0 ELIF base = 1 THEN 1
    ELIF exponent = 0 THEN 1 ELIF exponent = 1 THEN base
    ELIF ODD exponent THEN
      (base*base) ** (exponent OVER 2) * base
    ELSE
      (base*base) ** (exponent OVER 2)
    FI
  );
 
  printf(($" One Gibi-unit is: "g(0,1)"**"g(0)"="g(0,1)" - (cost: "g(0)
           " REAL multiplications)"l$, 2.0, thirty, 2.0 ** thirty,8));
 
  OP ** = (REAL base, REAL exponent)REAL: ( # ** REAL Operator can be overloaded #
    exp(ln(base)*exponent)
  );
 
  printf(($" One Gibi-unit is: "g(0,1)"**"g(0,1)"="g(0,1)" - (cost: "
           "depends on precision)"l$, 2.0, 30.0, 2.0 ** 30.0))
)
Output:
 One Gibi-unit is: int pow(2,30)=1073741824 - (cost: 29 INT multiplications)
 One Gibi-unit is: 2**30=1073741824 - (cost: 8 INT multiplications)
 One Gibi-unit is: 2.0**30=1073741824.0 - (cost: 8 REAL multiplications)
 One Gibi-unit is: 2.0**30.0=1073741824.0 - (cost: depends on precision)

AppleScript

on exponentiationOperatorTask(n, power)
    set power to power as integer
    set operatorResult to (n ^ power)
    set handlerResult to exponentiate(n, power)
    
    return {operator:operatorResult, |handler|:handlerResult}
end exponentiationOperatorTask

on exponentiate(n, power)
    -- AppleScript's ^ operator returns a real (ie. float) result. This handler does the same.
    set n to n as real
    set out to 1.0
    if (power < 0) then
        repeat -power times
            set out to out / n
        end repeat
    else
        repeat power times
            set out to out * n
        end repeat
    end if
    
    return out
end exponentiate

exponentiationOperatorTask(3, 3) --> {operator:27.0, |handler|:27.0}
exponentiationOperatorTask(2, 16) --> {operator:6.5536E+4, |handler|:6.5536E+4}
exponentiationOperatorTask(2.5, 10) --> {operator:9536.7431640625, |handler|:9536.7431640625}
exponentiationOperatorTask(2.5, -10) --> {operator:1.048576E-4, |handler|:1.048576E-4}

Arturo

myPow: function [base,xp][
    if xp < 0 [
        (floating? base)? -> return 1 // myPow base neg xp
                          -> return 1 / myPow base neg xp
    ]

    if xp = 0 ->
        return 1

    ans: 1
    while [xp > 0][
        ans: ans * base
        xp: xp - 1
    ]
    return ans
]

print ["2 ^ 3 =" myPow 2 3]
print ["1 ^ -10 =" myPow 1 neg 10]
print ["-1 ^ -3 =" myPow neg 1 neg 3]
print ""
print ["2.0 ^ -3 =" myPow 2.0 neg 3]
print ["1.5 ^ 0 =" myPow 1.5 0]
print ["4.5 ^ 2 =" myPow 4.5 2]
Output:
2 ^ 3 = 8 
1 ^ -10 = 1 
-1 ^ -3 = -1 

2.0 ^ -3 = 0.125 
1.5 ^ 0 = 1 
4.5 ^ 2 = 20.25

AutoHotkey

MsgBox % Pow(5,3)
MsgBox % Pow(2.5,4)

Pow(x, n){
	r:=1
	loop %n%
		r *= x
	return r
}

AWK

Traditional awk implementations do not provide an exponent operator, so we define a function to calculate the exponent. This one-liner reads base and exponent from stdin, one pair per line, and writes the result to stdout:

$ awk 'function pow(x,n){r=1;for(i=0;i<n;i++)r=r*x;return r}{print pow($1,$2)}'
Output:
2.5 2
6.25
10 6
1000000
3 0
1
But this last exponentation is wrong :
10 140
100000000000000048235962126657397336628942202864391877882749784196997612045996878213993935631944257381261260379071613194067266765009513873408
This is because traditionnal awk treat number internaly by finite precision.
If you want to use arbitrary precision number with (more recent) awk, you have to use -M option :
$ gawk -M '{ printf("%f\n",$1^$2) }'
Output:
10 140
100000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000,000000
And if you want to use locales for decimal separator, you have tu use -N option :
$ gawk -N '{ printf("%f\n",$1^$2) }'
Output:
2,5 2
6,250000

BASIC

Works with: QBasic

The vast majority of BASIC implementations don't support defining custom operators, or overloading of any kind.

DECLARE FUNCTION powL& (x AS INTEGER, y AS INTEGER)
DECLARE FUNCTION powS# (x AS SINGLE, y AS INTEGER)

DIM x AS INTEGER, y AS INTEGER
DIM a AS SINGLE

RANDOMIZE TIMER
a = RND * 10
x = INT(RND * 10)
y = INT(RND * 10)
PRINT x, y, powL&(x, y)
PRINT a, y, powS#(a, y)

FUNCTION powL& (x AS INTEGER, y AS INTEGER)
    DIM n AS INTEGER, m AS LONG
    IF x <> 0 THEN
        m = 1
        IF SGN(y) > 0 THEN
            FOR n = 1 TO y
                m = m * x
            NEXT
        END IF
    END IF
    powL& = m
END FUNCTION

FUNCTION powS# (x AS SINGLE, y AS INTEGER)
    DIM n AS INTEGER, m AS DOUBLE
    IF x <> 0 THEN
        m = 1
        IF y <> 0 THEN
            FOR n = 1 TO y
                m = m * x
            NEXT
            IF y < 0 THEN m = 1# / m
        END IF
    END IF
    powS# = m
END FUNCTION
Output:
 0             8             0
 7.768213      8             13260781.61887441
 1             9             1
 2.707636      9             7821.90151734948
 8             2             64
 9.712946      2             94.34131879665438

BASIC256

ni = int(rand * 10)
nf = round(rand * 10, 4)
ex = int(rand * 10)
print "     "; ni; " ^ "; ex; " = "; iPow (ni, ex)
print nf; " ^ "; ex; " = "; fPow (nf, ex)
end

function iPow (base, exponent)
    if exponent = 0 then return 1
    if exponent = 1 then return base
    if exponent < 0 then return 1 / iPow(base, -exponent)
    power = base
    for i = 2 to exponent
        power *= base
    next
    return power
end function

function fPow (base, exponent)
    if exponent = 0.0 then return 1.0
    if exponent = 1.0 then return base
    if exponent < 0.0 then return 1.0 / fPow(base, -exponent)
    power = base
    for i = 2 to exponent
        power *= base
    next
    return power
end function

True BASIC

RANDOMIZE

FUNCTION fPow (base, exponent)
    IF exponent = 0.0 THEN LET fPow = 1.0
    IF exponent = 1.0 THEN LET fPow = base
    IF exponent < 0.0 THEN LET fPow = 1.0 / fPow(base, -exponent)
    LET power = base
    FOR i = 2 TO exponent
        LET power = power * base
    NEXT i
    LET fPow = power
END FUNCTION

FUNCTION iPow (base, exponent)
    IF exponent = 0 THEN LET iPow = 1
    IF exponent = 1 THEN LET iPow = base
    IF exponent < 0 THEN LET iPow = 1 / iPow(base, -exponent)
    LET power = base
    FOR i = 2 TO exponent
        LET power = power * base
    NEXT i
    LET iPow = power
END FUNCTION

LET ni = ROUND(INT(RND * 10))
LET nf = RND * 10
LET ex = INT(RND * 10)
PRINT ni; " ^ "; ex; " = "; iPow (ni, ex)
PRINT nf; " ^ "; ex; " = "; fPow (nf, ex)
END

Yabasic

sub iPow (base, exponent)
    local power
    
    if exponent = 0  return 1
    if exponent = 1  return base
    if exponent < 0  return 1 / iPow(base, -exponent)
    power = base
    for i = 2 to exponent
        power = power * base
    next
    return power
end sub

sub fPow (base, exponent)
    local power
    
    if exponent = 0.0  return 1.0
    if exponent = 1.0  return base
    if exponent < 0.0  return 1.0 / fPow(base, -exponent)
    power = base
    for i = 2 to exponent
        power = power * base
    next
    return power
end sub

ni = round(ran(10))
nf = ran(10)
ex = int(ran(10))
print ni, " ^ ", ex, " = ", iPow (ni, ex)
print nf, " ^ ", ex, " = ", fPow (nf, ex)
end


BBC BASIC

      PRINT "11^5 = " ; FNipow(11, 5)
      PRINT "PI^3 = " ; FNfpow(PI, 3)
      END
      
      DEF FNipow(A%, B%)
      LOCAL I%, P%
      P% = 1
      FOR I% = 1 TO 32
        P% *= P%
        IF B% < 0 THEN P% *= A%
        B% = B% << 1
      NEXT
      = P%
      
      DEF FNfpow(A, B%)
      LOCAL I%, P
      P = 1
      FOR I% = 1 TO 32
        P *= P
        IF B% < 0 THEN P *= A
        B% = B% << 1
      NEXT
      = P
Output:
11^5 = 161051
PI^3 = 31.0062767

IS-BASIC

100 DEF POW(X,Y)
110   IF X=0 THEN LET POW=0:EXIT DEF
120   LET POW=EXP(Y*LOG(X))
130 END DEF
140 PRINT POW(PI,3)
150 PRINT PI^3

Befunge

Note: Only works for integer bases and powers.

v         v       \<
>&:32p&1-\>32g*\1-:|
                   $
                   .
                   @

Brat

#Procedure
exp = { base, exp |
  1.to(exp).reduce 1, { m, n | m = m * base }
}

#Numbers are weird
1.parent.^ = { rhs |
  num = my
  1.to(rhs).reduce 1 { m, n | m = m * num }
}

p exp 2 5 #Prints 32
p 2 ^ 5   #Prints 32

C

Two versions are given - one for integer bases, the other for floating point. The integer version returns 0 when the abs(base) is != 1 and the exponent is negative.

#include <stdio.h>
#include <assert.h>

int ipow(int base, int exp)
{
   int pow = base;
   int v = 1;
   if (exp < 0) {
      assert (base != 0);  /* divide by zero */
      return (base*base != 1)? 0: (exp&1)? base : 1;
   }
       
   while(exp > 0 )
   {
      if (exp & 1) v *= pow;
      pow *= pow;
      exp >>= 1;
    }
   return v;
}

double dpow(double base, int exp)
{
   double v=1.0;
   double pow = (exp <0)? 1.0/base : base;
   if (exp < 0) exp = - exp;

   while(exp > 0 )
   {
      if (exp & 1) v *= pow;
      pow *= pow;
      exp >>= 1;
   }
   return v;
}

int main()
{
    printf("2^6 = %d\n", ipow(2,6));
    printf("2^-6 = %d\n", ipow(2,-6));
    printf("2.71^6 = %lf\n", dpow(2.71,6));
    printf("2.71^-6 = %lf\n", dpow(2.71,-6));
}

The C11 standard features type-generic expressions via the _Generic keyword. We can add to the above example to use this feature.

Works with: Clang version 3.0+
#define generic_pow(base, exp)\
    _Generic((base),\
            double: dpow,\
            int: ipow)\
    (base, exp)

int main()
{
    printf("2^6 = %d\n", generic_pow(2,6));
    printf("2^-6 = %d\n", generic_pow(2,-6));
    printf("2.71^6 = %lf\n", generic_pow(2.71,6));
    printf("2.71^-6 = %lf\n", generic_pow(2.71,-6));
}

C#

In C# it is possible to overload operators (+, -, *, etc..), but to do so requires the overload to implement at least one argument as the calling type.

What this means, is that if we have the class, A, to do an overload of + - we must set one of the arguments as the type "A". This is because in C#, overloads are defined on a class basis - so when doing an operator, .Net looks at the class to find the operators. In this manner, one of the arguments must be of the class, else .Net would be looking there in vain.

This again means, that a direct overloading of the ^-character between two integers / double and integer is not possible.

However - coming to think of it, one could overload the "int" class, and enter the operator there. --LordMike 17:45, 5 May 2010 (UTC)

static void Main(string[] args)
{
	Console.WriteLine("5^5 = " + Expon(5, 5));
	Console.WriteLine("5.5^5 = " + Expon(5.5, 5));
	Console.ReadLine();
}

static double Expon(int Val, int Pow) 
{
	return Math.Pow(Val, Pow);
}
static double Expon(double Val, int Pow)
{
	return Math.Pow(Val, Pow);
}
Output:
5^5 = 3125
5.5^5 = 5032,84375

C++

While C++ does allow operator overloading, it does not have an exponentiation operator, therefore only a function definition is given. For non-negative exponents the integer and floating point versions are exactly the same, for obvious reasons. For negative exponents, the integer exponentiation would not give integer results; therefore there are several possibilities:

  1. Use floating point results even for integer exponents.
  2. Use integer results for integer exponents and give an error for negative exponents.
  3. Use integer results for integer exponents and return just the integer part (i.e. return 0 if the base is larger than one and the exponent is negative).

The third option somewhat resembles the integer division rules, and has the nice property that it can use the exact same algorithm as the floating point version. Therefore this option is chosen here. Actually the template can be used with any type which supports multiplication, division and explicit initialization from int. Note that there are several aspects about int which are not portably defined; most notably it is not guaranteed

  • that the negative of a valid int is again a valid int; indeed for most implementations, the minimal value doesn't have a positive counterpart,
  • whether the result of a%b is positive or negative if a is negative, and in which direction the corresponding division is rounded (however, it is guaranteed that (a/b)*b + a%b == a)

The code below tries to avoid those platform dependencies. Note that bitwise operations wouldn't help here either, because the representation of negative numbers can vary as well.

template<typename Number>
 Number power(Number base, int exponent)
{
  int zerodir;
  Number factor;
  if (exponent < 0)
  {
    zerodir = 1;
    factor = Number(1)/base;
  }
  else
  {
    zerodir = -1;
    factor = base;
  }

  Number result(1);
  while (exponent != 0)
  {
    if (exponent % 2 != 0)
    {
      result *= factor;
      exponent += zerodir;
    }
    else
    {
      factor *= factor;
      exponent /= 2;
    }
  }
  return result;
}

Chef

See Basic integer arithmetic#Chef.

Clojure

Operators in Clojure are functions, so this satisfies both requirements. Also, this is polymorphic- it will work with integers, floats, etc, even ratios. (Since operators are implemented as functions they are used in prefix notation)

(defn ** [x n] (reduce * (repeat n x)))

Usage:

(** 2 3)        ; 8
(** 7.2 2.1)    ; 373.24800000000005
(** 7/2 3)      ; 343/8

Common Lisp

Common Lisp has a few forms of iteration. One of the more general is the do loop. Using the do loop, one definition is given below:

(defun my-expt-do (a b)
  (do ((x 1 (* x a))
       (y 0 (+ y 1)))
      ((= y b) x)))

do takes three forms. The first is a list of variable initializers and incrementers. In this case, x, the eventual return value, is initialized to 1, and every iteration of the do loop replaces the value of x with x * a. Similarly, y is initialized to 0 and is replaced with y + 1. The second is a list of conditions and return values. In this case, when y = b, the loop stops, and the current value of x is returned. Common Lisp has no explicit return keyword, so x ends up being the return value for the function. The last form is the body of the loop, and usually consists of some action to perform (that has some side-effect). In this case, all the work is being done by the first and second forms, so there are no extra actions.

Of course, Lisp programmers often prefer recursive solutions.

(defun my-expt-rec (a b)
  (cond 
    ((= b 0) 1)
    (t (* a (my-expt-rec a (- b 1))))))

This solution uses the fact that a^0 = 1 and that a^b = a * a^{b-1}. cond is essentially a generalized if-statement. It takes a list of forms of the form (cond result). For instance, in this case, if b = 0, then function returns 1. t is the truth constant in Common Lisp and is often used as a default condition (similar to the default keyword in C/C++/Java or the else block in many languages).

Common Lisp has much more lenient rules for identifiers. In particular, ^ is a valid CL identifier. Since it is not already defined in the standard library, we can simply use it as a function name, just like any other function.

(defun ^ (a b)
  (do ((x 1 (* x a))
       (y 0 (+ y 1)))
      ((= y b) x)))

D

Translation of: Python
Translation of: C++

D has a built-in exponentiation operator: ^^

import std.stdio, std.conv;

struct Number(T) {
    T x; // base
    alias x this;
    string toString() const { return text(x); }

    Number opBinary(string op)(in int exponent)
    const pure nothrow @nogc if (op == "^^") in {
        if (exponent < 0)
            assert (x != 0, "Division by zero");
    } body {
        debug puts("opBinary ^^");

        int zerodir;
        T factor;
        if (exponent < 0) {
            zerodir = +1;
            factor = T(1) / x;
        } else {
            zerodir = -1;
            factor = x;
        }

        T result = 1;
        int e = exponent;
        while (e != 0)
            if (e % 2 != 0) {
                result *= factor;
                e += zerodir;
            } else {
                factor *= factor;
                e /= 2;
            }

        return Number(result);
    }
}

void main() {
    alias Double = Number!double;
    writeln(Double(2.5) ^^ 5);

    alias Int = Number!int;
    writeln(Int(3) ^^ 3);
    writeln(Int(0) ^^ -2); // Division by zero.
}
Output:

(Compiled in debug mode, stack trace removed)

core.exception.AssertError@exponentiation_operator.d(11): Division by zero
opBinary ^^
97.6563
opBinary ^^
27
opBinary

Delphi

program Exponentiation_operator;

{$APPTYPE CONSOLE}

uses
  System.SysUtils;

type
  TDouble = record
    Value: Double;
    class operator Implicit(a: TDouble): Double;
    class operator Implicit(a: Double): TDouble;
    class operator Implicit(a: TDouble): string;
    class operator LogicalXor(a: TDouble; b: Integer): TDouble;
  end;

  TInteger = record
    Value: Integer;
    class operator Implicit(a: TInteger): Integer;
    class operator Implicit(a: Integer): TInteger;
    class operator Implicit(a: TInteger): string;
    class operator LogicalXor(a: TInteger; b: Integer): TInteger;
  end;

{ TDouble }

class operator TDouble.Implicit(a: TDouble): Double;
begin
  Result := a.Value;
end;

class operator TDouble.Implicit(a: Double): TDouble;
begin
  Result.Value := a;
end;

class operator TDouble.Implicit(a: TDouble): string;
begin
  Result := a.Value.ToString;
end;

class operator TDouble.LogicalXor(a: TDouble; b: Integer): TDouble;
var
  i: Integer;
  val: Double;
begin
  val := 1;
  for i := 1 to b do
    val := val * a.Value;
  Result.Value := val;
end;

{ TInteger }

class operator TInteger.Implicit(a: TInteger): Integer;
begin
  Result := a.Value;
end;

class operator TInteger.Implicit(a: Integer): TInteger;
begin
  Result.Value := a;
end;

class operator TInteger.Implicit(a: TInteger): string;
begin
  Result := a.Value.ToString;
end;

class operator TInteger.LogicalXor(a: TInteger; b: Integer): TInteger;
var
  val, i: Integer;
begin
  if b < 0 then
    raise Exception.Create('Expoent must be greater or equal zero');

  val := 1;
  for i := 1 to b do
    val := val * a.Value;
  Result.Value := val;
end;

procedure Print(s: string);
begin
  Write(s);
end;

var
  valF: TDouble;
  valI: TInteger;

begin
  valF := 5.5;
  valI := 5;

  // Delphi  don't have "**" or "^" operator for overload,
  // "xor" operator has used instead
  Print('5^5 = ');
  Print(valI xor 5);
  print(#10);

  Print('5.5^5 = ');
  Print(valF xor 5);
  print(#10);

  readln;
end.
Output:
5^5 = 3125
5.5^5 = 5032,84375

E

Simple, unoptimized implementation which will accept any kind of number for the base. If the base is an int, then the result will be of type float64 if the exponent is negative, and int otherwise.

def power(base, exponent :int) {
    var r := base
    if (exponent < 0) {
        for _ in exponent..0 { r /= base }
    } else if (exponent <=> 0) {
        return 1
    } else {
        for _ in 2..exponent { r *= base }
    }
    return r
}

EasyLang

func mypow n exp .
   r = 1
   if exp < 0
      exp = -exp
      n = 1 / n
   .
   for i to exp
      r *= n
   .
   return r
.
print mypow pi 2
print mypow 2 -2

EchoLisp

;; this exponentiation function handles integer, rational or float x.
;; n is a positive or negative integer.

(define (** x n) (cond 
    ((zero? n) 1) 
    ((< n 0) (/ (** x (- n)))) ;; x**-n = 1 / x**n
    ((= n 1) x) 
    ((= n 0) 1) 
    ((odd? n) (* x (** x (1- n)))) ;; x**(2p+1) = x * x**2p
    (else (let ((m (** x (/ n 2)))) (* m m))))) ;; x**2p = (x**p) * (x**p)

(** 3 0)  1
(** 3 4)  81
(** 3 5)  243
(** 10 10)  10000000000
(** 1.3 10)  13.785849184900007

(** -3 5)  -243
(** 3 -4)  1/81
(** 3.7 -4)  0.005335720890574502
(** 2/3 7)  128/2187

(lib 'bigint)
(** 666 42)  
38540524895511613165266748863173814985473295063157418576769816295283207864908351682948692085553606681763707358759878656

Ela

Ela standard prelude already defines an exponentiation operator (**) but we will implement it by ourselves anyway:

open number

_ ^ 0           =  1
x ^ n | n > 0   =  f x (n - 1) x
      |else = fail "Negative exponent"
  where f _ 0 y = y
        f a d y = g a d
          where g b i | even i  = g (b * b) (i `quot` 2)
                      | else = f b (i - 1) (b * y)

(12 ^ 4, 12 ** 4)
Output:
(20736,20736)

Ela supports generic arithmetic functions and generic numeric literals. This is how we can change an implementation of a (^) function and make it generic:

open number

//Function quot from number module is defined only for
//integral numbers. We can use this as an universal quot.
uquot x y | x is Integral = x `quot` y
          | else = x / y

//Changing implementation by using generic numeric literals
//(e.g. 2u) and elimitating all comparisons with 0.
!x ^ n  | n ~= 0u = 1u
        | n > 0u  =  f x (n - 1u) x
        | else = fail "Negative exponent"
  where f a d y
          | d ~= 0u = y
          | else = g a d
          where g b i | even i  = g (b * b) (i `uquot` 2u)
                      | else = f b (i - 1u) (b * y)


(12 ^ 4, 12.34 ^ 4.04)
Output:
(20736,286138.2f)

We have a case of true polymorphism here and no overloading is required. However Ela supports overloading using classes (somewhat similar to Haskell type classes) so we can show how the same implementation could work with overloading (less preferable in this case because of more redundant code but still possible):

open number

//A class that defines our overloadable function
class Exponent a where
  (^) a->a->_

//Implementation for integers
instance Exponent Int where
  _ ^ 0           =  1
  x ^ n | n > 0   =  f x (n - 1) x
        |else = fail "Negative exponent"
    where f _ 0 y = y
          f a d y = g a d
            where g b i | even i  = g (b * b) (i `quot` 2)
                        | else = f b (i - 1) (b * y)

//Implementation for floats
instance Exponent Single where
  x ^ n | n < 0.001 = 1
        | n > 0 =  f x (n - 1) x
        | else = fail "Negative exponent"
    where f a d y
            | d < 0.001 = y
            | else = g a d
            where g b i | even i  = g (b * b) (i / 2)
                        | else = f b (i - 1) (b * y)

(12 ^ 4, 12.34 ^ 4.04)
Output:
(20736,286138.2f)

Elixir

defmodule My do
  def exp(x,y) when is_integer(x) and is_integer(y) and y>=0 do
    IO.write("int>   ")         # debug test
    exp_int(x,y)
  end
  def exp(x,y) when is_integer(y) do
    IO.write("float> ")         # debug test
    exp_float(x,y)
  end
  def exp(x,y), do: (IO.write("       "); :math.pow(x,y))
  
  defp exp_int(_,0), do: 1
  defp exp_int(x,y), do: Enum.reduce(1..y, 1, fn _,acc -> x * acc end)
  
  defp exp_float(_,y) when y==0, do: 1.0
  defp exp_float(x,y) when y<0, do: 1/exp_float(x,-y)
  defp exp_float(x,y), do: Enum.reduce(1..y, 1, fn _,acc -> x * acc end)
end

list = [{2,0}, {2,3}, {2,-2},
        {2.0,0}, {2.0,3}, {2.0,-2},
        {0.5,0}, {0.5,3}, {0.5,-2},
        {-2,2}, {-2,3}, {-2.0,2}, {-2.0,3},
        ]
IO.puts "                    ___My.exp___  __:math.pow_"
Enum.each(list, fn {x,y} ->
  sxy = "#{x} ** #{y}"
  sexp = inspect My.exp(x,y)
  spow = inspect :math.pow(x,y)         # For the comparison
  :io.fwrite("~10s = ~12s, ~12s~n", [sxy, sexp, spow])
end)
Output:
                    ___My.exp___  __:math.pow_
int>       2 ** 0 =            1,          1.0
int>       2 ** 3 =            8,          8.0
float>    2 ** -2 =         0.25,         0.25
float>   2.0 ** 0 =          1.0,          1.0
float>   2.0 ** 3 =          8.0,          8.0
float>  2.0 ** -2 =         0.25,         0.25
float>   0.5 ** 0 =          1.0,          1.0
float>   0.5 ** 3 =        0.125,        0.125
float>  0.5 ** -2 =          4.0,          4.0
int>      -2 ** 2 =            4,          4.0
int>      -2 ** 3 =           -8,         -8.0
float>  -2.0 ** 2 =          4.0,          4.0
float>  -2.0 ** 3 =         -8.0,         -8.0

Erlang

Works with: Erlang version OTP R14B02 and higher

pow(number, integer) -> number

pow(X, Y) when Y < 0 ->
    1/pow(X, -Y);
pow(X, Y) when is_integer(Y) ->
    pow(X, Y, 1).

pow(_, 0, B) ->
    B;
pow(X, Y, B) ->
    B2 = if Y rem 2 =:= 0 -> B; true -> X * B end,
    pow(X * X, Y div 2, B2).

Tail call optimised version which works for both integers and float bases.

ERRE

ERRE does not permit operator overloading, so we can use a procedure only. The procedure below handles *integer powers*: for floating point exponent you must use EXP and LOG predefined functions.

PROGRAM POWER

PROCEDURE POWER(A,B->POW)   ! this routine handles only *INTEGER* powers
  LOCAL FLAG%
  IF B<0 THEN B=-B FLAG%=TRUE
  POW=1
  FOR X=1 TO B DO
    POW=POW*A
  END FOR
  IF FLAG% THEN POW=1/POW
END PROCEDURE

BEGIN
   POWER(11,-2->POW) PRINT(POW)
   POWER(π,3->POW) PRINT(POW)
END PROGRAM
Output:
 8.264463E-03
 31.00628

F#

//Integer Exponentiation, more interesting anyway than repeated multiplication. Nigel Galloway, October 12th., 2018
let rec myExp n g=match g with
                  |0            ->1
                  |g when g%2=1 ->n*(myExp n (g-1))
                  |_            ->let p=myExp n (g/2) in p*p

printfn "%d" (myExp 3 15)
Output:
14348907

Factor

Simple, unoptimized implementation which accepts a positive or negative exponent:

: pow ( f n -- f' )
    dup 0 < [ abs pow recip ]
    [ [ 1 ] 2dip swap [ * ] curry times ] if ;

Here is a recursive implementation which splits the exponent in two:

: pow ( f n -- f' )
    {  
        { [ dup 0 < ] [ abs pow recip ] }
        { [ dup 0 = ] [ 2drop 1 ] }
        [ [ 2 mod 1 = swap 1 ? ] [ [ sq ] [ 2 /i ] bi* pow ] 2bi * ]
    } cond ;

This implementation recurses only when an odd factor is found:

USING: combinators kernel math ;
IN: test

: (pow) ( f n -- f' )
    [ dup even? ] [ [ sq ] [ 2 /i ] bi* ] while
    dup 1 = [ drop ] [ dupd 1 - (pow) * ] if ;

: pow ( f n -- f' )
    {
        { [ dup 0 < ] [ abs (pow) recip ] }
        { [ dup 0 = ] [ 2drop 1 ] }
        [ (pow) ]
    } cond ;

A non-recursive version of (pow) can be written as:

: (pow) ( f n -- f' )
    [ 1 ] 2dip     
    [ dup 1 = ] [
        dup even? [ [ sq ] [ 2 /i ] bi* ] [ [ [ * ] keep ] dip 1 - ] if
    ] until
    drop * ;

Forth

: ** ( n m -- n^m )
  1 swap  0 ?do over * loop  nip ;
: f**n ( f n -- f^n )
  dup 0= if
    drop fdrop 1e
  else dup 1 and if
    1- fdup recurse f*
  else
    2/ fdup f* recurse
  then then ;

Fortran

Works with: Fortran version 90 and later
MODULE Exp_Mod
IMPLICIT NONE

INTERFACE OPERATOR (.pow.)    ! Using ** instead would overload the standard exponentiation operator
  MODULE PROCEDURE Intexp, Realexp
END INTERFACE

CONTAINS

  FUNCTION Intexp (base, exponent)
    INTEGER :: Intexp
    INTEGER, INTENT(IN) :: base, exponent
    INTEGER :: i

    IF (exponent < 0) THEN
       IF (base == 1) THEN
          Intexp = 1
       ELSE
          Intexp = 0
       END IF
       RETURN
    END IF
    Intexp = 1
    DO i = 1, exponent
      Intexp = Intexp * base
    END DO
  END FUNCTION IntExp

  FUNCTION Realexp (base, exponent)
    REAL :: Realexp
    REAL, INTENT(IN) :: base
    INTEGER, INTENT(IN) :: exponent
    INTEGER :: i
  
    Realexp = 1.0
    IF (exponent < 0) THEN
       DO i = exponent, -1
          Realexp = Realexp / base
       END DO
    ELSE  
       DO i = 1, exponent
          Realexp = Realexp * base
       END DO
    END IF
  END FUNCTION RealExp
END MODULE Exp_Mod

PROGRAM EXAMPLE
USE Exp_Mod
  WRITE(*,*) 2.pow.30, 2.0.pow.30
END PROGRAM EXAMPLE
Output:
  1073741824    1.073742E+09

FreeBASIC

' FB 1.05.0

' Note that 'base' is a keyword in FB, so we use 'base_' instead as a parameter

Function Pow Overload (base_ As Double, exponent As Integer) As Double
  If exponent = 0.0 Then Return 1.0
  If exponent = 1.0 Then Return base_
  If exponent < 0.0 Then Return 1.0 / Pow(base_, -exponent)
  Dim power As Double = base_
  For i As Integer = 2 To exponent
     power *= base_
  Next
  Return power
End Function

Function Pow Overload(base_ As Integer, exponent As Integer) As Double
   Return Pow(CDbl(base_), exponent)
End Function

' check results of these functions using FB's built in '^' operator
Print "Pow(2, 2)       = "; Pow(2, 2)
Print "Pow(2.5, 2)     = "; Pow(2.5, 2)
Print "Pow(2, -3)      = "; Pow(2, -3) 
Print "Pow(1.78, 3)    = "; Pow(1.78, 3)
Print
Print "2 ^ 2           = "; 2 ^ 2
Print "2.5 ^ 2         = "; 2.5 ^ 2
Print "2 ^ -3          = "; 2 ^ -3 
Print "1.78 ^ 3        = "; 1.78 ^ 3
Print
Print "Press any key to quit"
Sleep
Output:
Pow(2, 2)       =  4
Pow(2.5, 2)     =  6.25
Pow(2, -3)      =  0.125
Pow(1.78, 3)    =  5.639752000000001

2 ^ 2           =  4
2.5 ^ 2         =  6.25
2 ^ -3          =  0.125
1.78 ^ 3        =  5.639752000000001

FutureBasic

local fn CustomPOW( base as double, exponent as NSInteger ) as double
  double     power = base, result
  NSUInteger i
  
  if exponent = 0.0 then result = 1.0  : exit fn
  if exponent = 1.0 then result = base : exit fn
  if exponent < 0.0
    for i = 2 to -exponent
      power = power * base
    next
    result = 1.0/power : exit fn
  end if
  for i = 2 to exponent
    power = power * base
  next
  result = power
end fn = result

print "Custom POW function:"
print "fn CustomPOW( 2,    2 ) = "; fn CustomPOW( 2,    2 )
print "fn CustomPOW( 2.5,  2 ) = "; fn CustomPOW( 2.5,  2 )
print "fn CustomPOW( 2,   -3 ) = "; fn CustomPOW( 2,   -3 )
print "fn CustomPOW( 1.78, 3 ) = "; fn CustomPOW( 1.78, 3 )
print "fn CustomPOW( 5.5,  5 ) = "; fn CustomPOW( 5.5,  5 )
print "fn CustomPOW( 4.5,  2 ) = "; fn CustomPOW( 4.5,  2 )
print "fn CustomPOW( -1,  -3 ) = "; fn CustomPOW( -1,  -3 )
print
print "Native FB ^ operator:"
print "2^2    = "; 2^2
print "2.5^2  = "; 2.5^2
print "2^-3   = "; 2^-3
print "1.78^3 = "; 1.78^3
print "5.5^5  = "; 5.5^5
print "4.5^2  = "; 4.5^2
print "-1^=3  = "; -1^-3
print
print "Native FB fn POW function:"
print "fn POW( 2,    2 ) = "; fn POW( 2,    2 )
print "fn POW( 2.5,  2 ) = "; fn POW( 2.5,  2 )
print "fn POW( 2,   -3 ) = "; fn POW( 2,   -3 )
print "fn POW( 1.78, 3 ) = "; fn POW( 1.78, 3 )
print "fn POW( 5.5,  5 ) = "; fn POW( 5.5,  5 )
print "fn POW( 4.5,  2 ) = "; fn POW( 4.5,  2 )
print "fn POW( -1,  -3 ) = "; fn POW( -1,  -3 )
print

HandleEvents
Output:
Custom POW function:
fn CustomPOW( 2,    2 ) = 4
fn CustomPOW( 2.5,  2 ) = 6.25
fn CustomPOW( 2,   -3 ) = 0.125
fn CustomPOW( 1.78, 3 ) = 5.639752000000001
fn CustomPOW( 5.5,  5 ) = 5032.84375
fn CustomPOW( 4.5,  2 ) = 20.25
fn CustomPOW( -1,  -3 ) = -1

Native FB ^ operator:
2^2    = 4
2.5^2  = 6.25
2^-3   = 0.125
1.78^3 = 5.639752000000001
5.5^5  = 5032.84375
4.5^2  = 20.25
-1^=3  = -1

Native FB fn POW function:
fn POW( 2,    2 ) = 4
fn POW( 2.5,  2 ) = 6.25
fn POW( 2,   -3 ) = 0.125
fn POW( 1.78, 3 ) = 5.639752000000001
fn POW( 5.5,  5 ) = 5032.84375
fn POW( 4.5,  2 ) = 20.25
fn POW( -1,  -3 ) = -1


GAP

expon := function(a, n, one, mul)
	local p;
	p := one;
	while n > 0 do
		if IsOddInt(n) then
			p := mul(a, p);
		fi;
		a := mul(a, a);
		n := QuoInt(n, 2);
	od;
	return p;
end;

expon(2, 10, 1, \*);
# 1024

# a more creative use of exponentiation
List([0 .. 31], n -> (1 - expon(0, n, 1, \-))/2);
# [ 0, 1, 1, 0, 1, 0, 0, 1, 1, 0, 0, 1, 0, 1, 1, 0,
#   1, 0, 0, 1, 0, 1, 1, 0, 0, 1, 1, 0, 1, 0, 0, 1 ]

Go

Go doesn't support operator defintion. Other notes: While I left the integer algorithm simple, I used the shift and square trick for the float algorithm, just to show an alternative.

package main

import (
    "errors"
    "fmt"
)

func expI(b, p int) (int, error) {
    if p < 0 {
        return 0, errors.New("negative power not allowed")
    }
    r := 1
    for i := 1; i <= p; i++ {
        r *= b
    }
    return r, nil
}

func expF(b float32, p int) float32 {
    var neg bool
    if p < 0 {
        neg = true
        p = -p
    }
    r := float32(1)
    for pow := b; p > 0; pow *= pow {
        if p&1 == 1 {
            r *= pow
        }
        p >>= 1
    }
    if neg {
        r = 1 / r
    }
    return r
}

func main() {
    ti := func(b, p int) {
        fmt.Printf("%d^%d: ", b, p)
        e, err := expI(b, p)
        if err != nil {
            fmt.Println(err)
        } else {
            fmt.Println(e)
        }
    }

    fmt.Println("expI tests")
    ti(2, 10)
    ti(2, -10)
    ti(-2, 10)
    ti(-2, 11)
    ti(11, 0)

    fmt.Println("overflow undetected")
    ti(10, 10)

    tf := func(b float32, p int) {
        fmt.Printf("%g^%d: %g\n", b, p, expF(b, p))
    }

    fmt.Println("\nexpF tests:")
    tf(2, 10)
    tf(2, -10)
    tf(-2, 10)
    tf(-2, 11)
    tf(11, 0)

    fmt.Println("disallowed in expI, allowed here")
    tf(0, -1)

    fmt.Println("other interesting cases for 32 bit float type")
    tf(10, 39)
    tf(10, -39)
    tf(-10, 39)
}
Output:
expI tests
2^10: 1024
2^-10: negative power not allowed
-2^10: 1024
-2^11: -2048
11^0: 1
overflow undetected
10^10: 1410065408

expF tests:
2^10: 1024
2^-10: 0.0009765625
-2^10: 1024
-2^11: -2048
11^0: 1
disallowed in expI, allowed here
0^-1: +Inf
other interesting cases for 32 bit float type
10^39: +Inf
10^-39: 0
-10^39: -Inf

Haskell

Here's the exponentiation operator from the Prelude:

(^) :: (Num a, Integral b) => a -> b -> a
_ ^ 0           =  1
x ^ n | n > 0   =  f x (n-1) x where
  f _ 0 y = y
  f a d y = g a d  where
    g b i | even i  = g (b*b) (i `quot` 2)
          | otherwise = f b (i-1) (b*y)
_ ^ _           = error "Prelude.^: negative exponent"

There's no difference in Haskell between a procedure (or function) and an operator, other than the infix notation. This routine is overloaded for any integral exponent (which includes the arbitrarily large Integer type) and any numeric type for the bases (including, for example, Complex). It uses the fast "binary" exponentiation algorithm. For a negative exponent, the type of the base must support division (and hence reciprocals):

(^^) :: (Fractional a, Integral b) => a -> b -> a
x ^^ n = if n >= 0 then x^n else recip (x^(negate n))

This rules out e.g. the integer types as base values in this case. Haskell also has a third exponentiation operator,

(**) :: Floating a => a -> a -> a
x ** y = exp (log x * y)

which is used for floating point arithmetic.

HicEst

WRITE(Clipboard) pow(5,   3)  ! 125
WRITE(ClipBoard) pow(5.5, 7)  ! 152243.5234

FUNCTION pow(x, n)
   pow = 1
   DO i = 1, n
      pow = pow * x
   ENDDO
END

Icon and Unicon

The procedure below will take an integer or real base and integer exponent and return base ^ exponent. If exponent is negative, base is coerced to real so as not to return 0. Operator overloading is not supported and this is not an efficient implementation.

procedure main()
bases := [5,5.]
numbers := [0,2,2.,-1,3]
every  write("expon(",b := !bases,", ",x := !numbers,")=",(expon(b,x) | "failed") \ 1)
end

procedure expon(base,power)
local op,res

base := numeric(base)            | runerror(102,base)
power := power = integer(power)  | runerr(101,power)

if power = 0 then return 1
else op := if power < 1 then 
              (base := real(base)) & "/"   # force real base
              else "*"

res := 1
every 1 to abs(power) do
   res := op(res,base)
return res
end

J

J is concretely specified, which makes it easy to define primitives in terms of other primitives (this is especially true of mathematical primitives, given the language's mathematical emphasis).

So we have any number of options. Here's the simplest, equivalent to the for each number, product = product * number of other languages. The base may be any number, and the exponent may be any non-negative integer (including zero):

   exp  =:  */@:#~ 
   
   10 exp 3
1000
   
   10 exp 0
1

We can make this more general by allowing the exponent to be any integer (including negatives), at the cost of a slight increase in complexity:

   exp  =:  *@:] %: */@:(#~|)
   
   10 exp _3
0.001

Or, we can define exponentiation as repeated multiplication (as opposed to multiplying a given number of copies of the base)

   exp =: dyad def 'x *^:y 1'

   10 exp 3
1000
   10 exp _3
0.001

Here, when we specify a negative number of repetitions, multiplication's inverse is used that many times.

J's calculus of functions permits us to define exponentiation in its full generality, as the inverse of log (i.e. exp = log-1):

 exp  =:  ^.^:_1
 
 81 exp 0.5   
9

Note that the definition above does not use the primitive exponentiation function ^ . The carets in it represent different (but related) things . The function is composed of three parts: ^. ^: _1 . The first part, ^., is the primitive logarithm operator (e.g. 3 = 10^.1000) .

The second part, ^: , is interesting: it is a "meta operator". It takes two arguments: a function f on its left, and a number N on its right. It produces a new function, which, when given an argument, applies f to that argument N times. For example, if we had a function increment, then increment^:3 X would increment X three times, so the result would be X+3.

In the case of ^. ^: _1 , f is ^. (i.e. logarithm) and N is -1. Therefore we apply log negative one times or the inverse of log once (precisely as in log-1).

Similarly, we can define exponentiation as the reverse of the inverse of root. That is, x pow y = y root-1 x:

 exp  =:  %:^:_1~
 
 81 exp 0.5
9

Compare this with the previous definition: it is the same, except that %: , root, has been substituted for ^. , logarithm, and the arguments have been reversed (or reflected) with ~.

That is, J is telling us that power is the same as the reflex of the inverse of root, exactly as we'd expect.

One last note: we said these definitions are the same as ^ in its full generality. What is meant by that? Well, in the context of this puzzle, it means both the base and exponent may be any real number. But J goes further than that: it also permits complex numbers.

Let's use Euler's famous formula, epi*i = -1 as an example:

   pi =: 3.14159265358979323846
   e  =: 2.71828182845904523536
   i  =: 2 %: _1                  NB.  Square root of -1
   
   e^(pi*i)
_1

And, as stated, our redefinition is equivalent:

   exp =: %:^:_1~
   
   e exp (pi*i)
_1

Java

Java does not support operator definition. This example is unoptimized, but will handle negative exponents as well. It is unnecessary to show intint since an int in Java will be cast as a double.

public class Exp{
   public static void main(String[] args){
      System.out.println(pow(2,30));
      System.out.println(pow(2.0,30)); //tests
      System.out.println(pow(2.0,-2));
   }

   public static double pow(double base, int exp){
      if(exp < 0) return 1 / pow(base, -exp);
      double ans = 1.0;
      for(;exp > 0;--exp) ans *= base;
      return ans;
   }
}
Output:
 1.073741824E9
 1.073741824E9
 0.25

JavaScript

function pow(base, exp) {
    if (exp != Math.floor(exp)) 
        throw "exponent must be an integer";
    if (exp < 0) 
        return 1 / pow(base, -exp);
    var ans = 1;
    while (exp > 0) {
        ans *= base;
        exp--;
    }
    return ans;
}

jq

# 0^0 => 1
# NOTE: jq converts very large integers to floats.
# This implementation uses reduce to avoid deep recursion
def power_int(n):
  if n == 0 then 1
  elif . == 0 then 0
  elif n < 0 then 1/power_int(-n)
  elif ((n | floor) == n) then
       ( (n % 2) | if . == 0 then 1 else -1 end ) as $sign
       | if (. == -1) then $sign
         elif . < 0 then (( -(.) | power_int(n) ) * $sign)
         else . as $in | reduce range(1;n) as $i ($in; . * $in)
         end
  else error("This is a toy implementation that requires n be integral")
  end ;
Demonstration:
def demo(x;y):
  x | [ power_int(y), (log*y|exp) ] ;

demo(2; 3),
demo(2; 64),
demo(1.1; 1024),
demo(1.1; -1024)

# Output:
[8,                      7.999999999999998]
[18446744073709552000,   18446744073709525000]
[2.4328178969536854e+42, 2.4328178969536693e+42]
[4.1104597317052596e-43, 4.1104597317052874e-43]

Julia

function pow(base::Number, exp::Integer)
  r = one(base)
  for i = 1:exp
    r *= base
  end
  return r
end
Output:
julia> println("5 ^ 3 ^ 2 = ", 5 ^ 3 ^ 2)
5 ^ 3 ^ 2 = 1953125

julia> println("(5 ^ 3) ^ 2 = ", (5 ^ 3) ^ 2)
(5 ^ 3) ^ 2 = 15625

julia> println("5 ^ (3 ^ 2) = ", 5 ^ (3 ^ 2))
5 ^ (3 ^ 2) = 1953125

Kotlin

Kotlin does not have a dedicated exponentiation operator (we would normally use Java's Math.pow method instead) but it's possible to implement integer and floating power exponentiation (with integer exponents) using infix extension functions which look like non-symbolic operators for these actions:

// version 1.0.6

infix fun Int.ipow(exp: Int): Int = 
    when {
        this ==  1 -> 1
        this == -1 -> if (exp and 1 == 0) 1 else -1 
        exp <  0   -> throw IllegalArgumentException("invalid exponent")
        exp == 0   -> 1
        else       -> {
            var ans = 1
            var base = this
            var e = exp
            while (e > 1) {
                if (e and 1 == 1) ans *= base
                e = e shr 1
                base *= base
            }
            ans * base
        }
    }

infix fun Double.dpow(exp: Int): Double {
    var ans = 1.0
    var e   = exp 
    var base = if (e < 0) 1.0 / this else this
    if (e < 0) e = -e
    while (e > 0) {
        if (e and 1 == 1) ans *= base
        e = e shr 1
        base *= base
    }
    return ans
}

fun main(args: Array<String>) {
    println("2  ^ 3   = ${2 ipow 3}")
    println("1  ^ -10 = ${1 ipow -10}")
    println("-1 ^ -3  = ${-1 ipow -3}")
    println()
    println("2.0 ^ -3 = ${2.0 dpow -3}")
    println("1.5 ^ 0  = ${1.5 dpow 0}")
    println("4.5 ^ 2  = ${4.5 dpow 2}")
}
Output:
2  ^ 3   = 8
1  ^ -10 = 1
-1 ^ -3  = -1

2.0 ^ -3 = 0.125
1.5 ^ 0  = 1.0
4.5 ^ 2  = 20.25

Lambdatalk

Following the example given in Scheme

{def ^
 {def *^
  {lambda {:base :exponent :acc}
   {if {= :exponent 0}
    then :acc
    else {*^ :base {- :exponent 1} {* :acc :base}}}}}
 {lambda {:base :exponent}
  {*^ :base :exponent 1}}}
-> ^

{^ 2 3}
-> 8
{^ {/ 1 2} 3}
-> 0.125       // No rational type as primitives
{^ 0.5 3}
-> 0.125

Liberty BASIC

  print " 11^5     = ", floatPow(  11,       5  )
  print " (-11)^5  = ", floatPow( -11,       5  )
  print " 11^( -5) = ", floatPow(  11,      -5  )
  print " 3.1416^3 = ", floatPow(   3.1416,  3  )
  print " 0^2      = ", floatPow(   0,       2  )
  print "  2^0     = ", floatPow(   2,       0  )
  print " -2^0     = ", floatPow(  -2,       0  )

  end

  function floatPow( a, b)
      if a <>0 then
          m =1
          if b =abs( b) then
              for n =1 to b
                  m =m *a
              next n
          else
              m =1 /floatPow( a, 0 - b)  ' LB has no unitary minus operator.
          end if
      else
          m =0
      end if
      floatPow =m
  end function

Lingo

Lingo doesn't support user-defined operators.

-- As for built-in power() function: 
-- base can be either integer or float; returns float.
on pow (base, exp)
  if exp=0 then return 1.0
  else if exp<0 then
    exp = -exp
    base = 1.0/base
  end if
  res = float(base)
  repeat with i = 2 to exp
    res = res*base
  end repeat
  return res
end

to int_power :n :m
  if equal? 0 :m [output 1]
  if equal? 0 modulo :m 2 [output int_power :n*:n :m/2]
  output :n * int_power :n :m-1
end

Lua

All numbers in Lua are floating point numbers (thus, there are no real integers). Operator overloading is supported for tables only.

number = {}

function number.pow( a, b )
    local ret = 1
    if b >= 0 then
        for i = 1, b do
            ret = ret * a.val
        end
    else
        for i = b, -1 do
            ret = ret / a.val
        end
    end    
    return ret
end

function number.New( v )
    local num = { val = v }
    local mt = { __pow = number.pow }
    setmetatable( num, mt )
    return num
end
             
x = number.New( 5 )    
print( x^2 )                   --> 25
print( number.pow( x, -4 ) )   --> 0.016

Lucid

Some misconceptions about Lucid

pow(n,x)
   k = n fby k div 2;
   p = x fby p*p;
   y =1 fby if even(k) then y else y*p;
   result y asa k eq 0;
end

M2000 Interpreter

Module Exponentiation {
	\\ a variable can be any type except  a string (no $ in name)
	\\ variable b is long type.
	\\ by default we pass by value arguments to a function
	\\ to pass by reference we have to use & before name, 
	\\ in the signature and in the call
	function pow(a, b as long) {
		p=a-a  ' make p same type as a
		p++
		if b>0 then for i=1& to b {p*=a}
		=p
	}
	const fst$="{0::-32} {1}"
	Document exp$
	k= pow(11&, 5)
	exp$=format$(fst$, k, type$(k)="Long")+{
	}
	l=pow(11, 5)
	exp$=format$(fst$, l, type$(l)="Double")+{
	}
	m=pow(pi, 3)
	exp$=format$(fst$, m, type$(m)="Decimal")+{
	}
	\\ send to clipboard
	clipboard exp$
	\\ send  monospaced type text to console using cr char to change lines
	Print #-2, exp$ 
	Rem Report exp$  ' send to console using proportional spacing and justification  
}
Exponentiation
Output:
                          161051 True
                          161051 True
  31.006276680299820175476315064 True

M4

M4 lacks floating point computation and operator definition.

define(`power',`ifelse($2,0,1,`eval($1*$0($1,decr($2)))')')
power(2,10)
Output:
1024

Mathematica / Wolfram Language

Define a function and an infix operator \[CirclePlus] with the same definition:

exponentiation[x_,y_Integer]:=Which[y>0,Times@@ConstantArray[x,y],y==0,1,y<0,1/exponentiation[x,-y]]
CirclePlus[x_,y_Integer]:=exponentiation[x,y]

Examples:

exponentiation[1.23,3]
exponentiation[4,0]
exponentiation[2.5,-2]
1.23\[CirclePlus]3
4\[CirclePlus]0
2.5\[CirclePlus]-2

gives back:

1.86087
1
0.16
1.86087
1
0.16

Note that \[CirclePlus] shows up as a special character in Mathematica namely a circle divided in 4 pieces. Note also that this function supports negative and positive exponents.

Maxima

"^^^"(a, n) := block(
   [p: 1],
   while n > 0 do (
      if oddp(n) then p: p * a,
      a: a * a,
      n: quotient(n, 2)
   ),
   p
)$

infix("^^^")$

2 ^^^ 10;
1024

2.5 ^^^ 10;
9536.7431640625

MiniScript

Translation of: Wren

MiniScript's built-in exponentiation operator is '^' which works for both integer and fractional bases and exponents. The language only has one number type whose underlying representation is a 64-bit float.

import "qa"

number.isInteger = function
  return self == floor(self)
end function

ipow = function(base, exp)
  if not base.isInteger then qa.abort("ipow must have an integer base")
  if not exp.isInteger  then qa.abort("ipow must have an integer exponent")
  if base == 1 or exp == 0 then return 1
  if base == -1 then
    if exp%2 == 0 then return 1
    return -1
  end if
  if exp < 0 then qa.abort("ipow cannot have a negative exponent")
  ans = 1
  e = exp
  while e > 1
    if e%2 == 1 then ans *= base
    e = floor(e/2)
    base *= base
  end while
  return ans * base
end function

fpow = function(base, exp)
  if not exp.isInteger  then qa.abort("fpow must have an integer exponent")
  ans = 1.0
  e = exp
  if e < 0 then
    base = 1 / base
    e = -e
  end if
  while e > 0
    if e%2 == 1 then ans *= base
    e = floor(e/2)
    base *= base
  end while
  return ans
end function

print "Using the reimplemented functions:"
print "  2  ^  3   = " + ipow(2, 3)
print "  1  ^ -10  = " + ipow(1, -10)
print " -1  ^ -3   = " + ipow(-1, -3)
print
print "  2.0 ^ -3  = " + fpow(2.0, -3)
print "  1.5 ^  0  = " + fpow(1.5, 0)
print "  4.5 ^  2  = " + fpow(4.5, 2)
print
print "Using the ^ operator:"
print "  2  ^  3   = " + 2 ^ 3
print "  1  ^ -10  = " + 1 ^ (-10)
print " -1  ^ -3   = " + (-1) ^ (-3)
print
print "  2.0 ^ -3  = " + 2.0 ^ (-3)
print "  1.5 ^  0  = " + 1.5 ^ 0
print "  4.5 ^  2  = " + 4.5 ^ 2
Output:
Using the reimplemented functions:
  2  ^  3   = 8
  1  ^ -10  = 1
 -1  ^ -3   = -1

  2.0 ^ -3  = 0.125
  1.5 ^  0  = 1
  4.5 ^  2  = 20.25

Using the ^ operator:
  2  ^  3   = 8
  1  ^ -10  = 1
 -1  ^ -3   = -1

  2.0 ^ -3  = 0.125
  1.5 ^  0  = 1
  4.5 ^  2  = 20.25

МК-61/52

С/П	x^y	С/П

Modula-2

Whilst some implementations or dialects of Modula-2 may permit definition or overloading of operators, neither is permitted in N.Wirth's classic language definition and the ISO Modula-2 standard. The operations are therefore given as library functions.

(* Library Interface *)
DEFINITION MODULE Exponentiation;

PROCEDURE IntExp(base, exp : INTEGER) : INTEGER;
 (* Raises base to the power of exp and returns the result
    both base and exp must be of type INTEGER *)

PROCEDURE RealExp(base : REAL; exp : INTEGER) : REAL;
 (* Raises base to the power of exp and returns the result
    base must be of type REAL, exp of type INTEGER *)

END Exponentiation.

(* Library Implementation *)
IMPLEMENTATION MODULE Exponentiation;

PROCEDURE IntExp(base, exp : INTEGER) : INTEGER;
  VAR
    i, res : INTEGER;
  BEGIN
    res := 1;
    FOR i := 1 TO exp DO
      res := res * base;
    END;
    RETURN res;
  END IntExp;

PROCEDURE RealExp(base: REAL; exp: INTEGER) : REAL;
  VAR
    i : INTEGER;
    res : REAL;
  BEGIN
    res := 1.0;
    IF exp < 0 THEN
      FOR i := exp TO -1 DO
        res := res / base;
      END;
    ELSE (* exp >= 0 *)
      FOR i := 1 TO exp DO
        res := res * base;
      END;
    END;
    RETURN res;
  END RealExp;

END Exponentiation.

Modula-3

MODULE Expt EXPORTS Main;

IMPORT IO, Fmt;

PROCEDURE IntExpt(arg, exp: INTEGER): INTEGER =
  VAR result := 1;
  BEGIN
    FOR i := 1 TO exp DO
      result := result * arg;
    END;
    RETURN result;
  END IntExpt;

PROCEDURE RealExpt(arg: REAL; exp: INTEGER): REAL =
  VAR result := 1.0;
  BEGIN
    IF exp < 0 THEN
      FOR i := exp TO -1 DO
        result := result / arg;
      END;
    ELSE
      FOR i := 1 TO exp DO
        result := result * arg;
      END;
    END;
    RETURN result;
  END RealExpt;

BEGIN
  IO.Put("2 ^ 4 = " & Fmt.Int(IntExpt(2, 4)) & "\n");
  IO.Put("2.5 ^ 4 = " & Fmt.Real(RealExpt(2.5, 4)) & "\n");
END Expt.
Output:
2 ^ 4 = 16
2.5 ^ 4 = 39.0625

Nemerle

Macros can be used to define a new operator:

using System;

macro @^ (val, pow : int)
{
    <[ Math.Pow($val, $pow) ]>
}

The file with the macro needs to be compiled as a library, and the resulting assembly must be referenced when compiling source files which use the operator.

using System;
using System.Console;
using Nemerle.Assertions;

module Expon
{
    Expon(val : int, pow : int) : int            // demonstrates simple/naive method
      requires pow > 0 otherwise throw ArgumentOutOfRangeException("Negative powers not allowed, will not return int.")
    {
        mutable result = 1;
        repeat(pow) {
            result *= val
        }
        result
    }
    
    Expon(val : double, pow : int) : double     // demonstrates shift and square method
    {
        mutable neg = false;
        mutable p = pow;
        when (pow < 0) {neg = true; p = -pow};
        mutable v = val;
        mutable result = 1d;
        
        while (p > 0) {
            when (p & 1 == 1) result *= v;
            v *= v;
            p >>= 1;
        }
        if (neg) 1d/result else result
    }
    
    Main() : void
    {
        def eight = 2^3;
        // def oops = 2^1.5; // compilation error as operator is defined for integer exponentiation
        def four = Expon(2, 2);
        def four_d = Expon(2.0, 2);
        
        WriteLine($"$eight, $four, $four_d");
    }
}

Nim

proc `^`[T: float|int](base: T; exp: int): T =
  var (base, exp) = (base, exp)
  result = 1

  if exp < 0:
    when T is int:
      if base * base != 1: return 0
      elif (exp and 1) == 0: return 1
      else: return base
    else:
      base = 1.0 / base
      exp = -exp

  while exp != 0:
    if (exp and 1) != 0:
      result *= base
    exp = exp shr 1
    base *= base

echo "2^6 = ", 2^6
echo "2^-6 = ", 2 ^ -6
echo "2.71^6 = ", 2.71^6
echo "2.71^-6 = ", 2.71 ^ -6

Objeck

class Exp {
  function : Main(args : String[]) ~ Nil {
    Pow(2,30)->PrintLine();
    Pow(2.0,30)->PrintLine();
    Pow(2.0,-2)->PrintLine();
   }
  
  function : native : Pow(base : Float, exp : Int) ~ Float {
    if(exp < 0) {
      return 1 / base->Power(exp * -1.0);
    };
    
    ans := 1.0;
    while(exp > 0) {
      ans *= base;
      exp -= 1;
    };
    
    return ans;
  }
}
1.07374182e+009
1.07374182e+009
0.25

OCaml

It is possible to create a generic exponential. For this, one must know the multiplication function, and the unit value. Here, the usual fast algorithm is used:

let pow one mul a n =
  let rec g p x = function
  | 0 -> x
  | i ->
      g (mul p p) (if i mod 2 = 1 then mul p x else x) (i/2)
  in
  g a one n
;;

pow 1 ( * ) 2 16;;  (* 65536 *)
pow 1.0 ( *. ) 2.0 16;; (* 65536. *)

(* pow is not limited to exponentiation *)
pow 0 ( + ) 2 16;;  (* 32 *)
pow "" ( ^ ) "abc " 10;;  (* "abc abc abc abc abc abc abc abc abc abc " *)
pow [ ] ( @ ) [ 1; 2 ] 10;;  (* [1; 2; 1; 2; 1; 2; 1; 2; 1; 2; 1; 2; 1; 2; 1; 2; 1; 2; 1; 2] *)

(* Thue-Morse sequence *)
Array.init 32 (fun n -> (1 - pow 1 ( - ) 0 n) lsr 1);;

(* [|0; 1; 1; 0; 1; 0; 0; 1; 1; 0; 0; 1; 0; 1; 1; 0;
     1; 0; 0; 1; 0; 1; 1; 0; 0; 1; 1; 0; 1; 0; 0; 1|]

See http://en.wikipedia.org/wiki/Thue-Morse_sequence
*)

See also Matrix-exponentiation operator#OCaml for a matrix usage.

Oforth

This function works either for int or floats :

: powint(r, n) 
| i | 
   1 n abs loop: i [ r * ]
   n isNegative ifTrue: [ inv ] ;

2 3 powint println
2 powint(3) println
1.2 4 powint println
1.2 powint(4) println
Output:
8
8
2.0736
2.0736

PARI/GP

This version works for integer and floating-point bases (as well as intmod bases, ...).

ex(a, b)={
  my(c = 1);
  while(b > 1,
    if(b % 2, c *= a);
    a = a^2;
    b >>= 1
  );
  a * c
};

PARI/GP also has a built-in operator that works for any type of numerical exponent:

ex2(a, b) = a ^ b;

Pascal

Program ExponentiationOperator(output);

function intexp (base, exponent: integer): longint;
  var
    i: integer;

  begin
    if (exponent < 0) then
      if (base = 1) then
        intexp := 1
      else
        intexp := 0
    else
    begin
      intexp := 1;
      for i := 1 to exponent do
        intexp := intexp * base;
    end;
  end;

function realexp (base: real; exponent: integer): real;
  var
    i: integer;

  begin
    realexp := 1.0;
    if (exponent < 0) then
      for i := exponent to -1 do
        realexp := realexp / base
    else 
      for i := 1 to exponent do
        realexp := realexp * base;
  end;
  
begin
  writeln('2^30: ', intexp(2, 30));
  writeln('2.0^30: ', realexp(2.0, 30));
end.
Output:
% ./ExponentiationOperator
2^30: 1073741824
2.0^30:  1.07374182400000E+009

With overload

Pascal functions can be overloaded. This means that the two functions can have the same name and the particular function executed will depend on the data types of the arguments.

Program ExponentiationOperator(output);

function newpower (base, exponent: integer): longint;
  var
    i: integer;

  begin
    if (exponent < 0) then
      if (base = 1) then
        newpower := 1
      else
        newpower := 0
    else
    begin
      newpower := 1;
      for i := 1 to exponent do
        newpower := newpower * base;
    end;
  end;

function newpower (base: real; exponent: integer): real;
  var
    i: integer;

  begin
    newpower := 1.0;
    if (exponent < 0) then
      for i := exponent to -1 do
        newpower := newpower / base
    else
      for i := 1 to exponent do
        newpower := newpower * base;
  end;

begin
  writeln('2^30: ', newpower(2, 30));
  writeln('2.0^30: ', newpower(2.0, 30));
  readln;
end.

Output is as before.

Perl

#!/usr/bin/perl -w 
use strict ;

sub expon {
   my ( $base , $expo ) = @_ ;
   if ( $expo == 0 ) {
      return 1 ;
   }
   elsif ( $expo == 1 ) {
      return $base ;
   }
   elsif ( $expo > 1 ) {
      my $prod = 1 ;
      foreach my $n ( 0..($expo - 1) ) {
	 $prod *= $base ;
      }
      return $prod ;
   }
   elsif ( $expo < 0 ) {
      return 1 / ( expon ( $base , -$expo ) ) ;
   }
}
print "3 to the power of 10 as a function is " . expon( 3 , 10 ) . " !\n" ;
print "3 to the power of 10 as a builtin is " . 3**10 . " !\n" ;
print "5.5 to the power of -3 as a function is " . expon( 5.5 , -3 ) . " !\n" ;
print "5.5 to the power of -3 as a builtin is " . 5.5**-3 . " !\n" ;
Output:
3 to the power of 10 as a function is 59049 !
3 to the power of 10 as a builtin is 59049 !
5.5 to the power of -3 as a function is 0.00601051840721262 !
5.5 to the power of -3 as a builtin is 0.00601051840721262 !

The following version is simpler and much faster for large exponents, since it uses exponentiation by squaring.

sub ex {
  my($base,$exp) = @_;
  die "Exponent '$exp' must be an integer!" if $exp != int($exp);
  return 1 if $exp == 0;
  ($base, $exp) = (1/$base, -$exp)  if $exp < 0;
  my $c = 1;
  while ($exp > 1) {
    $c *= $base if $exp % 2;
    $base *= $base;
    $exp >>= 1;
  }
  $base * $c;
}

Phix

Library: Phix/basics

The builtin power function handles atoms and integers for both arguments, whereas this deliberately restricts the exponent to an integer.
There is no operator overloading in Phix, or for that matter any builtin overriding.

with javascript_semantics
function powir(atom b, integer i)
    atom res = 1
    if i<0 then {b,i} = {1/b,abs(i)} end if
    while i do
        if and_bits(i,1) then res *= b end if
        b *= b
        i = floor(i/2)
    end while
    return res
end function
?powir(-3,-5)
?power(-3,-5)
Output:
-0.004115226337
-0.004115226337

PicoLisp

This uses Knuth's algorithm (The Art of Computer Programming, Vol. 2, page 442)

(de ** (X N)  # N th power of X
   (if (ge0 N)
      (let Y 1
         (loop
            (when (bit? 1 N)
               (setq Y (* Y X)) )
            (T (=0 (setq N (>> 1 N)))
               Y )
            (setq X (* X X)) ) )
      0 ) )

PL/I

declare exp generic
  (iexp when (fixed, fixed),
   fexp when (float, fixed) );
iexp: procedure (m, n) returns (fixed binary (31));
   declare (m, n) fixed binary (31) nonassignable;
   declare exp fixed binary (31) initial (m), i fixed binary;
   if m = 0 & n = 0 then signal error;
   if n = 0 then return (1);
   do i = 2 to n;
      exp = exp * m;
   end;
   return (exp);
end iexp;
fexp: procedure (a, n) returns (float (15));
   declare (a float, n fixed binary (31)) nonassignable;
   declare exp float initial (a), i fixed binary;
   if a = 0 & n = 0 then signal error;
   if n = 0 then return (1);
   do i = 2 to n;
      exp = exp * a;
   end;
   return (exp);
end fexp;

PowerShell

function pow($a, [int]$b) {
    if ($b -eq -1) { return 1/$a }
    if ($b -eq 0)  { return 1 }
    if ($b -eq 1)  { return $a }
    if ($b -lt 0) {
        $rec = $true # reciprocal needed
        $b = -$b
    }

    $result = $a
    2..$b | ForEach-Object {
        $result *= $a
    }

    if ($rec) {
        return 1/$result
    } else {
        return $result
    }
}

The function works for both integers and floating-point values as first argument.

PowerShell does not support operator overloading directly (and there wouldn't be an exponentiation operator to overload).

Output:
PS> pow 2 15
32768
PS> pow 2.71 -4
0,018540559532257
PS> pow (-1.35) 3
−2,460375

The negative first argument needs to be put in parentheses because it would otherwise be passed as string. This can be circumvented by declaring the first argument to the function as double, but then the return type would be always double while currently pow 2 3 returns an int.

Prolog

Works with: SWI-Prolog version 6

Declaring an Operator as an Arithmetic Function

In Prolog, we define predicates rather than functions. Still, functions and predicates are related: going one way, we can think of an n-place predicate as a function from its arguments to a member of the set {true, false}; going the other way, we can think of functions as predicates with a hidden ultimate argument, called a "return value". Following the latter approach, Prolog sometimes uses macro expansion to provide functional syntax by

1. catching terms fitting a certain pattern (viz. Base ^^ Exp, which is the same as '^^'(N, 3)),

2. calling the term with an extra argument (viz. call('^^'(Base, Exp), Power)),

3. replacing the occurrence of the term with the value instantiated in the extra argument (viz. Power).

The predicate is/2 supports functional syntax in its second argument: e.g., X is sqrt(2) + 1. New arithmetic functions can be added with the `arithmetic_function/1` directive, wherein the arity attributed to the function is one less than the arity of the predicate which will be called during term expansion and evaluation. The following directives establish ^^/2 as, first, an arithmetic function, and then as a right-associative binary operator (so that X is 2^^2^^2 == X = 2^(2^2)):

:- arithmetic_function((^^)/2).
:- op(200, xfy, user:(^^)).

When ^^/2 occurs in an expression in the second argument of is/2, Prolog calls the subsequently defined predicate ^^/3, and obtains the operators replacement value from the predicate's third argument.

Higher-order Predicate:

This solution employs the higher-order predicate foldl/4 from the standard SWI-Prolog library(apply), in conjunction with an auxiliary "folding predicate" (note, the definition uses the ^^ operator as an arithmetic function):

%% ^^/3
%
%   True if Power is Base ^ Exp.

^^(Base, Exp, Power) :-
    ( Exp < 0   ->  Power is 1 / (Base ^^ (Exp * -1))            % If exponent is negative, then ...

    ; Exp > 0   ->  length(Powers, Exp),                         % If exponent is positive, then
                    foldl( exp_folder(Base), Powers, 1, Power )  %    Powers is a list of free variables with length Exp
                                                                 %    and Power is Powers folded with exp_folder/4
             
    ; Power = 1                                                  % otherwise Exp must be 0, so
    ).

%% exp_folder/4
%
%       True when Power is the product of Base and Powers.
%       
%       This predicate is designed to work with foldl and a list of free variables.
%       It passes the result of each evaluation to the next application through its
%       fourth argument, instantiating the elements of Powers to each successive Power of the Base.

exp_folder(Base, Power, Powers, Power) :-
    Power is Base * Powers.

Example usage:

?- X is 2 ^^ 3.
X = 8.

?- X is 2 ^^ -3.
X = 0.125.

?- X is 2.5 ^^ -3.
X = 0.064.

?- X is 2.5 ^^ 3.
X = 15.625.

Recursive Predicate

An implementation of exponentiation using recursion and no control predicates.

exp_recursive(Base, NegExp, NegPower) :-
    NegExp < 0,
    Exp is NegExp * -1,
    exp_recursive_(Base, Exp, Base, Power),
    NegPower is 1 / Power.
exp_recursive(Base, Exp, Power) :-
    Exp > 0,
    exp_recursive_(Base, Exp, Base, Power).
exp_recursive(_, 0, 1).

exp_recursive_(_,    1,   Power, Power).
exp_recursive_(Base, Exp, Acc,   Power)   :-
    Exp > 1,
    NewAcc is Base * Acc,
    NewExp is Exp  - 1,
    exp_recursive_(Base, NewExp, NewAcc, Power).

PureBasic

PureBasic does not allow an operator to be redefined or operator overloading.

Procedure powI(base, exponent)
  Protected i, result.d
  If exponent < 0
    If base = 1
      result = 1
    EndIf
    ProcedureReturn result
  EndIf
  result = 1
  For i = 1 To exponent
    result * base
  Next
  ProcedureReturn result
EndProcedure
        
Procedure.f powF(base.f, exponent)
  Protected i, magExponent = Abs(exponent), result.d
  If base <> 0
    result = 1.0
    If exponent <> 0 
      For i = 1 To magExponent
        result * base
      Next
      If exponent < 0 
        result = 1.0 / result
      EndIf
    EndIf 
  EndIf
  ProcedureReturn result
EndProcedure

If OpenConsole()
  Define x, a.f, exp
  
  x = Random(10) - 5
  a = Random(10000) / 10000 * 10
  For exp = -3 To 3
    PrintN(Str(x) + " ^ " + Str(exp) + " = " + Str(powI(x, exp)))
    PrintN(StrF(a) + " ^ " + Str(exp) + " = " + StrF(powF(a, exp)))
    PrintN("--------------")
  Next 
 
  Print(#CRLF$ + #CRLF$ + "Press ENTER to exit")
  Input()
  CloseConsole()
EndIf
Output:
-3 ^ -3 = 0
6.997000 ^ -3 = 0.002919
--------------
-3 ^ -2 = 0
6.997000 ^ -2 = 0.020426
--------------
-3 ^ -1 = 0
6.997000 ^ -1 = 0.142918
--------------
-3 ^ 0 = 1
6.997000 ^ 0 = 1.000000
--------------
-3 ^ 1 = -3
6.997000 ^ 1 = 6.997000
--------------
-3 ^ 2 = 9
6.997000 ^ 2 = 48.958012
--------------
-3 ^ 3 = -27
6.997000 ^ 3 = 342.559235
-------------

Python

MULTIPLY = lambda x, y: x*y

class num(float):
    # the following method has complexity O(b)
    # rather than O(log b) via the rapid exponentiation
    def __pow__(self, b):
        return reduce(MULTIPLY, [self]*b, 1)

# works with ints as function or operator
print num(2).__pow__(3)
print num(2) ** 3

# works with floats as function or operator
print num(2.3).__pow__(8)
print num(2.3) ** 8

Quackery

Quackery does not have Float, but does have a library of Bignum Rationals.

  [ $ "bigrat.qky" loadfile ] now!
  
  forward                         is **    (   n n --> n   )
  
  [ dup 1 < iff
     [ 2drop 1 ] done
    dup 1 & iff
        [ 1 - dip dup ** * ] 
    else
      [ 1 >> dip [ dup * ] 
        ** ] ]              resolves **    (   n n --> n   )

  forward                         is (v**) ( n/d n --> n/d )

  [ dup 0 = iff
      [ drop 2drop 1 n->v ]
      done
    dup 1 & iff
      [ 1 - dip 2dup (v**)
        v* ]
    else
      [ 1 >> 
        dip [ 2dup v* ] 
        (v**) ] ]           resolves (v**) ( n/d n --> n/d )
    
  [ dup 0 < iff
      [ abs (v**) 1/v ]
    else (v**) ]                  is v**   ( n/d n --> n/d )
    
say "The 10th power of 2 is: "
2 10 ** echo cr cr
 
say "The -10th power of 2.5 is: " 
$ "2.5" $->v drop -10 v** 20 point$ echo$
Output:
The 10th power of 2 is: 1024

The -10th power of 2.5 is: 0.0001048576

R

# Method
pow <- function(x, y) 
{
   x <- as.numeric(x)
   y <- as.integer(y)   
   prod(rep(x, y))
}
#Operator
"%pow%" <- function(x,y) pow(x,y)

pow(3, 4)    # 81
2.5 %pow% 2  # 6.25

Racket

#lang racket
(define (^ base expt)
  (for/fold ((acum 1))
    ((i (in-range expt)))
    (* acum base)))

(^ 5 2) ; 25
(^ 5.0 2) ; 25.0

Raku

(formerly Perl 6)

Works with: Rakudo version 2023.09
proto pow (Real, Int --> Real) {*}
multi pow (0,     0)         { fail '0**0 is undefined' }
multi pow ($base, UInt $exp) { [*] $base xx $exp }
multi pow ($base, $exp)  { 1 / samewith $base, -$exp }

multi infix:<**> (Real $a, Int $b) { pow $a, $b }

# Testing

say pow .75, -5;
say .75 ** -5;

Retro

Retro has no floating point support in the standard VM.

From the math' vocabulary:

: pow  ( bp-n ) 1 swap [ over * ] times nip ;

And in use:

2 5 ^math'pow

The fast exponentiation algorithm can be coded as follows:

: pow ( n m -- n^m )
1 2rot
[ dup 1 and 0 <>
  [ [ tuck * swap ] dip ] ifTrue
  [ dup * ] dip 1 >> dup 0 <>
] while
drop drop ;

REXX

version 1 with error checking

The   iPow   function doesn't care what kind of number is to be raised to a power,
it can be an integer or floating point number.

Extra error checking was added to verify that the invocation is syntactically correct.

/*REXX program  computes and displays  various   (integer)   exponentiations.           */
                                                 say center('digits='digits(), 79, "─")
say 'iPow(17, 65)  is:'
say  iPow(17, 65)
say

say 'iPow(0, -3)  is:'
say  iPow(0, -3)
say

say 'iPow(8, 0)  is:'
say  iPow(8, 0)
say

numeric digits 12;                               say center('digits='digits(), 79, "─")
say 'iPow(2, -10)  is:'
say  iPow(2, -10)
say

numeric digits 30;                               say center('digits='digits(), 79, "─")
say 'iPow(-3.1415926535897932384626433, 3)  is:'
say  iPow(-3.1415926535897932384626433, 3)
say

numeric digits 60;                               say center('digits='digits(), 79, "─")
say 'iPow(5, 70)  is:'
say  iPow(5, 70)
say

numeric digits 100;                              say center('digits='digits(), 79, "─")
say 'iPow(17, 65)  is:'
say  iPow(17, 65)
say

numeric digits 1000;                             say center('digits='digits(), 79, "─")
say 'iPow(2, 1000)  is:'
say  iPow(2, 1000)
exit                                             /*stick a fork in it,  we're all done. */
/*──────────────────────────────────────────────────────────────────────────────────────*/
errMsg: say;     say '***error***';     say;     say arg(1);     say;     say;     exit 13
/*──────────────────────────────────────────────────────────────────────────────────────*/
iPow:   procedure;  parse arg x 1 _,p;           #args= arg()  /*_:   is a copy of  X.  */
        if #args<2            then call errMsg  "not enough arguments specified"
        if #args>2            then call errMsg  "too many arguments specified"
        if \datatype(x, 'N')  then call errMsg  "1st arg isn't numeric:"         x
        if \datatype(p, 'W')  then call errMsg  "2nd arg isn't an integer:"      p
        if p=0                then return 1                    /*handle powers of zero. */
        if x=0  |  x=1        then return x                    /*handle special cases.  */
               do abs(p) - 1;      _= _ * x;   end             /*perform exponentiation */
        if p<0                then _= 1 / _                    /*process its reciprocal.*/
        return _
output   when using the internal default inputs:
───────────────────────────────────digits=9────────────────────────────────────
iPow(17, 65)  is:
9.53190906E+79

iPow(0, -3)  is:
0

iPow(8, 0)  is:
1

───────────────────────────────────digits=12───────────────────────────────────
iPow(2, -10)  is:
0.0009765625

───────────────────────────────────digits=30───────────────────────────────────
iPow(-3.1415926535897932384626433, 3)  is:
-31.0062766802998201754763126013

───────────────────────────────────digits=60───────────────────────────────────
iPow(5, 70)  is:
8470329472543003390683225006796419620513916015625

──────────────────────────────────digits=100───────────────────────────────────
iPow(17, 65)  is:
95319090450218007303742536355848761234066170796000792973413605849481890760893457

──────────────────────────────────digits=1000──────────────────────────────────
iPow(2, 1000)  is:
107150860718626732094842504906000181056140481170553360744375038837035105112493612249319837881569585812759467291755314682
518714528569231404359845775746985748039345677748242309854210746050623711418779541821530464749835819412673987675591655439
46077062914571196477686542167660429831652624386837205668069376

version 2

An alternative to ipow that is about 30% faster (for 5**70) would be.

However, for single digit powers, version 2 is around 300% slower than version 1.

pp: Procedure
Parse Arg x,y
If x=0 & y<0 Then call errMsg x"**" y "is invalid"
yp=abs(y)
p.1=x
x.1=1
i=1
Do k=2 By 1 While i<=yp%2
  i=2*i
  kk=k-1
  p.k=p.kk*p.kk
  x.k=i
  /* Say k i x.k p.k */
  End
pp=1
Do i=k-1 To 1 By -1
  If x.i<=yp Then Do
    pp=pp*p.i
    yp=yp-x.i
    End
  End
If y<0 Then
  pp=1/pp
Return pp

Ring

see "11^5 = " + ipow(11, 5) + nl
see "pi^3 = " + fpow(3.14, 3) + nl

func ipow a, b
     p2 = 1
     for i = 1 to 32
         p2 *= p2
         if b < 0  p2 *= a ok
         b = b << 1
     next
     return p2
 
func fpow a, b
     p = 1
     for i = 1 to 32
         p *= p
         if b < 0  p *= a ok
         b = b << 1
     next
     return p

Output :

11^5 = 161051
pi^3 = 30.96

RPL

RPL cannot overload operators, but new functions can be added, making no difference in usage from operators because of the postfix syntax. RPL advocates that functions and operators should be able to handle many types of data - including unsigned integers and floating point numbers - with the same methods, making the code compact and versatile and making it easier to remember commands. The one-line program below can exponentiate real and complex numbers, but also matrices.

IF DUP NOT THEN DROP DUP TYPE 3 == SWAP IDN 1 IFTE ELSE 1 1 ROT START OVER * NEXT SWAP DROP END ≫ ‘POWER’ STO
25.2 3 POWER
#25d 3 POWER
-25 3 POWER
(2,5) 3 POWER
[[ 1 2 ][ 3 4 ]] 3 POWER
Output:
5: 16003.008
4: # 15625d
3: -15625
2: (-142,-65)
1: [[ 37 54 ][ 81 118 ]]

Ruby

We add a pow method to Numeric objects. To calculate 5.pow 3, this method fills an array [5, 5, 5] and then multiplies together the elements.

class Numeric
  def pow(m)
    raise TypeError, "exponent must be an integer: #{m}" unless m.is_a? Integer
    puts "pow!!"
    Array.new(m, self).reduce(1, :*)
  end
end

p 5.pow(3)
p 5.5.pow(3)
p 5.pow(3.1)
Output:
pow!!
125
pow!!
166.375
pow.rb:3:in `pow': exponent must be an integer: 3.1 (TypeError)
        from pow.rb:16:in `<main>'

To overload the ** exponentiation operator, this might work, but doesn't:

class Numeric
  def **(m)
    pow(m)
  end
end

It doesn't work because the ** method is defined independently for Numeric subclasses Fixnum, Bignum and Float. One must:

class Fixnum
  def **(m)
    print "Fixnum "
    pow(m)
  end
end
class Bignum
  def **(m)
    print "Bignum "
    pow(m)
  end
end
class Float
  def **(m)
    print "Float "
    pow(m)
  end
end

p i=2**64
p i ** 2
p 2.2 ** 3
Output:
Fixnum pow!!
18446744073709551616
Bignum pow!!
340282366920938463463374607431768211456
Float pow!!
10.648

Run BASIC

print " 11^5     = ";11^5
print " (-11)^5  = ";-11^5
print " 11^( -5) = ";11^-5
print " 3.1416^3 = ";3.1416^3
print " 0^2      = ";0^2
print "  2^0     = ";2^0
print " -2^0     = ";-2^0
Output:
 11^5     = 161051
 (-11)^5  = -161051
 11^( -5) = 6.20921325e-6
 3.1416^3 = 31.0064942
 0^2      = 0
  2^0     = 1
 -2^0     = 1

Rust

The num crate is the de-facto Rust library for numerical generics and it provides the One trait which allows for an exponentiation function that is generic over both integral and floating point types. The library provides this generic exponentiation function, the implementation of which is the pow function below.

extern crate num;
use num::traits::One;
use std::ops::Mul;

fn pow<T>(mut base: T, mut exp: usize) -> T 
    where T: Clone + One + Mul<T, Output=T>
{
    if exp == 0 { return T::one() }
    while exp & 1 == 0 {
        base = base.clone() * base;
        exp >>= 1;
    }
    if exp == 1 { return base }
    let mut acc = base.clone();

    while exp > 1 {
        exp >>= 1;
        base = base.clone() * base;
        if exp & 1 == 1 {
            acc = acc * base.clone();
        }
    }
    acc
}

Scala

This example is in need of improvement.
Works with: Scala version 2.8

There's no distinction between an operator and a method in Scala. Alas, there is no way of adding methods to a class, but one can make it look like a method has been added, through a method commonly known as Pimp My Library. Therefore, we show below how that can beaccomplished. We define the operator ↑ (unicode's uparrow), which is written as \u2191 below, to make cut & paste easier.

To use it, one has to import the implicit from the appropriate object. ExponentI will work for any integral type (Int, BigInt, etc), ExponentF will work for any fractional type (Double, BigDecimal, etc). Importing both at the same time won't work. In this case, it might be better to define implicits for the actual types being used, such as was done in Exponents.

object Exponentiation {
  import scala.annotation.tailrec
  
  @tailrec def powI[N](n: N, exponent: Int)(implicit num: Integral[N]): N = {
    import num._
    exponent match {
      case 0 => one
      case _ if exponent % 2 == 0 => powI((n * n), (exponent / 2))
      case _ => powI(n, (exponent - 1)) * n
    }
  }
  
  @tailrec def powF[N](n: N, exponent: Int)(implicit num: Fractional[N]): N = {
    import num._
    exponent match {
      case 0 => one
      case _ if exponent < 0 => one / powF(n, exponent.abs)
      case _ if exponent % 2 == 0 => powF((n * n), (exponent / 2))
      case _ => powF(n, (exponent - 1)) * n
    }
  }
  
  class ExponentI[N : Integral](n: N) {
    def \u2191(exponent: Int): N = powI(n, exponent)
  }

  class ExponentF[N : Fractional](n: N) {
    def \u2191(exponent: Int): N = powF(n, exponent)
  }

  object ExponentI {
    implicit def toExponentI[N : Integral](n: N): ExponentI[N] = new ExponentI(n)
  }
  
  object ExponentF {
    implicit def toExponentF[N : Fractional](n: N): ExponentF[N] = new ExponentF(n)
  }
  
  object Exponents {
    implicit def toExponent(n: Int): ExponentI[Int] = new ExponentI(n)
    implicit def toExponent(n: Double): ExponentF[Double] = new ExponentF(n)
  }
}
Functions powI and powF above are not tail recursive, since the result of the recursive call is multiplied by n. A tail recursive version of powI would be:
  @tailrec def powI[N](n: N, exponent: Int, acc:Int=1)(implicit num: Integral[N]): N = {
    exponent match {
      case 0 => acc
      case _ if exponent % 2 == 0 => powI(n * n, exponent / 2, acc)
      case _ => powI(n, (exponent - 1), acc*n)
    }
  }

Scheme

This definition of the exponentiation procedure ^ operates on bases of all numerical types that the multiplication procedure * operates on, i. e. integer, rational, real, and complex. The notion of an operator does not exist in Scheme. Application of a procedure to its arguments is always expressed with a prefix notation.

(define (^ base exponent)
  (define (*^ exponent acc)
    (if (= exponent 0)
        acc
        (*^ (- exponent 1) (* acc base))))
  (*^ exponent 1))

(display (^ 2 3))
(newline)
(display (^ (/ 1 2) 3))
(newline)
(display (^ 0.5 3))
(newline)
(display (^ 2+i 3))
(newline)
Output:
 8
 1/8
 0.125
 2+11i

Seed7

In Seed7 the ** operator is overloaded for both integerinteger and floatinteger (additionally there is a ** operator for floatfloat). The following re-implementation of both functions does not use another exponentiation function to do the computation. Instead the exponentiation-by-squaring algorithm is used.

const func integer: intPow (in var integer: base, in var integer: exponent) is func
  result
    var integer: result is 0;
  begin
    if exponent < 0 then
      raise(NUMERIC_ERROR);
    else
      if odd(exponent) then
        result := base;
      else
        result := 1;
      end if;
      exponent := exponent div 2;
      while exponent <> 0 do
        base *:= base;
        if odd(exponent) then
          result *:= base;
        end if;
        exponent := exponent div 2;
      end while;
    end if;
  end func;

Original source: [1]

const func float: fltIPow (in var float: base, in var integer: exponent) is func
  result
    var float: power is 1.0;
  local
    var integer: stop is 0;
  begin
    if base = 0.0 then
      if exponent < 0 then
        power := Infinity;
      elsif exponent > 0 then
        power := 0.0;
      end if;
    else
      if exponent < 0 then
        stop := -1;
      end if;
      if odd(exponent) then
        power := base;
      end if;
      exponent >>:= 1;
      while exponent <> stop do
        base *:= base;
        if odd(exponent) then
          power *:= base;
        end if;
        exponent >>:= 1;
      end while;
      if stop = -1 then
        power := 1.0 / power;
      end if;
    end if;
  end func;

Original source: [2]

Since Seed7 supports operator and function overloading a new exponentiation operator like ^* can be defined for integer and float bases:

$ syntax expr: .(). ^* .() is <- 4;

const func integer: (in var integer: base) ^* (in var integer: exponent) is
  return intPow(base, exponent);

const func float: (in var float: base) ^* (in var integer: exponent) is
  return fltIPow(base, exponent);

Sidef

Function definition:

func expon(_, {.is_zero}) { 1 }

func expon(base, exp {.is_neg}) {
    expon(1/base, -exp)
}

func expon(base, exp {.is_int}) {

  var c = 1
  while (exp > 1) {
    c *= base if exp.is_odd
    base *= base
    exp >>= 1
  }

  return (base * c)
}

say expon(3, 10)
say expon(5.5, -3)

Operator definition:

class Number {
    method (exp) {
        expon(self, exp)
    }
}

say (3  10)
say (5.5  -3)
Output:
59049
0.0060105184072126220886551465063861758076634109692

Slate

This code is from the current slate implementation:

x@(Number traits) raisedTo: y@(Integer traits)
[
  y isZero ifTrue: [^ x unit].
  x isZero \/ [y = 1] ifTrue: [^ x].
  y isPositive
    ifTrue:
      "(x * x raisedTo: y // 2) * (x raisedTo: y \\ 2)"
      [| count result |
       count: 1.
       [(count: (count bitShift: 1)) < y] whileTrue.
       result: x unit.
       [count isPositive]
	 whileTrue:
	   [result: result squared.
	    (y bitAnd: count) isZero ifFalse: [result: result * x].
	    count: (count bitShift: -1)].
       result]
    ifFalse: [(x raisedTo: y negated) reciprocal]
].

For floating numbers:

x@(Float traits) raisedTo: y@(Float traits)
"Implements floating-point exponentiation in terms of the natural logarithm
and exponential primitives - this is generally faster than the naive method."
[
  y isZero ifTrue: [^ x unit].
  x isZero \/ [y isUnit] ifTrue: [^ x].
  (x ln * y) exp
].

Smalltalk

Works with: GNU Smalltalk

Extending the class Number, we provide the operator for integers, floating points, rationals numbers (and any other derived class)

Number extend [
  ** anInt [
       | r |
       ( anInt isInteger )
            ifFalse:
              [ '** works fine only for integer powers'
	        displayOn: stderr . Character nl displayOn: stderr ].
       r := 1.
       1 to: anInt do: [ :i | r := ( r * self ) ].
       ^r
  ]
].

( 2.5 ** 3 ) displayNl.
( 2 ** 10 ) displayNl.
( 3/7 ** 3 ) displayNl.
Output:
15.625
1024
27/343

Standard ML

The following operators only take nonnegative integer exponents.

fun expt_int (a, b) = let
  fun aux (x, i) =
    if i = b then x
    else aux (x * a, i + 1)
in
  aux (1, 0)
end

fun expt_real (a, b) = let
  fun aux (x, i) =
    if i = b then x
    else aux (x * a, i + 1)
in
  aux (1.0, 0)
end

val op ** = expt_int
infix 6 **
val op *** = expt_real
infix 6 ***
- 2 ** 3;
val it = 8 : int
- 2.4 *** 3;
val it = 13.824 : real

Stata

mata
function pow(a, n) {
	x = a
	for(p=1; n>0; n=floor(n/2)) {
		if(mod(n,2)==1) p = p*x
		x = x*x
	}
	return(p)
}
end

Swift

Translation of: Python

Defines generic function raise(_:to:) and operator ** that will work with all bases conforming to protocol Numeric, including Float and Int.

func raise<T: Numeric>(_ base: T, to exponent: Int) -> T {
    precondition(exponent >= 0, "Exponent has to be nonnegative")
    return Array(repeating: base, count: exponent).reduce(1, *)
}

infix operator **: MultiplicationPrecedence

func **<T: Numeric>(lhs: T, rhs: Int) -> T {
    return raise(lhs, to: rhs)
}

let someFloat: Float = 2
let someInt: Int = 10

assert(raise(someFloat, to: someInt) == 1024)
assert(someFloat ** someInt == 1024)
assert(raise(someInt, to: someInt) == 10000000000)
assert(someInt ** someInt == 10000000000)

Tcl

Works with: Tcl version 8.5

Tcl already has both an exponentiation function (set x [expr {pow(2.4, 3.5)}]) and operator (set x [expr {2.4 ** 3.5}]). The operator cannot be overridden. The function may be overridden by a procedure in the tcl::mathfunc namespace, relative to the calling namespace.

This solution does not consider negative exponents.

package require Tcl 8.5
proc tcl::mathfunc::mypow {a b} {
    if { ! [string is int -strict $b]} {error "exponent must be an integer"}
    set res 1
    for {set i 1} {$i <= $b} {incr i} {set res [expr {$res * $a}]}
    return $res
}
expr {mypow(3, 3)} ;# ==> 27
expr {mypow(3.5, 3)} ;# ==> 42.875
expr {mypow(3.5, 3.2)} ;# ==> exponent must be an integer

TI-57

Machine code Comment
Lbl 9
STO 0
1
SUM 0
Lbl 1
INV Dsz
GTO 2
*
RCL 7
GTO 1
Lbl 2
=
R/S
RST
program power(t,x) // x is the display register
r0 = x
x = 1
r0 -= 1
loop
  if --r0 = 0
      exit loop
  
  x *= t
end loop

return x
end program
reset pointer

5 x⮂t 3 GTO 9 R/S

Output:
125.

Ursa

# these implementations ignore negative exponents
def intpow (int m, int n)
	if (< n 1)
		return 1
	end if
	decl int ret
	set ret 1
	for () (> n 0) (dec n)
		set ret (* ret m)
	end for
	return ret
end intpow

def floatpow (double m, int n)
	if (or (< n 1) (and (= m 0) (= n 0)))
		return 1
	end if
	decl int ret
	set ret 1
	for () (> n 0) (dec n)
		set ret (* ret m)
	end for
	return ret
end floatpow

VBA

Public Function exp(ByVal base As Variant, ByVal exponent As Long) As Variant
    Dim result As Variant
    If TypeName(base) = "Integer" Or TypeName(base) = "Long" Then
        'integer exponentiation
        result = 1
        If exponent < 0 Then
            result = IIf(Abs(base) <> 1, CVErr(2019), IIf(exponent Mod 2 = -1, base, 1))
        End If
        Do While exponent > 0
            If exponent Mod 2 = 1 Then result = result * base
            base = base * base
            exponent = exponent \ 2
        Loop
    Else
        Debug.Assert IsNumeric(base)
        'float exponentiation
        If base = 0 Then
            If exponent < 0 Then result = CVErr(11)
        Else
            If exponent < 0 Then
                base = 1# / base
                exponent = -exponent
            End If
            result = 1
            Do While exponent > 0
                If exponent Mod 2 = 1 Then result = result * base
                base = base * base
                exponent = exponent \ 2
            Loop
        End If
    End If
    exp = result
End Function
Public Sub main()
    Debug.Print "Integer exponentiation"
    Debug.Print "10^7=", exp(10, 7)
    Debug.Print "10^4=", exp(10, 4)
    Debug.Print "(-3)^3=", exp(-3, 3)
    Debug.Print "(-1)^(-5)=", exp(-1, -5)
    Debug.Print "10^(-1)=", exp(10, -1)
    Debug.Print "0^2=", exp(0, 2)
    Debug.Print "Float exponentiation"
    Debug.Print "10.0^(-3)=", exp(10#, -3)
    Debug.Print "10.0^(-4)=", exp(10#, -4)
    Debug.Print "(-3.0)^(-5)=", exp(-3#, -5)
    Debug.Print "(-3.0)^(-4)=", exp(-3#, -4)
    Debug.Print "0.0^(-4)=", exp(0#, -4)
End Sub
Output:
Integer exponentiation
10^7=          10000000 
10^4=          10000 
(-3)^3=       -27 
(-1)^(-5)=    -1 
10^(-1)=      Fout 2019
0^2=           0 
Float exponentiation
10.0^(-3)=     0,001 
10.0^(-4)=     0,0001 
(-3.0)^(-5)=  -4,11522633744856E-03 
(-3.0)^(-4)=   1,23456790123457E-02 
0.0^(-4)=     Fout 11

VBScript

Function pow(x,y)
	pow = 1
	If y < 0 Then 
		For i = 1 To Abs(y)
			pow = pow * (1/x)
		Next
	Else
		For i = 1 To y
			pow = pow * x
		Next
	End If
End Function

WScript.StdOut.Write "2 ^ 0 = " & pow(2,0)
WScript.StdOut.WriteLine
WScript.StdOut.Write "7 ^ 6 = " & pow(7,6)
WScript.StdOut.WriteLine
WScript.StdOut.Write "3.14159265359 ^ 9 = " & pow(3.14159265359,9)
WScript.StdOut.WriteLine
WScript.StdOut.Write "4 ^ -6 = " & pow(4,-6)
WScript.StdOut.WriteLine
WScript.StdOut.Write "-3 ^ 5 = " & pow(-3,5)
WScript.StdOut.WriteLine
Output:
2 ^ 0 = 1
7 ^ 6 = 117649
3.14159265359 ^ 9 = 29809.0993334639
4 ^ -6 = 0.000244140625
-3 ^ 5 = -243

Wren

Although Wren supports operator overloading, operators have to be instance methods and it is not possible to inherit from the built in Num class which already has a 'pow' method in any case.

I've therefore decided to implement the power functions as static methods of a Num2 class and then define the ^ operator for this class which calls these methods using its receiver and exponent as parameters.

class Num2 {
    static ipow(i, exp) {
        if (!i.isInteger) Fiber.abort("ipow method must have an integer receiver")
        if (!exp.isInteger) Fiber.abort("ipow method must have an integer exponent")
        if (i == 1 || exp == 0) return 1
        if (i == -1) return (exp%2 == 0) ? 1 : -1
        if (exp < 0) Fiber.abort("ipow method cannot have a negative exponent")  
        var ans = 1
        var base = i
        var e = exp
        while (e > 1) {
            if (e%2 == 1) ans = ans * base
            e = (e/2).floor
            base = base * base
        }
        return ans * base
    }

    static fpow(f, exp) {
        if (!exp.isInteger) Fiber.abort("fpow method must have an integer exponent")
        var ans = 1.0
        var e = exp
        var base = (e < 0) ? 1/f : f
        if (e < 0) e = -e
        while (e > 0) {
            if (e%2 == 1) ans = ans * base
            e = (e/2).floor
            base = base * base
        }
        return ans
    }

    construct new(n) { _n = n }

    ^(exp) {
        if (_n.isInteger && (exp >= 0 || _n.abs == 1)) return Num2.ipow(_n, exp)
        return Num2.fpow(_n, exp)
    }
}

System.print("Using static methods:")
System.print("  2  ^  3   = %(Num2.ipow(2, 3))")
System.print("  1  ^ -10  = %(Num2.ipow(1, -10))")
System.print(" -1  ^ -3   = %(Num2.ipow(-1, -3))")
System.print()
System.print("  2.0 ^ -3  = %(Num2.fpow(2.0, -3))")
System.print("  1.5 ^  0  = %(Num2.fpow(1.5, 0))")
System.print("  4.5 ^  2  = %(Num2.fpow(4.5, 2))")

System.print("\nUsing the ^ operator:")
System.print("  2  ^  3   = %(Num2.new(2) ^ 3)")
System.print("  1  ^ -10  = %(Num2.new(1) ^ -10)")
System.print(" -1  ^ -3   = %(Num2.new(-1) ^ -3)")
System.print()
System.print("  2.0 ^ -3  = %(Num2.new(2.0) ^ -3)")
System.print("  1.5 ^  0  = %(Num2.new(1.5) ^ 0)")
System.print("  4.5 ^  2  = %(Num2.new(4.5) ^ 2)")
Output:
Using static methods:
  2  ^  3   = 8
  1  ^ -10  = 1
 -1  ^ -3   = -1

  2.0 ^ -3  = 0.125
  1.5 ^  0  = 1
  4.5 ^  2  = 20.25

Using the ^ operator:
  2  ^  3   = 8
  1  ^ -10  = 1
 -1  ^ -3   = -1

  2.0 ^ -3  = 0.125
  1.5 ^  0  = 1
  4.5 ^  2  = 20.25

XPL0

To create an exponent operator you need to modify the compiler code, which is open source.

include c:\cxpl\codes;  \intrinsic 'code' declarations

func real Power(X, Y);  \X raised to the Y power; (X > 0.0)
real X;  int Y;
return Exp(float(Y) * Ln(X));

func IPower(X, Y);      \X raised to the Y power
int  X, Y;
int  P;
[P:= 1;
while Y do
    [if Y&1 then P:= P*X;
    X:= X*X;
    Y:= Y>>1;
    ];
return P;
];

int X, Y;
[Format(9, 0);
for X:= 1 to 10 do
    [for Y:= 0 to 7 do
        RlOut(0, Power(float(X), Y));
    CrLf(0);
    ];
CrLf(0);
for X:= 1 to 10 do
    [for Y:= 0 to 7 do
        [ChOut(0, 9);  IntOut(0, IPower(X, Y))];
    CrLf(0);
    ];
]
Output:
        1        1        1        1        1        1        1        1
        1        2        4        8       16       32       64      128
        1        3        9       27       81      243      729     2187
        1        4       16       64      256     1024     4096    16384
        1        5       25      125      625     3125    15625    78125
        1        6       36      216     1296     7776    46656   279936
        1        7       49      343     2401    16807   117649   823543
        1        8       64      512     4096    32768   262144  2097152
        1        9       81      729     6561    59049   531441  4782969
        1       10      100     1000    10000   100000  1000000 10000000

        1       1       1       1       1       1       1       1
        1       2       4       8       16      32      64      128
        1       3       9       27      81      243     729     2187
        1       4       16      64      256     1024    4096    16384
        1       5       25      125     625     3125    15625   78125
        1       6       36      216     1296    7776    46656   279936
        1       7       49      343     2401    16807   117649  823543
        1       8       64      512     4096    32768   262144  2097152
        1       9       81      729     6561    59049   531441  4782969
        1       10      100     1000    10000   100000  1000000 10000000

zkl

Int and Float have pow methods and zkl doesn't allow you to add operators, classes can implement existing ones.

Translation of: C
fcn pow(n,exp){
   reg v;
   if(n.isType(1)){ // Int
      if (exp<0) return(if(n*n!=1) 0 else (if(exp.isOdd) n else 1));
      v=1; 
   }else{
      if(exp<0){ n=1.0/n; exp=-exp; }
      v=1.0;
   }
   while(exp>0){
      if(exp.isOdd) v*=n;
      n*=n;
      exp/=2;
   }
   v
}
println("2^6 = %d".fmt(pow(2,6)));
println("2^-6 = %d".fmt(pow(2,-6)));
println("2.71^6 = %f".fmt(pow(2.71,6)));
println("2.71^-6 = %f".fmt(pow(2.71,-6)));
Output:
2^6 = 64
2^-6 = 0
2.71^6 = 396.109944
2.71^-6 = 0.002525

ZX Spectrum Basic

ZX Spectrum Basic does not support custom operators or integer datatypes, but here we implement exponentation using a function. The function itself makes use of the inbuilt exponentiation operator, which is kind of cheating, but hey this provides a working implementation.

10 PRINT e(3,2): REM 3 ^ 2
20 PRINT e(1.5,2.7): REM 1.5 ^ 2.7
30 STOP
9950 DEF FN e(a,b)=a^b

The same string slicing trick used in the recursive factorial function can be used to come up with an integer solution; it works for any non-negative exponent. It's not recommended though; even the Spectrum's famously slow inbuilt exponentiation function is faster for exponents greater than 3. (A FOR-NEXT loop is fastest until about e=12.)

9999 DEF FN e(m,e)=VAL "m*FN e(m,e-1)*1"((e<1)*12+1 TO )