Forward difference

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

Provide code that produces a list of numbers which is the n-th order forward difference, given a non-negative integer (specifying the order) and a list of numbers. The first-order forward difference of a list of numbers (A) is a new list (B) where Bn = An+1 - An. List B should have one less element as a result. The second-order forward difference of A will be the same as the first-order forward difference of B. That new list will have two fewer elements than A and one less than B. The goal of this task is to repeat this process up to the desired order.

For a more formal description, see the related Mathworld article.

Ada

<lang ada>with Ada.Text_Io; with Ada.Float_Text_Io; use Ada.Float_Text_Io; with Ada.containers.Vectors;

procedure Forward_Difference is

  package Flt_Vect is new Ada.Containers.Vectors(Positive, Float);
  use Flt_Vect;
  procedure Print(Item : Vector) is
  begin
     if not Item.Is_Empty then
        Ada.Text_IO.Put('[');
        for I in 1..Item.Length loop
           Put(Item => Item.Element(Positive(I)), Fore => 1, Aft => 1, Exp => 0);
            if Positive(I) < Positive(Item.Length) then
              Ada.Text_Io.Put(", ");
           end if;
        end loop;
        Ada.Text_Io.Put_line("]");
     else
        Ada.Text_IO.Put_Line("Empty List");
     end if;
     
  end Print;
  
 function Diff(Item : Vector; Num_Passes : Natural) return Vector is
     A : Vector := Item;
     B : Vector := Empty_Vector;
  begin
     if not A.Is_Empty then
        for I in 1..Num_Passes loop
           for I in 1..Natural(A.Length) - 1 loop
                 B.Append(A.Element(I + 1) - A.Element(I));
           end loop;
           Move(Target => A, Source => B);
        end loop;
     end if;
     return A;
  end Diff;
  Values : array(1..10) of Float := (90.0, 47.0, 58.0, 29.0, 22.0, 32.0, 55.0, 5.0, 55.0, 73.0);
  A : Vector;

begin

  for I in Values'range loop
     A.Append(Values(I)); -- Fill the vector
  end loop;
  Print(Diff(A, 1));
  Print(Diff(A, 2));
  Print(Diff(A, 9));
  Print(Diff(A, 10));
  print(Diff(A, 0));

end Forward_Difference;</lang> Output:

[-43.0, 11.0, -29.0, -7.0, 10.0, 23.0, -50.0, 50.0, 18.0]
[54.0, -40.0, 22.0, 17.0, 13.0, -73.0, 100.0, -32.0]
[-2921.0]
Empty List
[90.0, 47.0, 58.0, 29.0, 22.0, 32.0, 55.0, 5.0, 55.0, 73.0]

ALGOL 68

main:(
  MODE LISTREAL = [1:0]REAL;

  OP - = (LISTREAL a,b)LISTREAL: (
    [UPB a]REAL out;
    FOR i TO UPB out DO out[i]:=a[i]-b[i] OD;
    out
  );

  FORMAT real fmt=$zzz-d.d$;
  FORMAT repeat fmt = $n(UPB s-1)(f(real fmt)",")f(real fmt)$;
  FORMAT list fmt = $"("f(UPB s=1|real fmt|repeat fmt)")"$;

  FLEX [1:0] REAL s := (90, 47, 58, 29, 22, 32, 55, 5, 55, 73);

  printf((list fmt,s,$";"l$));
  TO UPB s-1 DO
    s := s[2:] - s[:UPB s-1];
    printf((list fmt,s,$";"l$))
  OD
)

Output:

(   90.0,   47.0,   58.0,   29.0,   22.0,   32.0,   55.0,    5.0,   55.0,   73.0);
(  -43.0,   11.0,  -29.0,   -7.0,   10.0,   23.0,  -50.0,   50.0,   18.0);
(   54.0,  -40.0,   22.0,   17.0,   13.0,  -73.0,  100.0,  -32.0);
(  -94.0,   62.0,   -5.0,   -4.0,  -86.0,  173.0, -132.0);
(  156.0,  -67.0,    1.0,  -82.0,  259.0, -305.0);
( -223.0,   68.0,  -83.0,  341.0, -564.0);
(  291.0, -151.0,  424.0, -905.0);
( -442.0,  575.0,-1329.0);
( 1017.0,-1904.0);
(-2921.0);

