Horner's rule for polynomial evaluation: Difference between revisions

m
syntax highlighting fixup automation
m (syntax highlighting fixup automation)
Line 24:
{{trans|Python}}
 
<langsyntaxhighlight lang="11l">F horner(coeffs, x)
V acc = 0
L(c) reversed(coeffs)
Line 30:
R acc
 
print(horner([-19, 7, -4, 6], 3))</langsyntaxhighlight>
 
{{out}}
Line 38:
 
=={{header|360 Assembly}}==
<langsyntaxhighlight lang="360asm">* Horner's rule for polynomial evaluation - 07/10/2015
HORNER CSECT
USING HORNER,R15 set base register
Line 58:
PG DS CL12 buffer
YREGS
END HORNER</langsyntaxhighlight>
{{out}}
<pre>
Line 65:
 
=={{header|ACL2}}==
<langsyntaxhighlight Lisplang="lisp">(defun horner (ps x)
(if (endp ps)
0
(+ (first ps)
(* x (horner (rest ps) x)))))</langsyntaxhighlight>
 
=={{header|Action!}}==
<langsyntaxhighlight Actionlang="action!">INT FUNC Horner(INT ARRAY coeffs INT count,x)
INT v,i
 
Line 102:
res=Horner(coeffs,4,x)
PrintF("=%I%E",res)
RETURN</langsyntaxhighlight>
{{out}}
[https://gitlab.com/amarok8bit/action-rosetta-code/-/raw/master/images/Horner's_rule_for_polynomial_evaluation.png Screenshot from Atari 8-bit computer]
Line 111:
 
=={{header|Ada}}==
<langsyntaxhighlight Adalang="ada">with Ada.Float_Text_IO; use Ada.Float_Text_IO;
 
procedure Horners_Rule is
Line 127:
begin
Put(Horner(Coeffs => (-19.0, 7.0, -4.0, 6.0), Val => 3.0), Aft=>1, Exp=>0);
end Horners_Rule;</langsyntaxhighlight>
Output:
<pre>128.0</pre>
 
=={{header|Aime}}==
<langsyntaxhighlight lang="aime">real
horner(list coeffs, real x)
{
Line 154:
 
0;
}</langsyntaxhighlight>
 
=={{header|ALGOL 68}}==
{{works with|ALGOL 68G}}
<langsyntaxhighlight lang="algol68">PROC horner = ([]REAL c, REAL x)REAL :
(
REAL res := 0.0;
Line 170:
[4]REAL coeffs := (-19.0, 7.0, -4.0, 6.0);
print( horner(coeffs, 3.0) )
)</langsyntaxhighlight>
 
=={{header|ALGOL W}}==
<langsyntaxhighlight lang="algolw">begin
% Horner's rule for polynominal evaluation %
% returns the value of the polynominal defined by coefficients, %
Line 199:
write( r_format := "A", r_w := 8, r_d := 2, Horner( coefficients, 4, 3 ) )
end test_cases
end.</langsyntaxhighlight>
{{out}}
<pre>
Line 207:
=={{header|APL}}==
Works in [[Dyalog APL]]
<syntaxhighlight lang APL="apl">h←⊥∘⌽</langsyntaxhighlight>
{{output}}
<pre>
Line 215:
 
=={{header|ATS}}==
<langsyntaxhighlight ATSlang="ats">#include
"share/atspre_staload.hats"
 
Line 238:
in
println! (res)
end // end of [main0]</langsyntaxhighlight>
 
=={{header|Arturo}}==
 
<langsyntaxhighlight lang="rebol">horner: function [coeffs, x][
result: 0
loop reverse coeffs 'c ->
Line 249:
]
 
print horner @[neg 19, 7, neg 4, 6] 3</langsyntaxhighlight>
 
{{out}}
Line 256:
 
=={{header|AutoHotkey}}==
<langsyntaxhighlight lang="autohotkey">Coefficients = -19, 7, -4, 6
x := 3
 
Line 271:
i := Co0 - A_Index + 1, Result := Result * x + Co%i%
Return, Result
}</langsyntaxhighlight>
Message box shows:
<pre>128</pre>
 
=={{header|AWK}}==
<langsyntaxhighlight lang="awk">#!/usr/bin/awk -f
function horner(x, A) {
acc = 0;
Line 287:
split(p,P);
print horner(x,P);
}</langsyntaxhighlight>
 
{{out}}
Line 296:
 
=={{header|Batch File}}==
<langsyntaxhighlight lang="dos">
@echo off
 
Line 320:
echo %return%
exit /b
</syntaxhighlight>
</lang>
{{out}}
<pre>
Line 330:
 
=={{header|BBC BASIC}}==
<langsyntaxhighlight lang="bbcbasic"> DIM coefficients(3)
coefficients() = -19, 7, -4, 6
PRINT FNhorner(coefficients(), 3)
Line 340:
v = v * x + coeffs(i%)
NEXT
= v</langsyntaxhighlight>
 
=={{header|Bracmat}}==
<langsyntaxhighlight lang="bracmat">( ( Horner
= accumulator coefficients x coeff
. !arg:(?coefficients.?x)
Line 354:
)
& Horner$(-19 7 -4 6.3)
);</langsyntaxhighlight>
Output:
<pre>128</pre>
Line 360:
=={{header|C}}==
{{trans|Fortran}}
<langsyntaxhighlight lang="c">#include <stdio.h>
 
double horner(double *coeffs, int s, double x)
Line 381:
printf("%5.1f\n", horner(coeffs, sizeof(coeffs)/sizeof(double), 3.0));
return 0;
}</langsyntaxhighlight>
 
=={{header|C sharp|C#}}==
<langsyntaxhighlight lang="csharp">using System;
using System.Linq;
 
Line 399:
Console.WriteLine(Horner(new[] { -19.0, 7.0, -4.0, 6.0 }, 3.0));
}
}</langsyntaxhighlight>
Output:
<pre>128</pre>
Line 406:
The same C function works too, but another solution could be:
 
<langsyntaxhighlight lang="cpp">#include <iostream>
#include <vector>
 
Line 426:
cout << horner(v, 3.0) << endl;
return 0;
}</langsyntaxhighlight>
 