APL

Works with: Dyalog APL
Translation of: J
      list ←  90 47 58 29 22 32 55 5 55 73
      
      fd   ←  {⍺=0:⍵⋄(⍺-1)∇(1↓⍵)-(¯1↓⍵)} 
      
      1 fd list 
¯43 11 ¯29 ¯7 10 23 ¯50 50 18
      
      2 fd list 
54 ¯40 22 17 13 ¯73 100 ¯32

C++

Works with: g++ version 4.1.2 20061115 (prerelease) (SUSE Linux)

This code uses a separate function to do a first-order forward difference, which is then called several times for calculating n-th order forward difference. No error checking is implemented.

<lang cpp>#include <vector>

  1. include <iterator>
  2. include <algorithm>

// calculate first order forward difference // requires: // * InputIterator is an input iterator // * OutputIterator is an output iterator // * The value type of InputIterator is copy-constructible and assignable // * The value type of InputIterator supports operator - // * The result type of operator- is assignable to the value_type of OutputIterator // returns: The iterator following the output sequence template<typename InputIterator, typename OutputIterator>

OutputIterator forward_difference(InputIterator first, InputIterator last,
                                  OutputIterator dest)

{

 // special case: for empty sequence, do nothing
 if (first == last)
   return dest;
 typedef typename std::iterator_traits<InputIterator>::value_type value_type;
 value_type temp = *first++;
 while (first != last)
 {
   value_type temp2 = *first++;
   *dest++ = temp2 - temp;
   temp = temp2;
 }
 return dest;

}

// calculate n-th order forward difference. // requires: // * InputIterator is an input iterator // * OutputIterator is an output iterator // * The value type of InputIterator is copy-constructible and assignable // * The value type of InputIterator supports operator - // * The result type of operator- is assignable to the value_type of InputIterator // * The result type of operator- is assignable to the value_type of OutputIterator // * order >= 0 // returns: The iterator following the output sequence template<typename InputIterator, typename OutputIterator>

OutputIterator nth_forward_difference(int order,
                                      InputIterator first, InputIterator last,
                                      OutputIterator dest)

{

 // special case: If order == 0, just copy input to output
 if (order == 0)
   return std::copy(first, last, dest);
 // second special case: If order == 1, just forward to the first-order function
 if (order == 1)
   return forward_difference(first, last, dest);
 // intermediate results are stored in a vector
 typedef typename std::iterator_traits<InputIterator>::value_type value_type;
 std::vector<value_type> temp_storage;
 // fill the vector with the result of the first order forward difference
 forward_difference(first, last, std::back_inserter(temp_storage));
 // the next n-2 iterations work directly on the vector
 typename std::vector<value_type>::iterator begin = temp_storage.begin(),
                                            end = temp_storage.end();
 for (int i = 1; i < order-1; ++i)
   end = forward_difference(begin, end, begin);
 // the final iteration writes directly to the output iterator
 return forward_difference(begin, end, dest);

}

// example usage code

  1. include <iostream>

int main() {

 double array[10] = { 90.0, 47.0, 58.0, 29.0, 22.0, 32.0, 55.0, 5.0, 55.0, 73.0 };
 // this stores the results in the vector dest
 std::vector<double> dest;
 nth_forward_difference(1, array, array+10, std::back_inserter(dest));
 // outut dest
 std::copy(dest.begin(), dest.end(), std::ostream_iterator<double>(std::cout, " "));
 std::cout << std::endl;
 // however, the results can also be output as they are calculated
 nth_forward_difference(2, array, array+10, std::ostream_iterator<double>(std::cout, " "));
 std::cout << std::endl;
 nth_forward_difference(9, array, array+10, std::ostream_iterator<double>(std::cout, " "));
 std::cout << std::endl;
 nth_forward_difference(10, array, array+10, std::ostream_iterator<double>(std::cout, " "));
 std::cout << std::endl;
 nth_forward_difference(0, array, array+10, std::ostream_iterator<double>(std::cout, " "));
 std::cout << std::endl;
 // finally, the results can also be written into the original array
 // (which of course destroys the original content)
 double* end = nth_forward_difference(3, array, array+10, array);
 for (double* p = array; p < end; ++p)
   std::cout << *p << " ";
 std::cout << std::endl;
 return 0;

}</lang>

This gives the following output:

-43 11 -29 -7 10 23 -50 50 18 
54 -40 22 17 13 -73 100 -32 
-2921 

90 47 58 29 22 32 55 5 55 73 
-94 62 -5 -4 -86 173 -132 

Note the empty line indicating the empty sequence for order 10.

D

<lang d>module fdiff ; import std.stdio ;

T[] fdiff(T = int)(T[] a, int level) {

   T[] s ;
   if(level < 0 || level >= a.length)
       return s ;
   s = a.dup ;
   for(int i = 0 ; i < level ;i++)
       for(int j = 0 ; j < s.length  - i - 1 ; j++)
           s[j] = s[j+1] - s[j] ;
   s.length = s.length - level ;   
   return s ;

}

void main() {

   auto a = [90.5, 47, 58, 29, 22, 32, 55, 5, 55, 73.5];
   for(int i = 0 ; i< a.length + 1; i++)
       writefln(a.fdiff(i));

}</lang> Sampe output:

D:\00MY\dmd>fdiff
[90.5 47 58 29 22 32 55 5 55 73.5]
[-43.5 11 -29 -7 10 23 -50 50 18.5]
[54.5 -40 22 17 13 -73 100 -31.5]
[-94.5 62 -5 -4 -86 173 -131.5]
[156.5 -67 1 -82 259 -304.5]
[-223.5 68 -83 341 -563.5]
[291.5 -151 424 -904.5]
[-442.5 575 -1328.5]
[1017.5 -1903.5]
[-2921]
[]

Common Lisp