Yet another solution, which is more idiomatic in C++ and works on any bidirectional sequence:
 
<langsyntaxhighlight lang="cpp">
#include <iostream>
 
Line 447:
std::cout << horner(c, c + 4, 3) << std::endl;
}
</syntaxhighlight>
</lang>
 
=={{header|Clojure}}==
<langsyntaxhighlight lang="clojure">(defn horner [coeffs x]
(reduce #(-> %1 (* x) (+ %2)) (reverse coeffs)))
 
(println (horner [-19 7 -4 6] 3))</langsyntaxhighlight>
 
=={{header|CoffeeScript}}==
<langsyntaxhighlight lang="coffeescript">
eval_poly = (x, coefficients) ->
# coefficients are for ascending powers
Line 466:
console.log eval_poly 10, [4, 3, 2, 1] # 1234
console.log eval_poly 2, [1, 1, 0, 0, 1] # 19
</syntaxhighlight>
</lang>
 
=={{header|Common Lisp}}==
<langsyntaxhighlight lang="lisp">(defun horner (coeffs x)
(reduce #'(lambda (coef acc) (+ (* acc x) coef))
coeffs :from-end t :initial-value 0))</langsyntaxhighlight>
 
Alternate version using LOOP. Coefficients are passed in a vector.
 
<langsyntaxhighlight lang="lisp">(defun horner (x a)
(loop :with y = 0
:for i :from (1- (length a)) :downto 0
Line 481:
:finally (return y)))
 
(horner 1.414 #(-2 0 1))</langsyntaxhighlight>
 
=={{header|D}}==
The poly() function of the standard library std.math module uses Horner's rule:
<langsyntaxhighlight lang="d">void main() {
void main() {
import std.stdio, std.math;
Line 493:
poly(x,pp).writeln;
}
}</langsyntaxhighlight>
Basic implementation:
<langsyntaxhighlight lang="d">import std.stdio, std.traits;
 
CommonType!(U, V) horner(U, V)(U[] p, V x) pure nothrow @nogc {
Line 506:
void main() {
[-19, 7, -4, 6].horner(3.0).writeln;
}</langsyntaxhighlight>
More functional style:
<langsyntaxhighlight lang="d">import std.stdio, std.algorithm, std.range;
 
auto horner(T, U)(in T[] p, in U x) pure nothrow @nogc {
Line 516:
void main() {
[-19, 7, -4, 6].horner(3.0).writeln;
}</langsyntaxhighlight>
 
=={{header|E}}==
 
<langsyntaxhighlight lang="e">def makeHornerPolynomial(coefficients :List) {
def indexing := (0..!coefficients.size()).descending()
return def hornerPolynomial(x) {
Line 529:
return acc
}
}</langsyntaxhighlight>
 
<langsyntaxhighlight lang="e">? makeHornerPolynomial([-19, 7, -4, 6])(3)
# value: 128</langsyntaxhighlight>
 
=={{header|EchoLisp}}==
=== Functional version ===
<langsyntaxhighlight lang="lisp">
(define (horner x poly)
(foldr (lambda (coeff acc) (+ coeff (* acc x))) 0 poly))
 
(horner 3 '(-19 7 -4 6)) → 128
</syntaxhighlight>
</lang>
=== Library ===
<langsyntaxhighlight lang="lisp">
(lib 'math)
Lib: math.lib loaded.
Line 550:
(poly->string 'x P) → 6x^3 -4x^2 +7x -19
(poly 3 P) → 128
</syntaxhighlight>
</lang>
 
=={{header|EDSAC order code}}==
<langsyntaxhighlight lang="edsac">
[Copyright <2021> <ERIK SARGSYAN>
Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"),
Line 615:
EZPF
</syntaxhighlight>
</lang>
{{out}}
<pre>
Line 624:
{{trans|C#}}
ELENA 5.0 :
<langsyntaxhighlight lang="elena">import extensions;
import system'routines;
Line 635:
{
console.printLine(horner(new real[]{-19.0r, 7.0r, -4.0r, 6.0r}, 3.0r))
}</langsyntaxhighlight>
{{out}}
<pre>
Line 642:
 
=={{header|Elixir}}==
<langsyntaxhighlight lang="elixir">horner = fn(list, x)-> List.foldr(list, 0, fn(c,acc)-> x*acc+c end) end
 
IO.puts horner.([-19,7,-4,6], 3)</langsyntaxhighlight>
 
{{out}}
Line 653:
=={{header|Emacs Lisp}}==
{{trans|Common Lisp}}
<langsyntaxhighlight Lisplang="lisp">(require 'cl-lib)
 
(defun horner (coeffs x)
Line 659:
coeffs :from-end t :initial-value 0))
 
(horner '(-19 7 -4 6) 3)</langsyntaxhighlight>
 
{{out}}
Line 666:
 
=={{header|Erlang}}==
<langsyntaxhighlight lang="erlang">
horner(L,X) ->
lists:foldl(fun(C, Acc) -> X*Acc+C end,0, lists:reverse(L)).
t() ->
horner([-19,7,-4,6], 3).
</syntaxhighlight>
</lang>
 
=={{header|ERRE}}==
<syntaxhighlight lang="erre">
<lang ERRE>
PROGRAM HORNER
 
Line 696:
PRINT(RES)
END PROGRAM
</syntaxhighlight>
</lang>
 
=={{header|Euler Math Toolbox}}==
 
<syntaxhighlight lang="euler math toolbox">
<lang Euler Math Toolbox>
>function horner (x,v) ...
$ n=cols(v); res=v{n};
Line 719:
3 2
6 x - 4 x + 7 x - 19
</syntaxhighlight>
</lang>
 
=={{header|F Sharp|F#}}==
<langsyntaxhighlight lang="fsharp">
let horner l x =
List.rev l |> List.fold ( fun acc c -> x*acc+c) 0
 
horner [-19;7;-4;6] 3
</syntaxhighlight>
</lang>
 
=={{header|Factor}}==
<langsyntaxhighlight lang="factor">: horner ( coeff x -- res )
[ <reversed> 0 ] dip '[ [ _ * ] dip + ] reduce ;</langsyntaxhighlight>
 
( scratchpad ) { -19 7 -4 6 } 3 horner .
Line 737:
 
=={{header|Forth}}==
<langsyntaxhighlight lang="forth">: fhorner ( coeffs len F: x -- F: val )
0e
floats bounds ?do
Line 746:
create coeffs 6e f, -4e f, 7e f, -19e f,
 
coeffs 4 3e fhorner f. \ 128.</langsyntaxhighlight>
 
=={{header|Fortran}}==
{{works with|Fortran|90 and later}}
<langsyntaxhighlight lang="fortran">program test_horner
 
implicit none
Line 773:
end function horner
 
end program test_horner</langsyntaxhighlight>
Output:
<pre>128.0</pre>
 
=== Fortran 77 ===
<langsyntaxhighlight lang="fortran"> FUNCTION HORNER(N,A,X)
IMPLICIT NONE
INTEGER I,N
Line 787:
END DO
HORNER=Y
END</langsyntaxhighlight>
 
As a matter of fact, computing the derivative is not much more difficult (see [http://www.cs.berkeley.edu/~wkahan/Math128/Poly.pdf Roundoff in Polynomial Evaluation], W. Kahan, 1986). The following subroutine computes both polynomial value and derivative for argument x.
 
<langsyntaxhighlight lang="fortran"> SUBROUTINE HORNER2(N,A,X,Y,Z)
C COMPUTE POLYNOMIAL VALUE AND DERIVATIVE
C SEE "ROUNDOFF IN POLYNOMIAL EVALUATION", W. KAHAN, 1986
Line 805:
10 Y = Y*X + A(I)
END
</syntaxhighlight>
</lang>
 
=={{header|FreeBASIC}}==
<langsyntaxhighlight lang="freebasic">
Function AlgoritmoHorner(coeffs() As Integer, x As Integer) As Integer
Dim As Integer i, acumulador = 0
Line 822:
Print AlgoritmoHorner(coeficientes(), x)
End
</syntaxhighlight>
</lang>
{{out}}
<pre>
Line 830:
=={{header|FunL}}==
{{trans|Haskell}}
<langsyntaxhighlight lang="funl">import lists.foldr
 
def horner( poly, x ) = foldr( \a, b -> a + b*x, 0, poly )
 
println( horner([-19, 7, -4, 6], 3) )</langsyntaxhighlight>
 
{{out}}
Line 843:
 
=={{header|FutureBasic}}==
<langsyntaxhighlight lang="futurebasic">include "NSLog.incl"
 
local fn horner( coeffs as CFArrayRef, x as NSInteger ) as double
Line 876:
NSLog( @"%7.1f", fn horner( coeffs, 2 ) )
 
HandleEvents</langsyntaxhighlight>
 
{{out}}
Line 889:
 
=={{header|GAP}}==
<langsyntaxhighlight lang="gap"># The idiomatic way to compute with polynomials
 
x := Indeterminate(Rationals, "x");
Line 920:
 
Horner(u, 3);
# 128</langsyntaxhighlight>
 
=={{header|Go}}==
<langsyntaxhighlight lang="go">package main
 
import "fmt"
Line 936:
func main() {
fmt.Println(horner(3, []int64{-19, 7, -4, 6}))
}</langsyntaxhighlight>
Output:
<pre>
Line 944:
=={{header|Groovy}}==
Solution:
<langsyntaxhighlight lang="groovy">def hornersRule = { coeff, x -> coeff.reverse().inject(0) { accum, c -> (accum * x) + c } }</langsyntaxhighlight>
 
Test includes demonstration of [[currying]] to create polynomial functions of one variable from generic Horner's rule calculation. Also demonstrates constructing the derivative function for the given polynomial. And finally demonstrates in the Newton-Raphson method to find one of the polynomial's roots using the polynomial and derivative functions constructed earlier.
<langsyntaxhighlight lang="groovy">def coefficients = [-19g, 7g, -4g, 6g]
println (["p coefficients":coefficients])
 
Line 969:
 
def root = newtonRaphson(3g, testPoly, testDeriv)
println ([root:root.toString()[0..5], "p(root)":testPoly(root).toString()[0..5], "p'(root)":testDeriv(root).toString()[0..5]])</langsyntaxhighlight>
 
Output:
Line 981:
 
=={{header|Haskell}}==
<langsyntaxhighlight lang="haskell">horner :: (Num a) => a -> [a] -> a
horner x = foldr (\a b -> a + b*x) 0
 
main = print $ horner 3 [-19, 7, -4, 6]</langsyntaxhighlight>
 
=={{header|HicEst}}==
<langsyntaxhighlight HicEstlang="hicest">REAL :: x=3, coeffs(4)
DATA coeffs/-19.0, 7.0, -4.0, 6.0/
 
Line 998:
Horner = x*Horner + c(i)
ENDDO
END</langsyntaxhighlight>
 
=={{header|Icon}} and {{header|Unicon}}==
 
<syntaxhighlight lang="icon">
<lang Icon>
procedure poly_eval (x, coeffs)
accumulator := 0
Line 1,013:
write (poly_eval (3, [-19, 7, -4, 6]))
end
</syntaxhighlight>
</lang>
 
=={{header|J}}==
'''Solution''':<langsyntaxhighlight lang="j">
horner =: (#."0 _ |.)~ NB. Tacit
horner =: [: +`*/ [: }: ,@,. NB. Alternate tacit (equivalent)
horner =: 4 : ' (+ *&y)/x' NB. Alternate explicit (equivalent)
</syntaxhighlight>
</lang>
'''Example''':<langsyntaxhighlight lang="j"> _19 7 _4 6 horner 3
128</langsyntaxhighlight>
'''Note:'''<br>
The primitive verb <code>p.</code> would normally be used to evaluate polynomials.
<langsyntaxhighlight lang="j"> _19 7 _4 6 p. 3
128</langsyntaxhighlight>
 
=={{header|Java}}==
{{works with|Java|1.5+}}
<langsyntaxhighlight lang="java5">import java.util.ArrayList;
import java.util.Collections;
import java.util.List;
Line 1,052:
return accumulator;
}
}</langsyntaxhighlight>
Output:
<pre>128.0</pre>
Line 1,060:
 
{{trans|Haskell}}
<langsyntaxhighlight lang="javascript">function horner(coeffs, x) {
return coeffs.reduceRight( function(acc, coeff) { return(acc * x + coeff) }, 0);
}
console.log(horner([-19,7,-4,6],3)); // ==> 128
</syntaxhighlight>
</lang>
 
=={{header|Julia}}==
Line 1,070:
 
'''Imperative''':
<langsyntaxhighlight lang="julia">function horner(coefs, x)
s = coefs[end] * one(x)
for k in length(coefs)-1:-1:1
Line 1,078:
end
 
@show horner([-19, 7, -4, 6], 3)</langsyntaxhighlight>
 
{{out}}
Line 1,084:
 
'''Functional''':
<langsyntaxhighlight lang="julia">horner2(coefs, x) = foldr((u, v) -> u + x * v, coefs, init=zero(promote_type(typeof(x),eltype(coefs))))
 
@show horner2([-19, 7, -4, 6], 3)</langsyntaxhighlight>
 
{{out}}
Line 1,093:
'''Note''':
In Julia 1.4 or later one would normally use the built-in '''evalpoly''' function for this purpose:
<langsyntaxhighlight lang="julia">
@show evalpoly(3, [-19, 7, -4, 6]) </langsyntaxhighlight>
 
{{out}}
Line 1,100:
 
=={{header|K}}==
<syntaxhighlight lang="k">
<lang K>
horner:{y _sv|x}
horner[-19 7 -4 6;3]
128
</syntaxhighlight>
</lang>
 
=={{header|Kotlin}}==
<langsyntaxhighlight lang="scala">// version 1.1.2
 
fun horner(coeffs: DoubleArray, x: Double): Double {
Line 1,118:
val coeffs = doubleArrayOf(-19.0, 7.0, -4.0, 6.0)
println(horner(coeffs, 3.0))
}</langsyntaxhighlight>
 
{{out}}
Line 1,126:
 
=={{header|Lambdatalk}}==
<langsyntaxhighlight lang="scheme">
{def horner
{def horner.r
Line 1,143:
-> 2.220446049250313e-16 ~ 0
 
</syntaxhighlight>
</lang>
 
=={{header|Liberty BASIC}}==
<langsyntaxhighlight lang="lb">src$ = "Hello"
coefficients$ = "-19 7 -4 6" ' list coefficients of all x^0..x^n in order
x = 3
Line 1,165:
horner = accumulator
end function
</langsyntaxhighlight>
 
=={{header|Logo}}==
<langsyntaxhighlight lang="logo">to horner :x :coeffs
if empty? :coeffs [output 0]
output (first :coeffs) + (:x * horner :x bf :coeffs)
end
 
show horner 3 [-19 7 -4 6] ; 128</langsyntaxhighlight>
 
=={{header|Lua}}==
<langsyntaxhighlight lang="lua">function horners_rule( coeff, x )
local res = 0
for i = #coeff, 1, -1 do
Line 1,186:
x = 3
coefficients = { -19, 7, -4, 6 }
print( horners_rule( coefficients, x ) )</langsyntaxhighlight>
 
=={{header|Maple}}==
<syntaxhighlight lang="maple">
<lang Maple>
applyhorner:=(L::list,x)->foldl((s,t)->s*x+t,op(ListTools:-Reverse(L))):
 
Line 1,195:
 
applyhorner([-19,7,-4,6],3);
</syntaxhighlight>
</lang>
Output:
<pre>
Line 1,204:
 
=={{header|Mathematica}} / {{header|Wolfram Language}}==
<langsyntaxhighlight Mathematicalang="mathematica">Horner[l_List, x_] := Fold[x #1 + #2 &, 0, l]
Horner[{6, -4, 7, -19}, x]
-> -19 + x (7 + x (-4 + 6 x))
 
-19 + x (7 + x (-4 + 6 x)) /. x -> 3
-> 128</langsyntaxhighlight>
 
=={{header|MATLAB}}==
<langsyntaxhighlight MATLABlang="matlab">function accumulator = hornersRule(x,coefficients)
 
accumulator = 0;
Line 1,220:
end
end</langsyntaxhighlight>
Output:
<langsyntaxhighlight MATLABlang="matlab">>> hornersRule(3,[-19, 7, -4, 6])
 
ans =
 
128</langsyntaxhighlight>
Matlab also has a built-in function "polyval" which uses Horner's Method to evaluate polynomials. The list of coefficients is in descending order of power, where as to task spec specifies ascending order.
<langsyntaxhighlight MATLABlang="matlab">>> polyval(fliplr([-19, 7, -4, 6]),3)
 
ans =
 
128</langsyntaxhighlight>
 
=={{header|Maxima}}==
<langsyntaxhighlight lang="maxima">/* Function horner already exists in Maxima, though it operates on expressions, not lists of coefficients */
horner(5*x^3+2*x+1);
x*(5*x^2+2)+1
Line 1,279:
 
poleval([0, 0, 0, 0, 1], x);
x^4</langsyntaxhighlight>
 
=={{header|Mercury}}==
<langsyntaxhighlight lang="mercury">
:- module horner.
:- interface.
Line 1,296:
 
horner(X, Cs) = list.foldr((func(C, Acc) = Acc * X + C), Cs, 0).
</syntaxhighlight>
</lang>
 
=={{header|МК-61/52}}==
<syntaxhighlight lang="text">ИП0 1 + П0
ИПE ИПD * КИП0 + ПE
ИП0 1 - x=0 04
ИПE С/П</langsyntaxhighlight>
 
''Input:'' Р1:РС - coefficients, Р0 - number of the coefficients, РD - ''x''.
 
=={{header|Modula-2}}==
<langsyntaxhighlight lang="modula2">MODULE Horner;
FROM RealStr IMPORT RealToStr;
FROM Terminal IMPORT WriteString,WriteLn,ReadChar;
Line 1,335:
WriteLn;
ReadChar
END Horner.</langsyntaxhighlight>
 
=={{header|NetRexx}}==
<langsyntaxhighlight lang="netrexx">/* NetRexx */
options replace format comments java crossref savelog symbols nobinary
 
Line 1,349:
End
Say r
Say 6*x**3-4*x**2+7*x-19</langsyntaxhighlight>
'''Output:'''
<pre>128
Line 1,355:
 
=={{header|Nim}}==
<langsyntaxhighlight lang="nim"># You can also just use `reversed` proc from stdlib `algorithm` module
iterator reversed[T](x: openArray[T]): T =
for i in countdown(x.high, x.low):
Line 1,364:
result = result * x + c
echo horner([-19, 7, -4, 6], 3)</langsyntaxhighlight>
 
=={{header|Oberon-2}}==
{{works with|oo2c}}
<langsyntaxhighlight lang="oberon2">
MODULE HornerRule;
IMPORT
Line 1,397:
Out.Int(Eval(coefs^,4,3),0);Out.Ln
END HornerRule.
</syntaxhighlight>
</lang>
{{out}}
<pre>
Line 1,404:
 
=={{header|Objeck}}==
<langsyntaxhighlight lang="objeck">
class Horner {
function : Main(args : String[]) ~ Nil {
Line 1,424:
}
}
</syntaxhighlight>
</lang>
 
=={{header|Objective-C}}==
{{works with|Mac OS X|10.6+}} Using blocks
<langsyntaxhighlight lang="objc">#import <Foundation/Foundation.h>
 
typedef double (^mfunc)(double, double);
Line 1,469:
}
return 0;
}</langsyntaxhighlight>
 
=={{header|OCaml}}==
 
<langsyntaxhighlight lang="ocaml"># let horner coeffs x =
List.fold_left (fun acc coef -> acc * x + coef) 0 (List.rev coeffs) ;;
val horner : int list -> int -> int = <fun>
Line 1,479:
# let coeffs = [-19; 7; -4; 6] in
horner coeffs 3 ;;
- : int = 128</langsyntaxhighlight>
It's also possible to do fold_right instead of reversing and doing fold_left; but fold_right is not tail-recursive.
 
=={{header|Octave}}==
<langsyntaxhighlight lang="octave">function r = horner(a, x)
r = 0.0;
for i = length(a):-1:1
Line 1,490:
endfunction
 
horner([-19, 7, -4, 6], 3)</langsyntaxhighlight>
 
=={{header|ooRexx}}==
<langsyntaxhighlight lang="oorexx">/* Rexx ---------------------------------------------------------------
* 04.03.2014 Walter Pachl
*--------------------------------------------------------------------*/
Line 1,504:
End
Say r
Say 6*x**3-4*x**2+7*x-19</langsyntaxhighlight>
'''Output:'''
<pre>128
Line 1,510:
 
=={{header|Oz}}==
<langsyntaxhighlight lang="oz">declare
fun {Horner Coeffs X}
{FoldL1 {Reverse Coeffs}
Line 1,522:
end
in
{Show {Horner [~19 7 ~4 6] 3}}</langsyntaxhighlight>
 
=={{header|PARI/GP}}==
Also note that Pari has a polynomial type. Evaluating these is as simple as <code>subst(P,variable(P),x)</code>.
<langsyntaxhighlight lang="parigp">horner(v,x)={
my(s=0);
forstep(i=#v,1,-1,s=s*x+v[i]);
s
};</langsyntaxhighlight>
 
=={{header|Pascal}}==
<langsyntaxhighlight lang="pascal">Program HornerDemo(output);
 
function horner(a: array of double; x: double): double;
Line 1,550:
write ('Horner calculated polynomial of 6*x^3 - 4*x^2 + 7*x - 19 for x = 3: ');
writeln (horner (poly, 3.0):8:4);
end.</langsyntaxhighlight>
Output:
<pre>Horner calculated polynomial of 6*x^3 - 4*x^2 + 7*x - 19 for x = 3: 128.0000
Line 1,556:
 
=={{header|Perl}}==
<langsyntaxhighlight Perllang="perl">use 5.10.0;
use strict;
use warnings;
Line 1,569:
my @coeff = (-19.0, 7, -4, 6);
my $x = 3;
say horner @coeff, $x;</langsyntaxhighlight>
 
===<!-- Perl -->Functional version===
<langsyntaxhighlight lang="perl">use strict;
use List::Util qw(reduce);
 
Line 1,582:
my @coeff = (-19.0, 7, -4, 6);
my $x = 3;
print horner(\@coeff, $x), "\n";</langsyntaxhighlight>
 
===<!-- Perl -->Recursive version===
<langsyntaxhighlight lang="perl">sub horner {
my ($coeff, $x) = @_;
@$coeff and
Line 1,591:
}
print horner( [ -19, 7, -4, 6 ], 3 );</langsyntaxhighlight>
 
=={{header|Phix}}==
<!--<langsyntaxhighlight Phixlang="phix">(phixonline)-->
<span style="color: #008080;">with</span> <span style="color: #008080;">javascript_semantics</span>
<span style="color: #008080;">function</span> <span style="color: #000000;">horner</span><span style="color: #0000FF;">(</span><span style="color: #004080;">atom</span> <span style="color: #000000;">x</span><span style="color: #0000FF;">,</span> <span style="color: #004080;">sequence</span> <span style="color: #000000;">coeff</span><span style="color: #0000FF;">)</span>
Line 1,605:
<span style="color: #0000FF;">?</span><span style="color: #000000;">horner</span><span style="color: #0000FF;">(</span><span style="color: #000000;">3</span><span style="color: #0000FF;">,{-</span><span style="color: #000000;">19</span><span style="color: #0000FF;">,</span> <span style="color: #000000;">7</span><span style="color: #0000FF;">,</span> <span style="color: #0000FF;">-</span><span style="color: #000000;">4</span><span style="color: #0000FF;">,</span> <span style="color: #000000;">6</span><span style="color: #0000FF;">})</span>
<!--</langsyntaxhighlight>-->
{{out}}
<pre>
Line 1,612:
 
=={{header|PHP}}==
<langsyntaxhighlight lang="php"><?php
function horner($coeff, $x) {
$result = 0;
Line 1,623:
$x = 3;
echo horner($coeff, $x), "\n";
?></langsyntaxhighlight>
 
===Functional version===
{{works with|PHP|5.3+}}
<langsyntaxhighlight lang="php"><?php
function horner($coeff, $x) {
return array_reduce(array_reverse($coeff), function ($a, $b) use ($x) { return $a * $x + $b; }, 0);
Line 1,635:
$x = 3;
echo horner($coeff, $x), "\n";
?></langsyntaxhighlight>
 
=={{header|Picat}}==
===Recursion===
<langsyntaxhighlight Picatlang="picat">horner([],_X,0).
horner([H|T],X,V) :-
horner(T,X,V1),
V = V1 * X + H.</langsyntaxhighlight>
 
===Iterative===
<langsyntaxhighlight Picatlang="picat">horner2(Coeff, X, V) =>
Acc = 0,
foreach(I in Coeff.length..-1..1)
Acc := Acc*X + Coeff[I]
end,
V = Acc.</langsyntaxhighlight>
 
===Functional approach===
<langsyntaxhighlight Picatlang="picat">h3(X,A,B) = A+B*X.
horner3(Coeff, X) = fold($h3(X),0,Coeff.reverse()).</langsyntaxhighlight>
 
===Test===
<langsyntaxhighlight Picatlang="picat">go =>
horner([-19, 7, -4, 6], 3, V),
println(V),
Line 1,666:
V3 = horner3([-19, 7, -4, 6], 3),
println(V3),
nl.</langsyntaxhighlight>
 
{{out}}
Line 1,674:
 
=={{header|PicoLisp}}==
<langsyntaxhighlight PicoLisplang="picolisp">(de horner (Coeffs X)
(let Res 0
(for C (reverse Coeffs)
(setq Res (+ C (* X Res))) ) ) )</langsyntaxhighlight>
<langsyntaxhighlight PicoLisplang="picolisp">: (horner (-19.0 7.0 -4.0 6.0) 3.0)
-> 128</langsyntaxhighlight>
 
=={{header|PL/I}}==
<syntaxhighlight lang="pl/i">
<lang PL/I>
declare (i, n) fixed binary, (x, value) float; /* 11 May 2010 */
get (x);
Line 1,695:
put (value);
end;
</syntaxhighlight>
</lang>
 
=={{header|Potion}}==
<langsyntaxhighlight lang="potion">horner = (x, coef) :
result = 0
coef reverse each (a) :
Line 1,706:
.
 
horner(3, (-19, 7, -4, 6)) print</langsyntaxhighlight>
 
=={{header|PowerShell}}==
{{works with|PowerShell|4.0}}
<syntaxhighlight lang="powershell">
<lang PowerShell>
function horner($coefficients, $x) {
$accumulator = 0
Line 1,721:
$x = 3
horner $coefficients $x
</syntaxhighlight>
</lang>
<b>Output:</b>
<pre>
Line 1,729:
=={{header|Prolog}}==
Tested with SWI-Prolog. Works with other dialects.
<langsyntaxhighlight Prologlang="prolog">horner([], _X, 0).
 
horner([H|T], X, V) :-
horner(T, X, V1),
V is V1 * X + H.
</syntaxhighlight>
</lang>
Output :
<langsyntaxhighlight Prologlang="prolog"> ?- horner([-19, 7, -4, 6], 3, V).
V = 128.</langsyntaxhighlight>
 
===Functional approach===
Works with SWI-Prolog and module lambda, written by <b>Ulrich Neumerkel</b> found there http://www.complang.tuwien.ac.at/ulrich/Prolog-inedit/lambda.pl
<langsyntaxhighlight Prologlang="prolog">:- use_module(library(lambda)).
 
 
Line 1,753:
f_horner(L, V, R) :-
foldr(\X^Y^Z^(Z is X * V + Y), 0, L, R).
</syntaxhighlight>
</lang>
 
===Functional syntax (Ciao)===
Works with Ciao (https://github.com/ciao-lang/ciao) and the fsyntax package:
<syntaxhighlight lang="prolog">
<lang Prolog>
:- module(_, [horner/3], [fsyntax, hiord]).
:- use_module(library(hiordlib)).
horner(L, X) := ~foldr((''(H,V0,V) :- V is V0*X + H), L, 0).
</syntaxhighlight>
</lang>
 
=={{header|PureBasic}}==
<langsyntaxhighlight PureBasiclang="purebasic">Procedure Horner(List Coefficients(), b)
Define result
ForEach Coefficients()
Line 1,770:
Next
ProcedureReturn result
EndProcedure</langsyntaxhighlight>
 
'''Implemented as
<langsyntaxhighlight PureBasiclang="purebasic">NewList a()
AddElement(a()): a()= 6
AddElement(a()): a()= -4
AddElement(a()): a()= 7
AddElement(a()): a()=-19
Debug Horner(a(),3)</langsyntaxhighlight>
'''Outputs
128
 
=={{header|Python}}==
<langsyntaxhighlight lang="python">>>> def horner(coeffs, x):
acc = 0
for c in reversed(coeffs):
Line 1,790:
 
>>> horner( (-19, 7, -4, 6), 3)
128</langsyntaxhighlight>
 
===Functional version===
<langsyntaxhighlight lang="python">>>> try: from functools import reduce
except: pass
 
Line 1,800:
 
>>> horner( (-19, 7, -4, 6), 3)
128</langsyntaxhighlight>
 
==={{libheader|NumPy}}===
<langsyntaxhighlight lang="python">>>> import numpy
>>> numpy.polynomial.polynomial.polyval(3, (-19, 7, -4, 6))
128.0</langsyntaxhighlight>
 
=={{header|R}}==
Procedural style:
<langsyntaxhighlight lang="r">horner <- function(a, x) {
y <- 0
for(c in rev(a)) {
Line 1,817:
}
 
cat(horner(c(-19, 7, -4, 6), 3), "\n")</langsyntaxhighlight>
Functional style:
<langsyntaxhighlight lang="r">horner <- function(x, v) {
Reduce(v, right=T, f=function(a, b) {
b * x + a
})
}</langsyntaxhighlight>
{{out}}
<pre>
Line 1,834:
Translated from Haskell
 
<langsyntaxhighlight lang="racket">
#lang racket
(define (horner x l)
Line 1,841:
(horner 3 '(-19 7 -4 6))
 
</syntaxhighlight>
</lang>
 
=={{header|Raku}}==
(formerly Perl 6)
<syntaxhighlight lang="raku" perl6line>sub horner ( @coeffs, $x ) {
@coeffs.reverse.reduce: { $^a * $x + $^b };
}
 
say horner( [ -19, 7, -4, 6 ], 3 );</langsyntaxhighlight>
 
A recursive version would spare us the need for reversing the list of coefficients. However, special care must be taken in order to write it, because the way Raku implements lists is not optimized for this kind of treatment. [[Lisp]]-style lists are, and fortunately it is possible to emulate them with [http://doc.raku.org/type/Pair Pairs] and the reduction meta-operator:
 
<syntaxhighlight lang="raku" perl6line>multi horner(Numeric $c, $) { $c }
multi horner(Pair $c, $x) {
$c.key + $x * horner( $c.value, $x )
}
say horner( [=>](-19, 7, -4, 6 ), 3 );</langsyntaxhighlight>
 
We can also use the composition operator:
<syntaxhighlight lang="raku" perl6line>sub horner ( @coeffs, $x ) {
([o] map { $_ + $x * * }, @coeffs)(0);
}
say horner( [ -19, 7, -4, 6 ], 3 );</langsyntaxhighlight>
 
{{out}}
Line 1,871:
 
One advantage of using the composition operator is that it allows for the use of an infinite list of coefficients.
<syntaxhighlight lang="raku" perl6line>sub horner ( @coeffs, $x ) {
map { .(0) }, [\o] map { $_ + $x * * }, @coeffs;
}
say horner( [ 1 X/ (1, |[\*] 1 .. *) ], i*pi )[20];
</syntaxhighlight>
</lang>
{{out}}
<pre>-0.999999999924349-5.28918515954219e-10i</pre>
 
=={{header|Rascal}}==
<langsyntaxhighlight lang="rascal">import List;
 
public int horners_rule(list[int] coefficients, int x){
Line 1,888:
acc = acc * x + i;}
return acc;
}</langsyntaxhighlight>
A neater and shorter solution using a reducer:
<langsyntaxhighlight lang="rascal">public int horners_rule2(list[int] coefficients, int x) = (0 | it * x + c | c <- reverse(coefficients));</langsyntaxhighlight>
Output:
<langsyntaxhighlight lang="rascal">rascal>horners_rule([-19, 7, -4, 6], 3)
int: 128
 
rascal>horners_rule2([-19, 7, -4, 6], 3)
int: 128</langsyntaxhighlight>
 
=={{header|REBOL}}==
 
<langsyntaxhighlight lang="rebol">REBOL []
 
horner: func [coeffs x] [
Line 1,910:
]
 
print horner [-19 7 -4 6] 3</langsyntaxhighlight>
 
=={{header|REXX}}==
===version 1===
<langsyntaxhighlight lang="rexx">/*REXX program demonstrates using Horner's rule for polynomial evaluation. */
numeric digits 30 /*use extra numeric precision. */
parse arg x poly /*get value of X and the coefficients. */
Line 1,932:
end /*j*/
say /*display a blank line for readability.*/
say ' answer = ' a /*stick a fork in it, we're all done. */</langsyntaxhighlight>
'''output''' &nbsp; when the following is used for input: &nbsp; <tt> 3 &nbsp; -19 &nbsp; 7 &nbsp; -4 &nbsp; 6 </tt>
<pre>
Line 1,943:
 
===version 2===
<langsyntaxhighlight lang="rexx">/* REXX ---------------------------------------------------------------
* 27.07.2012 Walter Pachl
* coefficients reversed to descending order of power
Line 1,987:
Say ' equation = ' equ
Say ' '
Say ' result = ' a</langsyntaxhighlight>
{{out}}
<pre> x = 3
Line 1,996:
 
=={{header|Ring}}==
<langsyntaxhighlight lang="ring">
coefficients = [-19, 7, -4, 6]
see "x = 3" + nl +
Line 2,009:
next
return w
</syntaxhighlight>
</lang>
Output:
<pre>
Line 2,025:
 
This said, solution to the problem is
<syntaxhighlight lang="rlab">
<lang RLaB>
>> a = [6, -4, 7, -19]
6 -4 7 -19
Line 2,033:
128
 
</syntaxhighlight>
</lang>
 
=={{header|Ruby}}==
<langsyntaxhighlight lang="ruby">def horner(coeffs, x)
coeffs.reverse.inject(0) {|acc, coeff| acc * x + coeff}
end
p horner([-19, 7, -4, 6], 3) # ==> 128</langsyntaxhighlight>
 
=={{header|Run BASIC}}==
<langsyntaxhighlight lang="runbasic">coef$ = "-19 7 -4 6" ' list coefficients of all x^0..x^n in order
x = 3
print horner(coef$,x) '128
Line 2,058:
next
horner = accum
end function</langsyntaxhighlight>
 
=={{header|Rust}}==
<langsyntaxhighlight lang="rust">fn horner(v: &[f64], x: f64) -> f64 {
v.iter().rev().fold(0.0, |acc, coeff| acc*x + coeff)
}
Line 2,068:
let v = [-19., 7., -4., 6.];
println!("result: {}", horner(&v, 3.0));
}</langsyntaxhighlight>
 
A generic version that works with any number type and much more. So much more, it's hard to imagine what that may be useful for.
<langsyntaxhighlight lang="rust">extern crate num; // 0.2.0
use num::Zero;
use std::ops::{Add, Mul};
Line 2,090:
let output: f64 = horner(&v, 3.0);
println!("result: {}", output);
}</langsyntaxhighlight>
 
=={{header|Sather}}==
<langsyntaxhighlight lang="sather">class MAIN is
action(s, e, x:FLT):FLT is
Line 2,107:
#OUT + horner(|-19.0, 7.0, -4.0, 6.0|, 3.0) + "\n";
end;
end;</langsyntaxhighlight>
 
=={{header|Scala}}==
<langsyntaxhighlight lang="scala">def horner(coeffs:List[Double], x:Double)=
coeffs.reverse.foldLeft(0.0){(a,c)=> a*x+c}
</syntaxhighlight>
</lang>
<langsyntaxhighlight lang="scala">val coeffs=List(-19.0, 7.0, -4.0, 6.0)
println(horner(coeffs, 3))
-> 128.0
</syntaxhighlight>
</lang>
 
=={{header|Scheme}}==
{{Works with|Scheme|R<math>^5</math>RS}}
<langsyntaxhighlight lang="scheme">(define (horner lst x)
(define (*horner lst x acc)
(if (null? lst)
Line 2,128:
 
(display (horner (list -19 7 -4 6) 3))
(newline)</langsyntaxhighlight>
Output:
<syntaxhighlight lang="text">128</langsyntaxhighlight>
 
=={{header|Seed7}}==
<langsyntaxhighlight lang="seed7">$ include "seed7_05.s7i";
include "float.s7i";
 
Line 2,154:
begin
writeln(horner(coeffs, 3.0) digits 1);
end func;</langsyntaxhighlight>
 
Output:
Line 2,163:
=={{header|Sidef}}==
Functional:
<langsyntaxhighlight lang="ruby">func horner(coeff, x) {
coeff.reverse.reduce { |a,b| a*x + b };
}
 
say horner([-19, 7, -4, 6], 3); # => 128</langsyntaxhighlight>
 
Recursive:
<langsyntaxhighlight lang="ruby">func horner(coeff, x) {
coeff.len > 0
&& (coeff[0] + x*horner(coeff.ft(1), x));
}
 
say horner([-19, 7, -4, 6], 3); # => 128</langsyntaxhighlight>
 
=={{header|Smalltalk}}==
{{works with|GNU Smalltalk}}
<langsyntaxhighlight lang="smalltalk">OrderedCollection extend [
horner: aValue [
^ self reverse inject: 0 into: [:acc :c | acc * aValue + c].
Line 2,185:
].
 
(#(-19 7 -4 6) asOrderedCollection horner: 3) displayNl.</langsyntaxhighlight>
 
=={{header|Standard ML}}==
<langsyntaxhighlight lang="sml">(* Assuming real type for coefficients and x *)
fun horner coeffList x = foldr (fn (a, b) => a + b * x) (0.0) coeffList</langsyntaxhighlight>
 
=={{header|Swift}}==
<langsyntaxhighlight lang="swift">func horner(coefs: [Double], x: Double) -> Double {
return reduce(lazy(coefs).reverse(), 0) { $0 * x + $1 }
}
 
println(horner([-19, 7, -4, 6], 3))</langsyntaxhighlight>
{{out}}
<pre>128.0</pre>
 
=={{header|Tcl}}==
<langsyntaxhighlight lang="tcl">package require Tcl 8.5
proc horner {coeffs x} {
set y 0
Line 2,208:
}
return $y
}</langsyntaxhighlight>
Demonstrating:
<langsyntaxhighlight lang="tcl">puts [horner {-19 7 -4 6} 3]</langsyntaxhighlight>
Output:
<pre>128</pre>
Line 2,218:
Note: this function, "Horner", gets its coefficients as a ParamArray which has no specified length. This array collect all arguments after the first one(s). This means you must specify x first, then the coefficients.
 
<syntaxhighlight lang="vba">
<lang VBA>
Public Function Horner(x, ParamArray coeff())
Dim result As Double
Line 2,231:
Horner = result
End Function
</syntaxhighlight>
</lang>
 
Output:
Line 2,240:
 
=={{header|VBScript}}==
<syntaxhighlight lang="vb">
<lang vb>
Function horners_rule(coefficients,x)
accumulator = 0
Line 2,250:
 
WScript.StdOut.WriteLine horners_rule(Array(-19,7,-4,6),3)
</syntaxhighlight>
</lang>
 
{{Out}}
Line 2,257:
=={{header|Visual Basic .NET}}==
{{trans|C#}}
<langsyntaxhighlight lang="vbnet">Module Module1
 
Function Horner(coefficients As Double(), variable As Double) As Double
Line 2,267:
End Sub
 
End Module</langsyntaxhighlight>
{{out}}
<pre>128</pre>
Line 2,273:
=={{header|Visual FoxPro}}==
===Coefficients in ascending order.===
<langsyntaxhighlight lang="vfp">
LOCAL x As Double
LOCAL ARRAY aCoeffs[1]
Line 2,293:
RETURN s
ENDFUNC
</syntaxhighlight>
</lang>
 
===Coefficients in descending order.===
<langsyntaxhighlight lang="vfp">
LOCAL x As Double
LOCAL ARRAY aCoeffs[1]
Line 2,315:
RETURN s
ENDFUNC
</syntaxhighlight>
</lang>
 
=={{header|Vlang}}==
<langsyntaxhighlight lang="vlang">fn horner(x i64, c []i64) i64 {
mut acc := i64(0)
for i := c.len - 1; i >= 0; i-- {
Line 2,328:
fn main() {
println(horner(3, [i64(-19), 7, -4, 6]))
}</langsyntaxhighlight>
 
{{out}}
Line 2,336:
 
=={{header|Wren}}==
<langsyntaxhighlight lang="ecmascript">var horner = Fn.new { |x, c|
var count = c.count
if (count == 0) return 0
Line 2,342:
}
 
System.print(horner.call(3, [-19, 7, -4, 6]))</langsyntaxhighlight>
 
{{out}}
Line 2,350:
 
=={{header|XPL0}}==
<langsyntaxhighlight XPL0lang="xpl0">code IntOut=11;
 
func Horner(X, N, C); \Return value of polynomial in X
Line 2,361:
];
 
IntOut(0, Horner(3, 4, [-19, 7, -4, 6]));</langsyntaxhighlight>
 
Output:
Line 2,369:
 
=={{header|zkl}}==
<langsyntaxhighlight lang="zkl">fcn horner(coeffs,x)
{ coeffs.reverse().reduce('wrap(a,coeff){ a*x + coeff },0.0) }</langsyntaxhighlight>
{{out}}
<pre>
10,327

edits