<lang lisp>(defun forward-difference (list)

 (mapcar #'- (rest list) list))

(defun nth-forward-difference (list n)

 (setf list (copy-list list))
 (loop repeat n do (map-into list #'- (rest list) list))
 (subseq list 0 (- (length list) n)))</lang>

E

pragma.enable("accumulator")
/** Single step. */
def forwardDifference(seq :List) {
    return accum [] for i in 0..(seq.size() - 2) {
        _.with(seq[i + 1] - seq[i])
    }
}

/** Iterative implementation of the goal. */
def nthForwardDifference1(var seq :List, n :(int >= 0)) {
    for _ in 1..n { seq := forwardDifference(seq) }
    return seq
}

/** Imperative implementation of the goal. */
def nthForwardDifference2(seq :List, n :(int >= 0)) {
  def buf := seq.diverge()
  def finalSize := seq.size() - n
  for lim in (finalSize..!seq.size()).descending() {
    for i in 0..!lim {
      buf[i] := buf[i + 1] - buf[i]
    }
  }
  return buf.run(0, finalSize)
}
? def sampleData := [90, 47, 58, 29, 22, 32, 55, 5, 55, 73]
> for n in 0..10 {
>   def r1 := nthForwardDifference1(sampleData, n)
>   require(r1 == nthForwardDifference2(sampleData, n))
>   println(r1)
> }

Fortran

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

  CONTAINS
 
  SUBROUTINE Fdiff(a, n)
    INTEGER, INTENT(IN) :: a(:), n
    INTEGER :: b(SIZE(a))  
    INTEGER :: i, j, arraysize
  
    b = a
    arraysize = SIZE(b)
    DO i = arraysize-1, arraysize-n, -1
      DO j = 1, i
        b(j) = b(j+1) - b(j)
      END DO
    END DO
    WRITE (*,*) b(1:arraysize-n)
  END SUBROUTINE Fdiff
END MODULE DIFFERENCE

PROGRAM TEST

  USE DIFFERENCE
  IMPLICIT NONE

  INTEGER :: array(10) = (/ 90, 47, 58, 29, 22, 32, 55, 5, 55, 73 /)
  INTEGER :: i
  
  DO i = 1, 9
    CALL Fdiff(array, i)
  END DO

  END PROGRAM TEST

Output

         -43          11         -29          -7          10          23         -50          50          18
          54         -40          22          17          13         -73         100         -32
         -94          62          -5          -4         -86         173        -132
         156         -67           1         -82         259        -305
        -223          68         -83         341        -564
         291        -151         424        -905
        -442         575       -1329
        1017       -1904
       -2921

Haskell

forwardDifference xs = zipWith (-) (tail xs) xs

nthForwardDifference xs n = iterate forwardDifference xs !! n
> take 10 (iterate forwardDifference [90, 47, 58, 29, 22, 32, 55, 5, 55, 73])
[[90,47,58,29,22,32,55,5,55,73],
 [-43,11,-29,-7,10,23,-50,50,18],
 [54,-40,22,17,13,-73,100,-32],
 [-94,62,-5,-4,-86,173,-132],
 [156,-67,1,-82,259,-305],
 [-223,68,-83,341,-564],
 [291,-151,424,-905],
 [-442,575,-1329],
 [1017,-1904],
 [-2921]]

IDL

Standard IDL library function TS_diff(X,k,[/double]):

print,(x = randomu(seed,8)*100)
     15.1473      58.0953      82.7465      16.8637      97.7182      59.7856      17.7699      74.9154
print,ts_diff(x,1)
    -42.9479     -24.6513      65.8828     -80.8545      37.9326      42.0157     -57.1455     0.000000
print,ts_diff(x,2)
    -18.2967     -90.5341      146.737     -118.787     -4.08316      99.1613     0.000000     0.000000
print,ts_diff(x,3)
     72.2374     -237.271      265.524     -114.704     -103.244     0.000000     0.000000     0.000000

J

Of the many ways to code this in J, a particularly concise solution is:

fd=: 2&(-~/\)

Alternatively, to reduce the number of J primitives (rather than characters), use:

fd=: (}.-}:)^:

(which is also elegant, because the open-ended power conjunction reads like "to the power of anything").

For example:

   list =: 90 47 58 29 22 32 55 5 55 73   NB.  Some numbers

   1 fd list
_43 11 _29 _7 10 23 _50 50 18
   
   2 fd list
54 _40 22 17 13 _73 100 _32

J is array oriented, so you can even ask for more than one forward difference at a time (i.e. N can be a list, instead of a single number):

   1 2 3 fd list                          NB.  First, second, and third forward differences (simultaneously)
43 _11 29  7 _10  _23  50 _50 _18
54 _40 22 17  13  _73 100 _32   0
94 _62  5  4  86 _173 132   0   0
   
   a: fd list                             NB.  All forward differences
  90    47   58   29  22   32  55   5  55 73
  43   _11   29    7 _10  _23  50 _50 _18  0
  54   _40   22   17  13  _73 100 _32   0  0
  94   _62    5    4  86 _173 132   0   0  0
 156   _67    1  _82 259 _305   0   0   0  0
 223   _68   83 _341 564    0   0   0   0  0
 291  _151  424 _905   0    0   0   0   0  0
 442  _575 1329    0   0    0   0   0   0  0
1017 _1904    0    0   0    0   0   0   0  0
2921     0    0    0   0    0   0   0   0  0
   0     0    0    0   0    0   0   0   0  0

Java

Works with: Java version 1.5+

<lang java>import java.util.Arrays; public class FD {

   public static void main(String args[]) {
       double[] a = {90, 47, 58, 29, 22, 32, 55, 5, 55, 73};
       System.out.println(Arrays.toString(dif(a, 1)));
       System.out.println(Arrays.toString(dif(a, 2)));
       System.out.println(Arrays.toString(dif(a, 9)));
       System.out.println(Arrays.toString(dif(a, 10)));      //let's test
       System.out.println(Arrays.toString(dif(a, 11)));
       System.out.println(Arrays.toString(dif(a, -1)));
       System.out.println(Arrays.toString(dif(a, 0)));
   }
   public static double[] dif(double[] a, int n) {
       if (n < 0)
           return null; // if the programmer was dumb
       for (int i = 0; i < n && a.length > 0; i++) {
           double[] b = new double[a.length - 1];
           for (int j = 0; j < b.length; j++){
               b[j] = a[j+1] - a[j];
           }
           a = b; //"recurse"
       }
       return a;
   }

}</lang>

Output:

[-43.0, 11.0, -29.0, -7.0, 10.0, 23.0, -50.0, 50.0, 18.0]
[54.0, -40.0, 22.0, 17.0, 13.0, -73.0, 100.0, -32.0]
[-2921.0]
[]
[]
null
[90.0, 47.0, 58.0, 29.0, 22.0, 32.0, 55.0, 5.0, 55.0, 73.0]

to fwd.diff :l
  if empty? :l [output []]
  if empty? bf :l [output []]
  output fput (first bf :l)-(first :l) fwd.diff bf :l
end
to nth.fwd.diff :n :l
  if :n = 0 [output :l]
  output nth.fwd.diff :n-1 fwd.diff :l
end
show nth.fwd.diff 9 [90 47 58 29 22 32 55 5 55 73]
[-2921]

Nial

Define forward difference for order 1

fd is - [rest, front]

forward difference of 4th order

b := 90 47 58 29 22 32 55 5 55 73 
4 fold fd b
= 156 -67 1 -82 259 -305

OCaml

<lang ocaml>let rec forward_difference = function

   a :: (b :: _ as xs) ->
     b - a :: forward_difference xs
 | _ ->
     []

let rec nth_forward_difference n xs =

 if n = 0 then
   xs
 else
   nth_forward_difference (pred n) (forward_difference xs)</lang>

Output:

# nth_forward_difference 9 [90; 47; 58; 29; 22; 32; 55; 5; 55; 73];;
- : int list = [-2921]

Perl

<lang perl>sub dif {

 my @s = @_;
 map { $s[$_+1] - $s[$_] } 0 .. $#s-1

}

sub difn {

 my ($n, @s) = @_;
 @s = dif @s foreach 1..$n;
 @s

}</lang>

Pop11

define forward_difference(l);
    lvars res = [], prev, el;
    if l = [] then
        return([]);
    endif;
    front(l) -> prev;
    for el in back(l) do
        cons(el - prev, res) -> res;
        el -> prev;
    endfor;
    rev(res);
enddefine;

define nth_difference(l, n);
    lvars res = l, i;
    for i from 1 to n do
        forward_difference(res) -> res;
    endfor;
    res;
enddefine;

Python

<lang python>>>> dif = lambda s: [x-s[i] for i,x in enumerate(s[1:])] >>> # or, dif = lambda s: [x-y for x,y in zip(s[1:],s[:-1])] >>> difn = lambda s, n: difn(dif(s), n-1) if n else s

>>> s = [90, 47, 58, 29, 22, 32, 55, 5, 55, 73] >>> difn(s, 0) [90, 47, 58, 29, 22, 32, 55, 5, 55, 73] >>> difn(s, 1) [-43, 11, -29, -7, 10, 23, -50, 50, 18] >>> difn(s, 2) [54, -40, 22, 17, 13, -73, 100, -32]

>>> from pprint import pprint >>> pprint( [difn(s, i) for i in xrange(10)] ) [[90, 47, 58, 29, 22, 32, 55, 5, 55, 73],

[-43, 11, -29, -7, 10, 23, -50, 50, 18],
[54, -40, 22, 17, 13, -73, 100, -32],
[-94, 62, -5, -4, -86, 173, -132],
[156, -67, 1, -82, 259, -305],
[-223, 68, -83, 341, -564],
[291, -151, 424, -905],
[-442, 575, -1329],
[1017, -1904],
[-2921]]</lang>

Ruby

<lang ruby>def dif(s)

 s.enum_cons(2).collect { |x, y| y - x }

end

def difn(s, n)

 (1..n).inject(s) { |s, | dif(s) }

end</lang>

Scheme

<lang scheme>(define (forward-diff lst)

 (if (or (null? lst) (null? (cdr lst)))
     '()
     (cons (- (cadr lst) (car lst))
           (forward-diff (cdr lst)))))

(define (nth-forward-diff n xs)

 (if (= n 0)
     xs
     (nth-forward-diff (- n 1)
                       (forward-diff xs))))</lang>

Output:

> (nth-forward-diff 9 '(90 47 58 29 22 32 55 5 55 73))
(-2921)

Smalltalk

This version runs on GNU Smalltalk. Other implementations might lack some of the utility methods we use:

Array extend [
    difference [
        ^self allButFirst with: self allButLast collect: [ :a :b | a - b ]
    ]

    nthOrderDifference: n [
        ^(1 to: n) inject: self into: [ :old :unused | old difference ]
    ]
]

s := #(90 47 58 29 22 32 55 5 55 73)
1 to: s size - 1 do: [ :i |
    (s nthOrderDifference: i) printNl ]